Difference between revisions of "Xmonad/Frequently asked questions"

From HaskellWiki
Jump to navigation Jump to search
(mention _JAVA_AWT_WM_NONREPARENTING environment variable)
Line 922: Line 922:
 
windows should be, as the Java gui code gets confused.
 
windows should be, as the Java gui code gets confused.
   
  +
If you are using openjdk6 >= 1.6.1, the cleanest way to work around the hardcoded list is to warn the vm that xmonad is non-reparenting by exporting the appropriate environment variable:
Using JDK 7 seems to work well, see below.
 
   
  +
_JAVA_AWT_WM_NONREPARENTING=1
The cleanest way to work around the hardcoded list is to lie to Java about what
 
  +
window manager you are using, by having the
 
 
Using JDK 7 seems to work well, too, see below.
[http://xmonad.org/xmonad-docs/xmonad-contrib/XMonad-Hooks-SetWMName.html SetWMName] extension convince Java that xmonad is '''"LG3D"'''. Normally you would use this in
 
  +
 
Otherwise, you can lie to Java about what window manager you are using, by having the [http://xmonad.org/xmonad-docs/xmonad-contrib/XMonad-Hooks-SetWMName.html SetWMName] extension convince Java that xmonad is '''"LG3D"'''. Normally you would use this in
 
startup hook, like this:
 
startup hook, like this:
   

Revision as of 02:54, 31 October 2009

Xmonad-logo-small.png

XMonad


xmonad: frequently asked questions

For configuration tricks, and using xmonad.hs, see Xmonad/General_xmonad.hs_config_tips.

For more documentation, see:

When I start xmonad, nothing happens.

Don't panic, this is expected behavior. XMonad is a minimal window manager, meaning it doesn't set a background, start a status bar, display a splash screen or play a soothing sound effect when it starts up. Once xmonad has started, the only thing it does is listen for your first command. Try pressing mod-shift-enter (that is Alt, Shift, and Enter pressed at the same time) to bring up an xterm. Once the xterm appears, use it to read xmonad's man page or point a web browser at http://xmonad.org/tour.html. If no xterm appears, see if any other advice on this page applies.

Installation

What build dependencies does xmonad have?

The hackage page for xmonad lists all dependencies, including:

  • Standard Haskell libraries (you might already have these installed):
  • Haskell X11 bindings:
  • C libraries:
    • libX
    • libXext
    • libXinerama

You likely have these already if you've built any programs for X.

xmonad is also availble pre-packaged for many distributions:

Using your distro package is almost always preferred.

Can I install without root permission?

Yes, the Haskell libraries that xmonad depends on can all by installed in the user package database. Simply append --user to the install phase:

   $ runhaskell Setup.hs install --user

The library will be registered in your ~/.ghc/ database.

How can I use xmonad with a display manager? (xdm, kdm, gdm)

The simplest way is to create or modify your ~/.xsession file to run xmonad. If you don't already have a .xsession, the minimal example looks like:

   xmonad

This requires that the ghc and the xmonad executable (or a symlink to them) are in a directory in the display manager $PATH environment. Alternatively, you can use the full path to xmonad and set ghc's path systemwide. If you do this, you'll also have to change the mod-q binding to use /path/to/xmonad and restart X to have xmonad use the new mod-q (first time only) since the mod-q binding calls xmonad to recompile itself. (See mod-q doesn't work section below.)

People using 'startx' can use these example xinitrc and run-xmonad scripts.

If you are using xdm, you're done. Login and enjoy xmonad.

If you're using kdm or gdm (KDE and GNOME's display mangers, respectively), you're almost done. When logging in, select the entry that says "xsession" or "default session" from the menu in order to use your ~/.xsession to start xmonad.

Alternatively, if you want a menu entry specifically for xmonad, create a file named "xmonad.desktop" in your /usr/share/xsessions (location varies by distribution) directory. For example:

   [Desktop Entry]
   Encoding=UTF-8
   Name=xmonad
   Comment=This session starts xmonad
   Exec=/usr/local/bin/xmonad
   Type=Application

Replace the "Exec=..." line with the actual path to your xmonad executable, and you should be able to login by selecting "xmonad" as a session from the menu in gdm/kdm.

For instructions on using gdm to launch a full GNOME session with xmonad as the window manager read this.

Compiling xmonad on PowerPC and compiler is not interactive

If you have ghc installed and are trying to compile xmonad and your compiler complains about not being interactive, never fear. To compile Setup.hs simply type:

   ghc --make Setup.hs -o Setup
   

Now you can:

   ./Setup configure
   ./Setup build
   sudo ./Setup install
   

If during the build process ghc complains about the "impossible happening", and mentions that you should change something to "-fvia-C", just edit the *.cabal file replacing the line that sets the arguments for ghc, changing "-fasm" to "-fvia-C".

How do I uninstall xmonad?

If you have installed xmonad using your package manager, then just use it. The following applies if you have built xmonad from source code (either darcs or stable release). Let's assume you've installed xmonad to

the $PREFIX (that is, gave --prefix=$PREFIX argument to Setup.lhs configure). If unsure, try your

$HOME and /usr/local as $PREFIX.

 rm  -f $PREFIX/bin/xmonad
 rm -rf $HOME/.xmonad
 rm -rf $PREFIX/lib/xmonad-$VERSION
 # If you have installed XMonadContrib:
 rm -rf $PREFIX/lib/xmonad-contrib-$VERSION

If you have installed xmonad 0.5 or newer, also run

 ghc-pkg unregister xmonad
 # If you have installed XMonadContrib:
 ghc-pkg unregister xmonad-contrib

Do not forget to purge that evil source code!

not found errors or changes to xmonad.hs won't take effect

Ensure that ghc, and the xmonad executable are both in the environment PATH from which you start X. Alternatively symlink them to locations already in the PATH. ghc-pkg list should show ghc, xmonad, X11, etc. without brackets, e.g. {xmonad} is bad. ghc-pkg check will tell you if you have inconsistent dependencies or other registration problems.

The mod-q action calls the xmonad binary to recompile itself, so if your display manager is starting it with /path/to/xmonad you'll also have to edit your xmonad.hs mod-q binding to use the full path and restart X (or in newer versions use 'xmonad --restart') to restart xmonad with the new mod-q full path binding.

If you recently changed ghc versions see #Upgraded GHC and now xmonad xmonad-contrib etc are not found

Configuring xmonad requires GHC, which is 200MB!

Yes. You can use xmonad-light, which allows some of the basic configurations, but if you really want to get the best xmonad experience, you need GHC.

Configuration

How do I configure xmonad?

By creating and editing the ~/.xmonad/xmonad.hs file, a Haskell source file.

You can use any Haskell you want in this module. The xmonad-contrib package contains many extension modules to make customizing xmonad easier. To have your changes take effect, save the xmonad.hs and either restart (mod-q) or exit X and log back in.

Example configurations are available on the wiki.

For extensive information on configuring, see the links at the top of this page, and the configuration tips page.

Rebinding the mod key (Alt conflicts with other apps; I want the ___ key!)

xmonad uses 'alt', actually mod1, as the default modifier. You may bind to other mod keys by editing your xmonad.hs modMask value, or by using xmodmap to rebind a key to mod1. The apple command key can be rebound to mod1 in this way. Use xmodmap to find what key your mod1 is bound to, as well.

You can rebind the Caps Lock key, to mod, if you wish. See this mailing list item.

If your new key binding doesn't appear to work, double check it doesn't clash with an existing binding.

An example, binding to the mod4 (often 'Win') key:

import XMonad

main = xmonad defaultConfig
         { modMask = mod4Mask
         , terminal = "urxvt"
         }

Multi head and workspaces (desktops)

See also xinerama troubles if your multi-head setup doesn't behave as described below.

XMonad multi-head workspace handling may not make sense at first. First, if you haven't yet read it, go through the workspace section of the Guided Tour. XMonad does not by default link all your monitor screens into one workspace like Gnome and friends, neither does it by default use a model like dwm or awesome window managers'. To limit this to a set of workspaces for each monitor dwm/awesome style, see (darcs only) Layout.IndependentScreens

In xmonad, each monitor can display any workspace, although you can't have the same workspace on multiple monitors. (Use clone or --same-as, etc. to have X do it.)

visible workspaces swap The other thing that may seem strange is that by default, when you have multiple workspaces visible and mod-n to a different visible workspace, your current one swaps with the other one. We'll see how to change that below, if you don't like the swapping -- simply change 'greedyView' to 'view' in your workspace key bindings. To illustrate with two monitors, using the convention "[1*] [3 ]" to mean workspaces 1 and 3 are visible with left monitor the currently active one:

-- 'greedyView' (default) workspace switching (easier to swap visible workspaces)

-- Typical keystrokes are mod-{w,e,r} to a screen, then mod-N a workspace

   [1*] [3 ] -- mod-3 --> [3*] [1 ] -- mod-e, mod-4 --> [3 ] [4*]
   [3 ] [4*] -- mod-w, mod-4 --> [4*] [3 ]

my focus moves instead By replacing the 'greedyView' function with 'view' in the workspace switching bindings (copy from the Template xmonad.hs for your xmonad version) you can have your focus shift to the monitor displaying the given workspace, instead of having that workspace 'brought to you.' For example:

-- 'view' workspace switching

-- (easier to focus another visible workspace, harder to swap)

   [1*] [3 ] -- mod-3 --> [1 ] [3*] -- mod-4 --> [1 ] [4*]
   [1 ] [4*] -- mod-w --> [1*] [4 ] -- mod-4 --> [1 ] [4*]

Replacing greedyView with view

Here is an example of changing greedyView to view using XMonad.Util.EZConfig's additionalKeysP:

(See contrib docs for EZConfig for more details)

import XMonad
-- skipped
import qualified XMonad.StackSet as W
import XMonad.Util.EZConfig

main = do
    xmonad $ defaultConfig {
        workspaces = myWorkspaces
        -- skipped
        } `additionalKeysP` myKeys

myWorkspaces = ["one","two","three","foo","bar","baz","lambda","no","more"]

myKeys =
    [
    -- other additional keys
    ]
    ++ -- important since ff. is a list itself, can't just put inside above list
    [ (otherModMasks ++ "M-" ++ [key], action tag)
         | (tag, key)  <- zip myWorkspaces "123456789"
         , (otherModMasks, action) <- [ ("", windows . W.view) -- was W.greedyView
                                      , ("S-", windows . W.shift)]
    ]

For use with additionalKeys or default binding style:

-- as above
myKeys =
    [
    -- other additional keys
    ]
    ++
    [((m .|. mod4Mask, k), windows $ f i)
         | (i, k) <- zip myWorkspaces [xK_1 .. xK_9]
         , (f, m) <- [(W.view, 0), (W.shift, shiftMask)]]

Screens are in wrong order

With xmonad-contrib newer than 0.8.*, (darcs version), see also XMonad.Actions.PhysicalScreens

Sometimes drivers don't do what you want, and your screens left to right are something weird like 1 0 2, so your mod-{w,e,r} bindings are messed up. Your driver may provide a utility to set screen order, but if not, or if you just don't want to mess with it, here's how to rebind the screen switching bindings:

Using XMonad.Util.EZConfig's additionalKeysP:

import XMonad
-- skipped
import qualified XMonad.StackSet as W
import XMonad.Util.EZConfig

main = do
    xmonad $ defaultConfig {
        -- skipped
        } `additionalKeysP` myKeys

myKeys =
    [
    -- other additional keys
    ]
    ++
    [ (mask ++ "M-" ++ [key], screenWorkspace scr >>= flip whenJust (windows . action))
         | (key, scr)  <- zip "wer" [1,0,2] -- was [0..] *** change to match your screen order ***
         , (action, mask) <- [ (W.view, "") , (W.shift, "S-")]
    ]

Using default key binding method or XMonad.Util.EZConfig's additionalKeys:

-- as above
myKeys =
    [
    -- other additional keys
    ]
    ++
    [((m .|. modm, key), screenWorkspace sc >>= flip whenJust (windows . f))
        | (key, sc) <- zip [xK_w, xK_e, xK_r] [1,0,2] -- was [0..] *** change to match your screen order ***
        , (f, m) <- [(W.view, 0), (W.shift, shiftMask)]]

I don't want the focus to follow the mouse

Easy. There is a setting focusFollowsMouse in the xmonad.hs file; set it to False and restart with mod+q.

How do I configure pointer-follows-focus?

If you are using > xmonad-0.7, you can use the already defined XMonad.Actions.UpdatePointer:

myLogHook = dynamicLogWithPP .... >> updatePointer

For xmonad-0.7, in your config, import XMonad.Actions.Warp from Xmonad contrib and

add this function:

pointerFollowsFocus :: Rational -> Rational -> X ()
pointerFollowsFocus h v = do
    dpy <- asks display
    root <- asks theRoot
    withFocused $ \w -> do
        wa <- io $ getWindowAttributes dpy w
        (sameRoot,_,w',_,_,_,_,_) <- io $ queryPointer dpy root
        if (sameRoot && w == w') then
            return ()
           else
            io $ warpPointer dpy none w 0 0 0 0
                (fraction h (wa_width wa)) (fraction v (wa_height wa))
          where fraction x y = floor (x * fromIntegral y)

Then set the logHook in your config to “pointerFollowsFocus x y”. If you already have a logHook, append “

>> pointerFollowsFocus x y” to it. For example:

myLogHook = dynamicLogWithPP defaultPP { ppCurrent = xmobarColor "#60ff45" ""
                                       , ppVisible = xmobarColor "#fffff0" "" } >> pointerFollowsFocus 1 1

Does xmonad support a statusbar?

Yes. The Hooks.DynamicLog and Hooks.ManageDocks modules are your friends for this purpose.

Arbitrary external programs may be used as a statusbar. See for example dzen or xmobar, an extensible status bar.

xmonad lets you use any application as a 'statusbar', as long as it is visible in a given 'gap' on the screen, and has the override-redirect property set to true. Many status bar/dock programs already set this property, for example, dzen. To set other applications, you can sometimes use normal X resources. For example, to use xclock, launch it with

   xclock -digital -xrm '*overrideRedirect: True' -geometry 1024x30+0+0

If, like xclock, your app doesn't set wm strut properties, so that ManageDocks and avoidStruts automatically leaves a gap, you can do it manually. Import the Layout.Gaps module and, set a gap of, e.g. (30,0,0,0), in xmonad.hs. A similar trick can be done for xsystray.

Also in xmonad-darcs (will release as xmonad-0.9) see the Layout.Monitor module.

You can see screenshots of statusbars on the screenshots page.

You can also use Gnome or KDE trays and menus with xmonad. The Hooks.EwmhDesktops, Config.Desktop, Config.Gnome, Config.Kde, etc. modules make desktop environment status bars more useful with xmonad.

To display xmonad logHook output in gnome-panel, see xmonad log applet.

dzen status bars

xmonad's XMonadContrib library comes with a really easy function for getting a status bar working with dzen. To use it, simply have a ~/.xmonad/xmonad.hs containing:

    import XMonad
    import XMonad.Hooks.DynamicLog

	-- darcs main:
    main = xmonad =<< dzen defaultConfig
	-- 0.8.1 main:
	main = dzen xmonad

which will launch xmonad with dzen2 if found, set up with nice colours and workspace information. See Don's config example for more information or DynamicLog dzen's documentation.

There is an excellent command-line option and in-text command reference for the SVN version of dzen2 here

gkrellm or other monitors that aren't bars

Gkrellm does not behave like a dock by default. However, there is an option in .gkrellm2/user_config which says dock = 0. If you set it to 1 xmonad will recognize gkrellm as a dock.

Unfortunately gkrellm usually won't hide under other windows regardless of any combination of above and below options in said config file. Opening and closing the gkrellm config usually resolves this (right click the top of gkrellm and select Configure.. from the menu).

In xmonad-darcs (will release as xmonad-0.9) the Layout.Monitor module may be helpful.

Make space for a panel dock or tray

ManageDocks makes it possible for Xmonad to work with panels in the way they expect, automatically leaving the appropriate amount of room for them at the edges of the screen. ManageDocks has been enabled in the example configuration above. By itself, configuration looks like this:

import XMonad
import XMonad.Hooks.ManageDocks
main = xmonad defaultConfig
              { manageHook = manageDocks <+> manageHook defaultConfig
              , layoutHook = avoidStruts  $  layoutHook defaultConfig
              }

Make new windows appear 'below' rather than 'above' the current window

TODO: clean this up and make it easy. Add copyable helpers to darcs ManageHelpers if needed.

Force new tiled windows down

See Hooks.ManageHelpers composeOne to specify hooks that only fire if earlier ones have not matched. You can use this to add swapDown only to the apps that haven't earlier been floated or identified as transient or dialog windows. TODO: examples.

Force all new windows down

(Not recommended) Add doF W.swapDown to your manageHook. For instance, a minimal config would look like this:

import XMonad
import qualified XMonad.StackSet as W
main = xmonad defaultConfig
              { manageHook = manageHook defaultConfig <+> doF W.swapDown
                -- 
                -- To prevent unwanted swaps when using this hook with
                -- other doShift hooks, make sure to put doF W.swapDown
                -- furthest to the right, or last in a composeAll hook list
              }

Warning: doF W.swapDown without restrictions will result in new floating windows popping up behind floating windows, and undesirable focus changes when starting and quickly destroying a window.

Better would be to only swapDown or promote to master specific windows. TODO: examples of matching and promoting or demoting specific windows.

Avoid the master window, but otherwise manage new windows normally

Note that this is not a good solution for people who use floating windows, since many operations on floats put the floating window into the master position. Some transient windows will be swappedDown to appear below the floating parent unless the user keeps a tiled window in master and floating windows lower in the stack at all times. The first composeOne solution or only using it on specific windows is better if you use floating windows very often.

-- <snip> 
import qualified XMonad.StackSet as W
import XMonad.Hooks.ManageHelpers
-- <snip>

myManageHook = fmap not isDialog --> doF avoidMaster

-- or if you have other stuff in the managehook, more like
-- myManageHook = (otherStuff) <+> (fmap not isDialog --> doF avoidMaster)

avoidMaster :: W.StackSet i l a s sd -> W.StackSet i l a s sd
avoidMaster = W.modify' $ \c -> case c of
     W.Stack t [] (r:rs) ->  W.Stack t [r] rs
     otherwise           -> c

Prevent new windows from stealing focus

Use a doF W.focusDown manageHook on selected windows, or even on all windows, similar to the swapDown examples above.

Floating a window or sending it to a specific workspace by default

See General xmonad.hs config tips regarding manageHook, and the section here about 'xprop' for this.

Startup programs

You may launch programs at startup in the usual X manner: by adding them to your .xsession or .Xinitrc. For example, the following .xsession file launches xpmroot to set the background image, xmodmap to rebind caps lock to ctrl. It then launches a status bar program with dzen, before finally launching xmonad:

   # .xsession
   xpmroot ~/.bg/407511721_eb8559457c_o.xpm &
   xrdb -merge .Xresources
   xmodmap -e "remove Lock = Caps_Lock"
   xmodmap -e "keysym Caps_Lock = Control_L"
   xmodmap -e "add Control = Control_L"
   status | dzen2 -ta r -fg '#a8a3f7' \
                        -bg '#3f3c6d' \
                        -fn '-*-terminus-medium-r-normal--16-*' \
                        -e "button1=exec:xterm" & 
   urxvt &
   $HOME/bin/xmonad

You may also launch applications from your xmonad.hs, using startupHook, however this runs each time xmonad is restarted with mod-q. Also in > xmonad-0.8 see spawnPid, mkSpawner, spawnOn.

Use manageHook to arrange your programs on different workspaces by matching various window properties such as className, appName (resource), title, or role.

Using floating windows

Use the regular swap or focus up and down to navigate them, and regular mod-enter to raise a window to the front. For a mod-enter binding, the darcs shiftMaster works better than swapMaster if you use multiple floats over tiled windows. See also this swapDown manage hook warning above. If you use that manageHook on all windows you will create new floats behind existing ones. If you use lots of floats for some reason see SimpleFloat layout, FloatKeys, Hooks.Place in xmonad-contrib.

Setting the X cursor

By default xmonad doesn't set a particular X cursor, which usually means the default X cursor will be used by the system. To set your own custom cursor, use the xsetroot program, as follows, from your startup file, i.e. .xinitrc, .xsession, display manager startup or .Desktop files:

   # For example, a nice left-pointing arrow head cursor
   xsetroot -cursor_name left_ptr

If you have development headers for X11, other cursors can be found in /usr/include/X11/cursorfont.h

Note that some display managers, such as "slim", don't unset the changes they make to the cursor when the window manager starts. This can be worked around by setting the cursor, as above.

Removing the borders around mplayer

You can also use the fullscreen layout, with the NoBorders smartBorders layout modifier, which automatically takes care of most cases.

To add 'smartBorders' to the default tiling modes:

    import XMonad
    import XMonad.Layout.NoBorders

    main = xmonad $ 
            defaultConfig
                { layoutHook = smartBorders $ layoutHook defaultConfig
                -- other fields like terminal, modMask, etc.
                }


You can also remove borders with a key binding using Actions.NoBorders extension. There's drawback: you need manually remove border any time you launch mplayer.

Although this action should be able to be automated, unfortunately you cannot currently use manageHook for this purpose. That's because borders are drawn after runManageHook is executed (see Operations.hs for details).

Alternatively you can manually move the mplayer window 1 pixel to the left and one pixel up by importing XMonad.Actions.FloatKeys and adding a keybinding similar to ((modm, xK_b), withFocused (keysMoveWindow (-1,-1)). (I have not tested yet if this can be used in combination with the manageHook.)

I need to find the class title or some other X property of my program

If you are using something like XMonad.Actions.WindowGo, or a hook, or some other feature like that where XMonad needs to know detailed information about a window, you can generally find what you need by splitting your screen between the window and a terminal; in the terminal, run xprop | grep CLASS or the like, and then click on the window. xprop will then print out quite a bit of useful information about the window.

  • resource (also known as appName) is the first element in WM_CLASS(STRING)
  • className is the second element in WM_CLASS(STRING)
  • title is WM_NAME(STRING)

For example, in WM_CLASS(STRING) = "emacs", "Emacs" -- "emacs" is resource (appName), "Emacs" is className.

(Applications may change the title after window creation, before xprop sees it. If possible, use resource or class in such cases.) stringProperty "WM_WINDOW_ROLE" can also be useful.

Sample output might look like:

_MOTIF_DRAG_RECEIVER_INFO(_MOTIF_DRAG_RECEIVER_INFO) = 0x6c, 0x0, 0x5, 0x0, 0x0, 0x0, 0x0, 0x0, 0x0, 0x0, 0x0, 0x0, 0x0, 0x0, 0x0, 0x0
XdndAware(ATOM) = BITMAP
WM_STATE(WM_STATE):
                window state: Normal
                icon window: 0x0
WM_HINTS(WM_HINTS):
                Client accepts input or input focus: True
                Initial state is Normal State.
                window id # of group leader: 0xf600001
_NET_WM_SYNC_REQUEST_COUNTER(CARDINAL) = 257949716
_NET_WM_WINDOW_TYPE(ATOM) = _NET_WM_WINDOW_TYPE_NORMAL
_NET_WM_USER_TIME_WINDOW(WINDOW): window id # 0xf600013
WM_CLIENT_LEADER(WINDOW): window id # 0xf600001
_NET_WM_PID(CARDINAL) = 476661
WM_LOCALE_NAME(STRING) = "en_US.utf8"
WM_CLIENT_MACHINE(STRING) = "localhost"
WM_NORMAL_HINTS(WM_SIZE_HINTS):
                program specified minimum size: 32 by 34
                program specified resize increment: 8 by 17
                program specified base size: 16 by 0
                window gravity: NorthWest
WM_PROTOCOLS(ATOM): protocols  WM_DELETE_WINDOW, WM_TAKE_FOCUS, _NET_WM_PING, _NET_WM_SYNC_REQUEST
WM_CLASS(STRING) = "emacs", "Emacs"
WM_ICON_NAME(STRING) = "emacs@craft"
_NET_WM_ICON_NAME(UTF8_STRING) = 0x45, 0x4d, 0x41, 0x43, 0x53
WM_NAME(STRING) = "EMACS"
_NET_WM_NAME(UTF8_STRING) = 0x45, 0x4d, 0x41, 0x43, 0x53

Note: the last several lines contain useful information like the CLASS and hinting information.

What about other properties, such as WM_WINDOW_ROLE?

Use stringProperty to extract string information, for example:

stringProperty "WM_WINDOW_ROLE" =? "presentationWidget" --> doFloat

For non-string properties, try XMonad.Hooks.ManageHelpers.

Consult the XMonad.ManageHook documentation for more information.

What is the xK_ value for this key?

Pressing the key of interest while focusing a xev window gives useful information. To limit xev's output use something like:

xev | sed -ne '/^KeyPress/,/^$/p'

A complete list can be found at XMonad key symbols.

How can I send a key sequence to a window?

This can be useful when some application uses a hotkey that you want to use in XMonad, yet be able to send the application window the hotkey when needed.

A solution is to use xdotool, which can (among other nifty things), send a fake keypress to the currently focused window. So, for instance, you can use the following keybinding to send Alt+L to the focused window by pressing Ctrl+Alt+L:

   , ((mod1Mask|controlMask, xK_l), spawn "xdotool key alt+l")

xdotool can also paste a line of ASCII text into the focused window. For instance, the following keybinding will insert the email address email@example.org each time the key Ctrl+Alt+e is pressed:

   , ((mod1Mask|controlMask, xK_e), spawn "xdotool text 'email@example.org'")

The XMonad.Util.Paste module (currently in the darcs repository only, will be in 0.9) defines functions to to the same with pure Haskell code.


I don't use a statusbar, but I'd like to have layout displayed for some time when it changes

Let's assume you have import qualified XMonad.StackSet as W in xmonad.hs.

Add the following declaration somewhere in the toplevel:

curLayout :: X String
curLayout = gets windowset >>= return . description . W.layout . W.workspace . W.current

Then add the keybinding:

    , ((mod1Mask, xK_a     ), sendMessage NextLayout >> (curLayout >>= \d->spawn $"xmessage "++d))

You might want to change xmessage to the more friendly program, such as osd_cat, qt-dialog or dzen2.

Another option is to use Layout.ShowWName which has some user configurable options such as font, color and fade timings.

More flexible way is to use dynamicLogString from XMonad.Hooks.DynamicLog (was added after 0.6 release), which can also display current workspace, window name, layout, and even arbitrary [X (Maybe String)], and format them nicely, printing them to xmonad's stdout.

How can I make xmonad use UTF8?

TODO: is this still accurate? Doesn't xmonad-0.8 and greater always use UTF8 with no extra imports or configuration changes?

Due to extensions like DynamicLog, xmonad is capable of text outputting which is not by default but can be encoded in UTF8. Therefore, if you want to output non-ASCII characters, you can take advantage of the System.IO.UTF8 module.

For example using DynamicLog you can define its output ppOutput like his:

import qualified System.IO.UTF8
-- lots of other stuff
ppLog = defaultPP
  { ppOutput = \s -> do
      h <- openFile "/home/$USER/.xmonad/xmonad.log" WriteMode
      System.IO.UTF8.hPutStrLn h s
      hClose h
  }

As it may not be ideal to reopen the file before every writing, you can just place the code somewhere else. See ray's config in xmonad's config archive.

How do I use compositing with xmonad?

Xmonad has the ability to use some compositing features yet still be actually useable ;-). For example, some really nice transparency can be used with a composite aware app like urxvt and xcompmgr.

First enable compositing in your X server configuration by including the following in your xorg.conf

Section "Extensions"
     Option "Composite" "enable"
EndSection

restart the X server and confirm it's working with xdpyinfo | grep Composite. If it returns Composite, then good...

Include this in ~/.Xdefaults

URxvt.depth: 32
URxvt*background: rgba:0000/0000/0000/cccc

this specifies that urxvt uses 32 bit colors and uses a transparent black background. The four c's specify the amount of alpha with ffff being full black and 0000 being fully transparent. You can also use the fading and blurRadius resources to give some nice effects in the transparency. see man urxvt.

finally you need to fire up xcompgr so that this will all actually work. probably you'll want to include it in your ~/.xinitrc or ~/.xsession file:

xcompmgr -c &

the -c option provides a soft shadow around your windows. There are many options, see man xcompmgr.

For an example with screenshots see andrewsw's config in the config archive.

On newer versions of XMonad, see also XMonad.Hooks.FadeInactive documentation.

Troubleshooting

Multi head or xinerama troubles

xmonad does not detect my multi-head setup

To diagnose the problem, execute the following on the command line:

   ghc -e Graphics.X11.Xinerama.compiledWithXinerama

If the output is True, skip to the getScreenInfo test below. If the output is False, your Haskell X11 library was not built against Xinerama. This is true of old Debian and Ubuntu packages, and may also occur if you built from source.

First, be sure that the Xinerama development headers are installed (libxinerama-dev in Debian and Ubuntu).

Next, check the configure output for the Haskell X11 library for the following lines:

   checking X11/extensions/Xinerama.h usability... yes
   checking X11/extensions/Xinerama.h presence... yes
   checking for X11/extensions/Xinerama.h... yes

If any of these lines end in "no", the Xinerama headers are not installed. If the lines end in "yes", execute:

   runghc Setup clean
   runghc Setup configure --user --prefix=$HOME
   runghc Setup build
   runghc Setup install

In the X11, xmonad and xmonad-contrib source directories. Try the compiledWithXinerama diagnostic again, this time it should return True. As always, execute "xmonad --recompile" when reinstalling any part of xmonad.

If compiledWithXinerama is True and multi-head still doesn't work, execute "xmonad --recompile" and press mod-q. If the problem persists, execute this command:

   ghc -e "Graphics.X11.openDisplay [] >>= Graphics.X11.Xinerama.getScreenInfo"

Here is a sample output from a system with two 1280 by 1024 monitors, oriented side by side:

   [Rectangle {rect_x = 0, rect_y = 0, rect_width = 1280, rect_height = 1024}, Rectangle {rect_x = 1280, rect_y = 0, rect_width = 1280, rect_height = 1024}]

Check to see whether there is a Rectangle corresponding to each of your screens. If there is not, and the compiledWithXinerama diagnostic returns True, there may be a problem with your X server configuration.

Missing X11 headers

Your build will fail if you've not installed the X11 C library headers at some point. ./configure for the Haskell X11 library will fail. To install the X11 C libs:

  • debian
   apt-get install libx11-dev

X11 fails to find libX11 or libXinerama

Cabal has difficulty locating library directories on some platforms (such as the Mac or RHEL4). First, locate the directory that contains libX11.so (libX11.dylib on Mac OS X). Add the following line to the .cabal file for the package:

   extra-lib-dirs: /your/path/here/
   

For example, on a 64 bit machine you might need to add:

   extra-lib-dirs: /usr/X11R6/lib/lib64
   

You can also add the paths to your .buildinfo file, or set the LD_LIBRARY_PATH environment variable.

Something is weird with multi head windows or workspaces (desktops)

See Configuration: Multi head and workspaces

mod-q doesn't work

Upgraded GHC and now xmonad xmonad-contrib etc are not found

When you change ghc versions you need to rebuild or reinstall haskell libraries to make sure they are compatible and registered with the new ghc. Often your distro packagers will try to make this as automatic as possible, by making it just happen. Or at least they will make it easier, e.g. gentoo's ghc-updater and haskell-updater. (This isn't just a Haskell/ghc issue; it's true for other languages, too: c.f. python-updater scripts, distro policies regarding gcc and glibc changes.)

Changes to the config file ignored or 'xmonad not found' when starting X

Both ghc and xmonad must be in your display manager init's $PATH when starting X and xmonad for reconfiguration by mod-q. Make sure the environment from which you start xmonad has the appropriate settings.

When changing the xmonad.hs and restarting with mod-q, xmonad will attempt to exec the xmonad binary. This means it must be in your $PATH environment variable, or the exec will fail silently and the old xmonad instance keeps running.

With xmonad 0.5 and later, mod-q will also call ghc on your ~/.xmonad/xmonad.hs file, and will continue with defaults if ghc is not found.

Additionally, if you change and reinstall the haskell-X11 or XMonadContrib library, changes to that package will not be noticed by xmonad's recompilation checker, so xmonad.hs won't be recompiled. (needs confirmation: is this true?) To fix this:

   xmonad --recompile

after reinstalling the contrib library.

Tabbed or other decorated layouts not shown

Both xmobar and xmonad's default Theme use the -misc-fixed-*-*-*-*-10-*-*-*-*-*-*-* font by default. This is possibly the most commonly installed font in the *nix world, but if it's not installed, or core fonts aren't working for some reason, you'll have problems. Without the font you have set in your Theme....

tabs and other decorated layouts will simply not draw. There should be font related errors in .xsession-errors or wherever your display manager directs stderr to help confirm that this is the cause of missing decorations. xmobar will spit out a cryptic error message and refuse to run.

Check with xfontsel that you have the fixed 10 font if you want to use the defaults. For xft, check that your xmonad and xmobar were compiled with xft support. (They are by default on most distros) Then customize your theme by using something like the following in your layoutHook

myTabbed = tabbed shrinkText defaultTheme {
          fontName = "xft:terminus:size=12" -- choose an installed font
          -- more theme customizations
        }

main = do
    -- skipped
        , layoutHook = avoidStruts $ myTabbed ||| layoutHook defaultConfig
    }

DE panels pagers or EwmhDesktops are broken (just upgraded to >0.8)

Starting with 0.9, EwmhDesktops users must change configuration by removing the obsolete ewmhDesktopsLayout from layoutHook, (it no longer exists), and updating to the current ewmh support which still includes a logHook, but in place of the old layout modifier, uses a startupHook and handleEventHook (see ff.).(No need to change config if using ewmh via Config.Desktop, Config.Gnome, etc. Your config will automatically be updated to use current ewmh support.)

Users of defaultConfig that explicitly include EwmhDesktops hooks and the ewmhDesktopsLayout modifier should remove them and instead use the new ewmh function which adds EWMH support to defaultConfig all at once. You should keep avoidStruts and manageDocks if you're using them.

The 0.9 way to use EwmhDesktops rather than a desktop config is:

import XMonad
import XMonad.Hooks.EwmhDesktops

main = xmonad $ ewmh defaultConfig {
        -- normal customizations
        }

defaultGaps doesn't work any more! (just upgraded to >0.7)

See Make space for a panel section: use XMonad.Hooks.ManageDocks avoidStruts for this instead of Gaps, or import XMonad.Layout.Gaps.

Showing fractions of lines in gvim, urxvt,etc.

This is due to certain layouts doesn't care about so called size hints (resize increments) specifically the WM_NORMAL_HINTS(WM_SIZE_HINTS) (use xprop to see it). This, combined with certain programs, like gvim, which doesn't check if it gets enough size to render the last line and uses it anyway render this annoying behaviour. Aside from patching the offending program, you can:

  1. Use a layout which uses these size hints like Hinted Grid, or HintedTile
  2. Use the layoutHints modifier on any layout
  3. Workaround in .vimrc. These lines in your .vimrc lets you change the number of lines with F4/Shift-F4:
  map <F4> :let &lines=&lines-1^M
  map <S-F4> :let &lines=&lines+1^M

The ^M is created with Ctrl-V Ctrl-M.

Losing text when resizing xterms

Being a dynamic tiling window manager, xmonad, like ion or dwm, makes heavy use of resizing. Clients such as xterm, might not take well to resizing and the window might require a refresh (Ctrl-L). To minimize this, several users recommend urxvt (rxvt-unicode), which handles resizing much better.

I just resized my terminal, but the terminal app didn't resize.

This is a SIGWINCH bug in the Linux kernel, believe it or not, starting in 2.6.26. Details here: http://groups.google.com/group/fa.linux.kernel/browse_thread/thread/8044876def45c0b0/4b7f4cd87feafe5e?show_docid=4b7f4cd87feafe5e.

The simplest solution is to up/downgrade to a kernel version without this bug.

However, there is a pending patch in the linux-next branch here: http://git.kernel.org/?p=linux/kernel/git/sfr/linux-next.git;a=commit;h=3e0301ea47644782e0c0432b66fffd9da86323cc. It should be included in a near-future version of the kernel.

XMonad is frozen!

XMonad stops but the current window still responds to keys

Usually this is because a dynamicLog is writing to a pipe handle that's not being read. For example the xmonad.hs uses spawnPipe to run a status bar and writes to it in the logHook, but the status bar is not installed, not in $PATH, or just plain not running, or else its not set up to read its stdin.

To cat the pipe an free up xmonad, find xmonad's pid via pgrep or htop, etc. let's say it's 1001, then ls -l /proc/1001/fd/ and look for the largest numbered pipe. Let's use 4. Then cat /proc/1001/fd/4 to free up xmonad so you can fix your xmonad.hs and xmobarrc to work correctly.

If you don't want xmonad info in a status bar, don't change the logHook to write output. Instead comment it out or delete the ppOutput field to leave it at the default.

With xmobar, if your logHook is writing to its stdin via ppOutput = hPutStrLn handleToXmobarProcess, make sure the .xmobarrc commands include a Run StdinReader line, and the template includes %StdinReader%.

(See John Goerzen's tutorial for an example of an .xmobarrc with working StdinReader.)

See also this issue on the xmonad bug tracker.

XMonad stops responding to keys (usually due to unclutter)

The number one cause for this is the 'unclutter' program, which can fool some clients into thinking they've lost the pointer, when in fact they have not. See the '-noevents' flag to unclutter.

Use the XMonad.Actions.Warp contrib module instead.

An app seems to have frozen and xmonad stops responding to keys

Often you can get X to behave again by running 'xclock -display :0' on the appropriate display via ssh or from a virtual terminal. If that's not enough kill suspect apps similarly.

There is also an option in (pre evdev versions of) xorg.conf which enables the key combination Ctrl+Alt+Keypad-Divide to break active keyboard and mouse grabs.

This may allow xmonad to continue normally in such cases. To enable this key combination, add the following line to your xorg.conf in the

Section Server Flags then restart X:

Option "AllowDeactivateGrabs" "on"

Problems with Java applications, Applet java console

See issue 177 for problems with focus.

The Java gui toolkit has a hardcoded list of so-called "non-reparenting" window managers. xmonad is not on this list (nor are many of the newer window managers). Attempts to run Java applications may result in `grey blobs' where windows should be, as the Java gui code gets confused.

If you are using openjdk6 >= 1.6.1, the cleanest way to work around the hardcoded list is to warn the vm that xmonad is non-reparenting by exporting the appropriate environment variable:

_JAVA_AWT_WM_NONREPARENTING=1

Using JDK 7 seems to work well, too, see below.

Otherwise, you can lie to Java about what window manager you are using, by having the SetWMName extension convince Java that xmonad is "LG3D". Normally you would use this in startup hook, like this:

-- etc
import XMonad.Hooks.SetWMName

main = do
    xmonad $ defaultConfig
    { modMask = mod4Mask
    , startupHook = setWMName "LG3D"
    -- other customizations
    }

However, in xmonad versions 0.7 and 0.8 modules using Hooks.EwmhDesktops, such as Config.Gnome, Config.Desktops, etc. setWMName to "xmonad" on each logHook event, thus over-writing the java startup hook setWMName. See below for a dirty hack to make both work together.

(Starting with xmonad-0.9. the window manager name is set once in startupHook after each mod-q, along with other EWMH initialization, but after that can be changed in order to fool java into at least attempting to work, rather than giving up too early.)

Using SetWMName with EwmhDesktops

These workarounds also fix an issue with Java gui applications where menus are not "selectable". Clicking on the menu item opens the dropdown list of options but you can't select one.

For > xmonad-0.8.1 -- (0.9 or darcs): (The situation has improved starting with 0.9. Rather than spamming the X server constantly, EwmhDesktops now sets wm name once when xmonad restarts, then leaves it up to the user to set different names as needed. With 0.9, simply setWMName in startupHook or with a keybinding, and use the ewmh config modifier to add ewmh support.)

-- etc
import XMonad.Hooks.EwmhDesktops
import XMonad.Hooks.SetWMName

main = do
    xmproc <- spawnPipe "/usr/local/bin/xmobar /home/me/.xmobarrc-top"

 -- using ewmh config modifier to add extended window manager hints

    xmonad $ ewmh defaultConfig
      { manageHook  = myManageHooks <+> manageDocks <+> manageHook defaultConfig
      , startupHook = setWMName "LG3D"
      , layoutHook  = avoidStruts $ myLayout ||| layoutHook defaultConfig
      , logHook     = dynamicLogWithPP xmobarPP
                          { ppOutput = hPutStrLn xmproc
                          , ppLayout = const ""
                          , ppTitle = xmobarColor "green" "" . shorten 80
                          }
      }

or if not using the ewmh config modifier, but rather defining each EwmhHook yourself: Add ewmhDesktopsStartup, (or startupHook gnomeConfig, startupHook desktopConfig, etc.) to startupHook before setWMName:

-- etc
import XMonad.Hooks.EwmhDesktops
import XMonad.Hooks.SetWMName

main = do

 -- defining EWMH hooks yourself

    xmonad $ defaultConfig
      { -- skipped
      , startupHook = ewmhDesktopsStartup >> setWMName "LG3D"
      }

For xmonad-0.8* :

-- etc
import XMonad.Hooks.EwmhDesktops
import XMonad.Hooks.ManageDocks
import XMonad.Hooks.SetWMName

main = do
    xmproc <- spawnPipe "/usr/local/bin/xmobar /home/me/.xmobarrc-top"
    xmonad $ defaultConfig
      { manageHook = myManageHooks <+> manageDocks <+> manageHook defaultConfig
      , layoutHook = avoidStruts $ ewmhDesktopsLayout $ myLayout ||| layoutHook defaultConfig
        -- NOTE: no $ used between dynamicLogWithPP and xmobarPP
      , logHook    = dynamicLogWithPP xmobarPP
                          { ppOutput = hPutStrLn xmproc
                          , ppLayout = const ""
                          , ppTitle = xmobarColor "green" "" . shorten 80
                          }
                     >> ewmhDesktopsLogHook
                     >> setWMName "LG3D"

      ---- or with a desktop config, e.g.
      -- , logHook = logHook gnomeConfig >> setWMName "LG3D"
      }

Changing AWT Toolkit

Another option is to use an AWT toolkit that is more window manager agnostic, (Some report that this causes keyboard to fail in some java application.) If you want to try it, set the environment varialbe:

  AWT_TOOLKIT=MToolkit

This seems to fix:

  • MATLAB
  • cgoban3
  • Netbeans
  • Using the free blackdown java runtime also seems to work correctly.

Use JDK 7

  • Using JDK 7 also seems to work well. Anthony Brown writes:

    I just downloaded and early binary release of JDK 7 and it looks like the new Java version behaves properly ... I tried using some Gui apps that gave me the infamous grey windows with Java6 (or Java5 without setting AWT_TOOLKIT=MToolkit) and so far no problems occured.

JDK 7 solved problems remaining even when using setWMName "LG3D" in logHook, (Gunnar Ahlberg #xmonad).

Persuade a java application to use a specific java runtime (JRE)

Sometimes it turns out that a program works with a specific JRE version, but not with another. Commercial programs tend to ship with their own JRE, so you may even notice that one program works while another doesn't. (For example, I've had a setup where Maple had problems while Matlab behaved well.) A java symlink in the right place can do wonders here. See this Ubuntu bug report for a number of examples.

XMonad doesn't save my layouts and windows

xmonad will remember your workspace layouts during dynamic restart (mod-q), but not when quitting X altogether. Note that this means if you add or remove layouts to the config.hs file, the changes won't be noticed during a hot-restart (the state from the previous session will be used).

You can reinitialise the xmonad state dynamically with mod-shift-space.

Some keys not working

If you've an unusual keyboard, X may not know precisely which keys you've bound xmonad actions to. An example is when you've use a French keyboard. You may need to set your own mod key, or use different key bindings in Config.hs. See this thread for advice on rebinding keys. Also, for binding to media keys, Benjamin A’Lee has written a great step by step guide to binding non-standard keys in xmonad.

Numeric keypad keys like xK_KP_2 not working

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:

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

Keybindings dont work with rdesktop

Try running with the "-K" (keep window manager key bindings) switch. For example, rdesktop -K -f 666.666.666.666 then press Ctrl-Alt-Enter, or simply rdesktop -K 666.666.666.666

Firefox's annoying popup downloader

Some applications, notably Firefox 1 and 2, create tranisent windows not set with the transient property. (e.g. firefox's download manager). When these windows appear, they can take focus and be annoying. For the case of firefox, the 'Download Statusbar' extension is useful for disabling this annoying UI feature.

Firefox's annoying ability to force you to view it even if you're on another workspace

If one uses EWM Hints support, firefox is enabled to choose when you view its workspace, i.e. if you open links from emails or irc or whatever. If you find it annoying... In about:config (vimperator :preferences!) set browser.tabs.loadDivertedInBackground to True to be able to load urls while working elsewhere, then browse them all later when you choose to shift to the firefox workspace. Also ubuntu users may need to disable the ubufox extension.

Copy and Paste on the Mac

When using X11 for Mac OS X, and you switch from the quartz WM to xmonad, you can lose copy/paste functionality between X windows and normal Mac apps. To fix this, and restore copy and paste, add

   quartz-wm --only-proxy &

in your .xinitrc above the line that runs xmonad. It will capture and syncronize copy/paste events in both environments. More specifically, it mirrors OS X copy actions into both PRIMARY and CLIPBOARD, but only CLIPBOARD into OS X paste.

OpenOffice looks bad

OpenOffice won't use (strangely) the GTK look, unless the following environment variable is set:

   OOO_FORCE_DESKTOP=gnome

Use this if you don't like the default look of OpenOffice in xmonad.

Help! xmonad just segfaulted

Due to this bug in GHC's recompilation checker,

   http://hackage.haskell.org/trac/ghc/ticket/1372

if you updated a previously built xmonad, or XMonadContrib, when a depedent library has changed in the meantime, GHC will happilly go ahead and link your libraries together, into a broken binary. This will at best produce a linker error, and at worst, a version of xmonad that will segfault.

The rule is: when rebuilding, for example, XMonadContrib, always clean first if any library it depends on has changed.

   runhaskell Setup.lhs clean

You may also want to make sure your config gets rebuilt:

   xmonad --recompile

Another possibility is your xmonad was compiled against a very old version of the haskell-x11 library. Use haskell-X11-1.4.2 or newer. This version incorporates a couple of WM_HINTS related segfault bug fixes.

Cabal: Executable stanza starting with field 'flag small_base description'

When using ghc 6.6, or old versions of Cabal, you may get errors when configuring:

   *** Exception: getSection got a line without a '{'.  Consider this a bug.

These are all symptoms of trying to compile xmonad with an old version of cabal.

The darcs version after xmonad 0.4 switched to requiring Cabal 1.2 to build xmonad. You must have Cabal 1.2 or newer to build xmonad older than 0.4. It will work fine with ghc 6.6.1, and you do not need to updated ghc. This will also not break older packages. Get cabal from Hackage:

   http://hackage.haskell.org/cgi-bin/hackage-scripts/package/Cabal

Build and install as usual, then rebuild xmonad.

To build Cabal with ghc 6.6.1 you will also need the filepath library, which is also (of course) available from hackage:

   http://hackage.haskell.org/cgi-bin/hackage-scripts/package/filepath