Xmonad/Config archive/Brent Yorgey's xmonad.hs: Difference between revisions
< Xmonad | Config archive
m (update to my current config.) |
(update my xmonad.hs) |
||
Line 10: | Line 10: | ||
</pre> | </pre> | ||
hsstatus is a utility I wrote to add date/time, battery, and uptime information to the output from xmonad. | hsstatus is a utility I wrote to add date/time, battery, and uptime information to the output from xmonad: | ||
<haskell> | |||
import System.IO | |||
import System.Time | |||
import System.Process | |||
main :: IO () | |||
main = do hSetBuffering stdout LineBuffering | |||
inp <- getLine | |||
stat <- mkStatus inp | |||
putStrLn stat | |||
main | |||
mkStatus :: String -> IO String | |||
mkStatus inp = do time <- getTime | |||
bat <- getBat | |||
loadAvg <- getLoadAvg | |||
return . concat $ [ inp, s | |||
, time, s | |||
, bat, s | |||
, loadAvg ] | |||
where s = " | " | |||
getTime :: IO String | |||
getTime = do cal <- (getClockTime >>= toCalendarTime) | |||
return $ concat | |||
[ show . (1+) . fromEnum . ctMonth $ cal | |||
, "/", show . ctDay $ cal | |||
, " ", show . fromMilitary . ctHour $ cal | |||
, ":", padMin . ctMin $ cal | |||
, " ", ampm . ctHour $ cal ] | |||
where | |||
fromMilitary 0 = 12 | |||
fromMilitary h | h > 12 = h - 12 | |||
| otherwise = h | |||
padMin m | m < 10 = '0' : (show m) | |||
| otherwise = show m | |||
ampm h | h < 12 = "AM" | |||
| otherwise = "PM" | |||
getBat :: IO String | |||
getBat = do (_, out, _, proc) <- runInteractiveCommand "/usr/bin/acpi | sed -r 's/.*?: (.*%).*/\\1/; s/discharging, ([0-9]+%)/\\1-/; s/charging, ([0-9]+%)/\\1+/; s/charged, //'" | |||
batInfo <- hGetLine out | |||
waitForProcess proc | |||
return batInfo | |||
getLoadAvg :: IO String | |||
getLoadAvg = do (_, out, _, proc) <- runInteractiveCommand "/usr/bin/uptime | sed 's/.*: //; s/,//g'" | |||
uptimeInfo <- hGetLine out | |||
waitForProcess proc | |||
return uptimeInfo | |||
</haskell> | |||
My xmonad.hs: | My xmonad.hs: | ||
Line 16: | Line 68: | ||
<haskell> | <haskell> | ||
import XMonad | import XMonad | ||
import qualified XMonad.StackSet as W | import qualified XMonad.StackSet as W | ||
import Graphics.X11.Xlib | import Graphics.X11.Xlib | ||
Line 25: | Line 78: | ||
import XMonad.Hooks.ManageDocks | import XMonad.Hooks.ManageDocks | ||
import XMonad.Layout.NoBorders | import XMonad.Layout.NoBorders | ||
import XMonad.Layout.ResizableTile | import XMonad.Layout.ResizableTile | ||
import XMonad.Layout.WindowNavigation | import XMonad.Layout.WindowNavigation | ||
import XMonad.Layout.ToggleLayouts | import qualified XMonad.Layout.ToggleLayouts as TL | ||
import XMonad.Layout.Named | import XMonad.Layout.Named | ||
import XMonad.Layout.PerWorkspace | import XMonad.Layout.PerWorkspace | ||
import XMonad.Layout.WorkspaceDir | import XMonad.Layout.WorkspaceDir | ||
import XMonad.Layout.ShowWName | |||
import XMonad.Layout.Reflect | |||
import XMonad.Layout.MultiToggle | |||
import XMonad.Actions.RotView | import XMonad.Actions.RotView | ||
Line 41: | Line 95: | ||
import XMonad.Actions.Warp | import XMonad.Actions.Warp | ||
import XMonad.Actions.Submap | import XMonad.Actions.Submap | ||
import XMonad.Actions. | import XMonad.Actions.Search | ||
import XMonad.Prompt | import XMonad.Prompt | ||
Line 48: | Line 102: | ||
import XMonad.Prompt.Shell | import XMonad.Prompt.Shell | ||
import XMonad.Prompt.Input | import XMonad.Prompt.Input | ||
main = xmonad $ byorgeyConfig | main = xmonad $ byorgeyConfig | ||
Line 66: | Line 119: | ||
, manageHook = manageHook defaultConfig <+> myManageHook | , manageHook = manageHook defaultConfig <+> myManageHook | ||
, layoutHook = myLayoutHook | , layoutHook = myLayoutHook | ||
, focusFollowsMouse = False | |||
} | } | ||
Line 82: | Line 136: | ||
-- for the gnome-panel. | -- for the gnome-panel. | ||
myGaps = [(18,24,0,0)] | myGaps = [(18,24,0,0)] | ||
myMouseBindings (XConfig {modMask = modm}) = M.fromList $ | myMouseBindings (XConfig {modMask = modm}) = M.fromList $ | ||
Line 148: | Line 184: | ||
, ((modm .|. shiftMask, xK_l), spawn "xscreensaver-command -lock") | , ((modm .|. shiftMask, xK_l), spawn "xscreensaver-command -lock") | ||
-- | -- bainsh the pointer | ||
, ((modm .|. shiftMask, xK_b), warpToWindow 1 1) | , ((modm .|. shiftMask, xK_b), warpToWindow 1 1) | ||
Line 172: | Line 208: | ||
, ((shiftMask .|. controlMask, xK_Down ), sendMessage $ Swap D) | , ((shiftMask .|. controlMask, xK_Down ), sendMessage $ Swap D) | ||
-- | -- toggles: fullscreen, flip x, flip y | ||
, ((modm .|. controlMask, xK_space), sendMessage ToggleLayout) | , ((modm .|. controlMask, xK_space), sendMessage TL.ToggleLayout) | ||
, ((modm .|. controlMask, xK_x), sendMessage $ Toggle REFLECTX) | |||
, ((modm .|. controlMask, xK_y), sendMessage $ Toggle REFLECTY) | |||
-- some prompts. | -- some prompts. | ||
Line 181: | Line 219: | ||
, ((modm .|. controlMask, xK_m), manPrompt myXPConfig) | , ((modm .|. controlMask, xK_m), manPrompt myXPConfig) | ||
-- add single lines to my NOTES file from a prompt. | -- add single lines to my NOTES file from a prompt. | ||
, ((modm .|. controlMask, xK_n), appendFilePrompt myXPConfig "/home/brent/NOTES") | , ((modm .|. controlMask, xK_n), appendFilePrompt myXPConfig "/home/brent/misc/NOTES") | ||
-- shell prompt. | -- shell prompt. | ||
, ((modm .|. controlMask, xK_s), shellPrompt myXPConfig) | , ((modm .|. controlMask, xK_s), shellPrompt myXPConfig) | ||
-- some searches. | -- some searches. | ||
, ((modm | , ((modm , xK_slash), submap . mySearchMap $ myPromptSearch) | ||
, ((modm .|. controlMask, xK_slash), submap . mySearchMap $ mySelectSearch) | |||
-- some random utilities. | -- some random utilities. | ||
Line 197: | Line 232: | ||
-- todos. | -- todos. | ||
, ((modm .|. controlMask, xK_t), submap . M.fromList $ | , ((modm .|. controlMask, xK_t), submap . M.fromList $ | ||
[ ((0, xK_a), appendFilePrompt myXPConfig "/home/brent/TODO") | [ ((0, xK_a), appendFilePrompt myXPConfig "/home/brent/misc/TODO") | ||
, ((0, xK_l), spawn "dzen-show-todos") | , ((0, xK_l), spawn "dzen-show-todos") | ||
, ((0, xK_e), spawn "emacs ~/TODO") | , ((0, xK_e), spawn "emacs ~/misc/TODO") | ||
, ((0, xK_u), spawn "cp ~/TODO.backup ~/TODO ; dzen-show-todos") | , ((0, xK_u), spawn "cp ~/misc/TODO.backup ~/misc/TODO ; dzen-show-todos") | ||
] | ] | ||
++ | ++ | ||
Line 208: | Line 243: | ||
] | ] | ||
mySearchMap method = M.fromList $ | |||
[ ((0, xK_g), method google) | |||
, ((0, xK_w), method wikipedia) | |||
, ((0, xK_h), method hoogle) | |||
, ((0, xK_s), method scholar) | |||
, ((0, xK_m), method mathworld) | |||
] | |||
myPromptSearch eng = inputPrompt myXPConfig "Search" ?+ \s -> | |||
(io (search "firefox" eng s) >> viewWeb) | |||
mySelectSearch eng = selectSearch "firefox" eng >> viewWeb | |||
viewWeb = windows (W.greedyView "1:web") | |||
-- 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. | ||
Line 224: | Line 270: | ||
++ | ++ | ||
[ className =? "Rhythmbox" --> doF (W.shift "=") | [ className =? "Rhythmbox" --> doF (W.shift "=") | ||
, className =? "XDvi" --> doF (W.shift "7:dvi") | |||
, manageDocks | , manageDocks | ||
] | ] | ||
where myFloats = ["Volume", "XClock", "Network-admin"] | where myFloats = ["Volume", "XClock", "Network-admin", "Xmessage"] | ||
-- specify a custom layout hook. | -- specify a custom layout hook. | ||
myLayoutHook = | myLayoutHook = | ||
-- show workspace names when switching. | |||
showWName' myShowWNameConfig $ | |||
-- workspace 1 starts in Full mode and can switch to tiled. | -- workspace 1 starts in Full mode and can switch to tiled. | ||
onWorkspace "1:web" (smartBorders (Full ||| myTiled)) $ | onWorkspace "1:web" (smartBorders (Full ||| myTiled)) $ | ||
-- start all workspaces in my home directory, with the ability | |||
-- to switch to a new working dir. | -- to switch to a new working dir. | ||
workspaceDir "~" $ | workspaceDir "~" $ | ||
Line 241: | Line 291: | ||
-- ability to toggle between fullscreen | -- ability to toggle between fullscreen | ||
toggleLayouts (noBorders Full) $ | TL.toggleLayouts (noBorders Full) $ | ||
-- toggle vertical/horizontal layout reflection | |||
mkToggle (single REFLECTX) $ | |||
mkToggle (single REFLECTY) $ | |||
-- borders automatically disappear for fullscreen windows | -- borders automatically disappear for fullscreen windows | ||
smartBorders $ | smartBorders $ | ||
myTiled ||| | myTiled ||| | ||
Mirror myTiled | Mirror myTiled | ||
myShowWNameConfig = defaultSWNConfig | |||
{ swn_bgcolor = "blue" | |||
, swn_color = "yellow" | |||
, swn_fade = 0.3 | |||
} | |||
myTiled = | myTiled = named "Tall" $ ResizableTall 1 0.01 0.5 [] | ||
botGap (_,x,_,_) = x | botGap (_,x,_,_) = x | ||
setBotGap g (a,_,c,d) = (a,g,c,d) | setBotGap g (a,_,c,d) = (a,g,c,d) | ||
</haskell> | </haskell> |
Revision as of 18:10, 31 January 2008
My .xsession file:
xscreensaver-command -exit; ( xscreensaver & ) xpmroot ~/images/cherry-tree-wp.png gnome-panel & $HOME/bin/xmonad | hsstatus | dzen2 -ta r -fg '#a8a3f7' -bg '#3f3c6d'
hsstatus is a utility I wrote to add date/time, battery, and uptime information to the output from xmonad:
import System.IO
import System.Time
import System.Process
main :: IO ()
main = do hSetBuffering stdout LineBuffering
inp <- getLine
stat <- mkStatus inp
putStrLn stat
main
mkStatus :: String -> IO String
mkStatus inp = do time <- getTime
bat <- getBat
loadAvg <- getLoadAvg
return . concat $ [ inp, s
, time, s
, bat, s
, loadAvg ]
where s = " | "
getTime :: IO String
getTime = do cal <- (getClockTime >>= toCalendarTime)
return $ concat
[ show . (1+) . fromEnum . ctMonth $ cal
, "/", show . ctDay $ cal
, " ", show . fromMilitary . ctHour $ cal
, ":", padMin . ctMin $ cal
, " ", ampm . ctHour $ cal ]
where
fromMilitary 0 = 12
fromMilitary h | h > 12 = h - 12
| otherwise = h
padMin m | m < 10 = '0' : (show m)
| otherwise = show m
ampm h | h < 12 = "AM"
| otherwise = "PM"
getBat :: IO String
getBat = do (_, out, _, proc) <- runInteractiveCommand "/usr/bin/acpi | sed -r 's/.*?: (.*%).*/\\1/; s/discharging, ([0-9]+%)/\\1-/; s/charging, ([0-9]+%)/\\1+/; s/charged, //'"
batInfo <- hGetLine out
waitForProcess proc
return batInfo
getLoadAvg :: IO String
getLoadAvg = do (_, out, _, proc) <- runInteractiveCommand "/usr/bin/uptime | sed 's/.*: //; s/,//g'"
uptimeInfo <- hGetLine out
waitForProcess proc
return uptimeInfo
My xmonad.hs:
import XMonad
import qualified XMonad.StackSet as W
import Graphics.X11.Xlib
import qualified Data.Map as M
import XMonad.Hooks.DynamicLog
import XMonad.Hooks.UrgencyHook
import XMonad.Hooks.ManageDocks
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.RotView
import XMonad.Actions.CycleWS
import qualified XMonad.Actions.FlexibleManipulate as Flex
import XMonad.Actions.SinkAll
import XMonad.Actions.Warp
import XMonad.Actions.Submap
import XMonad.Actions.Search
import XMonad.Prompt
import XMonad.Prompt.Man
import XMonad.Prompt.AppendFile
import XMonad.Prompt.Shell
import XMonad.Prompt.Input
main = xmonad $ byorgeyConfig
byorgeyConfig = myUrgencyHook $
defaultConfig
{ borderWidth = 2
, terminal = "urxvt-custom"
, workspaces = myWorkspaces
, defaultGaps = myGaps
, modMask = mod4Mask -- use Windoze key for mod
, normalBorderColor = "#dddddd"
, focusedBorderColor = "#0033ff"
, logHook = dynamicLogWithPP byorgeyPP
, mouseBindings = myMouseBindings
, keys = \c -> myKeys c `M.union` keys defaultConfig c
, manageHook = manageHook defaultConfig <+> myManageHook
, layoutHook = myLayoutHook
, focusFollowsMouse = False
}
-- have urgent events flash a yellow dzen bar with black text
myUrgencyHook = withUrgencyHook dzenUrgencyHook
{ args = ["-bg", "yellow", "-fg", "black"] }
-- define some custom workspace tags
myWorkspaces :: [String]
myWorkspaces = ["1:web", "2:irc", "3:code", "4:code", "5:ref" ]
++ ["6:write", "7:dvi"]
++ map show [8 .. 9 :: Int]
++ ["<", "=", ">"]
-- leave room at the top for the dzen status bar, and at the bottom
-- for the gnome-panel.
myGaps = [(18,24,0,0)]
myMouseBindings (XConfig {modMask = modm}) = M.fromList $
-- these two are normal...
[ ((modm, button1), (\w -> focus w >> mouseMoveWindow w))
, ((modm, button2), (\w -> focus w >> windows W.swapMaster))
-- but this one uses the FlexibleManipulate extension.
, ((modm, button3), (\w -> focus w >> Flex.mouseWindow Flex.linear w)) ]
-- my custom keybindings.
myKeys conf@(XConfig {modMask = modm}) = M.fromList $
[ ((modm .|. shiftMask, xK_x ), spawn (terminal byorgeyConfig))
, ((modm .|. shiftMask, xK_a ), kill)
-- toggle the bottom gap (to hide/show the gnome panel)
, ((modm , xK_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))
, ((controlMask .|. shiftMask, xK_s ), sinkAll)
]
++
-- mod-[1..9] %! Switch to workspace N
-- mod-shift-[1..9] %! Move client to workspace N
[ ((m .|. modm, k), windows $ f i)
| (i, k) <- zip (XMonad.workspaces conf) ([xK_1 .. xK_9] ++ [xK_0,xK_minus, xK_equal])
, (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)]]
++
-- rotate workspaces.
[ ((modm, xK_Right), nextWS )
, ((modm, xK_Left ), prevWS )
, ((modm .|. shiftMask, xK_Right), shiftToNext )
, ((modm .|. shiftMask, xK_Left ), shiftToPrev )
, ((modm .|. shiftMask .|. controlMask, xK_Right), shiftToNext >> nextWS )
, ((modm .|. shiftMask .|. controlMask, xK_Left ), shiftToPrev >> prevWS )
, ((modm .|. controlMask, xK_Right), rotView True)
, ((modm .|. controlMask, xK_Left ), rotView False)
-- expand/shrink windows
, ((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")
-- bainsh the pointer
, ((modm .|. shiftMask, xK_b), warpToWindow 1 1)
-- some programs to start with keybindings.
, ((modm .|. shiftMask, xK_f), spawn "firefox")
, ((modm .|. shiftMask, xK_c), spawn "xchat")
, ((modm .|. shiftMask, xK_g), spawn "gimp")
, ((modm .|. shiftMask, xK_m), spawn "rhythmbox")
, ((modm .|. shiftMask, xK_n), spawn "gksudo network-admin")
, ((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.
, ((controlMask, xK_Right), sendMessage $ Go R)
, ((controlMask, xK_Left ), sendMessage $ Go L)
, ((controlMask, xK_Up ), sendMessage $ Go U)
, ((controlMask, xK_Down ), sendMessage $ Go D)
, ((shiftMask .|. controlMask, xK_Right), sendMessage $ Swap R)
, ((shiftMask .|. controlMask, xK_Left ), sendMessage $ Swap L)
, ((shiftMask .|. controlMask, xK_Up ), sendMessage $ Swap U)
, ((shiftMask .|. controlMask, xK_Down ), sendMessage $ Swap D)
-- toggles: fullscreen, flip x, flip y
, ((modm .|. controlMask, xK_space), sendMessage TL.ToggleLayout)
, ((modm .|. controlMask, xK_x), sendMessage $ Toggle REFLECTX)
, ((modm .|. controlMask, xK_y), sendMessage $ Toggle REFLECTY)
-- some prompts.
-- ability to change the working dir for a workspace.
, ((modm .|. controlMask, xK_d), changeDir myXPConfig)
-- man page prompt
, ((modm .|. controlMask, xK_m), manPrompt myXPConfig)
-- add single lines to my NOTES file from a prompt.
, ((modm .|. controlMask, xK_n), appendFilePrompt myXPConfig "/home/brent/misc/NOTES")
-- shell prompt.
, ((modm .|. controlMask, xK_s), shellPrompt myXPConfig)
-- some searches.
, ((modm , xK_slash), submap . mySearchMap $ myPromptSearch)
, ((modm .|. controlMask, xK_slash), submap . mySearchMap $ mySelectSearch)
-- some random utilities.
, ((modm .|. controlMask, xK_c), spawn "dzen-cal") -- calendar
-- todos.
, ((modm .|. controlMask, xK_t), submap . M.fromList $
[ ((0, xK_a), appendFilePrompt myXPConfig "/home/brent/misc/TODO")
, ((0, xK_l), spawn "dzen-show-todos")
, ((0, xK_e), spawn "emacs ~/misc/TODO")
, ((0, xK_u), spawn "cp ~/misc/TODO.backup ~/misc/TODO ; dzen-show-todos")
]
++
[ ((0, key), spawn ("del-todo " ++ show n ++ " ; dzen-show-todos")) |
(key, n) <- zip ([xK_1 .. xK_9] ++ [xK_0]) ([1..10]) ]
)
]
mySearchMap method = M.fromList $
[ ((0, xK_g), method google)
, ((0, xK_w), method wikipedia)
, ((0, xK_h), method hoogle)
, ((0, xK_s), method scholar)
, ((0, xK_m), method mathworld)
]
myPromptSearch eng = inputPrompt myXPConfig "Search" ?+ \s ->
(io (search "firefox" eng s) >> viewWeb)
mySelectSearch eng = selectSearch "firefox" eng >> viewWeb
viewWeb = windows (W.greedyView "1:web")
-- some nice colors for the prompt windows to match the dzen status bar.
myXPConfig = defaultXPConfig
{ fgColor = "#a8a3f7"
, bgColor = "#3f3c6d"
}
-- specify some additional applications which should always float.
myManageHook :: ManageHook
myManageHook = composeAll $
[ className =? c --> doFloat | c <- myFloats ]
++
[ className =? "Rhythmbox" --> doF (W.shift "=")
, className =? "XDvi" --> doF (W.shift "7:dvi")
, manageDocks
]
where myFloats = ["Volume", "XClock", "Network-admin", "Xmessage"]
-- specify a custom layout hook.
myLayoutHook =
-- show workspace names when switching.
showWName' myShowWNameConfig $
-- workspace 1 starts in Full mode and can switch to tiled.
onWorkspace "1:web" (smartBorders (Full ||| myTiled)) $
-- start all workspaces in my home directory, with the ability
-- to switch to a new working dir.
workspaceDir "~" $
-- navigate directionally rather than with mod-j/k
configurableNavigation (navigateColor "#00aa00") $
-- ability to toggle between fullscreen
TL.toggleLayouts (noBorders Full) $
-- toggle vertical/horizontal layout reflection
mkToggle (single REFLECTX) $
mkToggle (single REFLECTY) $
-- borders automatically disappear for fullscreen windows
smartBorders $
myTiled |||
Mirror myTiled
myShowWNameConfig = defaultSWNConfig
{ swn_bgcolor = "blue"
, swn_color = "yellow"
, swn_fade = 0.3
}
myTiled = named "Tall" $ ResizableTall 1 0.01 0.5 []
botGap (_,x,_,_) = x
setBotGap g (a,_,c,d) = (a,g,c,d)