effects-0.2.4: Computational Effects

Safe HaskellSafe
LanguageHaskell98

Control.Effects

Contents

Synopsis

Running effects

Here's an example how to use the state effect from State:

example :: Int
example = run $ do
  with (ref 10) $ \u -> do
    val <- get u
    put u (val + 5)
    get u

with :: Monad m => Handler e r m a -> (Effect e m -> Layer e m a) -> m r Source #

with takes a handler and creates a new effect instance. The Effect is passed on to a function which can use it to do operations with it.

run :: Base Pure a -> a Source #

Unwrap the result of the top-level effect.

Defining effects

Here's and example how to define the state effect from Writer:

writer :: (Monad m, Monoid w) => Handler (w, a) (w, a) m a
writer = Handler
  { ret = \a -> return (mempty, a)
  , fin = return
  }

tell :: (AutoLift (w, r) m n, Monoid w) => Effect (w, r) m -> w -> n ()
tell p v = operation p $ \k -> do
  (w, r) <- k ()
  return (mappend v w, r)

data Handler e r m a Source #

A Handler e r m a is a handler of effects with type e. The ret field provides a function to lift pure values into the effect. The fin field provides a function to extract a final value of type r from the effect. The parameter m should normally be left polymorphic, it's the monad that handles the other effects.

Constructors

Handler 

Fields

  • ret :: a -> m e
     
  • fin :: e -> m r
     

operation :: AutoLift e m n => Effect e m -> ((a -> m e) -> m e) -> n a Source #

operation takes an effect identifier generated by with and a function which takes a continuation as parameter. The result is auto-lifted so it can be used inside any other effect.

Base monad

The effects are layered on top of a base monad. Here's an example how to use IO as a base monad:

exampleIO :: IO ()
exampleIO = runBase $ do
  with (ref 5) $ \x -> do
    val <- get x
    base $ print val

runBase :: Base m a -> m a Source #

Unwrap the result of a computation using a base monad.

base :: AutoLiftBase m n => m a -> n a Source #

base takes a computation in the base monad and auto-lifts it so it can be used inside any effect.

Effects machinery

Effects are layered in a stack on top of a base monad. Just like with monad transformers, operations lower in the stack need to be lifted to be able to be used together with operations higher in the stack. But as there are only two monads in play, Layer and Base, and because each operation is identified with exactly one layer using the Effect type, lifting can be done automatically.

The following types and classes show up in the type signatures. The compiler should be able to infer them for you.

newtype Layer e m a Source #

Layer e m is a monad that adds an effect e to the underlying monad m. (It is the continuation monad transformer with a friendlier name.)

Constructors

Layer 

Fields

Instances
(Applicative m, Monad m, AutoLiftInternal (Layer e m) (Layer d n) (Layer e m) (Layer d n)) => AutoLift e m (Layer d n) Source # 
Instance details

Defined in Control.Effects

Methods

operation' :: Effect e m -> ((a -> m e) -> m e) -> Layer d n a

(Applicative m, Monad m, AutoLiftInternal (Base m) (Layer e n) (Base m) (Layer e n)) => AutoLiftBase m (Layer e n) Source # 
Instance details

Defined in Control.Effects

Methods

base' :: m a -> Layer e n a

Monad (Layer e m) Source # 
Instance details

Defined in Control.Effects

Methods

(>>=) :: Layer e m a -> (a -> Layer e m b) -> Layer e m b #

(>>) :: Layer e m a -> Layer e m b -> Layer e m b #

return :: a -> Layer e m a #

fail :: String -> Layer e m a #

Functor (Layer e m) Source # 
Instance details

Defined in Control.Effects

Methods

fmap :: (a -> b) -> Layer e m a -> Layer e m b #

(<$) :: a -> Layer e m b -> Layer e m a #

Applicative (Layer e m) Source # 
Instance details

Defined in Control.Effects

Methods

pure :: a -> Layer e m a #

(<*>) :: Layer e m (a -> b) -> Layer e m a -> Layer e m b #

liftA2 :: (a -> b -> c) -> Layer e m a -> Layer e m b -> Layer e m c #

(*>) :: Layer e m a -> Layer e m b -> Layer e m b #

(<*) :: Layer e m a -> Layer e m b -> Layer e m a #

(Monoid e, Applicative m) => Alternative (Layer e m) Source # 
Instance details

Defined in Control.Effects

Methods

empty :: Layer e m a #

(<|>) :: Layer e m a -> Layer e m a -> Layer e m a #

some :: Layer e m a -> Layer e m [a] #

many :: Layer e m a -> Layer e m [a] #

(Monoid e, Applicative m) => MonadPlus (Layer e m) Source # 
Instance details

Defined in Control.Effects

Methods

mzero :: Layer e m a #

mplus :: Layer e m a -> Layer e m a -> Layer e m a #

newtype Base m a Source #

Base m is a newtype wrapper around a monadic computation.

Constructors

Base (m a) 
Instances
(Applicative m, Applicative n, Monad m, Monad n, AutoLiftInternal (Layer e m) (Base n) (Layer e m) (Base n)) => AutoLift e m (Base n) Source # 
Instance details

Defined in Control.Effects

Methods

operation' :: Effect e m -> ((a -> m e) -> m e) -> Base n a

(Applicative m, Applicative n, Monad m, Monad n, AutoLiftInternal (Base m) (Base n) (Base m) (Base n)) => AutoLiftBase m (Base n) Source # 
Instance details

Defined in Control.Effects

Methods

base' :: m a -> Base n a

Monad m => Monad (Base m) Source # 
Instance details

Defined in Control.Effects

Methods

(>>=) :: Base m a -> (a -> Base m b) -> Base m b #

(>>) :: Base m a -> Base m b -> Base m b #

return :: a -> Base m a #

fail :: String -> Base m a #

Functor m => Functor (Base m) Source # 
Instance details

Defined in Control.Effects

Methods

fmap :: (a -> b) -> Base m a -> Base m b #

(<$) :: a -> Base m b -> Base m a #

Applicative m => Applicative (Base m) Source # 
Instance details

Defined in Control.Effects

Methods

pure :: a -> Base m a #

(<*>) :: Base m (a -> b) -> Base m a -> Base m b #

liftA2 :: (a -> b -> c) -> Base m a -> Base m b -> Base m c #

(*>) :: Base m a -> Base m b -> Base m b #

(<*) :: Base m a -> Base m b -> Base m a #

newtype Pure a Source #

Pure is the identity monad and is used when no other base monad is needed.

Constructors

Pure a 
Instances
Monad Pure Source # 
Instance details

Defined in Control.Effects

Methods

(>>=) :: Pure a -> (a -> Pure b) -> Pure b #

(>>) :: Pure a -> Pure b -> Pure b #

return :: a -> Pure a #

fail :: String -> Pure a #

Functor Pure Source # 
Instance details

Defined in Control.Effects

Methods

fmap :: (a -> b) -> Pure a -> Pure b #

(<$) :: a -> Pure b -> Pure a #

Applicative Pure Source # 
Instance details

Defined in Control.Effects

Methods

pure :: a -> Pure a #

(<*>) :: Pure (a -> b) -> Pure a -> Pure b #

liftA2 :: (a -> b -> c) -> Pure a -> Pure b -> Pure c #

(*>) :: Pure a -> Pure b -> Pure b #

(<*) :: Pure a -> Pure b -> Pure a #

data Effect e (m :: * -> *) Source #

Effect e m is a proxy for the type checker to be able to work with multiple effects at the same time.

class (Applicative m, Applicative n, Monad m, Monad n) => AutoLift e m n Source #

Minimal complete definition

operation'

Instances
(Applicative m, Applicative n, Monad m, Monad n, AutoLiftInternal (Layer e m) (Base n) (Layer e m) (Base n)) => AutoLift e m (Base n) Source # 
Instance details

Defined in Control.Effects

Methods

operation' :: Effect e m -> ((a -> m e) -> m e) -> Base n a

(Applicative m, Monad m, AutoLiftInternal (Layer e m) (Layer d n) (Layer e m) (Layer d n)) => AutoLift e m (Layer d n) Source # 
Instance details

Defined in Control.Effects

Methods

operation' :: Effect e m -> ((a -> m e) -> m e) -> Layer d n a

class (Applicative m, Applicative n, Monad m, Monad n) => AutoLiftBase m n Source #

Minimal complete definition

base'

Instances
(Applicative m, Applicative n, Monad m, Monad n, AutoLiftInternal (Base m) (Base n) (Base m) (Base n)) => AutoLiftBase m (Base n) Source # 
Instance details

Defined in Control.Effects

Methods

base' :: m a -> Base n a

(Applicative m, Monad m, AutoLiftInternal (Base m) (Layer e n) (Base m) (Layer e n)) => AutoLiftBase m (Layer e n) Source # 
Instance details

Defined in Control.Effects

Methods

base' :: m a -> Layer e n a