aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Actions/WindowNavigation.hs
diff options
context:
space:
mode:
authorDevin Mullins <me@twifkak.com>2008-05-11 23:21:28 +0200
committerDevin Mullins <me@twifkak.com>2008-05-11 23:21:28 +0200
commitf61523e62c6d86e230cf628a14933596aaa45cd2 (patch)
tree725471dd3837af5116d3b3795965ad48c3d638a9 /XMonad/Actions/WindowNavigation.hs
parenta0f3bb7026ec88c9ee95388ce1c1b3e41a026c5a (diff)
downloadXMonadContrib-f61523e62c6d86e230cf628a14933596aaa45cd2.tar.gz
XMonadContrib-f61523e62c6d86e230cf628a14933596aaa45cd2.tar.xz
XMonadContrib-f61523e62c6d86e230cf628a14933596aaa45cd2.zip
X.A.WindowNavigation: fix currentPosition
Now properly deals with an unitialized state (e.g. from a restart) or an inconsistent state (e.g. from using mod-j/k). Deserves cleanup. darcs-hash:20080511212128-78224-13c7b897401800b9d729e765eba3385e40576f8d.gz
Diffstat (limited to 'XMonad/Actions/WindowNavigation.hs')
-rw-r--r--XMonad/Actions/WindowNavigation.hs51
1 files changed, 28 insertions, 23 deletions
diff --git a/XMonad/Actions/WindowNavigation.hs b/XMonad/Actions/WindowNavigation.hs
index 802ef00..17c3d56 100644
--- a/XMonad/Actions/WindowNavigation.hs
+++ b/XMonad/Actions/WindowNavigation.hs
@@ -45,25 +45,19 @@ import Graphics.X11.Xlib
-- - documentation :)
-- - tests? (esp. for edge cases in currentPosition)
-- - solve the 2+3, middle right to bottom left problem
+-- - manageHook to draw window decos?
+
+
+type WNState = Map WorkspaceId Point
-- go:
-- 1. get current position, verifying it matches the current window
-- 2. get target windowrect
-- 3. focus window
-- 4. set new position
-
--- key bindings to do the important stuff
-
-type WNState = Map WorkspaceId Point
-
--- 1. Get current position, window
--- 2. Determine list of windows in dir from pos, except window
--- 3. Grab closest one
-
go :: IORef WNState -> Direction -> X ()
go posRef dir = fromCurrentPoint $ \win pos -> do
targets <- filter ((/= win) . fst) <$> navigableTargets pos dir
- io $ putStrLn $ "pos: " ++ show pos ++ "; tgts: " ++ show targets
whenJust (listToMaybe targets) $ \(tw, tr) -> do
windows (W.focusWindow tw)
setPosition posRef pos tr
@@ -77,16 +71,27 @@ swap _ _ = return ()
-- a restart), derives the current position from the current window. Also,
-- verifies that the position is congruent with the current window (say, if you
-- used mod-j/k or mouse or something).
--- TODO: replace 0 0 0 0 with 'middle of current window'
--- TODO: correct if not in window, or add logHook
+-- TODO: worry about off-by-one issues with inside definition
currentPosition :: IORef WNState -> X Point
currentPosition posRef = do
+ root <- asks theRoot
+ currentWindow <- gets (W.peek . windowset)
+ currentRect <- maybe (Rectangle 0 0 0 0) snd <$> windowRect (fromMaybe root currentWindow)
+
wsid <- gets (W.tag . W.workspace . W.current . windowset)
mp <- M.lookup wsid <$> io (readIORef posRef)
- return $ fromMaybe (Point 0 0) mp
-navigableTargets :: Point -> Direction -> X [(Window, Rectangle)]
-navigableTargets point dir = navigable dir point <$> windowRects
+ case mp of
+ Just p | p `inside` currentRect -> return p
+ _ -> return (middleOf currentRect)
+
+ where Point px py `inside` Rectangle rx ry rw rh =
+ px >= rx && px < rx + fromIntegral rw &&
+ py >= rx && py < ry + fromIntegral rh
+
+ middleOf (Rectangle x y w h) =
+ Point (x + fromIntegral w `div` 2) (y + fromIntegral h `div` 2)
+ -- return $ fromMaybe (Point 0 0) mp
-- TODO: use a smarter algorithm (with memory of last position)
setPosition :: IORef WNState -> Point -> Rectangle -> X ()
@@ -95,6 +100,9 @@ setPosition posRef _ (Rectangle x y w h) = do
let position = Point (x + (fromIntegral w `div` 2)) (y + (fromIntegral h `div` 2))
io $ modifyIORef posRef $ M.insert wsid position
+navigableTargets :: Point -> Direction -> X [(Window, Rectangle)]
+navigableTargets point dir = navigable dir point <$> windowRects
+
-- Filters and sorts the windows in terms of what is closest from the Point in
-- the Direction.
navigable :: Direction -> Point -> [(Window, Rectangle)] -> [(Window, Rectangle)]
@@ -107,25 +115,22 @@ navigable d pt = sortby d . filter (inr d (fromPoint pt) . snd)
-- TODO: adjust rectangles based on screen position? (perhaps this is already handled)
windowRects :: X [(Window, Rectangle)]
windowRects = do
- dpy <- asks display
wins <- gets (visibleWindows . windowset)
- catMaybes <$> mapM (windowRect dpy) wins
+ catMaybes <$> mapM windowRect wins
where visibleWindows wset = concatMap (W.integrate' . W.stack . W.workspace)
(W.current wset : W.visible wset)
-windowRect :: Display -> Window -> X (Maybe (Window, Rectangle))
-windowRect dpy win = do
+windowRect :: Window -> X (Maybe (Window, Rectangle))
+windowRect win = withDisplay $ \dpy -> do
(_, x, y, w, h, _, _) <- io $ getGeometry dpy win
return $ Just $ (win, Rectangle x y w h)
`catchX` return Nothing
--- manageHook to draw window decos?
-
fromPoint :: Point -> FPoint
fromPoint p = P (fromIntegral $ pt_x p) (fromIntegral $ pt_y p)
--- Stolen from droundy's implementation of WindowNavigation. I should probably take the time
--- to understand the black magic below at some point.
+-- Stolen from droundy's implementation of WindowNavigation.
+-- TODO: refactor, perhaps
data FPoint = P Double Double