aboutsummaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
-rw-r--r--DynamicLog.hs14
-rw-r--r--DynamicWorkspaces.hs7
2 files changed, 10 insertions, 11 deletions
diff --git a/DynamicLog.hs b/DynamicLog.hs
index 7447f43..4bcfec8 100644
--- a/DynamicLog.hs
+++ b/DynamicLog.hs
@@ -65,9 +65,9 @@ pprWindowSet s = concatMap fmt $ sortBy (comparing S.tag)
where this = S.tag (S.workspace (S.current s))
visibles = map (S.tag . S.workspace) (S.visible s)
- fmt w | S.tag w == this = "[" ++ pprTag w ++ "]"
- | S.tag w `elem` visibles = "<" ++ pprTag w ++ ">"
- | isJust (S.stack w) = " " ++ pprTag w ++ " "
+ fmt w | S.tag w == this = "[" ++ S.tag w ++ "]"
+ | S.tag w `elem` visibles = "<" ++ S.tag w ++ ">"
+ | isJust (S.stack w) = " " ++ S.tag w ++ " "
| otherwise = ""
-- |
@@ -83,11 +83,7 @@ dynamicLogXinerama = withWindowSet $ io . putStrLn . pprWindowSetXinerama
pprWindowSetXinerama :: WindowSet -> String
pprWindowSetXinerama ws = "[" ++ unwords onscreen ++ "] " ++ unwords offscreen
- where onscreen = map (pprTag . S.workspace)
+ where onscreen = map (S.tag . S.workspace)
. sortBy (comparing S.screen) $ S.current ws : S.visible ws
- offscreen = map pprTag . filter (isJust . S.stack)
+ offscreen = map S.tag . filter (isJust . S.stack)
. sortBy (comparing S.tag) $ S.hidden ws
-
--- util functions
-pprTag :: Integral i => S.Workspace i a -> String
-pprTag = show . (+(1::Int)) . fromIntegral . S.tag
diff --git a/DynamicWorkspaces.hs b/DynamicWorkspaces.hs
index ab8dd8f..8decab1 100644
--- a/DynamicWorkspaces.hs
+++ b/DynamicWorkspaces.hs
@@ -21,7 +21,7 @@ module XMonadContrib.DynamicWorkspaces (
import Control.Monad.State ( gets, modify )
-import XMonad ( X, XState(..), Layout, trace )
+import XMonad ( X, XState(..), Layout, WorkspaceId, trace )
import Operations ( windows, view )
import StackSet ( tagMember, StackSet(..), Screen(..), Workspace(..),
integrate, differentiate )
@@ -36,9 +36,12 @@ import Graphics.X11.Xlib ( Window )
-- > , ((modMask .|. shiftMask, xK_Up), addWorkspace defaultLayouts)
-- > , ((modMask .|. shiftMask, xK_Down), removeWorkspace)
+allPossibleTags :: [WorkspaceId]
+allPossibleTags = map (:"") ['0'..]
+
addWorkspace :: [Layout Window] -> X ()
addWorkspace (l:ls) = do s <- gets windowset
- let newtag:_ = filter (not . (`tagMember` s)) [0..]
+ let newtag:_ = filter (not . (`tagMember` s)) allPossibleTags
modify $ \st -> st { layouts = insert newtag (l,ls) $ layouts st }
windows (addWorkspace' newtag)
addWorkspace [] = trace "bad layouts in XMonadContrib.DynamicWorkspaces.addWorkspace\n"