[xmonad] WindowNavigation and Spacing Issue

David Hrachovy david.hrachovy at gmail.com
Sun Aug 1 08:33:06 EDT 2010


Hello everyone!

when using WindowNavigation and Spacing together, the window
navigation doesn't work. If the 'spacing 2' is removed the navigation
works. I like both the features. Can you please help me set up window
spacing and easy window navigation?
Try out this minimal example to see the issue - NOTE: you have to
spawn at least three terminals to be able to see it):

import XMonad
import Data.Monoid
import System.Exit

import qualified XMonad.StackSet as W
import qualified Data.Map        as M

import XMonad.Layout.WindowNavigation
import XMonad.Layout.Spacing

myKeys conf@(XConfig {XMonad.modMask = modm}) = M.fromList $
    [ ((modm .|. shiftMask, xK_Return), spawn $ XMonad.terminal conf)
    -- Quit xmonad
    , ((modm .|. shiftMask, xK_q     ), io (exitWith ExitSuccess))

    -- Restart xmonad
    , ((modm              , xK_q     ), spawn "xmonad --recompile;
xmonad --restart")
    -- WindowNavigation
    , ((modm,                 xK_l), sendMessage $ Go R)
    , ((modm,                 xK_h ), sendMessage $ Go L)
    , ((modm,                 xK_k   ), sendMessage $ Go U)
    , ((modm,                 xK_j ), sendMessage $ Go D)
    ]

myLayout =  windowNavigation $ spacing 2 tiled
  where
    tiled   = Tall nmaster delta ratio
    nmaster = 1
    ratio   = 1/2
    delta   = 3/100

main = xmonad defaultConfig
        {
        terminal = "xterm",
        keys               = myKeys,
        layoutHook         = myLayout
        }



I am running xmonad 0.9.1.
Thank you

David H.


More information about the xmonad mailing list