aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Actions/WindowGo.hs
diff options
context:
space:
mode:
authorgwern0 <gwern0@gmail.com>2008-12-05 16:07:55 +0100
committergwern0 <gwern0@gmail.com>2008-12-05 16:07:55 +0100
commit262331d567a2cd4a2680977f81e8b2eb92b0b371 (patch)
tree9f742bce883c8aab09fd0796843bcf54b6193e7a /XMonad/Actions/WindowGo.hs
parentcc52df1bfa6888e169f76c447230a466227d796c (diff)
downloadXMonadContrib-262331d567a2cd4a2680977f81e8b2eb92b0b371.tar.gz
XMonadContrib-262331d567a2cd4a2680977f81e8b2eb92b0b371.tar.xz
XMonadContrib-262331d567a2cd4a2680977f81e8b2eb92b0b371.zip
XMonad.Actions.WindowGo: fix a floating-related focus bug
Ignore-this: c8b6625aa2bd4136937acbd2ad64ffd3 If a floating window was focused, a cross-workspace 'raise' would cause a loop of shifting windows. Apparently the problem was 'focus' and its mouse-handling. Spencer suggested that the calls to focus be replaced with 'focusWindow', which resolved it. darcs-hash:20081205150755-f7719-91e0d4144b560a56affbe16a942004e161f8d51c.gz
Diffstat (limited to 'XMonad/Actions/WindowGo.hs')
-rw-r--r--XMonad/Actions/WindowGo.hs22
1 files changed, 9 insertions, 13 deletions
diff --git a/XMonad/Actions/WindowGo.hs b/XMonad/Actions/WindowGo.hs
index deb67ae..81967a5 100644
--- a/XMonad/Actions/WindowGo.hs
+++ b/XMonad/Actions/WindowGo.hs
@@ -34,12 +34,12 @@ module XMonad.Actions.WindowGo (
import Control.Monad (filterM)
import Data.Char (toLower)
-import XMonad (Query(), X(), withWindowSet, spawn, runQuery, liftIO, focus)
+import XMonad (Query(), X(), withWindowSet, spawn, runQuery, liftIO)
+import Graphics.X11 (Window)
import XMonad.ManageHook
-import XMonad.Prompt.Shell (getBrowser, getEditor)
-import qualified XMonad.StackSet as W (allWindows, peek, swapMaster)
import XMonad.Operations (windows)
-import Graphics.X11 (Window)
+import XMonad.Prompt.Shell (getBrowser, getEditor)
+import qualified XMonad.StackSet as W (allWindows, peek, swapMaster, focusWindow)
{- $usage
Import the module into your @~\/.xmonad\/xmonad.hs@:
@@ -99,7 +99,7 @@ raiseMaybe f thatUserQuery = withWindowSet $ \s -> do
maybeResult <- filterM (runQuery thatUserQuery) (W.allWindows s)
case maybeResult of
[] -> f
- (x:_) -> focus x
+ (x:_) -> windows $ W.focusWindow x
-- | See 'runOrRaise' and 'raiseNextMaybe'. Version that allows cycling through matches.
runOrRaiseNext :: String -> Query Bool -> X ()
@@ -121,10 +121,10 @@ raiseNextMaybe f thatUserQuery = withWindowSet $ \s -> do
case ws of
[] -> f
(x:_) -> let go (Just w) | (w `elem` ws) = next w $ cycle ws
- go _ = focus x
+ go _ = windows $ W.focusWindow x
in go $ W.peek s
where
- next w (x:y:_) | x==w = focus y
+ next w (x:y:_) | x==w = windows $ W.focusWindow y
next w (_:xs) = next w xs
next _ _ = error "raiseNextMaybe: empty list"
@@ -148,16 +148,14 @@ raiseAndDo raisef thatUserQuery afterRaise = withWindowSet $ \s -> do
maybeResult <- filterM (runQuery thatUserQuery) (W.allWindows s)
case maybeResult of
[] -> raisef
- (x:_) -> do
- XMonad.focus x
- afterRaise x
+ (x:_) -> do windows $ W.focusWindow x
+ afterRaise x
{- | if the window is found the window is focused and the third argument is called
otherwise, raisef is called -}
runOrRaiseAndDo :: String -> Query Bool -> (Window -> X ()) -> X ()
runOrRaiseAndDo run query afterRaise = raiseAndDo (spawn run) query afterRaise
-
{- | if the window is found the window is focused and set to master
otherwise, the first argument is called
@@ -172,5 +170,3 @@ raiseMaster raisef thatUserQuery = raiseAndDo raisef thatUserQuery (\_ -> window
-}
runOrRaiseMaster :: String -> Query Bool -> X ()
runOrRaiseMaster run query = runOrRaiseAndDo run query (\_ -> windows W.swapMaster)
-
-