aboutsummaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
-rw-r--r--RotView.hs40
1 files changed, 18 insertions, 22 deletions
diff --git a/RotView.hs b/RotView.hs
index 46ce0bf..0bc995b 100644
--- a/RotView.hs
+++ b/RotView.hs
@@ -8,28 +8,24 @@ module XMonadContrib.RotView ( rotView ) where
-- , ((modMask .|. shiftMask, xK_Right), rotView True)
-- , ((modMask .|. shiftMask, xK_Left), rotView False)
-import qualified Data.Map as M
-import Control.Monad.State
-
-import Operations ( view )
-import XMonad ( X, WorkspaceId, workspace, whenJust )
-import StackSet ( StackSet )
+import Control.Monad.State ( gets )
+import Data.List ( sortBy )
import Data.Maybe ( listToMaybe )
-import qualified StackSet as W ( stacks, current, visibleWorkspaces, index )
-
-rotView :: Bool -> X ()
-rotView b = do ws <- gets windowset
- let m = W.current ws
- vis = W.visibleWorkspaces ws
- allws = if b then allWorkspaces ws else reverse $ allWorkspaces ws
- pivoted = uncurry (flip (++)) . span (/=m) $ allws
- interesting i = not (i `elem` vis) && not (isEmpty i ws)
- nextws = listToMaybe . filter interesting $ pivoted
- whenJust nextws view
--- | A list of all the workspaces.
-allWorkspaces :: StackSet WorkspaceId j a -> [WorkspaceId]
-allWorkspaces = M.keys . W.stacks
+import XMonad
+import StackSet
+import qualified Operations as O
-isEmpty :: WorkspaceId -> StackSet WorkspaceId j a -> Bool
-isEmpty i = maybe True null . W.index i
+rotView :: Bool -> X ()
+rotView b = do
+ ws <- gets windowset
+ let m = tag . workspace . current $ ws
+ sortWs = sortBy (\x y -> compare (tag x) (tag y))
+ pivoted = uncurry (flip (++)) . span ((< m) . tag) . sortWs . hidden $ ws
+ nextws = listToMaybe . filter (not.isEmpty) . (if b then id else reverse) $ pivoted
+ whenJust nextws (O.view . tag)
+
+isEmpty :: Workspace i a -> Bool
+isEmpty ws = case stack ws of
+ Empty -> True
+ _ -> False