Skip to content

Commit 776f688

Browse files
committed
X.L.ConditionalLayoutModifier: Init
1 parent 97508ac commit 776f688

File tree

3 files changed

+108
-0
lines changed

3 files changed

+108
-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: 101 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,101 @@
1+
{-# LANGUAGE FlexibleContexts #-}
2+
{-# LANGUAGE MultiParamTypeClasses #-}
3+
{-# LANGUAGE FlexibleInstances #-}
4+
{-# LANGUAGE TypeApplications #-}
5+
{-# LANGUAGE ExistentialQuantification #-}
6+
{-# LANGUAGE StandaloneDeriving #-}
7+
{-# LANGUAGE RankNTypes #-}
8+
{-# LANGUAGE TupleSections #-}
9+
10+
-----------------------------------------------------------------------------
11+
-- |
12+
-- Module : XMonad.Layout.ConditionModifier
13+
-- Copyright : (c) Ivan Malison <[email protected]>
14+
-- License : BSD
15+
--
16+
-- Maintainer : none
17+
-- Stability : unstable
18+
-- Portability : portable
19+
--
20+
-- This module provides a LayoutModifier that modifies an existing
21+
-- ModifiedLayout so that its modifications are only applied when a particular
22+
-- condition is met.
23+
-----------------------------------------------------------------------------
24+
25+
module XMonad.Layout.ConditionalModifier where
26+
27+
import XMonad
28+
import XMonad.Layout.LayoutModifier
29+
30+
class (Read c, Show c) => ModifierCondition c where
31+
shouldApply :: c -> X Bool
32+
33+
data ConditionalLayoutModifier m c a = (Read (m a), Show (m a), ModifierCondition c) =>
34+
ConditionalLayoutModifier c (m a)
35+
36+
deriving instance (Read (m a), Show (m a), ModifierCondition c) =>
37+
Show (ConditionalLayoutModifier m c a)
38+
deriving instance (Read (m a), Show (m a), ModifierCondition c) =>
39+
Read (ConditionalLayoutModifier m c a)
40+
41+
data NoOpModifier a = NoOpModifier deriving (Read,Show)
42+
43+
instance LayoutModifier NoOpModifier a
44+
45+
runModifierIfCondition ::
46+
(ModifierCondition c, LayoutModifier m a) =>
47+
m a -> c -> (forall m1. LayoutModifier m1 a => m1 a -> X b) -> X b
48+
runModifierIfCondition modifier condition action = do
49+
applyModifier <- shouldApply condition
50+
if applyModifier
51+
then action modifier
52+
else action NoOpModifier
53+
54+
instance (ModifierCondition c, LayoutModifier m Window) =>
55+
LayoutModifier (ConditionalLayoutModifier m c) Window where
56+
57+
modifyLayout (ConditionalLayoutModifier condition originalModifier) w r =
58+
runModifierIfCondition originalModifier condition
59+
(\modifier -> modifyLayout modifier w r)
60+
61+
modifyLayoutWithUpdate (ConditionalLayoutModifier condition originalModifier) w r = do
62+
applyModifier <- shouldApply condition
63+
if applyModifier
64+
then do
65+
(res, updatedModifier) <- modifyLayoutWithUpdate originalModifier w r
66+
let updatedModifiedModifier =
67+
(ConditionalLayoutModifier condition) <$> updatedModifier
68+
return (res, updatedModifiedModifier)
69+
else (, Nothing) . fst <$> modifyLayoutWithUpdate NoOpModifier w r
70+
71+
-- This function is not allowed to have any downstream effect, so it seems
72+
-- more reasonable to simply allow the message to pass than to make it depend
73+
-- on the condition.
74+
handleMess (ConditionalLayoutModifier condition originalModifier) mess = do
75+
fmap (ConditionalLayoutModifier condition) <$> handleMess originalModifier mess
76+
77+
handleMessOrMaybeModifyIt (ConditionalLayoutModifier condition originalModifier) mess = do
78+
applyModifier <- shouldApply condition
79+
if applyModifier
80+
then do
81+
result <- handleMessOrMaybeModifyIt originalModifier mess
82+
return $ case result of
83+
Nothing -> Nothing
84+
Just (Left updated) -> Just $ Left $ ConditionalLayoutModifier condition updated
85+
Just (Right message) -> Just $ Right message
86+
else return Nothing
87+
88+
redoLayout (ConditionalLayoutModifier condition originalModifier) r ms wrs = do
89+
applyModifier <- shouldApply condition
90+
if applyModifier
91+
then do
92+
(res, updatedModifier) <- redoLayout originalModifier r ms wrs
93+
let updatedModifiedModifier =
94+
(ConditionalLayoutModifier condition) <$> updatedModifier
95+
return (res, updatedModifiedModifier)
96+
else (, Nothing) . fst <$> redoLayout NoOpModifier r ms wrs
97+
98+
modifyDescription (ConditionalLayoutModifier _ originalModifier) l =
99+
modifyDescription originalModifier l
100+
101+

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)