xmonad-contrib-0.17.0.9: Community-maintained extensions for xmonad
CopyrightL. S. Leary 2018
LicenseBSD3-style (see LICENSE)
MaintainerL. S. Leary
Stabilityunstable
Portabilitynot portable
Safe HaskellSafe-Inferred
LanguageHaskell2010

XMonad.Util.PureX

Description

Unlike the opaque IO actions that X actions can wrap, regular reads from the XConf and modifications to the XState are fundamentally pure—contrary to the current treatment of such actions in most xmonad code. Pure modifications to the WindowSet can be readily composed, but due to the need for those modifications to be properly handled by windows, other pure changes to the XState cannot be interleaved with those changes to the WindowSet without superfluous refreshes, hence breaking composability.

This module aims to rectify that situation by drawing attention to it and providing PureX: a pure type with the same monadic interface to state as X. The XLike typeclass enables writing actions generic over the two monads; if pure, existing X actions can be generalised with only a change to the type signature. Various other utilities are provided, in particular the defile function which is needed by end-users.

Synopsis

Usage

The suggested pattern of usage for this module is to write composable, pure actions as XLike m => m Any or PureX Any values, where the encapsulated Any value encodes whether or not a refresh is needed to properly institute changes. These values can then be combined monoidally (i.e. with <> AKA <+>) or with operators such as <*, *>, <? and &> to build seamless new actions. The end user can run and handle the effects of the pure actions in the X monad by applying the defile function, which you may want to re-export. Alternatively, if an action does not make stackset changes that need to be handled by windows, it can be written with as an XLike m => m () and used directly.

Unfortunately since layouts must handle messages in the X monad, this approach does not quite apply to actions involving them. However a relatively direct translation to impure actions is possible: you can write composable, refresh-tracking actions as X Any values, making sure to eschew refresh-inducing functions like windows and sendMessage in favour of modifyWindowSet and utilities provided by XMonad.Actions.MessageFeedback. The windowBracket_ function recently added to XMonad.Operations is the impure analogue of defile. Note that PureX Any actions can be composed into impure ones after applying toX; don't use defile for this. E.g.

windowBracket_ (composableImpureAction <> toX composablePureAction)

Although both X and PureX have Monoid instances over monoidal values, (XLike m, Monoid a) is not enough to infer Monoid (m a) (due to the open-world assumption). Hence a Monoid (m Any) constraint may need to be used when working with XLike m => m Any where no context is forcing m to unify with X or PureX. This can also be avoided by working with PureX Any values and generalising them with toXLike where necessary.

PureX also enables a more monadic style when writing windowset operations; see the implementation of the utilities in this module for examples. For an example of a whole module written in terms of this one, see XMonad.Hooks.RefocusLast.

data PureX a Source #

The PureX newtype over ReaderT XConf (State XState) a.

Instances

Instances details
Applicative PureX Source # 
Instance details

Defined in XMonad.Util.PureX

Methods

pure :: a -> PureX a #

(<*>) :: PureX (a -> b) -> PureX a -> PureX b #

liftA2 :: (a -> b -> c) -> PureX a -> PureX b -> PureX c #

(*>) :: PureX a -> PureX b -> PureX b #

(<*) :: PureX a -> PureX b -> PureX a #

Functor PureX Source # 
Instance details

Defined in XMonad.Util.PureX

Methods

fmap :: (a -> b) -> PureX a -> PureX b #

(<$) :: a -> PureX b -> PureX a #

Monad PureX Source # 
Instance details

Defined in XMonad.Util.PureX

Methods

(>>=) :: PureX a -> (a -> PureX b) -> PureX b #

(>>) :: PureX a -> PureX b -> PureX b #

return :: a -> PureX a #

XLike PureX Source # 
Instance details

Defined in XMonad.Util.PureX

Methods

toX :: PureX a -> X a Source #

MonadReader XConf PureX Source # 
Instance details

Defined in XMonad.Util.PureX

Methods

ask :: PureX XConf #

local :: (XConf -> XConf) -> PureX a -> PureX a #

reader :: (XConf -> a) -> PureX a #

MonadState XState PureX Source # 
Instance details

Defined in XMonad.Util.PureX

Methods

get :: PureX XState #

put :: XState -> PureX () #

state :: (XState -> (a, XState)) -> PureX a #

Monoid a => Monoid (PureX a) Source # 
Instance details

Defined in XMonad.Util.PureX

Methods

mempty :: PureX a #

mappend :: PureX a -> PureX a -> PureX a #

mconcat :: [PureX a] -> PureX a #

Semigroup a => Semigroup (PureX a) Source # 
Instance details

Defined in XMonad.Util.PureX

Methods

(<>) :: PureX a -> PureX a -> PureX a #

sconcat :: NonEmpty (PureX a) -> PureX a #

stimes :: Integral b => b -> PureX a -> PureX a #

class (MonadReader XConf m, MonadState XState m) => XLike m where Source #

The XLike typeclass over monads reading XConf values and tracking XState state.

Methods

toX :: m a -> X a Source #

Instances

Instances details
XLike X Source # 
Instance details

Defined in XMonad.Util.PureX

Methods

toX :: X a -> X a Source #

XLike PureX Source # 
Instance details

Defined in XMonad.Util.PureX

Methods

toX :: PureX a -> X a Source #

defile :: PureX Any -> X () Source #

A version of windowBracket' specialised to take a PureX Any action and handle windowset changes with a refresh when the Any holds True. Analogous to windowBracket_. Don't bake this into your action; it's for the end-user.

windowBracket' :: XLike m => (a -> Bool) -> m a -> X a Source #

A generalisation of windowBracket. Handles refreshing for an action that performs no refresh of its own but can indicate that it needs one through a return value that's tested against the supplied predicate. The action can interleave changes to the WindowSet with IO or changes to the XState.

handlingRefresh :: X () -> X () Source #

A version of windowBracket specialised to take an X () action and perform a refresh handling any changes it makes.

runPureX :: PureX a -> XConf -> XState -> (a, XState) Source #

Consume a PureX a.

toXLike :: XLike m => PureX a -> m a Source #

Despite appearing less general, PureX a is actually isomorphic to XLike m => m a.

Utility

Generalised when* functions

when' :: (Monad m, Monoid a) => Bool -> m a -> m a Source #

A when that accepts a monoidal return value.

whenM' :: (Monad m, Monoid a) => m Bool -> m a -> m a Source #

A whenX/whenM that accepts a monoidal return value.

whenJust' :: (Monad m, Monoid b) => Maybe a -> (a -> m b) -> m b Source #

A whenJust that accepts a monoidal return value.

Infix operators

(<?) :: Monad m => m Any -> m a -> m Any infixl 4 Source #

Akin to <*. Discarding the wrapped value in the second argument either way, keep its effects iff the first argument returns Any True.

(&>) :: Applicative f => f Any -> f Any -> f Any infixl 1 Source #

Akin to a low precedence <>. Combines applicative effects left-to-right and wrapped Bools with && (instead of ||).

WindowSet operations

withWindowSet' :: XLike m => (WindowSet -> m a) -> m a Source #

A generalisation of withWindowSet.

withFocii :: (XLike m, Monoid a) => (WorkspaceId -> Window -> m a) -> m a Source #

If there is a current tag and a focused window, perform an operation with them, otherwise return mempty.

modify'' :: (Maybe (Stack a) -> Maybe (Stack a)) -> StackSet i l a s sd -> StackSet i l a s sd Source #

A variant of W.modify and W.modify' handling the Nothing and Just cases uniformly.

modifyWindowSet' :: XLike m => (WindowSet -> WindowSet) -> m () Source #

A generalisation of modifyWindowSet.

getStack :: XLike m => m (Maybe (Stack Window)) Source #

Get the stack from the current workspace.

putStack :: XLike m => Maybe (Stack Window) -> m () Source #

Set the stack on the current workspace.

peek :: XLike m => m (Maybe Window) Source #

Get the focused window if there is one.

focusWindow :: XLike m => Window -> m Any Source #

A refresh-tracking version of W.focusWindow.

focusNth :: XLike m => Int -> m Any Source #

A refresh-tracking version of XMonad.Actions.FocusNth.focusNth.

view :: XLike m => WorkspaceId -> m Any Source #

A version of W.view that tracks the need to refresh.

greedyView :: XLike m => WorkspaceId -> m Any Source #

A version of W.greedyView that tracks the need to refresh.

invisiView :: XLike m => WorkspaceId -> m Any Source #

View a workspace if it's not visible. An alternative to view and greedyView that—rather than changing the current screen or affecting another—opts not to act.

shift :: XLike m => WorkspaceId -> m Any Source #

A refresh-tracking version of W.Shift.

shiftWin :: XLike m => WorkspaceId -> Window -> m Any Source #

A refresh tracking version of W.shiftWin.

curScreen :: XLike m => m WindowScreen Source #

Get the current screen.

curWorkspace :: XLike m => m WindowSpace Source #

Get the current workspace.

curTag :: XLike m => m WorkspaceId Source #

Get the current tag.

curScreenId :: XLike m => m ScreenId Source #

Get the current ScreenId.