John-yates-xmonad.hs

From HaskellWiki
Revision as of 21:05, 7 November 2011 by Gwern (talk | contribs) (Reverted edits by LonnieGaudette (Talk); changed back to last version by Jsyjr)
(diff) ← Older revision | Latest revision (diff) | Newer revision → (diff)
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.
import XMonad
import XMonad.Config.Gnome
import XMonad.Hooks.DynamicLog
import XMonad.Hooks.EwmhDesktops
import XMonad.Util.Run(spawnPipe)
import System.IO

import qualified Data.Map as M

--  colors match Ubuntu Human theme and Gnome panels
selected   = "'#fad184'"
background = "'#efebe7'"
foreground = "'#000000'"

-- height matches Ubuntu top Gnome panel
barHeight = "24"

--  font intended to match Ubuntu default application font
appFontXft = "'xft\
                \:Sans\
                \:pixelsize=14\
                \:weight=regular\
                \:width=semicondensed\
                \:dpi=96\
                \:hinting=true\
                \:hintstyle=hintslight\
                \:antialias=true\
                \:rgba=rgb\
                \:lcdfilter=lcdlight\
             \'"

-- currently dzen2 compiled locally to get xft support
-- (-e prevents loss of title if naive user clicks on dzen2)
myDzenTitleBar =
    "dzen2\
        \ -ta l\
        \ -x 400 -w 900 -y 0\
        \ -e 'entertitle=uncollapse'\
        \ -h  " ++ barHeight  ++ "\
        \ -bg " ++ background ++ "\
        \ -fg " ++ foreground ++ "\
        \ -fn " ++ appFontXft

-- dmenu patched and compiled locally to add xft support
myDmenuTitleBar =
    "exec `dmenu_path | dmenu\
        \ -p 'Run:'\
        \ -i\
        \ -bh " ++ barHeight  ++ "\
        \ -nb " ++ background ++ "\
        \ -nf " ++ foreground ++ "\
        \ -sb " ++ selected   ++ "\
        \ -fn " ++ appFontXft ++ "\
    \`"


main = do
    xmproc <- spawnPipe myDzenTitleBar

    xmonad $ gnomeConfig
        { modMask = mod4Mask     -- Rebind Mod to Windows key
        , logHook    = myLogHookWithPP $ defaultPP
                         { ppOutput = hPutStrLn xmproc
                         , ppOrder = take 1 . drop 2
                         }
        , keys       = myKeys
        }
    where

myLogHookWithPP :: PP -> X ()
myLogHookWithPP pp = do
    ewmhDesktopsLogHook
    dynamicLogWithPP pp

defKeys    = keys defaultConfig
delKeys x  = foldr M.delete           (defKeys x) (toRemove x)
myKeys x   = foldr (uncurry M.insert) (delKeys x) (toAdd    x)

-- remove some of the default key bindings
toRemove x =
    [ (modMask x              , xK_p  )
    , (modMask x .|. shiftMask, xK_q  ) -- don't strand naive users
    ]

toAdd x   =
    [ ((modMask x              , xK_p ), spawn myDmenuTitleBar)
    ]