Xmonad/Config archive/vvv's xmonad.hs

From HaskellWiki
< Xmonad‎ | Config archive
Revision as of 21:29, 13 November 2007 by Vvv (talk | contribs) (updated - I use Config.CustomKeys now)
Jump to navigation Jump to search
The printable version is no longer supported and may have rendering errors. Please update your browser bookmarks and please use the default browser print function instead.
{-# OPTIONS_GHC -Wall #-}
import XMonad
import XMonad.Layouts
import XMonad.Operations
import qualified XMonad.StackSet as W
import Graphics.X11.Xlib

-- XMonadContrib
import XMonad.Actions.CycleWS
import XMonad.Actions.DynamicWorkspaces
import XMonad.Actions.Submap
import XMonad.Config.CustomKeys
import XMonad.Hooks.DynamicLog
import XMonad.Layout.NoBorders
import XMonad.Prompt
import XMonad.Prompt.Man
import XMonad.Prompt.Shell
import XMonad.Prompt.Ssh

import Data.Bits ((.|.))
import qualified Data.Map as M
import Data.Ratio ((%))

main :: IO ()
main = xmonad defaultConfig
       { workspaces         = ["1:term", "2:emacs", "3:web"]
       , defaultGaps        = [(0,15,0,0)]
       , layoutHook         = tiled ||| Mirror tiled ||| noBorders Full
       , focusedBorderColor = "#00ff00"
       , modMask            = mod4Mask
       , keys               = customKeys delKeys insKeys
       , logHook            = dynamicLog
       }
    where
      tiled = Tall 1 (2%100) (755%1024) -- Tall <nmaster> <delta> <ratio>

delKeys :: XConfig l -> [(KeyMask, KeySym)]
delKeys XConfig {modMask = modm} =
    [ (modm .|. shiftMask, xK_Return)
    , (modm,               xK_p)
    , (modm .|. shiftMask, xK_p)
    , (modm .|. shiftMask, xK_c)
    , (modm,               xK_b)
    ]
    ++
    [ (modm .|. m, k)
      | (m, k) <- zip [0, shiftMask] ([xK_1..xK_9] ++ [xK_w, xK_e, xK_r])
    ]

insKeys :: XConfig l -> [((KeyMask, KeySym), X ())]
insKeys conf@(XConfig {modMask = modm}) =
    [ ((mod1Mask, xK_F2    ), spawn $ terminal conf) -- mod1-f2 %! Run a terminal emulator
    , ((modm,      xK_Delete), kill) -- %! Close the focused window
    , ((mod1Mask, xK_Down  ), spawn "amixer set Master 1-") -- mod1-down %! Decrease audio volume
    , ((mod1Mask, xK_Up    ), spawn "amixer set Master 1+") -- mod1-up   %! Increase audio volume
    , ((modm .|. controlMask, xK_F11), spawn "xscreensaver-command -lock") -- %! Lock the screen
    , ((modm,      xK_s   ), modifyGap (\i n -> let x = (defaultGaps conf ++ repeat (0,0,0,0)) !! i in if n == x then (0,0,0,0) else x)) -- %! Toggle the status bar gap
    ]
    ++
    [ ((mod1Mask, xK_F1), manPrompt   defaultXPConfig) -- mod1-f1 %! Query for manual page to be displayed
    , ((mod1Mask, xK_F3), shellPrompt defaultXPConfig) -- mod1-f3 %! Query for command line to execute
    , ((mod1Mask, xK_F4), sshPrompt   defaultXPConfig) -- mod1-f4 %! Query for host to connect to with SSH

    , (-- mod-i submap
       (modm, xK_i), submap . M.fromList $
       [ ((m, k), f)
         | m <- [0, modm]
         , (k, f) <- [ (xK_i, toggleWS) -- mod-i i, mod-i mod-i %! Toggle to the workspace displayed previously
                     , (xK_p, prevWS  ) -- mod-i p, mod-i mod-p %! Switch to the previous workspace
                     , (xK_n, nextWS  ) -- mod-i n, mod-i mod-n %! Switch to the next workspace
                     ]
       ]
       ++
       [ ((0,         xK_apostrophe), selectWorkspace defaultXPConfig) -- mod-i ' %! Prompt for a workspace number/name to switch to
       , ((shiftMask, xK_a         ), renameWorkspace defaultXPConfig) -- mod-i A %! Allow the user to enter a name for the current workspace
       , ((0,         xK_BackSpace ), removeWorkspace) -- mod-i backspace %! Destroy current workspace
       ]
       ++
       [ ((m, k), withNthWorkspace f i)
         | (i, k) <- zip [0..] [xK_1..xK_9]
         , (f, m) <- [ (W.greedyView, 0   ) -- mod-i [1..9] %! Switch to workspace 1..9
                     , (W.greedyView, modm) -- mod-i mod-[1..9] %! Switch to workspace 1..9
                     , (W.shift, shiftMask) -- mod-i shift-[1..9] %! Move client to workspace 1..9
                     ]
       ]
      )
    ]