effect-monad-0.8.0.0: Embeds effect systems and program logics into Haskell using graded monads and parameterised monads

Safe HaskellNone
LanguageHaskell98

Control.Effect

Synopsis

Documentation

class Effect (m :: k -> * -> *) where Source #

Specifies "parametric effect monads" which are essentially monads but annotated by a type-level monoid formed by Plus and Unit

Minimal complete definition

return, (>>=)

Associated Types

type Unit m :: k Source #

Effect of a trivially effectful computation |

type Plus m (f :: k) (g :: k) :: k Source #

Cominbing effects of two subcomputations |

type Inv m (f :: k) (g :: k) :: Constraint Source #

Inv provides a way to give instances of Effect their own constraints for >>=

Methods

return :: a -> m (Unit m) a Source #

Effect-parameterised version of return. Annotated with the 'Unit m' effect, denoting pure compuation

(>>=) :: Inv m f g => m f a -> (a -> m g b) -> m (Plus m f g) b Source #

Effect-parameterise version of >>= (bind). Combines two effect annotations f and g on its parameter computations into Plus

(>>) :: Inv m f g => m f a -> m g b -> m (Plus m f g) b Source #

Instances

Effect Nat Counter Source # 

Associated Types

type Unit Counter (m :: Counter -> * -> *) :: k Source #

type Plus Counter (m :: Counter -> * -> *) (f :: Counter) (g :: Counter) :: k Source #

type Inv Counter (m :: Counter -> * -> *) (f :: Counter) (g :: Counter) :: Constraint Source #

Methods

return :: a -> m (Unit Counter m) a Source #

(>>=) :: Inv Counter m f g => m f a -> (a -> m g b) -> m (Plus Counter m f g) b Source #

(>>) :: Inv Counter m f g => m f a -> m g b -> m (Plus Counter m f g) b Source #

Effect [*] State Source # 

Associated Types

type Unit State (m :: State -> * -> *) :: k Source #

type Plus State (m :: State -> * -> *) (f :: State) (g :: State) :: k Source #

type Inv State (m :: State -> * -> *) (f :: State) (g :: State) :: Constraint Source #

Methods

return :: a -> m (Unit State m) a Source #

(>>=) :: Inv State m f g => m f a -> (a -> m g b) -> m (Plus State m f g) b Source #

(>>) :: Inv State m f g => m f a -> m g b -> m (Plus State m f g) b Source #

Effect [*] Reader Source # 

Associated Types

type Unit Reader (m :: Reader -> * -> *) :: k Source #

type Plus Reader (m :: Reader -> * -> *) (f :: Reader) (g :: Reader) :: k Source #

type Inv Reader (m :: Reader -> * -> *) (f :: Reader) (g :: Reader) :: Constraint Source #

Methods

return :: a -> m (Unit Reader m) a Source #

(>>=) :: Inv Reader m f g => m f a -> (a -> m g b) -> m (Plus Reader m f g) b Source #

(>>) :: Inv Reader m f g => m f a -> m g b -> m (Plus Reader m f g) b Source #

Effect [*] WriteOnce Source # 

Associated Types

type Unit WriteOnce (m :: WriteOnce -> * -> *) :: k Source #

type Plus WriteOnce (m :: WriteOnce -> * -> *) (f :: WriteOnce) (g :: WriteOnce) :: k Source #

type Inv WriteOnce (m :: WriteOnce -> * -> *) (f :: WriteOnce) (g :: WriteOnce) :: Constraint Source #

Methods

return :: a -> m (Unit WriteOnce m) a Source #

(>>=) :: Inv WriteOnce m f g => m f a -> (a -> m g b) -> m (Plus WriteOnce m f g) b Source #

(>>) :: Inv WriteOnce m f g => m f a -> m g b -> m (Plus WriteOnce m f g) b Source #

Effect [Mapping Symbol *] Reader Source # 

Associated Types

type Unit Reader (m :: Reader -> * -> *) :: k Source #

type Plus Reader (m :: Reader -> * -> *) (f :: Reader) (g :: Reader) :: k Source #

type Inv Reader (m :: Reader -> * -> *) (f :: Reader) (g :: Reader) :: Constraint Source #

Methods

return :: a -> m (Unit Reader m) a Source #

(>>=) :: Inv Reader m f g => m f a -> (a -> m g b) -> m (Plus Reader m f g) b Source #

(>>) :: Inv Reader m f g => m f a -> m g b -> m (Plus Reader m f g) b Source #

Effect [Mapping Symbol *] Writer Source # 

Associated Types

type Unit Writer (m :: Writer -> * -> *) :: k Source #

type Plus Writer (m :: Writer -> * -> *) (f :: Writer) (g :: Writer) :: k Source #

type Inv Writer (m :: Writer -> * -> *) (f :: Writer) (g :: Writer) :: Constraint Source #

Methods

return :: a -> m (Unit Writer m) a Source #

(>>=) :: Inv Writer m f g => m f a -> (a -> m g b) -> m (Plus Writer m f g) b Source #

(>>) :: Inv Writer m f g => m f a -> m g b -> m (Plus Writer m f g) b Source #

Effect (Maybe *) Update Source # 

Associated Types

type Unit Update (m :: Update -> * -> *) :: k Source #

type Plus Update (m :: Update -> * -> *) (f :: Update) (g :: Update) :: k Source #

type Inv Update (m :: Update -> * -> *) (f :: Update) (g :: Update) :: Constraint Source #

Methods

return :: a -> m (Unit Update m) a Source #

(>>=) :: Inv Update m f g => m f a -> (a -> m g b) -> m (Plus Update m f g) b Source #

(>>) :: Inv Update m f g => m f a -> m g b -> m (Plus Update m f g) b Source #

Effect * Counter Source # 

Associated Types

type Unit Counter (m :: Counter -> * -> *) :: k Source #

type Plus Counter (m :: Counter -> * -> *) (f :: Counter) (g :: Counter) :: k Source #

type Inv Counter (m :: Counter -> * -> *) (f :: Counter) (g :: Counter) :: Constraint Source #

Methods

return :: a -> m (Unit Counter m) a Source #

(>>=) :: Inv Counter m f g => m f a -> (a -> m g b) -> m (Plus Counter m f g) b Source #

(>>) :: Inv Counter m f g => m f a -> m g b -> m (Plus Counter m f g) b Source #

Effect * IMaybe Source # 

Associated Types

type Unit IMaybe (m :: IMaybe -> * -> *) :: k Source #

type Plus IMaybe (m :: IMaybe -> * -> *) (f :: IMaybe) (g :: IMaybe) :: k Source #

type Inv IMaybe (m :: IMaybe -> * -> *) (f :: IMaybe) (g :: IMaybe) :: Constraint Source #

Methods

return :: a -> m (Unit IMaybe m) a Source #

(>>=) :: Inv IMaybe m f g => m f a -> (a -> m g b) -> m (Plus IMaybe m f g) b Source #

(>>) :: Inv IMaybe m f g => m f a -> m g b -> m (Plus IMaybe m f g) b Source #

Effect * Vector Source # 

Associated Types

type Unit Vector (m :: Vector -> * -> *) :: k Source #

type Plus Vector (m :: Vector -> * -> *) (f :: Vector) (g :: Vector) :: k Source #

type Inv Vector (m :: Vector -> * -> *) (f :: Vector) (g :: Vector) :: Constraint Source #

Methods

return :: a -> m (Unit Vector m) a Source #

(>>=) :: Inv Vector m f g => m f a -> (a -> m g b) -> m (Plus Vector m f g) b Source #

(>>) :: Inv Vector m f g => m f a -> m g b -> m (Plus Vector m f g) b Source #

Monad m => Effect * (Monad m) Source # 

Associated Types

type Unit (Monad m) (m :: Monad m -> * -> *) :: k Source #

type Plus (Monad m) (m :: Monad m -> * -> *) (f :: Monad m) (g :: Monad m) :: k Source #

type Inv (Monad m) (m :: Monad m -> * -> *) (f :: Monad m) (g :: Monad m) :: Constraint Source #

Methods

return :: a -> m (Unit (Monad m) m) a Source #

(>>=) :: Inv (Monad m) m f g => m f a -> (a -> m g b) -> m (Plus (Monad m) m f g) b Source #

(>>) :: Inv (Monad m) m f g => m f a -> m g b -> m (Plus (Monad m) m f g) b Source #

Effect (Morph * *) T Source # 

Associated Types

type Unit T (m :: T -> * -> *) :: k Source #

type Plus T (m :: T -> * -> *) (f :: T) (g :: T) :: k Source #

type Inv T (m :: T -> * -> *) (f :: T) (g :: T) :: Constraint Source #

Methods

return :: a -> m (Unit T m) a Source #

(>>=) :: Inv T m f g => m f a -> (a -> m g b) -> m (Plus T m f g) b Source #

(>>) :: Inv T m f g => m f a -> m g b -> m (Plus T m f g) b Source #

class Subeffect (m :: k -> * -> *) f g where Source #

Specifies subeffecting behaviour

Minimal complete definition

sub

Methods

sub :: m f a -> m g a Source #

Instances

Submap s t => Subeffect [Mapping Symbol *] Reader s t Source #

If s is a subset of t then, s is a subeffect of t

Methods

sub :: s t a -> s g a Source #

Supermap s t => Subeffect [Mapping Symbol *] Writer s t Source # 

Methods

sub :: s t a -> s g a Source #