aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad
diff options
context:
space:
mode:
authordaniel <daniel@wagner-home.com>2010-02-15 01:07:31 +0100
committerdaniel <daniel@wagner-home.com>2010-02-15 01:07:31 +0100
commit55bde227212ab6b932b620af7b67a862324184a9 (patch)
tree7ec895e6a6d47f4a13b202db8bed3e2129c034d8 /XMonad
parent9bab6f6223ca749457f9bdd9fbf94b3c45625929 (diff)
downloadXMonadContrib-55bde227212ab6b932b620af7b67a862324184a9.tar.gz
XMonadContrib-55bde227212ab6b932b620af7b67a862324184a9.tar.xz
XMonadContrib-55bde227212ab6b932b620af7b67a862324184a9.zip
documentation for marshallPP
Ignore-this: efa38829b40dc1586f5f18c4bab21f7d darcs-hash:20100215000731-c98ca-8608df63586b6699bca3c52368e76c161b6b01b2.gz
Diffstat (limited to 'XMonad')
-rw-r--r--XMonad/Layout/IndependentScreens.hs35
1 files changed, 24 insertions, 11 deletions
diff --git a/XMonad/Layout/IndependentScreens.hs b/XMonad/Layout/IndependentScreens.hs
index 4e8f095..0b5b996 100644
--- a/XMonad/Layout/IndependentScreens.hs
+++ b/XMonad/Layout/IndependentScreens.hs
@@ -19,8 +19,10 @@ module XMonad.Layout.IndependentScreens (
VirtualWorkspace, PhysicalWorkspace,
workspaces',
withScreens, onCurrentScreen,
- countScreens,
marshallPP,
+ countScreens,
+ -- * Converting between virtual and physical workspaces
+ -- $converting
marshall, unmarshall, unmarshallS, unmarshallW,
marshallWindowSpace, unmarshallWindowSpace
) where
@@ -69,6 +71,14 @@ import XMonad.Hooks.DynamicLog
type VirtualWorkspace = WorkspaceId
type PhysicalWorkspace = WorkspaceId
+-- $converting
+-- You shouldn't need to use the functions below very much. They are used
+-- internally. However, in some cases, they may be useful, and so are exported
+-- just in case. In general, the \"marshall\" functions convert the convenient
+-- form (like \"web\") you would like to use in your configuration file to the
+-- inconvenient form (like \"2_web\") that xmonad uses internally. Similarly,
+-- the \"unmarshall\" functions convert in the other direction.
+
marshall :: ScreenId -> VirtualWorkspace -> PhysicalWorkspace
marshall (S sc) vws = show sc ++ '_':vws
@@ -76,12 +86,6 @@ unmarshall :: PhysicalWorkspace -> (ScreenId, VirtualWorkspace)
unmarshallS :: PhysicalWorkspace -> ScreenId
unmarshallW :: PhysicalWorkspace -> VirtualWorkspace
--- ^ 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
@@ -110,10 +114,17 @@ 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
+-- | This turns a naive pretty-printer into one that is aware of the
+-- independent screens. That is, you can write your pretty printer to behave
+-- the way you want on virtual workspaces; this function will convert that
+-- pretty-printer into one that first filters out physical workspaces on other
+-- screens, then converts all the physical workspaces on this screen to their
+-- virtual names.
+--
+-- For example, if you have handles @hLeft@ and @hRight@ for bars on the left and right screens, respectively, and @pp@ is a pretty-printer function that takes a handle, you could write
+--
+-- > logHook = let log screen handle = dynamicLogWithPP . marshallPP screen . pp $ handle
+-- > in log 0 hLeft >> log 1 hRight
marshallPP :: ScreenId -> PP -> PP
marshallPP s pp = pp {
ppCurrent = ppCurrent pp . snd . unmarshall,
@@ -130,7 +141,9 @@ marshallSort s vSort = pScreens . vSort . vScreens where
vScreens = map unmarshallWindowSpace . filter onScreen
pScreens = map (marshallWindowSpace s)
+-- | Convert the tag of the 'WindowSpace' from a 'VirtualWorkspace' to a 'PhysicalWorkspace'.
marshallWindowSpace :: ScreenId -> WindowSpace -> WindowSpace
+-- | Convert the tag of the 'WindowSpace' from a 'PhysicalWorkspace' to a 'VirtualWorkspace'.
unmarshallWindowSpace :: WindowSpace -> WindowSpace
marshallWindowSpace s ws = ws { tag = marshall s (tag ws) }