aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Actions/DynamicWorkspaces.hs
diff options
context:
space:
mode:
authorDavid Roundy <droundy@darcs.net>2008-02-29 23:30:47 +0100
committerDavid Roundy <droundy@darcs.net>2008-02-29 23:30:47 +0100
commit363314e16a5a39f21e34b0ff4ae0532f444be978 (patch)
tree7e4bd1a3b5782b0591f3964a768e412bced214c4 /XMonad/Actions/DynamicWorkspaces.hs
parent0876286d2ccc4b0ea99cff02e449d5b9ae320ad1 (diff)
downloadXMonadContrib-363314e16a5a39f21e34b0ff4ae0532f444be978.tar.gz
XMonadContrib-363314e16a5a39f21e34b0ff4ae0532f444be978.tar.xz
XMonadContrib-363314e16a5a39f21e34b0ff4ae0532f444be978.zip
in Prompt.Workspace sort by official workspace order.
darcs-hash:20080229223047-72aca-f66c6583d8be77207a3f083fe26be40f1f02e4b5.gz
Diffstat (limited to 'XMonad/Actions/DynamicWorkspaces.hs')
-rw-r--r--XMonad/Actions/DynamicWorkspaces.hs12
1 files changed, 7 insertions, 5 deletions
diff --git a/XMonad/Actions/DynamicWorkspaces.hs b/XMonad/Actions/DynamicWorkspaces.hs
index 17506aa..bf28091 100644
--- a/XMonad/Actions/DynamicWorkspaces.hs
+++ b/XMonad/Actions/DynamicWorkspaces.hs
@@ -22,12 +22,11 @@ module XMonad.Actions.DynamicWorkspaces (
toNthWorkspace, withNthWorkspace
) where
-import Data.List ( sort )
-
import XMonad hiding (workspaces)
import XMonad.StackSet hiding (filter, modify, delete)
import XMonad.Prompt.Workspace
import XMonad.Prompt ( XPConfig, mkXPrompt, XPrompt(..) )
+import XMonad.Util.WorkspaceCompare ( getSortByIndex )
-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@ file:
@@ -63,7 +62,8 @@ mkCompl l s = return $ filter (\x -> take (length s) x == s) l
withWorkspace :: XPConfig -> (String -> X ()) -> X ()
withWorkspace c job = do ws <- gets (workspaces . windowset)
- let ts = sort $ map tag ws
+ sort <- getSortByIndex
+ let ts = map tag $ sort ws
job' t | t `elem` ts = job t
| otherwise = addHiddenWorkspace t >> job t
mkXPrompt (Wor "") c (mkCompl ts) job'
@@ -76,13 +76,15 @@ renameWorkspace conf = workspacePrompt conf $ \w ->
in sets $ removeWorkspace' w s
toNthWorkspace :: (String -> X ()) -> Int -> X ()
-toNthWorkspace job wnum = do ws <- gets (sort . map tag . workspaces . windowset)
+toNthWorkspace job wnum = do sort <- getSortByIndex
+ ws <- gets (map tag . sort . workspaces . windowset)
case drop wnum ws of
(w:_) -> job w
[] -> return ()
withNthWorkspace :: (String -> WindowSet -> WindowSet) -> Int -> X ()
-withNthWorkspace job wnum = do ws <- gets (sort . map tag . workspaces . windowset)
+withNthWorkspace job wnum = do sort <- getSortByIndex
+ ws <- gets (map tag . sort . workspaces . windowset)
case drop wnum ws of
(w:_) -> windows $ job w
[] -> return ()