From 9bab6f6223ca749457f9bdd9fbf94b3c45625929 Mon Sep 17 00:00:00 2001 From: Daniel Wagner Date: Mon, 4 Jan 2010 06:42:51 +0100 Subject: DynamicLog support for IndependentScreens Ignore-this: 16fe32f1d66abf4a79f8670131663a60 darcs-hash:20100104054251-76d51-30115536bb28d19d05b4c9dd9d43108b2d531676.gz --- XMonad/Layout/IndependentScreens.hs | 52 ++++++++++++++++++++++++++++++------- 1 file changed, 43 insertions(+), 9 deletions(-) (limited to 'XMonad') diff --git a/XMonad/Layout/IndependentScreens.hs b/XMonad/Layout/IndependentScreens.hs index b1ec055..4e8f095 100644 --- a/XMonad/Layout/IndependentScreens.hs +++ b/XMonad/Layout/IndependentScreens.hs @@ -20,7 +20,9 @@ module XMonad.Layout.IndependentScreens ( workspaces', withScreens, onCurrentScreen, countScreens, - marshall, unmarshall + marshallPP, + marshall, unmarshall, unmarshallS, unmarshallW, + marshallWindowSpace, unmarshallWindowSpace ) where -- for the screen stuff @@ -29,7 +31,8 @@ import Control.Monad import Data.List import Graphics.X11.Xinerama import XMonad -import XMonad.StackSet hiding (workspaces) +import XMonad.StackSet hiding (filter, workspaces) +import XMonad.Hooks.DynamicLog -- $usage -- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@: @@ -69,14 +72,19 @@ type PhysicalWorkspace = WorkspaceId marshall :: ScreenId -> VirtualWorkspace -> PhysicalWorkspace marshall (S sc) vws = show sc ++ '_':vws -unmarshall :: PhysicalWorkspace -> (ScreenId, VirtualWorkspace) -unmarshall = ((S . read) *** drop 1) . break (=='_') +unmarshall :: PhysicalWorkspace -> (ScreenId, VirtualWorkspace) +unmarshallS :: PhysicalWorkspace -> ScreenId +unmarshallW :: PhysicalWorkspace -> VirtualWorkspace --- ^ You shouldn't need to use @marshall@ and @unmarshall@ very much. --- They simply convert between the physical and virtual worlds. For --- example, you might want to use them as part of a status bar --- configuration. The function @snd . unmarshall@ would discard the --- screen information from an otherwise unsightly workspace name. +-- ^ You shouldn't need to use @marshall@ or the various @unmarshall@ functions +-- very much. They simply convert between the physical and virtual worlds. +-- For example, you might want to use them as part of a status bar +-- configuration. The function @unmarshallW@ would discard the screen +-- information from an otherwise unsightly workspace name. + +unmarshall = ((S . read) *** drop 1) . break (=='_') +unmarshallS = fst . unmarshall +unmarshallW = snd . unmarshall workspaces' :: XConfig l -> [VirtualWorkspace] workspaces' = nub . map (snd . unmarshall) . workspaces @@ -101,3 +109,29 @@ onCurrentScreen f vws = screen . current >>= f . flip marshall vws -- countScreens :: (MonadIO m, Integral i) => m i countScreens = liftM genericLength . liftIO $ openDisplay "" >>= getScreenInfo + +-- TODO: documentation from here down +-- TODO: note somewhere that "marshall" functions go from convenient +-- to inconvenient, and "unmarshall" functions go from +-- inconvenient to convenient +marshallPP :: ScreenId -> PP -> PP +marshallPP s pp = pp { + ppCurrent = ppCurrent pp . snd . unmarshall, + ppVisible = ppVisible pp . snd . unmarshall, + ppHidden = ppHidden pp . snd . unmarshall, + ppHiddenNoWindows = ppHiddenNoWindows pp . snd . unmarshall, + ppUrgent = ppUrgent pp . snd . unmarshall, + ppSort = fmap (marshallSort s) (ppSort pp) + } + +marshallSort :: ScreenId -> ([WindowSpace] -> [WindowSpace]) -> ([WindowSpace] -> [WindowSpace]) +marshallSort s vSort = pScreens . vSort . vScreens where + onScreen ws = unmarshallS (tag ws) == s + vScreens = map unmarshallWindowSpace . filter onScreen + pScreens = map (marshallWindowSpace s) + +marshallWindowSpace :: ScreenId -> WindowSpace -> WindowSpace +unmarshallWindowSpace :: WindowSpace -> WindowSpace + +marshallWindowSpace s ws = ws { tag = marshall s (tag ws) } +unmarshallWindowSpace ws = ws { tag = unmarshallW (tag ws) } -- cgit v1.2.3