add type information for IndependentScreens

This commit is contained in:
daniel 2009-02-21 23:15:25 +00:00
parent efc2f1160f
commit cf07f9caca

View File

@ -1,23 +1,31 @@
-----------------------------------------------------------------------------
-- |
-- Module : XMonad.Layout.IndependentScreens
-- Copyright : (c) 2009 Daniel Wagner
-- License : BSD3
--
-- Maintainer : <daniel@wagner-home.com>
-- Stability : unstable
-- Portability : unportable
--
-- Utility functions for simulating independent sets of workspaces on
-- each screen (like dwm's workspace model), using internal tags to
-- distinguish workspaces associated with each screen.
-----------------------------------------------------------------------------
module IndependentScreens where module IndependentScreens where
marshall (S sc) ws = show sc ++ '_':ws -- for the screen stuff
unmarshall = ((S . read) *** drop 1) . break (=='_') import Control.Arrow hiding ((|||))
workspaces' = nub . map (snd . unmarshall) . workspaces import Control.Monad
withScreens n workspaces = [marshall sc ws | ws <- workspaces, sc <- [0..n-1]] import Control.Monad.Instances
onScreen f workspace = screen . current >>= f . flip marshall workspace import Data.List
countScreens = fmap genericLength $ openDisplay "" >>= getScreenInfo import Graphics.X11.Xinerama
import XMonad
import XMonad.StackSet hiding (workspaces)
type VirtualWorkspace = String
type PhysicalWorkspace = String
marshall :: ScreenId -> VirtualWorkspace -> PhysicalWorkspace
marshall (S sc) vws = show sc ++ '_':vws
unmarshall :: PhysicalWorkspace -> (ScreenId, VirtualWorkspace)
unmarshall = ((S . read) *** drop 1) . break (=='_')
workspaces' :: XConfig l -> [VirtualWorkspace]
workspaces' = nub . map (snd . unmarshall) . workspaces
withScreens :: ScreenId -> [VirtualWorkspace] -> [PhysicalWorkspace]
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
countScreens :: (MonadIO m, Integral i) => m i
countScreens = liftM genericLength . liftIO $ openDisplay "" >>= getScreenInfo