Copyright | (c) 2016 Allele Dev; 2017 Ixperta Solutions s.r.o.; 2017 Alexis King; 2024 Sayo Koyoneda |
---|---|
License | MPL-2.0 (see the LICENSE file) AND BSD-3-Clause (see the LICENSE.BSD3 file) |
Maintainer | ymdfield@outlook.jp |
Safe Haskell | None |
Language | GHC2021 |
Control.Monad.Hefty.Interpret
Description
This module provides functions for interpretation. Please refer to the documentation of the top-level module.
Synopsis
- runEff :: forall (m :: Type -> Type). Monad m => Eff ('[] :: [EffectH]) '[m] ~> m
- runPure :: Eff ('[] :: [EffectH]) ('[] :: [EffectF]) a -> a
- interpret :: forall (e :: Type -> Type) (ef :: [EffectF]) (eh :: [EffectH]). (e ~> Eff eh ef) -> Eff eh (e ': ef) ~> Eff eh ef
- interpretWith :: forall (e :: Type -> Type) (ef :: [EffectF]) a. Interpreter e (Eff ('[] :: [EffectH]) ef) a -> Eff ('[] :: [EffectH]) (e ': ef) a -> Eff ('[] :: [EffectH]) ef a
- interpretBy :: forall (e :: Type -> Type) (ef :: [EffectF]) ans a. (a -> Eff ('[] :: [EffectH]) ef ans) -> Interpreter e (Eff ('[] :: [EffectH]) ef) ans -> Eff ('[] :: [EffectH]) (e ': ef) a -> Eff ('[] :: [EffectH]) ef ans
- interpretRecWith :: forall e (ef :: [EffectF]) (eh :: [EffectH]) a. (forall ans x. e x -> (x -> Eff eh ef ans) -> Eff eh ef ans) -> Eff eh (e ': ef) a -> Eff eh ef a
- interpretH :: forall (e :: (Type -> Type) -> Type -> Type) (eh :: [EffectH]) (ef :: [EffectF]). HFunctor e => (e ~~> Eff eh ef) -> Eff (e ': eh) ef ~> Eff eh ef
- interpretHWith :: forall (e :: (Type -> Type) -> Type -> Type) (eh :: [EffectH]) (ef :: [EffectF]) a. HFunctor e => Interpreter (e (Eff '[e] ef)) (Eff eh ef) a -> Eff '[e] ef a -> Eff eh ef a
- interpretHBy :: forall (e :: (Type -> Type) -> Type -> Type) (eh :: [EffectH]) (ef :: [EffectF]) ans a. HFunctor e => (a -> Eff eh ef ans) -> Interpreter (e (Eff '[e] ef)) (Eff eh ef) ans -> Eff '[e] ef a -> Eff eh ef ans
- interpretRecHWith :: forall e (eh :: [(Type -> Type) -> Type -> Type]) (ef :: [EffectF]) a. HFunctor e => (forall ans x. e (Eff eh ef) x -> (x -> Eff eh ef ans) -> Eff eh ef ans) -> Eff (e ': eh) ef a -> Eff eh ef a
- reinterpret :: forall (e :: Type -> Type) (ef' :: [EffectF]) (ef :: [Type -> Type]) (eh :: [EffectH]). IsSuffixOf ef ef' => (e ~> Eff eh ef') -> Eff eh (e ': ef) ~> Eff eh ef'
- reinterpretN :: forall (n :: Natural) (e :: Type -> Type) (ef' :: [EffectF]) (ef :: [EffectF]) (eh :: [EffectH]). WeakenN n ef ef' => (e ~> Eff eh ef') -> Eff eh (e ': ef) ~> Eff eh ef'
- reinterpretWith :: forall (e :: Type -> Type) (ef' :: [EffectF]) (ef :: [Type -> Type]) (eh :: [EffectH]) a. IsSuffixOf ef ef' => Interpreter e (Eff eh ef') a -> Eff ('[] :: [EffectH]) (e ': ef) a -> Eff eh ef' a
- reinterpretNWith :: forall (n :: Natural) (e :: Type -> Type) (ef' :: [EffectF]) (ef :: [EffectF]) (eh :: [EffectH]) a. WeakenN n ef ef' => Interpreter e (Eff eh ef') a -> Eff ('[] :: [EffectH]) (e ': ef) a -> Eff eh ef' a
- reinterpretBy :: forall (e :: Type -> Type) (ef' :: [EffectF]) (ef :: [Type -> Type]) (eh :: [EffectH]) ans a. IsSuffixOf ef ef' => (a -> Eff eh ef' ans) -> Interpreter e (Eff eh ef') ans -> Eff ('[] :: [EffectH]) (e ': ef) a -> Eff eh ef' ans
- reinterpretNBy :: forall (n :: Natural) (e :: Type -> Type) (ef' :: [EffectF]) (ef :: [EffectF]) (eh :: [EffectH]) ans a. WeakenN n ef ef' => (a -> Eff eh ef' ans) -> Interpreter e (Eff eh ef') ans -> Eff ('[] :: [EffectH]) (e ': ef) a -> Eff eh ef' ans
- reinterpretRecWith :: forall e (ef' :: [EffectF]) (ef :: [EffectF]) (eh :: [EffectH]) a. IsSuffixOf ef ef' => (forall ans x. e x -> (x -> Eff eh ef' ans) -> Eff eh ef' ans) -> Eff eh (e ': ef) a -> Eff eh ef' a
- reinterpretRecNWith :: forall (n :: Natural) e (ef' :: [EffectF]) (ef :: [EffectF]) (eh :: [EffectH]) a. WeakenN n ef ef' => (forall ans x. e x -> (x -> Eff eh ef' ans) -> Eff eh ef' ans) -> Eff eh (e ': ef) a -> Eff eh ef' a
- reinterpretH :: forall (e :: (Type -> Type) -> Type -> Type) (eh :: [(Type -> Type) -> Type -> Type]) (eh' :: [EffectH]) (ef :: [EffectF]). (HFunctor e, IsSuffixOf eh eh') => (e ~~> Eff eh' ef) -> Eff (e ': eh) ef ~> Eff eh' ef
- reinterpretNH :: forall (n :: Natural) (e :: (Type -> Type) -> Type -> Type) (eh :: [EffectH]) (eh' :: [EffectH]) (ef :: [EffectF]). (HFunctor e, WeakenN n eh eh') => (e ~~> Eff eh' ef) -> Eff (e ': eh) ef ~> Eff eh' ef
- reinterpretHWith :: forall (e :: (Type -> Type) -> Type -> Type) (eh :: [EffectH]) (ef :: [EffectF]) a. HFunctor e => Interpreter (e (Eff '[e] ef)) (Eff eh ef) a -> Eff '[e] ef a -> Eff eh ef a
- reinterpretNHWith :: forall (n :: Natural) (e :: (Type -> Type) -> Type -> Type) (eh :: [EffectH]) (ef :: [EffectF]) a. (HFunctor e, WeakenN n ('[] :: [EffectH]) eh) => Interpreter (e (Eff '[e] ef)) (Eff eh ef) a -> Eff '[e] ef a -> Eff eh ef a
- reinterpretHBy :: forall (e :: (Type -> Type) -> Type -> Type) (eh :: [EffectH]) (ef :: [EffectF]) ans a. HFunctor e => (a -> Eff eh ef ans) -> Interpreter (e (Eff '[e] ef)) (Eff eh ef) ans -> Eff '[e] ef a -> Eff eh ef ans
- reinterpretNHBy :: forall (n :: Natural) (e :: (Type -> Type) -> Type -> Type) (eh :: [EffectH]) (ef :: [EffectF]) ans a. (HFunctor e, WeakenN n ('[] :: [EffectH]) eh) => (a -> Eff eh ef ans) -> Interpreter (e (Eff '[e] ef)) (Eff eh ef) ans -> Eff '[e] ef a -> Eff eh ef ans
- reinterpretRecHWith :: forall e (eh :: [(Type -> Type) -> Type -> Type]) (eh' :: [EffectH]) (ef :: [EffectF]) a. (HFunctor e, IsSuffixOf eh eh') => (forall ans x. e (Eff eh' ef) x -> (x -> Eff eh' ef ans) -> Eff eh' ef ans) -> Eff (e ': eh) ef a -> Eff eh' ef a
- reinterpretRecNHWith :: forall (n :: Natural) e (eh :: [(Type -> Type) -> Type -> Type]) (eh' :: [(Type -> Type) -> Type -> Type]) (ef :: [EffectF]) a. (HFunctor e, WeakenN n eh eh') => (forall ans x. e (Eff eh' ef) x -> (x -> Eff eh' ef ans) -> Eff eh' ef ans) -> Eff (e ': eh) ef a -> Eff eh' ef a
- interpose :: forall (e :: EffectF) (ef :: [EffectF]) (eh :: [EffectH]). e <| ef => (e ~> Eff eh ef) -> Eff eh ef ~> Eff eh ef
- interposeWith :: forall (e :: EffectF) (ef :: [EffectF]) a. e <| ef => Interpreter e (Eff ('[] :: [EffectH]) ef) a -> Eff ('[] :: [EffectH]) ef a -> Eff ('[] :: [EffectH]) ef a
- interposeBy :: forall (e :: EffectF) (ef :: [EffectF]) (eh :: [EffectH]) ans a. e <| ef => (a -> Eff eh ef ans) -> Interpreter e (Eff eh ef) ans -> Eff ('[] :: [EffectH]) ef a -> Eff eh ef ans
- interposeRecWith :: forall e (ef :: [EffectF]) (eh :: [EffectH]) a. e <| ef => (forall ans x. e x -> (x -> Eff eh ef ans) -> Eff eh ef ans) -> Eff eh ef a -> Eff eh ef a
- interposeH :: forall (e :: EffectH) (eh :: [EffectH]) (ef :: [EffectF]). (e <<| eh, HFunctor e) => (e ~~> Eff eh ef) -> Eff eh ef ~> Eff eh ef
- interposeRecHWith :: forall e (eh :: [EffectH]) (ef :: [EffectF]) a. (e <<| eh, HFunctor e) => (forall ans x. e (Eff eh ef) x -> (x -> Eff eh ef ans) -> Eff eh ef ans) -> Eff eh ef a -> Eff eh ef a
- iterEffBy :: forall (e :: Type -> Type) m ans a. Monad m => (a -> m ans) -> Interpreter e m ans -> Eff ('[] :: [EffectH]) '[e] a -> m ans
- iterEffHBy :: forall (e :: (Type -> Type) -> Type -> Type) m ans a. (Monad m, HFunctor e) => (a -> m ans) -> Interpreter (e (Eff '[e] ('[] :: [EffectF]))) m ans -> Eff '[e] ('[] :: [EffectF]) a -> m ans
- iterEffRecH :: forall (e :: (Type -> Type) -> Type -> Type) (m :: Type -> Type). (Monad m, HFunctor e) => (e ~~> m) -> Eff '[e] ('[] :: [EffectF]) ~> m
- iterEffRecHWith :: forall e m. (Monad m, HFunctor e) => (forall ans x. e m x -> (x -> m ans) -> m ans) -> Eff '[e] ('[] :: [EffectF]) ~> m
- iterEffRecHFWith :: forall eh ef m. (Monad m, HFunctor eh) => (forall ans x. eh m x -> (x -> m ans) -> m ans) -> (forall ans x. ef x -> (x -> m ans) -> m ans) -> Eff '[eh] '[ef] ~> m
- iterEffHFBy :: forall (eh :: (Type -> Type) -> Type -> Type) (ef :: EffectF) m ans a. (Monad m, HFunctor eh) => (a -> m ans) -> Interpreter (eh (Eff '[eh] '[ef])) m ans -> Interpreter ef m ans -> Eff '[eh] '[ef] a -> m ans
- iterAllEffHFBy :: forall (eh :: [EffectH]) (ef :: [EffectF]) m ans a. Monad m => (a -> m ans) -> Interpreter (UnionH eh (Eff eh ef)) m ans -> Interpreter (Union ef) m ans -> Eff eh ef a -> m ans
- iterAllEffHF :: forall (eh :: [EffectH]) (ef :: [EffectF]) (m :: Type -> Type). Monad m => (UnionH eh ~~> m) -> (Union ef ~> m) -> Eff eh ef ~> m
- splitLayer :: forall (ef :: [EffectF]) (eh :: [EffectH]) x. Eff ('[] :: [EffectH]) ef x -> Eff eh '[Eff ('[] :: [EffectH]) ef] x
- mergeLayer :: forall (eh :: [EffectH]) (ef :: [EffectF]) x. Eff eh '[Eff eh ef] x -> Eff eh ef x
- stateless :: forall (e :: Type -> Type) (m :: Type -> Type) ans. Monad m => (e ~> m) -> Interpreter e m ans
- qApp :: forall (eh :: [EffectH]) (ef :: [EffectF]) a b. FTCQueue (Eff eh ef) a b -> a -> Eff eh ef b
Running Eff
runEff :: forall (m :: Type -> Type). Monad m => Eff ('[] :: [EffectH]) '[m] ~> m Source #
Lowers the computation into a monad m
by treating the effect as a monad.
runPure :: Eff ('[] :: [EffectH]) ('[] :: [EffectF]) a -> a Source #
Extracts the value from a computation that contains only pure values without any effect.
Standard interpretation functions
For first-order effects
Arguments
:: forall (e :: Type -> Type) (ef :: [EffectF]) (eh :: [EffectH]). (e ~> Eff eh ef) | Effect handler |
-> Eff eh (e ': ef) ~> Eff eh ef |
Interprets the first-order effect e
at the head of the list using the provided natural transformation style handler.
Arguments
:: forall (e :: Type -> Type) (ef :: [EffectF]) a. Interpreter e (Eff ('[] :: [EffectH]) ef) a | Effect handler |
-> Eff ('[] :: [EffectH]) (e ': ef) a | |
-> Eff ('[] :: [EffectH]) ef a |
Interprets the first-order effect e
at the head of the list using the provided continuational stateful handler.
Arguments
:: forall (e :: Type -> Type) (ef :: [EffectF]) ans a. (a -> Eff ('[] :: [EffectH]) ef ans) | Value handler |
-> Interpreter e (Eff ('[] :: [EffectH]) ef) ans | Effect handler |
-> Eff ('[] :: [EffectH]) (e ': ef) a | |
-> Eff ('[] :: [EffectH]) ef ans |
Interprets the first-order effect e
at the head of the list using the provided value handler and continuational stateful handler.
Arguments
:: forall e (ef :: [EffectF]) (eh :: [EffectH]) a. (forall ans x. e x -> (x -> Eff eh ef ans) -> Eff eh ef ans) | Effect handler |
-> Eff eh (e ': ef) a | |
-> Eff eh ef a |
Interprets the first-order effect e
at the head of the list using the provided continuational stateful handler.
Interpretation is performed recursively with respect to the scopes of unelaborated higher-order effects eh
.
Note that during interpretation, the continuational state is reset (delimited) and does not persist beyond scopes.
For higher-order effects
Arguments
:: forall (e :: (Type -> Type) -> Type -> Type) (eh :: [EffectH]) (ef :: [EffectF]). HFunctor e | |
=> (e ~~> Eff eh ef) | Effect elaborator |
-> Eff (e ': eh) ef ~> Eff eh ef |
Interprets the higher-order effect e
at the head of the list using the provided natural transformation style elaborator.
Arguments
:: forall (e :: (Type -> Type) -> Type -> Type) (eh :: [EffectH]) (ef :: [EffectF]) a. HFunctor e | |
=> Interpreter (e (Eff '[e] ef)) (Eff eh ef) a | Effect elaborator |
-> Eff '[e] ef a | |
-> Eff eh ef a |
Interprets the single higher-order effect e
using the provided continuational stateful elaborator.
Arguments
:: forall (e :: (Type -> Type) -> Type -> Type) (eh :: [EffectH]) (ef :: [EffectF]) ans a. HFunctor e | |
=> (a -> Eff eh ef ans) | Value handler |
-> Interpreter (e (Eff '[e] ef)) (Eff eh ef) ans | Effect elaborator |
-> Eff '[e] ef a | |
-> Eff eh ef ans |
Interprets the single higher-order effect e
using the provided value handler and continuational stateful elaborator.
Arguments
:: forall e (eh :: [(Type -> Type) -> Type -> Type]) (ef :: [EffectF]) a. HFunctor e | |
=> (forall ans x. e (Eff eh ef) x -> (x -> Eff eh ef ans) -> Eff eh ef ans) | Effect elaborator |
-> Eff (e ': eh) ef a | |
-> Eff eh ef a |
Interprets the higher-order effect e
at the head of the list using the provided continuational stateful elaborator.
Interpretation is performed recursively with respect to the scopes of unelaborated higher-order effects eh
.
Note that during interpretation, the continuational state is reset (delimited) and does not persist beyond scopes.
Reinterpretation functions
For first-order effects
reinterpret :: forall (e :: Type -> Type) (ef' :: [EffectF]) (ef :: [Type -> Type]) (eh :: [EffectH]). IsSuffixOf ef ef' => (e ~> Eff eh ef') -> Eff eh (e ': ef) ~> Eff eh ef' Source #
reinterpretN :: forall (n :: Natural) (e :: Type -> Type) (ef' :: [EffectF]) (ef :: [EffectF]) (eh :: [EffectH]). WeakenN n ef ef' => (e ~> Eff eh ef') -> Eff eh (e ': ef) ~> Eff eh ef' Source #
reinterpretWith :: forall (e :: Type -> Type) (ef' :: [EffectF]) (ef :: [Type -> Type]) (eh :: [EffectH]) a. IsSuffixOf ef ef' => Interpreter e (Eff eh ef') a -> Eff ('[] :: [EffectH]) (e ': ef) a -> Eff eh ef' a Source #
reinterpretNWith :: forall (n :: Natural) (e :: Type -> Type) (ef' :: [EffectF]) (ef :: [EffectF]) (eh :: [EffectH]) a. WeakenN n ef ef' => Interpreter e (Eff eh ef') a -> Eff ('[] :: [EffectH]) (e ': ef) a -> Eff eh ef' a Source #
reinterpretBy :: forall (e :: Type -> Type) (ef' :: [EffectF]) (ef :: [Type -> Type]) (eh :: [EffectH]) ans a. IsSuffixOf ef ef' => (a -> Eff eh ef' ans) -> Interpreter e (Eff eh ef') ans -> Eff ('[] :: [EffectH]) (e ': ef) a -> Eff eh ef' ans Source #
reinterpretNBy :: forall (n :: Natural) (e :: Type -> Type) (ef' :: [EffectF]) (ef :: [EffectF]) (eh :: [EffectH]) ans a. WeakenN n ef ef' => (a -> Eff eh ef' ans) -> Interpreter e (Eff eh ef') ans -> Eff ('[] :: [EffectH]) (e ': ef) a -> Eff eh ef' ans Source #
reinterpretRecWith :: forall e (ef' :: [EffectF]) (ef :: [EffectF]) (eh :: [EffectH]) a. IsSuffixOf ef ef' => (forall ans x. e x -> (x -> Eff eh ef' ans) -> Eff eh ef' ans) -> Eff eh (e ': ef) a -> Eff eh ef' a Source #
reinterpretRecNWith :: forall (n :: Natural) e (ef' :: [EffectF]) (ef :: [EffectF]) (eh :: [EffectH]) a. WeakenN n ef ef' => (forall ans x. e x -> (x -> Eff eh ef' ans) -> Eff eh ef' ans) -> Eff eh (e ': ef) a -> Eff eh ef' a Source #
For higher-order effects
reinterpretH :: forall (e :: (Type -> Type) -> Type -> Type) (eh :: [(Type -> Type) -> Type -> Type]) (eh' :: [EffectH]) (ef :: [EffectF]). (HFunctor e, IsSuffixOf eh eh') => (e ~~> Eff eh' ef) -> Eff (e ': eh) ef ~> Eff eh' ef Source #
reinterpretNH :: forall (n :: Natural) (e :: (Type -> Type) -> Type -> Type) (eh :: [EffectH]) (eh' :: [EffectH]) (ef :: [EffectF]). (HFunctor e, WeakenN n eh eh') => (e ~~> Eff eh' ef) -> Eff (e ': eh) ef ~> Eff eh' ef Source #
reinterpretHWith :: forall (e :: (Type -> Type) -> Type -> Type) (eh :: [EffectH]) (ef :: [EffectF]) a. HFunctor e => Interpreter (e (Eff '[e] ef)) (Eff eh ef) a -> Eff '[e] ef a -> Eff eh ef a Source #
reinterpretNHWith :: forall (n :: Natural) (e :: (Type -> Type) -> Type -> Type) (eh :: [EffectH]) (ef :: [EffectF]) a. (HFunctor e, WeakenN n ('[] :: [EffectH]) eh) => Interpreter (e (Eff '[e] ef)) (Eff eh ef) a -> Eff '[e] ef a -> Eff eh ef a Source #
reinterpretHBy :: forall (e :: (Type -> Type) -> Type -> Type) (eh :: [EffectH]) (ef :: [EffectF]) ans a. HFunctor e => (a -> Eff eh ef ans) -> Interpreter (e (Eff '[e] ef)) (Eff eh ef) ans -> Eff '[e] ef a -> Eff eh ef ans Source #
reinterpretNHBy :: forall (n :: Natural) (e :: (Type -> Type) -> Type -> Type) (eh :: [EffectH]) (ef :: [EffectF]) ans a. (HFunctor e, WeakenN n ('[] :: [EffectH]) eh) => (a -> Eff eh ef ans) -> Interpreter (e (Eff '[e] ef)) (Eff eh ef) ans -> Eff '[e] ef a -> Eff eh ef ans Source #
reinterpretRecHWith :: forall e (eh :: [(Type -> Type) -> Type -> Type]) (eh' :: [EffectH]) (ef :: [EffectF]) a. (HFunctor e, IsSuffixOf eh eh') => (forall ans x. e (Eff eh' ef) x -> (x -> Eff eh' ef ans) -> Eff eh' ef ans) -> Eff (e ': eh) ef a -> Eff eh' ef a Source #
reinterpretRecNHWith :: forall (n :: Natural) e (eh :: [(Type -> Type) -> Type -> Type]) (eh' :: [(Type -> Type) -> Type -> Type]) (ef :: [EffectF]) a. (HFunctor e, WeakenN n eh eh') => (forall ans x. e (Eff eh' ef) x -> (x -> Eff eh' ef ans) -> Eff eh' ef ans) -> Eff (e ': eh) ef a -> Eff eh' ef a Source #
Interposition functions
For first-order effects
Arguments
:: forall (e :: EffectF) (ef :: [EffectF]) (eh :: [EffectH]). e <| ef | |
=> (e ~> Eff eh ef) | Effect handler |
-> Eff eh ef ~> Eff eh ef |
Reinterprets (hooks) the first-order effect e
in the list using the provided natural transformation style handler.
If multiple instances of e
exist in the list, the one closest to the head (with the smallest index) will be targeted.
Arguments
:: forall (e :: EffectF) (ef :: [EffectF]) a. e <| ef | |
=> Interpreter e (Eff ('[] :: [EffectH]) ef) a | Effect handler |
-> Eff ('[] :: [EffectH]) ef a | |
-> Eff ('[] :: [EffectH]) ef a |
Reinterprets (hooks) the first-order effect e
in the list using the provided continuational stateful handler.
If multiple instances of e
exist in the list, the one closest to the head (with the smallest index) will be targeted.
Arguments
:: forall (e :: EffectF) (ef :: [EffectF]) (eh :: [EffectH]) ans a. e <| ef | |
=> (a -> Eff eh ef ans) | Value handler |
-> Interpreter e (Eff eh ef) ans | Effect handler |
-> Eff ('[] :: [EffectH]) ef a | |
-> Eff eh ef ans |
Reinterprets (hooks) the first-order effect e
in the list using the provided value handler and continuational stateful handler.
If multiple instances of e
exist in the list, the one closest to the head (with the smallest index) will be targeted.
Arguments
:: forall e (ef :: [EffectF]) (eh :: [EffectH]) a. e <| ef | |
=> (forall ans x. e x -> (x -> Eff eh ef ans) -> Eff eh ef ans) | Effect handler |
-> Eff eh ef a | |
-> Eff eh ef a |
Reinterprets (hooks) the first-order effect e
in the list using the provided continuational stateful handler.
Interpretation is performed recursively with respect to the scopes of unelaborated higher-order effects eh
.
Note that during interpretation, the continuational state is reset (delimited) and does not persist beyond scopes.
If multiple instances of e
exist in the list, the one closest to the head (with the smallest index) will be targeted.
For higher-order effects
Arguments
:: forall (e :: EffectH) (eh :: [EffectH]) (ef :: [EffectF]). (e <<| eh, HFunctor e) | |
=> (e ~~> Eff eh ef) | Effect elaborator |
-> Eff eh ef ~> Eff eh ef |
Reinterprets (hooks) the higher-order effect e
in the list using the provided natural transformation style elaborator.
If multiple instances of e
exist in the list, the one closest to the head (with the smallest index) will be targeted.
Arguments
:: forall e (eh :: [EffectH]) (ef :: [EffectF]) a. (e <<| eh, HFunctor e) | |
=> (forall ans x. e (Eff eh ef) x -> (x -> Eff eh ef ans) -> Eff eh ef ans) | Effect elaborator |
-> Eff eh ef a | |
-> Eff eh ef a |
Reinterprets (hooks) the higher-order effect e
in the list using the provided continuational stateful elaborator.
Interpretation is performed recursively with respect to the scopes of unelaborated higher-order effects eh
.
Note that during interpretation, the continuational state is reset (delimited) and does not persist beyond scopes.
If multiple instances of e
exist in the list, the one closest to the head (with the smallest index) will be targeted.
Transformation to monads
Arguments
:: forall (e :: Type -> Type) m ans a. Monad m | |
=> (a -> m ans) | Value handler |
-> Interpreter e m ans | Effect handler |
-> Eff ('[] :: [EffectH]) '[e] a | |
-> m ans |
Traverses a computation containing only a single first-order effect e
using the provided value handler and continuational stateful handler, transforming it into a monad m
.
Arguments
:: forall (e :: (Type -> Type) -> Type -> Type) m ans a. (Monad m, HFunctor e) | |
=> (a -> m ans) | Value handler |
-> Interpreter (e (Eff '[e] ('[] :: [EffectF]))) m ans | Effect handler |
-> Eff '[e] ('[] :: [EffectF]) a | |
-> m ans |
Traverses a computation containing only a single higher-order effect e
using the provided value handler and continuational stateful elaborator, transforming it into a monad m
.
Arguments
:: forall (e :: (Type -> Type) -> Type -> Type) (m :: Type -> Type). (Monad m, HFunctor e) | |
=> (e ~~> m) | Effect elaborator |
-> Eff '[e] ('[] :: [EffectF]) ~> m |
Traverses a computation containing only a single higher-order effect e
using the provided natural transformation elaborator, transforming it into a monad m
.
Traversal is performed recursively with respect to the scope of the higher-order effect e
.
Note that during traversal, the continuational state is reset (delimited) and does not persist beyond scopes.
Arguments
:: forall e m. (Monad m, HFunctor e) | |
=> (forall ans x. e m x -> (x -> m ans) -> m ans) | Effect elaborator |
-> Eff '[e] ('[] :: [EffectF]) ~> m |
Traverses a computation containing only a single higher-order effect e
using the provided continuational stateful elaborator, transforming it into a monad m
.
Traversal is performed recursively with respect to the scope of the higher-order effect e
.
Note that during traversal, the continuational state is reset (delimited) and does not persist beyond scopes.
Arguments
:: forall eh ef m. (Monad m, HFunctor eh) | |
=> (forall ans x. eh m x -> (x -> m ans) -> m ans) | Effect elaborator |
-> (forall ans x. ef x -> (x -> m ans) -> m ans) | Effect handler |
-> Eff '[eh] '[ef] ~> m |
Traverses a computation containing only higher-order effects eh
and first-order effects ef
using the provided continuational stateful elaborator, transforming it into a monad m
.
Traversal is performed recursively with respect to the scopes of higher-order effects. Note that during traversal, the continuational state is reset (delimited) and does not persist beyond scopes.
Arguments
:: forall (eh :: (Type -> Type) -> Type -> Type) (ef :: EffectF) m ans a. (Monad m, HFunctor eh) | |
=> (a -> m ans) | Value handler |
-> Interpreter (eh (Eff '[eh] '[ef])) m ans | Effect elaborator |
-> Interpreter ef m ans | Effect handler |
-> Eff '[eh] '[ef] a | |
-> m ans |
Traverses a computation containing only higher-order effects eh
and first-order effects ef
using the provided value handler,
continuational stateful elaborator, and handler, transforming it into a monad m
.
Arguments
:: forall (eh :: [EffectH]) (ef :: [EffectF]) m ans a. Monad m | |
=> (a -> m ans) | Value handler |
-> Interpreter (UnionH eh (Eff eh ef)) m ans | Effect elaborator |
-> Interpreter (Union ef) m ans | Effect handler |
-> Eff eh ef a | |
-> m ans |
Traverses all effects using the provided value handler, continuational stateful elaborator, and handler, transforming them into a monad m
.
Arguments
:: forall (eh :: [EffectH]) (ef :: [EffectF]) (m :: Type -> Type). Monad m | |
=> (UnionH eh ~~> m) | Effect elaborator |
-> (Union ef ~> m) | Effect handler |
-> Eff eh ef ~> m |
Traverses all effects using the provided natural-transformation style elaborator and handler, transforming them into a monad m
.
Layer manipulation
splitLayer :: forall (ef :: [EffectF]) (eh :: [EffectH]) x. Eff ('[] :: [EffectH]) ef x -> Eff eh '[Eff ('[] :: [EffectH]) ef] x Source #
mergeLayer :: forall (eh :: [EffectH]) (ef :: [EffectF]) x. Eff eh '[Eff eh ef] x -> Eff eh ef x Source #