effects-0.1: Computational Effects

Control.Effects

Contents

Synopsis

Running effects

Here's an example how to use the state effect from Control.Effects.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 -> (Proxy (ContT e m) -> ContT e m a) -> m rSource

with takes a handler and creates a new Proxy (effect identifier). The Proxy is passed on to a function which can use it to do operations with it.

run :: Identity a -> aSource

Unwrap the result of the top-level effect.

Defining effects

Here's and example how to define the state effect from Control.Effects.State.

 ref :: Monad m => s -> Handler (s -> m a) a m a
 ref s_init = Handler
   { ret = return . return . return
   , fin = \f -> f s_init
   }

 get p   = operation p $ \k -> return $ \s -> do r <- k s; r s
 put p s = operation p $ \k -> return $ \_ -> do r <- k (); r s

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 narmally be left polymorphic, it's the monad that handles the other effects.

Constructors

Handler 

Fields

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

operation :: forall c m n a e. (c ~ ContT e m, AutoLift c n) => Proxy c -> ((a -> m e) -> m e) -> n aSource

Define an operation, which is autolifted so it can be used inside other effects.

I/O

runIO :: IO () -> IO ()Source

Variant of run that allows I/O effects. (Just the identity function, but it helps the type checker.)

io :: AutoLift IO n => IO a -> n aSource

Convert an IO action to an I/O effect operation.

Effects machinery

data ContT r m a

The continuation monad transformer. Can be used to add continuation handling to other monads.

Instances

AutoLift' m1 m2 n1 n2 => AutoLift' m1 m2 (ContT r1 n1) (ContT r2 n2) 
(AutoLift' m1 m2 Identity n, Monad m2) => AutoLift' m1 (ContT r m2) Identity (ContT s n) 
(AutoLift' m1 m2 IO n, Monad m2) => AutoLift' m1 (ContT r m2) IO (ContT s n) 
MonadTrans (ContT r) 
Monad (ContT r m) 
Functor (ContT r m) 
Applicative (ContT r m) 
MonadIO m => MonadIO (ContT r m) 

data Proxy m Source

class AutoLift m1 m2 Source

Instances

AutoLift' m1 m2 m1 m2 => AutoLift m1 m2