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

From HaskellWiki
Jump to navigation Jump to search
(found that Java bug about WM_CLASS, replaced comment with link)
(baffed the external link; been too long since I did wikimedia markup...)
Line 292: Line 292:
 
Sometimes, instead of matching a program's resource name or window class, it is useful to change the program's name and/or class to something easier to detect. This is most useful when starting programs inside terminal emulators, but can also be used to distinguish between, say, editor sessions.
 
Sometimes, instead of matching a program's resource name or window class, it is useful to change the program's name and/or class to something easier to detect. This is most useful when starting programs inside terminal emulators, but can also be used to distinguish between, say, editor sessions.
   
Most X11 programs allow you to specify their resource name and/or class. Usually it's not possible to do so down to the level of individual windows, so you are likely to require <tt>[[Xmonad/Frequently_asked_questions#What_about_other_properties.2C_such_as_WM_WINDOW_ROLE.3F|WM_WINDOW_ROLE]]</tt> for that. Note that Java-based programs do not support any useful way to set either resource name or window class ([[http://bugs.sun.com/bugdatabase/view_bug.do?bug_id=6528430|bug 6528430]]).
+
Most X11 programs allow you to specify their resource name and/or class. Usually it's not possible to do so down to the level of individual windows, so you are likely to require <tt>[[Xmonad/Frequently_asked_questions#What_about_other_properties.2C_such_as_WM_WINDOW_ROLE.3F|WM_WINDOW_ROLE]]</tt> for that. Note that Java-based programs do not support any useful way to set either resource name or window class ([http://bugs.sun.com/bugdatabase/view_bug.do?bug_id=6528430 bug 6528430]).
   
 
==== Gnome and KDE ====
 
==== Gnome and KDE ====

Revision as of 06:20, 24 February 2012


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

ManageHooks define special actions to be performed on newly created windows matching specific properties.

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

ManageHook examples

This example shifts Rythmbox to workspace "=" and XDvi to "7:dvi", floats Xmessage, and uses manageDocks to make docks visible on all workspaces. All this is combined with the default xmonad manageHook. This step-by-step tutorial covers initially setting up a manageHook, too.

import XMonad
import XMonad.Hooks.ManageDocks
import XMonad.Util.EZConfig
-- module imports and other top level definitions

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

main = xmonad $ defaultConfig
   { workspaces = ["1:dev","2:mail","3:web","4:comm","5:ham","6:tmp","7:dvi","8","9","0","-","="]
   , manageHook    = myManageHook <+> manageHook defaultConfig -- uses default too
   -- set terminal, modMask, etc.
   } `additionalKeysP` myKeys

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 <- myFloatsC ]
   , [ fmap ( c `isInfixOf`) className --> doFloat | c <- myMatchAnywhereFloatsC ]
   , [ fmap ( c `isInfixOf`) title     --> doFloat | c <- myMatchAnywhereFloatsT ]
   ]
   -- in a composeAll hook, you'd use: fmap ("VLC" `isInfixOf`) title --> doFloat
  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

Shift an app to a workspace and view it

The following will put new FocusMeNow windows on the "doc" workspace and also greedily view that workspace.

import Control.Monad (liftM2)

myManageHook = composeAll
    [ className = "FocusMeNow" --> viewShift "doc"
    -- more hooks
    ]
  where viewShift = doF . liftM2 (.) W.greedyView W.shift

Floating all new windows

To float all windows and manually tile them with mod-t, simply add <+> doFloat to your manage hooks. Warning: you don't want to combine this with hooks such as doF W.swapDown which put new windows below others. Also the floating layer isn't designed for extensive use, if possible limit doFloat to apps that really need it (see examples in previous section.)

-- skipped
main = xmonad defaultConfig
    { manageHook = myManageHooks <+> doFloat
      -- more changes
    }

Making windows unfloat

A related task is - how do I unfloat windows of a particular class or name? See the unfloat hook defined in the following example:

-- A manageHook to float everything by default and unfloat a few windows
myManageHook :: ManageHook
myManageHook = composeAll [ className =? "defcon.bin.x86" --> unfloat,
                            className =? "Darwinia" --> unfloat ]
               <+> doFloat <+> manageDocks
    where unfloat = ask >>= doF . W.sink

More info about ManageHooks

See the FAQ about using xprop to get the className, resource, title or other string properties of windows.

See also the documentation for ManageHook or the ManageHook section in Extending XMonad.


Gimp

The most popular gimp setups with xmonad are the default of floating all gimp windows, or using two nested Layout.IM modifiers to put the toolbox and dock panels to either side of some other layout like tabbed or (MyFavoriteTilingLayout ||| Full), plus usually floating tool dialogs with manageHooks. Some people combine the toolbox and dock into a single panel. See sample configs below.

Gimp windows as seen by xmonad

To choose how to work with the gimp in xmonad it's helpful to understand the different types of windows as xmonad sees them. If you just want some example setups, skip to the next section.

  • All gimp windows, i.e. those with WM_CLASS class of "Gimp". These windows float if you have manageHook defaultConfig anywhere in your manageHook. You probably don't want this if you plan to tile even the gimp tool setting dialogs. Otherwise keep the manageHook defaultConfig, and only unfloat the gimp-toolbox, gimp-image-window, and possibly gimp-dock.
  • Transient or fixed size windows, like file open, ok/cancel, fixed size tool dialogs, etc. XMonad floats these by default for all applications, even without using manageHook defaultConfig. If you really want to you can unfloat specific transients or fixed size windows -- see unfloat above.
  • Gimp toolbox or dock(s), matched with WM_WINDOW_ROLE(STRING) to use layoutHooks or manageHooks to place and manage them. Also, with drag and drop you can combine or separate their tabs and panes into one or more windows depending on how you want to use them.
On startup, a default gimp install creates (1) an empty image window, (2) the toolbox window (brushes, eraser, etc. and their options), and (3) a single dock (layers, paths, etc.) Customize them by dragging tabs to and from existing panels or onto the "create panel separator" on either type of window, (it will highlight when a dragged tab is over it). (It's just below the fg/bg color swatches on the toolbox window.)
  • Gimp tool windows, matched by suffix "tool" with WM_WINDOW_ROLE(STRING). (Or with darcs xmonad (0.9) use isDialog from ManageHelpers). These are the many tool settings popups like Levels, Threshold, Curves that normally don't have toolbox tabs. Most people probably want these floated, below is an example of how to do it if you're not starting from all gimp windows being floated.

Tiling most windows in gimp

A good way to work with the gimp in xmonad is to tile most windows with resizableTall, Full, tabbed (or several layout choices separated by ||| ) in the center of the screen, and....

Use withIM, nested withIM's, or XMonad.Layout.LayoutCombinators to tile your toolbox, combined toolbox and dock, or separate toolbox and dock(s) at the screen edges. As needed, float or unfloat windows by role, or by using Hooks.ManageHelpers.isDialog from darcs xmonad-contrib.

(See also Gimp windows section.)

To use nested withIM's to have the toolbox and dock treated separately, see Nathan Howell's blog post about XMonad and the Gimp.

Xmonadgimp.jpg

If the property matching doesn't seem to be working correctly, check class or role with xprop. See Using xprop to find an X property.

Here are some sample gimp related manageHook snippets.

  • For people using manageHook defaultConfig or class =? "Gimp":
import XMonad
import qualified XMonad.StackSet as W

myManageHook = composeAll
    [ (role =? "gimp-toolbox" <||> role =? "gimp-image-window") --> (ask >>= doF . W.sink)
    -- Note: hooks earlier in this list override later ones, so put the
    -- role hooks earlier than 'className =? "Gimp" ...' if you use both.

    -- other skipped manageHooks...
    ]
  where role = stringProperty "WM_WINDOW_ROLE"
  • For people not using manageHook defaultConfig or class =? "Gimp":
import XMonad
import Data.List -- for `isSuffixOf`
-- etc

myManageHook = composeAll
    [ -- other manageHooks
    ,  className =? "Gimp-2.6"  --> doShift "*" -- may be "Gimp" or "Gimp-2.4" instead
    , (className =? "Gimp-2.6" <&&> fmap ("tool" `isSuffixOf`) role) --> doFloat
    ]
  where role = stringProperty "WM_WINDOW_ROLE"

If you use a Tabbed or Full layout as your main layout and get unwanted focus shifts using withIM, instead try LayoutCombinators or ComboP, or one of the other layout combiners in xmonad-0.9. Also make sure you're using shiftMaster instead of swapMaster in your key and mouse bindings (swapMaster was old default before xmonad-0.9 and some people may still have it in xmonad.hs.)

Also, instead of picking the Full/Tabbed window with mod-tab, you can add the following to your mouse bindings, to be able to roll the mouse wheel over the gimp toolbox till the correct window is focused, which seems to prevent the shifting around:

import XMonad.Actions.FlexibleManipulate as Flex

      -- optional. but nicer than normal mouse move and size
    , ((mod4Mask, button3), Flex.mouseWindow Flex.discrete)
      -- scroll wheel window focusing
    , ((mod4Mask, button4), const $ windows W.swapDown)
    , ((mod4Mask, button5), const $ windows W.swapUp)

To use draggable width (DragPane combining Full and Tabbed) to put a single combined toolbox and dock to the right side of the screen:

-- etc
import XMonad.Hooks.ManageDocks
import XMonad.Layout.NoBorders (smartBorders)
import XMonad.Layout.DragPane
import XMonad.Layout.LayoutCombinators hiding ((|||))
import XMonad.Layout.Tabbed

myLayoutHook = avoidStruts . smartBorders $
    Tall 1 (3 / 100) (1 / 2) ||| tabbedLayout ||| Full ||| gimpLayout
  where
    tabbedLayout = tabbedBottomAlways shrinkText defaultTheme
    gimpLayout = tabbedLayout ****||* Full
AmphiGimpDragCombo.png

To use withIM and a specific workspace ("*" here) for the gimp:

-- etc
import XMonad.Layout.IM
import XMonad.Layout.PerWorkspace
import XMonad.Layout.ResizableTile -- Actions.WindowNavigation is nice too
import XMonad.Util.EZConfig -- or use another method of binding resizable keys

main = xmonad $ defaultConfig
    { modMask = mod4Mask
    -- make sure to use the same workspace Id in workspaces, doShift, and onWorkspace
    , workspaces = ["a","b","c","d","e","f","g","*","i"]
    -- etc
    , manageHook = myManageHook
    -- note: the default manageHook floats gimp, so do not <+> manageHook defaultConfig
    , layoutHook = myLayouts
    } `additionalKeysP` myKeys

myKeys =  -- resize both axes in resizableTall
    [ ("M-C-k", sendMessage $ MirrorExpand)
    , ("M-C-j", sendMessage $ MirrorShrink)
    , ("M-C-h", sendMessage $ Shrink)
    , ("M-C-l", sendMessage $ Expand)
    ]

myLayoutHook =
    onWorkspace "*" gimpLayout $
    layoutHook defaultConfig -- layouts to use on other workspaces
  where
    gimpLayout = withIM (11/64) (Role "gimp-toolbox") $ ResizableTall 2 (1/118) (11/20) [1] ||| Full

--  other variations
--where
--  mainLayouts =  layoutHook defaultConfig
--  gimpLayout = avoidStruts $ withIM (11/64) (Role "gimp-toolbox") $ mainLayouts
--  gimpLayout = Full ||| (avoidStruts $ withIM (11/64) (Role "gimp-toolbox") $ ResizableTall 2 (1/118) (11/20) [1])
--  etc

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 -- TODO: find method that only calls windows once

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.

Matching specific windows by setting the resource name or class

Sometimes, instead of matching a program's resource name or window class, it is useful to change the program's name and/or class to something easier to detect. This is most useful when starting programs inside terminal emulators, but can also be used to distinguish between, say, editor sessions.

Most X11 programs allow you to specify their resource name and/or class. Usually it's not possible to do so down to the level of individual windows, so you are likely to require WM_WINDOW_ROLE for that. Note that Java-based programs do not support any useful way to set either resource name or window class (bug 6528430).

Gnome and KDE

All Gnome and KDE programs support --name= and --class= options to specify the resource name and class for windows opened by those programs. Use the --help-all option to see these and other low-level options not normally visible.

Terminal emulator factories

gnome-terminal by default starts a single back-end "factory" and spawns terminal windows from it; all of these windows will share the same resource name and class. Use the --disable-factory option with --name= or --class= to ensure that the created window is not shared with unrelated terminals.

Other terminal emulators for Gnome and KDE are likely to behave similarly. (konsole does not, at least as of this writing.) Look for options to disable shared sessions or factories.

Xt (Xaw, Motif) applications

Programs such as xterm and the rxvt family of terminal emulators use the standard X11 Xt toolkit, and accept standard toolkit options ("man 7 X"; see the OPTIONS section). Specifically of interest here is the -name option. You cannot set the window class; this is fixed by the toolkit to a constant string supplied by the application developer (see XrmInitialize()).

urxvtc and urxvtd

This combination uses a single backend (urxvtd) which is asked to open terminal windows by urxvtc. These windows will share the same resource name. Do not use -name with urxvtc; instead, use urxvt directly. (See Terminal emulator factories above.)

Caveat

Programs using the standard X11 toolkit use the resource name and class to read configuration information from the app-defaults database and ~/.Xresources. Be careful when changing the resource name to insure that it is not being used to select specific configuration information, or copy that configuration information to the new resource name you are using.

Gtk+ and Qt

Gtk+ and Qt programs are encouraged but not required to support --name and --class as specified in Gnome and KDE above. Unfortunately, if a given program doesn't support the standard options, it probably doesn't provide any way to control its resource name or class.

Emacs

When Emacs has been built with support for X11, both -name and --name options should work regardless of the X11 toolkit used. If Emacs only supports running in a terminal, you will need to control the terminal used to run it instead (e.g. "xterm -n myeditor -e emacs somefile".)

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:

-- other imports
import qualified XMonad.StackSet as W
import XMonad.Util.EZConfig

main = xmonad $ defaultConfig {
          terminal = "urxvt"
        , modMask  = mod4Mask
        }
        `additionalKeysP`
        [ ("M-<Up>", windows W.swapUp)
        , ("M-x f", spawn "firefox")
        ]
        `additionalMouseBindings`
        [ ((mod4Mask, button3), (\w -> focus w >> Flex.mouseResizeWindow w))
        , ((mod4Mask, button4), (\_ -> windows W.focusUp ))
        , ((mod4Mask, button5), (\_ -> windows W.focusDown))
        ]

This is also described in [1]

Adding your own mouse bindings

Adding your own mouse bindings is explained in [2] Also see the EZConfig example above.

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

Binding to the numeric keypad

Bind to the non-numeric versions of these keys. They work regardless of NumLock status. To avoid conflicts with other apps you probably want to use them with modifiers. Here is an example of using them to navigate workspaces in the usual mod-N mod-shift-N way, but on the key pad:

-- other imports
import qualified XMonad.StackSet as W
import XMonad.Util.EZConfig

myWorkspaces = ["1","2","3","4","5","6","7","8","9","0"]

modm = mod4Mask -- win key for mod

myKeys = -- use with EZConfig.additionalKeys or edit to match your key binding method
    [
    -- more custom keybindings
    ]
    ++
    [((m .|. modm, k), windows $ f i)
        | (i, k) <- zip myWorkspaces numPadKeys
        , (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)]]
    ]

-- Non-numeric num pad keys, sorted by number 
numPadKeys = [ xK_KP_End,  xK_KP_Down,  xK_KP_Page_Down -- 1, 2, 3
             , xK_KP_Left, xK_KP_Begin, xK_KP_Right     -- 4, 5, 6
             , xK_KP_Home, xK_KP_Up,    xK_KP_Page_Up   -- 7, 8, 9
             , xK_KP_Insert] -- 0

Binding Workspaces on Function Keys

With default key binding method or EZConfig.additionalKeys

-- other imports
import qualified XMonad.StackSet as W
import XMonad.Util.EZConfig

-- 'zip' will only bind as many keys as there are workspaces so define some more
myWorkspaces = map show [1..12]

modm = mod4Mask -- win key for mod

main = xmonad $ defaultConfig
        { workspaces = myWorkspaces
        } `additionalKeys` myKeys

myKeys =
    [
    -- more custom keybindings
    ]
    ++
    [((m .|. modm, k), windows $ f i)
        | (i, k) <- zip myWorkspaces [xK_F1..xK_F12]
        , (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)]]
    ]

With EZConfig.additionalKeysP use something like the following myKeys instead:

myKeys =
    [
    -- other "M-C-z" style keys
    ]
    ++
    [ (otherModMasks ++ "M-" ++ key, action tag)
        | (tag, key)  <- zip myWorkspaces (map (\x -> "<F" ++ show x ++ ">") [1..12])
        , (otherModMasks, action) <- [ ("", windows . W.greedyView) -- or W.view
                                     , ("S-", windows . W.shift)]
    ]

For reference, the individual bindings assembled by the above list comprehensions look like this:

-- default or additionalKeys style:
    -- skipped
    , ((modm, xK_F12), windows $ W.greedyView "12")
    , ((shiftMask .|. modm, xK_F1), windows $ W.shift "1")
    -- etc

-- additionalKeysP style:
    -- skipped
    , ("M-<F12>", windows $ W.greedyView "12")
    , ("M-S-<F1>", windows $ W.shift "1")
    -- etc

Navigating and Displaying Workspaces

Using Next Previous Recent Workspaces rather than mod-n

The Actions.Plane, Actions.CycleWS, and Actions.CycleRecentWS extensions allow many ways to navigate workspaces, or shift windows to other workspaces.

Plane is easier to set up, especially if you use Gnome. CycleWS allows binding to nearly any behavior you'd ever want. Actions.CycleRecentWS allows swapping with previous or next most recently viewed workspace similar to how many window managers cycle windows with alt tab.

In darcs xmonad-contrib (will release as 0.9): Layout.IndependentScreens simulates dwm style workspaces per screen. For spatial navigation more general than Plane, i.e. four 3x3 grids of workspaces, see Actions.WorkspaceCursors.

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. (Note that in xmonad newer than 0.8.* the scratchpad workspace has been renamed to "NSP".)

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)

    -- toggle to the workspace displayed previously, except scratchpad**
    , ((modKey, xK_slash myToggle)
    ]

  -- 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
        -- | toggle any workspace but scratchpad
        myToggle = windows $ W.view =<< W.tag . head . filter 
                ((\x -> x /= "NSP" && x /= "SP") . W.tag) . W.hidden


  -- *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.

**This is another way to toggle workspaces except scratchpad.

--
import Control.Monad

    -- toggle to the workspace displayed previously, except scratchpad
    , ((modKey, xK_slash toggleSkip ["NSP"])

        -- | toggle any workspace but scratchpad
        toggleSkip :: [WorkspaceId] -> X ()
        toggleSkip skips = do
            hs <- gets (flip skipTags skips . W.hidden . windowset)
            unless (null hs) (windows . W.view . W.tag $ head hs)
--

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
  --

Doing things on another workspace while focus stays on current

With darcs xmonad (will release as 0.9) -- see also Actions.OnScreen and onScr below.

You can use something like the following in your keybindings for a two monitor setup (or two screens via LayoutScreens.)

import qualified XMonad.StackSet as W

      -- c here is your XConfig l, aka defaultConfig { ....
    , ((modMask c, xK_v), withOtherOf2 W.view)  -- focus other visible screen
    , ((modMask c, xK_g), withOtherOf2 W.greedyView)  -- swap workspaces on screens
    , ((modMask c, xK_f), withOtherOf2 W.shift) -- move current window to other screen
    , ((modMask c, xK_u), onOtherOf2 W.focusUp) -- focus up on other screen
    ]

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

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

More generally

onWorkspace :: WorkspaceId -> (WindowSet -> WindowSet)
            -> (WindowSet -> WindowSet)
onWorkspace wsid f w = W.view (W.currentTag w) . f . W.view wsid $ w

-- silly usage example: focus master on workspace "3"
    , ((modMask c, xK_F12), windows $ onWorkspace "3" W.focusMaster)

Quick and dirty OnScreen helper

With darcs xmonad (will release as 0.9) see also Actions.OnScreen

-- For example, to focus a specific workspace on the second screen
-- use something like this in startupHook or a key binding:
-- If the requested screen doesn't exist, the action is done on the
-- current screen instead.

import qualified XMonad.StackSet as W
     -- skipped
     , startupHook = onScr 1 W.greedyView "web" 
     -- skipped

onScr :: ScreenId -> (WorkspaceId -> WindowSet -> WindowSet) -> WorkspaceId -> X ()
onScr n f i = screenWorkspace n >>= \sn -> windows (f i . maybe id W.view sn)

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

See XMonad.Util.ExtensibleState for persistent custom state. (>0.9)

It's nearly always better to use ExtensibleState, but you may still find some use for IORef's:

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

Multi head with VMs VNC or other non standard X

To manually split your screen if your X server doesn't deal with xinerama correctly, see the LayoutScreens extension or Fake Xinerama.

Also, if you're not sure if xmonad was compiled with xinerama support, see the xinerama sections in the XMonad FAQ to check and remedy.