Skip to content

Commit 427dfd4

Browse files
committed
X.L.ConditionalLayoutModifier: Init
1 parent 97508ac commit 427dfd4

File tree

3 files changed

+107
-0
lines changed

3 files changed

+107
-0
lines changed

CHANGES.md

Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -130,6 +130,12 @@
130130

131131
### New Modules
132132

133+
* `XMonad.Layout.ConditionModifier`
134+
135+
This module provides a LayoutModifier that modifies an existing
136+
LayoutModifier so that its modifications are only applied when a particular
137+
condition is met.
138+
133139
* `XMonad.Hooks.TaffybarPagerHints`
134140

135141
Add a module that exports information about XMonads internal state that is

XMonad/Layout/ConditionalModifier.hs

Lines changed: 100 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,100 @@
1+
{-# LANGUAGE FlexibleContexts #-}
2+
{-# LANGUAGE MultiParamTypeClasses #-}
3+
{-# LANGUAGE FlexibleInstances #-}
4+
{-# LANGUAGE ExistentialQuantification #-}
5+
{-# LANGUAGE StandaloneDeriving #-}
6+
{-# LANGUAGE RankNTypes #-}
7+
{-# LANGUAGE TupleSections #-}
8+
9+
-----------------------------------------------------------------------------
10+
-- |
11+
-- Module : XMonad.Layout.ConditionModifier
12+
-- Copyright : (c) Ivan Malison <[email protected]>
13+
-- License : BSD
14+
--
15+
-- Maintainer : none
16+
-- Stability : unstable
17+
-- Portability : portable
18+
--
19+
-- This module provides a LayoutModifier that modifies an existing
20+
-- ModifiedLayout so that its modifications are only applied when a particular
21+
-- condition is met.
22+
-----------------------------------------------------------------------------
23+
24+
module XMonad.Layout.ConditionalModifier where
25+
26+
import XMonad
27+
import XMonad.Layout.LayoutModifier
28+
29+
class (Read c, Show c) => ModifierCondition c where
30+
shouldApply :: c -> X Bool
31+
32+
data ConditionalLayoutModifier m c a = (Read (m a), Show (m a), ModifierCondition c) =>
33+
ConditionalLayoutModifier c (m a)
34+
35+
deriving instance (Read (m a), Show (m a), ModifierCondition c) =>
36+
Show (ConditionalLayoutModifier m c a)
37+
deriving instance (Read (m a), Show (m a), ModifierCondition c) =>
38+
Read (ConditionalLayoutModifier m c a)
39+
40+
data NoOpModifier a = NoOpModifier deriving (Read,Show)
41+
42+
instance LayoutModifier NoOpModifier a
43+
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+
instance (ModifierCondition c, LayoutModifier m Window) =>
54+
LayoutModifier (ConditionalLayoutModifier m c) Window where
55+
56+
modifyLayout (ConditionalLayoutModifier condition originalModifier) w r =
57+
runModifierIfCondition originalModifier condition
58+
(\modifier -> modifyLayout modifier w r)
59+
60+
modifyLayoutWithUpdate (ConditionalLayoutModifier condition originalModifier) w r = do
61+
applyModifier <- shouldApply condition
62+
if applyModifier
63+
then do
64+
(res, updatedModifier) <- modifyLayoutWithUpdate originalModifier w r
65+
let updatedModifiedModifier =
66+
ConditionalLayoutModifier condition <$> updatedModifier
67+
return (res, updatedModifiedModifier)
68+
else (, Nothing) . fst <$> modifyLayoutWithUpdate NoOpModifier w r
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
89+
if applyModifier
90+
then do
91+
(res, updatedModifier) <- redoLayout originalModifier r ms wrs
92+
let updatedModifiedModifier =
93+
ConditionalLayoutModifier condition <$> updatedModifier
94+
return (res, updatedModifiedModifier)
95+
else (, Nothing) . fst <$> redoLayout NoOpModifier r ms wrs
96+
97+
modifyDescription (ConditionalLayoutModifier _ originalModifier) l =
98+
modifyDescription originalModifier l
99+
100+

xmonad-contrib.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -213,6 +213,7 @@ library
213213
XMonad.Layout.Column
214214
XMonad.Layout.Combo
215215
XMonad.Layout.ComboP
216+
XMonad.Layout.ConditionalModifier
216217
XMonad.Layout.Cross
217218
XMonad.Layout.Decoration
218219
XMonad.Layout.DecorationAddons

0 commit comments

Comments
 (0)