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

From HaskellWiki
Jump to navigation Jump to search
(initial contents)
 
 
(5 intermediate revisions by one other user not shown)
Line 1: Line 1:
  +
Things that are no different from standard are commented out to make it easier to scan for the interesting bits. Removed type signatures for the same reason. Obviously, neither is the case in my real Config.hs. ;)
<haskell>
 
-----------------------------------------------------------------------------
 
-- |
 
-- Module : Config.hs
 
-- Copyright : (c) Spencer Janssen 2007
 
-- License : BSD3-style (see LICENSE)
 
--
 
-- Maintainer : dons@galois.com
 
-- Stability : stable
 
-- Portability : portable
 
--
 
-- This module specifies configurable defaults for xmonad. If you change
 
-- values here, be sure to recompile and restart (mod-q) xmonad,
 
-- for the changes to take effect.
 
--
 
------------------------------------------------------------------------
 
   
  +
<haskell>
  +
{-
 
module Config where
 
module Config where
   
--
 
-- Useful imports
 
--
 
 
import XMonad
 
import XMonad
 
import Operations
 
import Operations
Line 29: Line 13:
 
import System.Exit
 
import System.Exit
 
import Graphics.X11.Xlib
 
import Graphics.X11.Xlib
  +
-}
   
-- % Extension-provided imports
 
 
import XMonadContrib.Dzen
 
import XMonadContrib.Dzen
 
import XMonadContrib.NoBorders
 
import XMonadContrib.NoBorders
Line 40: Line 24:
 
import XMonadContrib.WindowNavigation
 
import XMonadContrib.WindowNavigation
   
  +
-- Added workspace zero. Really, should append it to the end, as xmonad starts in `head workspaces`.
-- | The default number of workspaces (virtual screens) and their names.
 
-- By default we use numeric strings, but any string may be used as a
 
-- workspace name. The number of workspaces is determined by the length
 
-- of this list.
 
--
 
-- A tagging example:
 
--
 
-- > workspaces = ["web", "irc", "code" ] ++ map show [4..9]
 
--
 
workspaces :: [WorkspaceId]
 
 
workspaces = map show [0 .. 9 :: Int]
 
workspaces = map show [0 .. 9 :: Int]
   
  +
-- mod4 == apple/cmd key for me (per xmodmap)
-- | modMask lets you specify which modkey you want to use. The default
 
  +
modMask = mod4Mask
-- is mod1Mask ("left alt"). You may also consider using mod3Mask
 
-- ("right alt"), which does not conflict with emacs keybindings. The
 
-- "windows key" is usually mod4Mask.
 
--
 
modMask :: KeyMask
 
modMask = mod4Mask -- mod4Mask = cmd (see xev and my .Xmodmap)
 
   
-- | The mask for the numlock key. Numlock status is "masked" from the
+
-- apple doesn't have a numlock key
-- current modifier status, so the keybindings will work with numlock on or
 
-- off. You may need to change this on some systems.
 
--
 
-- You can find the numlock modifier by running "xmodmap" and looking for a
 
-- modifier with Num_Lock bound to it:
 
--
 
-- > $ xmodmap | grep Num
 
-- > mod2 Num_Lock (0x4d)
 
--
 
-- Set numlockMask = 0 if you don't have a numlock key, or want to treat
 
-- numlock status separately.
 
--
 
numlockMask :: KeyMask
 
 
numlockMask = 0
 
numlockMask = 0
   
  +
{-
-- | Width of the window border in pixels.
 
--
 
 
borderWidth :: Dimension
 
borderWidth :: Dimension
 
borderWidth = 1
 
borderWidth = 1
 
-- | Border colors for unfocused and focused windows, respectively.
 
--
 
 
normalBorderColor, focusedBorderColor :: String
 
normalBorderColor, focusedBorderColor :: String
 
normalBorderColor = "#dddddd"
 
normalBorderColor = "#dddddd"
 
focusedBorderColor = "#ff0000"
 
focusedBorderColor = "#ff0000"
 
-- | Default offset of drawable screen boundaries from each physical
 
-- screen. Anything non-zero here will leave a gap of that many pixels
 
-- on the given edge, on the that screen. A useful gap at top of screen
 
-- for a menu bar (e.g. 15)
 
--
 
-- An example, to set a top gap on monitor 1, and a gap on the bottom of
 
-- monitor 2, you'd use a list of geometries like so:
 
--
 
-- > defaultGaps = [(18,0,0,0),(0,18,0,0)] -- 2 gaps on 2 monitors
 
--
 
-- Fields are: top, bottom, left, right.
 
--
 
 
defaultGaps :: [(Int,Int,Int,Int)]
 
defaultGaps :: [(Int,Int,Int,Int)]
 
defaultGaps = [(0,0,0,0)] -- 15 for default dzen font
 
defaultGaps = [(0,0,0,0)] -- 15 for default dzen font
 
------------------------------------------------------------------------
 
-- Window rules
 
 
-- | Execute arbitrary actions and WindowSet manipulations when managing
 
-- a new window. You can use this to, for example, always float a
 
-- particular program, or have a client always appear on a particular
 
-- workspace.
 
--
 
 
manageHook :: Window -- ^ the new window to manage
 
manageHook :: Window -- ^ the new window to manage
 
-> String -- ^ window title
 
-> String -- ^ window title
Line 115: Line 46:
 
-> String -- ^ window resource class
 
-> String -- ^ window resource class
 
-> X (WindowSet -> WindowSet)
 
-> X (WindowSet -> WindowSet)
 
-- Always float various programs:
 
 
manageHook w _ _ c | c `elem` floats = fmap (W.float w . snd) (floatLocation w)
 
manageHook w _ _ c | c `elem` floats = fmap (W.float w . snd) (floatLocation w)
 
where floats = ["MPlayer", "Gimp"]
 
where floats = ["MPlayer", "Gimp"]
 
-- Desktop panels and dock apps should be ignored by xmonad:
 
 
manageHook w _ n _ | n `elem` ignore = reveal w >> return (W.delete w)
 
manageHook w _ n _ | n `elem` ignore = reveal w >> return (W.delete w)
 
where ignore = ["gnome-panel", "desktop_window", "kicker", "kdesktop"]
 
where ignore = ["gnome-panel", "desktop_window", "kicker", "kdesktop"]
 
-- Automatically send Firefox windows to the "web" workspace:
 
-- If a workspace named "web" doesn't exist, the window will appear on the
 
-- current workspace.
 
 
manageHook _ _ "Gecko" _ = return $ W.shift "web"
 
manageHook _ _ "Gecko" _ = return $ W.shift "web"
 
-- The default rule: return the WindowSet unmodified. You typically do not
 
-- want to modify this line.
 
 
manageHook _ _ _ _ = return id
 
manageHook _ _ _ _ = return id
  +
-}
   
  +
-- | Normal window managers respond to windows setting the UrgencyHint by
-- |
 
  +
-- flashing the taskbar. Here, I throw up a dzen, "Xchat is requesting your attention yada yada."
-- Normal window managers respond to windows setting the UrgencyHint by
 
-- flashing the taskbar. Since xmonad doesn't have a taskbar, you get the
 
-- option of how to respond.
 
 
 
urgencyHook :: Window -> X ()
 
urgencyHook :: Window -> X ()
 
urgencyHook = dzenUrgencyHook (5 `seconds`)
 
urgencyHook = dzenUrgencyHook (5 `seconds`)
   
  +
-- Replace Full with noBorders tabbed.
------------------------------------------------------------------------
 
-- Extensible layouts
 
 
-- | The list of possible layouts. Add your custom layouts to this list.
 
layouts :: [Layout Window]
 
 
layouts = [ Layout tiled
 
layouts = [ Layout tiled
 
, Layout $ Mirror tiled
 
, Layout $ Mirror tiled
--, Layout Full
 
-- Add extra layouts you want to use here:
 
 
, Layout $ noBorders $ tabbed shrinkText defaultTConf
 
, Layout $ noBorders $ tabbed shrinkText defaultTConf
-- % Extension-provided layouts
 
 
]
 
]
 
where
 
where
  +
-- The standard definition.
-- default tiling algorithm partitions the screen into two panes
 
 
tiled = Tall nmaster delta ratio
 
tiled = Tall nmaster delta ratio
 
-- The default number of windows in the master pane
 
 
nmaster = 1
 
nmaster = 1
 
-- Default proportion of screen occupied by master pane
 
 
ratio = 1%2
 
ratio = 1%2
 
-- Percent of screen to increment by when resizing panes
 
 
delta = 3%100
 
delta = 3%100
   
  +
-- withUrgencyHook catches the urgency events from X clients.
-- | The top level layout switcher. Most users will not need to modify this binding.
 
  +
-- configurableNavigation noNavigateBorders lets me use a/w/s/d to navigate
--
 
  +
-- windows orthographically (esp. since I'm in a 2x2 grid often).
-- By default, we simply switch between the layouts listed in `layouts'
 
-- above, but you may program your own selection behaviour here. Layout
 
-- transformers, for example, would be hooked in here.
 
--
 
layoutHook :: Layout Window
 
 
layoutHook = Layout $ withUrgencyHook $ configurableNavigation noNavigateBorders $ Select layouts
 
layoutHook = Layout $ withUrgencyHook $ configurableNavigation noNavigateBorders $ Select layouts
   
  +
{-
-- | Register with xmonad a list of layouts whose state we can preserve over restarts.
 
-- There is typically no need to modify this list, the defaults are fine.
 
--
 
serialisedLayouts :: [Layout Window]
 
 
serialisedLayouts = layoutHook : layouts
 
serialisedLayouts = layoutHook : layouts
 
------------------------------------------------------------------------
 
-- Logging
 
 
-- | Perform an arbitrary action on each internal state change or X event.
 
-- Examples include:
 
-- * do nothing
 
-- * log the state to stdout
 
--
 
-- See the 'DynamicLog' extension for examples.
 
--
 
logHook :: X ()
 
 
logHook = return ()
 
logHook = return ()
  +
-}
   
  +
keys = M.fromList $
------------------------------------------------------------------------
 
  +
[ ((modMask .|. shiftMask, xK_Return), spawn "urxvt") -- urxvt instead of xterm
-- Key bindings:
 
  +
, ((modMask .|. shiftMask, xK_d ), spawn "(date; sleep 2) | dzen2") -- %! Print current date
   
  +
{-
-- | The xmonad key bindings. Add, modify or remove key bindings here.
 
--
 
-- (The comment formatting character is used when generating the manpage)
 
--
 
keys :: M.Map (KeyMask, KeySym) (X ())
 
keys = M.fromList $
 
-- launching and killing programs
 
[ ((modMask .|. shiftMask, xK_Return), spawn "rxvt") -- %! Launch an xterm
 
 
, ((modMask, xK_p ), spawn "exe=`dmenu_path | dmenu` && eval \"exec $exe\"") -- %! Launch dmenu
 
, ((modMask, xK_p ), spawn "exe=`dmenu_path | dmenu` && eval \"exec $exe\"") -- %! Launch dmenu
, ((modMask .|. shiftMask, xK_p ), spawn "gmrun") -- %! Launch gmrun
 
, ((modMask .|. shiftMask, xK_d ), spawn "(date; sleep 2) | dzen2") -- %! Print current date
 
, ((modMask .|. shiftMask, xK_t ), dzen "Hi!\n" (2 `seconds`))
 
 
, ((modMask .|. shiftMask, xK_c ), kill) -- %! Close the focused window
 
, ((modMask .|. shiftMask, xK_c ), kill) -- %! Close the focused window
 
 
, ((modMask, xK_space ), sendMessage NextLayout) -- %! Rotate through the available layout algorithms
 
, ((modMask, xK_space ), sendMessage NextLayout) -- %! Rotate through the available layout algorithms
 
, ((modMask .|. shiftMask, xK_space ), setLayout layoutHook) -- %! Reset the layouts on the current workspace to default
 
, ((modMask .|. shiftMask, xK_space ), setLayout layoutHook) -- %! Reset the layouts on the current workspace to default
 
 
, ((modMask, xK_n ), refresh) -- %! Resize viewed windows to the correct size
 
, ((modMask, xK_n ), refresh) -- %! Resize viewed windows to the correct size
 
-- move focus up or down the window stack
 
 
, ((modMask, xK_Tab ), windows W.focusDown) -- %! Move focus to the next window
 
, ((modMask, xK_Tab ), windows W.focusDown) -- %! Move focus to the next window
 
, ((modMask, xK_j ), windows W.focusDown) -- %! Move focus to the next window
 
, ((modMask, xK_j ), windows W.focusDown) -- %! Move focus to the next window
 
, ((modMask, xK_k ), windows W.focusUp ) -- %! Move focus to the previous window
 
, ((modMask, xK_k ), windows W.focusUp ) -- %! Move focus to the previous window
 
, ((modMask, xK_m ), windows W.focusMaster ) -- %! Move focus to the master window
 
, ((modMask, xK_m ), windows W.focusMaster ) -- %! Move focus to the master window
 
-- modifying the window order
 
 
, ((modMask, xK_Return), windows W.swapMaster) -- %! Swap the focused window and the master window
 
, ((modMask, xK_Return), windows W.swapMaster) -- %! Swap the focused window and the master window
 
, ((modMask .|. shiftMask, xK_j ), windows W.swapDown ) -- %! Swap the focused window with the next window
 
, ((modMask .|. shiftMask, xK_j ), windows W.swapDown ) -- %! Swap the focused window with the next window
 
, ((modMask .|. shiftMask, xK_k ), windows W.swapUp ) -- %! Swap the focused window with the previous window
 
, ((modMask .|. shiftMask, xK_k ), windows W.swapUp ) -- %! Swap the focused window with the previous window
 
-- resizing the master/slave ratio
 
 
, ((modMask, xK_h ), sendMessage Shrink) -- %! Shrink the master area
 
, ((modMask, xK_h ), sendMessage Shrink) -- %! Shrink the master area
 
, ((modMask, xK_l ), sendMessage Expand) -- %! Expand the master area
 
, ((modMask, xK_l ), sendMessage Expand) -- %! Expand the master area
 
-- floating layer support
 
-- , ((modMask, xK_t ), withFocused $ windows . (liftM2.liftM2) W.float return floatLocation) -- %! Pull window into float layer
 
 
, ((modMask, xK_t ), withFocused $ windows . W.sink) -- %! Push window back into tiling
 
, ((modMask, xK_t ), withFocused $ windows . W.sink) -- %! Push window back into tiling
 
-- increase or decrease number of windows in the master area
 
 
, ((modMask , xK_comma ), sendMessage (IncMasterN 1)) -- %! Increment the number of windows in the master area
 
, ((modMask , xK_comma ), sendMessage (IncMasterN 1)) -- %! Increment the number of windows in the master area
 
, ((modMask , xK_period), sendMessage (IncMasterN (-1))) -- %! Deincrement the number of windows in the master area
 
, ((modMask , xK_period), sendMessage (IncMasterN (-1))) -- %! Deincrement the number of windows in the master area
 
-- toggle the status bar gap
 
 
, ((modMask , xK_b ), modifyGap (\i n -> let x = (defaultGaps ++ repeat (0,0,0,0)) !! i in if n == x then (0,0,0,0) else x)) -- %! Toggle the status bar gap
 
, ((modMask , xK_b ), modifyGap (\i n -> let x = (defaultGaps ++ repeat (0,0,0,0)) !! i in if n == x then (0,0,0,0) else x)) -- %! Toggle the status bar gap
 
-- quit, or restart
 
 
, ((modMask.|.controlMask, xK_q ), io (exitWith ExitSuccess)) -- %! Quit xmonad
 
, ((modMask.|.controlMask, xK_q ), io (exitWith ExitSuccess)) -- %! Quit xmonad
 
, ((modMask , xK_q ), broadcastMessage ReleaseResources >> restart Nothing True) -- %! Restart xmonad
 
, ((modMask , xK_q ), broadcastMessage ReleaseResources >> restart Nothing True) -- %! Restart xmonad
  +
-}
   
  +
-- RotView cycles between non-empty workspaces -- i/o equals "left"/"right"
-- % Extension-provided key bindings
 
  +
-- along the number keys.
 
, ((modMask , xK_i ), rotView False)
 
, ((modMask , xK_i ), rotView False)
 
, ((modMask , xK_o ), rotView True)
 
, ((modMask , xK_o ), rotView True)
  +
-- Workspace navigation as set up in the layoutHooks definition.
 
, ((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)
  +
-- WindowBringer -- type the title of a window to jump to it or grab it.
 
, ((modMask .|. shiftMask, xK_g ), gotoMenu)
 
, ((modMask .|. shiftMask, xK_g ), gotoMenu)
 
, ((modMask .|. shiftMask, xK_b ), bringMenu)
 
, ((modMask .|. shiftMask, xK_b ), bringMenu)
 
]
 
]
  +
{-
 
++
 
++
-- mod-[1..9] %! Switch to workspace N
 
-- mod-shift-[1..9] %! Move client to workspace N
 
 
[((m .|. modMask, k), windows $ f i)
 
[((m .|. modMask, k), windows $ f i)
 
| (i, k) <- zip workspaces [xK_0 .. xK_9]
 
| (i, k) <- zip workspaces [xK_0 .. xK_9]
 
, (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)]]
 
, (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)]]
  +
-}
-- I don't have multiple screens, so let's free up those keys: --
 
-- ++
 
-- mod-{w,e,r} %! Switch to physical/Xinerama screens 1, 2, or 3
 
-- mod-shift-{w,e,r} %! Move client to screen 1, 2, or 3
 
-- [((m .|. modMask, key), screenWorkspace sc >>= flip whenJust (windows . f))
 
-- | (key, sc) <- zip [xK_w, xK_e, xK_r] [0..]
 
-- , (f, m) <- [(W.view, 0), (W.shift, shiftMask)]]
 
   
  +
-- I don't have multiple screens, so I free up mod{-shift,}-{w,e,r} by
-- % Extension-provided key bindings lists
 
  +
-- removing those mappings. (Used in the above Workspace navigation definition.)
  +
  +
-- Alt-Apple-Number swaps the current workspace with the numbered one.
  +
-- A simple way to move collections of windows at once.
 
++
 
++
 
[((modMask .|. mod1Mask, k), windows $ swapWithCurrent i)
 
[((modMask .|. mod1Mask, k), windows $ swapWithCurrent i)
 
| (i, k) <- zip workspaces [xK_0 ..]]
 
| (i, k) <- zip workspaces [xK_0 ..]]
  +
-- | Mouse bindings: default actions bound to mouse events
 
  +
-- Change modMask to controlMask .|. shiftMask, since Apple translates
--
 
  +
-- Apple-Click into Right-Click.
 
mouseBindings :: M.Map (KeyMask, Button) (Window -> X ())
 
mouseBindings :: M.Map (KeyMask, Button) (Window -> X ())
 
mouseBindings = M.fromList $
 
mouseBindings = M.fromList $
Line 285: Line 148:
 
, ((controlMask .|. shiftMask, button3), (\w -> focus w >> mouseResizeWindow w))
 
, ((controlMask .|. shiftMask, button3), (\w -> focus w >> mouseResizeWindow w))
 
-- you may also bind events to the mouse scroll wheel (button4 and button5)
 
-- you may also bind events to the mouse scroll wheel (button4 and button5)
 
-- % Extension-provided mouse bindings
 
 
]
 
]
 
-- % Extension-provided definitions
 
 
</haskell>
 
</haskell>
  +
  +
[[Category:XMonad configuration]]

Latest revision as of 21:56, 6 November 2007

Things that are no different from standard are commented out to make it easier to scan for the interesting bits. Removed type signatures for the same reason. Obviously, neither is the case in my real Config.hs. ;)

{-
module Config where

import XMonad
import Operations
import qualified StackSet as W
import Data.Ratio
import Data.Bits ((.|.))
import qualified Data.Map as M
import System.Exit
import Graphics.X11.Xlib
-}

import XMonadContrib.Dzen
import XMonadContrib.NoBorders
import XMonadContrib.RotView
import XMonadContrib.SwapWorkspaces
import XMonadContrib.Tabbed
import XMonadContrib.UrgencyHook
import XMonadContrib.WindowBringer
import XMonadContrib.WindowNavigation

-- Added workspace zero. Really, should append it to the end, as xmonad starts in `head workspaces`.
workspaces = map show [0 .. 9 :: Int]

-- mod4 == apple/cmd key for me (per xmodmap)
modMask = mod4Mask

-- apple doesn't have a numlock key
numlockMask = 0

{-
borderWidth :: Dimension
borderWidth = 1
normalBorderColor, focusedBorderColor :: String
normalBorderColor  = "#dddddd"
focusedBorderColor = "#ff0000"
defaultGaps :: [(Int,Int,Int,Int)]
defaultGaps = [(0,0,0,0)] -- 15 for default dzen font
manageHook :: Window -- ^ the new window to manage
           -> String -- ^ window title
           -> String -- ^ window resource name
           -> String -- ^ window resource class
           -> X (WindowSet -> WindowSet)
manageHook w _ _ c | c `elem` floats = fmap (W.float w . snd) (floatLocation w)
 where floats = ["MPlayer", "Gimp"]
manageHook w _ n _ | n `elem` ignore = reveal w >> return (W.delete w)
 where ignore = ["gnome-panel", "desktop_window", "kicker", "kdesktop"]
manageHook _ _ "Gecko" _ = return $ W.shift "web"
manageHook _ _ _ _ = return id
-}

-- | Normal window managers respond to windows setting the UrgencyHint by
-- flashing the taskbar. Here, I throw up a dzen, "Xchat is requesting your attention yada yada."
urgencyHook :: Window -> X ()
urgencyHook = dzenUrgencyHook (5 `seconds`)

-- Replace Full with noBorders tabbed.
layouts = [ Layout tiled
          , Layout $ Mirror tiled
          , Layout $ noBorders $ tabbed shrinkText defaultTConf
          ]
  where
     -- The standard definition.
     tiled   = Tall nmaster delta ratio
     nmaster = 1
     ratio   = 1%2
     delta   = 3%100

-- withUrgencyHook catches the urgency events from X clients.
-- configurableNavigation noNavigateBorders lets me use a/w/s/d to navigate
-- windows orthographically (esp. since I'm in a 2x2 grid often).
layoutHook = Layout $ withUrgencyHook $ configurableNavigation noNavigateBorders $ Select layouts

{-
serialisedLayouts = layoutHook : layouts
logHook = return ()
-}

keys = M.fromList $
    [ ((modMask .|. shiftMask, xK_Return), spawn "urxvt") -- urxvt instead of xterm
    , ((modMask .|. shiftMask, xK_d     ), spawn "(date; sleep 2) | dzen2") -- %! Print current date

{-
    , ((modMask,               xK_p     ), spawn "exe=`dmenu_path | dmenu` && eval \"exec $exe\"") -- %! Launch dmenu
    , ((modMask .|. shiftMask, xK_c     ), kill) -- %! Close the focused window
    , ((modMask,               xK_space ), sendMessage NextLayout) -- %! Rotate through the available layout algorithms
    , ((modMask .|. shiftMask, xK_space ), setLayout layoutHook) -- %!  Reset the layouts on the current workspace to default
    , ((modMask,               xK_n     ), refresh) -- %! Resize viewed windows to the correct size
    , ((modMask,               xK_Tab   ), windows W.focusDown) -- %! Move focus to the next window
    , ((modMask,               xK_j     ), windows W.focusDown) -- %! Move focus to the next window
    , ((modMask,               xK_k     ), windows W.focusUp  ) -- %! Move focus to the previous window
    , ((modMask,               xK_m     ), windows W.focusMaster  ) -- %! Move focus to the master window
    , ((modMask,               xK_Return), windows W.swapMaster) -- %! Swap the focused window and the master window
    , ((modMask .|. shiftMask, xK_j     ), windows W.swapDown  ) -- %! Swap the focused window with the next window
    , ((modMask .|. shiftMask, xK_k     ), windows W.swapUp    ) -- %! Swap the focused window with the previous window
    , ((modMask,               xK_h     ), sendMessage Shrink) -- %! Shrink the master area
    , ((modMask,               xK_l     ), sendMessage Expand) -- %! Expand the master area
    , ((modMask,               xK_t     ), withFocused $ windows . W.sink) -- %! Push window back into tiling
    , ((modMask              , xK_comma ), sendMessage (IncMasterN 1)) -- %! Increment the number of windows in the master area
    , ((modMask              , xK_period), sendMessage (IncMasterN (-1))) -- %! Deincrement the number of windows in the master area
    , ((modMask              , xK_b     ), modifyGap (\i n -> let x = (defaultGaps ++ repeat (0,0,0,0)) !! i in if n == x then (0,0,0,0) else x)) -- %! Toggle the status bar gap
    , ((modMask.|.controlMask, xK_q     ), io (exitWith ExitSuccess)) -- %! Quit xmonad
    , ((modMask              , xK_q     ), broadcastMessage ReleaseResources >> restart Nothing True) -- %! Restart xmonad
-}

-- RotView cycles between non-empty workspaces -- i/o equals "left"/"right"
-- along the number keys.
    , ((modMask              , xK_i     ), rotView False)
    , ((modMask              , xK_o     ), rotView True)
-- Workspace navigation as set up in the layoutHooks definition.
    , ((modMask,               xK_a     ), sendMessage $ Go L)
    , ((modMask,               xK_w     ), sendMessage $ Go U)
    , ((modMask,               xK_s     ), sendMessage $ Go D)
    , ((modMask,               xK_d     ), sendMessage $ Go R)
-- WindowBringer -- type the title of a window to jump to it or grab it.
    , ((modMask .|. shiftMask, xK_g     ), gotoMenu)
    , ((modMask .|. shiftMask, xK_b     ), bringMenu)
    ]
{-
    ++
    [((m .|. modMask, k), windows $ f i)
        | (i, k) <- zip workspaces [xK_0 .. xK_9]
        , (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)]]
-}

-- I don't have multiple screens, so I free up mod{-shift,}-{w,e,r} by
-- removing those mappings. (Used in the above Workspace navigation definition.)

-- Alt-Apple-Number swaps the current workspace with the numbered one.
-- A simple way to move collections of windows at once.
    ++
    [((modMask .|. mod1Mask, k), windows $ swapWithCurrent i)
        | (i, k) <- zip workspaces [xK_0 ..]]

-- Change modMask to controlMask .|. shiftMask, since Apple translates
-- Apple-Click into Right-Click.
mouseBindings :: M.Map (KeyMask, Button) (Window -> X ())
mouseBindings = M.fromList $
    -- mod-button1 %! Set the window to floating mode and move by dragging
    [ ((controlMask .|. shiftMask, button1), (\w -> focus w >> mouseMoveWindow w))
    -- mod-button2 %! Raise the window to the top of the stack
    , ((controlMask .|. shiftMask, button2), (\w -> focus w >> windows W.swapMaster))
    -- mod-button3 %! Set the window to floating mode and resize by dragging
    , ((controlMask .|. shiftMask, button3), (\w -> focus w >> mouseResizeWindow w))
    -- you may also bind events to the mouse scroll wheel (button4 and button5)
    ]