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

From HaskellWiki
< Xmonad‎ | Config archive
Revision as of 12:22, 27 February 2008 by Byorgey (talk | contribs)
Jump to navigation Jump to search

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:

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.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.Actions.WindowGo

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

import XMonad.Util.WorkspaceCompare
import XMonad.Util.Loggers
import XMonad.Util.EZConfig
import XMonad.Util.Scratchpad

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
           { ppExtras = [ date "%a %b %d  %I:%M %p"
                        , battery
                        , loadAvg
                        ]
           , ppOrder = \(ws:l:t:exs) -> [t,l,ws]++exs
           }
       , mouseBindings      = myMouseBindings
       , manageHook         = manageHook defaultConfig <+> myManageHook
       , layoutHook         = myLayoutHook
       , focusFollowsMouse  = False
       , startupHook        = do checkKeymap byorgeyConfig $
                                   myKeys
       }
       `additionalKeysP` myKeys


-- 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 = ["web", "irc", "code", "code2", "ref" ]
               ++ ["write", "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)]

-- my custom mouse bindings.
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 = myKeymap byorgeyConfig

myKeymap conf =

    -- mod-[1..9] %! Switch to workspace N
    -- mod-shift-[1..9] %! Move client to workspace N
    [ (m ++ "M-" ++ [k], windows $ f i)
        | (i, k) <- zip (XMonad.workspaces conf) "1234567890-="
        , (f, m) <- [(W.greedyView, ""), (W.shift, "S-")]
    ]

    ++
    [ ("M-x x", spawn $ terminal conf)

      -- in conjunction with manageHook, open a small temporary
      -- floating terminal
    , ("M-x s", scratchpadSpawnAction conf)

    , ("M-S-a", kill)

    -- toggle the bottom gap (to hide/show the gnome panel)
    , ("M-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))

    -- rotate workspaces.
    , ("M-<R>",     nextWS )
    , ("M-<L>",     prevWS )
    , ("M-S-<R>",   shiftToNext )
    , ("M-S-<L>",   shiftToPrev )
    , ("M-S-C-<R>", shiftToNext >> nextWS )
    , ("M-S-C-<L>", shiftToPrev >> prevWS )
    , ("M-C-<R>",   moveTo Next NonEmptyWS)
    , ("M-C-<L>",   moveTo Prev NonEmptyWS)

    , ("M-f",       moveTo Next EmptyWS)
    , ("M-d",       moveTo Prev EmptyWS)

    -- expand/shrink windows
    , ("M-r k", sendMessage MirrorExpand)
    , ("M-r j", sendMessage MirrorShrink)
    , ("M-r h", sendMessage Shrink)
    , ("M-r l", sendMessage Expand)

    -- switch to previous workspace
    , ("M-z", toggleWS)

    -- lock the screen with xscreensaver
    , ("M-S-l", spawn "xscreensaver-command -lock")

    -- bainsh the pointer
    , ("M-S-b", warpToWindow 1 1)

    -- some programs to start with keybindings.
    , ("M-x f", runOrRaise "firefox" (className =? "Firefox-bin"))
    , ("M-x g", spawn "gimp")
    , ("M-x m", spawn "rhythmbox")
    , ("M-x t", spawn "xclock")

    -- configuration.
    , ("M-c x", spawn "em ~/.xmonad/xmonad.hs")
    , ("M-c n", spawn "gksudo network-admin")
    , ("M-c v", spawn "gnome-volume-control --class=Volume")

    -- window navigation keybindings.
    , ("C-<R>", sendMessage $ Go R)
    , ("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)

    -- toggles: fullscreen, flip x, flip y
    , ("M-C-<Space>", sendMessage TL.ToggleLayout)
    , ("M-C-x",       sendMessage $ Toggle REFLECTX)
    , ("M-C-y",       sendMessage $ Toggle REFLECTY)

    -- some prompts.
      -- ability to change the working dir for a workspace.
    , ("M-p d", changeDir myXPConfig)
      -- man page prompt
    , ("M-p m", manPrompt myXPConfig)
      -- add single lines to my NOTES file from a prompt.
    , ("M-p n", appendFilePrompt myXPConfig "/home/brent/misc/NOTES")
      -- shell prompt.
    , ("M-p s", shellPrompt myXPConfig)
    , ("M-p p", spawn "exe=`dmenu_path | dmenu` && eval \"exec $exe\"")

      -- some searches.
    , ("M-/", submap . mySearchMap $ myPromptSearch)
    , ("M-C-/", submap . mySearchMap $ mySelectSearch)

    -- some random utilities.
    , ("M-C-c", spawn "dzen-cal")  -- calendar

    -- todos.
    , ("M-C-t a", appendFilePrompt myXPConfig "/home/brent/misc/TODO")
    , ("M-C-t l", spawn "dzen-show-todos")
    , ("M-C-t e", spawn "emacs ~/misc/TODO")
    , ("M-C-t u", spawn "cp ~/misc/TODO.backup ~/misc/TODO ; dzen-show-todos")    ]
    ++
    [ ("M-C-t " ++ [key], spawn ("del-todo " ++ show n ++ " ; dzen-show-todos"))
      | (key, n) <- zip "1234567890" [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 "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 "dvi")
                   , manageDocks
                   , scratchpadManageHookDefault
                   ]
    where myFloats = ["Volume", "XClock", "Network-admin", "Xmessage"]

doRectFloat :: W.RationalRect -> ManageHook
doRectFloat r = ask >>= \w -> doF (W.float w r)

scratchpadRect :: W.RationalRect
scratchpadRect = W.RationalRect 0.25 0.375 0.5 0.25

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

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