From 2b489e383285c5e79c270a0e86d3d596fba8b181 Mon Sep 17 00:00:00 2001 From: daniel Date: Sun, 22 Feb 2009 00:15:25 +0100 Subject: add type information for IndependentScreens darcs-hash:20090221231525-c98ca-6b2d3ecc5ff2de314911dfe37c85a67b5723bea4.gz --- XMonad/Layout/IndependentScreens.hs | 50 +++++++++++++++++++++---------------- 1 file changed, 29 insertions(+), 21 deletions(-) (limited to 'XMonad/Layout/IndependentScreens.hs') diff --git a/XMonad/Layout/IndependentScreens.hs b/XMonad/Layout/IndependentScreens.hs index d5a1f86..abbe510 100644 --- a/XMonad/Layout/IndependentScreens.hs +++ b/XMonad/Layout/IndependentScreens.hs @@ -1,23 +1,31 @@ ------------------------------------------------------------------------------ --- | --- Module : XMonad.Layout.IndependentScreens --- Copyright : (c) 2009 Daniel Wagner --- License : BSD3 --- --- Maintainer : --- 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 -marshall (S sc) ws = show sc ++ '_':ws -unmarshall = ((S . read) *** drop 1) . break (=='_') -workspaces' = nub . map (snd . unmarshall) . workspaces -withScreens n workspaces = [marshall sc ws | ws <- workspaces, sc <- [0..n-1]] -onScreen f workspace = screen . current >>= f . flip marshall workspace -countScreens = fmap genericLength $ openDisplay "" >>= getScreenInfo +-- for the screen stuff +import Control.Arrow hiding ((|||)) +import Control.Monad +import Control.Monad.Instances +import Data.List +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 -- cgit v1.2.3