Xmonad/Config archive/nattfodd's xmonad.hs

From HaskellWiki
< Xmonad‎ | Config archive
Revision as of 11:14, 22 November 2007 by Nattfodd (talk | contribs)
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.Layouts
import XMonad.Operations
import XMonad.Hooks.DynamicLog
import qualified Data.Map as M
import Graphics.X11
import qualified XMonad.StackSet as W
import Data.Bits ((.|.))
import Data.Ratio ((%))
import System.IO

-- XMonadContrib
-- import XMonad.Util.Dzen
import XMonad.Layout.NoBorders
import XMonad.Hooks.UrgencyHook
import XMonad.Util.EZConfig
import XMonad.Util.Run


main = do
    h <- spawnPipe ("dzen2" ++ " " ++ flags)
    xmonad $ defaultConfig
        { workspaces         = workspaces'
        , defaultGaps        = [(14,0,0,0)]
        , layoutHook         = layoutHook'
        , terminal           = "/home/heimdall/scripts/urxvt"
        , normalBorderColor  = "#dddddd"
        , logHook            = dynamicLogWithPP defaultPP
                                { ppOutput = hPutStrLn h }
        , focusedBorderColor = "#aa0000" }
        `additionalKeys` keys'
        where
            fg    = "'grey70'"
            bg    = "'#2c2c32'"
            fn    = "'-*-profont-*-*-*-*-12-*-*-*-*-*-*'"
            flags = "-e '' -w 700 -ta l -fg " ++ fg ++ " -bg " ++ bg ++ " -fn " ++ fn

workspaces' = map show [1 .. 13 :: Int]


layoutHook' =     tiled
              ||| Mirror tiled
              ||| noBorders Full
              where
                  tiled   = Tall nmaster delta ratio
                  nmaster = 1     -- The default number of windows in the master pane
                  ratio   = 1%2   -- Default proportion of screen occupied by master pane
                  delta   = 5%100 -- Percent of screen to increment by when resizing panes

keys' = [((m .|. mod1Mask, k), windows $ f i)
            | (i, k) <- zip workspaces' [0x26,0xe9,0x22,0x27,0x28,0x2d,0xe8,0x5f,0xe7,0xe0,xK_a,xK_z,xK_e,xK_r]
            , (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)]]
        ++ [((mod1Mask, 0x3b), sendMessage (IncMasterN (-1)))]