From 6406dd5f886f0c81ab7459c6c958ecb2e3f8c5e7 Mon Sep 17 00:00:00 2001 From: daniel Date: Sun, 22 Feb 2009 00:59:59 +0100 Subject: documentation for IndependentScreens darcs-hash:20090221235959-c98ca-aec12eaa56be89487168a37d1e2f3199f0359a54.gz --- XMonad/Layout/IndependentScreens.hs | 70 +++++++++++++++++++++++++++++++++---- 1 file changed, 64 insertions(+), 6 deletions(-) (limited to 'XMonad/Layout/IndependentScreens.hs') diff --git a/XMonad/Layout/IndependentScreens.hs b/XMonad/Layout/IndependentScreens.hs index bdd53f8..3ad4cbd 100644 --- a/XMonad/Layout/IndependentScreens.hs +++ b/XMonad/Layout/IndependentScreens.hs @@ -13,7 +13,15 @@ -- distinguish workspaces associated with each screen. ----------------------------------------------------------------------------- -module XMonad.Layout.IndependentScreens where +module XMonad.Layout.IndependentScreens ( + -- * Usage + -- $usage + VirtualWorkspace, PhysicalWorkspace, + workspaces', + withScreens, onCurrentScreen, + countScreens, + marshall, unmarshall +) where -- for the screen stuff import Control.Arrow hiding ((|||)) @@ -24,8 +32,40 @@ import Graphics.X11.Xinerama import XMonad import XMonad.StackSet hiding (workspaces) -type VirtualWorkspace = String -type PhysicalWorkspace = String +-- $usage +-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@: +-- +-- > import XMonad.Layout.IndependentScreens +-- +-- You can define your workspaces by calling @withScreens@: +-- +-- > myConfig = defaultConfig { workspaces = withScreens 2 ["web", "email", "irc"] } +-- +-- This will create \"physical\" workspaces with distinct internal names for +-- each (screen, virtual workspace) pair. +-- +-- Then edit any keybindings that use the list of workspaces or refer +-- to specific workspace names. In the default configuration, only +-- the keybindings for changing workspace do this: +-- +-- > [((m .|. modMask, k), windows $ f i) +-- > | (i, k) <- zip (XMonad.workspaces conf) [xK_1 .. xK_9] +-- > , (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)]] +-- +-- This should change to +-- +-- > [((m .|. modMask, k), windows $ onCurrentScreen f i) +-- > | (i, k) <- zip (workspaces' conf) [xK_1 .. xK_9] +-- > , (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)]] +-- +-- In particular, the analogue of @XMonad.workspaces@ is +-- @workspaces'@, and you can use @onCurrentScreen@ to convert functions +-- of virtual workspaces to functions of physical workspaces, which work +-- by marshalling the virtual workspace name and the currently focused +-- screen into a physical workspace name. + +type VirtualWorkspace = WorkspaceId +type PhysicalWorkspace = WorkspaceId marshall :: ScreenId -> VirtualWorkspace -> PhysicalWorkspace marshall (S sc) vws = show sc ++ '_':vws @@ -33,14 +73,32 @@ marshall (S sc) vws = show sc ++ '_':vws unmarshall :: PhysicalWorkspace -> (ScreenId, VirtualWorkspace) unmarshall = ((S . read) *** drop 1) . break (=='_') +-- ^ 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. + workspaces' :: XConfig l -> [VirtualWorkspace] workspaces' = nub . map (snd . unmarshall) . workspaces -withScreens :: ScreenId -> [VirtualWorkspace] -> [PhysicalWorkspace] +withScreens :: ScreenId -- ^ The number of screens to make workspaces for + -> [VirtualWorkspace] -- ^ The desired virtual workspace names + -> [PhysicalWorkspace] -- ^ A list of all internal physical workspace names withScreens n vws = [marshall sc pws | pws <- vws, sc <- [0..n-1]] -onScreen :: (VirtualWorkspace -> WindowSet -> a) -> (PhysicalWorkspace -> WindowSet -> a) -onScreen f vws = screen . current >>= f . flip marshall vws +onCurrentScreen :: (VirtualWorkspace -> WindowSet -> a) -> (PhysicalWorkspace -> WindowSet -> a) +onCurrentScreen f vws = screen . current >>= f . flip marshall vws +-- | In case you don't know statically how many screens there will be, you can call this in main before starting xmonad. For example, part of my config reads +-- +-- > main = do +-- > nScreens <- countScreens +-- > xmonad $ defaultConfig { +-- > ... +-- > workspaces = withScreens nScreens (workspaces defaultConfig), +-- > ... +-- > } +-- countScreens :: (MonadIO m, Integral i) => m i countScreens = liftM genericLength . liftIO $ openDisplay "" >>= getScreenInfo -- cgit v1.2.3