aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Layout/WindowNavigation.hs
diff options
context:
space:
mode:
authorDevin Mullins <me@twifkak.com>2008-04-22 06:52:48 +0200
committerDevin Mullins <me@twifkak.com>2008-04-22 06:52:48 +0200
commit563f847e224850d4e6b9f937f5bab361da921377 (patch)
tree881ac634aa8ea8e9525baf72618c434cf2339e65 /XMonad/Layout/WindowNavigation.hs
parent653e31baa06f74b7f08edcb104f731660544467a (diff)
downloadXMonadContrib-563f847e224850d4e6b9f937f5bab361da921377.tar.gz
XMonadContrib-563f847e224850d4e6b9f937f5bab361da921377.tar.xz
XMonadContrib-563f847e224850d4e6b9f937f5bab361da921377.zip
WindowNavigation: extract navigable function
darcs-hash:20080422045248-78224-659dfcfb05f891904c88ea9782b43c1df85a7beb.gz
Diffstat (limited to 'XMonad/Layout/WindowNavigation.hs')
-rw-r--r--XMonad/Layout/WindowNavigation.hs13
1 files changed, 8 insertions, 5 deletions
diff --git a/XMonad/Layout/WindowNavigation.hs b/XMonad/Layout/WindowNavigation.hs
index 8c01df9..cee5079 100644
--- a/XMonad/Layout/WindowNavigation.hs
+++ b/XMonad/Layout/WindowNavigation.hs
@@ -127,10 +127,10 @@ instance LayoutModifier WindowNavigation Window where
wrs = filter ((`elem` existing_wins) . fst) $ filter ((/=r) . snd) $
filter ((/=w) . fst) origwrs
wnavigable = nub $ concatMap
- (\d -> truncHead $ sortby d $ filter (inr d pt . snd) wrs) [U,D,R,L]
+ (\d -> truncHead $ navigable d pt wrs) [U,D,R,L]
wnavigablec = nub $ concatMap
(\d -> map (\(win,_) -> (win,dirc d)) $
- truncHead $ sortby d $ filter (inr d pt . snd) wrs) [U,D,R,L]
+ truncHead $ navigable d pt wrs) [U,D,R,L]
wothers = case state of Just (NS _ wo) -> map fst wo
_ -> []
mapM_ (sc nbc) (wothers \\ map fst wnavigable)
@@ -139,7 +139,7 @@ instance LayoutModifier WindowNavigation Window where
handleMessOrMaybeModifyIt (WindowNavigation conf (I (Just (NS pt wrs)))) m
| Just (Go d) <- fromMessage m =
- case sortby d $ filter (inr d pt . snd) wrs of
+ case navigable d pt wrs of
[] -> return Nothing
((w,r):_) -> do modify focusWindowHere
return $ Just $ Left $ WindowNavigation conf $ I $ Just $
@@ -155,7 +155,7 @@ instance LayoutModifier WindowNavigation Window where
has x (Just (W.Stack t l rr)) = x `elem` (t : l ++ rr)
| Just (Swap d) <- fromMessage m =
- case sortby d $ filter (inr d pt . snd) wrs of
+ case navigable d pt wrs of
[] -> return Nothing
((w,_):_) -> do let swap st = unint (W.focus st) $ map (swapw (W.focus st)) $ W.integrate st
swapw y x | x == w = y
@@ -171,7 +171,7 @@ instance LayoutModifier WindowNavigation Window where
windows $ W.modify' swap
return Nothing
| Just (Move d) <- fromMessage m =
- case sortby d $ filter (inr d pt . snd) wrs of
+ case navigable d pt wrs of
[] -> return Nothing
((w,_):_) -> do mst <- gets (W.stack . W.workspace . W.current . windowset)
return $ do st <- mst
@@ -184,6 +184,9 @@ instance LayoutModifier WindowNavigation Window where
handleMessOrMaybeModifyIt (WindowNavigation conf (I $ Just (NS pt wrs))) (SomeMessage Hide)
handleMessOrMaybeModifyIt _ _ = return Nothing
+navigable :: Direction -> Point -> [(Window, Rectangle)] -> [(Window, Rectangle)]
+navigable d pt = sortby d . filter (inr d pt . snd)
+
truncHead :: [a] -> [a]
truncHead (x:_) = [x]
truncHead [] = []