{-# OPTIONS_GHC -fno-warn-missing-signatures -fno-warn-orphans #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
module XMonad.Config (defaultConfig, Default(..)) where
import XMonad.Core as XMonad hiding
    (workspaces,manageHook,keys,logHook,startupHook,borderWidth,mouseBindings
    ,layoutHook,modMask,terminal,normalBorderColor,focusedBorderColor,focusFollowsMouse
    ,handleEventHook,clickJustFocuses,rootMask,clientMask)
import qualified XMonad.Core as XMonad
    (workspaces,manageHook,keys,logHook,startupHook,borderWidth,mouseBindings
    ,layoutHook,modMask,terminal,normalBorderColor,focusedBorderColor,focusFollowsMouse
    ,handleEventHook,clickJustFocuses,rootMask,clientMask)
import XMonad.Layout
import XMonad.Operations
import XMonad.ManageHook
import qualified XMonad.StackSet as W
import Data.Bits ((.|.))
import Data.Default.Class
import Data.Monoid
import qualified Data.Map as M
import System.Exit
import Graphics.X11.Xlib
import Graphics.X11.Xlib.Extras
workspaces :: [WorkspaceId]
workspaces :: [WorkspaceId]
workspaces = (Int -> WorkspaceId) -> [Int] -> [WorkspaceId]
forall a b. (a -> b) -> [a] -> [b]
map Int -> WorkspaceId
forall a. Show a => a -> WorkspaceId
show [Int
1 .. Int
9 :: Int]
defaultModMask :: KeyMask
defaultModMask :: KeyMask
defaultModMask = KeyMask
mod1Mask
borderWidth :: Dimension
borderWidth :: Button
borderWidth = Button
1
normalBorderColor, focusedBorderColor :: String
normalBorderColor :: WorkspaceId
normalBorderColor  = WorkspaceId
"gray" 
focusedBorderColor :: WorkspaceId
focusedBorderColor = WorkspaceId
"red"  
manageHook :: ManageHook
manageHook :: ManageHook
manageHook = [ManageHook] -> ManageHook
forall m. Monoid m => [m] -> m
composeAll
                [ Query WorkspaceId
className Query WorkspaceId -> WorkspaceId -> Query Bool
forall a. Eq a => Query a -> a -> Query Bool
=? WorkspaceId
"MPlayer"        Query Bool -> ManageHook -> ManageHook
forall (m :: * -> *) a. (Monad m, Monoid a) => m Bool -> m a -> m a
--> ManageHook
doFloat
                , Query WorkspaceId
className Query WorkspaceId -> WorkspaceId -> Query Bool
forall a. Eq a => Query a -> a -> Query Bool
=? WorkspaceId
"mplayer2"       Query Bool -> ManageHook -> ManageHook
forall (m :: * -> *) a. (Monad m, Monoid a) => m Bool -> m a -> m a
--> ManageHook
doFloat ]
logHook :: X ()
logHook :: X ()
logHook = () -> X ()
forall a. a -> X a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
handleEventHook :: Event -> X All
handleEventHook :: Event -> X All
handleEventHook Event
_ = All -> X All
forall a. a -> X a
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool -> All
All Bool
True)
startupHook :: X ()
startupHook :: X ()
startupHook = () -> X ()
forall a. a -> X a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
layout :: Choose Tall (Choose (Mirror Tall) Full) a
layout = Tall a
tiled Tall a
-> Choose (Mirror Tall) Full a
-> Choose Tall (Choose (Mirror Tall) Full) a
forall (l :: * -> *) a (r :: * -> *). l a -> r a -> Choose l r a
||| Tall a -> Mirror Tall a
forall (l :: * -> *) a. l a -> Mirror l a
Mirror Tall a
tiled Mirror Tall a -> Full a -> Choose (Mirror Tall) Full a
forall (l :: * -> *) a (r :: * -> *). l a -> r a -> Choose l r a
||| Full a
forall a. Full a
Full
  where
     
     tiled :: Tall a
tiled   = Int -> Rational -> Rational -> Tall a
forall a. Int -> Rational -> Rational -> Tall a
Tall Int
nmaster Rational
delta Rational
ratio
     
     nmaster :: Int
nmaster = Int
1
     
     ratio :: Rational
ratio   = Rational
1Rational -> Rational -> Rational
forall a. Fractional a => a -> a -> a
/Rational
2
     
     delta :: Rational
delta   = Rational
3Rational -> Rational -> Rational
forall a. Fractional a => a -> a -> a
/Rational
100
clientMask :: EventMask
clientMask :: Window
clientMask = Window
structureNotifyMask Window -> Window -> Window
forall a. Bits a => a -> a -> a
.|. Window
enterWindowMask Window -> Window -> Window
forall a. Bits a => a -> a -> a
.|. Window
propertyChangeMask
rootMask :: EventMask
rootMask :: Window
rootMask =  Window
substructureRedirectMask Window -> Window -> Window
forall a. Bits a => a -> a -> a
.|. Window
substructureNotifyMask
        Window -> Window -> Window
forall a. Bits a => a -> a -> a
.|. Window
enterWindowMask Window -> Window -> Window
forall a. Bits a => a -> a -> a
.|. Window
leaveWindowMask Window -> Window -> Window
forall a. Bits a => a -> a -> a
.|. Window
structureNotifyMask
        Window -> Window -> Window
forall a. Bits a => a -> a -> a
.|. Window
buttonPressMask
terminal :: String
terminal :: WorkspaceId
terminal = WorkspaceId
"xterm"
focusFollowsMouse :: Bool
focusFollowsMouse :: Bool
focusFollowsMouse = Bool
True
clickJustFocuses :: Bool
clickJustFocuses :: Bool
clickJustFocuses = Bool
True
keys :: XConfig Layout -> M.Map (KeyMask, KeySym) (X ())
keys :: XConfig Layout -> Map (KeyMask, Window) (X ())
keys conf :: XConfig Layout
conf@(XConfig {modMask :: forall (l :: * -> *). XConfig l -> KeyMask
XMonad.modMask = KeyMask
modMask}) = [((KeyMask, Window), X ())] -> Map (KeyMask, Window) (X ())
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList ([((KeyMask, Window), X ())] -> Map (KeyMask, Window) (X ()))
-> [((KeyMask, Window), X ())] -> Map (KeyMask, Window) (X ())
forall a b. (a -> b) -> a -> b
$
    
    [ ((KeyMask
modMask KeyMask -> KeyMask -> KeyMask
forall a. Bits a => a -> a -> a
.|. KeyMask
shiftMask, Window
xK_Return), WorkspaceId -> X ()
forall (m :: * -> *). MonadIO m => WorkspaceId -> m ()
spawn (WorkspaceId -> X ()) -> WorkspaceId -> X ()
forall a b. (a -> b) -> a -> b
$ XConfig Layout -> WorkspaceId
forall (l :: * -> *). XConfig l -> WorkspaceId
XMonad.terminal XConfig Layout
conf) 
    , ((KeyMask
modMask,               Window
xK_p     ), WorkspaceId -> X ()
forall (m :: * -> *). MonadIO m => WorkspaceId -> m ()
spawn WorkspaceId
"dmenu_run") 
    , ((KeyMask
modMask KeyMask -> KeyMask -> KeyMask
forall a. Bits a => a -> a -> a
.|. KeyMask
shiftMask, Window
xK_p     ), WorkspaceId -> X ()
forall (m :: * -> *). MonadIO m => WorkspaceId -> m ()
spawn WorkspaceId
"gmrun") 
    , ((KeyMask
modMask KeyMask -> KeyMask -> KeyMask
forall a. Bits a => a -> a -> a
.|. KeyMask
shiftMask, Window
xK_c     ), X ()
kill) 
    , ((KeyMask
modMask,               Window
xK_space ), ChangeLayout -> X ()
forall a. Message a => a -> X ()
sendMessage ChangeLayout
NextLayout) 
    , ((KeyMask
modMask KeyMask -> KeyMask -> KeyMask
forall a. Bits a => a -> a -> a
.|. KeyMask
shiftMask, Window
xK_space ), Layout Window -> X ()
setLayout (Layout Window -> X ()) -> Layout Window -> X ()
forall a b. (a -> b) -> a -> b
$ XConfig Layout -> Layout Window
forall (l :: * -> *). XConfig l -> l Window
XMonad.layoutHook XConfig Layout
conf) 
    , ((KeyMask
modMask,               Window
xK_n     ), X ()
refresh) 
    
    , ((KeyMask
modMask,               Window
xK_Tab   ), (WindowSet -> WindowSet) -> X ()
windows WindowSet -> WindowSet
forall i l a s sd. StackSet i l a s sd -> StackSet i l a s sd
W.focusDown) 
    , ((KeyMask
modMask KeyMask -> KeyMask -> KeyMask
forall a. Bits a => a -> a -> a
.|. KeyMask
shiftMask, Window
xK_Tab   ), (WindowSet -> WindowSet) -> X ()
windows WindowSet -> WindowSet
forall i l a s sd. StackSet i l a s sd -> StackSet i l a s sd
W.focusUp  ) 
    , ((KeyMask
modMask,               Window
xK_j     ), (WindowSet -> WindowSet) -> X ()
windows WindowSet -> WindowSet
forall i l a s sd. StackSet i l a s sd -> StackSet i l a s sd
W.focusDown) 
    , ((KeyMask
modMask,               Window
xK_k     ), (WindowSet -> WindowSet) -> X ()
windows WindowSet -> WindowSet
forall i l a s sd. StackSet i l a s sd -> StackSet i l a s sd
W.focusUp  ) 
    , ((KeyMask
modMask,               Window
xK_m     ), (WindowSet -> WindowSet) -> X ()
windows WindowSet -> WindowSet
forall i l a s sd. StackSet i l a s sd -> StackSet i l a s sd
W.focusMaster  ) 
    
    , ((KeyMask
modMask,               Window
xK_Return), (WindowSet -> WindowSet) -> X ()
windows WindowSet -> WindowSet
forall i l a s sd. StackSet i l a s sd -> StackSet i l a s sd
W.swapMaster) 
    , ((KeyMask
modMask KeyMask -> KeyMask -> KeyMask
forall a. Bits a => a -> a -> a
.|. KeyMask
shiftMask, Window
xK_j     ), (WindowSet -> WindowSet) -> X ()
windows WindowSet -> WindowSet
forall i l a s sd. StackSet i l a s sd -> StackSet i l a s sd
W.swapDown  ) 
    , ((KeyMask
modMask KeyMask -> KeyMask -> KeyMask
forall a. Bits a => a -> a -> a
.|. KeyMask
shiftMask, Window
xK_k     ), (WindowSet -> WindowSet) -> X ()
windows WindowSet -> WindowSet
forall i l a s sd. StackSet i l a s sd -> StackSet i l a s sd
W.swapUp    ) 
    
    , ((KeyMask
modMask,               Window
xK_h     ), Resize -> X ()
forall a. Message a => a -> X ()
sendMessage Resize
Shrink) 
    , ((KeyMask
modMask,               Window
xK_l     ), Resize -> X ()
forall a. Message a => a -> X ()
sendMessage Resize
Expand) 
    
    , ((KeyMask
modMask,               Window
xK_t     ), (Window -> X ()) -> X ()
withFocused ((Window -> X ()) -> X ()) -> (Window -> X ()) -> X ()
forall a b. (a -> b) -> a -> b
$ (WindowSet -> WindowSet) -> X ()
windows ((WindowSet -> WindowSet) -> X ())
-> (Window -> WindowSet -> WindowSet) -> Window -> X ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Window -> WindowSet -> WindowSet
forall a i l s sd.
Ord a =>
a -> StackSet i l a s sd -> StackSet i l a s sd
W.sink) 
    
    , ((KeyMask
modMask              , Window
xK_comma ), IncMasterN -> X ()
forall a. Message a => a -> X ()
sendMessage (Int -> IncMasterN
IncMasterN Int
1)) 
    , ((KeyMask
modMask              , Window
xK_period), IncMasterN -> X ()
forall a. Message a => a -> X ()
sendMessage (Int -> IncMasterN
IncMasterN (-Int
1))) 
    
    , ((KeyMask
modMask KeyMask -> KeyMask -> KeyMask
forall a. Bits a => a -> a -> a
.|. KeyMask
shiftMask, Window
xK_q     ), IO () -> X ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
io IO ()
forall a. IO a
exitSuccess) 
    , ((KeyMask
modMask              , Window
xK_q     ), WorkspaceId -> X ()
forall (m :: * -> *). MonadIO m => WorkspaceId -> m ()
spawn WorkspaceId
"if type xmonad; then xmonad --recompile && xmonad --restart; else xmessage xmonad not in \\$PATH: \"$PATH\"; fi") 
    , ((KeyMask
modMask KeyMask -> KeyMask -> KeyMask
forall a. Bits a => a -> a -> a
.|. KeyMask
shiftMask, Window
xK_slash ), X ()
helpCommand) 
    
    , ((KeyMask
modMask              , Window
xK_question), X ()
helpCommand) 
    ]
    [((KeyMask, Window), X ())]
-> [((KeyMask, Window), X ())] -> [((KeyMask, Window), X ())]
forall a. [a] -> [a] -> [a]
++
    
    
    [((KeyMask
m KeyMask -> KeyMask -> KeyMask
forall a. Bits a => a -> a -> a
.|. KeyMask
modMask, Window
k), (WindowSet -> WindowSet) -> X ()
windows ((WindowSet -> WindowSet) -> X ())
-> (WindowSet -> WindowSet) -> X ()
forall a b. (a -> b) -> a -> b
$ WorkspaceId -> WindowSet -> WindowSet
f WorkspaceId
i)
        | (WorkspaceId
i, Window
k) <- [WorkspaceId] -> [Window] -> [(WorkspaceId, Window)]
forall a b. [a] -> [b] -> [(a, b)]
zip (XConfig Layout -> [WorkspaceId]
forall (l :: * -> *). XConfig l -> [WorkspaceId]
XMonad.workspaces XConfig Layout
conf) [Window
xK_1 .. Window
xK_9]
        , (WorkspaceId -> WindowSet -> WindowSet
f, KeyMask
m) <- [(WorkspaceId -> WindowSet -> WindowSet
forall s i l a sd.
(Eq s, Eq i) =>
i -> StackSet i l a s sd -> StackSet i l a s sd
W.greedyView, KeyMask
0), (WorkspaceId -> WindowSet -> WindowSet
forall a s i l sd.
(Ord a, Eq s, Eq i) =>
i -> StackSet i l a s sd -> StackSet i l a s sd
W.shift, KeyMask
shiftMask)]]
    [((KeyMask, Window), X ())]
-> [((KeyMask, Window), X ())] -> [((KeyMask, Window), X ())]
forall a. [a] -> [a] -> [a]
++
    
    
    [((KeyMask
m KeyMask -> KeyMask -> KeyMask
forall a. Bits a => a -> a -> a
.|. KeyMask
modMask, Window
key), ScreenId -> X (Maybe WorkspaceId)
screenWorkspace ScreenId
sc X (Maybe WorkspaceId) -> (Maybe WorkspaceId -> X ()) -> X ()
forall a b. X a -> (a -> X b) -> X b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (Maybe WorkspaceId -> (WorkspaceId -> X ()) -> X ())
-> (WorkspaceId -> X ()) -> Maybe WorkspaceId -> X ()
forall a b c. (a -> b -> c) -> b -> a -> c
flip Maybe WorkspaceId -> (WorkspaceId -> X ()) -> X ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust ((WindowSet -> WindowSet) -> X ()
windows ((WindowSet -> WindowSet) -> X ())
-> (WorkspaceId -> WindowSet -> WindowSet) -> WorkspaceId -> X ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WorkspaceId -> WindowSet -> WindowSet
f))
        | (Window
key, ScreenId
sc) <- [Window] -> [ScreenId] -> [(Window, ScreenId)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Window
xK_w, Window
xK_e, Window
xK_r] [ScreenId
0..]
        , (WorkspaceId -> WindowSet -> WindowSet
f, KeyMask
m) <- [(WorkspaceId -> WindowSet -> WindowSet
forall s i l a sd.
(Eq s, Eq i) =>
i -> StackSet i l a s sd -> StackSet i l a s sd
W.view, KeyMask
0), (WorkspaceId -> WindowSet -> WindowSet
forall a s i l sd.
(Ord a, Eq s, Eq i) =>
i -> StackSet i l a s sd -> StackSet i l a s sd
W.shift, KeyMask
shiftMask)]]
  where
    helpCommand :: X ()
    helpCommand :: X ()
helpCommand = WorkspaceId -> X ()
forall (m :: * -> *). MonadIO m => WorkspaceId -> m ()
xmessage WorkspaceId
help
mouseBindings :: XConfig Layout -> M.Map (KeyMask, Button) (Window -> X ())
mouseBindings :: XConfig Layout -> Map (KeyMask, Button) (Window -> X ())
mouseBindings (XConfig {modMask :: forall (l :: * -> *). XConfig l -> KeyMask
XMonad.modMask = KeyMask
modMask}) = [((KeyMask, Button), Window -> X ())]
-> Map (KeyMask, Button) (Window -> X ())
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList
    
    [ ((KeyMask
modMask, Button
button1), \Window
w -> Window -> X ()
focus Window
w X () -> X () -> X ()
forall a b. X a -> X b -> X b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Window -> X ()
mouseMoveWindow Window
w
                                          X () -> X () -> X ()
forall a b. X a -> X b -> X b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> (WindowSet -> WindowSet) -> X ()
windows WindowSet -> WindowSet
forall i l a s sd. StackSet i l a s sd -> StackSet i l a s sd
W.shiftMaster)
    
    , ((KeyMask
modMask, Button
button2), (WindowSet -> WindowSet) -> X ()
windows ((WindowSet -> WindowSet) -> X ())
-> (Window -> WindowSet -> WindowSet) -> Window -> X ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (WindowSet -> WindowSet
forall i l a s sd. StackSet i l a s sd -> StackSet i l a s sd
W.shiftMaster (WindowSet -> WindowSet)
-> (WindowSet -> WindowSet) -> WindowSet -> WindowSet
forall b c a. (b -> c) -> (a -> b) -> a -> c
.) ((WindowSet -> WindowSet) -> WindowSet -> WindowSet)
-> (Window -> WindowSet -> WindowSet)
-> Window
-> WindowSet
-> WindowSet
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Window -> WindowSet -> WindowSet
forall s a i l sd.
(Eq s, Eq a, Eq i) =>
a -> StackSet i l a s sd -> StackSet i l a s sd
W.focusWindow)
    
    , ((KeyMask
modMask, Button
button3), \Window
w -> Window -> X ()
focus Window
w X () -> X () -> X ()
forall a b. X a -> X b -> X b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Window -> X ()
mouseResizeWindow Window
w
                                         X () -> X () -> X ()
forall a b. X a -> X b -> X b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> (WindowSet -> WindowSet) -> X ()
windows WindowSet -> WindowSet
forall i l a s sd. StackSet i l a s sd -> StackSet i l a s sd
W.shiftMaster)
    
    ]
instance (a ~ Choose Tall (Choose (Mirror Tall) Full)) => Default (XConfig a) where
  def :: XConfig a
def = XConfig
    { borderWidth :: Button
XMonad.borderWidth        = Button
borderWidth
    , workspaces :: [WorkspaceId]
XMonad.workspaces         = [WorkspaceId]
workspaces
    , layoutHook :: Choose Tall (Choose (Mirror Tall) Full) Window
XMonad.layoutHook         = Choose Tall (Choose (Mirror Tall) Full) Window
forall {a}. Choose Tall (Choose (Mirror Tall) Full) a
layout
    , terminal :: WorkspaceId
XMonad.terminal           = WorkspaceId
terminal
    , normalBorderColor :: WorkspaceId
XMonad.normalBorderColor  = WorkspaceId
normalBorderColor
    , focusedBorderColor :: WorkspaceId
XMonad.focusedBorderColor = WorkspaceId
focusedBorderColor
    , modMask :: KeyMask
XMonad.modMask            = KeyMask
defaultModMask
    , keys :: XConfig Layout -> Map (KeyMask, Window) (X ())
XMonad.keys               = XConfig Layout -> Map (KeyMask, Window) (X ())
keys
    , logHook :: X ()
XMonad.logHook            = X ()
logHook
    , startupHook :: X ()
XMonad.startupHook        = X ()
startupHook
    , mouseBindings :: XConfig Layout -> Map (KeyMask, Button) (Window -> X ())
XMonad.mouseBindings      = XConfig Layout -> Map (KeyMask, Button) (Window -> X ())
mouseBindings
    , manageHook :: ManageHook
XMonad.manageHook         = ManageHook
manageHook
    , handleEventHook :: Event -> X All
XMonad.handleEventHook    = Event -> X All
handleEventHook
    , focusFollowsMouse :: Bool
XMonad.focusFollowsMouse  = Bool
focusFollowsMouse
    , clickJustFocuses :: Bool
XMonad.clickJustFocuses       = Bool
clickJustFocuses
    , clientMask :: Window
XMonad.clientMask         = Window
clientMask
    , rootMask :: Window
XMonad.rootMask           = Window
rootMask
    , handleExtraArgs :: [WorkspaceId] -> XConfig Layout -> IO (XConfig Layout)
XMonad.handleExtraArgs = \ [WorkspaceId]
xs XConfig Layout
theConf -> case [WorkspaceId]
xs of
                [] -> XConfig Layout -> IO (XConfig Layout)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return XConfig Layout
theConf
                [WorkspaceId]
_ -> WorkspaceId -> IO (XConfig Layout)
forall a. WorkspaceId -> IO a
forall (m :: * -> *) a. MonadFail m => WorkspaceId -> m a
fail (WorkspaceId
"unrecognized flags:" WorkspaceId -> WorkspaceId -> WorkspaceId
forall a. [a] -> [a] -> [a]
++ [WorkspaceId] -> WorkspaceId
forall a. Show a => a -> WorkspaceId
show [WorkspaceId]
xs)
    , extensibleConf :: Map TypeRep ConfExtension
XMonad.extensibleConf     = Map TypeRep ConfExtension
forall k a. Map k a
M.empty
    }
{-# DEPRECATED defaultConfig "Use def (from Data.Default, and re-exported by XMonad and XMonad.Config) instead." #-}
defaultConfig :: XConfig (Choose Tall (Choose (Mirror Tall) Full))
defaultConfig :: XConfig (Choose Tall (Choose (Mirror Tall) Full))
defaultConfig = XConfig (Choose Tall (Choose (Mirror Tall) Full))
forall a. Default a => a
def
help :: String
help :: WorkspaceId
help = [WorkspaceId] -> WorkspaceId
unlines [WorkspaceId
"The default modifier key is 'alt'. Default keybindings:",
    WorkspaceId
"",
    WorkspaceId
"-- launching and killing programs",
    WorkspaceId
"mod-Shift-Enter  Launch xterminal",
    WorkspaceId
"mod-p            Launch dmenu",
    WorkspaceId
"mod-Shift-p      Launch gmrun",
    WorkspaceId
"mod-Shift-c      Close/kill the focused window",
    WorkspaceId
"mod-Space        Rotate through the available layout algorithms",
    WorkspaceId
"mod-Shift-Space  Reset the layouts on the current workSpace to default",
    WorkspaceId
"mod-n            Resize/refresh viewed windows to the correct size",
    WorkspaceId
"mod-Shift-/      Show this help message with the default keybindings",
    WorkspaceId
"",
    WorkspaceId
"-- move focus up or down the window stack",
    WorkspaceId
"mod-Tab        Move focus to the next window",
    WorkspaceId
"mod-Shift-Tab  Move focus to the previous window",
    WorkspaceId
"mod-j          Move focus to the next window",
    WorkspaceId
"mod-k          Move focus to the previous window",
    WorkspaceId
"mod-m          Move focus to the master window",
    WorkspaceId
"",
    WorkspaceId
"-- modifying the window order",
    WorkspaceId
"mod-Return   Swap the focused window and the master window",
    WorkspaceId
"mod-Shift-j  Swap the focused window with the next window",
    WorkspaceId
"mod-Shift-k  Swap the focused window with the previous window",
    WorkspaceId
"",
    WorkspaceId
"-- resizing the master/slave ratio",
    WorkspaceId
"mod-h  Shrink the master area",
    WorkspaceId
"mod-l  Expand the master area",
    WorkspaceId
"",
    WorkspaceId
"-- floating layer support",
    WorkspaceId
"mod-t  Push window back into tiling; unfloat and re-tile it",
    WorkspaceId
"",
    WorkspaceId
"-- increase or decrease number of windows in the master area",
    WorkspaceId
"mod-comma  (mod-,)   Increment the number of windows in the master area",
    WorkspaceId
"mod-period (mod-.)   Deincrement the number of windows in the master area",
    WorkspaceId
"",
    WorkspaceId
"-- quit, or restart",
    WorkspaceId
"mod-Shift-q  Quit xmonad",
    WorkspaceId
"mod-q        Restart xmonad",
    WorkspaceId
"",
    WorkspaceId
"-- Workspaces & screens",
    WorkspaceId
"mod-[1..9]         Switch to workSpace N",
    WorkspaceId
"mod-Shift-[1..9]   Move client to workspace N",
    WorkspaceId
"mod-{w,e,r}        Switch to physical/Xinerama screens 1, 2, or 3",
    WorkspaceId
"mod-Shift-{w,e,r}  Move client to screen 1, 2, or 3",
    WorkspaceId
"",
    WorkspaceId
"-- Mouse bindings: default actions bound to mouse events",
    WorkspaceId
"mod-button1  Set the window to floating mode and move by dragging",
    WorkspaceId
"mod-button2  Raise the window to the top of the stack",
    WorkspaceId
"mod-button3  Set the window to floating mode and resize by dragging"]