1
+ {-# LANGUAGE ExistentialQuantification #-}
1
2
{-# LANGUAGE FlexibleContexts #-}
2
- {-# LANGUAGE MultiParamTypeClasses #-}
3
3
{-# LANGUAGE FlexibleInstances #-}
4
- {-# LANGUAGE ExistentialQuantification #-}
5
- {-# LANGUAGE StandaloneDeriving #-}
4
+ {-# LANGUAGE MultiParamTypeClasses #-}
5
+ {-# LANGUAGE PatternGuards #-}
6
6
{-# LANGUAGE RankNTypes #-}
7
+ {-# LANGUAGE StandaloneDeriving #-}
7
8
{-# LANGUAGE TupleSections #-}
8
9
9
10
-----------------------------------------------------------------------------
16
17
-- Stability : unstable
17
18
-- Portability : portable
18
19
--
19
- -- This module provides a LayoutModifier that modifies an existing
20
+ -- This module provides a LayoutModifier combinator that modifies an existing
20
21
-- ModifiedLayout so that its modifications are only applied when a particular
21
22
-- condition is met.
22
23
-----------------------------------------------------------------------------
@@ -25,10 +26,16 @@ module XMonad.Layout.ConditionalLayout where
25
26
26
27
import XMonad
27
28
import XMonad.Layout.LayoutModifier
29
+ import qualified XMonad.StackSet as W
28
30
31
+ -- | A
29
32
class (Read c , Show c ) => ModifierCondition c where
30
- shouldApply :: c -> X Bool
33
+ shouldApply :: c -> WorkspaceId -> X Bool
31
34
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.
32
39
data ConditionalLayoutModifier m c a = (Read (m a ), Show (m a ), ModifierCondition c ) =>
33
40
ConditionalLayoutModifier c (m a )
34
41
@@ -37,28 +44,21 @@ deriving instance (Read (m a), Show (m a), ModifierCondition c) =>
37
44
deriving instance (Read (m a ), Show (m a ), ModifierCondition c ) =>
38
45
Read (ConditionalLayoutModifier m c a )
39
46
40
- data NoOpModifier a = NoOpModifier deriving (Read ,Show )
47
+ data NoOpModifier a = NoOpModifier deriving (Read , Show )
41
48
42
49
instance LayoutModifier NoOpModifier a
43
50
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
-
53
51
instance (ModifierCondition c , LayoutModifier m Window ) =>
54
52
LayoutModifier (ConditionalLayoutModifier m c ) Window where
55
53
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
59
59
60
60
modifyLayoutWithUpdate (ConditionalLayoutModifier condition originalModifier) w r = do
61
- applyModifier <- shouldApply condition
61
+ applyModifier <- shouldApply condition $ W. tag w
62
62
if applyModifier
63
63
then do
64
64
(res, updatedModifier) <- modifyLayoutWithUpdate originalModifier w r
@@ -67,25 +67,23 @@ instance (ModifierCondition c, LayoutModifier m Window) =>
67
67
return (res, updatedModifiedModifier)
68
68
else (, Nothing ) . fst <$> modifyLayoutWithUpdate NoOpModifier w r
69
69
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
89
87
if applyModifier
90
88
then do
91
89
(res, updatedModifier) <- redoLayout originalModifier r ms wrs
0 commit comments