Xmonad/Config archive/Brent Yorgey's xmonad.hs

From HaskellWiki
< Xmonad‎ | Config archive
Revision as of 19:01, 22 December 2007 by Byorgey (talk | contribs) (update to my current config.)
Jump to navigation Jump to search

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.

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
import XMonad.Layout.NoBorders
import XMonad.Layout.Tabbed
import XMonad.Layout.ResizableTile
import XMonad.Layout.WindowNavigation
import XMonad.Layout.ToggleLayouts
import XMonad.Layout.Named
import XMonad.Layout.PerWorkspace
import XMonad.Layout.WorkspaceDir

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.NoBorders

import XMonad.Prompt
import XMonad.Prompt.Man
import XMonad.Prompt.AppendFile
import XMonad.Prompt.Shell
import XMonad.Prompt.Input
import XMonad.Util.Search

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
       }

-- 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)]

-- define a custom pretty-print mode for DynamicLog
byorgeyPP :: PP
byorgeyPP = defaultPP { ppHiddenNoWindows = showNamedWorkspaces
                      , ppHidden  = dzenColor "black"  "#a8a3f7" . pad
                      , ppCurrent = dzenColor "yellow" "#a8a3f7" . pad
                      , ppUrgent  = dzenColor "red"    "yellow"
                      , ppSep     = " | "
                      , ppWsSep   = ""
                      , ppTitle   = shorten 65
                      , ppOrder   = reverse
                      }

-- Always show workspaces with special names.  Other workspaces
--   are only shown when they contain windows.
showNamedWorkspaces wsId = if (':' `elem` wsId)
                               then pad wsId
                               else ""

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")

    -- banish 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)

    -- toggle to fullscreen.
    , ((modm .|. controlMask, xK_space), sendMessage ToggleLayout)

    -- 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/NOTES")
      -- shell prompt.
    , ((modm .|. controlMask, xK_s), shellPrompt myXPConfig)

      -- some searches.
    , ((modm .|. controlMask, xK_slash), submap . M.fromList $
        [ ((0, xK_g), mySearch google)
        , ((0, xK_w), mySearch wikipedia)
        , ((0, xK_h), mySearch hoogle)
        ])

    -- 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/TODO")
        , ((0, xK_l),    spawn "dzen-show-todos")
        , ((0, xK_e),    spawn "emacs ~/TODO")
        , ((0, xK_u),    spawn "cp ~/TODO.backup ~/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]) ]
      )
    ]

mySearch eng = inputPrompt myXPConfig "Search" ?+ \s ->
               (io (search "firefox" eng s) >>
                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 "=")
                   , manageDocks
                   ]
    where myFloats = ["Volume", "XClock", "Network-admin"]

-- specify a custom layout hook.
myLayoutHook =
    -- 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
    toggleLayouts (noBorders Full) $

    -- borders automatically disappear for fullscreen windows
    smartBorders $
        myTiled |||
        Mirror myTiled |||
        noBorders myTiled

myTiled  = Named "Tall" $ ResizableTall 1 0.03 0.5 []

botGap (_,x,_,_) = x
setBotGap g (a,_,c,d) = (a,g,c,d)