aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Actions/UpdateFocus.hs
diff options
context:
space:
mode:
authorDaniel Schoepe <asgaroth_@gmx.de>2009-04-07 21:18:19 +0200
committerDaniel Schoepe <asgaroth_@gmx.de>2009-04-07 21:18:19 +0200
commitd6cd263c475ac0d2243d69268e6d246ba4728ac0 (patch)
tree3bbfcf2a3eecdb7ad61e065ff2b7ee65c73177d8 /XMonad/Actions/UpdateFocus.hs
parent27a4fc19a7aadf432bf36905ebc829929ecb0e63 (diff)
downloadXMonadContrib-d6cd263c475ac0d2243d69268e6d246ba4728ac0.tar.gz
XMonadContrib-d6cd263c475ac0d2243d69268e6d246ba4728ac0.tar.xz
XMonadContrib-d6cd263c475ac0d2243d69268e6d246ba4728ac0.zip
Update focus on mouse moves within inactive windows
Ignore-this: 36c05c60420520dab708401d8a80fc85 This patch adds functionality to update the focus on moves in unfocused windows, which would make sense if one wanted the focus to follow the mouse. Currently this only happens when the mouse enters/leaves a window. This patch should fix issue #205. darcs-hash:20090407191819-cb1c6-f94441281224917d710ae5e1e1dbc1c9f3fa98b6.gz
Diffstat (limited to 'XMonad/Actions/UpdateFocus.hs')
-rw-r--r--XMonad/Actions/UpdateFocus.hs61
1 files changed, 61 insertions, 0 deletions
diff --git a/XMonad/Actions/UpdateFocus.hs b/XMonad/Actions/UpdateFocus.hs
new file mode 100644
index 0000000..fb51ea3
--- /dev/null
+++ b/XMonad/Actions/UpdateFocus.hs
@@ -0,0 +1,61 @@
+-----------------------------------------------------------------------------
+-- |
+-- Module : XMonadContrib.UpdateFocus
+-- Copyright : (c) Daniel Schoepe
+-- License : BSD3-style (see LICENSE)
+--
+-- Maintainer : Daniel Schoepe <asgaroth_@gmx.de>
+-- Stability : unstable
+-- Portability : unportable
+--
+-- Updates the focus on mouse move in unfocused windows.
+--
+-----------------------------------------------------------------------------
+
+module XMonad.Actions.UpdateFocus (
+ -- * Usage
+ -- $usage
+ focusOnMouseMove,
+ adjustEventInput
+) where
+
+import XMonad
+import qualified XMonad.StackSet as W
+import Graphics.X11.Xlib.Extras
+import Control.Monad (when)
+import Data.Monoid
+
+-- $usage
+-- To make the focus update on mouse movement within an unfocused window, add the
+-- following to your @~\/.xmonad\/xmonad.hs@:
+--
+-- > import XMonad.Actions.UpdateFocus
+-- > xmonad $ defaultConfig {
+-- > ..
+-- > startupHook = adjustEventInput
+-- > handleEventHook = focusOnMouseMove
+-- > ..
+-- > }
+--
+-- This module is probably only useful when focusFollowsMouse is set to True(default).
+
+-- | Changes the focus if the mouse is moved within an unfocused window.
+focusOnMouseMove :: Event -> X All
+focusOnMouseMove (MotionEvent { ev_x = x, ev_y = y, ev_window = root }) = do
+ -- check only every 15 px to avoid excessive calls to translateCoordinates
+ when (x `mod` 15 == 0 || y `mod` 15 == 0) $ do
+ dpy <- asks display
+ Just foc <- withWindowSet $ return . W.peek
+ -- get the window under the pointer:
+ (_,_,_,w) <- io $ translateCoordinates dpy root root (fromIntegral x) (fromIntegral y)
+ when (foc /= w) $ focus w
+ return (All True)
+focusOnMouseMove _ = return (All True)
+
+-- | Adjusts the event mask to pick up pointer movements.
+adjustEventInput :: X ()
+adjustEventInput = withDisplay $ \dpy -> do
+ rootw <- asks theRoot
+ io $ selectInput dpy rootw $ substructureRedirectMask .|. substructureNotifyMask
+ .|. enterWindowMask .|. leaveWindowMask .|. structureNotifyMask
+ .|. buttonPressMask .|. pointerMotionMask \ No newline at end of file