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

Synopsis

Documentation

data Eff (w :: Maybe *) where Source #

Parametric effect update monad. A bit like a writer monad specialised to the Maybe monoid, providing a single memory cell that can be updated, but with heterogeneous behaviour. Provides an effect system that explains whether a single memory cell has been updated or not

Constructors

Put :: a -> Eff (Just a) 
NoPut :: Eff Nothing 

data Update w a Source #

Constructors

Update 

Fields

Instances

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 #

type Unit (Maybe *) Update Source # 
type Inv (Maybe *) Update s t Source # 
type Inv (Maybe *) Update s t = ()
type Plus (Maybe *) Update s (Nothing *) Source # 
type Plus (Maybe *) Update s (Nothing *) = s
type Plus (Maybe *) Update s (Just * t) Source # 
type Plus (Maybe *) Update s (Just * t) = Just * t

put :: a -> Update (Just a) () Source #

Update the memory cell with a new value of type a