| Copyright | (c) 2024-2025 Sayo contributors |
|---|---|
| License | MPL-2.0 (see the LICENSE file) |
| Maintainer | ymdfield@outlook.jp |
| Safe Haskell | None |
| Language | GHC2021 |
Control.Monad.Hefty
Description
Heftia is an extensible effects library that generalizes "Algebraic Effects and Handlers" to higher-order effects, providing users with maximum flexibility and delivering standard and reasonable speed. In its generalization, the focus is on ensuring predictable results based on simple, consistent semantics, while preserving soundness.
Basic Usage
The following is an example of defining, using, and interpreting the first-order
effect Log for logging and the higher-order effect Span for representing
named spans in a program.
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE TemplateHaskell #-}
import Control.Monad.Hefty
import Prelude hiding (log, span)
data Log :: Effect where
Log :: String -> Log f ()
makeEffectF ''Log
data Span :: Effect where
Span :: String -> f a -> Span f a
makeEffectH ''Span
runLog :: (Emb IO :> es) => Eff (Log ': es) ~> Eff es
runLog = interpret \(Log msg) -> liftIO $ putStrLn $ "[LOG] " <> msg
runSpan :: (Emb IO :> es) => Eff (Span ': es) ~> Eff es
runSpan = interpret \(Span name m) -> do
liftIO $ putStrLn $ "[Start span '" <> name <> "']"
r <- m
liftIO $ putStrLn $ "[End span '" <> name <> "']"
pure r
prog :: IO ()
prog = runEff . runLog . runSpan $ do
span "example program" do
log "foo"
span "greeting" do
log "hello"
log "world"
log "bar"
>>> prog
[Start span 'example program']
[LOG] foo
[Start span 'greeting']
[LOG] hello
[LOG] world
[End span 'greeting']
[LOG] bar
[End span 'example program']
- When defining effects, you use the Template Haskell functions
makeEffectFandmakeEffectH.
Algebraic Handler
An interpreter function that realizes features related to the continuation in algebraic effects.
It is a function that takes two arguments: an effectful operation and a continuation, which is the continuation of the computation from that operation, and returns the computation up to the end of the computation being interpreted.
By ignoring the continuation argument, it allows for global escapes like the Throw effect.
runThrow :: (FOEses) =>Eff(e ': es) a ->ThrowEffes (Eithere a) runThrow =interpretBy(pure.Right) handleThrow handleThrow ::Applicativeg =>AlgHandler(e) f g (ThrowEithere a) handleThrow (e) _ =Throwpure$Lefte
Here, handleThrow is the algebraic handler for the Throw effect.
By calling the continuation argument multiple times, it allows for non-deterministic computations like the Data.Effect.NonDet effect.
runNonDet :: (Alternativef) =>Eff(':ChooseEmpty': es) a ->Effes (f a) runNonDet =interpretsBy(pure.pure) $ (\k ->ChooseliftA2(<|>) (kFalse) (kTrue))!:(\_ ->Emptypureempty)!:nil
The function passed as the second argument to interpretBy/interpretsBy is the algebraic handler.
Additionally, what is passed as the first argument to interpretBy/interpretsBy is called a value handler.
This extends the continuation in the computation being interpreted.
We shall call the state of computation that emerges through algebraic interpretation and behaves according to continuation-based semantics a "algebraic state".
Naming Rules for Interpretation Functions
Functions may additionally have
WithorByat the end of their names.- These provide functionality equivalent to "Algebraic Effects and Handlers," meaning they offer access to delimited continuations during interpretation.
- Functions in the
Byfamily take two arguments: a value handler and a algebraic effect handler. They are the most generalized form. - Functions in the
Withfamily omit the value handler and take only the effect interpreter as an argument. - The difference between
interpretBy ret f mandinterpretWith f m >>= retis that, during interpretation, the delimited continuation passed as the second argumentktofin the former extends up to whenretfinishes, whereas in the latter, it only goes untilmfinishes (just beforeret), soretis not included ink. - Functions without
WithorBycannot manipulate continuations; therefore, you cannot maintain internal state or perform behaviors like global escapes or non-deterministic computations during interpretation.
Semantics of effects
Consider the following example.
data SomeEff :: Effect where
SomeAction :: SomeEff m a
makeEffectF ''SomeEff
-- | Throws an exception when 'SomeAction' is encountered
runSomeEff :: (Throw String :> es) => Eff (SomeEff ': es) ~> Eff es
runSomeEff = interpret \SomeAction -> throw "not caught"
-- | Catches the exception if 'someAction' results in one
action :: (SomeEff :> es, Catch String :> es, Throw String :> es) => Eff es String
action = someAction `catch` \(_ :: String) -> pure "caught"
prog1 :: IO ()
prog1 = runPure . runThrow . runCatch . runSomeEff $ action
>>> prog1
Right "caught"
prog2 :: IO ()
prog2 = runPure . runThrow . runSomeEff . runCatch $ action
>>> prog2
Left "not caught"
When applying runCatch after runSomeEff in prog1, the exception is caught, but in the reverse order, it is not caught.
We will now explain this behavior to understand it.
In Heftia, the behavior of higher-order effects is based on reduction semantics—that is, term rewriting semantics similar to those in "Algebraic Effects and Handlers." By properly understanding and becoming familiar with this semantics, users can quickly and easily predict execution results.
Let's revisit the definition of runCatch:
runCatch :: (e `Throw` es,InFOEses) =>Eff(e ': es)Catch~>Effes runCatch =interprethandleCatch handleCatch :: (e `Throw` es,InFOEses) =>Catche~~>Effes handleCatch (action hdl) = action &CatchinterposeWith\(e) _ -> hdl eThrow
When runCatch encounters code like ... (action `catch` hdl) ... in the program, it rewrites that part to ... (interposeWith (\(Throw e) _ -> hdl e) action) ....
In general, functions like interpret and interpose behave this way—they recursively rewrite the target higher-order effects according to the given handler.
Rewriting proceeds from the deepest scope toward the outer scopes.
The same applies to first-order effects. Handling an effect means rewriting the effects that appear in the program.
With this in mind, let's follow the rewriting step by step.
Looking at prog1.
First, when runSomeEff is applied to action:
runSomeEff action =interpret(\SomeAction ->throw"not caught") $ someAction `` \(_ :: String) ->catchpure"caught" ==>throw"not caught" `` \(_ :: String) ->catchpure"caught"
The program is rewritten into a program like the above.
Next, when runCatch is applied to this, it evaluates to:
runCatch $throw"not caught" `` \(_ :: String) ->catchpure"caught" ==>interposeWith(\(e) _ ->Throwpure"caught") $throw"not caught" ==>pure"caught"
In this way, the exception is caught.
On the other hand, in prog2, when runCatch is applied to action:
runCatch action = runCatch $ someAction `` \(_ :: String) ->catchpure"caught" ==>interposeWith(\(e) _ ->Throwpure"caught") $ someAction
At this point, since there is no throw in the computation
that is the target of interposeWith (only someAction appears, which is not
throw!), interposeWith does nothing because there is no
throw to rewrite:
==> someAction
Therefore, when runSomeEff is applied:
runSomeEff someAction
==> throw "not caught"
Thus, the exception remains as is.
In other words, in prog2, at the point of runCatch, it is impossible for runCatch to know that someAction will later be rewritten into throw.
Interpreters decide what to do based only on the current state of the program's rewriting. They do not change the result based on any other information.
This is all there is to the reduction semantics of algebraic effects.
Independence from IO Semantics
As seen in the initial example with logs and spans, IO operations are embedded as effects.
Not limited to IO, any monad can be embedded as an effect.
Embedded IO can be viewed as instruction scripts, and to avoid confusion when using Heftia, it should be regarded as such.
Rather than thinking "Haskell represents side effects via a type-level tag called IO", it's better to think:
- Haskell is a purely functional language where you cannot write anything other than pure functions.
IOis just an opaque algebraic data type whose definition you cannot see, but no different from others.- The runtime system treats the value
mainas a sequence of instructions to be executed on the CPU. - Programming with side effects in Haskell is meta-programming where you write a pure function program that outputs
IO-typed instruction scripts.
In fact, the semantics of effects in Heftia are completely isolated from the level of IO.
Considerations at the IO level, such as "asynchronous exceptions might be thrown",
"what is the current state of exception masking", or
"this state/environment value is local and not shared between threads", have no influence on effect interpretation and need not be considered.
IO is just a data type representing programs with side effects, and we are merely meta-programming it.
The consistent semantics of algebraic effects prevent leaks of abstraction from the IO level.
This is a significant difference from IO-fused effect system libraries like effectful and cleff.
Interpreting Multiple Effects Simultaneously
For example, consider a situation where you want to use multiple Catch effects simultaneously.
The following is a case where both String and Int appear as exception types:
prog ::Eff'[String,CatchInt,CatchString,ThrowInt] ()Throw
In this case, you may get stuck trying to use runCatch.
This is because runCatch has the following type signature:
runCatch :: (e `Throw` es,InFOEses) =>Eff(e ': es)Catch~>Effes
You cannot write runCatch . runCatch. It requires the higher-order effects to be exhausted after interpretation:
runCatch . runCatch $ prog
^^^^^^^^
• No instance for ‘Data.Effect.FirstOrder (Catch Int)’
arising from a use of ‘runCatch’
• In the second argument of ‘(.)’, namely ‘runCatch’
In the first argument of ‘($)’, namely ‘runCatch . runCatch’
In the expression: runCatch . runCatch $ progIn situations like this, where you want to perform algebraic interpretation on multiple higher-order effects simultaneously, you generally cannot reduce the higher-order effect list step by step or via multi-staging. Instead, you need to interpret all of them at once simultaneously.
This is possible by interprets family and pattern matching on the open union using the !: operator.
prog' ::Eff'[String,ThrowInt] () prog' =Throwinterprets(handleCatch!:handleCatch!:nil) prog
Synopsis
- type Eff = Eff Freer
- data Freer (f :: Type -> Type) a
- type ($) (f :: Type -> Type) a = f a
- type ($$) (h :: (Type -> Type) -> Type -> Type) (f :: Type -> Type) = h f
- type AlgHandler (e :: Effect) (m :: Type -> Type) (n :: Type -> Type) ans = forall x. e m x -> (x -> n ans) -> n ans
- type (~>) (f :: Type -> Type) (g :: Type -> Type) = forall x. f x -> g x
- type (~~>) (e :: (Type -> Type) -> Type -> Type) (f :: Type -> Type) = e f ~> f
- class FOEs (es :: [Effect])
- class FormOf e ~ 'Polynomial => PolyHFunctor (e :: Effect)
- class PolyHFunctors (es :: [Effect])
- type (:>) (e :: Effect) (es :: [Effect]) = MemberBy LabelResolver (Discriminator LabelResolver e) e es
- type In (e :: Effect) (es :: [Effect]) = MemberBy IdentityResolver (IdentityDiscriminator e) e es
- type Has (key :: k) (e :: Effect) (es :: [Effect]) = MemberBy KeyResolver (KeyDiscriminator key) (e # key) es
- type family (es :: [Effect]) ++ (es' :: [Effect]) :: [Effect] where ...
- (!:) :: forall (f :: Type -> Type) a r (es :: [Effect]). Elem e order => (e f a -> r) -> (Union es f a -> r) -> Union (e ': es) f a -> r
- (!++) :: forall (es :: [Effect]) (es' :: [Effect]) (f :: Type -> Type) a r. KnownLength es => (Union es f a -> r) -> (Union es' f a -> r) -> Union (es ++ es') f a -> r
- nil :: forall (f :: Type -> Type) a r. Union ('[] :: [Effect]) f a -> r
- perform :: forall e (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (e :> es, Free c ff) => e (Eff ff es) a -> Eff ff es a
- perform' :: forall {k} (key :: k) e (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (Has key e es, Free c ff) => e (Eff ff es) a -> Eff ff es a
- perform'' :: forall {k} (tag :: k) e (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). ((e # tag) :> es, Free c ff) => e (Eff ff es) a -> Eff ff es a
- send :: forall e (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (In e es, Free c ff) => e (Eff ff es) a -> Eff ff es a
- sendAt :: forall (i :: Nat) (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (KnownIndex i es, Free c ff) => At i es (Eff ff es) a -> Eff ff es a
- sendFor :: forall e (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (KnownOrder e, Free c ff) => Membership e es -> e (Eff ff es) a -> Eff ff es a
- emb :: forall f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (Emb f :> es, Free c ff) => f a -> Eff ff es a
- runEff :: forall (m :: Type -> Type). Monad m => Eff '[Emb m] ~> m
- runPure :: Eff ('[] :: [Effect]) a -> 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
- 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
- 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
- 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
- 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
- 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
- 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
- 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
- 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
- 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
- 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
- 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
- interposeBy :: forall (e :: Effect) (es :: [Effect]) ans a. (e :> es, FOEs es) => (a -> Eff es ans) -> AlgHandler e (Eff es) (Eff es) ans -> Eff es a -> Eff es ans
- interposeOnBy :: forall {k} (key :: k) (e :: Effect) (es :: [Effect]) ans a. (Has key e es, FOEs es) => (a -> Eff es ans) -> AlgHandler e (Eff es) (Eff es) ans -> Eff es a -> Eff es ans
- interposeInBy :: forall (e :: Effect) (es :: [Effect]) ans a. (In e es, FOEs es) => (a -> Eff es ans) -> AlgHandler e (Eff es) (Eff es) ans -> Eff es a -> Eff es ans
- interposeWith :: forall (e :: Effect) (es :: [Effect]) a. (e :> es, FOEs es) => AlgHandler e (Eff es) (Eff es) a -> Eff es a -> Eff es a
- interposeOnWith :: forall {k} (key :: k) (e :: Effect) (es :: [Effect]) a. (Has key e es, FOEs es) => AlgHandler e (Eff es) (Eff es) a -> Eff es a -> Eff es a
- interposeInWith :: forall (e :: Effect) (es :: [Effect]) a. (In e es, FOEs es) => AlgHandler e (Eff es) (Eff es) a -> Eff es a -> Eff 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
- interposeForWith :: forall (e :: Effect) (es :: [Effect]) a. (KnownOrder e, FOEs es) => Membership e es -> AlgHandler e (Eff es) (Eff es) a -> Eff es a -> Eff es a
- interposeForBy :: forall (e :: Effect) (es :: [Effect]) ans a. (KnownOrder e, FOEs es) => Membership e es -> (a -> Eff es ans) -> AlgHandler e (Eff es) (Eff es) ans -> Eff es a -> Eff es ans
- 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
- stateless :: forall (e :: (Type -> Type) -> Type -> Type) (m :: Type -> Type) (n :: Type -> Type) ans. Monad n => (e m ~> n) -> AlgHandler e m n ans
- 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
- type StateHandler s (e :: k -> Type -> Type) (m :: k) (n :: Type -> Type) ans = forall x. e m x -> s -> (s -> x -> n ans) -> n ans
- interpretStateBy :: forall s (e :: Effect) (es :: [Effect]) ans a. (KnownOrder e, FOEs es) => s -> (s -> a -> Eff es ans) -> StateHandler s e (Eff (e ': es)) (Eff es) ans -> Eff (e ': es) a -> Eff es ans
- reinterpretStateBy :: forall s (e :: Effect) (es' :: [Effect]) (es :: [Effect]) ans a. (Suffix es es', KnownOrder e, FOEs es) => s -> (s -> a -> Eff es' ans) -> StateHandler s e (Eff (e ': es)) (Eff es') ans -> Eff (e ': es) a -> Eff es' ans
- interposeStateBy :: forall s (e :: Effect) (es :: [Effect]) ans a. (e :> es, FOEs es) => s -> (s -> a -> Eff es ans) -> StateHandler s e (Eff es) (Eff es) ans -> Eff es a -> Eff es ans
- interposeStateInBy :: forall s (e :: Effect) (es :: [Effect]) ans a. (In e es, FOEs es) => s -> (s -> a -> Eff es ans) -> StateHandler s e (Eff es) (Eff es) ans -> Eff es a -> Eff es ans
- interposeStateForBy :: forall s (e :: Effect) (es :: [Effect]) ans a. (KnownOrder e, FOEs es) => Membership e es -> s -> (s -> a -> Eff es ans) -> StateHandler s e (Eff es) (Eff es) ans -> Eff es a -> Eff es ans
- transform :: forall (e :: Effect) (e' :: Effect) (es :: [Effect]) a (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (KnownOrder e, KnownOrder e', Free c ff) => (e (Eff ff (e' ': es)) ~> e' (Eff ff (e' ': es))) -> Eff ff (e ': es) a -> Eff ff (e' ': es) a
- translate :: forall (e :: Effect) (e' :: Effect) (es :: [Effect]) a (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (KnownOrder e, e' :> es, Free c ff) => (e (Eff ff es) ~> e' (Eff ff es)) -> Eff ff (e ': es) a -> Eff ff es a
- translateOn :: forall {k} (key :: k) (e :: Effect) (e' :: Effect) (es :: [Effect]) a (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (KnownOrder e, Has key e' es, Free c ff) => (e (Eff ff es) ~> e' (Eff ff es)) -> Eff ff (e ': es) a -> Eff ff es a
- translateIn :: forall (e :: Effect) (e' :: Effect) (es :: [Effect]) a (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (KnownOrder e, In e' es, Free c ff) => (e (Eff ff es) ~> e' (Eff ff es)) -> Eff ff (e ': es) a -> Eff ff es a
- translateFor :: forall (e :: Effect) (e' :: Effect) (es :: [Effect]) a (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (KnownOrder e, KnownOrder e', Free c ff) => Membership e' es -> (e (Eff ff es) ~> e' (Eff ff es)) -> Eff ff (e ': es) a -> Eff ff es a
- rewrite :: forall (e :: Effect) (es :: [Effect]) a (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (e :> es, Free c ff) => (e (Eff ff es) ~> e (Eff ff es)) -> Eff ff es a -> Eff ff es a
- rewriteOn :: forall {k} (key :: k) (e :: Effect) (es :: [Effect]) a (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Has key e es, Free c ff) => (e (Eff ff es) ~> e (Eff ff es)) -> Eff ff es a -> Eff ff es a
- rewriteIn :: forall (e :: Effect) (es :: [Effect]) a (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (In e es, Free c ff) => (e (Eff ff es) ~> e (Eff ff es)) -> Eff ff es a -> Eff ff es a
- rewriteFor :: forall (e :: Effect) (es :: [Effect]) a (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (KnownOrder e, Free c ff) => Membership e es -> (e (Eff ff es) ~> e (Eff ff es)) -> Eff ff es a -> Eff ff es a
- raise :: forall (e :: Effect) (es :: [Effect]) a (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). Free c ff => Eff ff es a -> Eff ff (e ': es) a
- raises :: forall (es :: [Effect]) (es' :: [Effect]) a (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Suffix es es', Free c ff) => Eff ff es a -> Eff ff es' a
- raisesUnder :: forall (e :: Effect) (es :: [Effect]) (es' :: [Effect]) a (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Suffix es es', Free c ff) => Eff ff (e ': es) a -> Eff ff (e ': es') a
- raiseUnder :: forall (e0 :: Effect) (e1 :: Effect) (es :: [Effect]) a (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). Free c ff => Eff ff (e0 ': es) a -> Eff ff (e0 ': (e1 ': es)) a
- class Suffix (es :: [Effect]) (es' :: [Effect])
- class SuffixUnder (es :: [Effect]) (es' :: [Effect])
- onlyFOEs :: forall (es :: [Effect]) a (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, WeakenHOEs es) => Eff ff (RemoveHOEs es) a -> Eff ff es a
- type WeakenHOEs (es :: [Effect]) = (WeakenHOEs_ es 0 (OrderOf (HeadOf es)), FOEs (RemoveHOEs es))
- type family RemoveHOEs (es :: [Effect]) :: [Effect] where ...
- onlyPolys :: forall (es :: [Effect]) a (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, WeakenExps es) => Eff ff (RemoveExps es) a -> Eff ff es a
- type WeakenExps (es :: [Effect]) = (WeakenExps_ es 0 (FormOf (HeadOf es)), PolyHFunctors (RemoveExps es))
- type family RemoveExps (es :: [Effect]) :: [Effect] where ...
- raisePrefix :: forall (es' :: [Effect]) (es :: [Effect]) a (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (KnownLength es', Free c ff) => Eff ff es a -> Eff ff (es' ++ es) a
- raiseSuffix :: forall (es' :: [Effect]) (es :: [Effect]) a (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). Free c ff => Eff ff es a -> Eff ff (es ++ es') a
- raisePrefix1 :: forall {k} (fs :: [k -> Effect]) (x :: k) (es :: [Effect]) a (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (KnownLength fs, Free c ff) => Eff ff es a -> Eff ff (Each fs x ++ es) a
- subsume :: forall (e :: Effect) (es :: [Effect]) a (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (In e es, Free c ff) => Eff ff (e ': es) a -> Eff ff es a
- subsumeUnder :: forall (e1 :: Effect) (e0 :: Effect) (es :: [Effect]) a (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (In e1 es, KnownOrder e0, Free c ff) => Eff ff (e0 ': (e1 ': es)) a -> Eff ff (e0 ': es) a
- tag :: forall {k} (tag :: k) (e :: Effect) (es :: [Effect]) a (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (KnownOrder e, KnownOrder (e # tag), Free c ff) => Eff ff (e ': es) a -> Eff ff ((e # tag) ': es) a
- untag :: forall {k} (tag :: k) (e :: Effect) (es :: [(Type -> Type) -> Type -> Type]) a (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (KnownOrder e, KnownOrder (e # tag), Free c ff) => Eff ff ((e # tag) ': es) a -> Eff ff (e ': es) a
- type KnownOrder (e :: Effect) = Elem e (OrderOf e)
- type Type = TYPE LiftedRep
- liftIO :: MonadIO m => IO a -> m a
- module Data.Effect
- module Data.Effect.Tag
- module Data.Effect.TH
- module Data.Effect.HFunctor.TH
- type ($) (f :: Type -> Type) a = f a
- pass :: forall w a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Tell w :> es, WriterH w :> es, Monad (Eff ff es), Free c ff) => Eff ff es (w -> w, a) -> Eff ff es a
- sub :: forall ref a b (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (CC ref :> es, Monad (Eff ff es), Free c ff) => (ref a -> Eff ff es b) -> (a -> Eff ff es b) -> Eff ff es b
- callCC_ :: forall (ref :: Type -> Type) a b (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (CC ref :> es, Monad (Eff ff es), Free c ff) => ((a -> Eff ff es b) -> Eff ff es a) -> Eff ff es a
- class (forall (f :: Type -> Type). c (ff f)) => Free (c :: (Type -> Type) -> Constraint) (ff :: (Type -> Type) -> Type -> Type) | ff -> c where
- type (~>) (f :: Type -> Type) (g :: Type -> Type) = forall x. f x -> g x
- type (~~>) (e :: (Type -> Type) -> Type -> Type) (f :: Type -> Type) = e f ~> f
- type ($$) (h :: (Type -> Type) -> Type -> Type) (f :: Type -> Type) = h f
- unEff :: Eff ff es a -> ff (Union es (Eff ff es)) a
- perform :: forall e (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (e :> es, Free c ff) => e (Eff ff es) a -> Eff ff es a
- perform' :: forall {k} (key :: k) e (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (Has key e es, Free c ff) => e (Eff ff es) a -> Eff ff es a
- perform'' :: forall {k} (tag :: k) e (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). ((e # tag) :> es, Free c ff) => e (Eff ff es) a -> Eff ff es a
- send :: forall e (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (In e es, Free c ff) => e (Eff ff es) a -> Eff ff es a
- sendAt :: forall (i :: Nat) (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (KnownIndex i es, Free c ff) => At i es (Eff ff es) a -> Eff ff es a
- sendFor :: forall e (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (KnownOrder e, Free c ff) => Membership e es -> e (Eff ff es) a -> Eff ff es a
- emb :: forall f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (Emb f :> es, Free c ff) => f a -> Eff ff es a
- convertEff :: forall (ff :: (Type -> Type) -> Type -> Type) (gg :: (Type -> Type) -> Type -> Type) (es :: [Effect]) a (c :: (Type -> Type) -> Constraint) (c' :: (Type -> Type) -> Constraint). (Free c ff, Free c' gg, forall (r :: Type -> Type). c (gg r)) => Eff ff es a -> Eff gg es a
- convertFree :: forall (c :: (Type -> Type) -> Constraint) ff (c' :: (Type -> Type) -> Constraint) gg (r :: Type -> Type) a. (Free c ff, Free c' gg, c (gg r)) => ff r a -> gg r a
Basics
type ($$) (h :: (Type -> Type) -> Type -> Type) (f :: Type -> Type) = h f infixr 4 #
Type-level infix applcation for higher-order functors.
type AlgHandler (e :: Effect) (m :: Type -> Type) (n :: Type -> Type) ans = forall x. e m x -> (x -> n ans) -> n ans Source #
type (~>) (f :: Type -> Type) (g :: Type -> Type) = forall x. f x -> g x infixr 2 #
A natural transformation.
The list es consists only of first-order effects.
Instances
| FOEs ('[] :: [Effect]) | |
Defined in Data.Effect.OpenUnion | |
| (FirstOrder e, FOEs es) => FOEs (e ': es) | |
Defined in Data.Effect.OpenUnion | |
class FormOf e ~ 'Polynomial => PolyHFunctor (e :: Effect) #
A higher-order polynomial functor.
Instances
class PolyHFunctors (es :: [Effect]) #
The list es consists only of polynomial effects.
Instances
| PolyHFunctors ('[] :: [Effect]) | |
Defined in Data.Effect.OpenUnion | |
| (PolyHFunctor e, PolyHFunctors es) => PolyHFunctors (e ': es) | |
Defined in Data.Effect.OpenUnion | |
type (:>) (e :: Effect) (es :: [Effect]) = MemberBy LabelResolver (Discriminator LabelResolver e) e es infix 4 #
type In (e :: Effect) (es :: [Effect]) = MemberBy IdentityResolver (IdentityDiscriminator e) e es infix 4 #
type Has (key :: k) (e :: Effect) (es :: [Effect]) = MemberBy KeyResolver (KeyDiscriminator key) (e # key) es #
(!:) :: forall (f :: Type -> Type) a r (es :: [Effect]). Elem e order => (e f a -> r) -> (Union es f a -> r) -> Union (e ': es) f a -> r infixr 5 #
(!++) :: forall (es :: [Effect]) (es' :: [Effect]) (f :: Type -> Type) a r. KnownLength es => (Union es f a -> r) -> (Union es' f a -> r) -> Union (es ++ es') f a -> r infixr 5 #
perform :: forall e (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (e :> es, Free c ff) => e (Eff ff es) a -> Eff ff es a #
perform' :: forall {k} (key :: k) e (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (Has key e es, Free c ff) => e (Eff ff es) a -> Eff ff es a #
perform'' :: forall {k} (tag :: k) e (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). ((e # tag) :> es, Free c ff) => e (Eff ff es) a -> Eff ff es a #
send :: forall e (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (In e es, Free c ff) => e (Eff ff es) a -> Eff ff es a #
sendAt :: forall (i :: Nat) (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (KnownIndex i es, Free c ff) => At i es (Eff ff es) a -> Eff ff es a #
sendFor :: forall e (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (KnownOrder e, Free c ff) => Membership e es -> e (Eff ff es) a -> Eff ff es a #
emb :: forall f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (Emb f :> es, Free c ff) => f a -> Eff ff es a #
Interpreting effects
Running Eff
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.
Standard functions
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 #
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 #
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 #
Reinterpretation functions
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 #
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 #
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 #
Interposition functions
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 #
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 #
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.
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.
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.
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.
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.
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.
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 #
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.
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 |
Transformation to monads
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 #
Utilities
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.
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 #
Ad-hoc stateful interpretation
Theses entities provides an ad-hoc specialized version to accelerate interpretations that have a
single state type s, especially for effects like State or
Writer.
type StateHandler s (e :: k -> Type -> Type) (m :: k) (n :: Type -> Type) ans = forall x. e m x -> s -> (s -> x -> n ans) -> n ans Source #
An ad-hoc stateful version of Handler for performance.
Interpretation functions
interpretStateBy :: forall s (e :: Effect) (es :: [Effect]) ans a. (KnownOrder e, FOEs es) => s -> (s -> a -> Eff es ans) -> StateHandler s e (Eff (e ': es)) (Eff es) ans -> Eff (e ': es) a -> Eff es ans Source #
reinterpretStateBy :: forall s (e :: Effect) (es' :: [Effect]) (es :: [Effect]) ans a. (Suffix es es', KnownOrder e, FOEs es) => s -> (s -> a -> Eff es' ans) -> StateHandler s e (Eff (e ': es)) (Eff es') ans -> Eff (e ': es) a -> Eff es' ans Source #
Interposition functions
interposeStateBy :: forall s (e :: Effect) (es :: [Effect]) ans a. (e :> es, FOEs es) => s -> (s -> a -> Eff es ans) -> StateHandler s e (Eff es) (Eff es) ans -> Eff es a -> Eff es ans Source #
interposeStateInBy :: forall s (e :: Effect) (es :: [Effect]) ans a. (In e es, FOEs es) => s -> (s -> a -> Eff es ans) -> StateHandler s e (Eff es) (Eff es) ans -> Eff es a -> Eff es ans Source #
interposeStateForBy :: forall s (e :: Effect) (es :: [Effect]) ans a. (KnownOrder e, FOEs es) => Membership e es -> s -> (s -> a -> Eff es ans) -> StateHandler s e (Eff es) (Eff es) ans -> Eff es a -> Eff es ans Source #
Transforming effects
Rewriting effectful operations
transform :: forall (e :: Effect) (e' :: Effect) (es :: [Effect]) a (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (KnownOrder e, KnownOrder e', Free c ff) => (e (Eff ff (e' ': es)) ~> e' (Eff ff (e' ': es))) -> Eff ff (e ': es) a -> Eff ff (e' ': es) a #
translate :: forall (e :: Effect) (e' :: Effect) (es :: [Effect]) a (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (KnownOrder e, e' :> es, Free c ff) => (e (Eff ff es) ~> e' (Eff ff es)) -> Eff ff (e ': es) a -> Eff ff es a #
translateOn :: forall {k} (key :: k) (e :: Effect) (e' :: Effect) (es :: [Effect]) a (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (KnownOrder e, Has key e' es, Free c ff) => (e (Eff ff es) ~> e' (Eff ff es)) -> Eff ff (e ': es) a -> Eff ff es a #
translateIn :: forall (e :: Effect) (e' :: Effect) (es :: [Effect]) a (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (KnownOrder e, In e' es, Free c ff) => (e (Eff ff es) ~> e' (Eff ff es)) -> Eff ff (e ': es) a -> Eff ff es a #
translateFor :: forall (e :: Effect) (e' :: Effect) (es :: [Effect]) a (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (KnownOrder e, KnownOrder e', Free c ff) => Membership e' es -> (e (Eff ff es) ~> e' (Eff ff es)) -> Eff ff (e ': es) a -> Eff ff es a #
rewrite :: forall (e :: Effect) (es :: [Effect]) a (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (e :> es, Free c ff) => (e (Eff ff es) ~> e (Eff ff es)) -> Eff ff es a -> Eff ff es a #
rewriteOn :: forall {k} (key :: k) (e :: Effect) (es :: [Effect]) a (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Has key e es, Free c ff) => (e (Eff ff es) ~> e (Eff ff es)) -> Eff ff es a -> Eff ff es a #
rewriteIn :: forall (e :: Effect) (es :: [Effect]) a (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (In e es, Free c ff) => (e (Eff ff es) ~> e (Eff ff es)) -> Eff ff es a -> Eff ff es a #
rewriteFor :: forall (e :: Effect) (es :: [Effect]) a (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (KnownOrder e, Free c ff) => Membership e es -> (e (Eff ff es) ~> e (Eff ff es)) -> Eff ff es a -> Eff ff es a #
Manipulating the effect list (without rewriting effectful operations)
Insertion functions
raise :: forall (e :: Effect) (es :: [Effect]) a (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). Free c ff => Eff ff es a -> Eff ff (e ': es) a #
raises :: forall (es :: [Effect]) (es' :: [Effect]) a (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Suffix es es', Free c ff) => Eff ff es a -> Eff ff es' a #
raisesUnder :: forall (e :: Effect) (es :: [Effect]) (es' :: [Effect]) a (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Suffix es es', Free c ff) => Eff ff (e ': es) a -> Eff ff (e ': es') a #
raiseUnder :: forall (e0 :: Effect) (e1 :: Effect) (es :: [Effect]) a (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). Free c ff => Eff ff (e0 ': es) a -> Eff ff (e0 ': (e1 ': es)) a #
class SuffixUnder (es :: [Effect]) (es' :: [Effect]) #
Minimal complete definition
Instances
| Suffix es es' => SuffixUnder es es' | |
Defined in Data.Effect.OpenUnion | |
| SuffixUnder es es' => SuffixUnder (e ': es) (e ': es') | |
Defined in Data.Effect.OpenUnion | |
onlyFOEs :: forall (es :: [Effect]) a (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, WeakenHOEs es) => Eff ff (RemoveHOEs es) a -> Eff ff es a #
type WeakenHOEs (es :: [Effect]) = (WeakenHOEs_ es 0 (OrderOf (HeadOf es)), FOEs (RemoveHOEs es)) #
type family RemoveHOEs (es :: [Effect]) :: [Effect] where ... #
Equations
| RemoveHOEs ('[] :: [Effect]) = '[] :: [Effect] | |
| RemoveHOEs (e ': es) = OrderCase (OrderOf e) (e ': RemoveHOEs es) (RemoveHOEs es) |
onlyPolys :: forall (es :: [Effect]) a (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, WeakenExps es) => Eff ff (RemoveExps es) a -> Eff ff es a #
type WeakenExps (es :: [Effect]) = (WeakenExps_ es 0 (FormOf (HeadOf es)), PolyHFunctors (RemoveExps es)) #
type family RemoveExps (es :: [Effect]) :: [Effect] where ... #
Equations
| RemoveExps ('[] :: [Effect]) = '[] :: [Effect] | |
| RemoveExps (e ': es) = FormCase (FormOf e) (e ': RemoveExps es) (RemoveExps es) |
raisePrefix :: forall (es' :: [Effect]) (es :: [Effect]) a (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (KnownLength es', Free c ff) => Eff ff es a -> Eff ff (es' ++ es) a #
raiseSuffix :: forall (es' :: [Effect]) (es :: [Effect]) a (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). Free c ff => Eff ff es a -> Eff ff (es ++ es') a #
raisePrefix1 :: forall {k} (fs :: [k -> Effect]) (x :: k) (es :: [Effect]) a (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (KnownLength fs, Free c ff) => Eff ff es a -> Eff ff (Each fs x ++ es) a #
subsume :: forall (e :: Effect) (es :: [Effect]) a (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (In e es, Free c ff) => Eff ff (e ': es) a -> Eff ff es a #
subsumeUnder :: forall (e1 :: Effect) (e0 :: Effect) (es :: [Effect]) a (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (In e1 es, KnownOrder e0, Free c ff) => Eff ff (e0 ': (e1 ': es)) a -> Eff ff (e0 ': es) a #
Manipulating Tags
tag :: forall {k} (tag :: k) (e :: Effect) (es :: [Effect]) a (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (KnownOrder e, KnownOrder (e # tag), Free c ff) => Eff ff (e ': es) a -> Eff ff ((e # tag) ': es) a #
untag :: forall {k} (tag :: k) (e :: Effect) (es :: [(Type -> Type) -> Type -> Type]) a (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (KnownOrder e, KnownOrder (e # tag), Free c ff) => Eff ff ((e # tag) ': es) a -> Eff ff (e ': es) a #
Misc
type KnownOrder (e :: Effect) = Elem e (OrderOf e) #
liftIO :: MonadIO m => IO a -> m a #
Lift a computation from the IO monad.
This allows us to run IO computations in any monadic stack, so long as it supports these kinds of operations
(i.e. IO is the base monad for the stack).
Example
import Control.Monad.Trans.State -- from the "transformers" library printState :: Show s => StateT s IO () printState = do state <- get liftIO $ print state
Had we omitted , we would have ended up with this error:liftIO
• Couldn't match type ‘IO’ with ‘StateT s IO’ Expected type: StateT s IO () Actual type: IO ()
The important part here is the mismatch between StateT s IO () and .IO ()
Luckily, we know of a function that takes an and returns an IO a(m a): ,
enabling us to run the program and see the expected results:liftIO
> evalStateT printState "hello" "hello" > evalStateT printState 3 3
module Data.Effect
module Data.Effect.Tag
module Data.Effect.TH
module Data.Effect.HFunctor.TH
pass :: forall w a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Tell w :> es, WriterH w :> es, Monad (Eff ff es), Free c ff) => Eff ff es (w -> w, a) -> Eff ff es a #
For a given scope, uses the function (the first component of the pair returned by that scope) to modify the accumulated value of that scope, and then accumulates the result into the current outer scope.
pass m = do
(w, (f, a)) <- listen m
tell $ f w
pure a
sub :: forall ref a b (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (CC ref :> es, Monad (Eff ff es), Free c ff) => (ref a -> Eff ff es b) -> (a -> Eff ff es b) -> Eff ff es b #
callCC_ :: forall (ref :: Type -> Type) a b (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (CC ref :> es, Monad (Eff ff es), Free c ff) => ((a -> Eff ff es b) -> Eff ff es a) -> Eff ff es a #
class (forall (f :: Type -> Type). c (ff f)) => Free (c :: (Type -> Type) -> Constraint) (ff :: (Type -> Type) -> Type -> Type) | ff -> c where #
Instances
type (~>) (f :: Type -> Type) (g :: Type -> Type) = forall x. f x -> g x infixr 2 #
A natural transformation.
type ($$) (h :: (Type -> Type) -> Type -> Type) (f :: Type -> Type) = h f infixr 4 #
Type-level infix applcation for higher-order functors.
perform :: forall e (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (e :> es, Free c ff) => e (Eff ff es) a -> Eff ff es a #
perform' :: forall {k} (key :: k) e (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (Has key e es, Free c ff) => e (Eff ff es) a -> Eff ff es a #
perform'' :: forall {k} (tag :: k) e (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). ((e # tag) :> es, Free c ff) => e (Eff ff es) a -> Eff ff es a #
send :: forall e (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (In e es, Free c ff) => e (Eff ff es) a -> Eff ff es a #
sendAt :: forall (i :: Nat) (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (KnownIndex i es, Free c ff) => At i es (Eff ff es) a -> Eff ff es a #
sendFor :: forall e (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (KnownOrder e, Free c ff) => Membership e es -> e (Eff ff es) a -> Eff ff es a #
emb :: forall f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) a (c :: (Type -> Type) -> Constraint). (Emb f :> es, Free c ff) => f a -> Eff ff es a #
convertEff :: forall (ff :: (Type -> Type) -> Type -> Type) (gg :: (Type -> Type) -> Type -> Type) (es :: [Effect]) a (c :: (Type -> Type) -> Constraint) (c' :: (Type -> Type) -> Constraint). (Free c ff, Free c' gg, forall (r :: Type -> Type). c (gg r)) => Eff ff es a -> Eff gg es a #
convertFree :: forall (c :: (Type -> Type) -> Constraint) ff (c' :: (Type -> Type) -> Constraint) gg (r :: Type -> Type) a. (Free c ff, Free c' gg, c (gg r)) => ff r a -> gg r a #