aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Actions/CycleWS.hs
diff options
context:
space:
mode:
authorDaniel Schoepe <daniel.schoepe@gmail.com>2009-09-19 21:17:17 +0200
committerDaniel Schoepe <daniel.schoepe@gmail.com>2009-09-19 21:17:17 +0200
commitc1a6ed7be8b090cea63a70fa86ee614d011d0f63 (patch)
tree2611d41215616daba97a239330d85a00123f44e6 /XMonad/Actions/CycleWS.hs
parent3bd3fd1d4bd1af1ffe306307a80387c82d304664 (diff)
downloadXMonadContrib-c1a6ed7be8b090cea63a70fa86ee614d011d0f63.tar.gz
XMonadContrib-c1a6ed7be8b090cea63a70fa86ee614d011d0f63.tar.xz
XMonadContrib-c1a6ed7be8b090cea63a70fa86ee614d011d0f63.zip
Factor out direction types and put them in X.U.Types
Ignore-this: b2255ec2754fcdf797b1ce2c082642ba This patch factors out commonly used direction types like data Direction darcs-hash:20090919191717-7f603-09c283e51a0b886d260008676d71e3daf31f4394.gz
Diffstat (limited to 'XMonad/Actions/CycleWS.hs')
-rw-r--r--XMonad/Actions/CycleWS.hs12
1 files changed, 5 insertions, 7 deletions
diff --git a/XMonad/Actions/CycleWS.hs b/XMonad/Actions/CycleWS.hs
index 6cce784..f7c9fe4 100644
--- a/XMonad/Actions/CycleWS.hs
+++ b/XMonad/Actions/CycleWS.hs
@@ -60,7 +60,7 @@ module XMonad.Actions.CycleWS (
-- * Moving between workspaces, take two!
-- $taketwo
- , WSDirection(..)
+ , Direction1D(..)
, WSType(..)
, shiftTo
@@ -80,6 +80,7 @@ import Data.Maybe ( isNothing, isJust )
import XMonad hiding (workspaces)
import XMonad.StackSet hiding (filter)
+import XMonad.Util.Types
import XMonad.Util.WorkspaceCompare
-- $usage
@@ -211,9 +212,6 @@ the letter 'p' in its name. =)
-}
--- | Direction to cycle through the sort order.
-data WSDirection = Next | Prev
-
-- | What type of workspaces should be included in the cycle?
data WSType = EmptyWS -- ^ cycle through empty workspaces
| NonEmptyWS -- ^ cycle through non-empty workspaces
@@ -238,12 +236,12 @@ wsTypeToPred (WSIs p) = p
-- | View the next workspace in the given direction that satisfies
-- the given condition.
-moveTo :: WSDirection -> WSType -> X ()
+moveTo :: Direction1D -> WSType -> X ()
moveTo dir t = findWorkspace getSortByIndex dir t 1 >>= windows . greedyView
-- | Move the currently focused window to the next workspace in the
-- given direction that satisfies the given condition.
-shiftTo :: WSDirection -> WSType -> X ()
+shiftTo :: Direction1D -> WSType -> X ()
shiftTo dir t = findWorkspace getSortByIndex dir t 1 >>= windows . shift
-- | Given a function @s@ to sort workspaces, a direction @dir@, a
@@ -259,7 +257,7 @@ shiftTo dir t = findWorkspace getSortByIndex dir t 1 >>= windows . shift
-- that 'moveTo' and 'shiftTo' are implemented by applying @(>>=
-- (windows . greedyView))@ and @(>>= (windows . shift))@, respectively,
-- to the output of 'findWorkspace'.
-findWorkspace :: X WorkspaceSort -> WSDirection -> WSType -> Int -> X WorkspaceId
+findWorkspace :: X WorkspaceSort -> Direction1D -> WSType -> Int -> X WorkspaceId
findWorkspace s dir t n = findWorkspaceGen s (wsTypeToPred t) (maybeNegate dir n)
where
maybeNegate Next d = d