cleff-0.1.0.0: Fast and concise extensible effects
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

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.

Handler types

data SendSite e esSend Source #

The send-site environment.

Constructors

SendSite 

Fields

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

The typeclass that indicates 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.

Minimal complete definition

Nothing

Methods

sendSite :: SendSite e esSend Source #

Obtain the send-site environment.

hdlPtr :: Handling e es esSend => MemPtr InternalHandler e Source #

Get the pointer to the current effect handler itself.

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

Get the send-site Env.

newtype InstHandling e es esSend a Source #

Newtype wrapper for instantiating the Handling typeclass locally, a la the reflection trick. We do not use the reflection library directly so as not to expose this piece of implementation detail to the user.

Constructors

InstHandling (Handling e es esSend => a) 

instHandling :: forall e es esSend a. (Handling e es esSend => a) -> SendSite e esSend -> a Source #

Instantiate an Handling typeclass, i.e. pass an implicit send-site environment in. This function shouldn't be directly used anyhow.

type Handler e es = forall esSend. Handling e es esSend => 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

mkInternalHandler :: MemPtr InternalHandler e -> Env es -> Handler e es -> InternalHandler e Source #

Transform a Handler into an InternalHandler given a pointer that is going to point to the InternalHandler and the current Env.

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' 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 while being able to leave it unhandled (i.e. you can resend the effects in the handler).

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.

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.

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

Common implementation of transform and translate. It is overly general on its own so it is not exported in Cleff.

Combinators for interpreting higher effects

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

Run a computation in the current effect stack. This is useful for interpreting higher-order effects, like a bracketing effect:

data Resource m a where
  Bracket :: m a -> (a -> m ()) -> (a -> m b) -> Resource m b
Bracket alloc dealloc use ->
  bracket
    (toEff alloc)
    (toEff . dealloc)
    (toEff . use)

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

Run a computation in the current effect stack, but handles the current effect inside the computation differently by providing a new Handler. 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 e es esSend => ((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 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.