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

From HaskellWiki
< Xmonad‎ | Config archive
Revision as of 02:21, 30 October 2008 by Byorgey (talk | contribs) (update my darcs xmonad.hs)
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.

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.TwoPane
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.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
import XMonad.Actions.CycleRecentWS
                                   -- (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 = ["wb", "ir", "c1", "c2", "rf" ]
               ++ ["wr", "dv", "pn", "pl"]
               ++ ["0","-","=","[","]","\\"]

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

-- 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)
    , ("M-S-b", spawn "urxvt-big")

      -- 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)
--    , ("M-a", cycleRecentWS [xK_Super_L] xK_a xK_s)    -- this seems to be broken on this laptop

    -- 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-3.0" (className =? "Firefox-bin")) -- (21)
    , ("M-x g", spawn "gimp")                                   -- (0)
    , ("M-x m", spawn "rhythmbox")                              -- (0)
    , ("M-x t", spawn "xclock -update 1")                       -- (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 "network-admin" >> spawn (terminal conf ++ " -e 'watch ifconfig'"))
    , ("M-c v", spawn "gnome-volume-control --class=Volume")    -- (0)
    , ("M-c k", spawn "xkill")

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

    -- switch to urgent window
    , ("M-s", focusUrgent)

    -- 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")
    , ("M-p x", appendFilePrompt myXPConfig "/home/brent/foo/BLAH")
      -- 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 "wb"
--   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 "wb")                           -- (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 "dv")      -- (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"
                     , "gnome-search-tool"
                     ]
          myFloatTitles = ["Bridge Bid", "xbuffy"]

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

    -- start all workspaces in my home directory, with the ability
    -- to switch to a new working dir.                          -- (10,11)
    workspaceDir "~" $

--    modWorkspace "plan"  (workspaceDir "~/org") $
--    modWorkspace "=" (workspaceDir "~/xmonad") $

    -- 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 ["wb","ir"] (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)
    TwoPane (3/100) (1/2)

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

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