index-core-1.0.0: Indexed Types

Safe HaskellSafe-Infered

Control.IMonad.Restrict

Contents

Description

Restricted monads are a subset of indexed monads where the return value is restricted to a single index. They build on top of IMonad using the (:=) type constructor which restricts the index of the return value.

Synopsis

Restriction

The (:=) type constructor restricts the index that the return value inhabits.

returnR and (!>=) provide the restricted operations corresponding to returnI and (?>=). If returnI and (?>=) satisfy the monad laws, then so will returnR and (!>=):

 returnR >!> f = f

 f >!> returnR = f

 (f >!> g) >!> h = f >!> (g >!> h)

The type synonym R rearranges the type variables of the restricted monad to match conventional notation.

data (a := i) j whereSource

(a := i) represents a locked value of type a that you can only access at the index i.

V seals values of type a, restricting them to a single index i.

Constructors

V :: a -> (a := i) i 

type R m i j a = m (a := j) iSource

An indexed monad where the final index, j, is 'R'estricted

returnR :: IMonad m => a -> m (a := i) iSource

A returnI that restricts the final index

(!>=) :: IMonad m => m (a := j) i -> (a -> m (b := k) j) -> m (b := k) iSource

A flipped bindI that restricts the intermediate and final index

Functions

Functions derived from returnR and (!>=)

(=<!) :: IMonad m => (a -> m (b := k) j) -> m (a := j) i -> m (b := k) iSource

A bindI that restricts the intermediate and final index

(!>) :: IMonad m => m (a := j) i -> m (b := k) j -> m (b := k) iSource

Sequence two indexed monads

(>!>) :: IMonad m => (a -> m (b := j) i) -> (b -> m (c := k) j) -> a -> m (c := k) iSource

Composition of restricted Kleisli arrows

This is equivalent to (>>>) from Control.Category.

(<!<) :: IMonad m => (b -> m (c := k) j) -> (a -> m (b := j) i) -> a -> m (c := k) iSource

Composition of restricted Kleisli arrows

This is equivalent to (<<<) from Control.Category.

joinR :: IMonad m => m (m (a := k) j := j) i -> m (a := k) iSource

joinR joins two monad layers into one

voidR :: IMonad m => m (a := i) i -> m (() := i) iSource

Discard the result of evaluation

foreverR :: IMonad m => m (a := i) i -> m (b := j) iSource

foreverR repeats the action indefinitely

mapMR :: IMonad m => (a -> m (b := i) i) -> [a] -> m ([b] := i) iSource

"mapMR f" is equivalent to "sequenceR . map f"

mapMR_ :: IMonad m => (a -> m (b := i) i) -> [a] -> m (() := i) iSource

"mapMR_ f" is equivalent to "sequenceR_ . map f"

forMR :: IMonad m => [a] -> (a -> m (b := i) i) -> m ([b] := i) iSource

mapMR with its arguments flipped

forMR_ :: IMonad m => [a] -> (a -> m (b := i) i) -> m (() := i) iSource

mapMR_ with its arguments flipped

replicateMR :: IMonad m => Int -> m (a := i) i -> m ([a] := i) iSource

"replicateMR n m" performs m n times and collects the results

replicateMR_ :: IMonad m => Int -> m (a := i) i -> m (() := i) iSource

"replicateMR_ n m" performs m n times and ignores the results

sequenceR :: IMonad m => [m (a := i) i] -> m ([a] := i) iSource

Evaluate each action from left to right and collect the results

sequenceR_ :: IMonad m => [m (a := i) i] -> m (() := i) iSource

Evaluate each action from left to right and ignore the results

whenR :: IMonad m => Bool -> m (() := i) i -> m (() := i) iSource

"whenR p m" executes m if p is True

unlessR :: IMonad m => Bool -> m (() := i) i -> m (() := i) iSource

"unlessR p m" executes m if p is False

Interoperability

The following types and functions convert between ordinary monads and restricted monads.

Use u to convert an ordinary monad to a restricted monad so that it can be used within an indexed do block like so:

 -- Both do blocks are indexed, using syntax rebinding from Control.IMonad.Do
 do x <- indexedAction
    lift $ do
        y <- u $ ordinaryAction1 x
        u $ ordinaryAction2 x y

Use D to convert an index-preserving restricted monad into an ordinary monad so that it can be used within a normal do block.

 -- An ordinary do block (i.e. without syntax rebinding from Control.IMonad.Do)
 do x <- D $ indexPreservingAction
    D $ anotherIndexPreservingAction x

data U m a i whereSource

The U type 'U'pgrades ordinary monads to restricted monads

Constructors

U :: m (a i) -> U m a i 

Fields

unU :: m (a i)
 

Instances

Monad m => IMonad (U m) 
Monad m => IFunctor (U m) 

u :: Monad m => m a -> U m (a := i) iSource

u transforms an ordinary monad into a restricted monad

data D i m r Source

The D type 'D'owngrades index-preserving restricted monads to ordinary monads

Constructors

D 

Fields

unD :: m (r := i) i
 

Instances

IMonad m => Monad (D i m)