heftia-0.7.0.0: higher-order algebraic effects done right
Copyright(c) 2016 Allele Dev; 2017 Ixperta Solutions s.r.o.; 2017 Alexis King; 2024 Sayo contributors
LicenseMPL-2.0 AND BSD-3-Clause (see the LICENSE and LICENSE.BSD3 files)
Maintainerymdfield@outlook.jp
Safe HaskellNone
LanguageGHC2021

Control.Monad.Hefty.Interpret

Description

This module provides functions for interpretation. Please refer to the documentation of the top-level module.

Synopsis

Documentation

runEff :: forall (m :: Type -> Type). Monad m => Eff '[Emb m] ~> m Source #

Lowers the computation into a monad m by treating the effect as a monad.

runPure :: Eff ('[] :: [Effect]) a -> a Source #

Extracts the value from a computation that contains only pure values without any effect.

interpretWith :: forall (e :: Effect) (es :: [Effect]) a. (KnownOrder e, FOEs es) => AlgHandler e (Eff (e ': es)) (Eff es) a -> Eff (e ': es) a -> Eff es a Source #

Interprets the effect e at the head of the list using the provided algebraic handler.

interpretBy :: forall (e :: Effect) (es :: [Effect]) ans a. (KnownOrder e, FOEs es) => (a -> Eff es ans) -> AlgHandler e (Eff (e ': es)) (Eff es) ans -> Eff (e ': es) a -> Eff es ans Source #

Interprets the effect e at the head of the list using the provided value handler and algebraic handler.

interpretsBy :: forall (es :: [Effect]) (r :: [Effect]) ans a. (FOEs r, KnownLength es) => (a -> Eff r ans) -> AlgHandler (Union es) (Eff (es ++ r)) (Eff r) ans -> Eff (es ++ r) a -> Eff r ans Source #

reinterpretBy :: forall (e :: Effect) (es :: [Effect]) (es' :: [Effect]) ans a. (KnownOrder e, FOEs es, Suffix es es') => (a -> Eff es' ans) -> AlgHandler e (Eff (e ': es)) (Eff es') ans -> Eff (e ': es) a -> Eff es' ans Source #

reinterpretsBy :: forall (es :: [Effect]) (r :: [Effect]) (r' :: [Effect]) ans a. (FOEs r, Suffix r r', KnownLength es) => (a -> Eff r' ans) -> AlgHandler (Union es) (Eff (es ++ r)) (Eff r') ans -> Eff (es ++ r) a -> Eff r' ans Source #

reinterpretWith :: forall (e :: Effect) (es' :: [Effect]) (es :: [Effect]) a. (Suffix es es', KnownOrder e, FOEs es) => AlgHandler e (Eff (e ': es)) (Eff es') a -> Eff (e ': es) a -> Eff es' a Source #

interposeBy Source #

Arguments

:: forall (e :: Effect) (es :: [Effect]) ans a. (e :> es, FOEs es) 
=> (a -> Eff es ans)

Value handler

-> AlgHandler e (Eff es) (Eff es) ans

Effect handler

-> Eff es a 
-> Eff es ans 

Reinterprets (hooks) the effect e in the list using the provided value handler and algebraic handler.

interposeOnBy Source #

Arguments

:: forall {k} (key :: k) (e :: Effect) (es :: [Effect]) ans a. (Has key e es, FOEs es) 
=> (a -> Eff es ans)

Value handler

-> AlgHandler e (Eff es) (Eff es) ans

Effect handler

-> Eff es a 
-> Eff es ans 

Reinterprets (hooks) the effect e in the list using the provided value handler and algebraic handler.

interposeInBy Source #

Arguments

:: forall (e :: Effect) (es :: [Effect]) ans a. (In e es, FOEs es) 
=> (a -> Eff es ans)

Value handler

-> AlgHandler e (Eff es) (Eff es) ans

Effect handler

-> Eff es a 
-> Eff es ans 

Reinterprets (hooks) the effect e in the list using the provided value handler and algebraic handler.

interposeWith Source #

Arguments

:: forall (e :: Effect) (es :: [Effect]) a. (e :> es, FOEs es) 
=> AlgHandler e (Eff es) (Eff es) a

Effect handler

-> Eff es a 
-> Eff es a 

Reinterprets (hooks) the effect e in the list using the provided algebraic handler.

interposeOnWith Source #

Arguments

:: forall {k} (key :: k) (e :: Effect) (es :: [Effect]) a. (Has key e es, FOEs es) 
=> AlgHandler e (Eff es) (Eff es) a

Effect handler

-> Eff es a 
-> Eff es a 

Reinterprets (hooks) the effect e in the list using the provided algebraic handler.

interposeInWith Source #

Arguments

:: forall (e :: Effect) (es :: [Effect]) a. (In e es, FOEs es) 
=> AlgHandler e (Eff es) (Eff es) a

Effect handler

-> Eff es a 
-> Eff es a 

Reinterprets (hooks) the effect e in the list using the provided algebraic handler.

interposeForWith Source #

Arguments

:: forall (e :: Effect) (es :: [Effect]) a. (KnownOrder e, FOEs es) 
=> Membership e es 
-> AlgHandler e (Eff es) (Eff es) a

Effect handler

-> Eff es a 
-> Eff es a 

Reinterprets (hooks) the effect e in the list using the provided algebraic handler.

interposeForBy Source #

Arguments

:: forall (e :: Effect) (es :: [Effect]) ans a. (KnownOrder e, FOEs es) 
=> Membership e es 
-> (a -> Eff es ans)

Value handler

-> AlgHandler e (Eff es) (Eff es) ans

Effect handler

-> Eff es a 
-> Eff es ans 

stateless :: forall (e :: (Type -> Type) -> Type -> Type) (m :: Type -> Type) (n :: Type -> Type) ans. Monad n => (e m ~> n) -> AlgHandler e m n ans Source #

Lifts a stateless handler into a algebraic handler.

interposeIn :: forall (e :: Effect) (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (In e es, Free c ff) => (e ~~> Eff ff es) -> Eff ff es a -> Eff ff es a #

interpret :: forall (e :: Effect) (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (KnownOrder e, Free c ff) => (e ~~> Eff ff es) -> Eff ff (e ': es) a -> Eff ff es a #

reinterpret :: forall (e :: Effect) (es :: [Effect]) (es' :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (Suffix es es', KnownOrder e, Free c ff) => (e ~~> Eff ff es') -> Eff ff (e ': es) a -> Eff ff es' a #

interprets :: forall (es :: [Effect]) (r :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (KnownLength es, Free c ff) => (Union es ~~> Eff ff r) -> Eff ff (es ++ r) a -> Eff ff r a #

reinterprets :: forall (es :: [Effect]) (r :: [Effect]) (r' :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (Suffix r r', KnownLength es, Free c ff) => (Union es (Eff ff r') ~> Eff ff r') -> Eff ff (es ++ r) a -> Eff ff r' a #

interpose :: forall (e :: Effect) (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (e :> es, Free c ff) => (e ~~> Eff ff es) -> Eff ff es a -> Eff ff es a #

interposeOn :: forall {k} (key :: k) (e :: Effect) (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (Has key e es, Free c ff) => (e ~~> Eff ff es) -> Eff ff es a -> Eff ff es a #

interposeFor :: forall (e :: Effect) (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (KnownOrder e, Free c ff) => Membership e es -> (e ~~> Eff ff es) -> Eff ff es a -> Eff ff es a #

preinterpose :: forall (e :: Effect) (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (e :> es, Free c ff) => (e ~~> Eff ff es) -> Eff ff es a -> Eff ff es a #

preinterposeOn :: forall {k} (key :: k) (e :: Effect) (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (Has key e es, Free c ff) => (e ~~> Eff ff es) -> Eff ff es a -> Eff ff es a #

preinterposeIn :: forall (e :: Effect) (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (In e es, Free c ff) => (e ~~> Eff ff es) -> Eff ff es a -> Eff ff es a #

preinterposeFor :: forall (e :: Effect) (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (KnownOrder e, Free c ff) => Membership e es -> (e ~~> Eff ff es) -> Eff ff es a -> Eff ff es a #

interpretAll :: forall (es :: [Effect]) (es' :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). Free c ff => (Union es ~~> Eff ff es') -> Eff ff es a -> Eff ff es' a #

iterAllEff :: forall (es :: [Effect]) f (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (Free c ff, c f) => (Union es ~~> f) -> Eff ff es a -> f a #