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.XFreer

Description

This module defines a "freer indexed monad" XFree. It generalizes freer monad to have type indices/parameters:

It defines Functor instance for XFree f p q, XApplicative and XMonad instances for XFree f, as well as Applicative and Monad instances for XFree f p p, where f is an effect of kind k -> k -> Type -> Type

XFree simplifies defining indexed monadic computations as GADTs without making them into ad-hoc indexed monads and defining all needed applicative and monadic functions on them.

Example

Given an indexed (non-composable) effect XState that allows changing data type of the stored data and tracks these changes on the type level:

data IxdState s s' x where
  XGet :: IxdState s s s
  XPut :: s' -> IxdState s s' ()

you can make it into an indexed monad and use it with do notation (with RebindableSyntax and Control.XMonad.Do) with a few lines of boilerplate:

type XState = XFree IxdState

xGet :: XState s s s
xGet = xfree XGet

xPut :: s' -> XState s s' ()
xPut = xfree . XPut

To execute this effect you need an interpreter:

runXState :: XState s s' x -> s -> (x, s')
runXState (Pure x) s = (x, s)
runXState (Bind m j) s =
  let (x, s') = unIxdState m s in runXState (j x) s'

unIxdState :: IxdState s s' x -> (s -> (x, s'))
unIxdState XGet s = (s, s)
unIxdState (XPut s) _ = ((), s)
Synopsis

Documentation

data XFree f p q a where Source #

XFree is the freer indexed monad that wraps an (algebraic, non-composable) effect to provide Functor, XApplicative and XMonad (indexed applicative and monad) for free.

Constructors

Pure :: a -> XFree f p p a 
Bind :: f p q x -> (x -> XFree f q r a) -> XFree f p r a 
Instances
XApplicative (XFree f :: k -> k -> Type -> Type) Source # 
Instance details

Defined in Control.XFreer

Methods

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

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

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

(*>:) :: XFree f p q 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 a Source #

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 #

Monad (XFree f p p) Source #

XFree (f p p) is a normal Monad, it supports mapM, forM, sequence, etc.

Instance details

Defined in Control.XFreer

Methods

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

(>>) :: XFree f p p a -> XFree f p p b -> XFree f p p b #

return :: a -> XFree f p p a #

fail :: String -> XFree f p p a #

Functor (XFree f p q) Source # 
Instance details

Defined in Control.XFreer

Methods

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

(<$) :: a -> XFree f p q b -> XFree f p q a #

Applicative (XFree f p p) Source #

XFree (f p p) is a normal Applicative, it supports forever, traverse, sequenceA, etc.

Instance details

Defined in Control.XFreer

Methods

pure :: a -> XFree f p p a #

(<*>) :: XFree f p p (a -> b) -> XFree f p p a -> XFree f p p b #

liftA2 :: (a -> b -> c) -> XFree f p p a -> XFree f p p b -> XFree f p p c #

(*>) :: XFree f p p a -> XFree f p p b -> XFree f p p b #

(<*) :: XFree f p p a -> XFree f p p b -> XFree f p p a #

xfree :: f p q a -> XFree f p q a Source #

Function to convert an indexed effect to XFree monad (see example above)