aboutsummaryrefslogtreecommitdiffstats
path: root/CycleWS.hs
diff options
context:
space:
mode:
authormail <mail@joachim-breitner.de>2007-10-07 12:39:33 +0200
committermail <mail@joachim-breitner.de>2007-10-07 12:39:33 +0200
commit6a386110616c2156847ae575f787e494de1dff8a (patch)
tree08b9aa42921389cc01a006c428efc3f05e31ab75 /CycleWS.hs
parent802450ed9fa6c5fd2e0a27f398cc01dcd5a1c864 (diff)
downloadXMonadContrib-6a386110616c2156847ae575f787e494de1dff8a.tar.gz
XMonadContrib-6a386110616c2156847ae575f787e494de1dff8a.tar.xz
XMonadContrib-6a386110616c2156847ae575f787e494de1dff8a.zip
Move my NextWorkspace functionality into CycleWS
Hi, This patch merges the additional functionality of my NextWorkspace into CycleWS, using a compatible interface for what was there before. Greetings, Joachim darcs-hash:20071007103933-c9905-c5cfc7d03abbeddf78631deee384583d15015801.gz
Diffstat (limited to 'CycleWS.hs')
-rw-r--r--CycleWS.hs114
1 files changed, 81 insertions, 33 deletions
diff --git a/CycleWS.hs b/CycleWS.hs
index 3a95ab4..1b6b10f 100644
--- a/CycleWS.hs
+++ b/CycleWS.hs
@@ -1,51 +1,99 @@
-----------------------------------------------------------------------------
-- |
-- Module : XMonadContrib.CycleWS
--- Copyright : (C) 2007 Andrea Rossato
--- License : BSD3
---
--- Maintainer : andrea.rossato@unibz.it
+-- Copyright : (c) Joachim Breitner <mail@joachim-breitner.de>
+-- License : BSD3-style (see LICENSE)
+--
+-- Maintainer : Joachim Breitner <mail@joachim-breitner.de>
-- Stability : unstable
-- Portability : unportable
--
--- A module to cycle between Workspaces
+-- Provides bindings to cycle forward or backward through the list
+-- of workspaces, and to move windows there.
--
-----------------------------------------------------------------------------
module XMonadContrib.CycleWS (
- -- * Usage
- -- $usage
- nextWS
- , prevWS
- ) where
+ -- * Usage
+ -- $usage
+ nextWS,
+ prevWS,
+ shiftToNext,
+ shiftToPrev,
+ ) where
+
+import Control.Monad.State ( gets )
+import Data.List ( sortBy, findIndex )
+import Data.Maybe ( fromMaybe )
+import Data.Ord ( comparing )
import XMonad
+import StackSet hiding (filter, findIndex)
import Operations
-import qualified StackSet as W
-import {-# SOURCE #-} Config (workspaces)
-import Data.List
+import {-# SOURCE #-} qualified Config (workspaces)
-- $usage
--- Import this module in Config.hs:
+-- You can use this module with the following in your Config.hs file:
+--
+-- > import XMonadContrib.NextWorkspace
+--
+-- > , ((modMask, xK_Right), nextWS)
+-- > , ((modMask, xK_Left), prevWWS)
+-- > , ((modMask .|. shiftMask, xK_Right), shiftToNext)
+-- > , ((modMask .|. shiftMask, xK_Left), shiftToPrev)
--
--- > import XMonadContrib.CycleWS
+-- If you want to follow the moved window, you can use both actions:
--
--- And add, in you key bindings:
+-- > , ((modMask .|. shiftMask, xK_Right), shiftToNext >> nextWS)
+-- > , ((modMask .|. shiftMask, xK_Left), shiftToPrev >> prevWS)
--
--- > , ((modMask , xK_comma ), prevWS )
--- > , ((modMask , xK_period), nextWS )
-
-nextWS, prevWS :: X ()
-nextWS = withWindowSet $ \s -> windows $ W.view (workspaces !! (setWS s N))
-prevWS = withWindowSet $ \s -> windows $ W.view (workspaces !! (setWS s P))
-
-data Dir = P | N deriving Eq
-setWS :: WindowSet -> Dir -> Int
-setWS s d
- | d == N && cur == (lw - 1) = 0
- | d == N = cur + 1
- | d == P && cur == 0 = lw - 1
- | otherwise = cur - 1
- where
- cur = maybe 0 id $ elemIndex (W.tag (W.workspace ((W.current s)))) workspaces
- lw = length workspaces
+
+-- %import XMonadContrib.NextWorkspace
+-- %keybind , ((modMask, xK_Right), nextWS)
+-- %keybind , ((modMask, xK_Left), prevWWS)
+-- %keybind , ((modMask .|. shiftMask, xK_Right), shiftToNext)
+-- %keybind , ((modMask .|. shiftMask, xK_Left), shiftToPrev)
+
+
+-- ---------------------
+-- |
+-- Switch to next workspace
+nextWS :: X()
+nextWS = switchWorkspace (1)
+
+-- ---------------------
+-- |
+-- Switch to previous workspace
+prevWS :: X()
+prevWS = switchWorkspace (-1)
+
+-- |
+-- Move focused window to next workspace
+shiftToNext :: X()
+shiftToNext = shiftBy (1)
+
+-- |
+-- Move focused window to previous workspace
+shiftToPrev :: X ()
+shiftToPrev = shiftBy (-1)
+
+switchWorkspace :: Int -> X ()
+switchWorkspace d = wsBy d >>= windows . greedyView
+
+shiftBy :: Int -> X ()
+shiftBy d = wsBy d >>= windows . shift
+
+wsBy :: Int -> X (WorkspaceId)
+wsBy d = do
+ ws <- gets windowset
+ let orderedWs = sortBy (comparing wsIndex) (workspaces ws)
+ let now = fromMaybe 0 $ findWsIndex (workspace (current ws)) orderedWs
+ let next = orderedWs !! ((now + d) `mod` length orderedWs)
+ return $ tag next
+
+
+wsIndex :: WindowSpace -> Maybe Int
+wsIndex ws = findIndex (==(tag ws)) Config.workspaces
+
+findWsIndex :: WindowSpace -> [WindowSpace] -> Maybe Int
+findWsIndex ws wss = findIndex ((== tag ws) . tag) wss