aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Layout/WindowNavigation.hs
diff options
context:
space:
mode:
authorDavid Roundy <droundy@darcs.net>2007-11-15 00:19:14 +0100
committerDavid Roundy <droundy@darcs.net>2007-11-15 00:19:14 +0100
commit813ce2d41eb0b0af6523fdaec1475b8debed50d7 (patch)
tree5d8e10d3c004660b1a892f6c10db066ff1474f74 /XMonad/Layout/WindowNavigation.hs
parent08a08748ef822c5bcadfebd86e84035c8cb47003 (diff)
downloadXMonadContrib-813ce2d41eb0b0af6523fdaec1475b8debed50d7.tar.gz
XMonadContrib-813ce2d41eb0b0af6523fdaec1475b8debed50d7.tar.xz
XMonadContrib-813ce2d41eb0b0af6523fdaec1475b8debed50d7.zip
fix bug in WindowNavigation.
We weren't properly cleaning up in some cases, because we called focus, which calls windows, while handling a message, which had the result that changes to the layout were overwritten. This had the result that windowNavigation combined with DragPane left stray drag bars hanging around. darcs-hash:20071114231914-72aca-5d9e48462aa44a72c9b759dd1eb0adf60b41c5aa.gz
Diffstat (limited to 'XMonad/Layout/WindowNavigation.hs')
-rw-r--r--XMonad/Layout/WindowNavigation.hs16
1 files changed, 13 insertions, 3 deletions
diff --git a/XMonad/Layout/WindowNavigation.hs b/XMonad/Layout/WindowNavigation.hs
index 4608ba5..6388a2e 100644
--- a/XMonad/Layout/WindowNavigation.hs
+++ b/XMonad/Layout/WindowNavigation.hs
@@ -27,11 +27,11 @@ module XMonad.Layout.WindowNavigation (
import Graphics.X11.Xlib ( Rectangle(..), Window, Pixel, setWindowBorder )
import Control.Monad.Reader ( ask )
-import Control.Monad.State ( gets )
+import Control.Monad.State ( gets, modify )
import Data.List ( nub, sortBy, (\\) )
import XMonad
import qualified XMonad.StackSet as W
-import XMonad.Operations ( windows, focus )
+import XMonad.Operations ( windows )
import XMonad.Layout.LayoutModifier
import XMonad.Util.Invisible
import XMonad.Util.XUtils
@@ -144,9 +144,19 @@ instance LayoutModifier WindowNavigation Window where
| Just (Go d) <- fromMessage m =
case sortby d $ filter (inr d pt . snd) wrs of
[] -> return Nothing
- ((w,r):_) -> do focus w
+ ((w,r):_) -> do modify focusWindowHere
return $ Just $ Left $ WindowNavigation conf $ I $ Just $
NS (centerd d pt r) wrs
+ where focusWindowHere :: XState -> XState
+ focusWindowHere s
+ | Just w == W.peek (windowset s) = s
+ | has w $ W.stack $ W.workspace $ W.current $ windowset s =
+ s { windowset = until ((Just w ==) . W.peek)
+ W.focusUp $ windowset s }
+ | otherwise = s
+ has _ Nothing = False
+ has x (Just (W.Stack t l rr)) = x `elem` (t : l ++ rr)
+
| Just (Swap d) <- fromMessage m =
case sortby d $ filter (inr d pt . snd) wrs of
[] -> return Nothing