freer-indexed-0.1.0.0: Freer indexed monad for type-level resource-aware effectual operations.

Copyright(c) Evgeny Poberezkin
LicenseBSD3
Maintainerevgeny@poberezkin.com
Stabilityexperimental
Portabilitynon-portable
Safe HaskellSafe
LanguageHaskell2010

Control.XMonad

Contents

Description

XMonad and 'XMonadFail type classes for type-indexed (parameterized) monads with additional functions on them.

Synopsis

XMonad

class XApplicative m => XMonad m where Source #

The XMonad class defines the basic operations over a parameterized (indexed) monad, where two type parameters must be correctly chained.

These monads have been described by Oleg Kiselyov in parameterized monads

Indexed monads have been previously released by Edward A. Kmett and Reiner Pope as the package indexed - this package adds other monadic functions and freer indexed monad XFree.

Semantically, these computations can represent type-level state changes of some associated resource, with the first index parameter meaning initial resource state prior to the computation, and the second index - the final resource state, making each computation an edge in the graph of resource state transitions.

Chained type parameters in bind operation require that associated resource changes are continuos.

When combined with computations defined as GADTs and singleton types they can be used to limit allowed computations depending on the context (that is reflected in the final type of the previous and initial type of the next computations) and to make type-level state transitions dependent on the run-time parameters and also on the results of the previous computations.

do expressions can support such parameterized monads using RebindableSyntax extension and Control.XMonad.Do module (it has to be imported separately).

If your code contains any action that can fail (e.g. "monadic" binding with a potentially incomplete pattern match, your computation needs to be an instance of XMonadFail as well to be used in do expression.

To use do expressions Prelude has to be explicitly imported hiding monad operators:

import Prelude hiding ((>>), (>>=))

Instances of XMonad should satisfy the same laws as Monad:

Left identity
xreturn a >>=: k = k a
Right identity
m >>=: xreturn = m
Associativity
m >>=: (\x -> k x >>=: h) = (m >>=: k) >>=: h

XMonad and XApplicative operations should relate as follows:

The above laws imply:

and that xpure and (<*>:) satisfy the applicative functor laws.

Minimal complete definition

(>>=:)

Methods

(>>=:) :: forall a b p q r. m p q a -> (a -> m q r b) -> m p r b infixl 1 Source #

Sequentially compose two parameterized actions, passing any value produced by the first as an argument to the second, and ensuring the continuity in type parameters changes.

(>>:) :: forall a b p q r. m p q a -> m q r b -> m p r b infixl 1 Source #

Sequentially compose two actions, discarding any value produced by the first, and ensuring the continuity in type parameters changes.

xreturn :: a -> m p p a Source #

Inject a value into the monadic type.

Instances
XMonad (XFree f :: k -> k -> Type -> Type) Source # 
Instance details

Defined in Control.XFreer

Methods

(>>=:) :: XFree f p q a -> (a -> XFree f q r b) -> XFree f p r b Source #

(>>:) :: XFree f p q a -> XFree f q r b -> XFree f p r b Source #

xreturn :: a -> XFree f p p a Source #

XMonad functions

(=<<:) :: XMonad m => (a -> m q r b) -> m p q a -> m p r b infixr 1 Source #

xliftM :: XMonad m => (a -> r) -> m p q a -> m p q r Source #

Promote a function to XMonad.

xliftM2 :: XMonad m => (a -> b -> c) -> m p q a -> m q r b -> m p r c Source #

Promote a binary function to XMonad, scanning the monadic arguments from left to right.

xliftM3 :: XMonad m => (a -> b -> c -> d) -> m p q a -> m q r b -> m r s c -> m p s d Source #

Promote a function to a monad, scanning the monadic arguments from left to right.

xap :: XMonad m => m p q (a -> b) -> m q r a -> m p r b Source #

liftXM operations can be replaced by uses of ap, which promotes function application.

return f `ap` x1 `ap` ... `ap` xn

is equivalent to

liftMn f x1 x2 ... xn

xjoin :: XMonad m => m p q (m q r a) -> m p r a Source #

The xjoin function removes one level of indexed monadic structure, projecting its bound argument into the outer level.

'join bss' can be understood as the do expression

do bs <- bss
   bs

Please note the chaining order of type parameters - from outside to inside.

(>=>:) :: XMonad m => (a -> m p q b) -> (b -> m q r c) -> a -> m p r c infixr 1 Source #

Left-to-right composition of Kleisli arrows.

'(f >=>: g) a' is equivalent to \x -> f x >>=: g

(<=<:) :: XMonad m => (b -> m q r c) -> (a -> m p q b) -> a -> m p r c infixr 1 Source #

Right-to-left composition of Kleisli arrows. Same as (>=>:), with the arguments flipped.

This operator resembles function composition (.):

(.)    ::             (b ->       c) -> (a ->       b) -> a ->       c
(<=<:) :: XMonad m => (b -> m q r c) -> (a -> m p q b) -> a -> m p r c

(<$!>:) :: XMonad m => (a -> b) -> m p q a -> m p q b infixl 4 Source #

Strict version of <$> for indexed monads.

XMonadFail

class XMonad m => XMonadFail m where Source #

When a type-indexed computation value is bound in do-notation (using RebindableSyntax for XMonad), the pattern on the left hand side of <- might not match. In this case, this class provides a function xfail to recover.

An XMonad without an XMonadFail instance may only be used in conjunction with pattern that always match, such as newtypes, tuples, data types with only a single data constructor, and irrefutable patterns (~pat).

Instances of XMonadFail should satisfy the following law: xfail s should be a left zero for >>=:.

xfail s >>=: f = xfail s

Methods

xfail :: String -> m p q a Source #