index-core-1.0.4: Indexed Types

Safe HaskellSafe
LanguageHaskell2010

Control.IMonad.Core

Contents

Description

This module provides the IFunctor and IMonad classes which are the indexed counterparts to Functor and Monad from Control.Monad.

Synopsis

Indexed Monads

I deviate from Conor's terminology, referring to his monads on indexed types as "indexed monads" and referring to his indexed monads as "restricted monads". This module provides "indexed monads".

Indexed monads generalize the traditional approach to parametrizing the initial and final states of ordinary monads. The IMonad class does not require specifying a concrete index of kind k for the intermediate or final state of the bindI operation, permitting operations which may end in multiple possible states.

class IFunctor f where Source #

An endofunctor within the category of index-preserving functions

All instances must satisfy the functor laws:

fmapI id == id

fmapI (f . g) == fmapI f . fmapI g

Minimal complete definition

fmapI

Methods

fmapI :: (a :-> b) -> f a :-> f b Source #

Instances

Monad m => IFunctor k k (U k * m) Source # 

Methods

fmapI :: (U k * m :-> a) b -> (k :-> f a) (f b) Source #

class IFunctor m => IMonad m where Source #

An indexed monad

All instances must satisfy the monad laws:

returnI >?> f = f

f >?> returnI = f

(f >?> g) >?> h = f >?> (g >?> h)

Minimal complete definition

returnI, bindI

Methods

returnI :: a :-> m a Source #

bindI :: (a :-> m b) -> m a :-> m b Source #

Instances

Monad m => IMonad k (U k * m) Source # 

Methods

returnI :: a i -> m a i Source #

bindI :: (U k * m :-> a) (m b) -> (U k * m :-> m a) (m b) Source #

Functions

Functions derived from returnI and bindI

(?>=) :: IMonad m => m a i -> (a :-> m b) -> m b i infixl 1 Source #

An infix bindI with arguments flipped

(=<?) :: IMonad m => (a :-> m b) -> m a :-> m b infixr 1 Source #

An infix bindI

(>?>) :: IMonad m => (a :-> m b) -> (b :-> m c) -> a :-> m c infixr 1 Source #

Composition of indexed Kleisli arrows

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

(<?<) :: IMonad m => (b :-> m c) -> (a :-> m b) -> a :-> m c infixr 1 Source #

Composition of indexed Kleisli arrows

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