summaryrefslogtreecommitdiffstats
path: root/XMonad
diff options
context:
space:
mode:
authorSpencer Janssen <spencerjanssen@gmail.com>2008-10-07 23:20:53 +0200
committerSpencer Janssen <spencerjanssen@gmail.com>2008-10-07 23:20:53 +0200
commit1dbbf91b4b3f24e81534dbd5c537bc9b161d07e5 (patch)
tree38128dfc6f8fea52da254714554db50b0b195056 /XMonad
parentf2015e3a8da76ad819ce3968f057ab10974ec656 (diff)
downloadmetatile-1dbbf91b4b3f24e81534dbd5c537bc9b161d07e5.tar
metatile-1dbbf91b4b3f24e81534dbd5c537bc9b161d07e5.zip
Partial fix for #40
Improvements: - clicking on the root will change focus to that screen - moving the mouse from a window on a screen to an empty screen changes focus to that screen The only remaining issue is that moving the mouse between two empty screens does not change focus. In order to solve this, we'd have to select motion events on the root window, which is potentially expensive. darcs-hash:20081007212053-25a6b-ccec914ace595db38dc035a3b56478bdbf1cc6d3
Diffstat (limited to 'XMonad')
-rw-r--r--XMonad/Operations.hs18
1 files changed, 12 insertions, 6 deletions
diff --git a/XMonad/Operations.hs b/XMonad/Operations.hs
index 40a1a38..5f7d39a 100644
--- a/XMonad/Operations.hs
+++ b/XMonad/Operations.hs
@@ -294,11 +294,17 @@ setTopFocus = withWindowSet $ maybe (setFocusX =<< asks theRoot) setFocusX . W.p
-- This happens if X notices we've moved the mouse (and perhaps moved
-- the mouse to a new screen).
focus :: Window -> X ()
-focus w = withWindowSet $ \s -> do
- if W.member w s then when (W.peek s /= Just w) $ do
- local (\c -> c { mouseFocused = True }) $ do
- windows (W.focusWindow w)
- else whenX (isRoot w) $ setFocusX w
+focus w = local (\c -> c { mouseFocused = True }) $ withWindowSet $ \s -> do
+ let stag = W.tag . W.workspace
+ curr = stag $ W.current s
+ mnew <- maybe (return Nothing) (fmap (fmap stag) . uncurry pointScreen)
+ =<< asks mousePosition
+ root <- asks theRoot
+ case () of
+ _ | W.member w s && W.peek s /= Just w -> windows (W.focusWindow w)
+ | Just new <- mnew, w == root && curr /= new
+ -> windows (W.view new)
+ | otherwise -> return ()
-- | Call X to set the keyboard focus details.
setFocusX :: Window -> X ()
@@ -311,7 +317,7 @@ setFocusX w = withWindowSet $ \ws -> do
setButtonGrab True otherw
-- If we ungrab buttons on the root window, we lose our mouse bindings.
- whenX (not <$> isRoot w) $ setButtonGrab False w
+ whenX (isRoot w) $ setButtonGrab False w
io $ do setInputFocus dpy w revertToPointerRoot 0
-- raiseWindow dpy w