Difference between revisions of "Xmonad/General xmonad.hs config tips"

From HaskellWiki
Jump to navigation Jump to search
(Break into subsections and re-arrange by frequency of request)
Line 9: Line 9:
 
Please add what you found useful, and of course improving existing tips or adding alternatives is highly appreciated!
 
Please add what you found useful, and of course improving existing tips or adding alternatives is highly appreciated!
   
  +
== Managing Windows aka Manage Hooks ==
== Making window float by default, or send it to specific workspace ==
 
  +
=== Making window float by default, or send it to specific workspace ===
 
 
This example shifts Rythmbox to workspace "=" and XDvi to "7:dvi", floats Xmessage, and uses manageDocks to leave gaps for status bars automatically. All this is combined with the default xmonad manageHook. [[Xmonad/Config_archive/John_Goerzen%27s_Configuration|This step-by-step tutorial]] covers initially setting up a manageHook, too.
 
This example shifts Rythmbox to workspace "=" and XDvi to "7:dvi", floats Xmessage, and uses manageDocks to leave gaps for status bars automatically. All this is combined with the default xmonad manageHook. [[Xmonad/Config_archive/John_Goerzen%27s_Configuration|This step-by-step tutorial]] covers initially setting up a manageHook, too.
   
Line 20: Line 20:
 
, className =? "XDvi" --> doShift "7:dvi"
 
, className =? "XDvi" --> doShift "7:dvi"
 
, className =? "Xmessage" --> doFloat
 
, className =? "Xmessage" --> doFloat
, manageDocks
+
, avoidStruts
 
]
 
]
   
Line 26: Line 26:
 
{
 
{
 
-- terminal, modMask, keys, etc.
 
-- terminal, modMask, keys, etc.
-- bind a key to 'sendMessage ToggleStruts' to toggle statusbar
+
-- (bind to 'sendMessage ToggleStruts' to toggle avoidStruts statusbar)
 
, manageHook = manageHook defaultConfig <+> myManageHook -- uses default too
 
, manageHook = manageHook defaultConfig <+> myManageHook -- uses default too
 
-- layoutHook, logHook, etc.
 
-- layoutHook, logHook, etc.
Line 65: Line 65:
   
 
See also the [http://xmonad.org/xmonad-docs/xmonad/XMonad-ManageHook.html documentation for ManageHook].
 
See also the [http://xmonad.org/xmonad-docs/xmonad/XMonad-ManageHook.html documentation for ManageHook].
  +
  +
=== Making windows unfloat ===
  +
A related task is - how do I unfloat windows of a particular class or
  +
name? Some people using lots of apps with dialogs and transient windows
  +
that don't set 'fixed size' or 'transient to' hints (so they don't float
  +
by default as intended) would rather default to floating everything, and
  +
specify windows to tile. Well, as before, we need to set up a managehook,
  +
and then write a simple function which duplicates the mod-t functionality of
  +
unfloating (but with a different type):
  +
<haskell>
  +
myManageHook :: ManageHook
  +
myManageHook = composeAll [ className =? "defcon.bin.x86" --> unfloat,
  +
className =? "Darwinia" --> unfloat ]
  +
<+> doFloat <+> manageDocks
  +
where unfloat = ask >>= doF . W.sink
  +
</haskell>
   
 
=== Starting an app on more than one workspace ===
 
=== Starting an app on more than one workspace ===
 
 
To start emacs on workspaces 2, 3, and 4, for example, use something like the following in your manage hook:
 
To start emacs on workspaces 2, 3, and 4, for example, use something like the following in your manage hook:
 
<haskell>
 
<haskell>
Line 80: Line 95:
 
</haskell>
 
</haskell>
   
  +
=== Ignoring a client (or having it sticky) ===
== Making windows unfloat ==
 
A related task is - how do I unfloat windows of a particular class or name? Well, as before, we need to set up a managehook, and then we write a simple function which duplicates the mod-t functionality of unfloating (but with a different type):
 
<haskell>
 
myManageHook :: ManageHook
 
myManageHook = composeAll [ className =? "defcon.bin.x86" --> unfloat,
 
className =? "Darwinia" --> unfloat ]
 
<+> manageDocks
 
where unfloat = ask >>= doF . W.sink
 
</haskell>
 
 
== Ignoring a client (or having it sticky) ==
 
 
 
You can have the position and geometry of a client window respected, and have that window
 
You can have the position and geometry of a client window respected, and have that window
 
be sticky, by ignoring it when it is created:
 
be sticky, by ignoring it when it is created:
Line 97: Line 101:
 
main = xmonad $ defaultConfig
 
main = xmonad $ defaultConfig
 
{
 
{
  +
--
....
 
, manageHook = manageHook defaultConfig
+
, manageHook = manageHook defaultConfig
<+>
+
<+>
(className =? "XClock" --> doIgnore)
+
(className =? "XClock" --> doIgnore)
  +
--
...
 
 
}
 
}
 
</haskell>
 
</haskell>
Line 108: Line 112:
 
In >xmonad-0.8, the XMonad.Layout.Monitor offers some useful functions for managing such windows as well.
 
In >xmonad-0.8, the XMonad.Layout.Monitor offers some useful functions for managing such windows as well.
   
== Adding your own keybindings ==
+
== Key and Mouse Bindings ==
  +
=== Adding your own keybindings ===
   
 
This adds Mod-x keybinding for running ''xlock''.
 
This adds Mod-x keybinding for running ''xlock''.
 
<haskell>
 
<haskell>
 
import qualified Data.Map as M
 
import qualified Data.Map as M
  +
--
 
-- skipped
 
   
 
main = xmonad $ defaultConfig {
 
main = xmonad $ defaultConfig {
Line 130: Line 134:
 
Also, the [http://code.haskell.org/XMonadContrib/XMonad/Actions/CycleWindows.hs Util.EZConfig] extension allows adding keybindings with simpler syntax, and even creates submaps for sequences like, e.g. "mod-x f" to launch firefox. You can use normal xmonad keybinding lists with its additionalKeys function, or with additionalKeysP, the bindings look like this:
 
Also, the [http://code.haskell.org/XMonadContrib/XMonad/Actions/CycleWindows.hs Util.EZConfig] extension allows adding keybindings with simpler syntax, and even creates submaps for sequences like, e.g. "mod-x f" to launch firefox. You can use normal xmonad keybinding lists with its additionalKeys function, or with additionalKeysP, the bindings look like this:
 
<haskell>
 
<haskell>
main = xmonad $ defaultConfig { terminal = "urxvt" }
+
main = xmonad $ defaultConfig {
`additionalKeysP`
+
terminal = "urxvt"
  +
, modMask = mod4Mask
[ ("M-<Up>", windows XMonad.StackSet.swapUp)
 
  +
}
, ("M-x f", spawn "firefox")
 
]
+
`additionalKeysP`
  +
[ ("M-<Up>", windows XMonad.StackSet.swapUp)
  +
, ("M-x f", spawn "firefox")
  +
]
   
 
</haskell>
 
</haskell>
Line 140: Line 147:
 
This is also described in [http://xmonad.org/xmonad-docs/xmonad-contrib/XMonad-Doc-Extending.html#9]
 
This is also described in [http://xmonad.org/xmonad-docs/xmonad-contrib/XMonad-Doc-Extending.html#9]
   
  +
=== Adding your own mouse bindings ===
== Displaying keybindings with dzen2 ==
 
  +
Adding your own mouse bindings is explained in
  +
[http://xmonad.org/xmonad-docs/xmonad-contrib/XMonad-Doc-Extending.html#13]
  +
  +
If you have a mouse with more than 5 buttons you can simply use '6'
  +
instead of 'button6' which isn't defined.
  +
  +
e.g. with
  +
[http://xmonad.org/xmonad-docs/xmonad-contrib/XMonad-Util-EZConfig.html EZConfig]:
  +
  +
,((0, 6), (\w -> focus w >> windows W.swapMaster))
   
  +
=== Displaying keybindings with dzen2 ===
 
Sometimes, trying different xmonad.hs files, or while dialing in custom key bindings it can be nice to have a reminder of what does what. Of course, just editing or grepping the xmonad.hs is one solution, but for a nice colourized output, try adapting a script like this to your needs:
 
Sometimes, trying different xmonad.hs files, or while dialing in custom key bindings it can be nice to have a reminder of what does what. Of course, just editing or grepping the xmonad.hs is one solution, but for a nice colourized output, try adapting a script like this to your needs:
   
Line 175: Line 193:
 
[[image: Showkeys.png|220px]]
 
[[image: Showkeys.png|220px]]
   
  +
== Navigating and Displaying Workspaces ==
== Adding your own mouse bindings ==
 
  +
=== Using Next Previous Recent Workspaces rather than mod-n ===
  +
The Actions.Plane and Actions.CycleWS extensions allow many ways to
  +
navigate workspaces, or shift windows to other workspaces. Plane is
  +
easier to set up, CycleWS allows nearly any behaviour you'd ever want.
  +
Actions.CycleRecentWS allows swapping with previous or next workspace
  +
similar to how many window managers cycle windows with alt tab.
   
  +
=== Skipping the Scratchpad workspace while using CycleWS ===
Adding your own mouse bindings is explained in
 
  +
The Util.Scratchpad module provides a configurable floating terminal that is easily shifted to the current workspace or banished to its own "SP" workspace. Most people want the "SP" tag ignored during workspace navigation.
[http://xmonad.org/xmonad-docs/xmonad-contrib/XMonad-Doc-Extending.html#13]
 
 
If you have a mouse with more than 5 buttons you can simply use '6'
 
instead of 'button6' which isn't defined.
 
 
e.g. with
 
[http://xmonad.org/xmonad-docs/xmonad-contrib/XMonad-Util-EZConfig.html EZConfig]:
 
 
,((0, 6), (\w -> focus w >> windows W.swapMaster))
 
 
== Skipping the Scratchpad workspace while using CycleWS ==
 
 
The Actions.Plane and Actions.CycleWS extensions allow many ways to navigate workspaces, or shift windows to other workspaces. Plane is easier to set up, CycleWS allows nearly any behaviour you'd ever want. The Util.Scratchpad module provides a configurable floating terminal that is easily shifted to the current workspace or banished to its own "SP" workspace. Most people want the "SP" tag ignored during workspace navigation.
 
   
 
Here's one way to do that with Actions.CycleWS, ready to be customized, for example to use HiddenEmptyWSs instead of HiddenNonEmptyWSs, etc.
 
Here's one way to do that with Actions.CycleWS, ready to be customized, for example to use HiddenEmptyWSs instead of HiddenNonEmptyWSs, etc.
Line 256: Line 268:
 
top level definitions if you want to use them repeatedly.
 
top level definitions if you want to use them repeatedly.
   
  +
=== Doing things on second of two monitors while focus stays on current ===
==Do not show scratchpad workspace in status bar or dynamicLog==
 
  +
You can use something like the following in your keybindings.
  +
<haskell>
  +
-- c here is your XConfig l, aka defaultConfig { ....
  +
, ((modMask c, xK_v), withOtherOf2 W.view)
  +
, ((modMask c, xK_f), withOtherOf2 W.shift)
  +
, ((modMask c, xK_u), onOtherOf2 W.focusUp)
  +
]
  +
  +
withOtherOf2 :: (WorkspaceId -> WindowSet -> WindowSet) -> X ()
  +
withOtherOf2 fn = do
  +
tag <- withWindowSet $ screenWorkspace . (1 -) . W.screen . W.current
  +
flip whenJust (windows . fn) tag
  +
  +
onOtherOf2 :: (WindowSet -> WindowSet) -> X ()
  +
onOtherOf2 fn' = do
  +
wset <- gets windowset
  +
this <- return . W.currentTag $ wset
  +
that <- screenWorkspace . (1 -) . W.screen . W.current $ wset
  +
windows $ W.view this . fn' . maybe id W.view that
  +
</haskell>
   
  +
===Do not show scratchpad workspace in status bar or dynamicLog===
 
You can also use <hask>fmap (.scratchpadFilterOutWorkspace)</hask> on a ppSort
 
You can also use <hask>fmap (.scratchpadFilterOutWorkspace)</hask> on a ppSort
 
in your logHook.
 
in your logHook.
Line 268: Line 301:
 
import XMonad.Util.WorkspaceCompare
 
import XMonad.Util.WorkspaceCompare
   
-- skipped
+
-- etc
 
 
, logHook = dynamicLogWithPP defaultPP {
 
, logHook = dynamicLogWithPP defaultPP {
 
ppSort = fmap (.scratchpadFilterOutWorkspace) getSortByTag
 
ppSort = fmap (.scratchpadFilterOutWorkspace) getSortByTag
  +
--
 
</haskell>
 
</haskell>
   
  +
== Arranging Windows aka Layouts ==
== Sharing a configuration across different hosts ==
 
  +
=== Binding keys to a specific layout ===
 
It is possible to have different parts of the configuration file vary from one host to another, without needing a different config file for each host. Here is an example from my configuration file:
 
<haskell>
 
import System.Posix.Unistd
 
 
-- skipped
 
 
main = do
 
host <- fmap nodeName getSystemID
 
-- equivalent, and arguably more readable is
 
-- host <- getSystemID >>= nodeName
 
xmonad $ defaultConfig
 
{ terminal = "rxvt"
 
, modMask = (if host == "janice" then
 
mod1Mask .|. controlMask
 
else
 
mod4Mask)
 
-- also can pass hostname to other functions if needed
 
, logHook = dynamicLogWithPP $ myPP host
 
}
 
 
myPP hostname =
 
if hostname == "janice" then dzenPP else xmobarPP
 
</haskell>
 
 
== Binding keys to a specific layout ==
 
   
 
Sometimes people want to bind a key to a particular layout, rather
 
Sometimes people want to bind a key to a particular layout, rather
Line 328: Line 336:
 
</haskell>
 
</haskell>
   
  +
=== Docks, Monitors, Sticky Windows ===
== Using local state in the config file ==
 
  +
See [[#Ignoring a client (or having it sticky)]]
  +
  +
== Misc ==
  +
=== Using local state in the config file ===
   
 
As the xmonad config file is really just the entry point to the entire
 
As the xmonad config file is really just the entry point to the entire
Line 368: Line 380:
   
 
Note IORef is allocated at startup.
 
Note IORef is allocated at startup.
  +
  +
=== Sharing a configuration across different hosts ===
  +
  +
It is possible to have different parts of the configuration file vary from one host to another, without needing a different config file for each host. Here is an example from my configuration file:
  +
<haskell>
  +
import System.Posix.Unistd
  +
  +
-- etc
  +
  +
main = do
  +
host <- fmap nodeName getSystemID
  +
-- or -- host <- nodeName `fmap` getSystemID
  +
-- or -- host <- nodeName <$> getSystemID -- import Control.Applicative
  +
xmonad $ defaultConfig
  +
{ terminal = "rxvt"
  +
, modMask = (if host === "janice" then
  +
mod1Mask .|. controlMask
  +
else
  +
mod4Mask)
  +
-- also can pass hostname to functions outside main if needed
  +
, logHook = dynamicLogWithPP $ myPP host
  +
, startupHook = whereAmI host
  +
} where -- like this:
  +
whereAmI name = spawn $ xmessage "Silly, this host is " ++ name
  +
  +
-- and this:
  +
myPP hostname =
  +
if hostname === "janice" then dzenPP else xmobarPP
  +
</haskell>

Revision as of 17:49, 17 February 2009


This document assumes you're running >= XMonad-0.8.

It describes general tips for configuring xmonad.hs, for example "How to make window X float by default" and others. If you can't find what you're searching for, you may want to look at the Config archive or ask for help on #xmonad@irc.freenode.net.

Also useful, for an overview of how to configure bindings and hooks, and (somewhat out of date) summary of xmonad-contrib extensions, see XMonad.Doc.Extending.

Please add what you found useful, and of course improving existing tips or adding alternatives is highly appreciated!

Managing Windows aka Manage Hooks

Making window float by default, or send it to specific workspace

This example shifts Rythmbox to workspace "=" and XDvi to "7:dvi", floats Xmessage, and uses manageDocks to leave gaps for status bars automatically. All this is combined with the default xmonad manageHook. This step-by-step tutorial covers initially setting up a manageHook, too.

-- module imports and other top level definitions

myManageHook = composeAll
   [ className =? "Rhythmbox" --> doShift "="
   , className =? "XDvi"      --> doShift "7:dvi"
   , className =? "Xmessage"  --> doFloat
   , avoidStruts
   ]

main = xmonad $ defaultConfig
   {
   -- terminal, modMask, keys, etc.
   -- (bind to 'sendMessage ToggleStruts' to toggle avoidStruts statusbar)
   , manageHook    = manageHook defaultConfig <+> myManageHook -- uses default too
   -- layoutHook, logHook, etc.
   }

This example sends Firefox to workspace "web" when it starts. Gajim gets sent to workspace "jabber". Finally, it floats Firefox dialog windows, Gajim and Xmessage windows, and windows with Google or Pidgin as any part of the class name, likewise any window with "VLC" anywhere in its title.

-- Data.List provides isPrefixOf isSuffixOf and isInfixOf
import Data.List 
--
myManageHook = composeAll . concat $
   [ [ className =? "Firefox-bin" --> doShift "web" ]
   , [ className =? "Gajim.py"    --> doShift "jabber" ]
   , [(className =? "Firefox" <&&> resource =? "Dialog") --> doFloat]

     -- using list comprehensions and partial matches
   , [ className =?  c --> doFloat | c <- myFloats ]
   , [ fmap ( c `isInfixOf`) className --> doFloat | c <- myMatchAnywhereFloatsC ]
   , [ fmap ( c `isInfixOf`) title     --> doFloat | c <- myMatchAnywhereFloatsT ]
   ]
  where myFloatsC = ["Gajim.py", "Xmessage"]
        myMatchAnywhereFloatsC = ["Google","Pidgin"]
        myMatchAnywhereFloatsT = ["VLC"] -- this one is silly for only one string!

Here's another example using both classes and titles:

myManageHook :: ManageHook
myManageHook = composeAll . concat $
    [ [ title =? t --> doFloat | t <- myTitleFloats]
    , [ className =? c --> doFloat | c <- myClassFloats ] ]
    where
        myTitleFloats = ["Transferring"] -- for the KDE "open link" popup from konsole
        myClassFloats = ["Pinentry"] -- for gpg passphrase entry

See the FAQ about using xprop to get the properties of windows.

See also the documentation for ManageHook.

Making windows unfloat

A related task is - how do I unfloat windows of a particular class or name? Some people using lots of apps with dialogs and transient windows that don't set 'fixed size' or 'transient to' hints (so they don't float by default as intended) would rather default to floating everything, and specify windows to tile. Well, as before, we need to set up a managehook, and then write a simple function which duplicates the mod-t functionality of unfloating (but with a different type):

myManageHook :: ManageHook
myManageHook = composeAll [ className =? "defcon.bin.x86" --> unfloat,
                            className =? "Darwinia" --> unfloat ]
               <+> doFloat <+> manageDocks
                   where unfloat = ask >>= doF . W.sink

Starting an app on more than one workspace

To start emacs on workspaces 2, 3, and 4, for example, use something like the following in your manage hook:

-- etc
import XMonad.Actions.CopyWindow

myManageHook = composeAll
    [ className =? "Emacs" --> (ask >>= doF .  \w -> (\ws -> foldr ($) ws (copyToWss ["2","4"] w) ) . W.shift "3" ) :: ManageHook
    , resource  =? "kdesktop" --> doIgnore
    ]
  where copyToWss ids win = map (copyWindow win) ids

Ignoring a client (or having it sticky)

You can have the position and geometry of a client window respected, and have that window be sticky, by ignoring it when it is created:

main = xmonad $ defaultConfig
{
  --
  , manageHook    = manageHook defaultConfig
                         <+>
                         (className =? "XClock" --> doIgnore)
  --
}

Would let xclock be sticky, and have its geometry respected.

In >xmonad-0.8, the XMonad.Layout.Monitor offers some useful functions for managing such windows as well.

Key and Mouse Bindings

Adding your own keybindings

This adds Mod-x keybinding for running xlock.

import qualified Data.Map as M
--

main = xmonad $ defaultConfig {
  --
  , keys          = \c -> mykeys c `M.union` keys defaultConfig c }
  --
  }
where
    mykeys (XConfig {modMask = modm}) = M.fromList $
         [ ((modm , xK_x), spawn "xlock") ]

For a list of the identifiers used for various keys, see Graphics.X11.Types and ExtraTypes.

Also, the Util.EZConfig extension allows adding keybindings with simpler syntax, and even creates submaps for sequences like, e.g. "mod-x f" to launch firefox. You can use normal xmonad keybinding lists with its additionalKeys function, or with additionalKeysP, the bindings look like this:

main = xmonad $ defaultConfig {
          terminal = "urxvt"
        , modMask  = mod4Mask
        }
        `additionalKeysP`
        [ ("M-<Up>", windows XMonad.StackSet.swapUp)
        , ("M-x f", spawn "firefox")
        ]

This is also described in [1]

Adding your own mouse bindings

Adding your own mouse bindings is explained in [2]

If you have a mouse with more than 5 buttons you can simply use '6' instead of 'button6' which isn't defined.

e.g. with EZConfig:

 ,((0, 6), (\w -> focus w >> windows W.swapMaster))

Displaying keybindings with dzen2

Sometimes, trying different xmonad.hs files, or while dialing in custom key bindings it can be nice to have a reminder of what does what. Of course, just editing or grepping the xmonad.hs is one solution, but for a nice colourized output, try adapting a script like this to your needs:

fgCol=green4
bgCol=black
titleCol=green4
commentCol=slateblue
keyCol=green2
XCol=orange3
startLine=3
( echo "   ^fg($titleCol) ----------- keys -----------^fg()";
  egrep 'xK_|eys' ~/.xmonad/xmonad.hs | tail -n +$startLine \
    | sed -e 's/\( *--\)\(.*eys*\)/\1^fg('$commentCol')\2^fg()/' \
          -e 's/((\(.*xK_.*\)), *\(.*\))/^fg('$keyCol')\1^fg(), ^fg('$XCol')\2^fg()/'                                                                                
  echo '^togglecollapse()';
  echo '^scrollhome()' ) | dzen2 -fg $fgCol -bg $bgCol -x 700 -y 36 -l 22 -ta l -w 900 -p

Then bind a key to spawn "/path/to/my/showKeysScript". While there's plenty of room for improvement in the parsing, this is fine for a quick and dirty display of normal or additionalKeys style bindings. It obviously would need to be changed to parse additionalKeysP style. To have comments displayed, note that it looks for indented comments containing 'eys' so use "Keys" or "keys" in " --" style comments to create keybinding subsections.

Note that in older versions of dzen ^togglecollapse() and ^scrollhome() may not yet be supported. Use something like the following in dzen command line to get similar result:

-e 'onstart=togglecollapse,scrollhome;
    entertitle=uncollapse,grabkeys;
    enterslave=grabkeys;leaveslave=collapse,ungrabkeys;
    button2=togglestick;button3=exit:13;
    button4=scrollup;button5=scrolldown;
    key_Escape=ungrabkeys,exit'

Showkeys.png

Navigating and Displaying Workspaces

Using Next Previous Recent Workspaces rather than mod-n

The Actions.Plane and Actions.CycleWS extensions allow many ways to navigate workspaces, or shift windows to other workspaces. Plane is easier to set up, CycleWS allows nearly any behaviour you'd ever want. Actions.CycleRecentWS allows swapping with previous or next workspace similar to how many window managers cycle windows with alt tab.

Skipping the Scratchpad workspace while using CycleWS

The Util.Scratchpad module provides a configurable floating terminal that is easily shifted to the current workspace or banished to its own "SP" workspace. Most people want the "SP" tag ignored during workspace navigation.

Here's one way to do that with Actions.CycleWS, ready to be customized, for example to use HiddenEmptyWSs instead of HiddenNonEmptyWSs, etc.

Note that notSP is defined in the where clause of this example. It is just another name for (return $ ("SP" /=) . W.tag) :: X (WindowSpace -> Bool) Likewise, for getSortByIndexNoSP, look in where clause.

--
import qualified XMonad.StackSet as W
import XMonad.Util.EZConfig -- optional, but helpful
import Xmonad.Actions.CycleWS
import XMonad.Util.Scratchpad
import XMonad.Util.WorkspaceCompare

modKey = mod4Mask

--  other keybindings [    ]
    ++
    -- focus /any/ workspace except scratchpad, even visible
    [ ((modKey,               xK_Right ), moveTo Next (WSIs notSP))
    , ((modKey,               xK_Left  ), moveTo Prev (WSIs notSP))

    -- move window to /any/ workspace except scratchpad
    , ((modKey .|. shiftMask, xK_Right ), shiftTo Next (WSIs notSP))
    , ((modKey .|. shiftMask, xK_Left  ), shiftTo Prev (WSIs notSP))

    -- focus HiddenNonEmpty wss except scratchpad
    , ((modKey .|. controlMask , xK_Right),
          windows . W.greedyView =<< findWorkspace getSortByIndexNoSP Next HiddenNonEmptyWS 1)
    , ((modKey .|. controlMask , xK_Left),
          windows . W.greedyView =<< findWorkspace getSortByIndexNoSP Prev HiddenNonEmptyWS 1)

    -- move window to HiddenNonEmpty wss except scratchpad
    , ((modKey .|. shiftMask, xK_Right),
          windows . W.shift =<< findWorkspace getSortByIndexNoSP Next HiddenNonEmptyWS 1)
    , ((modKey .|. shiftMask, xK_Left),
          windows . W.shift =<< findWorkspace getSortByIndexNoSP Prev HiddenNonEmptyWS 1)

    -- move window to and focus HiddenNonEmpty wss except scratchpad
    , ((modKey .|. controlMask .|. shiftMask, xK_Right), shiftAndView' Next)
    , ((modKey .|. controlMask .|. shiftMask, xK_Left), shiftAndView' Prev)
    ]

  -- Make sure to put any where clause after your last list of key bindings*
  where notSP = (return $ ("SP" /=) . W.tag) :: X (WindowSpace -> Bool)
        -- | any workspace but scratchpad
        shiftAndView dir = findWorkspace getSortByIndex dir (WSIs notSP) 1
                >>= \t -> (windows . W.shift $ t) >> (windows . W.greedyView $ t)
        -- | hidden, non-empty workspaces less scratchpad
        shiftAndView' dir = findWorkspace getSortByIndexNoSP dir HiddenNonEmptyWS 1
                >>= \t -> (windows . W.shift $ t) >> (windows . W.greedyView $ t)
        getSortByIndexNoSP =
                fmap (.scratchpadFilterOutWorkspace) getSortByIndex

  -- *For example, you could not (++) another list here

  --   ------------------------------------------------------------------------
  --   If notSP or some variant of the shiftAndView functions isn't needed, but
  --   you do want to use shiftTo or moveTo, delete notSP and use a version of:
  --   ((modKey, xK_Right ), moveTo Next . WSIs . return $ ("SP" /=) . W.tag)

Also of course, the where definitions, or X () actions bound here can be moved out to top level definitions if you want to use them repeatedly.

Doing things on second of two monitors while focus stays on current

You can use something like the following in your keybindings.

      -- c here is your XConfig l, aka defaultConfig { ....
    , ((modMask c, xK_v), withOtherOf2 W.view)
    , ((modMask c, xK_f), withOtherOf2 W.shift)
    , ((modMask c, xK_u), onOtherOf2 W.focusUp)                                                                                                                  
    ]

withOtherOf2 :: (WorkspaceId -> WindowSet -> WindowSet) -> X ()
withOtherOf2 fn = do
   tag <- withWindowSet $ screenWorkspace . (1 -) . W.screen . W.current
   flip whenJust (windows . fn) tag

onOtherOf2 :: (WindowSet -> WindowSet) -> X ()
onOtherOf2 fn' = do
   wset <- gets windowset
   this <- return . W.currentTag $ wset
   that <- screenWorkspace . (1 -) . W.screen . W.current $ wset
   windows $ W.view this . fn' . maybe id W.view that

Do not show scratchpad workspace in status bar or dynamicLog

You can also use fmap (.scratchpadFilterOutWorkspace) on a ppSort in your logHook.

  , logHook = dynamicLogWithPP defaultPP {
                ppSort = fmap (.scratchpadFilterOutWorkspace) $ ppSort defaultPP

or

import XMonad.Util.WorkspaceCompare

  -- etc
  , logHook = dynamicLogWithPP defaultPP {
                ppSort = fmap (.scratchpadFilterOutWorkspace) getSortByTag
  --

Arranging Windows aka Layouts

Binding keys to a specific layout

Sometimes people want to bind a key to a particular layout, rather than having to cycle through the available layouts:

You can do this using the JumpToLayout message from the XMonad.Layout.LayoutCombinators extension module. For example:

import XMonad hiding ( (|||) )  -- don't use the normal ||| operator
import XMonad.Layout.LayoutCombinators   -- use the one from LayoutCombinators instead
import XMonad.Util.EZConfig  -- add keybindings easily

main = xmonad myConfig

myConfig = defaultConfig {
  --                     
  layoutHook = tall ||| Mirror tall ||| Full
  --                                    
} `additionalKeysP`
  [ ("M-<F1>", sendMessage $ JumpToLayout "Tall")
  , ("M-<F2>", sendMessage $ JumpToLayout "Mirror Tall")
  , ("M-<F3>", sendMessage $ JumpToLayout "Full")       
  ]                                              
      
tall = Tall 1 (3/100) (1/2)

Docks, Monitors, Sticky Windows

See #Ignoring a client (or having it sticky)

Misc

Using local state in the config file

As the xmonad config file is really just the entry point to the entire program, you can do arbitrary IO effects before running xmonad. Including initialising mutable "global" state. That state could even be made persistent , independent of xmonad's built-in persistence (by writing it to a file on mod-q).

Here's an example where we store the layouts "IncMaster" value in a local mutable variable, so that we can provide a key binding that takes that value to compute an offset.

import XMonad
import XMonad.Util.EZConfig
import Data.IORef
import XMonad.Actions.FocusNth

main = do
    offset <- newIORef 1
    xmonad $ defaultConfig
         `additionalKeys`
           ([ ((modMask defaultConfig, xK_comma ),
                    do io $ modifyIORef offset (\i -> max 0 (i-1))
                       sendMessage (IncMasterN (-1))
                    )

            , ((modMask defaultConfig, xK_period ),
                    do io $ modifyIORef offset (+1)
                       sendMessage (IncMasterN 1)
                   ) -- %! Expand the master area

            ] ++ [((modMask defaultConfig .|. shiftMask, k), do
                        n <- io $ readIORef offset
                        focusNth (i+n))
                 | (i, k) <- zip [0 .. 8] [xK_1 ..]]
            )

Note IORef is allocated at startup.

Sharing a configuration across different hosts

It is possible to have different parts of the configuration file vary from one host to another, without needing a different config file for each host. Here is an example from my configuration file:

import System.Posix.Unistd

-- etc

main = do
    host <- fmap nodeName getSystemID
    -- or -- host <- nodeName `fmap` getSystemID
    -- or -- host <- nodeName <$> getSystemID -- import Control.Applicative
    xmonad $ defaultConfig
      { terminal           = "rxvt"
      , modMask            = (if host === "janice" then
                                mod1Mask .|. controlMask
                              else
                                mod4Mask)
      -- also can pass hostname to functions outside main if needed
      , logHook = dynamicLogWithPP $ myPP host
      , startupHook = whereAmI host
      } where -- like this:
          whereAmI name = spawn $ xmessage "Silly, this host is " ++ name

        -- and this:
myPP hostname =
    if hostname === "janice" then dzenPP else xmobarPP