Skip to content

Commit 0a99348

Browse files
committed
Allow messages to flow to original modifier in conditional layout
1 parent 726cc6d commit 0a99348

File tree

2 files changed

+55
-41
lines changed

2 files changed

+55
-41
lines changed

XMonad/Layout/ConditionalLayout.hs

Lines changed: 36 additions & 38 deletions
Original file line numberDiff line numberDiff line change
@@ -1,9 +1,10 @@
1+
{-# LANGUAGE ExistentialQuantification #-}
12
{-# LANGUAGE FlexibleContexts #-}
2-
{-# LANGUAGE MultiParamTypeClasses #-}
33
{-# LANGUAGE FlexibleInstances #-}
4-
{-# LANGUAGE ExistentialQuantification #-}
5-
{-# LANGUAGE StandaloneDeriving #-}
4+
{-# LANGUAGE MultiParamTypeClasses #-}
5+
{-# LANGUAGE PatternGuards #-}
66
{-# LANGUAGE RankNTypes #-}
7+
{-# LANGUAGE StandaloneDeriving #-}
78
{-# LANGUAGE TupleSections #-}
89

910
-----------------------------------------------------------------------------
@@ -16,7 +17,7 @@
1617
-- Stability : unstable
1718
-- Portability : portable
1819
--
19-
-- This module provides a LayoutModifier that modifies an existing
20+
-- This module provides a LayoutModifier combinator that modifies an existing
2021
-- ModifiedLayout so that its modifications are only applied when a particular
2122
-- condition is met.
2223
-----------------------------------------------------------------------------
@@ -25,10 +26,16 @@ module XMonad.Layout.ConditionalLayout where
2526

2627
import XMonad
2728
import XMonad.Layout.LayoutModifier
29+
import qualified XMonad.StackSet as W
2830

31+
-- | A
2932
class (Read c, Show c) => ModifierCondition c where
30-
shouldApply :: c -> X Bool
33+
shouldApply :: c -> WorkspaceId -> X Bool
3134

35+
-- | 'ConditionalLayoutModifier' takes a condition implemented as a
36+
-- 'ModifierCondition' together with a 'LayoutModifier' and builds a new
37+
-- 'LayoutModifier' that is exactly like the provided 'LayoutModifier', except
38+
-- that it is only applied when the provided condition evalutes to True.
3239
data ConditionalLayoutModifier m c a = (Read (m a), Show (m a), ModifierCondition c) =>
3340
ConditionalLayoutModifier c (m a)
3441

@@ -37,28 +44,21 @@ deriving instance (Read (m a), Show (m a), ModifierCondition c) =>
3744
deriving instance (Read (m a), Show (m a), ModifierCondition c) =>
3845
Read (ConditionalLayoutModifier m c a)
3946

40-
data NoOpModifier a = NoOpModifier deriving (Read,Show)
47+
data NoOpModifier a = NoOpModifier deriving (Read, Show)
4148

4249
instance LayoutModifier NoOpModifier a
4350

44-
runModifierIfCondition ::
45-
(ModifierCondition c, LayoutModifier m a) =>
46-
m a -> c -> (forall m1. LayoutModifier m1 a => m1 a -> X b) -> X b
47-
runModifierIfCondition modifier condition action = do
48-
applyModifier <- shouldApply condition
49-
if applyModifier
50-
then action modifier
51-
else action NoOpModifier
52-
5351
instance (ModifierCondition c, LayoutModifier m Window) =>
5452
LayoutModifier (ConditionalLayoutModifier m c) Window where
5553

56-
modifyLayout (ConditionalLayoutModifier condition originalModifier) w r =
57-
runModifierIfCondition originalModifier condition
58-
(\modifier -> modifyLayout modifier w r)
54+
modifyLayout (ConditionalLayoutModifier condition originalModifier) w r = do
55+
applyModifier <- shouldApply condition $ W.tag w
56+
if applyModifier
57+
then modifyLayout originalModifier w r
58+
else modifyLayout NoOpModifier w r
5959

6060
modifyLayoutWithUpdate (ConditionalLayoutModifier condition originalModifier) w r = do
61-
applyModifier <- shouldApply condition
61+
applyModifier <- shouldApply condition $ W.tag w
6262
if applyModifier
6363
then do
6464
(res, updatedModifier) <- modifyLayoutWithUpdate originalModifier w r
@@ -67,25 +67,23 @@ instance (ModifierCondition c, LayoutModifier m Window) =>
6767
return (res, updatedModifiedModifier)
6868
else (, Nothing) . fst <$> modifyLayoutWithUpdate NoOpModifier w r
6969

70-
-- This function is not allowed to have any downstream effect, so it seems
71-
-- more reasonable to simply allow the message to pass than to make it depend
72-
-- on the condition.
73-
handleMess (ConditionalLayoutModifier condition originalModifier) mess = do
74-
fmap (ConditionalLayoutModifier condition) <$> handleMess originalModifier mess
75-
76-
handleMessOrMaybeModifyIt (ConditionalLayoutModifier condition originalModifier) mess = do
77-
applyModifier <- shouldApply condition
78-
if applyModifier
79-
then do
80-
result <- handleMessOrMaybeModifyIt originalModifier mess
81-
return $ case result of
82-
Nothing -> Nothing
83-
Just (Left updated) -> Just $ Left $ ConditionalLayoutModifier condition updated
84-
Just (Right message) -> Just $ Right message
85-
else return Nothing
86-
87-
redoLayout (ConditionalLayoutModifier condition originalModifier) r ms wrs = do
88-
applyModifier <- shouldApply condition
70+
-- This function is not allowed to have any effect on layout, so we always
71+
-- pass the message along to the original modifier to ensure that it is
72+
-- allowed to update its internal state appropriately. This is particularly
73+
-- important for messages like 'Hide' or 'ReleaseResources'.
74+
handleMessOrMaybeModifyIt
75+
(ConditionalLayoutModifier condition originalModifier) mess = do
76+
result <- handleMessOrMaybeModifyIt originalModifier mess
77+
return $ case result of
78+
Nothing -> Nothing
79+
Just (Left updated) ->
80+
Just $ Left $
81+
ConditionalLayoutModifier condition updated
82+
Just (Right message) -> Just $ Right message
83+
84+
redoLayoutWithWorkspace (ConditionalLayoutModifier condition originalModifier)
85+
w r ms wrs = do
86+
applyModifier <- shouldApply condition $ W.tag w
8987
if applyModifier
9088
then do
9189
(res, updatedModifier) <- redoLayout originalModifier r ms wrs

XMonad/Layout/LayoutModifier.hs

Lines changed: 19 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -188,11 +188,27 @@ class (Show (m a), Read (m a)) => LayoutModifier m a where
188188
redoLayout :: m a -- ^ the layout modifier
189189
-> Rectangle -- ^ screen rectangle
190190
-> Maybe (Stack a) -- ^ current window stack
191-
-> [(a, Rectangle)] -- ^ (window,rectangle) pairs returned
191+
-> [(a, Rectangle)] -- ^ (window, rectangle) pairs returned
192192
-- by the underlying layout
193193
-> X ([(a, Rectangle)], Maybe (m a))
194194
redoLayout m r ms wrs = do hook m; return $ pureModifier m r ms wrs
195195

196+
-- | 'redoLayoutWithWorkspace' is exactly like 'redoLayout', execept
197+
-- that the original workspace is also provided as an argument
198+
redoLayoutWithWorkspace :: m a
199+
-- ^ the layout modifier
200+
-> Workspace WorkspaceId (ModifiedLayout m l a) a
201+
-- ^ The original workspace that is being laid out
202+
-> Rectangle
203+
-- ^ screen rectangle
204+
-> Maybe (Stack a)
205+
-- ^ current window stack
206+
-> [(a, Rectangle)]
207+
-- ^ (window, rectangle) pairs returned by the
208+
-- underlying layout
209+
-> X ([(a, Rectangle)], Maybe (m a))
210+
redoLayoutWithWorkspace m _ = redoLayout m
211+
196212
-- | 'pureModifier' allows you to intercept a call to 'runLayout'
197213
-- /after/ it is called on the underlying layout, in order to
198214
-- modify the list of window\/rectangle pairings it has returned,
@@ -251,9 +267,9 @@ class (Show (m a), Read (m a)) => LayoutModifier m a where
251267
-- | The 'LayoutClass' instance for a 'ModifiedLayout' defines the
252268
-- semantics of a 'LayoutModifier' applied to an underlying layout.
253269
instance (LayoutModifier m a, LayoutClass l a, Typeable m) => LayoutClass (ModifiedLayout m l) a where
254-
runLayout (Workspace i (ModifiedLayout m l) ms) r =
270+
runLayout w@(Workspace i (ModifiedLayout m l) ms) r =
255271
do ((ws, ml'),mm') <- modifyLayoutWithUpdate m (Workspace i l ms) r
256-
(ws', mm'') <- redoLayout (fromMaybe m mm') r ms ws
272+
(ws', mm'') <- redoLayoutWithWorkspace (fromMaybe m mm') w r ms ws
257273
let ml'' = case mm'' `mplus` mm' of
258274
Just m' -> Just $ ModifiedLayout m' $ fromMaybe l ml'
259275
Nothing -> ModifiedLayout m <$> ml'

0 commit comments

Comments
 (0)