aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Actions/CycleWS.hs
diff options
context:
space:
mode:
authormail <mail@joachim-breitner.de>2007-12-27 19:26:35 +0100
committermail <mail@joachim-breitner.de>2007-12-27 19:26:35 +0100
commit5ec14af63aa33027efb643e6a832a579b983fc11 (patch)
tree6a21dcdb03d95086d512c65c828e7c9ecc0c999d /XMonad/Actions/CycleWS.hs
parentccf5f3193175e164330871d0aa243fd5899287d0 (diff)
downloadXMonadContrib-5ec14af63aa33027efb643e6a832a579b983fc11.tar.gz
XMonadContrib-5ec14af63aa33027efb643e6a832a579b983fc11.tar.xz
XMonadContrib-5ec14af63aa33027efb643e6a832a579b983fc11.zip
Add support for cycling through screens to CycleWS
darcs-hash:20071227182635-c9905-de6cc264b94f665c46400199836e8ce9ec7b146c.gz
Diffstat (limited to 'XMonad/Actions/CycleWS.hs')
-rw-r--r--XMonad/Actions/CycleWS.hs41
1 files changed, 33 insertions, 8 deletions
diff --git a/XMonad/Actions/CycleWS.hs b/XMonad/Actions/CycleWS.hs
index 6e4e822..864d8ed 100644
--- a/XMonad/Actions/CycleWS.hs
+++ b/XMonad/Actions/CycleWS.hs
@@ -10,7 +10,7 @@
-- Portability : unportable
--
-- Provides bindings to cycle forward or backward through the list
--- of workspaces, and to move windows there.
+-- of workspaces, and to move windows there, and to cycle between the screens.
--
-----------------------------------------------------------------------------
@@ -22,9 +22,11 @@ module XMonad.Actions.CycleWS (
shiftToNext,
shiftToPrev,
toggleWS,
+ nextScreen,
+ prevScreen
) where
-import Data.List ( findIndex )
+import Data.List ( findIndex, sortBy )
import Data.Maybe ( fromMaybe )
import XMonad hiding (workspaces)
@@ -36,16 +38,18 @@ import XMonad.Util.WorkspaceCompare
--
-- > import XMonad.Actions.CycleWS
--
--- > , ((modMask x, xK_Right), nextWS)
--- > , ((modMask x, xK_Left), prevWS)
--- > , ((modMask x .|. shiftMask, xK_Right), shiftToNext)
--- > , ((modMask x .|. shiftMask, xK_Left), shiftToPrev)
+-- > , ((modMask x, xK_Down), nextWS)
+-- > , ((modMask x, xK_Up), prevWS)
+-- > , ((modMask x .|. shiftMask, xK_Down), shiftToNext)
+-- > , ((modMask x .|. shiftMask, xK_Up), shiftToPrev)
+-- > , ((modMask x, xK_Right), nextScreen)
+-- > , ((modMask x, xK_Left), prevScreen)
-- > , ((modMask x, xK_t), toggleWS)
--
-- If you want to follow the moved window, you can use both actions:
--
--- > , ((modMask x .|. shiftMask, xK_Right), shiftToNext >> nextWS)
--- > , ((modMask x .|. shiftMask, xK_Left), shiftToPrev >> prevWS)
+-- > , ((modMask x .|. shiftMask, xK_Down), shiftToNext >> nextWS)
+-- > , ((modMask x .|. shiftMask, xK_Up), shiftToPrev >> prevWS)
--
-- For detailed instructions on editing your key bindings, see
-- "XMonad.Doc.Extending#Editing_key_bindings".
@@ -88,3 +92,24 @@ wsBy d = do
findWsIndex :: WindowSpace -> [WindowSpace] -> Maybe Int
findWsIndex ws wss = findIndex ((== tag ws) . tag) wss
+
+-- | View next screen
+nextScreen :: X ()
+nextScreen = switchScreen 1
+
+-- | View prev screen
+prevScreen :: X ()
+prevScreen = switchScreen (-1)
+
+switchScreen :: Int -> X ()
+switchScreen d = do s <- screenBy d
+ mws <- screenWorkspace s
+ case mws of
+ Nothing -> return ()
+ Just ws -> windows (view ws)
+
+screenBy :: Int -> X (ScreenId)
+screenBy d = do ws <- gets windowset
+ --let ss = sortBy screen (screens ws)
+ let now = screen (current ws)
+ return $ (now + fromIntegral d) `mod` fromIntegral (length (screens ws))