Difference between revisions of "Xmonad/Config archive/Brent Yorgey's xmonad.hs"

From HaskellWiki
Jump to navigation Jump to search
m (Data.Bits is now re-exported from XMonad)
(update to my current config.)
Line 2: Line 2:
 
import XMonad
 
import XMonad
 
import qualified XMonad.StackSet as W
 
import qualified XMonad.StackSet as W
import XMonad.Operations
 
 
 
import Graphics.X11.Xlib
 
import Graphics.X11.Xlib
   
 
import qualified Data.Map as M
 
import qualified Data.Map as M
   
import XMonad.ManageHook
 
 
import XMonad.Hooks.DynamicLog
 
import XMonad.Hooks.DynamicLog
  +
import XMonad.Hooks.UrgencyHook
  +
  +
import XMonad.Layout
 
import XMonad.Layout.NoBorders
 
import XMonad.Layout.NoBorders
import XMonad.Layouts
 
 
import XMonad.Layout.Tabbed
 
import XMonad.Layout.Tabbed
import qualified XMonad.Actions.FlexibleManipulate as Flex
 
 
import XMonad.Layout.ResizableTile
 
import XMonad.Layout.ResizableTile
import XMonad.Hooks.UrgencyHook
 
 
import XMonad.Layout.WindowNavigation
 
import XMonad.Layout.WindowNavigation
 
import XMonad.Layout.ToggleLayouts
 
import XMonad.Layout.ToggleLayouts
 
import XMonad.Layout.Named
 
import XMonad.Layout.Named
  +
import XMonad.Layout.PerWorkspace
  +
import XMonad.Layout.Accordion
  +
import XMonad.Layout.WorkspaceDir
   
 
import XMonad.Actions.RotView
 
import XMonad.Actions.RotView
 
import XMonad.Actions.CycleWS
 
import XMonad.Actions.CycleWS
  +
import qualified XMonad.Actions.FlexibleManipulate as Flex
  +
  +
import XMonad.Prompt
  +
import XMonad.Prompt.Man
  +
import XMonad.Prompt.AppendFile
  +
import XMonad.Prompt.Email
  +
import XMonad.Prompt.Shell
   
 
main = xmonad $ byorgeyConfig
 
main = xmonad $ byorgeyConfig
   
  +
byorgeyConfig = myUrgencyHook $
byorgeyConfig = withUrgencyHook dzenUrgencyHook { args = ["-bg", "yellow", "-fg", "black"] } $
 
 
defaultConfig
 
defaultConfig
 
{ borderWidth = 2
 
{ borderWidth = 2
 
, terminal = "urxvt-custom"
 
, terminal = "urxvt-custom"
, workspaces = ["1:web", "2:irc", "3:code", "4:code", "5:ref" ]
+
, workspaces = myWorkspaces
++ map show [6 .. 9 :: Int]
+
, defaultGaps = myGaps
, defaultGaps = [(18,0,0,0)]
+
, modMask = mod4Mask -- use Windoze key for mod
, modMask = mod4Mask
 
 
, normalBorderColor = "#dddddd"
 
, normalBorderColor = "#dddddd"
, focusedBorderColor = "#0033ff"
+
, focusedBorderColor = "#0033ff"
 
, logHook = dynamicLogWithPP byorgeyPP
 
, logHook = dynamicLogWithPP byorgeyPP
, mouseBindings = \(XConfig {modMask = modm}) -> M.fromList $
+
, mouseBindings = myMouseBindings
[ ((modm, button1), (\w -> focus w >> mouseMoveWindow w))
+
, keys = \c -> myKeys c `M.union` keys defaultConfig c
-- mod-button2 %! Raise the window to the top of the stack
 
, ((modm, button2), (\w -> focus w >> windows W.swapMaster))
 
-- mod-button3 %! Set the window to floating mode and resize by dragging
 
, ((modm, button3), (\w -> focus w >> Flex.mouseWindow Flex.linear w)) ]
 
, keys = \c -> mykeys c `M.union` keys defaultConfig c
 
 
, manageHook = manageHook defaultConfig <+> myManageHook
 
, manageHook = manageHook defaultConfig <+> myManageHook
, layoutHook = configurableNavigation (navigateColor "#00aa00") $
+
, layoutHook = myLayoutHook
toggleLayouts (noBorders Full) $
 
(smartBorders (tiled ||| Mirror tiled ||| tabbed shrinkText defaultTConf))
 
 
}
 
}
where
 
tiled = Named "RTall" $ ResizableTall 1 0.03 0.5 []
 
   
  +
-- have urgent events flash a yellow dzen bar with black text
mykeys (XConfig {modMask = modm}) = M.fromList $
 
  +
myUrgencyHook = withUrgencyHook dzenUrgencyHook
[ ((modm .|. shiftMask, xK_x ), spawn (terminal byorgeyConfig))
 
  +
{ args = ["-bg", "yellow", "-fg", "black"] }
, ((modm .|. shiftMask, xK_a ), kill)
 
-- rotate workspaces
 
, ((modm .|. controlMask, xK_Right), rotView True)
 
, ((modm .|. controlMask, xK_Left), rotView False)
 
 
, ((modm, xK_w), sendMessage MirrorExpand)
 
, ((modm, xK_s), sendMessage MirrorShrink)
 
   
-- switch to previous workspace
+
-- define some custom workspace tags
  +
myWorkspaces :: [String]
, ((modm, xK_z), toggleWS)
 
  +
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
-- lock the screen with xscreensaver
 
  +
-- for the gnome-panel.
, ((modm .|. shiftMask, xK_l), spawn "xscreensaver-command -lock")
 
  +
myGaps = [(18,24,0,0)]
   
  +
-- define a custom pretty-print mode for DynamicLog
-- some programs to start with keybindings.
 
  +
byorgeyPP :: PP
, ((modm .|. shiftMask, xK_f), spawn "firefox")
 
  +
byorgeyPP = defaultPP { ppHiddenNoWindows = showNamedWorkspaces
, ((modm .|. shiftMask, xK_n), spawn "gksudo network-admin")
 
  +
, ppHidden = dzenColor "black" "#a8a3f7" . pad
, ((modm .|. shiftMask, xK_c), spawn "xchat")
 
  +
, ppCurrent = dzenColor "yellow" "#a8a3f7" . pad
, ((modm .|. shiftMask, xK_v), spawn "gnome-volume-control --class=Volume")
 
, ((modm .|. shiftMask, xK_t), spawn "xclock")
+
, ppSep = " | "
, ((modm .|. shiftMask .|. controlMask, xK_t), spawn "xclock -update 1")
+
, ppWsSep = ""
  +
, ppTitle = shorten 80
  +
, 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)) ]
  +
  +
  +
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))
  +
  +
]
  +
  +
++
  +
-- 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")
  +
  +
-- some programs to start with keybindings.
  +
, ((modm .|. shiftMask, xK_f), spawn "firefox")
  +
, ((modm .|. shiftMask, xK_n), spawn "gksudo network-admin")
  +
, ((modm .|. shiftMask, xK_c), spawn "xchat")
  +
, ((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)
   
-- window navigation keybindings.
+
-- some prompts.
  +
-- ability to change the working dir for a workspace.
, ((modm, xK_Right), sendMessage $ Go R)
 
, ((modm, xK_Left ), sendMessage $ Go L)
+
, ((modm .|. controlMask, xK_d), changeDir myXPConfig)
  +
-- man page prompt
, ((modm, xK_Up ), sendMessage $ Go U)
 
, ((modm, xK_Down ), sendMessage $ Go D)
+
, ((modm .|. controlMask, xK_m), manPrompt myXPConfig)
  +
-- add single lines to my NOTES file from a prompt.
, ((modm .|. shiftMask, xK_Right), sendMessage $ Swap R)
 
, ((modm .|. shiftMask, xK_Left ), sendMessage $ Swap L)
+
, ((modm .|. controlMask, xK_n), appendFilePrompt myXPConfig "/home/brent/NOTES")
, ((modm .|. shiftMask, xK_Up ), sendMessage $ Swap U)
+
, ((modm .|. controlMask, xK_e), emailPrompt myXPConfig ["brent@localhost"])
, ((modm .|. shiftMask, xK_Down ), sendMessage $ Swap D)
+
, ((modm .|. controlMask, xK_s), shellPrompt myXPConfig)
  +
]
   
  +
-- some nice colors for the prompt windows to match the dzen status bar.
-- toggle to fullscreen.
 
  +
myXPConfig = defaultXPConfig
, ((modm .|. controlMask, xK_space), sendMessage ToggleLayout)
 
]
+
{ fgColor = "#a8a3f7"
  +
, bgColor = "#3f3c6d"
  +
}
   
  +
-- specify some additional applications which should always float.
 
myManageHook :: ManageHook
 
myManageHook :: ManageHook
myManageHook = composeAll [ className =? c --> doFloat | c <- myFloats ]
+
myManageHook = composeAll . concat $
  +
[ [ className =? c --> doFloat | c <- myFloats ]
where myFloats = ["Volume", "XClock", "Network-admin"]
 
  +
, [ resource =? r --> doIgnore | r <- myIgnore ] ]
  +
where myFloats = ["Volume", "XClock", "Network-admin"]
  +
myIgnore = ["gnome-panel"]
   
-- define a custom pretty-print mode for DynamicLog
+
-- specify a custom layout hook.
  +
myLayoutHook =
byorgeyPP :: PP
 
  +
-- workspace 1 starts in Full mode and can switch to tiled.
byorgeyPP = defaultPP { ppHiddenNoWindows = \wsId -> if (':' `elem` wsId) then wsId ++ " " else ""
 
  +
onWorkspace "1:web" (smartBorders (Full ||| myTiled)) $
, ppHidden = (++"*")
 
  +
, ppCurrent = dzenColor "black" "#a8a3f7" . (++"*")
 
  +
-- start all workspaces in my home directory, with the ability
, ppSep = " | "
 
  +
-- to switch to a new working dir.
, ppTitle = shorten 80
 
  +
workspaceDir "~" $
, ppOrder = reverse }
 
  +
  +
-- 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 |||
  +
tabbed shrinkText defaultTConf |||
  +
Accordion
  +
  +
myTiled = Named "RTall" $ ResizableTall 1 0.03 0.5 []
  +
  +
botGap (_,x,_,_) = x
  +
setBotGap g (a,_,c,d) = (a,g,c,d)
 
</haskell>
 
</haskell>

Revision as of 16:32, 10 December 2007

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.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.Accordion
import XMonad.Layout.WorkspaceDir

import XMonad.Actions.RotView
import XMonad.Actions.CycleWS
import qualified XMonad.Actions.FlexibleManipulate as Flex

import XMonad.Prompt
import XMonad.Prompt.Man
import XMonad.Prompt.AppendFile
import XMonad.Prompt.Email
import XMonad.Prompt.Shell

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
                      , ppSep     = " | "
                      , ppWsSep   = ""
                      , ppTitle   = shorten 80
                      , 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)) ]


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

    ]

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

    -- some programs to start with keybindings.
    , ((modm .|. shiftMask, xK_f), spawn "firefox")
    , ((modm .|. shiftMask, xK_n), spawn "gksudo network-admin")
    , ((modm .|. shiftMask, xK_c), spawn "xchat")
    , ((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")
    , ((modm .|. controlMask, xK_e), emailPrompt myXPConfig ["brent@localhost"])
    , ((modm .|. controlMask, xK_s), shellPrompt myXPConfig)
    ]

-- 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 . concat $
                   [ [ className =? c --> doFloat | c <- myFloats ]
                   , [ resource =? r --> doIgnore | r <- myIgnore ] ]
    where myFloats = ["Volume", "XClock", "Network-admin"]
          myIgnore = ["gnome-panel"]

-- 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 |||
        tabbed shrinkText defaultTConf |||
        Accordion

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

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