aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Actions/WindowNavigation.hs
diff options
context:
space:
mode:
authorDevin Mullins <me@twifkak.com>2008-05-25 05:23:25 +0200
committerDevin Mullins <me@twifkak.com>2008-05-25 05:23:25 +0200
commiteee99f38c73b75eed4b4fac283c75261800ae977 (patch)
tree441ac52fdbf4eef407893a4646f0c7638022081c /XMonad/Actions/WindowNavigation.hs
parent898efa5e7b595d94cbeac812778d1ab49a4360ea (diff)
downloadXMonadContrib-eee99f38c73b75eed4b4fac283c75261800ae977.tar.gz
XMonadContrib-eee99f38c73b75eed4b4fac283c75261800ae977.tar.xz
XMonadContrib-eee99f38c73b75eed4b4fac283c75261800ae977.zip
X.A.WindowNavigation: add logHook for better state tracking
darcs-hash:20080525032325-78224-5afb5996c4097846b35af21a715a66407a46f65e.gz
Diffstat (limited to 'XMonad/Actions/WindowNavigation.hs')
-rw-r--r--XMonad/Actions/WindowNavigation.hs19
1 files changed, 13 insertions, 6 deletions
diff --git a/XMonad/Actions/WindowNavigation.hs b/XMonad/Actions/WindowNavigation.hs
index a072f67..3d636ba 100644
--- a/XMonad/Actions/WindowNavigation.hs
+++ b/XMonad/Actions/WindowNavigation.hs
@@ -45,9 +45,9 @@ import Graphics.X11.Xlib
-- Don't use it! What, are you crazy?
-- TODO:
--- - logHook? (2+1, start at master, j,j,a)
--- - cleanup (including inr)
-- - documentation :)
+-- - monad for WNState?
+-- - cleanup (including inr)
-- - tests? (esp. for edge cases in currentPosition)
-- - solve the 2+3, middle right to bottom left problem
-- - manageHook to draw window decos?
@@ -68,7 +68,8 @@ withWindowNavigationKeys :: [((KeyMask, KeySym), WNAction)] -> XConfig l -> IO (
withWindowNavigationKeys wnKeys conf = do
posRef <- newIORef M.empty
return conf { keys = \cnf -> M.fromList (map (second (fromWNAction posRef)) wnKeys)
- `M.union` keys conf cnf }
+ `M.union` keys conf cnf,
+ logHook = logHook conf >> trackMovement posRef }
where fromWNAction posRef (WNGo dir) = go posRef dir
fromWNAction posRef (WNSwap dir) = swap posRef dir
@@ -97,13 +98,19 @@ swap = withTargetWindow swapWithFocused
swapWin win1 win2 win = if win == win1 then win2 else if win == win2 then win1 else win
withTargetWindow :: (Window -> WindowSet -> WindowSet) -> IORef WNState -> Direction -> X ()
-withTargetWindow adj posRef dir = fromCurrentPoint $ \win pos -> do
+withTargetWindow adj posRef dir = fromCurrentPoint posRef $ \win pos -> do
targets <- filter ((/= win) . fst) <$> navigableTargets pos dir
whenJust (listToMaybe targets) $ \(targetWin, targetRect) -> do
windows (adj targetWin)
setPosition posRef pos targetRect
- where fromCurrentPoint f = withFocused $ \win -> do
- currentPosition posRef >>= f win
+
+trackMovement :: IORef WNState -> X ()
+trackMovement posRef = fromCurrentPoint posRef $ \win pos -> do
+ windowRect win >>= flip whenJust (setPosition posRef pos . snd)
+
+fromCurrentPoint :: IORef WNState -> (Window -> Point -> X ()) -> X ()
+fromCurrentPoint posRef f = withFocused $ \win -> do
+ currentPosition posRef >>= f win
-- Gets the current position from the IORef passed in, or if nothing (say, from
-- a restart), derives the current position from the current window. Also,