| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Polysemy.Final
Synopsis
- data Final m z a where- WithWeaving :: (forall f. Functor f => f () -> (forall x. f (z x) -> m (f x)) -> (forall x. f x -> Maybe x) -> m (f a)) -> Final m z a
 
- withWeaving :: forall m a r. Member (Final m) r => (forall f. Functor f => f () -> (forall x. f (Sem r x) -> m (f x)) -> (forall x. f x -> Maybe x) -> m (f a)) -> Sem r a
- withStrategic :: Member (Final m) r => Strategic m (Sem r) a -> Sem r a
- embedFinal :: Functor m => Member (Final m) r => m a -> Sem r a
- interpretFinal :: forall e m r a. (Member (Final m) r, Functor m) => (forall x n. e n x -> Strategic m n x) -> Sem (e ': r) a -> Sem r a
- type Strategic m n a = forall f. Functor f => Sem (WithStrategy m f n) (m (f a))
- type WithStrategy m f n = WithTactics (Embed m) f n '[]
- pureS :: Applicative m => a -> Strategic m n a
- liftS :: Functor m => m a -> Strategic m n a
- runS :: Monad m => n a -> Sem (WithStrategy m f n) (m (f a))
- bindS :: Monad m => (a -> n b) -> Sem (WithStrategy m f n) (f a -> m (f b))
- getInspectorS :: Sem (WithStrategy m f n) (Inspector f)
- getInitialStateS :: Sem (WithStrategy m f n) (f ())
- runFinal :: Monad m => Sem '[Final m, Embed m] a -> m a
- runFinalLift :: Monad m => (forall x. n x -> m x) -> Sem [Final m, Embed m, Embed n] a -> m a
- runFinalLiftIO :: MonadIO m => Sem [Final m, Embed m, Embed IO] a -> m a
Effect
data Final m z a where Source #
An effect for embedding higher-order effects in the final target monad of the effect stack.
This is very useful for writing interpreters that interpret higher-order effects in terms of the final monad - however, these interpreters are subject to very different semantics than regular ones.
For more information, see interpretFinal.
Constructors
| WithWeaving :: (forall f. Functor f => f () -> (forall x. f (z x) -> m (f x)) -> (forall x. f x -> Maybe x) -> m (f a)) -> Final m z a | 
Instances
| type DefiningModule Final Source # | |
| Defined in Polysemy.Final | |
Actions
withWeaving :: forall m a r. Member (Final m) r => (forall f. Functor f => f () -> (forall x. f (Sem r x) -> m (f x)) -> (forall x. f x -> Maybe x) -> m (f a)) -> Sem r a Source #
Allows for embedding higher-order actions of the final monad
 by providing the means of explicitly threading effects through Sem r
Consider using withStrategic instead,
 as it provides a more user-friendly interface to the same power.
You are discouraged from using withWeaving directly in application code,
 as it ties your application code directly to the underlying monad.
withStrategic :: Member (Final m) r => Strategic m (Sem r) a -> Sem r a Source #
Allows for embedding higher-order actions of the final monad
 by providing the means of explicitly threading effects through 'Sem r'
 to the final monad. This is done through the use of the Strategic
 environment.
You are discouraged from using withStrategic in application code,
 as it ties your application code directly to the underlying monad.
embedFinal :: Functor m => Member (Final m) r => m a -> Sem r a Source #
withWeaving admits an implementation of sendM.
Just like sendM, you are discouraged from using this in application code.
Combinators for Interpreting to the Final Monad
interpretFinal :: forall e m r a. (Member (Final m) r, Functor m) => (forall x n. e n x -> Strategic m n x) -> Sem (e ': r) a -> Sem r a Source #
Like interpretH, but may be used to
 interpret higher-order effects in terms of the final monad.
Beware: Any interpreters built using this (or Final in general)
 will not respect local/global state semantics based on the order of
 interpreters run. You should signal interpreters that make use of
 Final by adding a "-Final" suffix to the names of these.
State semantics of effects that are not interpreted in terms of the final monad will always appear local to effects that are interpreted in terms of the final monad.
State semantics between effects that are interpreted in terms of the final monad depend on the final monad. I.e. if the final monad is a monad transformer stack, then state semantics will depend on the order monad transformers are stacked.
Strategy
Strategy is a domain-specific language very similar to Tactics
 (see Tactical), and is used to describe how higher-order effects
 are threaded down to the final monad.
Much like Tactics, computations can be run and threaded
 through the use of runS and bindS, and first-order constructors
 may use pureS. In addition, liftS may be used to
 lift actions of the final monad.
Unlike Tactics, the final return value within a Strategic
 must be a monadic value of the target monad
 with the functorial state wrapped inside of it.
type WithStrategy m f n = WithTactics (Embed m) f n '[] Source #
runS :: Monad m => n a -> Sem (WithStrategy m f n) (m (f a)) Source #
Lifts a monadic action into the stateful environment, in terms
 of the final monad.
 The stateful environment will be the same as the one that the target monad
 is initially run in.
 Use bindS  if you'd prefer to explicitly manage your stateful environment.
getInspectorS :: Sem (WithStrategy m f n) (Inspector f) Source #
Get a natural transformation capable of potentially inspecting values
 inside of f. Binding the result of getInspectorS produces a function that
 can sometimes peek inside values returned by bindS.
This is often useful for running callback functions that are not managed by polysemy code.
See also getInspectorT
getInitialStateS :: Sem (WithStrategy m f n) (f ()) Source #
Interpretations
runFinal :: Monad m => Sem '[Final m, Embed m] a -> m a Source #
Lower a Sem containing only a lifted, final monad into that monad.
 The appearance of Lift as the final effect
 is to allow the use of operations that rely on a LastMember (Lift m)
runFinalLift :: Monad m => (forall x. n x -> m x) -> Sem [Final m, Embed m, Embed n] a -> m a Source #
Lower a Sem containing two lifted monad into the final monad,
 by interpreting one of the monads in terms of the other one.
This allows for the use of operations that rely on a LastMember (Lift m)m can be transformed to the final monad;
 but be warned, this breaks the implicit contract of LastMember (Lift m)m is the final monad, so depending on the final monad and operations
 used, runFinalLift may become unsafe.
For example, runFinalLift is unsafe with asyncToIO if
 the final monad is non-deterministic, or a continuation
 monad.