DynamicLog support for IndependentScreens

This commit is contained in:
Daniel Wagner 2010-01-04 05:42:51 +00:00
parent 0909472d54
commit e44bab10e7

View File

@ -20,7 +20,9 @@ module XMonad.Layout.IndependentScreens (
workspaces', workspaces',
withScreens, onCurrentScreen, withScreens, onCurrentScreen,
countScreens, countScreens,
marshall, unmarshall marshallPP,
marshall, unmarshall, unmarshallS, unmarshallW,
marshallWindowSpace, unmarshallWindowSpace
) where ) where
-- for the screen stuff -- for the screen stuff
@ -29,7 +31,8 @@ import Control.Monad
import Data.List import Data.List
import Graphics.X11.Xinerama import Graphics.X11.Xinerama
import XMonad import XMonad
import XMonad.StackSet hiding (workspaces) import XMonad.StackSet hiding (filter, workspaces)
import XMonad.Hooks.DynamicLog
-- $usage -- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@: -- 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 :: ScreenId -> VirtualWorkspace -> PhysicalWorkspace
marshall (S sc) vws = show sc ++ '_':vws marshall (S sc) vws = show sc ++ '_':vws
unmarshall :: PhysicalWorkspace -> (ScreenId, VirtualWorkspace) unmarshall :: PhysicalWorkspace -> (ScreenId, VirtualWorkspace)
unmarshall = ((S . read) *** drop 1) . break (=='_') unmarshallS :: PhysicalWorkspace -> ScreenId
unmarshallW :: PhysicalWorkspace -> VirtualWorkspace
-- ^ You shouldn't need to use @marshall@ and @unmarshall@ very much. -- ^ You shouldn't need to use @marshall@ or the various @unmarshall@ functions
-- They simply convert between the physical and virtual worlds. For -- very much. They simply convert between the physical and virtual worlds.
-- example, you might want to use them as part of a status bar -- For example, you might want to use them as part of a status bar
-- configuration. The function @snd . unmarshall@ would discard the -- configuration. The function @unmarshallW@ would discard the screen
-- screen information from an otherwise unsightly workspace name. -- information from an otherwise unsightly workspace name.
unmarshall = ((S . read) *** drop 1) . break (=='_')
unmarshallS = fst . unmarshall
unmarshallW = snd . unmarshall
workspaces' :: XConfig l -> [VirtualWorkspace] workspaces' :: XConfig l -> [VirtualWorkspace]
workspaces' = nub . map (snd . unmarshall) . workspaces 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 :: (MonadIO m, Integral i) => m i
countScreens = liftM genericLength . liftIO $ openDisplay "" >>= getScreenInfo 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) }