cleff-0.3.2.0: Fast and concise extensible effects
Copyright(c) 2021 Xy Ren
LicenseBSD3
Maintainerxy.r@outlook.com
Stabilityunstable
Portabilitynon-portable (GHC only)
Safe HaskellNone
LanguageHaskell2010

Cleff.Internal.Interpret

Description

This module contains functions for interpreting effects. Most of the times you won't need to import this directly; the module Cleff reexports most of the functionalities.

This is an internal module and its API may change even between minor versions. Therefore you should be extra careful if you're to depend on this module.

Synopsis

Trivial handling

adjust :: forall es es'. (Rec es' -> Rec es) -> Eff es ~> Eff es' Source #

Adjust the effect stack by a contravariant transformation function over the stack. This function reveals the profunctorial nature of Eff; in particular, Eff is a profunctor [Effect] -> Type, lmap is adjust, and rmap is fmap.

raise :: forall e es. Eff es ~> Eff (e ': es) Source #

Lift a computation into a bigger effect stack with one more effect. For a more general version see raiseN.

raiseN :: forall es' es. KnownList es' => Eff es ~> Eff (es' ++ es) Source #

Lift a computation into a bigger effect stack with arbitrarily more effects. This function requires TypeApplications.

inject :: forall es' es. Subset es' es => Eff es' ~> Eff es Source #

Lift a computation with a fixed, known effect stack into some superset of the stack.

subsume :: forall e es. e :> es => Eff (e ': es) ~> Eff es Source #

Eliminate a duplicate effect from the top of the effect stack. For a more general version see subsumeN.

subsumeN :: forall es' es. Subset es' es => Eff (es' ++ es) ~> Eff es Source #

Eliminate several duplicate effects from the top of the effect stack. This function requires TypeApplications.

raiseUnder :: forall e' e es. Eff (e ': es) ~> Eff (e ': (e' ': es)) Source #

Like raise, but adds the new effect under the top effect. This is useful for transforming an interpreter e' :> es => Eff (e : es) ~> Eff es into a reinterpreter Eff (e : es) ~> Eff (e' : es):

myInterpreter :: Bar :> es => Eff (Foo : es) ~> Eff es
myInterpreter = ...

myReinterpreter :: Eff (Foo : es) ~> Eff (Bar : es)
myReinterpreter = myInterpreter . raiseUnder

In other words,

reinterpret h == interpret h . raiseUnder

However, note that this function is suited for transforming an existing interpreter into a reinterpreter; if you want to define a reinterpreter from scratch, you should still prefer reinterpret, which is both easier to use and more efficient.

Since: 0.2.0.0

raiseNUnder :: forall es' e es. KnownList es' => Eff (e ': es) ~> Eff (e ': (es' ++ es)) Source #

Like raiseUnder, but allows introducing multiple effects. This function requires TypeApplications.

Since: 0.2.0.0

raiseUnderN :: forall e es' es. KnownList es' => Eff (es' ++ es) ~> Eff (es' ++ (e ': es)) Source #

Like raiseUnder, but allows introducing the effect under multiple effects. This function requires TypeApplications.

Since: 0.2.0.0

raiseNUnderN :: forall es'' es' es. (KnownList es', KnownList es'') => Eff (es' ++ es) ~> Eff (es' ++ (es'' ++ es)) Source #

A generalization of both raiseUnderN and raiseNUnder, allowing introducing multiple effects under multiple effects. This function requires TypeApplications and is subject to serious type ambiguity; you most likely will need to supply all three type variables explicitly.

Since: 0.2.0.0

Handler types

class Handling esSend e es | esSend -> e es Source #

The typeclass that denotes a handler scope, handling effect e sent from the effect stack esSend in the effect stack es.

You should not define instances for this typeclass whatsoever.

esSend :: Handling esSend e es => Env esSend Source #

Get the send-site Env.

type Handler e es = forall esSend. Handling esSend e es => e (Eff esSend) ~> Eff es Source #

The type of an effect handler, which is a function that transforms an effect e from an arbitrary effect stack into computations in the effect stack es.

type Translator e e' = forall esSend. e (Eff esSend) ~> e' (Eff esSend) Source #

The type of a simple transformation function from effect e to e'.

Interpreting effects

interpret :: forall e es. Handler e es -> Eff (e ': es) ~> Eff es Source #

Interpret an effect e in terms of effects in the effect stack es with an effect handler.

reinterpret :: forall e' e es. Handler e (e' ': es) -> Eff (e ': es) ~> Eff (e' ': es) Source #

Like interpret, but adds a new effect e' to the stack that can be used in the handler.

reinterpret2 :: forall e' e'' e es. Handler e (e' ': (e'' ': es)) -> Eff (e ': es) ~> Eff (e' ': (e'' ': es)) Source #

Like reinterpret, but adds two new effects.

reinterpret3 :: forall e' e'' e''' e es. Handler e (e' ': (e'' ': (e''' ': es))) -> Eff (e ': es) ~> Eff (e' ': (e'' ': (e''' ': es))) Source #

Like reinterpret, but adds three new effects.

reinterpretN :: forall es' e es. KnownList es' => Handler e (es' ++ es) -> Eff (e ': es) ~> Eff (es' ++ es) Source #

Like reinterpret, but adds arbitrarily many new effects. This function requires TypeApplications.

interpose :: forall e es. e :> es => Handler e es -> Eff es ~> Eff es Source #

Respond to an effect, but does not eliminate it from the stack. This means you can re-send the operations in the effect handler; it is often useful when you need to "intercept" operations so you can add extra behaviors like logging.

impose :: forall e' e es. e :> es => Handler e (e' ': es) -> Eff es ~> Eff (e' ': es) Source #

Like interpose, but allows to introduce one new effect to use in the handler.

imposeN :: forall es' e es. (KnownList es', e :> es) => Handler e (es' ++ es) -> Eff es ~> Eff (es' ++ es) Source #

Like impose, but allows introducing arbitrarily many effects. This requires TypeApplications.

Translating effects

transform :: forall e e' es. e' :> es => Translator e e' -> Eff (e ': es) ~> Eff es Source #

Interpret an effect in terms of another effect in the stack via a simple Translator.

transform trans = interpret (sendVia toEff . trans)

translate :: forall e e' es. Translator e e' -> Eff (e ': es) ~> Eff (e' ': es) Source #

Like transform, but instead of using an effect in stack, add a new one to the top of it.

translate trans = reinterpret (sendVia toEff . trans)

Combinators for interpreting higher effects

toEff :: Handling esSend e es => Eff esSend ~> Eff es Source #

Run a computation in the current effect stack; this is useful for interpreting higher-order effects. For example, if you want to interpret a bracketing effects in terms of IO:

data Resource m a where
  Bracket :: m a -> (a -> m ()) -> (a -> m b) -> Resource m b

You will not be able to simply write this for the effect:

runBracket :: IOE :> es => Eff (Resource : es) a -> Eff es a
runBracket = interpret \case
  Bracket alloc dealloc use -> UnliftIO.bracket alloc dealloc use

This is because effects are sended from all kinds of stacks that has Resource in it, so effect handlers received the effect as Resource esSend a, where esSend is an arbitrary stack with Resource, instead of Resource es a. This means alloc, dealloc and use are of type Eff esSend a, while bracket can only take and return Eff es a. So we need to use toEff, which converts an Eff esSend a into an Eff es a:

runBracket :: IOE :> es => Eff (Resource : es) a -> Eff es a
runBracket = interpret \case
  Bracket alloc dealloc use -> UnliftIO.bracket
    (toEff alloc)
    (toEff . dealloc)
    (toEff . use)

toEffWith :: forall esSend e es. Handling esSend e es => Handler e es -> Eff esSend ~> Eff es Source #

Run a computation in the current effect stack, just like toEff, but takes a Handler of the current effect being interpreted, so that inside the computation being ran, the effect is interpreted differently. This is useful for interpreting effects with local contexts, like Local:

runReader :: r -> Eff (Reader r : es) ~> Eff es
runReader x = interpret (handle x)
  where
    handle :: r -> Handler (Reader r) es
    handle r = \case
      Ask       -> pure r
      Local f m -> toEffWith (handle $ f r) m

withFromEff :: Handling esSend e es => ((Eff es ~> Eff esSend) -> Eff esSend a) -> Eff es a Source #

Temporarily gain the ability to lift some Eff es actions into Eff esSend. This is only useful for dealing with effect operations with the monad type in the negative position, which means it's unlikely that you need to use this function in implementing your effects.