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

From HaskellWiki
Jump to navigation Jump to search
(EZConfig)
(latest version of my config -- requires 1-minute-ago darcs)
Line 11: Line 11:
 
import Data.Ratio ((%))
 
import Data.Ratio ((%))
 
import Graphics.X11.Xlib
 
import Graphics.X11.Xlib
  +
import Graphics.X11.Xlib.Extras
   
 
-- Contribs
 
-- Contribs
Line 24: Line 25:
   
 
-- Get ready!
 
-- Get ready!
 
main = xmonad $ withUrgencyHook dzenUrgencyHook { args = ["-bg", "darkgreen", "-xs", "1"] }
main = xmonad $ defaultConfig
+
$ defaultConfig
 
{ workspaces = workspaces'
 
{ workspaces = workspaces'
 
, modMask = modMask'
 
, modMask = modMask'
Line 31: Line 33:
 
, terminal = "urxvtc || urxvt"
 
, terminal = "urxvtc || urxvt"
 
, mouseBindings = mouseBindings'
 
, mouseBindings = mouseBindings'
  +
, eventHook = noFollow
  +
, logHook = withUrgents (io . print)
 
}
 
}
 
`additionalKeys` keys'
 
`additionalKeys` keys'
Line 38: Line 42:
 
workspaces' = map show $ [1 .. 9 :: Int] ++ [0]
 
workspaces' = map show $ [1 .. 9 :: Int] ++ [0]
   
  +
layoutHook' =
layoutHook' = Layout $ withUrgencyHook dzenUrgencyHook { args = ["-bg", "darkgreen", "-xs", "1"] }
 
  +
configurableNavigation noNavigateBorders $
$ configurableNavigation noNavigateBorders
 
$ layouts
+
layouts
   
layouts = tiled
+
layouts =
||| Mirror tiled
+
tiled
  +
||| Mirror tiled
||| noBorders (tabbed shrinkText defaultTConf { fontName = "fixed" })
+
||| noBorders (tabbed shrinkText
  +
defaultTConf { fontName = "-*-terminus-medium-r-normal--12-*-iso8859-1" })
 
where
 
where
 
tiled = Tall nmaster delta ratio
 
tiled = Tall nmaster delta ratio
Line 50: Line 56:
 
ratio = 1%2 -- Default proportion of screen occupied by master pane
 
ratio = 1%2 -- Default proportion of screen occupied by master pane
 
delta = 3%100 -- Percent of screen to increment by when resizing panes
 
delta = 3%100 -- Percent of screen to increment by when resizing panes
  +
  +
noFollow CrossingEvent {} = return False
  +
noFollow _ = return True
   
 
keys' =
 
keys' =
[ ((modMask' .|. shiftMask, xK_d ), spawn "date | dzen2 -p 2 -xs 1") -- %! Print current date
+
[ ((modMask' .|. shiftMask, xK_d ), spawn "echo date | dzen2 -p 2 -xs 1") -- %! Print current date
, ((modMask' .|. mod1Mask, xK_m ), submap $ M.fromList -- %! MPD prefix key
+
, ((modMask' .|. mod1Mask, xK_m ), submap $ M.fromList -- %! MPD prefix key
[ ((modMask' .|. mod1Mask, xK_p ), spawn "mpc toggle") -- %! MPD: Toggle pause/play
+
[ ((modMask' .|. mod1Mask, xK_p ), spawn "mpc toggle") -- %! MPD: Toggle pause/play
, ((modMask' .|. mod1Mask, xK_m ), spawn "mpc | head -1 | dzen2 -p 2 -xs 1") -- %! MPD: Print the currently playing song
+
, ((modMask' .|. mod1Mask, xK_m ), spawn "mpc | head -1 | dzen2 -p 2 -xs 1") -- %! MPD: Print the currently playing song
, ((modMask' .|. mod1Mask, xK_comma ), spawn "mpc prev") -- %! MPD: Go to previous song
+
, ((modMask' .|. mod1Mask, xK_comma ), spawn "mpc prev") -- %! MPD: Go to previous song
, ((modMask' .|. mod1Mask, xK_period), spawn "mpc next") -- %! MPD: Go to next song
+
, ((modMask' .|. mod1Mask, xK_period ), spawn "mpc next") -- %! MPD: Go to next song
 
] )
 
] )
, ((modMask' .|. mod1Mask, xK_space ), withFocused $ \w -> hide w >> reveal w >> setFocusX w) -- %! force the window to redraw itself
+
, ((modMask' .|. mod1Mask, xK_space ), withFocused $ \w -> hide w >> reveal w >> setFocusX w) -- %! force the window to redraw itself
, ((modMask' , xK_i ), prevWS)
+
, ((modMask' , xK_i ), prevWS)
, ((modMask' , xK_o ), nextWS)
+
, ((modMask' , xK_o ), nextWS)
, ((modMask' .|. shiftMask, xK_i ), shiftToPrev)
+
, ((modMask' .|. shiftMask, xK_i ), shiftToPrev)
, ((modMask' .|. shiftMask, xK_o ), shiftToNext)
+
, ((modMask' .|. shiftMask, xK_o ), shiftToNext)
, ((modMask', xK_a ), sendMessage $ Go L)
+
, ((modMask', xK_a ), sendMessage $ Go L)
, ((modMask', xK_w ), sendMessage $ Go U)
+
, ((modMask', xK_w ), sendMessage $ Go U)
, ((modMask', xK_s ), sendMessage $ Go D)
+
, ((modMask', xK_s ), sendMessage $ Go D)
, ((modMask', xK_d ), sendMessage $ Go R)
+
, ((modMask', xK_d ), sendMessage $ Go R)
, ((modMask' .|. shiftMask, xK_g ), gotoMenu)
+
, ((modMask' .|. shiftMask, xK_g ), gotoMenu)
, ((modMask' .|. shiftMask, xK_b ), bringMenu)
+
, ((modMask' .|. shiftMask, xK_b ), bringMenu)
 
, ((modMask' , xK_BackSpace), focusUrgent)
 
, ((modMask' , xK_BackSpace), focusUrgent)
 
]
 
]
 
++
 
++
-- modMask'-[1..9] %! Switch to workspace N
+
-- modMask'-[1..0] %! Switch to workspace N
-- modMask'-shift-[1..9] %! Move client to workspace N
+
-- modMask'-shift-[1..0] %! Move client to workspace N
 
[((m .|. modMask', k), windows $ f i)
 
[((m .|. modMask', k), windows $ f i)
 
| (i, k) <- zip workspaces' $ [xK_1 .. xK_9] ++ [xK_0]
 
| (i, k) <- zip workspaces' $ [xK_1 .. xK_9] ++ [xK_0]
, (f, m) <- [(W.view, 0), (W.shift, shiftMask)]]
+
, (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)]]
 
++
 
++
 
-- modMask'-{e,r} %! Switch to physical/Xinerama screens 1 or 2
 
-- modMask'-{e,r} %! Switch to physical/Xinerama screens 1 or 2

Revision as of 04:44, 12 November 2007

-- XMonad Core
import XMonad
import XMonad.Layouts
import XMonad.Operations
import qualified XMonad.StackSet as W

-- GHC hierarchical libraries
import Data.Bits ((.|.))
import qualified Data.Map as M
import Data.Ratio ((%))
import Graphics.X11.Xlib
import Graphics.X11.Xlib.Extras

-- Contribs
import XMonad.Actions.CycleWS
import XMonad.Actions.SwapWorkspaces
import XMonad.Actions.Submap
import XMonad.Actions.WindowBringer
import XMonad.Hooks.UrgencyHook
import XMonad.Layout.NoBorders
import XMonad.Layout.Tabbed
import XMonad.Layout.WindowNavigation
import XMonad.Util.EZConfig

-- Get ready!
main = xmonad $ withUrgencyHook dzenUrgencyHook { args = ["-bg", "darkgreen", "-xs", "1"] }
              $ defaultConfig
                { workspaces     = workspaces'
                , modMask        = modMask'
                , numlockMask    = 0
                , layoutHook     = layoutHook'
                , terminal       = "urxvtc || urxvt"
                , mouseBindings  = mouseBindings'
                , eventHook      = noFollow
                , logHook        = withUrgents (io . print)
                }
                `additionalKeys` keys'

modMask'    = mod4Mask

workspaces' = map show $ [1 .. 9 :: Int] ++ [0]

layoutHook' =
    configurableNavigation noNavigateBorders $
    layouts

layouts =
        tiled
    ||| Mirror tiled
    ||| noBorders (tabbed shrinkText
                          defaultTConf { fontName = "-*-terminus-medium-r-normal--12-*-iso8859-1" })
  where
     tiled   = Tall nmaster delta ratio
     nmaster = 2     -- The default number of windows in the master pane
     ratio   = 1%2   -- Default proportion of screen occupied by master pane
     delta   = 3%100 -- Percent of screen to increment by when resizing panes

noFollow CrossingEvent {} = return False
noFollow _                = return True

keys' =
    [ ((modMask' .|. shiftMask, xK_d        ), spawn "echo date | dzen2 -p 2 -xs 1") -- %! Print current date
    , ((modMask' .|. mod1Mask,  xK_m        ), submap $ M.fromList -- %! MPD prefix key
        [ ((modMask' .|. mod1Mask,  xK_p        ), spawn "mpc toggle") -- %! MPD: Toggle pause/play
        , ((modMask' .|. mod1Mask,  xK_m        ), spawn "mpc | head -1 | dzen2 -p 2 -xs 1") -- %! MPD: Print the currently playing song
        , ((modMask' .|. mod1Mask,  xK_comma    ), spawn "mpc prev") -- %! MPD: Go to previous song
        , ((modMask' .|. mod1Mask,  xK_period   ), spawn "mpc next") -- %! MPD: Go to next song
        ] )
    , ((modMask' .|. mod1Mask,  xK_space    ), withFocused $ \w -> hide w >> reveal w >> setFocusX w) -- %! force the window to redraw itself
    , ((modMask'              , xK_i        ), prevWS)
    , ((modMask'              , xK_o        ), nextWS)
    , ((modMask' .|. shiftMask, xK_i        ), shiftToPrev)
    , ((modMask' .|. shiftMask, xK_o        ), shiftToNext)
    , ((modMask',               xK_a        ), sendMessage $ Go L)
    , ((modMask',               xK_w        ), sendMessage $ Go U)
    , ((modMask',               xK_s        ), sendMessage $ Go D)
    , ((modMask',               xK_d        ), sendMessage $ Go R)
    , ((modMask' .|. shiftMask, xK_g        ), gotoMenu)
    , ((modMask' .|. shiftMask, xK_b        ), bringMenu)
    , ((modMask'              , xK_BackSpace), focusUrgent)
    ]
    ++
    -- modMask'-[1..0] %! Switch to workspace N
    -- modMask'-shift-[1..0] %! Move client to workspace N
    [((m .|. modMask', k), windows $ f i)
        | (i, k) <- zip workspaces' $ [xK_1 .. xK_9] ++ [xK_0]
        , (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)]]
    ++
    -- modMask'-{e,r} %! Switch to physical/Xinerama screens 1 or 2
    -- modMask'-shift-{e,r} %! Move client to screen 1 or 2
    [((m .|. modMask', key), screenWorkspace sc >>= flip whenJust (windows . f))
        | (key, sc) <- zip [xK_e, xK_r] [0..]
        , (f, m) <- [(W.view, 0), (W.shift, shiftMask)]]
    ++
    [((modMask' .|. mod1Mask, k), windows $ swapWithCurrent i)
        | (i, k) <- zip workspaces' $ [xK_1 .. xK_9] ++ [xK_0]]

-- I have "Emulate three button mouse" turned on in Darwin X11, so mod4 (Apple) right-clicks.
-- Use ctrl-shift, instead.
mouseBindings' (XConfig {XMonad.modMask = modMask}) = M.fromList $
    -- ctrl-shift-button1 %! Set the window to floating mode and move by dragging
    [ ((controlMask .|. shiftMask, button1), (\w -> focus w >> mouseMoveWindow w))

    -- ctrl-shift-button2 %! Raise the window to the top of the stack
    , ((controlMask .|. shiftMask, button2), (\w -> focus w >> windows W.swapMaster))

    -- ctrl-shift-button3 %! Set the window to floating mode and resize by dragging
    , ((controlMask .|. shiftMask, button3), (\w -> focus w >> mouseResizeWindow w))
    ]