aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Layout
diff options
context:
space:
mode:
authorAdam Vogt <vogt.adam@gmail.com>2009-10-22 06:11:26 +0200
committerAdam Vogt <vogt.adam@gmail.com>2009-10-22 06:11:26 +0200
commit36728ae60e3effdfe645a9a34cfd2e1067a37516 (patch)
tree153d6eaf1780df2802bb8e5acefac9cbeda4d849 /XMonad/Layout
parent0c9f1ac69bad6af19f3129ec50c4899bac5c149a (diff)
downloadXMonadContrib-36728ae60e3effdfe645a9a34cfd2e1067a37516.tar.gz
XMonadContrib-36728ae60e3effdfe645a9a34cfd2e1067a37516.tar.xz
XMonadContrib-36728ae60e3effdfe645a9a34cfd2e1067a37516.zip
Refer to modm as the current modMask
Ignore-this: d097c7dc1746c55e1d4078a7148f9d5a This makes the config suggestions consistent with the current template. darcs-hash:20091022041126-1499c-5dd63076fdd71a61276cfc8e648bada81d9cc586.gz
Diffstat (limited to 'XMonad/Layout')
-rw-r--r--XMonad/Layout/BoringWindows.hs6
-rw-r--r--XMonad/Layout/Combo.hs8
-rw-r--r--XMonad/Layout/ComboP.hs10
-rw-r--r--XMonad/Layout/Gaps.hs8
-rw-r--r--XMonad/Layout/GridVariants.hs8
-rw-r--r--XMonad/Layout/IndependentScreens.hs4
-rw-r--r--XMonad/Layout/LayoutBuilder.hs4
-rw-r--r--XMonad/Layout/LayoutCombinators.hs2
-rw-r--r--XMonad/Layout/LayoutScreens.hs8
-rw-r--r--XMonad/Layout/Magnifier.hs10
-rw-r--r--XMonad/Layout/Maximize.hs2
-rw-r--r--XMonad/Layout/MessageControl.hs2
-rw-r--r--XMonad/Layout/Minimize.hs4
-rw-r--r--XMonad/Layout/Mosaic.hs6
-rw-r--r--XMonad/Layout/MosaicAlt.hs10
-rw-r--r--XMonad/Layout/MouseResizableTile.hs4
-rw-r--r--XMonad/Layout/MultiToggle.hs2
-rw-r--r--XMonad/Layout/Reflect.hs4
-rw-r--r--XMonad/Layout/ResizableTile.hs4
-rw-r--r--XMonad/Layout/ToggleLayouts.hs4
-rw-r--r--XMonad/Layout/WindowArranger.hs28
-rw-r--r--XMonad/Layout/WindowNavigation.hs16
-rw-r--r--XMonad/Layout/WorkspaceDir.hs2
23 files changed, 78 insertions, 78 deletions
diff --git a/XMonad/Layout/BoringWindows.hs b/XMonad/Layout/BoringWindows.hs
index 9f84e96..bc675a9 100644
--- a/XMonad/Layout/BoringWindows.hs
+++ b/XMonad/Layout/BoringWindows.hs
@@ -51,9 +51,9 @@ import qualified XMonad.StackSet as W
--
-- Then to your keybindings, add:
--
--- > , ((modMask, xK_j), focusUp)
--- > , ((modMask, xK_k), focusDown)
--- > , ((modMask, xK_m), focusMaster)
+-- > , ((modm, xK_j), focusUp)
+-- > , ((modm, xK_k), focusDown)
+-- > , ((modm, xK_m), focusMaster)
--
-- For more detailed instructions on editing the layoutHook see:
--
diff --git a/XMonad/Layout/Combo.hs b/XMonad/Layout/Combo.hs
index 04ef1db..069e1a0 100644
--- a/XMonad/Layout/Combo.hs
+++ b/XMonad/Layout/Combo.hs
@@ -51,10 +51,10 @@ import qualified XMonad.StackSet as W ( differentiate )
-- each sublayout. To do this, use "XMonad.Layout.WindowNavigation",
-- and add the following key bindings (or something similar):
--
--- > , ((modMask x .|. controlMask .|. shiftMask, xK_Right), sendMessage $ Move R)
--- > , ((modMask x .|. controlMask .|. shiftMask, xK_Left ), sendMessage $ Move L)
--- > , ((modMask x .|. controlMask .|. shiftMask, xK_Up ), sendMessage $ Move U)
--- > , ((modMask x .|. controlMask .|. shiftMask, xK_Down ), sendMessage $ Move D)
+-- > , ((modm .|. controlMask .|. shiftMask, xK_Right), sendMessage $ Move R)
+-- > , ((modm .|. controlMask .|. shiftMask, xK_Left ), sendMessage $ Move L)
+-- > , ((modm .|. controlMask .|. shiftMask, xK_Up ), sendMessage $ Move U)
+-- > , ((modm .|. controlMask .|. shiftMask, xK_Down ), sendMessage $ Move D)
--
-- For detailed instruction on editing the key binding see
-- "XMonad.Doc.Extending#Editing_key_bindings".
diff --git a/XMonad/Layout/ComboP.hs b/XMonad/Layout/ComboP.hs
index e84e2b7..9218d86 100644
--- a/XMonad/Layout/ComboP.hs
+++ b/XMonad/Layout/ComboP.hs
@@ -57,11 +57,11 @@ import qualified XMonad.StackSet as W
-- To use it, import \"XMonad.Layout.WindowNavigation\", and add the following key
-- bindings (or something similar):
--
--- > , ((modMask x .|. controlMask .|. shiftMask, xK_Right), sendMessage $ Move R)
--- > , ((modMask x .|. controlMask .|. shiftMask, xK_Left ), sendMessage $ Move L)
--- > , ((modMask x .|. controlMask .|. shiftMask, xK_Up ), sendMessage $ Move U)
--- > , ((modMask x .|. controlMask .|. shiftMask, xK_Down ), sendMessage $ Move D)
--- > , ((modMask x .|. controlMask .|. shiftMask, xK_s ), sendMessage $ SwapWindow)
+-- > , ((modm .|. controlMask .|. shiftMask, xK_Right), sendMessage $ Move R)
+-- > , ((modm .|. controlMask .|. shiftMask, xK_Left ), sendMessage $ Move L)
+-- > , ((modm .|. controlMask .|. shiftMask, xK_Up ), sendMessage $ Move U)
+-- > , ((modm .|. controlMask .|. shiftMask, xK_Down ), sendMessage $ Move D)
+-- > , ((modm .|. controlMask .|. shiftMask, xK_s ), sendMessage $ SwapWindow)
--
-- For detailed instruction on editing the key binding see
-- "XMonad.Doc.Extending#Editing_key_bindings".
diff --git a/XMonad/Layout/Gaps.hs b/XMonad/Layout/Gaps.hs
index 9f7e057..76dd57c 100644
--- a/XMonad/Layout/Gaps.hs
+++ b/XMonad/Layout/Gaps.hs
@@ -54,10 +54,10 @@ import Data.List (delete)
-- You can additionally add some keybindings to toggle or modify the gaps,
-- for example:
--
--- > , ((modMask x .|. controlMask, xK_g), sendMessage $ ToggleGaps) -- toggle all gaps
--- > , ((modMask x .|. controlMask, xK_t), sendMessage $ ToggleGap U) -- toggle the top gap
--- > , ((modMask x .|. controlMask, xK_w), sendMessage $ IncGap R 5) -- increment the right-hand gap
--- > , ((modMask x .|. controlMask, xK_q), sendMessage $ DecGap R 5) -- decrement the right-hand gap
+-- > , ((modm .|. controlMask, xK_g), sendMessage $ ToggleGaps) -- toggle all gaps
+-- > , ((modm .|. controlMask, xK_t), sendMessage $ ToggleGap U) -- toggle the top gap
+-- > , ((modm .|. controlMask, xK_w), sendMessage $ IncGap R 5) -- increment the right-hand gap
+-- > , ((modm .|. controlMask, xK_q), sendMessage $ DecGap R 5) -- decrement the right-hand gap
--
-- If you want complete control over all gaps, you could include
-- something like this in your keybindings, assuming in this case you
diff --git a/XMonad/Layout/GridVariants.hs b/XMonad/Layout/GridVariants.hs
index 2d47a5a..69e97a2 100644
--- a/XMonad/Layout/GridVariants.hs
+++ b/XMonad/Layout/GridVariants.hs
@@ -51,10 +51,10 @@ import qualified XMonad.StackSet as W
-- To be able to change the geometry of the master grid, add something
-- like this to your keybindings:
--
--- > ((modMask .|. shiftMask, xK_equal), sendMessage $ IncMasterCols 1),
--- > ((modMask .|. shiftMask, xK_minus), sendMessage $ IncMasterCols (-1)),
--- > ((modMask .|. ctrlMask, xK_equal), sendMessage $ IncMasterRows 1),
--- > ((modMask .|. ctrlMask, xK_minus), sendMessage $ IncMasterRows (-1))
+-- > ((modm .|. shiftMask, xK_equal), sendMessage $ IncMasterCols 1),
+-- > ((modm .|. shiftMask, xK_minus), sendMessage $ IncMasterCols (-1)),
+-- > ((modm .|. controlMask, xK_equal), sendMessage $ IncMasterRows 1),
+-- > ((modm .|. controlMask, xK_minus), sendMessage $ IncMasterRows (-1))
-- | Grid layout. The parameter is the desired x:y aspect ratio of windows
data Grid a = Grid !Rational
diff --git a/XMonad/Layout/IndependentScreens.hs b/XMonad/Layout/IndependentScreens.hs
index 3ad4cbd..4992a5f 100644
--- a/XMonad/Layout/IndependentScreens.hs
+++ b/XMonad/Layout/IndependentScreens.hs
@@ -48,13 +48,13 @@ import XMonad.StackSet hiding (workspaces)
-- to specific workspace names. In the default configuration, only
-- the keybindings for changing workspace do this:
--
--- > [((m .|. modMask, k), windows $ f i)
+-- > [((m .|. modm, k), windows $ f i)
-- > | (i, k) <- zip (XMonad.workspaces conf) [xK_1 .. xK_9]
-- > , (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)]]
--
-- This should change to
--
--- > [((m .|. modMask, k), windows $ onCurrentScreen f i)
+-- > [((m .|. modm, k), windows $ onCurrentScreen f i)
-- > | (i, k) <- zip (workspaces' conf) [xK_1 .. xK_9]
-- > , (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)]]
--
diff --git a/XMonad/Layout/LayoutBuilder.hs b/XMonad/Layout/LayoutBuilder.hs
index 23a4f27..29972b9 100644
--- a/XMonad/Layout/LayoutBuilder.hs
+++ b/XMonad/Layout/LayoutBuilder.hs
@@ -70,8 +70,8 @@ import Control.Monad
--
-- You may wish to add the following keybindings:
--
--- > , ((modMask x .|. shiftMask, xK_h ), sendMessage $ IncLayoutN (-1))
--- > , ((modMask x .|. shiftMask, xK_l ), sendMessage $ IncLayoutN 1)
+-- > , ((modm .|. shiftMask, xK_h ), sendMessage $ IncLayoutN (-1))
+-- > , ((modm .|. shiftMask, xK_l ), sendMessage $ IncLayoutN 1)
--
-- For detailed instruction on editing the key binding see:
--
diff --git a/XMonad/Layout/LayoutCombinators.hs b/XMonad/Layout/LayoutCombinators.hs
index 0c20e33..b052759 100644
--- a/XMonad/Layout/LayoutCombinators.hs
+++ b/XMonad/Layout/LayoutCombinators.hs
@@ -78,7 +78,7 @@ import XMonad.Layout.DragPane
--
-- Then bind some keys to a 'JumpToLayout' message:
--
--- > , ((modMask x .|. controlMask, xK_f), sendMessage $ JumpToLayout "Full") -- jump directly to the Full layout
+-- > , ((modm .|. controlMask, xK_f), sendMessage $ JumpToLayout "Full") -- jump directly to the Full layout
--
-- See below for more detailed documentation.
diff --git a/XMonad/Layout/LayoutScreens.hs b/XMonad/Layout/LayoutScreens.hs
index ea30968..aa8699c 100644
--- a/XMonad/Layout/LayoutScreens.hs
+++ b/XMonad/Layout/LayoutScreens.hs
@@ -39,8 +39,8 @@ import qualified XMonad.StackSet as W
--
-- Then add some keybindings; for example:
--
--- > , ((modMask x .|. shiftMask, xK_space), layoutScreens 2 (TwoPane 0.5 0.5))
--- > , ((modMask x .|. controlMask .|. shiftMask, xK_space), rescreen)
+-- > , ((modm .|. shiftMask, xK_space), layoutScreens 2 (TwoPane 0.5 0.5))
+-- > , ((modm .|. controlMask .|. shiftMask, xK_space), rescreen)
--
-- Another example use would be to handle a scenario where xrandr didn't
-- work properly (e.g. a VNC X server in my case) and you want to be able
@@ -48,9 +48,9 @@ import qualified XMonad.StackSet as W
--
-- > import XMonad.Layout.LayoutScreens
--
--- > , ((modMask x .|. shiftMask, xK_space),
+-- > , ((modm .|. shiftMask, xK_space),
-- > layoutScreens 1 (fixedLayout [Rectangle 0 0 1024 768]))
--- > , ((modMask x .|. controlMask .|. shiftMask, xK_space), rescreen)
+-- > , ((modm .|. controlMask .|. shiftMask, xK_space), rescreen)
--
-- For detailed instructions on editing your key bindings, see
-- "XMonad.Doc.Extending#Editing_key_bindings".
diff --git a/XMonad/Layout/Magnifier.hs b/XMonad/Layout/Magnifier.hs
index a4c1882..82e1789 100644
--- a/XMonad/Layout/Magnifier.hs
+++ b/XMonad/Layout/Magnifier.hs
@@ -59,11 +59,11 @@ import XMonad.Layout.LayoutModifier
-- Magnifier supports some commands. To use them add something like
-- this to your key bindings:
--
--- > , ((modMask x .|. controlMask , xK_plus ), sendMessage MagnifyMore)
--- > , ((modMask x .|. controlMask , xK_minus), sendMessage MagnifyLess)
--- > , ((modMask x .|. controlMask , xK_o ), sendMessage ToggleOff )
--- > , ((modMask x .|. controlMask .|. shiftMask, xK_o ), sendMessage ToggleOn )
--- > , ((modMask x .|. controlMask , xK_m ), sendMessage Toggle )
+-- > , ((modm .|. controlMask , xK_plus ), sendMessage MagnifyMore)
+-- > , ((modm .|. controlMask , xK_minus), sendMessage MagnifyLess)
+-- > , ((modm .|. controlMask , xK_o ), sendMessage ToggleOff )
+-- > , ((modm .|. controlMask .|. shiftMask, xK_o ), sendMessage ToggleOn )
+-- > , ((modm .|. controlMask , xK_m ), sendMessage Toggle )
--
-- Note that a few other extension modules, such as
-- "XMonad.Layout.MultiToggle" and "XMonad.Layout.ToggleLayouts", also
diff --git a/XMonad/Layout/Maximize.hs b/XMonad/Layout/Maximize.hs
index 82a886f..875d895 100644
--- a/XMonad/Layout/Maximize.hs
+++ b/XMonad/Layout/Maximize.hs
@@ -43,7 +43,7 @@ import Data.List ( partition )
--
-- In the key-bindings, do something like:
--
--- > , ((modMask x, xK_backslash), withFocused (sendMessage . maximizeRestore))
+-- > , ((modm, xK_backslash), withFocused (sendMessage . maximizeRestore))
-- > ...
--
-- For detailed instruction on editing the key binding see:
diff --git a/XMonad/Layout/MessageControl.hs b/XMonad/Layout/MessageControl.hs
index 2b62339..51999a1 100644
--- a/XMonad/Layout/MessageControl.hs
+++ b/XMonad/Layout/MessageControl.hs
@@ -54,7 +54,7 @@ import Control.Arrow (second)
-- @sendMessage $ escape message@, e.g.
--
-- > -- Change the inner layout
--- > ((modMask .|. controlMask, xK_space), sendMessage $ escape NextLayout)
+-- > ((modm .|. controlMask, xK_space), sendMessage $ escape NextLayout)
--
-- If you want unescaped messages to be handled /only/ by the enclosing
-- layout, use the 'ignore' modifier:
diff --git a/XMonad/Layout/Minimize.hs b/XMonad/Layout/Minimize.hs
index dca7600..37462a4 100644
--- a/XMonad/Layout/Minimize.hs
+++ b/XMonad/Layout/Minimize.hs
@@ -43,8 +43,8 @@ import Data.List
--
-- In the key-bindings, do something like:
--
--- > , ((modMask', xK_m ), withFocused (\f -> sendMessage (MinimizeWin f)))
--- > , ((modMask' .|. shiftMask, xK_m ), sendMessage RestoreNextMinimizedWin)
+-- > , ((modm, xK_m ), withFocused (\f -> sendMessage (MinimizeWin f)))
+-- > , ((modm .|. shiftMask, xK_m ), sendMessage RestoreNextMinimizedWin)
--
-- The first action will minimize the focused window, while the second one will restore
-- the next minimized window.
diff --git a/XMonad/Layout/Mosaic.hs b/XMonad/Layout/Mosaic.hs
index b9bad4a..7eac5e9 100644
--- a/XMonad/Layout/Mosaic.hs
+++ b/XMonad/Layout/Mosaic.hs
@@ -56,10 +56,10 @@ import Data.Monoid(Monoid,mempty, mappend)
-- To change the choice in aspect ratio and the relative sizes of windows, add
-- to your keybindings:
--
--- > , ((modMask, xK_a), sendMessage Taller)
--- > , ((modMask, xK_z), sendMessage Wider)
+-- > , ((modm, xK_a), sendMessage Taller)
+-- > , ((modm, xK_z), sendMessage Wider)
--
--- > , ((modMask, xK_r), sendMessage Reset)
+-- > , ((modm, xK_r), sendMessage Reset)
--
-- For more detailed instructions on editing the layoutHook see:
--
diff --git a/XMonad/Layout/MosaicAlt.hs b/XMonad/Layout/MosaicAlt.hs
index d06d7fd..4faf0d6 100644
--- a/XMonad/Layout/MosaicAlt.hs
+++ b/XMonad/Layout/MosaicAlt.hs
@@ -50,11 +50,11 @@ import Data.Ratio
--
-- In the key-bindings, do something like:
--
--- > , ((modMask x .|. shiftMask , xK_a ), withFocused (sendMessage . expandWindowAlt))
--- > , ((modMask x .|. shiftMask , xK_z ), withFocused (sendMessage . shrinkWindowAlt))
--- > , ((modMask x .|. shiftMask , xK_s ), withFocused (sendMessage . tallWindowAlt))
--- > , ((modMask x .|. shiftMask , xK_d ), withFocused (sendMessage . wideWindowAlt))
--- > , ((modMask x .|. controlMask, xK_space), sendMessage resetAlt)
+-- > , ((modm .|. shiftMask , xK_a ), withFocused (sendMessage . expandWindowAlt))
+-- > , ((modm .|. shiftMask , xK_z ), withFocused (sendMessage . shrinkWindowAlt))
+-- > , ((modm .|. shiftMask , xK_s ), withFocused (sendMessage . tallWindowAlt))
+-- > , ((modm .|. shiftMask , xK_d ), withFocused (sendMessage . wideWindowAlt))
+-- > , ((modm .|. controlMask, xK_space), sendMessage resetAlt)
-- > ...
--
-- For detailed instruction on editing the key binding see:
diff --git a/XMonad/Layout/MouseResizableTile.hs b/XMonad/Layout/MouseResizableTile.hs
index 2348689..d82c80e 100644
--- a/XMonad/Layout/MouseResizableTile.hs
+++ b/XMonad/Layout/MouseResizableTile.hs
@@ -49,8 +49,8 @@ import XMonad.Util.XUtils
--
-- You may also want to add the following key bindings:
--
--- > , ((modMask x, xK_u), sendMessage ShrinkSlave) -- %! Shrink a slave area
--- > , ((modMask x, xK_i), sendMessage ExpandSlave) -- %! Expand a slave area
+-- > , ((modm, xK_u), sendMessage ShrinkSlave) -- %! Shrink a slave area
+-- > , ((modm, xK_i), sendMessage ExpandSlave) -- %! Expand a slave area
--
-- For detailed instruction on editing the key binding see:
--
diff --git a/XMonad/Layout/MultiToggle.hs b/XMonad/Layout/MultiToggle.hs
index a5dbb48..ebf41b0 100644
--- a/XMonad/Layout/MultiToggle.hs
+++ b/XMonad/Layout/MultiToggle.hs
@@ -63,7 +63,7 @@ import Data.Maybe
-- you can now dynamically apply the 'XMonad.Layout.Mirror' transformation:
--
-- > ...
--- > , ((modMask, xK_x ), sendMessage $ Toggle MIRROR)
+-- > , ((modm, xK_x ), sendMessage $ Toggle MIRROR)
-- > ...
--
-- (That should be part of your key bindings.) When you press @mod-x@, the
diff --git a/XMonad/Layout/Reflect.hs b/XMonad/Layout/Reflect.hs
index 4d7725c..aed67ac 100644
--- a/XMonad/Layout/Reflect.hs
+++ b/XMonad/Layout/Reflect.hs
@@ -58,8 +58,8 @@ import XMonad.Layout.MultiToggle
--
-- Finally, add some keybindings to do the toggling, for example:
--
--- > , ((modMask x .|. controlMask, xK_x), sendMessage $ Toggle REFLECTX)
--- > , ((modMask x .|. controlMask, xK_y), sendMessage $ Toggle REFLECTY)
+-- > , ((modm .|. controlMask, xK_x), sendMessage $ Toggle REFLECTX)
+-- > , ((modm .|. controlMask, xK_y), sendMessage $ Toggle REFLECTY)
--
-- | Apply a horizontal reflection (left \<--\> right) to a
diff --git a/XMonad/Layout/ResizableTile.hs b/XMonad/Layout/ResizableTile.hs
index a55f42c..cf5994a 100644
--- a/XMonad/Layout/ResizableTile.hs
+++ b/XMonad/Layout/ResizableTile.hs
@@ -42,8 +42,8 @@ import Data.List ((\\))
--
-- You may also want to add the following key bindings:
--
--- > , ((modMask x, xK_a), sendMessage MirrorShrink)
--- > , ((modMask x, xK_z), sendMessage MirrorExpand)
+-- > , ((modm, xK_a), sendMessage MirrorShrink)
+-- > , ((modm, xK_z), sendMessage MirrorExpand)
--
-- For detailed instruction on editing the key binding see:
--
diff --git a/XMonad/Layout/ToggleLayouts.hs b/XMonad/Layout/ToggleLayouts.hs
index c77b0a2..233f5ff 100644
--- a/XMonad/Layout/ToggleLayouts.hs
+++ b/XMonad/Layout/ToggleLayouts.hs
@@ -38,11 +38,11 @@ import XMonad.StackSet (Workspace (..))
--
-- To toggle between layouts add a key binding like
--
--- > , ((modMask x .|. controlMask, xK_space), sendMessage ToggleLayout)
+-- > , ((modm .|. controlMask, xK_space), sendMessage ToggleLayout)
--
-- or a key binding like
--
--- > , ((modMask x .|. controlMask, xK_space), sendMessage (Toggle "Full"))
+-- > , ((modm .|. controlMask, xK_space), sendMessage (Toggle "Full"))
--
-- For detailed instruction on editing the key binding see:
--
diff --git a/XMonad/Layout/WindowArranger.hs b/XMonad/Layout/WindowArranger.hs
index 7ddb6e6..43ccb0a 100644
--- a/XMonad/Layout/WindowArranger.hs
+++ b/XMonad/Layout/WindowArranger.hs
@@ -53,20 +53,20 @@ import Data.Maybe
-- You may also want to define some key binding to move or resize
-- windows. These are good defaults:
--
--- > , ((modMask x .|. controlMask , xK_s ), sendMessage Arrange )
--- > , ((modMask x .|. controlMask .|. shiftMask, xK_s ), sendMessage DeArrange )
--- > , ((modMask x .|. controlMask , xK_Left ), sendMessage (MoveLeft 1))
--- > , ((modMask x .|. controlMask , xK_Right), sendMessage (MoveRight 1))
--- > , ((modMask x .|. controlMask , xK_Down ), sendMessage (MoveDown 1))
--- > , ((modMask x .|. controlMask , xK_Up ), sendMessage (MoveUp 1))
--- > , ((modMask x .|. shiftMask, xK_Left ), sendMessage (IncreaseLeft 1))
--- > , ((modMask x .|. shiftMask, xK_Right), sendMessage (IncreaseRight 1))
--- > , ((modMask x .|. shiftMask, xK_Down ), sendMessage (IncreaseDown 1))
--- > , ((modMask x .|. shiftMask, xK_Up ), sendMessage (IncreaseUp 1))
--- > , ((modMask x .|. controlMask .|. shiftMask, xK_Left ), sendMessage (DecreaseLeft 1))
--- > , ((modMask x .|. controlMask .|. shiftMask, xK_Right), sendMessage (DecreaseRight 1))
--- > , ((modMask x .|. controlMask .|. shiftMask, xK_Down ), sendMessage (DecreaseDown 1))
--- > , ((modMask x .|. controlMask .|. shiftMask, xK_Up ), sendMessage (DecreaseUp 1))
+-- > , ((modm .|. controlMask , xK_s ), sendMessage Arrange )
+-- > , ((modm .|. controlMask .|. shiftMask, xK_s ), sendMessage DeArrange )
+-- > , ((modm .|. controlMask , xK_Left ), sendMessage (MoveLeft 1))
+-- > , ((modm .|. controlMask , xK_Right), sendMessage (MoveRight 1))
+-- > , ((modm .|. controlMask , xK_Down ), sendMessage (MoveDown 1))
+-- > , ((modm .|. controlMask , xK_Up ), sendMessage (MoveUp 1))
+-- > , ((modm .|. shiftMask, xK_Left ), sendMessage (IncreaseLeft 1))
+-- > , ((modm .|. shiftMask, xK_Right), sendMessage (IncreaseRight 1))
+-- > , ((modm .|. shiftMask, xK_Down ), sendMessage (IncreaseDown 1))
+-- > , ((modm .|. shiftMask, xK_Up ), sendMessage (IncreaseUp 1))
+-- > , ((modm .|. controlMask .|. shiftMask, xK_Left ), sendMessage (DecreaseLeft 1))
+-- > , ((modm .|. controlMask .|. shiftMask, xK_Right), sendMessage (DecreaseRight 1))
+-- > , ((modm .|. controlMask .|. shiftMask, xK_Down ), sendMessage (DecreaseDown 1))
+-- > , ((modm .|. controlMask .|. shiftMask, xK_Up ), sendMessage (DecreaseUp 1))
--
-- For detailed instructions on editing your key bindings, see
-- "XMonad.Doc.Extending#Editing_key_bindings".
diff --git a/XMonad/Layout/WindowNavigation.hs b/XMonad/Layout/WindowNavigation.hs
index 34660be..6a8cba4 100644
--- a/XMonad/Layout/WindowNavigation.hs
+++ b/XMonad/Layout/WindowNavigation.hs
@@ -49,14 +49,14 @@ import XMonad.Util.XUtils
--
-- In keybindings:
--
--- > , ((modMask x, xK_Right), sendMessage $ Go R)
--- > , ((modMask x, xK_Left ), sendMessage $ Go L)
--- > , ((modMask x, xK_Up ), sendMessage $ Go U)
--- > , ((modMask x, xK_Down ), sendMessage $ Go D)
--- > , ((modMask x .|. controlMask, xK_Right), sendMessage $ Swap R)
--- > , ((modMask x .|. controlMask, xK_Left ), sendMessage $ Swap L)
--- > , ((modMask x .|. controlMask, xK_Up ), sendMessage $ Swap U)
--- > , ((modMask x .|. controlMask, xK_Down ), sendMessage $ Swap D)
+-- > , ((modm, xK_Right), sendMessage $ Go R)
+-- > , ((modm, xK_Left ), sendMessage $ Go L)
+-- > , ((modm, xK_Up ), sendMessage $ Go U)
+-- > , ((modm, xK_Down ), sendMessage $ Go D)
+-- > , ((modm .|. controlMask, xK_Right), sendMessage $ Swap R)
+-- > , ((modm .|. controlMask, xK_Left ), sendMessage $ Swap L)
+-- > , ((modm .|. controlMask, xK_Up ), sendMessage $ Swap U)
+-- > , ((modm .|. controlMask, xK_Down ), sendMessage $ Swap D)
--
-- For detailed instruction on editing the key binding see:
--
diff --git a/XMonad/Layout/WorkspaceDir.hs b/XMonad/Layout/WorkspaceDir.hs
index a989fcb..ccfaafe 100644
--- a/XMonad/Layout/WorkspaceDir.hs
+++ b/XMonad/Layout/WorkspaceDir.hs
@@ -56,7 +56,7 @@ import XMonad.StackSet ( tag, currentTag )
-- WorkspaceDir provides also a prompt. To use it you need to import
-- "XMonad.Prompt" and add something like this to your key bindings:
--
--- > , ((modMask x .|. shiftMask, xK_x ), changeDir defaultXPConfig)
+-- > , ((modm .|. shiftMask, xK_x ), changeDir defaultXPConfig)
--
-- For detailed instruction on editing the key binding see:
--