aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Actions
diff options
context:
space:
mode:
authorIlya Portnov <portnov84@rambler.ru>2011-05-15 17:42:46 +0200
committerIlya Portnov <portnov84@rambler.ru>2011-05-15 17:42:46 +0200
commit19372972eba5cb9b9adfeb9f5fa31456946b0ecd (patch)
tree8f0898297a667589a4cfad486e700de1ccabaa79 /XMonad/Actions
parentd2d1294856f855ed492ad3cdba9013333689cb8a (diff)
downloadXMonadContrib-19372972eba5cb9b9adfeb9f5fa31456946b0ecd.tar.gz
XMonadContrib-19372972eba5cb9b9adfeb9f5fa31456946b0ecd.tar.xz
XMonadContrib-19372972eba5cb9b9adfeb9f5fa31456946b0ecd.zip
Extend GridSelect navigation
Ignore-this: f2d279b8e46e6eaf3477fdc5cf77be63 Add moveNext and movePrev, which move selection to next/previous item. darcs-hash:20110515154246-c5067-e117b3d5753e868963b36a10d2e17ccc427a97b7.gz
Diffstat (limited to 'XMonad/Actions')
-rw-r--r--XMonad/Actions/GridSelect.hs27
1 files changed, 26 insertions, 1 deletions
diff --git a/XMonad/Actions/GridSelect.hs b/XMonad/Actions/GridSelect.hs
index d9413e0..d0d14db 100644
--- a/XMonad/Actions/GridSelect.hs
+++ b/XMonad/Actions/GridSelect.hs
@@ -60,6 +60,7 @@ module XMonad.Actions.GridSelect (
-- * Navigation Components
setPos,
move,
+ moveNext, movePrev,
select,
cancel,
transformSearchString
@@ -404,6 +405,30 @@ move (dx,dy) = do
newPos = (x+dx,y+dy)
setPos newPos
+moveNext :: TwoD a ()
+moveNext = do
+ position <- gets td_curpos
+ elems <- gets td_elementmap
+ let n = length elems
+ m = case findIndex (\p -> fst p == position) elems of
+ Nothing -> Nothing
+ Just k | k == n-1 -> Just 0
+ | otherwise -> Just (k+1)
+ whenJust m $ \i ->
+ setPos (fst $ elems !! i)
+
+movePrev :: TwoD a ()
+movePrev = do
+ position <- gets td_curpos
+ elems <- gets td_elementmap
+ let n = length elems
+ m = case findIndex (\p -> fst p == position) elems of
+ Nothing -> Nothing
+ Just 0 -> Just (n-1)
+ Just k -> Just (k-1)
+ whenJust m $ \i ->
+ setPos (fst $ elems !! i)
+
-- | Apply a transformation function the current search string
transformSearchString :: (String -> String) -> TwoD a ()
transformSearchString f = do
@@ -661,4 +686,4 @@ gridselectWorkspace :: GSConfig WorkspaceId ->
(WorkspaceId -> WindowSet -> WindowSet) -> X ()
gridselectWorkspace conf viewFunc = withWindowSet $ \ws -> do
let wss = map W.tag $ W.hidden ws ++ map W.workspace (W.current ws : W.visible ws)
- gridselect conf (zip wss wss) >>= flip whenJust (windows . viewFunc) \ No newline at end of file
+ gridselect conf (zip wss wss) >>= flip whenJust (windows . viewFunc)