aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Layout/PerWorkspace.hs
diff options
context:
space:
mode:
authorAndrea Rossato <andrea.rossato@unibz.it>2008-02-22 18:59:54 +0100
committerAndrea Rossato <andrea.rossato@unibz.it>2008-02-22 18:59:54 +0100
commit06325c7850954999b2bf5732142bcc860a7c6d99 (patch)
treef5b8b124652b022b345adda646d9b7a2b28c7053 /XMonad/Layout/PerWorkspace.hs
parent704ce0d5650dcf438772d62ae7eef846ae387f11 (diff)
downloadXMonadContrib-06325c7850954999b2bf5732142bcc860a7c6d99.tar.gz
XMonadContrib-06325c7850954999b2bf5732142bcc860a7c6d99.tar.xz
XMonadContrib-06325c7850954999b2bf5732142bcc860a7c6d99.zip
PerWorkspace: reimplemented using runLayout
This way we have a Xinerama safe PerWorkspace and the emptyLayout method for free. darcs-hash:20080222175954-32816-97e4fc1140aa66ead879df019af3f091579251ab.gz
Diffstat (limited to 'XMonad/Layout/PerWorkspace.hs')
-rw-r--r--XMonad/Layout/PerWorkspace.hs100
1 files changed, 27 insertions, 73 deletions
diff --git a/XMonad/Layout/PerWorkspace.hs b/XMonad/Layout/PerWorkspace.hs
index bc51a96..ea3bcd6 100644
--- a/XMonad/Layout/PerWorkspace.hs
+++ b/XMonad/Layout/PerWorkspace.hs
@@ -10,23 +10,14 @@
-- Stability : unstable
-- Portability : unportable
--
--- Configure layouts on a per-workspace basis. NOTE that this module
--- does not (yet) work in conjunction with multiple screens! =(
---
--- Note also that when using PerWorkspace, on initial startup workspaces
--- may not respond to messages properly until a window has been opened.
--- This is due to a limitation inherent in the way PerWorkspace is
--- implemented: it cannot decide which layout to use until actually
--- required to lay out some windows (which does not happen until a window
--- is opened).
+-- Configure layouts on a per-workspace basis.
-----------------------------------------------------------------------------
-module XMonad.Layout.PerWorkspace (
- -- * Usage
- -- $usage
-
- onWorkspace, onWorkspaces
- ) where
+module XMonad.Layout.PerWorkspace
+ ( -- * Usage
+ -- $usage
+ onWorkspace, onWorkspaces
+ ) where
import XMonad
import qualified XMonad.StackSet as W
@@ -52,9 +43,6 @@ import Data.Maybe (fromMaybe)
-- layout D instead of C. You could do that as follows:
--
-- > layoutHook = A ||| B ||| onWorkspace "foo" D C
---
--- NOTE that this module does not (yet) work in conjunction with
--- multiple screens. =(
-- | Specify one layout to use on a particular workspace, and another
-- to use on all others. The second layout can be another call to
@@ -64,7 +52,7 @@ onWorkspace :: (LayoutClass l1 a, LayoutClass l2 a)
-> (l1 a) -- ^ layout to use on the matched workspace
-> (l2 a) -- ^ layout to use everywhere else
-> PerWorkspace l1 l2 a
-onWorkspace wsId l1 l2 = PerWorkspace [wsId] Nothing l1 l2
+onWorkspace wsId l1 l2 = PerWorkspace [wsId] True l1 l2
-- | Specify one layout to use on a particular set of workspaces, and
-- another to use on all other workspaces.
@@ -73,73 +61,39 @@ onWorkspaces :: (LayoutClass l1 a, LayoutClass l2 a)
-> (l1 a) -- ^ layout to use on matched workspaces
-> (l2 a) -- ^ layout to use everywhere else
-> PerWorkspace l1 l2 a
-onWorkspaces wsIds l1 l2 = PerWorkspace wsIds Nothing l1 l2
+onWorkspaces wsIds l1 l2 = PerWorkspace wsIds True l1 l2
-- | Structure for representing a workspace-specific layout along with
--- a layout for all other workspaces. We store the tags of workspaces
--- to be matched, and the two layouts. Since layouts are stored\/tracked
--- per workspace, once we figure out whether we're on a matched workspace,
--- we can cache that information using a (Maybe Bool). This is necessary
--- to be able to correctly implement the 'description' method of
--- LayoutClass, since a call to description is not able to query the
--- WM state to find out which workspace it was called in.
+-- a layout for all other workspaces. We store the tags of workspaces
+-- to be matched, and the two layouts. We save the layout choice in
+-- the Bool, to be used to implement description.
data PerWorkspace l1 l2 a = PerWorkspace [WorkspaceId]
- (Maybe Bool)
+ Bool
(l1 a)
(l2 a)
deriving (Read, Show)
-instance (LayoutClass l1 a, LayoutClass l2 a) => LayoutClass (PerWorkspace l1 l2) a where
-
- -- do layout with l1, then return a modified PerWorkspace caching
- -- the fact that we're in the matched workspace.
- doLayout p@(PerWorkspace _ (Just True) lt _) r s = do
- (wrs, mlt') <- doLayout lt r s
- return (wrs, Just $ mkNewPerWorkspaceT p mlt')
-
- -- do layout with l1, then return a modified PerWorkspace caching
- -- the fact that we're not in the matched workspace.
- doLayout p@(PerWorkspace _ (Just False) _ lf) r s = do
- (wrs, mlf') <- doLayout lf r s
- return (wrs, Just $ mkNewPerWorkspaceF p mlf')
+instance (LayoutClass l1 a, LayoutClass l2 a, Show a) => LayoutClass (PerWorkspace l1 l2) a where
+ runLayout (W.Workspace i p@(PerWorkspace wsIds _ lt lf) ms) r
+ | i `elem` wsIds = do (wrs, mlt') <- runLayout (W.Workspace i lt ms) r
+ return (wrs, Just $ mkNewPerWorkspaceT p mlt')
+ | otherwise = do (wrs, mlt') <- runLayout (W.Workspace i lf ms) r
+ return (wrs, Just $ mkNewPerWorkspaceF p mlt')
- -- figure out which layout to use based on the current workspace.
- doLayout (PerWorkspace wsIds Nothing l1 l2) r s = do
- t <- getCurrentTag
- doLayout (PerWorkspace wsIds (Just $ t `elem` wsIds) l1 l2) r s
+ handleMessage (PerWorkspace wsIds bool lt lf) m
+ | bool = handleMessage lt m >>= maybe (return Nothing) (\nt -> return . Just $ PerWorkspace wsIds bool nt lf)
+ | otherwise = handleMessage lf m >>= maybe (return Nothing) (\nf -> return . Just $ PerWorkspace wsIds bool lt nf)
- -- handle messages; same drill as doLayout.
- handleMessage p@(PerWorkspace _ (Just True) lt _) m = do
- mlt' <- handleMessage lt m
- return . Just $ mkNewPerWorkspaceT p mlt'
-
- handleMessage p@(PerWorkspace _ (Just False) _ lf) m = do
- mlf' <- handleMessage lf m
- return . Just $ mkNewPerWorkspaceF p mlf'
-
- handleMessage (PerWorkspace _ Nothing _ _) _ = return Nothing
-
- description (PerWorkspace _ (Just True ) l1 _) = description l1
- description (PerWorkspace _ (Just False) _ l2) = description l2
-
- -- description's result is not in the X monad, so we have to wait
- -- until a doLayout for the information about which workspace
- -- we're in to get cached.
- description _ = "PerWorkspace"
+ description (PerWorkspace _ True l1 _) = description l1
+ description (PerWorkspace _ _ _ l2) = description l2
-- | Construct new PerWorkspace values with possibly modified layouts.
mkNewPerWorkspaceT :: PerWorkspace l1 l2 a -> Maybe (l1 a) ->
PerWorkspace l1 l2 a
-mkNewPerWorkspaceT (PerWorkspace wsIds b lt lf) mlt' =
- (\lt' -> PerWorkspace wsIds b lt' lf) $ fromMaybe lt mlt'
+mkNewPerWorkspaceT (PerWorkspace wsIds _ lt lf) mlt' =
+ (\lt' -> PerWorkspace wsIds True lt' lf) $ fromMaybe lt mlt'
mkNewPerWorkspaceF :: PerWorkspace l1 l2 a -> Maybe (l2 a) ->
PerWorkspace l1 l2 a
-mkNewPerWorkspaceF (PerWorkspace wsIds b lt lf) mlf' =
- (\lf' -> PerWorkspace wsIds b lt lf') $ fromMaybe lf mlf'
-
--- | Get the tag of the currently active workspace. Note that this
--- is only guaranteed to be the same workspace for which doLayout
--- was called if there is only one screen.
-getCurrentTag :: X WorkspaceId
-getCurrentTag = gets windowset >>= return . W.tag . W.workspace . W.current
+mkNewPerWorkspaceF (PerWorkspace wsIds _ lt lf) mlf' =
+ (\lf' -> PerWorkspace wsIds False lt lf') $ fromMaybe lf mlf'