| Copyright | (c) 2021 Ningning Xie Daan Leijen |
|---|---|
| License | MIT |
| Maintainer | xnning@hku.hk; daan@microsoft.com |
| Stability | Experimental |
| Safe Haskell | None |
| Language | Haskell2010 |
Control.Mp.Eff
Description
Efficient effect handlers based on Evidence passing semantics. The implementation is based on "Generalized Evidence Passing for Effect Handlers", Ningning Xie and Daan Leijen, 2021 (pdf), The implementation is closely based on the Ev.Eff library described in detail in "Effect Handlers in Haskell, Evidently", Ningning Xie and Daan Leijen, Haskell 2020 (pdf). The _Mp.Eff_ and _Ev.Eff_ libraries expose the exact same interface, but the _Mp.Eff_ library can express full effect handler semantics, including non-scoped resumptions -- it is slightly slower though (see the 2021 paper for benchmarks and a detailed comparison).
An example of defining and using a Reader effect:
{-# LANGUAGE TypeOperators, FlexibleContexts, Rank2Types #-}
import Control.Mp.Eff
-- A Reader effect definition with one operation ask of type () to a.
data Reader a e ans = Reader{ ask :: Op () a e ans }
greet :: (Reader String :? e) => Eff e String
greet = do s <- perform ask ()
return ("hello " ++ s)
test :: String
test = runEff $
handler (Reader{ ask = value "world" }) $ -- :: Reader String () Int
do s <- greet -- executes in context :: Eff (Reader String :* ()) Int
return (length s)
Enjoy,
Ningning Xie and Daan Leijen, Mar 2021.
Synopsis
- data Eff e a
- runEff :: Eff () a -> a
- type (:?) h e = In h e
- data (h :: * -> * -> *) :* e
- perform :: In h e => (forall e' ans. h e' ans -> Op a b e' ans) -> a -> Eff e b
- handler :: h e ans -> Eff (h :* e) ans -> Eff e ans
- handlerRet :: (ans -> a) -> h e a -> Eff (h :* e) ans -> Eff e a
- handlerHide :: h (h' :* e) ans -> Eff (h :* e) ans -> Eff (h' :* e) ans
- mask :: Eff e ans -> Eff (h :* e) ans
- data Op a b e ans
- value :: a -> Op () a e ans
- function :: (a -> Eff e b) -> Op a b e ans
- except :: (a -> Eff e ans) -> Op a b e ans
- operation :: (a -> (b -> Eff e ans) -> Eff e ans) -> Op a b e ans
- data Local a e ans
- local :: a -> Eff (Local a :* e) ans -> Eff e ans
- localRet :: a -> (ans -> a -> b) -> Eff (Local a :* e) ans -> Eff e b
- handlerLocal :: a -> h (Local a :* e) ans -> Eff (h :* e) ans -> Eff e ans
- handlerLocalRet :: a -> (ans -> a -> b) -> h (Local a :* e) b -> Eff (h :* e) ans -> Eff e b
- lget :: Local a e ans -> Op () a e ans
- lput :: Local a e ans -> Op a () e ans
- lmodify :: Local a e ans -> Op (a -> a) () e ans
- localGet :: Eff (Local a :* e) a
- localPut :: a -> Eff (Local a :* e) ()
- localModify :: (a -> a) -> Eff (Local a :* e) ()
Effect monad
Effect context
Perform and Handlers
mask :: Eff e ans -> Eff (h :* e) ans Source #
Mask the top effect handler in the give action (i.e. if a operation is performed
on an h effect inside e the top handler is ignored).
Defining operations
The abstract type of operations of type a to b, for a handler
defined in an effect context e and answer type ans.
value :: a -> Op () a e ans Source #
Create an operation that always resumes with a constant value (of type a).
(see also the perform example).
function :: (a -> Eff e b) -> Op a b e ans Source #
Create an operation that takes an argument of type a and always resumes with a result of type b.
These are called tail-resumptive operations and are implemented more efficient than
general operations as they can execute in-place (instead of yielding to the handler).
Most operations are tail-resumptive. (See also the handlerLocal example).
except :: (a -> Eff e ans) -> Op a b e ans Source #
Create an operation that never resumes (an exception).
(See handlerRet for an example).
operation :: (a -> (b -> Eff e ans) -> Eff e ans) -> Op a b e ans Source #
Create an fully general operation from type a to b.
the function f takes the argument, and a resumption function of type b ->
that can be called to resume from the original call site. For example:Eff e ans
data Amb e ans = Amb { flip :: forall b. Op () Bool e ans }
xor :: (Amb :? e) => Eff e Bool
xor = do x <- perform flip ()
y <- perform flip ()
return ((x && not y) || (not x && y))
solutions :: Eff (Amb :* e) a -> Eff e [a]
solutions = handlerRet (\x -> [x]) $
Amb{ flip = operation (\() k -> do{ xs <- k True; ys <- k False; return (xs ++ ys)) }) }
Local state
The type of the built-in state effect.
(This state is generally more efficient than rolling your own and usually
used in combination with handlerLocal to provide local isolated state)
local :: a -> Eff (Local a :* e) ans -> Eff e ans Source #
Create a local state handler with an initial state of type a.
localRet :: a -> (ans -> a -> b) -> Eff (Local a :* e) ans -> Eff e b Source #
Create a local state handler with an initial state of type a,
with a return function to combine the final result with the final state to a value of type b.
handlerLocal :: a -> h (Local a :* e) ans -> Eff (h :* e) ans -> Eff e ans Source #
Create a new handler for h which can access the locally isolated state .
This is fully local to the handler Local ah only and not visible in the action as
apparent from its effect context (which does not contain ).Local a
data State a e ans = State { get :: Op () a e ans, put :: Op a () e ans }
state :: a -> Eff (State a :* e) ans -> Eff e ans
state init = handlerLocal init (State{ get = function (\_ -> perform lget ()),
put = function (\x -> perform lput x) })
test = runEff $
state (41::Int) $
inc -- see :?
handlerLocalRet :: a -> (ans -> a -> b) -> h (Local a :* e) b -> Eff (h :* e) ans -> Eff e b Source #
Create a new handler for h which can access the locally isolated state .
This is fully local to the handler Local ah only and not visible in the action as
apparent from its effect context (which does not contain ). The
Local aret argument can be used to transform the final result combined with the final state.