| Copyright | L. S. Leary 2018 | 
|---|---|
| License | BSD3-style (see LICENSE) | 
| Maintainer | L. S. Leary | 
| Stability | unstable | 
| Portability | not portable | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
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
- data PureX a
 - class (MonadReader XConf m, MonadState XState m) => XLike (m :: Type -> Type) where
 - defile :: PureX Any -> X ()
 - windowBracket' :: XLike m => (a -> Bool) -> m a -> X a
 - handlingRefresh :: X () -> X ()
 - runPureX :: PureX a -> XConf -> XState -> (a, XState)
 - toXLike :: XLike m => PureX a -> m a
 - when' :: (Monad m, Monoid a) => Bool -> m a -> m a
 - whenM' :: (Monad m, Monoid a) => m Bool -> m a -> m a
 - whenJust' :: (Monad m, Monoid b) => Maybe a -> (a -> m b) -> m b
 - (<?) :: Monad m => m Any -> m a -> m Any
 - (&>) :: Applicative f => f Any -> f Any -> f Any
 - withWindowSet' :: XLike m => (WindowSet -> m a) -> m a
 - withFocii :: (XLike m, Monoid a) => (WorkspaceId -> Window -> m a) -> m a
 - modify'' :: (Maybe (Stack a) -> Maybe (Stack a)) -> StackSet i l a s sd -> StackSet i l a s sd
 - modifyWindowSet' :: XLike m => (WindowSet -> WindowSet) -> m ()
 - getStack :: XLike m => m (Maybe (Stack Window))
 - putStack :: XLike m => Maybe (Stack Window) -> m ()
 - peek :: XLike m => m (Maybe Window)
 - focusWindow :: XLike m => Window -> m Any
 - focusNth :: XLike m => Int -> m Any
 - view :: XLike m => WorkspaceId -> m Any
 - greedyView :: XLike m => WorkspaceId -> m Any
 - invisiView :: XLike m => WorkspaceId -> m Any
 - shift :: XLike m => WorkspaceId -> m Any
 - shiftWin :: XLike m => WorkspaceId -> Window -> m Any
 - curScreen :: XLike m => m WindowScreen
 - curWorkspace :: XLike m => m WindowSpace
 - curTag :: XLike m => m WorkspaceId
 - curScreenId :: XLike m => m ScreenId
 
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.
The PureX newtype over ReaderT XConf (State XState) a.
class (MonadReader XConf m, MonadState XState m) => XLike (m :: Type -> Type) where Source #
The XLike typeclass over monads reading XConf values and tracking
   XState state.
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.
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.
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.
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.