Xmonad/Config archive/loupgaroublonds xmonad.hs

From HaskellWiki
Jump to navigation Jump to search

This is my configuration that works under gnome. It's not too sophisticated, although there's a certain amount of verbosity i could get rid of if i wanted to. Most of it's there, though because of some fun plans i have for Prompt. If only prompt would work on 64-bit....

Highlights include:

Replaces Full with Tabs. The philosophy is that you should always know what's on a workspace when you look at it. Nothing should be hiding behind something else.

Alternate Mod Key so not to interfere with other programs.

For each application hotkey, there is also one that will invoke it on what ever is on the clipboard. There is also a bit of hackery for the terminal, so that it doesn't close when the app is done running. This is good for reviewing the output.

EZConfig for easier configuration of key presses. It's not just easier, but also cleaner and easier on the eyes.


Toggle Full screen mode for watching movies. Note that the border i use is black, for the same reason. To be fair, i didn't like the flicker effect from NoBorders the last time i tried it.

In the future, i want to hook up compositing to fade the non active windows. Then i can do away with borders completely.

The usual EWMH and Dock hooks for all your Gnome Needs.

Since firefox can be on more than one workspace, although they always start in workspace 'web', manageOne is used to make sure transient windows show up where they belong before firefox gets to them.

That should be the big stuff. Enjoy.

Description
{-# OPTIONS_GHC -fglasgow-exts #-}

import XMonad
import XMonad.Operations

import XMonad.Actions.Commands
import XMonad.Actions.CycleWS
import XMonad.Actions.DeManage

import XMonad.Hooks.EwmhDesktops
import XMonad.Hooks.ManageDocks
import XMonad.Hooks.ManageHelpers


import qualified XMonad.Util.EZConfig as EZ
import XMonad.Util.Run
import XMonad.Util.WindowProperties
import XMonad.Util.XSelection

import qualified Data.Map as M

import qualified XMonad.Actions.DwmPromote as DwmP
import qualified XMonad.Actions.FlexibleResize as Flex
import qualified XMonad.Actions.SinkAll as SinkAll

import qualified XMonad.Layout.PerWorkspace as PW
import qualified XMonad.Layout.Tabbed as Tab

import qualified XMonad.StackSet as W

import Data.Monoid
import Data.Maybe
import System.IO
import System.Exit

main = do
  xmonad $ _config

_config = defaultConfig
          { borderWidth        = 2
          , terminal           = terminalCmd
          , normalBorderColor  = _normalBorderColor
          , focusedBorderColor = _focusedBorderColor
          , workspaces         = ["werk", "web", "praten", "muziek"
                                 , "bier", "zes", "zeven", "acht"
                                 , "negen", "tien"]
          , layoutHook = _layout
          , keys = _keys
          , modMask = mod4Mask
          , logHook = _logHook
          , manageHook = _manageHook }


_normalBorderColor :: String
_normalBorderColor = "#EFEFEF"

_focusedBorderColor :: String
_focusedBorderColor= "#000000"

-- Applications
terminalCmd :: String
terminalCmd = "gnome-terminal"

runTerminal :: X ()
runTerminal = spawn terminalCmd

saveSession :: String -> String
saveSession cmd = "bash -c '" ++ cmd ++ "; bash'"
pasteTerminal :: X ()
pasteTerminal = modifySelectionAndUnsafePromptSelection saveSession $ terminalCmd ++ " -x "

browserCmd :: String
browserCmd = "firefox"

runBrowser :: X ()
runBrowser = spawn browserCmd

pasteBrowser :: X ()
pasteBrowser = safePromptSelection browserCmd

cmdLineCmd :: String
cmdLineCmd = "gmrun"

runCmdLine :: X ()
runCmdLine = spawn cmdLineCmd

fileManagerCmd :: String
fileManagerCmd = "nautilus"

runFileManager :: X ()
runFileManager = spawn fileManagerCmd

musicPlayerCmd :: String
musicPlayerCmd = "exaile"

runMusicPlayer :: X ()
runMusicPlayer = spawn musicPlayerCmd

pasteMusicPlayer :: X ()
pasteMusicPlayer = promptSelection musicPlayerCmd


-- Keys
_keys :: XConfig Layout -> M.Map (KeyMask, KeySym) (X())
_keys = \conf -> EZ.mkKeymap conf $(_emacsKeys conf)

_emacsKeys :: XConfig Layout -> [(String, X())]
_emacsKeys  = \conf ->
              [ -- Applications
                ("M-t", runTerminal)
              , ("M-v M-t", pasteTerminal)
              , ("M-i", runBrowser)
              , ("M-v M-i", pasteBrowser)
              , ("M-p", runCmdLine)
              , ("M-e", runMusicPlayer)
              , ("M-h", runFileManager)

              -- Layouts
              , ("M-n", refresh)
              , ("M-S-<Space>", setLayout $ XMonad.layoutHook conf)
              , ("M-<Space>", sendMessage NextLayout)
              , ("M-<Tab>", windows W.focusDown)
              , ("M-j", windows W.focusDown)
              , ("M-k", windows W.focusUp)
              , ("M-<Return>", windows W.focusMaster)
              , ("M-S-<Return>",  DwmP.dwmpromote)
              , ("M-S-j", windows W.swapDown)
              , ("M-S-k", windows W.swapUp)
              , ("M-g", sendMessage Shrink)
              , ("M-l", sendMessage Expand)
              , ("M-r", withFocused $ windows . W.sink)
              , ("M-,", sendMessage (IncMasterN 1))
              , ("M-.", sendMessage (IncMasterN (-1)))
              -- Toggle full screen
              , ("M-<F12>", sendMessage ToggleStruts >> refresh)

              -- Windows
              , ("M-c", kill)             -- window
              , ("M-S-c", SinkAll.withAll killWindow) ] -- window
              ++
              [ ("M-S-" ++ [num], windows $ W.shift name)
                    | (name, num) <-
                        zip (XMonad.workspaces conf) (['1' .. '9'] ++ ['0'])]

              -- Workspaces
              ++
              [ ("M-" ++ [num], windows $ W.greedyView name)
                    | (name, num) <-
                        zip (XMonad.workspaces conf) (['1' .. '9'] ++ ['0'])]
              ++
              [ ("M-<Right>", moveTo Next NonEmptyWS)
              , ("M-<Left>", moveTo Prev NonEmptyWS)
              , ("M-S-<Right>", moveTo Next EmptyWS)
              , ("M-S-<Left>", moveTo Prev EmptyWS)
              -- Toggle between current and previous
              , ("M-`", toggleWS)

              -- xmonad
              , ("M1-q", broadcastMessage ReleaseResources
                           >> restart "xmonad" True)]


-- Mouse bindings

_mouseBindings :: XConfig Layout -> M.Map (ButtonMask, Button) (Window -> X ())
_mouseBindings (XConfig {XMonad.modMask = modMask}) = M.fromList $
    -- mod-button1, Set the window to floating mode and move by dragging
    [ ((modMask, button1), (\w -> focus w >> mouseMoveWindow w))
    -- mod-button2, Raise the window to the top of the stack
    , ((modMask, button2), (\w -> focus w >> windows W.swapMaster))
    -- mod-button3, Set the window to floating mode and resize by dragging
    , ((modMask, button3), (\w -> focus w >> Flex.mouseResizeWindow w))
    -- you may also bind events to the mouse scroll wheel (button4 and button5)
    ]

-- Layouts

_layout = ewmhDesktopsLayout $ avoidStruts $ PW.onWorkspaces ["web", "bier"] Tab.simpleTabbed
          (tiled ||| Mirror tiled ||| Tab.simpleTabbed)
    where
      tiled   = Tall nmaster delta ratio
      nmaster = 1
      ratio   = 1/2
      delta   = 3/100

-- ManageHooks
_manageHook = composeAll
              [ className =? "MPlayer"        --> doFloat
              , resource  =? "desktop_window" --> doIgnore
              , className =? "Kplayer"        --> doFloat
              , className =? "Exaile.py"      --> doF (W.shift "muziek")
              , className =? "Firstboot"      --> doFloat
              , className =? "CinePaint"      --> doFloat
              , title =? "Follow-up Curves (Br2HDR)" --> doFloat
              , className =? "Plasma"         --> doIgnore
              , className =? "Qt-subapplication" --> doIgnore
              , checkDock --> doIgnore ] 
              <+> composeOne
                      [ transience
                      , className =? "Firefox"    -?> doF (W.shift "web")
                      ]
              <+> manageDocks


-- LogHooks

_logHook = ewmhDesktopsLogHook