From 5959f0388196a67aee5862c45f2265f8607cc15b Mon Sep 17 00:00:00 2001 From: Wirt Wolff Date: Mon, 17 Aug 2009 23:55:49 +0200 Subject: A.CycleWS: add toggleOrView fns, fix doc, prevent head exception Ignore-this: 35acc32e696e665aca900721d309d1d3 darcs-hash:20090817215549-18562-ebaf740cc0846b99c78b8d62fa616d2864feadfa.gz --- XMonad/Actions/CycleWS.hs | 51 ++++++++++++++++++++++++++++++++++++++++++++--- 1 file changed, 48 insertions(+), 3 deletions(-) (limited to 'XMonad/Actions/CycleWS.hs') diff --git a/XMonad/Actions/CycleWS.hs b/XMonad/Actions/CycleWS.hs index 5e267ca..6cce784 100644 --- a/XMonad/Actions/CycleWS.hs +++ b/XMonad/Actions/CycleWS.hs @@ -42,7 +42,11 @@ module XMonad.Actions.CycleWS ( , prevWS , shiftToNext , shiftToPrev + + -- * Toggling the previous workspace + -- $toggling , toggleWS + , toggleOrView -- * Moving between screens (xinerama) @@ -65,9 +69,12 @@ module XMonad.Actions.CycleWS ( -- * The mother-combinator , findWorkspace + , toggleOrDoSkip + , skipTags ) where +import Control.Monad ( unless ) import Data.List ( findIndex ) import Data.Maybe ( isNothing, isJust ) @@ -102,7 +109,7 @@ import XMonad.Util.WorkspaceCompare -- -- > , ((modMask x , xK_f), moveTo Next EmptyWS) -- find a free workspace -- > , ((modMask x .|. controlMask, xK_Right), -- a crazy keybinding! --- > do t <- findWorkspace getXineramaWsCompare Next NonEmptyWS 2 +-- > do t <- findWorkspace getSortByXineramaRule Next NonEmptyWS 2 -- > windows . view $ t ) -- -- For detailed instructions on editing your key bindings, see @@ -135,9 +142,47 @@ shiftToNext = shiftBy 1 shiftToPrev :: X () shiftToPrev = shiftBy (-1) +-- $toggling + -- | Toggle to the workspace displayed previously. toggleWS :: X () -toggleWS = windows $ view =<< tag . head . hidden +toggleWS = do + hs <- gets (hidden . windowset) + unless (null hs) (windows . view . tag $ head hs) + +-- | 'XMonad.StackSet.greedyView' a workspace, or if already there, view +-- the previously displayed workspace ala weechat. Change @greedyView@ to +-- @toggleOrView@ in your workspace bindings as in the 'XMonad.StackSet.view' +-- faq at . +-- For more flexibility see 'toggleOrDoSkip'. +toggleOrView :: WorkspaceId -> X () +toggleOrView = toggleOrDoSkip [] greedyView + +-- | Allows ignoring listed workspace tags (such as scratchpad's \"NSP\") while +-- finding the previously displayed workspace, or choice of different actions, +-- like view, shift, etc. For example: +-- +-- > import qualified XMonad.StackSet as W +-- > import XMonad.Actions.CycleWS +-- > +-- > -- toggleOrView for people who prefer view to greedyView +-- > toggleOrView' = toggleOrDoSkip [] W.view +-- > +-- > -- toggleOrView ignoring scratchpad and named scratchpad workspace +-- > toggleOrViewNoSP = toggleOrDoSkip ["NSP"] W.greedyView +toggleOrDoSkip :: [WorkspaceId] -> (WorkspaceId -> WindowSet -> WindowSet) + -> WorkspaceId -> X () +toggleOrDoSkip skips f toWS = do + ws <- gets windowset + let hs' = hidden ws `skipTags` skips + if toWS == (tag . workspace $ current ws) + then unless (null hs') (windows . f . tag $ head hs') + else windows (f toWS) + +-- | List difference ('\\') for workspaces and tags. Removes workspaces +-- matching listed tags from the given workspace list. +skipTags :: (Eq i) => [Workspace i l a] -> [i] -> [Workspace i l a] +skipTags wss ids = filter ((`notElem` ids) . tag) wss switchWorkspace :: Int -> X () switchWorkspace d = wsBy d >>= windows . greedyView @@ -229,7 +274,7 @@ findWorkspaceGen sortX wsPredX d = do let cur = workspace (current ws) sorted = sort (workspaces ws) pivoted = let (a,b) = span ((/= (tag cur)) . tag) sorted in b ++ a - ws' = filter wsPred $ pivoted + ws' = filter wsPred pivoted mCurIx = findWsIndex cur ws' d' = if d > 0 then d - 1 else d next = if null ws' -- cgit v1.2.3