Difference between revisions of "Xmonad/Config archive/Brent Yorgey's darcs xmonad.hs"

From HaskellWiki
Jump to navigation Jump to search
(upload my newest config, with annotations)
Line 15: Line 15:
 
</pre>
 
</pre>
   
My current config file, which works with the latest development xmonad and xmonad-contrib:
+
My current config file, which works with the latest development xmonad and xmonad-contrib, annotated to show which extensions are being used where:
   
 
<haskell>
 
<haskell>
  +
import XMonad -- (0) core xmonad libraries
import XMonad
 
   
import qualified XMonad.StackSet as W
+
import qualified XMonad.StackSet as W -- (0a) window stack manipulation
  +
import qualified Data.Map as M -- (0b) map creation
import Graphics.X11.Xlib
 
   
  +
-- Hooks -----------------------------------------------------
import qualified Data.Map as M
 
   
import XMonad.Hooks.DynamicLog
+
import XMonad.Hooks.DynamicLog -- (1) for dzen status bar
import XMonad.Hooks.UrgencyHook
+
import XMonad.Hooks.UrgencyHook -- (2) alert me when people use my nick
  +
-- on IRC
import XMonad.Hooks.ManageDocks
 
  +
import XMonad.Hooks.ManageDocks -- (3) automatically avoid covering my
  +
-- status bar with windows
  +
import XMonad.Hooks.ManageHelpers -- (4) for doCenterFloat, put floating
  +
-- windows in the middle of the
  +
-- screen
   
  +
-- Layout ----------------------------------------------------
import XMonad.Layout.NoBorders
 
import XMonad.Layout.ResizableTile
 
import XMonad.Layout.WindowNavigation
 
import qualified XMonad.Layout.ToggleLayouts as TL
 
import XMonad.Layout.Named
 
import XMonad.Layout.PerWorkspace
 
import XMonad.Layout.WorkspaceDir
 
import XMonad.Layout.ShowWName
 
import XMonad.Layout.Reflect
 
import XMonad.Layout.MultiToggle
 
   
import XMonad.Actions.CycleWS
+
import XMonad.Layout.ResizableTile -- (5) resize non-master windows too
  +
import XMonad.Layout.Grid -- (6) grid layout
  +
import XMonad.Layout.NoBorders -- (7) get rid of borders sometimes
  +
-- (8) navigate between windows
  +
import XMonad.Layout.WindowNavigation -- directionally
  +
import XMonad.Layout.Named -- (9) rename some layouts
  +
import XMonad.Layout.PerWorkspace -- (10) use different layouts on different WSs
  +
import XMonad.Layout.WorkspaceDir -- (11) set working directory
  +
-- per-workspace
  +
import XMonad.Layout.ShowWName -- (12) show workspace names when
  +
-- switching
  +
import XMonad.Layout.Reflect -- (13) ability to reflect layouts
  +
import XMonad.Layout.MultiToggle -- (14) apply layout modifiers dynamically
  +
import XMonad.Layout.MultiToggle.Instances
  +
-- (15) ability to magnify the focused
  +
-- window
  +
import qualified XMonad.Layout.Magnifier as Mag
  +
  +
import XMonad.Layout.Gaps
  +
  +
-- Actions ---------------------------------------------------
  +
  +
import XMonad.Actions.CycleWS -- (16) general workspace-switching
  +
-- goodness
  +
-- (17) more flexible window resizing
 
import qualified XMonad.Actions.FlexibleManipulate as Flex
 
import qualified XMonad.Actions.FlexibleManipulate as Flex
import XMonad.Actions.SinkAll
+
import XMonad.Actions.Warp -- (18) warp the mouse pointer
import XMonad.Actions.Warp
+
import XMonad.Actions.Submap -- (19) create keybinding submaps
import XMonad.Actions.Submap
+
import XMonad.Actions.Search -- (20) some predefined web searches
import XMonad.Actions.Search
+
import XMonad.Actions.WindowGo -- (21) runOrRaise
import XMonad.Actions.WindowGo
+
import XMonad.Actions.UpdatePointer -- (22) auto-warp the pointer to the LR
  +
-- corner of the focused window
  +
  +
-- Prompts ---------------------------------------------------
  +
  +
import XMonad.Prompt -- (23) general prompt stuff.
  +
import XMonad.Prompt.Man -- (24) man page prompt
  +
import XMonad.Prompt.AppendFile -- (25) append stuff to my NOTES file
  +
import XMonad.Prompt.Shell -- (26) shell prompt
  +
import XMonad.Prompt.Input -- (27) generic input prompt, used for
  +
-- making more generic search
  +
-- prompts than those in
  +
-- XMonad.Prompt.Search
   
  +
-- Utilities -------------------------------------------------
import XMonad.Prompt
 
import XMonad.Prompt.Man
 
import XMonad.Prompt.AppendFile
 
import XMonad.Prompt.Shell
 
import XMonad.Prompt.Input
 
   
import XMonad.Util.WorkspaceCompare
+
import XMonad.Util.Loggers -- (28) some extra loggers for my
  +
-- status bar
import XMonad.Util.Loggers
 
import XMonad.Util.EZConfig
+
import XMonad.Util.EZConfig -- (29) "M-C-x" style keybindings
import XMonad.Util.Scratchpad
+
import XMonad.Util.Scratchpad -- (30) 'scratchpad' terminal
  +
import XMonad.Util.Run -- (31) for 'spawnPipe', 'hPutStrLn'
   
  +
-- (31)
main = xmonad $ byorgeyConfig
 
  +
main = do h <- spawnPipe "dzen2 -ta r -fg '#a8a3f7' -bg '#3f3c6d' -e 'onstart=lower'"
  +
xmonad $ byorgeyConfig h -- (0)
   
byorgeyConfig = myUrgencyHook $
+
byorgeyConfig h = myUrgencyHook $ -- (2)
 
defaultConfig
 
defaultConfig
 
{
 
{
Line 67: Line 98:
 
, terminal = "urxvt-custom"
 
, terminal = "urxvt-custom"
 
, workspaces = myWorkspaces
 
, workspaces = myWorkspaces
, defaultGaps = myGaps
 
 
, modMask = mod4Mask -- use Windoze key for mod
 
, modMask = mod4Mask -- use Windoze key for mod
 
, normalBorderColor = "#dddddd"
 
, normalBorderColor = "#dddddd"
 
, focusedBorderColor = "#0033ff"
 
, focusedBorderColor = "#0033ff"
, logHook = dynamicLogWithPP $ byorgeyPP
+
-- (22)
{ ppExtras = [ date "%a %b %d %I:%M %p"
+
, logHook = myDynamicLog h >> updatePointer (Relative 1 1)
, battery
 
, loadAvg
 
]
 
, ppOrder = \(ws:l:t:exs) -> [t,l,ws]++exs
 
}
 
 
, mouseBindings = myMouseBindings
 
, mouseBindings = myMouseBindings
  +
-- (0)
 
, manageHook = manageHook defaultConfig <+> myManageHook
 
, manageHook = manageHook defaultConfig <+> myManageHook
 
, layoutHook = myLayoutHook
 
, layoutHook = myLayoutHook
 
, focusFollowsMouse = False
 
, focusFollowsMouse = False
, startupHook = do checkKeymap byorgeyConfig $
 
myKeys
 
}
 
`additionalKeysP` myKeys
 
   
  +
-- XXX fixme: comment! -- (29)
  +
, startupHook = return () >> checkKeymap (byorgeyConfig h) (myKeys h)
  +
}
  +
`additionalKeysP` (myKeys h) -- (29)
   
 
-- have urgent events flash a yellow dzen bar with black text
 
-- have urgent events flash a yellow dzen bar with black text
myUrgencyHook = withUrgencyHook dzenUrgencyHook
+
myUrgencyHook = withUrgencyHook dzenUrgencyHook -- (2)
 
{ args = ["-bg", "yellow", "-fg", "black"] }
 
{ args = ["-bg", "yellow", "-fg", "black"] }
   
Line 99: Line 125:
 
++ ["<", "=", ">"]
 
++ ["<", "=", ">"]
   
  +
myDynamicLog h = dynamicLogWithPP $ byorgeyPP -- (1)
-- leave room at the top for the dzen status bar, and at the bottom
 
  +
{ ppExtras = [ date "%a %b %d %I:%M %p" -- (1,28)
-- for the gnome-panel.
 
  +
, battery -- (28)
myGaps = [(18,24,0,0)]
 
  +
, loadAvg -- (28)
  +
]
  +
, ppOrder = \(ws:l:t:exs) -> [t,l,ws]++exs -- (1)
  +
, ppOutput = hPutStrLn h -- (1,31)
  +
}
   
 
-- my custom mouse bindings.
 
-- my custom mouse bindings.
myMouseBindings (XConfig {modMask = modm}) = M.fromList $
+
myMouseBindings (XConfig {modMask = modm}) = M.fromList $ -- (0b)
 
-- these two are normal...
 
-- these two are normal...
[ ((modm, button1), (\w -> focus w >> mouseMoveWindow w))
+
[ ((modm, button1), (\w -> focus w >> mouseMoveWindow w)) -- (0)
, ((modm, button2), (\w -> focus w >> windows W.swapMaster))
+
, ((modm, button2), (\w -> focus w >> windows W.swapMaster)) -- (0)
-- but this one uses the FlexibleManipulate extension.
+
-- but this one uses the FlexibleManipulate extension. -- (17)
 
, ((modm, button3), (\w -> focus w >> Flex.mouseWindow Flex.linear w)) ]
 
, ((modm, button3), (\w -> focus w >> Flex.mouseWindow Flex.linear w)) ]
   
 
-- my custom keybindings.
 
-- my custom keybindings.
myKeys = myKeymap byorgeyConfig
+
myKeys h = myKeymap (byorgeyConfig h)
   
 
myKeymap conf =
 
myKeymap conf =
Line 118: Line 149:
 
-- mod-[1..9] %! Switch to workspace N
 
-- mod-[1..9] %! Switch to workspace N
 
-- mod-shift-[1..9] %! Move client to workspace N
 
-- mod-shift-[1..9] %! Move client to workspace N
[ (m ++ "M-" ++ [k], windows $ f i)
+
[ (m ++ "M-" ++ [k], windows $ f i) -- (0)
| (i, k) <- zip (XMonad.workspaces conf) "1234567890-="
+
| (i, k) <- zip (XMonad.workspaces conf) "1234567890-=" -- (0)
, (f, m) <- [(W.greedyView, ""), (W.shift, "S-")]
+
, (f, m) <- [(W.greedyView, ""), (W.shift, "S-")] -- (0a)
 
]
 
]
   
 
++
 
++
[ ("M-x x", spawn $ terminal conf)
+
[ ("M-S-x", spawn $ terminal conf) -- (0)
   
 
-- in conjunction with manageHook, open a small temporary
 
-- in conjunction with manageHook, open a small temporary
 
-- floating terminal
 
-- floating terminal
, ("M-x s", scratchpadSpawnAction conf)
+
, ("M-x s", scratchpadSpawnAction conf) -- (30)
   
, ("M-S-a", kill)
+
, ("M-S-a", kill) -- (0)
   
  +
-- some gap-toggling
-- toggle the bottom gap (to hide/show the gnome panel)
 
, ("M-g", modifyGap (\i n -> let x = (XMonad.defaultGaps conf ++ repeat (0,0,0,0)) !! i in if botGap n == botGap x then setBotGap 0 x else x))
+
, ("M-g b", sendMessage $ ToggleStrut D) -- (3)
  +
, ("M-g t", sendMessage $ ToggleStrut U) -- "
  +
, ("M-g a", sendMessage $ ToggleStruts) -- "
   
  +
, ("M-g g", sendMessage $ ToggleGaps)
-- rotate workspaces.
 
  +
]
, ("M-<R>", nextWS )
 
, ("M-<L>", prevWS )
 
, ("M-S-<R>", shiftToNext )
 
, ("M-S-<L>", shiftToPrev )
 
, ("M-S-C-<R>", shiftToNext >> nextWS )
 
, ("M-S-C-<L>", shiftToPrev >> prevWS )
 
, ("M-C-<R>", moveTo Next NonEmptyWS)
 
, ("M-C-<L>", moveTo Prev NonEmptyWS)
 
   
  +
++
, ("M-f", moveTo Next EmptyWS)
 
, ("M-d", moveTo Prev EmptyWS)
+
[ ("M-g " ++ f ++ " <" ++ dk ++ ">", sendMessage $ m d)
  +
| (dk, d) <- [("L",L), ("D",D), ("U",U), ("R",R)]
  +
, (f, m) <- [("v", ToggleGap), ("h", IncGap 10), ("f", DecGap 10)]
  +
]
  +
  +
++
  +
-- rotate workspaces.
  +
[ ("M-C-<R>", nextWS ) -- (16)
  +
, ("M-C-<L>", prevWS ) -- "
  +
, ("M-S-<R>", shiftToNext ) -- "
  +
, ("M-S-<L>", shiftToPrev ) -- "
  +
, ("M-S-C-<R>", shiftToNext >> nextWS ) -- "
  +
, ("M-S-C-<L>", shiftToPrev >> prevWS ) -- "
  +
, ("M-<R>", moveTo Next NonEmptyWS) -- "
  +
, ("M-<L>", moveTo Prev NonEmptyWS) -- "
  +
, ("M-f", moveTo Next EmptyWS) -- "
  +
, ("M-d", moveTo Prev EmptyWS) -- "
   
 
-- expand/shrink windows
 
-- expand/shrink windows
, ("M-r k", sendMessage MirrorExpand)
+
, ("M-r k", sendMessage MirrorExpand) -- (5)
, ("M-r j", sendMessage MirrorShrink)
+
, ("M-r j", sendMessage MirrorShrink) -- (5)
, ("M-r h", sendMessage Shrink)
+
, ("M-r h", sendMessage Shrink) -- (0)
, ("M-r l", sendMessage Expand)
+
, ("M-r l", sendMessage Expand) -- (0)
   
 
-- switch to previous workspace
 
-- switch to previous workspace
, ("M-z", toggleWS)
+
, ("M-z", toggleWS) -- (16)
   
 
-- lock the screen with xscreensaver
 
-- lock the screen with xscreensaver
, ("M-S-l", spawn "xscreensaver-command -lock")
+
, ("M-S-l", spawn "xscreensaver-command -lock") -- (0)
   
 
-- bainsh the pointer
 
-- bainsh the pointer
, ("M-S-b", warpToWindow 1 1)
+
, ("M-b", warpToWindow 1 1) -- (18)
   
 
-- some programs to start with keybindings.
 
-- some programs to start with keybindings.
, ("M-x f", runOrRaise "firefox" (className =? "Firefox-bin"))
+
, ("M-x f", runOrRaise "firefox" (className =? "Firefox-bin")) -- (21)
, ("M-x g", spawn "gimp")
+
, ("M-x g", spawn "gimp") -- (0)
, ("M-x m", spawn "rhythmbox")
+
, ("M-x m", spawn "rhythmbox") -- (0)
, ("M-x t", spawn "xclock")
+
, ("M-x t", spawn "xclock") -- (0)
  +
, ("M-x S-g", spawn "javaws ~/playing/go/cgoban.jnlp") -- (0)
   
 
-- configuration.
 
-- configuration.
, ("M-c x", spawn "em ~/.xmonad/xmonad.hs")
+
, ("M-c x", spawn "em ~/.xmonad/xmonad.hs") -- (0)
, ("M-c n", spawn "gksudo network-admin")
+
, ("M-c n", spawn "gksudo network-admin" >> spawn (terminal conf ++ " -e 'watch ifconfig'"))
, ("M-c v", spawn "gnome-volume-control --class=Volume")
+
, ("M-c v", spawn "gnome-volume-control --class=Volume") -- (0)
   
 
-- window navigation keybindings.
 
-- window navigation keybindings.
, ("C-<R>", sendMessage $ Go R)
+
, ("C-<R>", sendMessage $ Go R) -- (8)
, ("C-<L>", sendMessage $ Go L)
+
, ("C-<L>", sendMessage $ Go L) -- "
, ("C-<U>", sendMessage $ Go U)
+
, ("C-<U>", sendMessage $ Go U) -- "
, ("C-<D>", sendMessage $ Go D)
+
, ("C-<D>", sendMessage $ Go D) -- "
, ("S-C-<R>", sendMessage $ Swap R)
+
, ("S-C-<R>", sendMessage $ Swap R) -- "
, ("S-C-<L>", sendMessage $ Swap L)
+
, ("S-C-<L>", sendMessage $ Swap L) -- "
, ("S-C-<U>", sendMessage $ Swap U)
+
, ("S-C-<U>", sendMessage $ Swap U) -- "
, ("S-C-<D>", sendMessage $ Swap D)
+
, ("S-C-<D>", sendMessage $ Swap D) -- "
   
-- toggles: fullscreen, flip x, flip y
+
-- toggles: fullscreen, flip x, flip y, mirror, no borders
, ("M-C-<Space>", sendMessage TL.ToggleLayout)
+
, ("M-C-<Space>", sendMessage $ Toggle NBFULL) -- (14)
, ("M-C-x", sendMessage $ Toggle REFLECTX)
+
, ("M-C-x", sendMessage $ Toggle REFLECTX) -- (14,13)
, ("M-C-y", sendMessage $ Toggle REFLECTY)
+
, ("M-C-y", sendMessage $ Toggle REFLECTY) -- (14,13)
  +
, ("M-C-m", sendMessage $ Toggle MIRROR) -- "
  +
, ("M-C-b", sendMessage $ Toggle NOBORDERS) -- "
   
 
-- some prompts.
 
-- some prompts.
 
-- ability to change the working dir for a workspace.
 
-- ability to change the working dir for a workspace.
, ("M-p d", changeDir myXPConfig)
+
, ("M-p d", changeDir myXPConfig) -- (11)
 
-- man page prompt
 
-- man page prompt
, ("M-p m", manPrompt myXPConfig)
+
, ("M-p m", manPrompt myXPConfig) -- (24)
-- add single lines to my NOTES file from a prompt.
+
-- add single lines to my NOTES file from a prompt. -- (25)
 
, ("M-p n", appendFilePrompt myXPConfig "/home/brent/misc/NOTES")
 
, ("M-p n", appendFilePrompt myXPConfig "/home/brent/misc/NOTES")
 
-- shell prompt.
 
-- shell prompt.
, ("M-p s", shellPrompt myXPConfig)
+
, ("M-p s", shellPrompt myXPConfig) -- (26)
, ("M-p p", spawn "exe=`dmenu_path | dmenu` && eval \"exec $exe\"")
+
, ("M-p p", spawn "exe=`dmenu_path | dmenu` && eval \"exec $exe\"") -- (0)
   
 
-- some searches.
 
-- some searches.
, ("M-/", submap . mySearchMap $ myPromptSearch)
+
, ("M-/", submap . mySearchMap $ myPromptSearch) -- (19,20)
, ("M-C-/", submap . mySearchMap $ mySelectSearch)
+
, ("M-C-/", submap . mySearchMap $ mySelectSearch) -- (19,20)
   
 
-- some random utilities.
 
-- some random utilities.
 
, ("M-C-c", spawn "dzen-cal") -- calendar
 
, ("M-C-c", spawn "dzen-cal") -- calendar
   
  +
-- todos. -- (25)
-- todos.
 
 
, ("M-C-t a", appendFilePrompt myXPConfig "/home/brent/misc/TODO")
 
, ("M-C-t a", appendFilePrompt myXPConfig "/home/brent/misc/TODO")
, ("M-C-t l", spawn "dzen-show-todos")
+
, ("M-C-t l", spawn "dzen-show-todos") -- (0)
, ("M-C-t e", spawn "emacs ~/misc/TODO")
+
, ("M-C-t e", spawn "emacs ~/misc/TODO") -- (0)
 
, ("M-C-t u", spawn "cp ~/misc/TODO.backup ~/misc/TODO ; dzen-show-todos") ]
 
, ("M-C-t u", spawn "cp ~/misc/TODO.backup ~/misc/TODO ; dzen-show-todos") ]
  +
++ -- (0)
++
 
 
[ ("M-C-t " ++ [key], spawn ("del-todo " ++ show n ++ " ; dzen-show-todos"))
 
[ ("M-C-t " ++ [key], spawn ("del-todo " ++ show n ++ " ; dzen-show-todos"))
 
| (key, n) <- zip "1234567890" [1..10]
 
| (key, n) <- zip "1234567890" [1..10]
 
]
 
]
   
  +
hackage = searchEngine "hackage" "http://hackage.haskell.org/cgi-bin/hackage-scripts/package/"
mySearchMap method = M.fromList $
 
  +
[ ((0, xK_g), method google)
 
  +
-- Perform a search, using the given method, based on a keypress
, ((0, xK_w), method wikipedia)
 
  +
mySearchMap method = M.fromList $ -- (0b)
, ((0, xK_h), method hoogle)
 
, ((0, xK_s), method scholar)
+
[ ((0, xK_g), method google) -- (20)
, ((0, xK_m), method mathworld)
+
, ((0, xK_w), method wikipedia) -- "
  +
, ((0, xK_h), method hoogle) -- "
  +
, ((shiftMask, xK_h), method hackage)
  +
, ((0, xK_s), method scholar) -- "
  +
, ((0, xK_m), method mathworld) -- "
  +
, ((0, xK_p), method maps) -- "
  +
, ((0, xK_d), method dictionary) -- "
 
]
 
]
   
  +
-- Prompt search: get input from the user via a prompt, then
myPromptSearch eng = inputPrompt myXPConfig "Search" ?+ \s ->
 
  +
-- run the search in firefox and automatically switch to the "web"
(io (search "firefox" eng s) >> viewWeb)
 
  +
-- workspace
  +
myPromptSearch (SearchEngine _ site)
  +
= inputPrompt myXPConfig "Search" ?+ \s -> -- (27)
  +
(search "firefox" site s >> viewWeb) -- (0,20)
   
  +
-- Select search: do a search based on the X selection
mySelectSearch eng = selectSearch "firefox" eng >> viewWeb
 
  +
mySelectSearch eng = selectSearch eng >> viewWeb -- (20)
   
  +
-- Switch to the "web" workspace
viewWeb = windows (W.greedyView "web")
 
  +
viewWeb = windows (W.greedyView "web") -- (0,0a)
   
 
-- some nice colors for the prompt windows to match the dzen status bar.
 
-- some nice colors for the prompt windows to match the dzen status bar.
myXPConfig = defaultXPConfig
+
myXPConfig = defaultXPConfig -- (23)
 
{ fgColor = "#a8a3f7"
 
{ fgColor = "#a8a3f7"
 
, bgColor = "#3f3c6d"
 
, bgColor = "#3f3c6d"
 
}
 
}
   
  +
-- Set up a customized manageHook (rules for handling windows on
-- specify some additional applications which should always float.
 
  +
-- creation)
myManageHook :: ManageHook
 
  +
myManageHook :: ManageHook -- (0)
 
myManageHook = composeAll $
 
myManageHook = composeAll $
[ className =? c --> doFloat | c <- myFloats ]
+
-- auto-float certain windows
++
+
[ className =? c --> doCenterFloat | c <- myFloats ] -- (4)
[ className =? "Rhythmbox" --> doF (W.shift "=")
+
++
, className =? "XDvi" --> doF (W.shift "dvi")
+
[ title =? t --> doFloat | t <- myFloatTitles ]
, manageDocks
+
++
, scratchpadManageHookDefault
+
-- send certain windows to certain workspaces
]
+
[ className =? "Rhythmbox" --> doF (W.shift "=") -- (0,0a)
  +
, className =? "XDvi" --> doF (W.shift "dvi") -- (0,0a)
where myFloats = ["Volume", "XClock", "Network-admin", "Xmessage"]
 
  +
-- unmanage docks such as gnome-panel and dzen
 
  +
, manageDocks -- (3)
doRectFloat :: W.RationalRect -> ManageHook
 
  +
-- manage the scratchpad terminal window
doRectFloat r = ask >>= \w -> doF (W.float w r)
 
  +
, scratchpadManageHookDefault -- (30)
 
  +
]
scratchpadRect :: W.RationalRect
 
  +
-- windows to auto-float
scratchpadRect = W.RationalRect 0.25 0.375 0.5 0.25
 
  +
where myFloats = [ "Volume"
  +
, "XClock"
  +
, "Network-admin"
  +
, "Xmessage"
  +
, "Inkscape"
  +
, "gnome-search-tool"
  +
]
  +
myFloatTitles = ["Bridge Bid"]
   
 
-- specify a custom layout hook.
 
-- specify a custom layout hook.
 
myLayoutHook =
 
myLayoutHook =
-- show workspace names when switching.
 
showWName' myShowWNameConfig $
 
   
  +
-- automatically avoid overlapping my dzen status bar.
-- workspace 1 starts in Full mode and can switch to tiled.
 
  +
avoidStrutsOn [U] $ -- (3)
onWorkspace "web" (smartBorders (Full ||| myTiled)) $
 
  +
  +
-- make manual gap adjustment possible.
  +
gaps (zip [U,D,L,R] (repeat 0)) $
  +
  +
-- show workspace names when switching.
  +
showWName' myShowWNameConfig $ -- (12)
   
 
-- start all workspaces in my home directory, with the ability
 
-- start all workspaces in my home directory, with the ability
-- to switch to a new working dir.
+
-- to switch to a new working dir. -- (10,11)
workspaceDir "~" $
+
chooseMod ["=", ">"] (workspaceDir "~/xmonad") (workspaceDir "~") $
   
 
-- navigate directionally rather than with mod-j/k
 
-- navigate directionally rather than with mod-j/k
configurableNavigation (navigateColor "#00aa00") $
+
configurableNavigation (navigateColor "#00aa00") $ -- (8)
  +
  +
-- ability to toggle between fullscreen, reflect x/y, no borders,
  +
-- and mirrored.
  +
mkToggle1 NBFULL $ -- (14)
  +
mkToggle1 REFLECTX $ -- (14,13)
  +
mkToggle1 REFLECTY $ -- (14,13)
  +
mkToggle1 NOBORDERS $ -- "
  +
mkToggle1 MIRROR $ -- "
   
-- ability to toggle between fullscreen
+
-- borders automatically disappear for fullscreen windows.
  +
smartBorders $ -- (7)
TL.toggleLayouts (noBorders Full) $
 
   
  +
-- "web" and "irc" start in Full mode and can switch to tiled...
-- toggle vertical/horizontal layout reflection
 
  +
onWorkspaces ["web","irc"] (Full ||| myTiled) $ -- (10,0)
mkToggle (single REFLECTX) $
 
mkToggle (single REFLECTY) $
 
   
  +
-- ...whereas all other workspaces start tall and can switch
-- borders automatically disappear for fullscreen windows
 
  +
-- to a grid layout with the focused window magnified.
smartBorders $
 
myTiled |||
+
myTiled ||| -- resizable tall layout
  +
Mag.magnifier Grid -- (15,6)
Mirror myTiled
 
   
  +
-- Show the new workspace name in a yellow on blue box for 0.3 seconds
myShowWNameConfig = defaultSWNConfig
 
  +
-- each time I switch workspaces.
  +
myShowWNameConfig = defaultSWNConfig -- (12)
 
{ swn_bgcolor = "blue"
 
{ swn_bgcolor = "blue"
 
, swn_color = "yellow"
 
, swn_color = "yellow"
Line 289: Line 368:
 
}
 
}
   
  +
-- use ResizableTall instead of Tall, but still call it "Tall".
myTiled = named "Tall" $ ResizableTall 1 0.01 0.5 []
 
  +
myTiled = named "Tall" $ ResizableTall 1 0.01 0.5 [] -- (9,5)
   
botGap (_,x,_,_) = x
 
setBotGap g (a,_,c,d) = (a,g,c,d)
 
 
</haskell>
 
</haskell>
   

Revision as of 21:04, 20 June 2008

My .xsession file:

gnome-power-manager 
gnome-volume-manager &

xpmroot ~/images/cherry-tree-wp.png

xmodmap -e 'clear Lock'

export PATH=$PATH:/home/brent/local/bin
export OOO_FORCE_DESKTOP=gnome
gnome-panel &
$HOME/local/bin/xmonad | dzen2 -ta r -fg '#a8a3f7' -bg '#3f3c6d'

My current config file, which works with the latest development xmonad and xmonad-contrib, annotated to show which extensions are being used where:

import XMonad                          -- (0) core xmonad libraries

import qualified XMonad.StackSet as W  -- (0a) window stack manipulation
import qualified Data.Map as M         -- (0b) map creation

-- Hooks -----------------------------------------------------

import XMonad.Hooks.DynamicLog     -- (1)  for dzen status bar
import XMonad.Hooks.UrgencyHook    -- (2)  alert me when people use my nick
                                   --      on IRC
import XMonad.Hooks.ManageDocks    -- (3)  automatically avoid covering my
                                   --      status bar with windows
import XMonad.Hooks.ManageHelpers  -- (4)  for doCenterFloat, put floating
                                   --      windows in the middle of the
                                   --      screen

-- Layout ----------------------------------------------------

import XMonad.Layout.ResizableTile -- (5)  resize non-master windows too
import XMonad.Layout.Grid          -- (6)  grid layout
import XMonad.Layout.NoBorders     -- (7)  get rid of borders sometimes
                                   -- (8)  navigate between windows
import XMonad.Layout.WindowNavigation  --  directionally
import XMonad.Layout.Named         -- (9)  rename some layouts
import XMonad.Layout.PerWorkspace  -- (10) use different layouts on different WSs
import XMonad.Layout.WorkspaceDir  -- (11) set working directory
                                   --      per-workspace
import XMonad.Layout.ShowWName     -- (12) show workspace names when
                                   --      switching
import XMonad.Layout.Reflect       -- (13) ability to reflect layouts
import XMonad.Layout.MultiToggle   -- (14) apply layout modifiers dynamically
import XMonad.Layout.MultiToggle.Instances
                                   -- (15) ability to magnify the focused
                                   --      window
import qualified XMonad.Layout.Magnifier as Mag

import XMonad.Layout.Gaps

-- Actions ---------------------------------------------------

import XMonad.Actions.CycleWS      -- (16) general workspace-switching
                                   --      goodness
                                   -- (17) more flexible window resizing
import qualified XMonad.Actions.FlexibleManipulate as Flex
import XMonad.Actions.Warp         -- (18) warp the mouse pointer
import XMonad.Actions.Submap       -- (19) create keybinding submaps
import XMonad.Actions.Search       -- (20) some predefined web searches
import XMonad.Actions.WindowGo     -- (21) runOrRaise
import XMonad.Actions.UpdatePointer -- (22) auto-warp the pointer to the LR
                                    --      corner of the focused window

-- Prompts ---------------------------------------------------

import XMonad.Prompt                -- (23) general prompt stuff.
import XMonad.Prompt.Man            -- (24) man page prompt
import XMonad.Prompt.AppendFile     -- (25) append stuff to my NOTES file
import XMonad.Prompt.Shell          -- (26) shell prompt
import XMonad.Prompt.Input          -- (27) generic input prompt, used for
                                    --      making more generic search
                                    --      prompts than those in
                                    --      XMonad.Prompt.Search

-- Utilities -------------------------------------------------

import XMonad.Util.Loggers          -- (28) some extra loggers for my
                                    --      status bar
import XMonad.Util.EZConfig         -- (29) "M-C-x" style keybindings
import XMonad.Util.Scratchpad       -- (30) 'scratchpad' terminal
import XMonad.Util.Run              -- (31) for 'spawnPipe', 'hPutStrLn'

                                                                -- (31)
main = do h <- spawnPipe "dzen2 -ta r -fg '#a8a3f7' -bg '#3f3c6d' -e 'onstart=lower'"
          xmonad $ byorgeyConfig h                              -- (0)

byorgeyConfig h = myUrgencyHook $                               -- (2)
     defaultConfig
       {
         borderWidth        = 2
       , terminal           = "urxvt-custom"
       , workspaces         = myWorkspaces
       , modMask            = mod4Mask  -- use Windoze key for mod
       , normalBorderColor  = "#dddddd"
       , focusedBorderColor = "#0033ff"
                                                                -- (22)
       , logHook            = myDynamicLog h >> updatePointer (Relative 1 1)
       , mouseBindings      = myMouseBindings
                                                                -- (0)
       , manageHook         = manageHook defaultConfig <+> myManageHook
       , layoutHook         = myLayoutHook
       , focusFollowsMouse  = False

         -- XXX fixme: comment!                                 -- (29)
       , startupHook        = return () >> checkKeymap (byorgeyConfig h) (myKeys h)
       }
       `additionalKeysP` (myKeys h)                             -- (29)

-- have urgent events flash a yellow dzen bar with black text
myUrgencyHook = withUrgencyHook dzenUrgencyHook                 -- (2)
    { args = ["-bg", "yellow", "-fg", "black"] }

-- define some custom workspace tags
myWorkspaces :: [String]
myWorkspaces = ["web", "irc", "code", "code2", "ref" ]
               ++ ["write", "dvi"]
               ++ map show [8 .. 9 :: Int]
               ++ ["<", "=", ">"]

myDynamicLog h = dynamicLogWithPP $ byorgeyPP                   -- (1)
  { ppExtras = [ date "%a %b %d  %I:%M %p"                      -- (1,28)
               , battery                                        -- (28)
               , loadAvg                                        -- (28)
               ]
  , ppOrder = \(ws:l:t:exs) -> [t,l,ws]++exs                    -- (1)
  , ppOutput = hPutStrLn h                                      -- (1,31)
  }

-- my custom mouse bindings.
myMouseBindings (XConfig {modMask = modm}) = M.fromList $       -- (0b)
    -- these two are normal...
    [ ((modm, button1), (\w -> focus w >> mouseMoveWindow w))   -- (0)
    , ((modm, button2), (\w -> focus w >> windows W.swapMaster)) -- (0)
    -- but this one uses the FlexibleManipulate extension.      -- (17)
    , ((modm, button3), (\w -> focus w >> Flex.mouseWindow Flex.linear w)) ]

-- my custom keybindings.
myKeys h = myKeymap (byorgeyConfig h)

myKeymap conf =

    -- mod-[1..9] %! Switch to workspace N
    -- mod-shift-[1..9] %! Move client to workspace N
    [ (m ++ "M-" ++ [k], windows $ f i)                         -- (0)
        | (i, k) <- zip (XMonad.workspaces conf) "1234567890-=" -- (0)
        , (f, m) <- [(W.greedyView, ""), (W.shift, "S-")]       -- (0a)
    ]

    ++
    [ ("M-S-x", spawn $ terminal conf)                          -- (0)

      -- in conjunction with manageHook, open a small temporary
      -- floating terminal
    , ("M-x s", scratchpadSpawnAction conf)                     -- (30)

    , ("M-S-a", kill)                                           -- (0)

    -- some gap-toggling
    , ("M-g b", sendMessage $ ToggleStrut D)                    -- (3)
    , ("M-g t", sendMessage $ ToggleStrut U)                    --  "
    , ("M-g a", sendMessage $ ToggleStruts)                     --  "

    , ("M-g g", sendMessage $ ToggleGaps)
    ]

    ++
    [ ("M-g " ++ f ++ " <" ++ dk ++ ">", sendMessage $ m d)
        | (dk, d) <- [("L",L), ("D",D), ("U",U), ("R",R)]
        , (f, m)  <- [("v", ToggleGap), ("h", IncGap 10), ("f", DecGap 10)]
    ]

    ++
    -- rotate workspaces.
    [ ("M-C-<R>",   nextWS )                                    -- (16)
    , ("M-C-<L>",   prevWS )                                    --  "
    , ("M-S-<R>",   shiftToNext )                               --  "
    , ("M-S-<L>",   shiftToPrev )                               --  "
    , ("M-S-C-<R>", shiftToNext >> nextWS )                     --  "
    , ("M-S-C-<L>", shiftToPrev >> prevWS )                     --  "
    , ("M-<R>",     moveTo Next NonEmptyWS)                     --  "
    , ("M-<L>",     moveTo Prev NonEmptyWS)                     --  "
    , ("M-f",       moveTo Next EmptyWS)                        --  "
    , ("M-d",       moveTo Prev EmptyWS)                        --  "

    -- expand/shrink windows
    , ("M-r k", sendMessage MirrorExpand)                       -- (5)
    , ("M-r j", sendMessage MirrorShrink)                       -- (5)
    , ("M-r h", sendMessage Shrink)                             -- (0)
    , ("M-r l", sendMessage Expand)                             -- (0)

    -- switch to previous workspace
    , ("M-z", toggleWS)                                         -- (16)

    -- lock the screen with xscreensaver
    , ("M-S-l", spawn "xscreensaver-command -lock")             -- (0)

    -- bainsh the pointer
    , ("M-b", warpToWindow 1 1)                                 -- (18)

    -- some programs to start with keybindings.
    , ("M-x f", runOrRaise "firefox" (className =? "Firefox-bin")) -- (21)
    , ("M-x g", spawn "gimp")                                   -- (0)
    , ("M-x m", spawn "rhythmbox")                              -- (0)
    , ("M-x t", spawn "xclock")                                 -- (0)
    , ("M-x S-g", spawn "javaws ~/playing/go/cgoban.jnlp")      -- (0)

    -- configuration.
    , ("M-c x", spawn "em ~/.xmonad/xmonad.hs")                 -- (0)
    , ("M-c n", spawn "gksudo network-admin" >> spawn (terminal conf ++ " -e 'watch ifconfig'"))
    , ("M-c v", spawn "gnome-volume-control --class=Volume")    -- (0)

    -- window navigation keybindings.
    , ("C-<R>", sendMessage $ Go R)                             -- (8)
    , ("C-<L>", sendMessage $ Go L)                             --  "
    , ("C-<U>", sendMessage $ Go U)                             --  "
    , ("C-<D>", sendMessage $ Go D)                             --  "
    , ("S-C-<R>", sendMessage $ Swap R)                         --  "
    , ("S-C-<L>", sendMessage $ Swap L)                         --  "
    , ("S-C-<U>", sendMessage $ Swap U)                         --  "
    , ("S-C-<D>", sendMessage $ Swap D)                         --  "

    -- toggles: fullscreen, flip x, flip y, mirror, no borders
    , ("M-C-<Space>", sendMessage $ Toggle NBFULL)              -- (14)
    , ("M-C-x",       sendMessage $ Toggle REFLECTX)            -- (14,13)
    , ("M-C-y",       sendMessage $ Toggle REFLECTY)            -- (14,13)
    , ("M-C-m",       sendMessage $ Toggle MIRROR)              --  "
    , ("M-C-b",       sendMessage $ Toggle NOBORDERS)           --  "

    -- some prompts.
      -- ability to change the working dir for a workspace.
    , ("M-p d", changeDir myXPConfig)                           -- (11)
      -- man page prompt
    , ("M-p m", manPrompt myXPConfig)                           -- (24)
      -- add single lines to my NOTES file from a prompt.       -- (25)
    , ("M-p n", appendFilePrompt myXPConfig "/home/brent/misc/NOTES")
      -- shell prompt.
    , ("M-p s", shellPrompt myXPConfig)                         -- (26)
    , ("M-p p", spawn "exe=`dmenu_path | dmenu` && eval \"exec $exe\"") -- (0)

      -- some searches.
    , ("M-/", submap . mySearchMap $ myPromptSearch)            -- (19,20)
    , ("M-C-/", submap . mySearchMap $ mySelectSearch)          -- (19,20)

    -- some random utilities.
    , ("M-C-c", spawn "dzen-cal")  -- calendar

    -- todos.                                                   -- (25)
    , ("M-C-t a", appendFilePrompt myXPConfig "/home/brent/misc/TODO")
    , ("M-C-t l", spawn "dzen-show-todos")                      -- (0)
    , ("M-C-t e", spawn "emacs ~/misc/TODO")                    -- (0)
    , ("M-C-t u", spawn "cp ~/misc/TODO.backup ~/misc/TODO ; dzen-show-todos")    ]
    ++                                                          -- (0)
    [ ("M-C-t " ++ [key], spawn ("del-todo " ++ show n ++ " ; dzen-show-todos"))
      | (key, n) <- zip "1234567890" [1..10]
    ]

hackage = searchEngine "hackage" "http://hackage.haskell.org/cgi-bin/hackage-scripts/package/"

-- Perform a search, using the given method, based on a keypress
mySearchMap method = M.fromList $                               -- (0b)
        [ ((0, xK_g), method google)                            -- (20)
        , ((0, xK_w), method wikipedia)                         --  "
        , ((0, xK_h), method hoogle)                            --  "
        , ((shiftMask, xK_h), method hackage)
        , ((0, xK_s), method scholar)                           --  "
        , ((0, xK_m), method mathworld)                         --  "
        , ((0, xK_p), method maps)                              --  "
        , ((0, xK_d), method dictionary)                        --  "
        ]

-- Prompt search: get input from the user via a prompt, then
--   run the search in firefox and automatically switch to the "web"
--   workspace
myPromptSearch (SearchEngine _ site)
  = inputPrompt myXPConfig "Search" ?+ \s ->                    -- (27)
      (search "firefox" site s >> viewWeb)                      -- (0,20)

-- Select search: do a search based on the X selection
mySelectSearch eng = selectSearch eng >> viewWeb                -- (20)

-- Switch to the "web" workspace
viewWeb = windows (W.greedyView "web")                          -- (0,0a)

-- some nice colors for the prompt windows to match the dzen status bar.
myXPConfig = defaultXPConfig                                    -- (23)
    { fgColor = "#a8a3f7"
    , bgColor = "#3f3c6d"
    }

-- Set up a customized manageHook (rules for handling windows on
--   creation)
myManageHook :: ManageHook                                      -- (0)
myManageHook = composeAll $
                   -- auto-float certain windows
                 [ className =? c --> doCenterFloat | c <- myFloats ] -- (4)
                 ++
                 [ title =? t     --> doFloat | t <- myFloatTitles ]
                 ++
                   -- send certain windows to certain workspaces
                 [ className =? "Rhythmbox" --> doF (W.shift "=")  -- (0,0a)
                 , className =? "XDvi" --> doF (W.shift "dvi")     -- (0,0a)
                   -- unmanage docks such as gnome-panel and dzen
                 , manageDocks                                     -- (3)
                   -- manage the scratchpad terminal window
                 , scratchpadManageHookDefault                     -- (30)
                 ]
    -- windows to auto-float
    where myFloats = [ "Volume"
                     , "XClock"
                     , "Network-admin"
                     , "Xmessage"
                     , "Inkscape"
                     , "gnome-search-tool"
                     ]
          myFloatTitles = ["Bridge Bid"]

-- specify a custom layout hook.
myLayoutHook =

    -- automatically avoid overlapping my dzen status bar.
    avoidStrutsOn [U] $                                        -- (3)

    -- make manual gap adjustment possible.
    gaps (zip [U,D,L,R] (repeat 0)) $

    -- show workspace names when switching.
    showWName' myShowWNameConfig $                              -- (12)

    -- start all workspaces in my home directory, with the ability
    -- to switch to a new working dir.                          -- (10,11)
    chooseMod ["=", ">"] (workspaceDir "~/xmonad") (workspaceDir "~") $

    -- navigate directionally rather than with mod-j/k
    configurableNavigation (navigateColor "#00aa00") $          -- (8)

    -- ability to toggle between fullscreen, reflect x/y, no borders,
    -- and mirrored.
    mkToggle1 NBFULL $                                  -- (14)
    mkToggle1 REFLECTX $                                -- (14,13)
    mkToggle1 REFLECTY $                                -- (14,13)
    mkToggle1 NOBORDERS $                               --  "
    mkToggle1 MIRROR $                                  --  "

    -- borders automatically disappear for fullscreen windows.
    smartBorders $                                              -- (7)

    -- "web" and "irc" start in Full mode and can switch to tiled...
    onWorkspaces ["web","irc"] (Full ||| myTiled) $             -- (10,0)

    -- ...whereas all other workspaces start tall and can switch
    -- to a grid layout with the focused window magnified.
    myTiled |||           -- resizable tall layout
    Mag.magnifier Grid                                          -- (15,6)

-- Show the new workspace name in a yellow on blue box for 0.3 seconds
-- each time I switch workspaces.
myShowWNameConfig = defaultSWNConfig                            -- (12)
    { swn_bgcolor = "blue"
    , swn_color = "yellow"
    , swn_fade = 0.3
    }

-- use ResizableTall instead of Tall, but still call it "Tall".
myTiled = named "Tall" $ ResizableTall 1 0.01 0.5 []            -- (9,5)

For other support scripts etc., see my 0.6 config.