Xmonad/Config archive/Brent Yorgey's xmonad.hs
< Xmonad | Config archive
import XMonad
import qualified XMonad.StackSet as W
import XMonad.Operations
import Data.Bits ((.|.))
import Graphics.X11.Xlib
import qualified Data.Map as M
import XMonad.ManageHook
import XMonad.Hooks.DynamicLog
import XMonad.Layout.NoBorders
import XMonad.Layouts
import XMonad.Layout.Tabbed
import qualified XMonad.Actions.FlexibleManipulate as Flex
import XMonad.Layout.ResizableTile
import XMonad.Hooks.UrgencyHook
import XMonad.Layout.WindowNavigation
import XMonad.Layout.ToggleLayouts
import XMonad.Layout.Named
import XMonad.Actions.RotView
import XMonad.Actions.CycleWS
main = xmonad $ byorgeyConfig
byorgeyConfig = withUrgencyHook dzenUrgencyHook { args = ["-bg", "yellow", "-fg", "black"] } $
defaultConfig
{ borderWidth = 2
, terminal = "urxvt-custom"
, workspaces = ["1:web", "2:irc", "3:code", "4:code", "5:ref" ]
++ map show [6 .. 9 :: Int]
, defaultGaps = [(18,0,0,0)]
, modMask = mod4Mask
, normalBorderColor = "#dddddd"
, focusedBorderColor = "#0033ff"
, logHook = dynamicLogWithPP byorgeyPP
, mouseBindings = \(XConfig {modMask = modm}) -> M.fromList $
[ ((modm, button1), (\w -> focus w >> mouseMoveWindow w))
-- mod-button2 %! Raise the window to the top of the stack
, ((modm, button2), (\w -> focus w >> windows W.swapMaster))
-- mod-button3 %! Set the window to floating mode and resize by dragging
, ((modm, button3), (\w -> focus w >> Flex.mouseWindow Flex.linear w)) ]
, keys = \c -> mykeys c `M.union` keys defaultConfig c
, manageHook = manageHook defaultConfig <+> myManageHook
, layoutHook = configurableNavigation (navigateColor "#00aa00") $
toggleLayouts (noBorders Full) $
(smartBorders (tiled ||| Mirror tiled ||| tabbed shrinkText defaultTConf))
}
where
tiled = Named "RTall" $ ResizableTall 1 0.03 0.5 []
mykeys (XConfig {modMask = modm}) = M.fromList $
[ ((modm .|. shiftMask, xK_x ), spawn (terminal byorgeyConfig))
, ((modm .|. shiftMask, xK_a ), kill)
-- rotate workspaces
, ((modm .|. controlMask, xK_Right), rotView True)
, ((modm .|. controlMask, xK_Left), rotView False)
, ((modm, xK_w), sendMessage MirrorExpand)
, ((modm, xK_s), sendMessage MirrorShrink)
-- switch to previous workspace
, ((modm, xK_z), toggleWS)
-- lock the screen with xscreensaver
, ((modm .|. shiftMask, xK_l), spawn "xscreensaver-command -lock")
-- some programs to start with keybindings.
, ((modm .|. shiftMask, xK_f), spawn "firefox")
, ((modm .|. shiftMask, xK_n), spawn "gksudo network-admin")
, ((modm .|. shiftMask, xK_c), spawn "xchat")
, ((modm .|. shiftMask, xK_v), spawn "gnome-volume-control --class=Volume")
, ((modm .|. shiftMask, xK_t), spawn "xclock")
, ((modm .|. shiftMask .|. controlMask, xK_t), spawn "xclock -update 1")
-- window navigation keybindings.
, ((modm, xK_Right), sendMessage $ Go R)
, ((modm, xK_Left ), sendMessage $ Go L)
, ((modm, xK_Up ), sendMessage $ Go U)
, ((modm, xK_Down ), sendMessage $ Go D)
, ((modm .|. shiftMask, xK_Right), sendMessage $ Swap R)
, ((modm .|. shiftMask, xK_Left ), sendMessage $ Swap L)
, ((modm .|. shiftMask, xK_Up ), sendMessage $ Swap U)
, ((modm .|. shiftMask, xK_Down ), sendMessage $ Swap D)
-- toggle to fullscreen.
, ((modm .|. controlMask, xK_space), sendMessage ToggleLayout)
]
myManageHook :: ManageHook
myManageHook = composeAll [ className =? c --> doFloat | c <- myFloats ]
where myFloats = ["Volume", "XClock", "Network-admin"]
-- define a custom pretty-print mode for DynamicLog
byorgeyPP :: PP
byorgeyPP = defaultPP { ppHiddenNoWindows = \wsId -> if (':' `elem` wsId) then wsId ++ " " else ""
, ppHidden = (++"*")
, ppCurrent = dzenColor "black" "#a8a3f7" . (++"*")
, ppSep = " | "
, ppTitle = shorten 80
, ppOrder = reverse }