Skip to content
New issue

Have a question about this project? Sign up for a free GitHub account to open an issue and contact its maintainers and the community.

By clicking “Sign up for GitHub”, you agree to our terms of service and privacy statement. We’ll occasionally send you account related emails.

Already on GitHub? Sign in to your account

X.L.ConditionalLayoutModifier: Init #582

Open
wants to merge 3 commits into
base: master
Choose a base branch
from
Open
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
6 changes: 6 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
Expand Up @@ -134,6 +134,12 @@

Layout modifier for user provided per-window aspect ratios.

* `XMonad.Layout.ConditionModifier`

This module provides a LayoutModifier that modifies an existing
LayoutModifier so that its modifications are only applied when a particular
condition is met.

* `XMonad.Hooks.TaffybarPagerHints`

Add a module that exports information about XMonads internal state that is
Expand Down
103 changes: 103 additions & 0 deletions XMonad/Layout/ConditionalLayout.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,103 @@
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TupleSections #-}

-----------------------------------------------------------------------------
-- |
-- Module : XMonad.Layout.ConditionalLayout
-- Copyright : (c) Ivan Malison <IvanMalison@gmail.com>
-- License : BSD
--
-- Maintainer : none
-- Stability : unstable
-- Portability : portable
--
-- This module provides a LayoutModifier combinator that modifies an existing
-- ModifiedLayout so that its modifications are only applied when a particular
-- condition is met.
-----------------------------------------------------------------------------

module XMonad.Layout.ConditionalLayout where

import XMonad
import XMonad.Layout.LayoutModifier
import qualified XMonad.StackSet as W

-- | A 'ModifierCondition' is a condition run in 'X' that takes a 'WorkspaceId'
-- as a parameter. The reason that this must exist as a type class and a simple
-- function will not suffice is that 'ModifierCondition's are used as parameters
-- to 'ConditionalLayoutModifier', which must implement 'Read' and 'Show' in
-- order to also implement 'LayoutModifier'. By defining a new type for
-- condition, we sidestep the issue that functions can not implement these
-- typeclasses.
class (Read c, Show c) => ModifierCondition c where
shouldApply :: c -> WorkspaceId -> X Bool

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

deriving instance (Read (m a), Show (m a), ModifierCondition c) =>
Show (ConditionalLayoutModifier m c a)
deriving instance (Read (m a), Show (m a), ModifierCondition c) =>
Read (ConditionalLayoutModifier m c a)

data NoOpModifier a = NoOpModifier deriving (Read, Show)

instance LayoutModifier NoOpModifier a

instance (ModifierCondition c, LayoutModifier m Window) =>
LayoutModifier (ConditionalLayoutModifier m c) Window where

modifyLayout (ConditionalLayoutModifier condition originalModifier) w r = do
applyModifier <- shouldApply condition $ W.tag w
if applyModifier
then modifyLayout originalModifier w r
else modifyLayout NoOpModifier w r

modifyLayoutWithUpdate (ConditionalLayoutModifier condition originalModifier) w r = do
applyModifier <- shouldApply condition $ W.tag w
if applyModifier
then do
(res, updatedModifier) <- modifyLayoutWithUpdate originalModifier w r
let updatedModifiedModifier =
ConditionalLayoutModifier condition <$> updatedModifier
return (res, updatedModifiedModifier)
else (, Nothing) . fst <$> modifyLayoutWithUpdate NoOpModifier w r

-- This function is not allowed to have any effect on layout, so we always
-- pass the message along to the original modifier to ensure that it is
-- allowed to update its internal state appropriately. This is particularly
-- important for messages like 'Hide' or 'ReleaseResources'.
Comment on lines +75 to +78
Copy link
Contributor Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

This is crucial -- This function does not have any effect on layout, so we don't need to evaluate the condition to decide whether or not to pass the message along to the original modifier.

handleMessOrMaybeModifyIt
(ConditionalLayoutModifier condition originalModifier) mess = do
result <- handleMessOrMaybeModifyIt originalModifier mess
return $ case result of
Nothing -> Nothing
Just (Left updated) ->
Just $ Left $
ConditionalLayoutModifier condition updated
Just (Right message) -> Just $ Right message
Copy link
Contributor Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

One small detail here is that we always modify messages even if the condition might be viewed as evaluating to false in the moment. I don't think this is a big problem because there is no way to affect the layout.


redoLayoutWithWorkspace (ConditionalLayoutModifier condition originalModifier)
w r ms wrs = do
applyModifier <- shouldApply condition $ W.tag w
if applyModifier
then do
(res, updatedModifier) <- redoLayout originalModifier r ms wrs
let updatedModifiedModifier =
ConditionalLayoutModifier condition <$> updatedModifier
return (res, updatedModifiedModifier)
else (, Nothing) . fst <$> redoLayout NoOpModifier r ms wrs

modifyDescription (ConditionalLayoutModifier _ originalModifier) l =
modifyDescription originalModifier l


22 changes: 19 additions & 3 deletions XMonad/Layout/LayoutModifier.hs
Original file line number Diff line number Diff line change
Expand Up @@ -188,11 +188,27 @@ class (Show (m a), Read (m a)) => LayoutModifier m a where
redoLayout :: m a -- ^ the layout modifier
-> Rectangle -- ^ screen rectangle
-> Maybe (Stack a) -- ^ current window stack
-> [(a, Rectangle)] -- ^ (window,rectangle) pairs returned
-> [(a, Rectangle)] -- ^ (window, rectangle) pairs returned
-- by the underlying layout
-> X ([(a, Rectangle)], Maybe (m a))
redoLayout m r ms wrs = do hook m; return $ pureModifier m r ms wrs

-- | 'redoLayoutWithWorkspace' is exactly like 'redoLayout', execept
-- that the original workspace is also provided as an argument
redoLayoutWithWorkspace :: m a
-- ^ the layout modifier
-> Workspace WorkspaceId (ModifiedLayout m l a) a
-- ^ The original workspace that is being laid out
-> Rectangle
-- ^ screen rectangle
-> Maybe (Stack a)
-- ^ current window stack
-> [(a, Rectangle)]
-- ^ (window, rectangle) pairs returned by the
-- underlying layout
-> X ([(a, Rectangle)], Maybe (m a))
redoLayoutWithWorkspace m _ = redoLayout m
Comment on lines +198 to +210
Copy link
Contributor Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

I worry that some may find this unpalatable for some reason, but I believe that the way I have implemented this leads to no change in the current behavior of anything.


-- | 'pureModifier' allows you to intercept a call to 'runLayout'
-- /after/ it is called on the underlying layout, in order to
-- modify the list of window\/rectangle pairings it has returned,
Expand Down Expand Up @@ -251,9 +267,9 @@ class (Show (m a), Read (m a)) => LayoutModifier m a where
-- | The 'LayoutClass' instance for a 'ModifiedLayout' defines the
-- semantics of a 'LayoutModifier' applied to an underlying layout.
instance (LayoutModifier m a, LayoutClass l a, Typeable m) => LayoutClass (ModifiedLayout m l) a where
runLayout (Workspace i (ModifiedLayout m l) ms) r =
runLayout w@(Workspace i (ModifiedLayout m l) ms) r =
do ((ws, ml'),mm') <- modifyLayoutWithUpdate m (Workspace i l ms) r
(ws', mm'') <- redoLayout (fromMaybe m mm') r ms ws
(ws', mm'') <- redoLayoutWithWorkspace (fromMaybe m mm') w r ms ws
let ml'' = case mm'' `mplus` mm' of
Just m' -> Just $ ModifiedLayout m' $ fromMaybe l ml'
Nothing -> ModifiedLayout m <$> ml'
Expand Down
1 change: 1 addition & 0 deletions xmonad-contrib.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -213,6 +213,7 @@ library
XMonad.Layout.Column
XMonad.Layout.Combo
XMonad.Layout.ComboP
XMonad.Layout.ConditionalLayout
XMonad.Layout.Cross
XMonad.Layout.Decoration
XMonad.Layout.DecorationAddons
Expand Down