incipit-core-0.3.0.0: A Prelude for Polysemy
Safe HaskellSafe-Inferred
LanguageHaskell2010

IncipitCore

Description

This is the central module on which to build upon when constructing Preludes for Polysemy libraries. It reexports most core effects.

Synopsis

Documentation

embedToFinal :: forall (m :: Type -> Type) (r :: [(Type -> Type) -> Type -> Type]) a. (Member (Final m) r, Functor m) => Sem (Embed m ': r) a -> Sem r a #

Transform an Embed m effect into a Final m effect

Since: polysemy-1.2.0.0

runFinal :: Monad m => Sem '[Final m] a -> m a #

Lower a Sem containing only a single lifted, final Monad into that monad.

If you also need to process an Embed m effect, use this together with embedToFinal.

Since: polysemy-1.2.0.0

embedFinal :: forall m (r :: [(Type -> Type) -> Type -> Type]) a. (Member (Final m) r, Functor m) => m a -> Sem r a #

withWeavingToFinal admits an implementation of embed.

Just like embed, you are discouraged from using this in application code.

Since: polysemy-1.2.0.0

data Final (m :: Type -> Type) (z :: Type -> Type) a #

An effect for embedding higher-order actions 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.

Final is more powerful than Embed, but is also less flexible to interpret (compare runEmbedded with finalToFinal). If you only need the power of embed, then you should use Embed instead.

Beware: Final actions are interpreted as actions of the final monad, and the effectful state visible to withWeavingToFinal / withStrategicToFinal / interpretFinal is that of all interpreters run in order to produce the final monad.

This means that any interpreter built using Final 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. For example, if the final monad is a monad transformer stack, then state semantics will depend on the order monad transformers are stacked.

Since: polysemy-1.2.0.0

Instances

Instances details
type DefiningModule Final 
Instance details

Defined in Polysemy.Final

type DefiningModule Final = "Polysemy.Final"

transform :: forall e1 e2 (r :: [Effect]) a. Member e2 r => (forall (rInitial :: EffectRow) x. e1 (Sem rInitial) x -> e2 (Sem rInitial) x) -> Sem (e1 ': r) a -> Sem r a #

Transform an effect e1 into an effect e2 that is already somewhere inside of the stack.

Since: polysemy-1.2.3.0

rewrite :: forall e1 e2 (r :: [Effect]) a. (forall (rInitial :: EffectRow) x. e1 (Sem rInitial) x -> e2 (Sem rInitial) x) -> Sem (e1 ': r) a -> Sem (e2 ': r) a #

Rewrite an effect e1 directly into e2, and put it on the top of the effect stack.

Since: polysemy-1.2.3.0

interceptH #

Arguments

:: forall e (r :: [Effect]) a. Member e r 
=> (forall x (rInitial :: EffectRow). e (Sem rInitial) x -> Tactical e (Sem rInitial) r x)

A natural transformation from the handled effect to other effects already in Sem.

-> Sem r a

Unlike interpretH, interceptH does not consume any effects.

-> Sem r a 

Like intercept, but for higher-order effects.

See the notes on Tactical for how to use this function.

intercept #

Arguments

:: forall e (r :: [Effect]) a. (Member e r, FirstOrder e "intercept") 
=> (forall x (rInitial :: EffectRow). e (Sem rInitial) x -> Sem r x)

A natural transformation from the handled effect to other effects already in Sem.

-> Sem r a

Unlike interpret, intercept does not consume any effects.

-> Sem r a 

Like interpret, but instead of handling the effect, allows responding to the effect while leaving it unhandled. This allows you, for example, to intercept other effects and insert logic around them.

reinterpret3 #

Arguments

:: forall e1 (e2 :: Effect) (e3 :: Effect) (e4 :: Effect) (r :: [Effect]) a. FirstOrder e1 "reinterpret3" 
=> (forall (rInitial :: EffectRow) x. e1 (Sem rInitial) x -> Sem (e2 ': (e3 ': (e4 ': r))) x)

A natural transformation from the handled effect to the new effects.

-> Sem (e1 ': r) a 
-> Sem (e2 ': (e3 ': (e4 ': r))) a 

Like reinterpret, but introduces three intermediary effects.

reinterpret3H #

Arguments

:: forall e1 (e2 :: Effect) (e3 :: Effect) (e4 :: Effect) (r :: [Effect]) a. (forall (rInitial :: EffectRow) x. e1 (Sem rInitial) x -> Tactical e1 (Sem rInitial) (e2 ': (e3 ': (e4 ': r))) x)

A natural transformation from the handled effect to the new effects.

-> Sem (e1 ': r) a 
-> Sem (e2 ': (e3 ': (e4 ': r))) a 

Like reinterpret3, but for higher-order effects.

See the notes on Tactical for how to use this function.

reinterpret2 #

Arguments

:: forall e1 (e2 :: Effect) (e3 :: Effect) (r :: [Effect]) a. FirstOrder e1 "reinterpret2" 
=> (forall (rInitial :: EffectRow) x. e1 (Sem rInitial) x -> Sem (e2 ': (e3 ': r)) x)

A natural transformation from the handled effect to the new effects.

-> Sem (e1 ': r) a 
-> Sem (e2 ': (e3 ': r)) a 

Like reinterpret, but introduces two intermediary effects.

reinterpret2H #

Arguments

:: forall e1 (e2 :: Effect) (e3 :: Effect) (r :: [Effect]) a. (forall (rInitial :: EffectRow) x. e1 (Sem rInitial) x -> Tactical e1 (Sem rInitial) (e2 ': (e3 ': r)) x)

A natural transformation from the handled effect to the new effects.

-> Sem (e1 ': r) a 
-> Sem (e2 ': (e3 ': r)) a 

Like reinterpret2, but for higher-order effects.

See the notes on Tactical for how to use this function.

reinterpret #

Arguments

:: forall e1 (e2 :: Effect) (r :: [Effect]) a. FirstOrder e1 "reinterpret" 
=> (forall (rInitial :: EffectRow) x. e1 (Sem rInitial) x -> Sem (e2 ': r) x)

A natural transformation from the handled effect to the new effect.

-> Sem (e1 ': r) a 
-> Sem (e2 ': r) a 

Like interpret, but instead of removing the effect e, reencodes it in some new effect f. This function will fuse when followed by runState, meaning it's free to reinterpret in terms of the State effect and immediately run it.

reinterpretH #

Arguments

:: forall e1 (e2 :: Effect) (r :: [Effect]) a. (forall (rInitial :: EffectRow) x. e1 (Sem rInitial) x -> Tactical e1 (Sem rInitial) (e2 ': r) x)

A natural transformation from the handled effect to the new effect.

-> Sem (e1 ': r) a 
-> Sem (e2 ': r) a 

Like reinterpret, but for higher-order effects.

See the notes on Tactical for how to use this function.

interpretH #

Arguments

:: forall e (r :: [Effect]) a. (forall (rInitial :: EffectRow) x. e (Sem rInitial) x -> Tactical e (Sem rInitial) r x)

A natural transformation from the handled effect to other effects already in Sem.

-> Sem (e ': r) a 
-> Sem r a 

Like interpret, but for higher-order effects (ie. those which make use of the m parameter.)

See the notes on Tactical for how to use this function.

interpret #

Arguments

:: forall e (r :: [Effect]) a. FirstOrder e "interpret" 
=> (forall (rInitial :: EffectRow) x. e (Sem rInitial) x -> Sem r x)

A natural transformation from the handled effect to other effects already in Sem.

-> Sem (e ': r) a 
-> Sem r a 

The simplest way to produce an effect handler. Interprets an effect e by transforming it into other effects inside of r.

withLowerToIO #

Arguments

:: forall (r :: [(Type -> Type) -> Type -> Type]) a. Member (Embed IO) r 
=> ((forall x. Sem r x -> IO x) -> IO () -> IO a)

A lambda that takes the lowering function, and a finalizing IO action to mark a the forked thread as being complete. The finalizing action need not be called.

-> Sem r a 

Run an effect stack all the way down to IO by running it in a new thread, and temporarily turning the current thread into an event poll.

This function creates a thread, and so should be compiled with -threaded.

Since: polysemy-0.5.0.0

makeSem_ :: Name -> Q [Dec] #

Like makeSem, but does not provide type signatures and fixities. This can be used to attach Haddock comments to individual arguments for each generated function.

data Output o m a where
  Output :: o -> Output o m ()

makeSem_ ''Output

-- | Output the value @o@.
output :: forall o r
       .  Member (Output o) r
       => o         -- ^ Value to output.
       -> Sem r ()  -- ^ No result.

Because of limitations in Template Haskell, signatures have to follow some rules to work properly:

  • makeSem_ must be used before the explicit type signatures
  • signatures have to specify argument of Sem representing union of effects as r (e.g. Sem r ())
  • all arguments in effect's type constructor have to follow naming scheme from data constructor's declaration:
data Foo e m a where
  FooC1 :: Foo x m ()
  FooC2 :: Foo (Maybe x) m ()

should have x in type signature of fooC1:

fooC1 :: forall x r. Member (Foo x) r => Sem r ()

and Maybe x in signature of fooC2:

fooC2 :: forall x r. Member (Foo (Maybe x)) r => Sem r ()
  • all effect's type variables and r have to be explicitly quantified using forall (order is not important)

These restrictions may be removed in the future, depending on changes to the compiler.

Change in (TODO(Sandy): version): in case of GADTs, signatures now only use names from data constructor's type and not from type constructor declaration.

Since: polysemy-0.1.2.0

makeSem :: Name -> Q [Dec] #

If T is a GADT representing an effect algebra, as described in the module documentation for Polysemy, $(makeSem ''T) automatically generates a smart constructor for every data constructor of T. This also works for data family instances. Names of smart constructors are created by changing first letter to lowercase or removing prefix : in case of operators. Fixity declaration is preserved for both normal names and operators.

Since: polysemy-0.1.2.0

bindTSimple #

Arguments

:: forall m f (r :: [Effect]) (e :: Effect) a b. (a -> m b)

The monadic continuation to lift. This is usually a parameter in your effect.

Continuations executed via bindTSimple will run in the same environment which produced the a.

-> f a 
-> Sem (WithTactics e f m r) (f b) 

Lift a kleisli action into the stateful environment. You can use bindTSimple to execute an effect parameter of the form a -> m b by providing the result of a runTSimple or another bindTSimple.

This is a less flexible but significantly simpler variant of bindT. Instead of returning a Sem kleisli action corresponding to the provided kleisli action, bindTSimple runs the kleisli action immediately.

Since: polysemy-1.5.0.0

bindT #

Arguments

:: forall a m b (e :: Effect) f (r :: [Effect]). (a -> m b)

The monadic continuation to lift. This is usually a parameter in your effect.

Continuations lifted via bindT will run in the same environment which produced the a.

-> Sem (WithTactics e f m r) (f a -> Sem (e ': r) (f b)) 

Lift a kleisli action into the stateful environment. You can use bindT to get an effect parameter of the form a -> m b into something that can be used after calling runT on an effect parameter m a.

runTSimple #

Arguments

:: forall m a (e :: Effect) (r :: [Effect]). m a

The monadic action to lift. This is usually a parameter in your effect.

-> Tactical e m r a 

Run a monadic action in a Tactical environment. The stateful environment used will be the same one that the effect is initally run in. Use bindTSimple if you'd prefer to explicitly manage your stateful environment.

This is a less flexible but significantly simpler variant of runT. Instead of returning a Sem action corresponding to the provided action, runTSimple runs the action immediately.

Since: polysemy-1.5.0.0

runT #

Arguments

:: forall m a (e :: Effect) f (r :: [Effect]). m a

The monadic action to lift. This is usually a parameter in your effect.

-> Sem (WithTactics e f m r) (Sem (e ': r) (f a)) 

Run a monadic action in a Tactical environment. The stateful environment used will be the same one that the effect is initally run in. Use bindT if you'd prefer to explicitly manage your stateful environment.

pureT :: forall f a (e :: Effect) (m :: Type -> Type) (r :: [Effect]). Functor f => a -> Sem (WithTactics e f m r) (f a) #

Lift a value into Tactical.

getInspectorT :: forall (e :: Effect) (f :: Type -> Type) (m :: Type -> Type) (r :: [Effect]). Sem (WithTactics e f m r) (Inspector f) #

Get a natural transformation capable of potentially inspecting values inside of f. Binding the result of getInspectorT produces a function that can sometimes peek inside values returned by bindT.

This is often useful for running callback functions that are not managed by polysemy code.

Example

We can use the result of getInspectorT to "undo" pureT (or any of the other Tactical functions):

ins <- getInspectorT
fa <- pureT "hello"
fb <- pureT True
let a = inspect ins fa   -- Just "hello"
    b = inspect ins fb   -- Just True

getInitialStateT :: forall f (m :: Type -> Type) (r :: [Effect]) (e :: Effect). Sem (WithTactics e f m r) (f ()) #

Get the stateful environment of the world at the moment the effect e is to be run. Prefer pureT, runT or bindT instead of using this function directly.

type Tactical (e :: Effect) (m :: Type -> Type) (r :: [Effect]) x = forall (f :: Type -> Type). Functor f => Sem (WithTactics e f m r) (f x) #

Tactical is an environment in which you're capable of explicitly threading higher-order effect states. This is provided by the (internal) effect Tactics, which is capable of rewriting monadic actions so they run in the correct stateful environment.

Inside a Tactical, you're capable of running pureT, runT and bindT which are the main tools for rewriting monadic stateful environments.

For example, consider trying to write an interpreter for Resource, whose effect is defined as:

data Resource m a where
  Bracket :: m a -> (a -> m ()) -> (a -> m b) -> Resource m b

Here we have an m a which clearly needs to be run first, and then subsequently call the a -> m () and a -> m b arguments. In a Tactical environment, we can write the threading code thusly:

Bracket alloc dealloc use -> do
  alloc'   <- runT  alloc
  dealloc' <- bindT dealloc
  use'     <- bindT use

where

alloc'   ::         Sem (Resource ': r) (f a1)
dealloc' :: f a1 -> Sem (Resource ': r) (f ())
use'     :: f a1 -> Sem (Resource ': r) (f x)

The f type here is existential and corresponds to "whatever state the other effects want to keep track of." f is always a Functor.

alloc', dealloc' and use' are now in a form that can be easily consumed by your interpreter. At this point, simply bind them in the desired order and continue on your merry way.

We can see from the types of dealloc' and use' that since they both consume a f a1, they must run in the same stateful environment. This means, for illustration, any puts run inside the use block will not be visible inside of the dealloc block.

Power users may explicitly use getInitialStateT and bindT to construct whatever data flow they'd like; although this is usually unnecessary.

type WithTactics (e :: Effect) (f :: Type -> Type) (m :: Type -> Type) (r :: [Effect]) = (Tactics f m (e ': r) :: (Type -> Type) -> Type -> Type) ': r #

newtype Inspector (f :: Type -> Type) #

A container for inspect. See the documentation for getInspectorT.

Constructors

Inspector 

Fields

(.@@) infixl 8 #

Arguments

:: forall m (r :: [Effect]) (e :: Effect) f z. Monad m 
=> (forall x. Sem r x -> m x)

The lowering function, likely runM.

-> (forall y. (forall x. Sem r x -> m x) -> Sem (e ': r) y -> Sem r (f y)) 
-> Sem (e ': r) z 
-> m (f z) 

Like .@, but for interpreters which change the resulting type --- eg. lowerError.

(.@) infixl 8 #

Arguments

:: forall m (r :: [Effect]) (e :: Effect) z. Monad m 
=> (forall x. Sem r x -> m x)

The lowering function, likely runM.

-> (forall y. (forall x. Sem r x -> m x) -> Sem (e ': r) y -> Sem r y) 
-> Sem (e ': r) z 
-> m z 

Some interpreters need to be able to lower down to the base monad (often IO) in order to function properly --- some good examples of this are lowerError and lowerResource.

However, these interpreters don't compose particularly nicely; for example, to run lowerResource, you must write:

runM . lowerError runM

Notice that runM is duplicated in two places here. The situation gets exponentially worse the more intepreters you have that need to run in this pattern.

Instead, .@ performs the composition we'd like. The above can be written as

(runM .@ lowerError)

The parentheses here are important; without them you'll run into operator precedence errors.

Warning: This combinator will duplicate work that is intended to be just for initialization. This can result in rather surprising behavior. For a version of .@ that won't duplicate work, see the .@! operator in polysemy-zoo.

Interpreters using Final may be composed normally, and avoid the work duplication issue. For that reason, you're encouraged to use -Final interpreters instead of lower- interpreters whenever possible.

runM :: Monad m => Sem '[Embed m] a -> m a #

Lower a Sem containing only a single lifted Monad into that monad.

embed :: forall m (r :: [(Type -> Type) -> Type -> Type]) a. Member (Embed m) r => m a -> Sem r a #

Embed a monadic action m in Sem.

Since: polysemy-1.0.0.0

insertAt :: forall (index :: Nat) (inserted :: [Effect]) (head :: [Effect]) (oldTail :: [Effect]) (tail :: [Effect]) (old :: [Effect]) (full :: [Effect]) a. (ListOfLength index head, WhenStuck index (InsertAtUnprovidedIndex :: Constraint), old ~ Append head oldTail, tail ~ Append inserted oldTail, full ~ Append head tail, InsertAtIndex index head tail oldTail full inserted) => Sem old a -> Sem full a #

Introduce a set of effects into Sem at the index i, before the effect that previously occupied that position. This is intended to be used with a type application:

let
  sem1 :: Sem [e1, e2, e3, e4, e5] a
  sem1 = insertAt @2 (sem0 :: Sem [e1, e2, e5] a)

Since: polysemy-1.6.0.0

subsume :: forall (e :: Effect) (r :: [Effect]) a. Member e r => Sem (e ': r) a -> Sem r a #

Interprets an effect in terms of another identical effect.

This is useful for defining interpreters that use reinterpretH without immediately consuming the newly introduced effect. Using such an interpreter recursively may result in duplicate effects, which may then be eliminated using subsume.

For a version that can introduce an arbitrary number of new effects and reorder existing ones, see subsume_.

Since: polysemy-1.2.0.0

subsume_ :: forall (r :: EffectRow) (r' :: EffectRow) a. Subsume r r' => Sem r a -> Sem r' a #

Allows reordering and adding known effects on top of the effect stack, as long as the polymorphic "tail" of new stack is a raise-d version of the original one. This function is highly polymorphic, so it may be a good idea to use its more concrete version (subsume), fitting functions from the raise family or type annotations to avoid vague errors in ambiguous contexts.

Since: polysemy-1.4.0.0

raise3Under :: forall (e4 :: Effect) (e1 :: Effect) (e2 :: Effect) (e3 :: Effect) (r :: [Effect]) a. Sem (e1 ': (e2 ': (e3 ': r))) a -> Sem (e1 ': (e2 ': (e3 ': (e4 ': r)))) a #

Like raise, but introduces an effect three levels underneath the head of the list.

Since: polysemy-1.4.0.0

raise2Under :: forall (e3 :: Effect) (e1 :: Effect) (e2 :: Effect) (r :: [Effect]) a. Sem (e1 ': (e2 ': r)) a -> Sem (e1 ': (e2 ': (e3 ': r))) a #

Like raise, but introduces an effect two levels underneath the head of the list.

Since: polysemy-1.4.0.0

raiseUnder3 :: forall (e2 :: Effect) (e3 :: Effect) (e4 :: Effect) (e1 :: Effect) (r :: [Effect]) a. Sem (e1 ': r) a -> Sem (e1 ': (e2 ': (e3 ': (e4 ': r)))) a #

Like raise, but introduces three new effects underneath the head of the list.

Since: polysemy-1.2.0.0

raiseUnder2 :: forall (e2 :: Effect) (e3 :: Effect) (e1 :: Effect) (r :: [Effect]) a. Sem (e1 ': r) a -> Sem (e1 ': (e2 ': (e3 ': r))) a #

Like raise, but introduces two new effects underneath the head of the list.

Since: polysemy-1.2.0.0

raiseUnder :: forall (e2 :: Effect) (e1 :: Effect) (r :: [Effect]) a. Sem (e1 ': r) a -> Sem (e1 ': (e2 ': r)) a #

Like raise, but introduces a new effect underneath the head of the list. See raiseUnder2 or raiseUnder3 for introducing more effects. If you need to introduce even more of them, check out subsume_.

raiseUnder can be used in order to turn transformative interpreters into reinterpreters. This is especially useful if you're writing an interpreter which introduces an intermediary effect, and then want to use an existing interpreter on that effect.

For example, given:

fooToBar :: Member Bar r => Sem (Foo ': r) a -> Sem r a
runBar   :: Sem (Bar ': r) a -> Sem r a

You can write:

runFoo :: Sem (Foo ': r) a -> Sem r a
runFoo =
    runBar     -- Consume Bar
  . fooToBar   -- Interpret Foo in terms of the new Bar
  . raiseUnder -- Introduces Bar under Foo

Since: polysemy-1.2.0.0

raise :: forall (e :: Effect) (r :: EffectRow) a. Sem r a -> Sem (e ': r) a #

Introduce an effect into Sem. Analogous to lift in the mtl ecosystem. For a variant that can introduce an arbitrary number of effects, see raise_.

raise_ :: forall (r :: EffectRow) (r' :: EffectRow) a. Raise r r' => Sem r a -> Sem r' a #

Introduce an arbitrary number of effects on top of the effect stack. This function is highly polymorphic, so it may be good idea to use its more concrete versions (like raise) or type annotations to avoid vague errors in ambiguous contexts.

Since: polysemy-1.4.0.0

type family Members (es :: [k]) (r :: [k]) where ... #

Makes constraints of functions that use multiple effects shorter by translating single list of effects into multiple Member constraints:

foo :: Members '[ Output Int
                , Output Bool
                , State String
                ] r
    => Sem r ()

translates into:

foo :: ( Member (Output Int) r
       , Member (Output Bool) r
       , Member (State String) r
       )
    => Sem r ()

Since: polysemy-0.1.2.0

Equations

Members ('[] :: [k]) (r :: [k]) = () 
Members (e ': es :: [k]) (r :: [k]) = (Member e r, Members es r) 

type InterpreterFor (e :: Effect) (r :: [Effect]) = forall a. Sem (e ': r) a -> Sem r a #

Type synonym for interpreters that consume an effect without changing the return value. Offered for user convenience.

r Is kept polymorphic so it's possible to place constraints upon it:

teletypeToIO :: Member (Embed IO) r
             => InterpreterFor Teletype r

type InterpretersFor (es :: [Effect]) (r :: [Effect]) = forall a. Sem (Append es r) a -> Sem r a #

Variant of InterpreterFor that takes a list of effects. @since 1.5.0.0

type Member (e :: k) (r :: [k]) = MemberNoError e r #

A proof that the effect e is available somewhere inside of the effect stack r.

type MemberWithError (e :: Effect) (r :: [Effect]) = (MemberNoError e r, WhenStuck (LocateEffect e r) (AmbiguousSend e r :: Constraint)) #

Like Member, but will produce an error message if the types are ambiguous. This is the constraint used for actions generated by makeSem.

Be careful with this. Due to quirks of TypeError, the custom error messages emitted by this can potentially override other, more helpful error messages. See the discussion in Issue #227.

Since: polysemy-1.2.3.0

data Sem (r :: EffectRow) a #

The Sem monad handles computations of arbitrary extensible effects. A value of type Sem r describes a program with the capabilities of r. For best results, r should always be kept polymorphic, but you can add capabilities via the Member constraint.

The value of the Sem monad is that it allows you to write programs against a set of effects without a predefined meaning, and provide that meaning later. For example, unlike with mtl, you can decide to interpret an Error effect traditionally as an Either, or instead as (a significantly faster) IO Exception. These interpretations (and others that you might add) may be used interchangeably without needing to write any newtypes or Monad instances. The only change needed to swap interpretations is to change a call from runError to errorToIOFinal.

The effect stack r can contain arbitrary other monads inside of it. These monads are lifted into effects via the Embed effect. Monadic values can be lifted into a Sem via embed.

Higher-order actions of another monad can be lifted into higher-order actions of Sem via the Final effect, which is more powerful than Embed, but also less flexible to interpret.

A Sem can be interpreted as a pure value (via run) or as any traditional Monad (via runM or runFinal). Each effect E comes equipped with some interpreters of the form:

runE :: Sem (E ': r) a -> Sem r a

which is responsible for removing the effect E from the effect stack. It is the order in which you call the interpreters that determines the monomorphic representation of the r parameter.

Order of interpreters can be important - it determines behaviour of effects that manipulate state or change control flow. For example, when interpreting this action:

>>> :{
  example :: Members '[State String, Error String] r => Sem r String
  example = do
    put "start"
    let throwing, catching :: Members '[State String, Error String] r => Sem r String
        throwing = do
          modify (++"-throw")
          throw "error"
          get
        catching = do
          modify (++"-catch")
          get
    catch @String throwing (\ _ -> catching)
:}

when handling Error first, state is preserved after error occurs:

>>> :{
  example
    & runError
    & fmap (either id id)
    & evalState ""
    & runM
    & (print =<<)
:}
"start-throw-catch"

while handling State first discards state in such cases:

>>> :{
  example
    & evalState ""
    & runError
    & fmap (either id id)
    & runM
    & (print =<<)
:}
"start-catch"

A good rule of thumb is to handle effects which should have "global" behaviour over other effects later in the chain.

After all of your effects are handled, you'll be left with either a Sem '[] a, a Sem '[ Embed m ] a, or a Sem '[ Final m ] a value, which can be consumed respectively by run, runM, and runFinal.

Examples

As an example of keeping r polymorphic, we can consider the type

Member (State String) r => Sem r ()

to be a program with access to

get :: Sem r String
put :: String -> Sem r ()

methods.

By also adding a

Member (Error Bool) r

constraint on r, we gain access to the

throw :: Bool -> Sem r a
catch :: Sem r a -> (Bool -> Sem r a) -> Sem r a

functions as well.

In this sense, a Member (State s) r constraint is analogous to mtl's MonadState s m and should be thought of as such. However, unlike mtl, a Sem monad may have an arbitrary number of the same effect.

For example, we can write a Sem program which can output either Ints or Bools:

foo :: ( Member (Output Int) r
       , Member (Output Bool) r
       )
    => Sem r ()
foo = do
  output @Int  5
  output True

Notice that we must use -XTypeApplications to specify that we'd like to use the (Output Int) effect.

Since: polysemy-0.1.2.0

Instances

Instances details
Member (Fail :: (Type -> Type) -> Type -> Type) r => MonadFail (Sem r)

Since: polysemy-1.1.0.0

Instance details

Defined in Polysemy.Internal

Methods

fail :: String -> Sem r a #

Member Fixpoint r => MonadFix (Sem r) 
Instance details

Defined in Polysemy.Internal

Methods

mfix :: (a -> Sem r a) -> Sem r a #

Member (Embed IO) r => MonadIO (Sem r)

This instance will only lift IO actions. If you want to lift into some other MonadIO type, use this instance, and handle it via the embedToMonadIO interpretation.

Instance details

Defined in Polysemy.Internal

Methods

liftIO :: IO a -> Sem r a #

Member NonDet r => Alternative (Sem r) 
Instance details

Defined in Polysemy.Internal

Methods

empty :: Sem r a #

(<|>) :: Sem r a -> Sem r a -> Sem r a #

some :: Sem r a -> Sem r [a] #

many :: Sem r a -> Sem r [a] #

Applicative (Sem f) 
Instance details

Defined in Polysemy.Internal

Methods

pure :: a -> Sem f a #

(<*>) :: Sem f (a -> b) -> Sem f a -> Sem f b #

liftA2 :: (a -> b -> c) -> Sem f a -> Sem f b -> Sem f c #

(*>) :: Sem f a -> Sem f b -> Sem f b #

(<*) :: Sem f a -> Sem f b -> Sem f a #

Functor (Sem f) 
Instance details

Defined in Polysemy.Internal

Methods

fmap :: (a -> b) -> Sem f a -> Sem f b #

(<$) :: a -> Sem f b -> Sem f a #

Monad (Sem f) 
Instance details

Defined in Polysemy.Internal

Methods

(>>=) :: Sem f a -> (a -> Sem f b) -> Sem f b #

(>>) :: Sem f a -> Sem f b -> Sem f b #

return :: a -> Sem f a #

Member NonDet r => MonadPlus (Sem r)

Since: polysemy-0.2.1.0

Instance details

Defined in Polysemy.Internal

Methods

mzero :: Sem r a #

mplus :: Sem r a -> Sem r a -> Sem r a #

Monoid a => Monoid (Sem f a)

Since: polysemy-1.6.0.0

Instance details

Defined in Polysemy.Internal

Methods

mempty :: Sem f a #

mappend :: Sem f a -> Sem f a -> Sem f a #

mconcat :: [Sem f a] -> Sem f a #

Semigroup a => Semigroup (Sem f a)

Since: polysemy-1.6.0.0

Instance details

Defined in Polysemy.Internal

Methods

(<>) :: Sem f a -> Sem f a -> Sem f a #

sconcat :: NonEmpty (Sem f a) -> Sem f a #

stimes :: Integral b => b -> Sem f a -> Sem f a #

type Effect = (Type -> Type) -> Type -> Type #

The kind of effects.

Since: polysemy-0.5.0.0

type EffectRow = [Effect] #

The kind of effect rows.

Since: polysemy-0.5.0.0

newtype Embed (m :: Type -> Type) (z :: Type -> Type) a where #

An effect which allows a regular Monad m into the Sem ecosystem. Monadic actions in m can be lifted into Sem via embed.

For example, you can use this effect to lift IO actions directly into Sem:

embed (putStrLn "hello") :: Member (Embed IO) r => Sem r ()

That being said, you lose out on a significant amount of the benefits of Sem by using embed directly in application code; doing so will tie your application code directly to the underlying monad, and prevent you from interpreting it differently. For best results, only use Embed in your effect interpreters.

Consider using trace and traceToIO as a substitute for using putStrLn directly.

Since: polysemy-1.0.0.0

Constructors

Embed 

Fields

lowerAsync #

Arguments

:: forall (r :: [(Type -> Type) -> Type -> Type]) a. Member (Embed IO) r 
=> (forall x. Sem r x -> IO x)

Strategy for lowering a Sem action down to IO. This is likely some combination of runM and other interpreters composed via .@.

-> Sem (Async ': r) a 
-> Sem r a 

Run an Async effect in terms of async.

Since: polysemy-1.0.0.0

asyncToIOFinal :: forall (r :: [(Type -> Type) -> Type -> Type]) a. Member (Final IO) r => Sem (Async ': r) a -> Sem r a #

Run an Async effect in terms of async through final IO.

Beware: Effects that aren't interpreted in terms of IO will have local state semantics in regards to Async effects interpreted this way. See Final.

Notably, unlike asyncToIO, this is not consistent with State unless runStateIORef is used. State that seems like it should be threaded globally throughout Async will not be.

Use asyncToIO instead if you need to run pure, stateful interpreters after the interpreter for Async. (Pure interpreters are interpreters that aren't expressed in terms of another effect or monad; for example, runState.)

Since: polysemy-1.2.0.0

asyncToIO :: forall (r :: [(Type -> Type) -> Type -> Type]) a. Member (Embed IO) r => Sem (Async ': r) a -> Sem r a #

A more flexible --- though less performant --- version of asyncToIOFinal.

This function is capable of running Async effects anywhere within an effect stack, without relying on Final to lower it into IO. Notably, this means that State effects will be consistent in the presence of Async.

asyncToIO is unsafe if you're using await inside higher-order actions of other effects interpreted after Async. See Issue #205.

Prefer asyncToIOFinal unless you need to run pure, stateful interpreters after the interpreter for Async. (Pure interpreters are interpreters that aren't expressed in terms of another effect or monad; for example, runState.)

Since: polysemy-1.0.0.0

sequenceConcurrently :: forall t (r :: [(Type -> Type) -> Type -> Type]) a. (Traversable t, Member Async r) => t (Sem r a) -> Sem r (t (Maybe a)) #

Perform a sequence of effectful actions concurrently.

Since: polysemy-1.2.2.0

cancel :: forall (r :: [Effect]) a. MemberWithError Async r => Async a -> Sem r () #

await :: forall (r :: [Effect]) a. MemberWithError Async r => Async a -> Sem r a #

async :: forall (r :: [Effect]) a. MemberWithError Async r => Sem r a -> Sem r (Async (Maybe a)) #

data Async (m :: Type -> Type) a #

An effect for spawning asynchronous computations.

The Maybe returned by async is due to the fact that we can't be sure an Error effect didn't fail locally.

Since: polysemy-0.5.0.0

Instances

Instances details
type DefiningModule Async 
Instance details

Defined in Polysemy.Async

type DefiningModule Async = "Polysemy.Async"

atomicStateToState :: forall s (r :: [(Type -> Type) -> Type -> Type]) a. Member (State s :: (Type -> Type) -> Type -> Type) r => Sem ((AtomicState s :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r a #

Transform an AtomicState effect to a State effect, discarding the notion of atomicity.

atomicStateToIO :: forall s (r :: [(Type -> Type) -> Type -> Type]) a. Member (Embed IO) r => s -> Sem ((AtomicState s :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r (s, a) #

Run an AtomicState effect in terms of atomic operations in IO.

Internally, this simply creates a new IORef, passes it to runAtomicStateIORef, and then returns the result and the final value of the IORef.

Beware: As this uses an IORef internally, all other effects will have local state semantics in regards to AtomicState effects interpreted this way. For example, throw and catch will never revert atomicModifys, even if runError is used after atomicStateToIO.

Since: polysemy-1.2.0.0

runAtomicStateTVar :: forall (r :: [(Type -> Type) -> Type -> Type]) s a. Member (Embed IO) r => TVar s -> Sem ((AtomicState s :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r a #

Run an AtomicState effect by transforming it into atomic operations over a TVar.

runAtomicStateIORef :: forall s (r :: [(Type -> Type) -> Type -> Type]) a. Member (Embed IO) r => IORef s -> Sem ((AtomicState s :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r a #

Run an AtomicState effect by transforming it into atomic operations over an IORef.

atomicModify' :: forall s (r :: [(Type -> Type) -> Type -> Type]). Member (AtomicState s :: (Type -> Type) -> Type -> Type) r => (s -> s) -> Sem r () #

A variant of atomicModify in which the computation is strict in the new state.

atomicModify :: forall s (r :: [(Type -> Type) -> Type -> Type]). Member (AtomicState s :: (Type -> Type) -> Type -> Type) r => (s -> s) -> Sem r () #

atomicPut :: forall s (r :: [(Type -> Type) -> Type -> Type]). Member (AtomicState s :: (Type -> Type) -> Type -> Type) r => s -> Sem r () #

atomicState' :: forall s a (r :: [(Type -> Type) -> Type -> Type]). Member (AtomicState s :: (Type -> Type) -> Type -> Type) r => (s -> (s, a)) -> Sem r a #

A variant of atomicState in which the computation is strict in the new state and return value.

atomicGets :: forall s s' (r :: [(Type -> Type) -> Type -> Type]). Member (AtomicState s :: (Type -> Type) -> Type -> Type) r => (s -> s') -> Sem r s' #

Since: polysemy-1.2.2.0

atomicGet :: forall s (r :: [(Type -> Type) -> Type -> Type]). Member (AtomicState s :: (Type -> Type) -> Type -> Type) r => Sem r s #

atomicState :: forall s a (r :: [(Type -> Type) -> Type -> Type]). Member (AtomicState s :: (Type -> Type) -> Type -> Type) r => (s -> (s, a)) -> Sem r a #

Atomically reads and modifies the state.

data AtomicState s (m :: k) a #

A variant of State that supports atomic operations.

Since: polysemy-1.1.0.0

Instances

Instances details
type DefiningModule (AtomicState :: Type -> k -> Type -> Type) 
Instance details

Defined in Polysemy.AtomicState

type DefiningModule (AtomicState :: Type -> k -> Type -> Type) = "Polysemy.AtomicState"

lowerError #

Arguments

:: forall e (r :: [(Type -> Type) -> Type -> Type]) a. (Typeable e, Member (Embed IO) r) 
=> (forall x. Sem r x -> IO x)

Strategy for lowering a Sem action down to IO. This is likely some combination of runM and other interpreters composed via .@.

-> Sem ((Error e :: (Type -> Type) -> Type -> Type) ': r) a 
-> Sem r (Either e a) 

Run an Error effect as an IO Exception. This interpretation is significantly faster than runError, at the cost of being less flexible.

Since: polysemy-1.0.0.0

errorToIOFinal :: forall e (r :: [(Type -> Type) -> Type -> Type]) a. (Typeable e, Member (Final IO) r) => Sem ((Error e :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r (Either e a) #

Run an Error effect as an IO Exception through final IO. This interpretation is significantly faster than runError.

Beware: Effects that aren't interpreted in terms of IO will have local state semantics in regards to Error effects interpreted this way. See Final.

Since: polysemy-1.2.0.0

mapError :: forall e1 e2 (r :: [(Type -> Type) -> Type -> Type]) a. Member (Error e2 :: (Type -> Type) -> Type -> Type) r => (e1 -> e2) -> Sem ((Error e1 :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r a #

Transform one Error into another. This function can be used to aggregate multiple errors into a single type.

Since: polysemy-1.0.0.0

runError :: forall e (r :: [(Type -> Type) -> Type -> Type]) a. Sem ((Error e :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r (Either e a) #

Run an Error effect in the style of ExceptT.

catchJust #

Arguments

:: forall e (r :: [(Type -> Type) -> Type -> Type]) b a. Member (Error e :: (Type -> Type) -> Type -> Type) r 
=> (e -> Maybe b)

Predicate to select exceptions

-> Sem r a

Computation to run

-> (b -> Sem r a)

Handler

-> Sem r a 

The function catchJust is like catch, but it takes an extra argument which is an exception predicate, a function which selects which type of exceptions we're interested in.

tryJust :: forall e (r :: [(Type -> Type) -> Type -> Type]) b a. Member (Error e :: (Type -> Type) -> Type -> Type) r => (e -> Maybe b) -> Sem r a -> Sem r (Either b a) #

A variant of try that takes an exception predicate to select which exceptions are caught (c.f. catchJust). If the exception does not match the predicate, it is re-thrown.

try :: forall e (r :: [(Type -> Type) -> Type -> Type]) a. Member (Error e :: (Type -> Type) -> Type -> Type) r => Sem r a -> Sem r (Either e a) #

Similar to catch, but returns an Either result which is (Right a) if no exception of type e was thrown, or (Left ex) if an exception of type e was thrown and its value is ex.

note :: forall e (r :: [(Type -> Type) -> Type -> Type]) a. Member (Error e :: (Type -> Type) -> Type -> Type) r => e -> Maybe a -> Sem r a #

Attempt to extract a Just a from a Maybe a, throwing the provided exception upon Nothing.

fromExceptionSemVia :: forall exc err (r :: [(Type -> Type) -> Type -> Type]) a. (Exception exc, Member (Error err :: (Type -> Type) -> Type -> Type) r, Member (Final IO) r) => (exc -> err) -> Sem r a -> Sem r a #

Like fromExceptionSem, but with the ability to transform the exception before turning it into an Error.

fromExceptionSem :: forall e (r :: [(Type -> Type) -> Type -> Type]) a. (Exception e, Member (Error e :: (Type -> Type) -> Type -> Type) r, Member (Final IO) r) => Sem r a -> Sem r a #

Run a Sem r action, converting any IO exception generated by it into an Error.

fromExceptionVia :: forall exc err (r :: [(Type -> Type) -> Type -> Type]) a. (Exception exc, Member (Error err :: (Type -> Type) -> Type -> Type) r, Member (Embed IO) r) => (exc -> err) -> IO a -> Sem r a #

Like fromException, but with the ability to transform the exception before turning it into an Error.

fromException :: forall e (r :: [(Type -> Type) -> Type -> Type]) a. (Exception e, Member (Error e :: (Type -> Type) -> Type -> Type) r, Member (Embed IO) r) => IO a -> Sem r a #

Lift an exception generated from an IO action into an Error.

fromEitherM :: forall e m (r :: [(Type -> Type) -> Type -> Type]) a. (Member (Error e :: (Type -> Type) -> Type -> Type) r, Member (Embed m) r) => m (Either e a) -> Sem r a #

A combinator doing embed and fromEither at the same time. Useful for interoperating with IO.

Since: polysemy-0.5.1.0

fromEither :: forall e (r :: [(Type -> Type) -> Type -> Type]) a. Member (Error e :: (Type -> Type) -> Type -> Type) r => Either e a -> Sem r a #

Upgrade an Either into an Error effect.

Since: polysemy-0.5.1.0

catch :: forall e (r :: [Effect]) a. MemberWithError (Error e :: (Type -> Type) -> Type -> Type) r => Sem r a -> (e -> Sem r a) -> Sem r a #

throw :: forall e (r :: [Effect]) a. MemberWithError (Error e :: (Type -> Type) -> Type -> Type) r => e -> Sem r a #

data Error e (m :: k -> Type) (a :: k) #

Instances

Instances details
type DefiningModule (Error :: Type -> (k -> Type) -> k -> Type) 
Instance details

Defined in Polysemy.Error

type DefiningModule (Error :: Type -> (k -> Type) -> k -> Type) = "Polysemy.Error"

failToEmbed :: forall (m :: Type -> Type) (r :: [(Type -> Type) -> Type -> Type]) a. (Member (Embed m) r, MonadFail m) => Sem ((Fail :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r a #

Run a Fail effect in terms of an underlying MonadFail instance.

failToNonDet :: forall (r :: [(Type -> Type) -> Type -> Type]) a. Member NonDet r => Sem ((Fail :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r a #

Transform a Fail effect into a NonDet effect, through mapping any failure to empty.

failToError :: forall e (r :: [(Type -> Type) -> Type -> Type]) a. Member (Error e :: (Type -> Type) -> Type -> Type) r => (String -> e) -> Sem ((Fail :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r a #

Transform a Fail effect into an Error e effect, through providing a function for transforming any failure to an exception.

runFail :: forall (r :: [(Type -> Type) -> Type -> Type]) a. Sem ((Fail :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r (Either String a) #

Run a Fail effect purely.

data Fail (m :: k) (a :: k1) #

runInputSem :: forall i (r :: EffectRow) a. Sem r i -> Sem ((Input i :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r a #

Runs an Input effect by evaluating a monadic action for each request.

runInputList :: forall i (r :: [(Type -> Type) -> Type -> Type]) a. [i] -> Sem ((Input (Maybe i) :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r a #

Run an Input effect by providing a different element of a list each time. Returns Nothing after the list is exhausted.

runInputConst :: forall i (r :: [(Type -> Type) -> Type -> Type]) a. i -> Sem ((Input i :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r a #

Run an Input effect by always giving back the same value.

inputs :: forall i j (r :: [(Type -> Type) -> Type -> Type]). Member (Input i :: (Type -> Type) -> Type -> Type) r => (i -> j) -> Sem r j #

Apply a function to an input, cf. asks

input :: forall i (r :: [Effect]). MemberWithError (Input i :: (Type -> Type) -> Type -> Type) r => Sem r i #

data Input (i :: k) (m :: k1) (a :: k) #

An effect which can provide input to an application. Useful for dealing with streaming input.

Instances

Instances details
type DefiningModule (Input :: k1 -> k2 -> k1 -> Type) 
Instance details

Defined in Polysemy.Input

type DefiningModule (Input :: k1 -> k2 -> k1 -> Type) = "Polysemy.Input"

runOutputSem :: forall o (r :: EffectRow) a. (o -> Sem r ()) -> Sem ((Output o :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r a #

Runs an Output effect by running a monadic action for each of its values.

runOutputBatched :: forall o (r :: [(Type -> Type) -> Type -> Type]) a. Member (Output [o] :: (Type -> Type) -> Type -> Type) r => Int -> Sem ((Output o :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r a #

Accumulate outputs so they are delayed until they reach at least size size.

If size is 0, this interpretation will not emit anything in the resulting Output effect.

Since: polysemy-1.0.0.0

ignoreOutput :: forall o (r :: [(Type -> Type) -> Type -> Type]) a. Sem ((Output o :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r a #

Run an Output effect by ignoring it.

Since: polysemy-1.0.0.0

outputToIOMonoidAssocR :: forall o m (r :: [(Type -> Type) -> Type -> Type]) a. (Monoid m, Member (Embed IO) r) => (o -> m) -> Sem ((Output o :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r (m, a) #

Like outputToIOMonoid, but right-associates uses of <>.

This asymptotically improves performance if the time complexity of <> for the Monoid depends only on the size of the first argument.

You should always use this instead of outputToIOMonoid if the monoid is a list, such as String.

Beware: As this uses an IORef internally, all other effects will have local state semantics in regards to Output effects interpreted this way. For example, throw and catch will never revert outputs, even if runError is used after outputToIOMonoidAssocR.

Since: polysemy-1.2.0.0

outputToIOMonoid :: forall o m (r :: [(Type -> Type) -> Type -> Type]) a. (Monoid m, Member (Embed IO) r) => (o -> m) -> Sem ((Output o :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r (m, a) #

Run an Output effect in terms of atomic operations in IO.

Internally, this simply creates a new IORef, passes it to runOutputMonoidIORef, and then returns the result and the final value of the IORef.

Beware: As this uses an IORef internally, all other effects will have local state semantics in regards to Output effects interpreted this way. For example, throw and catch will never revert outputs, even if runError is used after outputToIOMonoid.

Since: polysemy-1.2.0.0

runOutputMonoidTVar :: forall o m (r :: [(Type -> Type) -> Type -> Type]) a. (Monoid m, Member (Embed IO) r) => TVar m -> (o -> m) -> Sem ((Output o :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r a #

Run an Output effect by transforming it into atomic operations over a TVar.

Since: polysemy-1.1.0.0

runOutputMonoidIORef :: forall o m (r :: [(Type -> Type) -> Type -> Type]) a. (Monoid m, Member (Embed IO) r) => IORef m -> (o -> m) -> Sem ((Output o :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r a #

Run an Output effect by transforming it into atomic operations over an IORef.

Since: polysemy-1.1.0.0

runLazyOutputMonoidAssocR :: forall o m (r :: [(Type -> Type) -> Type -> Type]) a. Monoid m => (o -> m) -> Sem ((Output o :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r (m, a) #

Like runLazyOutputMonoid, but right-associates uses of <>.

This asymptotically improves performance if the time complexity of <> for the Monoid depends only on the size of the first argument.

You should always use this instead of runLazyOutputMonoid if the monoid is a list, such as String.

Warning: This inherits the nasty space leak issue of WriterT! Don't use this if you don't have to.

Since: polysemy-1.3.0.0

runOutputMonoidAssocR :: forall o m (r :: [(Type -> Type) -> Type -> Type]) a. Monoid m => (o -> m) -> Sem ((Output o :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r (m, a) #

Like runOutputMonoid, but right-associates uses of <>.

This asymptotically improves performance if the time complexity of <> for the Monoid depends only on the size of the first argument.

You should always use this instead of runOutputMonoid if the monoid is a list, such as String.

Since: polysemy-1.1.0.0

runLazyOutputMonoid :: forall o m (r :: [(Type -> Type) -> Type -> Type]) a. Monoid m => (o -> m) -> Sem ((Output o :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r (m, a) #

Run an Output effect by transforming it into a monoid, and accumulate it lazily.

Warning: This inherits the nasty space leak issue of WriterT! Don't use this if you don't have to.

Since: polysemy-1.3.0.0

runOutputMonoid :: forall o m (r :: [(Type -> Type) -> Type -> Type]) a. Monoid m => (o -> m) -> Sem ((Output o :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r (m, a) #

Run an Output effect by transforming it into a monoid.

Since: polysemy-1.0.0.0

runLazyOutputList :: forall o (r :: [(Type -> Type) -> Type -> Type]) a. Sem ((Output o :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r ([o], a) #

Run an Output effect by transforming it into a list of its values, lazily.

Warning: This inherits the nasty space leak issue of WriterT! Don't use this if you don't have to.

Since: polysemy-1.3.0.0

runOutputList :: forall o (r :: [(Type -> Type) -> Type -> Type]) a. Sem ((Output o :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r ([o], a) #

Run an Output effect by transforming it into a list of its values.

Since: polysemy-1.0.0.0

output :: forall o (r :: [Effect]). MemberWithError (Output o :: (Type -> Type) -> Type -> Type) r => o -> Sem r () #

data Output o (m :: k) a #

An effect capable of sending messages. Useful for streaming output and for logging.

Instances

Instances details
type DefiningModule (Output :: Type -> k -> Type -> Type) 
Instance details

Defined in Polysemy.Output

type DefiningModule (Output :: Type -> k -> Type -> Type) = "Polysemy.Output"

inputToReader :: forall i (r :: [(Type -> Type) -> Type -> Type]) a. Member (Reader i) r => Sem ((Input i :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r a #

Transform an Input effect into a Reader effect.

Since: polysemy-1.0.0.0

runReader :: forall i (r :: [(Type -> Type) -> Type -> Type]) a. i -> Sem (Reader i ': r) a -> Sem r a #

Run a Reader effect with a constant value.

asks :: forall i j (r :: [(Type -> Type) -> Type -> Type]). Member (Reader i) r => (i -> j) -> Sem r j #

local :: forall i (r :: [Effect]) a. MemberWithError (Reader i) r => (i -> i) -> Sem r a -> Sem r a #

ask :: forall i (r :: [Effect]). MemberWithError (Reader i) r => Sem r i #

data Reader i (m :: Type -> Type) a #

An effect corresponding to ReaderT.

Instances

Instances details
type DefiningModule Reader 
Instance details

Defined in Polysemy.Reader

type DefiningModule Reader = "Polysemy.Reader"

resourceToIO :: forall (r :: [(Type -> Type) -> Type -> Type]) a. Member (Embed IO) r => Sem (Resource ': r) a -> Sem r a #

A more flexible --- though less safe --- version of resourceToIOFinal

This function is capable of running Resource effects anywhere within an effect stack, without relying on an explicit function to lower it into IO. Notably, this means that State effects will be consistent in the presence of Resource.

ResourceToIO' is safe whenever you're concerned about exceptions thrown by effects _already handled_ in your effect stack, or in IO code run directly inside of bracket. It is not safe against exceptions thrown explicitly at the main thread. If this is not safe enough for your use-case, use resourceToIOFinal instead.

This function creates a thread, and so should be compiled with -threaded.

Since: polysemy-1.0.0.0

runResource :: forall (r :: [(Type -> Type) -> Type -> Type]) a. Sem (Resource ': r) a -> Sem r a #

Run a Resource effect purely.

Since: polysemy-1.0.0.0

lowerResource #

Arguments

:: forall (r :: [(Type -> Type) -> Type -> Type]) a. Member (Embed IO) r 
=> (forall x. Sem r x -> IO x)

Strategy for lowering a Sem action down to IO. This is likely some combination of runM and other interpreters composed via .@.

-> Sem (Resource ': r) a 
-> Sem r a 

Run a Resource effect in terms of bracket.

Since: polysemy-1.0.0.0

resourceToIOFinal :: forall (r :: [(Type -> Type) -> Type -> Type]) a. Member (Final IO) r => Sem (Resource ': r) a -> Sem r a #

Run a Resource effect in terms of bracket through final IO

Beware: Effects that aren't interpreted in terms of IO will have local state semantics in regards to Resource effects interpreted this way. See Final.

Notably, unlike resourceToIO, this is not consistent with State unless runStateInIORef is used. State that seems like it should be threaded globally throughout brackets will not be.

Use resourceToIO instead if you need to run pure, stateful interpreters after the interpreter for Resource. (Pure interpreters are interpreters that aren't expressed in terms of another effect or monad; for example, runState.)

Since: polysemy-1.2.0.0

onException #

Arguments

:: forall (r :: [(Type -> Type) -> Type -> Type]) a b. Member Resource r 
=> Sem r a

computation to run first

-> Sem r b

computation to run afterward if an exception was raised

-> Sem r a 

Like bracketOnError, but for the simple case of one computation to run afterward.

Since: polysemy-0.4.0.0

finally #

Arguments

:: forall (r :: [(Type -> Type) -> Type -> Type]) a b. Member Resource r 
=> Sem r a

computation to run first

-> Sem r b

computation to run afterward (even if an exception was raised)

-> Sem r a 

Like bracket, but for the simple case of one computation to run afterward.

Since: polysemy-0.4.0.0

bracket_ #

Arguments

:: forall (r :: [(Type -> Type) -> Type -> Type]) a b c. Member Resource r 
=> Sem r a

computation to run first

-> Sem r b

computation to run last (even if an exception was raised)

-> Sem r c

computation to run in-between

-> Sem r c 

A variant of bracket where the return value from the first computation is not required.

cf. bracket and bracket_

Since: polysemy-1.5.0.0

bracketOnError :: forall (r :: [Effect]) a c b. MemberWithError Resource r => Sem r a -> (a -> Sem r c) -> (a -> Sem r b) -> Sem r b #

bracket :: forall (r :: [Effect]) a c b. MemberWithError Resource r => Sem r a -> (a -> Sem r c) -> (a -> Sem r b) -> Sem r b #

data Resource (m :: Type -> Type) a #

An effect capable of providing bracket semantics. Interpreters for this will successfully run the deallocation action even in the presence of other short-circuiting effects.

Instances

Instances details
type DefiningModule Resource 
Instance details

Defined in Polysemy.Resource

type DefiningModule Resource = "Polysemy.Resource"

hoistStateIntoStateT :: forall s (r :: [(Type -> Type) -> Type -> Type]) a. Sem ((State s :: (Type -> Type) -> Type -> Type) ': r) a -> StateT s (Sem r) a #

Hoist a State effect into a StateT monad transformer. This can be useful when writing interpreters that need to interop with MTL.

Since: polysemy-0.1.3.0

stateToST :: forall s st (r :: [(Type -> Type) -> Type -> Type]) a. Member (Embed (ST st)) r => s -> Sem ((State s :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r (s, a) #

Run an State effect in terms of operations in ST.

Internally, this simply creates a new STRef, passes it to runStateSTRef, and then returns the result and the final value of the STRef.

Beware: As this uses an STRef internally, all other effects will have local state semantics in regards to State effects interpreted this way. For example, throw and catch will never revert puts, even if runError is used after stateToST.

When not using the plugin, one must introduce the existential st type to stateToST, so that the resulting type after runM can be resolved into forall st. ST st (s, a) for use with runST. Doing so requires -XScopedTypeVariables.

stResult :: forall s a. (s, a)
stResult = runST ( (runM $ stateToST @_ @st undefined $ pure undefined) :: forall st. ST st (s, a) )

Since: polysemy-1.3.0.0

runStateSTRef :: forall s st (r :: [(Type -> Type) -> Type -> Type]) a. Member (Embed (ST st)) r => STRef st s -> Sem ((State s :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r a #

Run a State effect by transforming it into operations over an STRef.

Since: polysemy-1.3.0.0

stateToIO :: forall s (r :: [(Type -> Type) -> Type -> Type]) a. Member (Embed IO) r => s -> Sem ((State s :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r (s, a) #

Run an State effect in terms of operations in IO.

Internally, this simply creates a new IORef, passes it to runStateIORef, and then returns the result and the final value of the IORef.

Note: This is not safe in a concurrent setting, as modify isn't atomic. If you need operations over the state to be atomic, use atomicStateToIO instead.

Beware: As this uses an IORef internally, all other effects will have local state semantics in regards to State effects interpreted this way. For example, throw and catch will never revert puts, even if runError is used after stateToIO.

Since: polysemy-1.2.0.0

runStateIORef :: forall s (r :: [(Type -> Type) -> Type -> Type]) a. Member (Embed IO) r => IORef s -> Sem ((State s :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r a #

Run a State effect by transforming it into operations over an IORef.

Note: This is not safe in a concurrent setting, as modify isn't atomic. If you need operations over the state to be atomic, use runAtomicStateIORef or runAtomicStateTVar instead.

Since: polysemy-1.0.0.0

execLazyState :: forall s (r :: [(Type -> Type) -> Type -> Type]) a. s -> Sem ((State s :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r s #

Run a State effect with local state, lazily.

Since: polysemy-1.2.3.1

evalLazyState :: forall s (r :: [(Type -> Type) -> Type -> Type]) a. s -> Sem ((State s :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r a #

Run a State effect with local state, lazily.

Since: polysemy-1.0.0.0

runLazyState :: forall s (r :: [(Type -> Type) -> Type -> Type]) a. s -> Sem ((State s :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r (s, a) #

Run a State effect with local state, lazily.

execState :: forall s (r :: [(Type -> Type) -> Type -> Type]) a. s -> Sem ((State s :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r s #

Run a State effect with local state.

Since: polysemy-1.2.3.1

evalState :: forall s (r :: [(Type -> Type) -> Type -> Type]) a. s -> Sem ((State s :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r a #

Run a State effect with local state.

Since: polysemy-1.0.0.0

runState :: forall s (r :: [(Type -> Type) -> Type -> Type]) a. s -> Sem ((State s :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r (s, a) #

Run a State effect with local state.

modify' :: forall s (r :: [(Type -> Type) -> Type -> Type]). Member (State s :: (Type -> Type) -> Type -> Type) r => (s -> s) -> Sem r () #

A variant of modify in which the computation is strict in the new state.

modify :: forall s (r :: [(Type -> Type) -> Type -> Type]). Member (State s :: (Type -> Type) -> Type -> Type) r => (s -> s) -> Sem r () #

gets :: forall s a (r :: [(Type -> Type) -> Type -> Type]). Member (State s :: (Type -> Type) -> Type -> Type) r => (s -> a) -> Sem r a #

put :: forall s (r :: [Effect]). MemberWithError (State s :: (Type -> Type) -> Type -> Type) r => s -> Sem r () #

get :: forall s (r :: [Effect]). MemberWithError (State s :: (Type -> Type) -> Type -> Type) r => Sem r s #

data State s (m :: k) a #

An effect for providing statefulness. Note that unlike mtl's StateT, there is no restriction that the State effect corresponds necessarily to local state. It could could just as well be interrpeted in terms of HTTP requests or database access.

Interpreters which require statefulness can reinterpret themselves in terms of State, and subsequently call runState.

Instances

Instances details
type DefiningModule (State :: Type -> k -> Type -> Type) 
Instance details

Defined in Polysemy.State

type DefiningModule (State :: Type -> k -> Type -> Type) = "Polysemy.State"

retag :: forall {k1} {k2} (k3 :: k1) (k4 :: k2) (e :: (Type -> Type) -> Type -> Type) (r :: [(Type -> Type) -> Type -> Type]) a. Member (Tagged k4 e) r => Sem (Tagged k3 e ': r) a -> Sem r a #

Transform a Tagged k1 e effect into a Tagged k2 e effect

untag :: forall {k1} (k2 :: k1) (e :: (Type -> Type) -> Type -> Type) (r :: [(Type -> Type) -> Type -> Type]) a. Sem (Tagged k2 e ': r) a -> Sem (e ': r) a #

Run a Tagged k e effect through reinterpreting it to e

tagged :: forall {k1} (k2 :: k1) (e :: Effect) (r :: [Effect]) a. Sem (e ': r) a -> Sem (Tagged k2 e ': r) a #

A reinterpreting version of tag.

tag :: forall {k1} (k2 :: k1) (e :: (Type -> Type) -> Type -> Type) (r :: [(Type -> Type) -> Type -> Type]) a. Member (Tagged k2 e) r => Sem (e ': r) a -> Sem r a #

Tag uses of an effect, effectively gaining access to the tagged effect locally.

This may be used to create tagged- variants of regular actions.

For example:

taggedLocal :: forall k i r a
             . Member (Tagged k (Reader i)) r
            => (i -> i)
            -> Sem r a
            -> Sem r a
taggedLocal f m =
  tag k (Reader i) $ local @i f (raise m)

data Tagged (k3 :: k) (e :: k1 -> k2 -> Type) (m :: k1) (a :: k2) #

An effect for annotating effects and disambiguating identical effects.

writerToIOAssocRFinal :: forall o (r :: [(Type -> Type) -> Type -> Type]) a. (Monoid o, Member (Final IO) r) => Sem (Writer o ': r) a -> Sem r (o, a) #

Like writerToIOFinal. but right-associates uses of <>.

This asymptotically improves performance if the time complexity of <> for the Monoid depends only on the size of the first argument.

You should always use this instead of writerToIOFinal if the monoid is a list, such as String.

Beware: Effects that aren't interpreted in terms of IO will have local state semantics in regards to Writer effects interpreted this way. See Final.

Since: polysemy-1.2.0.0

writerToIOFinal :: forall o (r :: [(Type -> Type) -> Type -> Type]) a. (Monoid o, Member (Final IO) r) => Sem (Writer o ': r) a -> Sem r (o, a) #

Run a Writer effect by transforming it into atomic operations through final IO.

Internally, this simply creates a new TVar, passes it to runWriterTVar, and then returns the result and the final value of the TVar.

Beware: Effects that aren't interpreted in terms of IO will have local state semantics in regards to Writer effects interpreted this way. See Final.

Since: polysemy-1.2.0.0

runWriterTVar :: forall o (r :: [(Type -> Type) -> Type -> Type]) a. (Monoid o, Member (Final IO) r) => TVar o -> Sem (Writer o ': r) a -> Sem r a #

Transform a Writer effect into atomic operations over a TVar through final IO.

Since: polysemy-1.2.0.0

runLazyWriterAssocR :: forall o (r :: [(Type -> Type) -> Type -> Type]) a. Monoid o => Sem (Writer o ': r) a -> Sem r (o, a) #

Like runLazyWriter, but right-associates uses of <>.

This asymptotically improves performance if the time complexity of <> for the Monoid depends only on the size of the first argument.

You should always use this instead of runLazyWriter if the monoid is a list, such as String.

Warning: This inherits the nasty space leak issue of WriterT! Don't use this if you don't have to.

Since: polysemy-1.3.0.0

runWriterAssocR :: forall o (r :: [(Type -> Type) -> Type -> Type]) a. Monoid o => Sem (Writer o ': r) a -> Sem r (o, a) #

Like runWriter, but right-associates uses of <>.

This asymptotically improves performance if the time complexity of <> for the Monoid depends only on the size of the first argument.

You should always use this instead of runWriter if the monoid is a list, such as String.

Since: polysemy-1.1.0.0

runLazyWriter :: forall o (r :: [(Type -> Type) -> Type -> Type]) a. Monoid o => Sem (Writer o ': r) a -> Sem r (o, a) #

Run a Writer effect in the style of WriterT lazily.

Warning: This inherits the nasty space leak issue of WriterT! Don't use this if you don't have to.

Since: polysemy-1.3.0.0

runWriter :: forall o (r :: [(Type -> Type) -> Type -> Type]) a. Monoid o => Sem (Writer o ': r) a -> Sem r (o, a) #

Run a Writer effect in the style of WriterT (but without the nasty space leak!)

outputToWriter :: forall o (r :: [(Type -> Type) -> Type -> Type]) a. Member (Writer o) r => Sem ((Output o :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r a #

Transform an Output effect into a Writer effect.

Since: polysemy-1.0.0.0

censor :: forall o (r :: [(Type -> Type) -> Type -> Type]) a. Member (Writer o) r => (o -> o) -> Sem r a -> Sem r a #

Since: polysemy-0.7.0.0

writerToEndoWriter :: forall o (r :: [(Type -> Type) -> Type -> Type]) a. (Monoid o, Member (Writer (Endo o)) r) => Sem (Writer o ': r) a -> Sem r a #

Transform a Writer o effect into a Writer (Endo o) effect, right-associating all uses of <> for o.

This can be used together with raiseUnder in order to create -AssocR variants out of regular Writer interpreters.

Since: polysemy-1.2.0.0

pass :: forall o (r :: [Effect]) a. MemberWithError (Writer o) r => Sem r (o -> o, a) -> Sem r a #

listen :: forall o (r :: [Effect]) a. MemberWithError (Writer o) r => Sem r a -> Sem r (o, a) #

tell :: forall o (r :: [Effect]). MemberWithError (Writer o) r => o -> Sem r () #

data Writer o (m :: Type -> Type) a #

An effect capable of emitting and intercepting messages.

Instances

Instances details
type DefiningModule Writer 
Instance details

Defined in Polysemy.Internal.Writer

type DefiningModule Writer = "Polysemy.Internal.Writer"

type (++) a b = Append a b infixr 5 Source #

Convenience type alias for concatenating two effect rows.

unitT :: Functor f => Sem (WithTactics e f m r) (f ()) Source #

Convenience alias for pureT ().

send :: forall e (r :: [(Type -> Type) -> Type -> Type]) a. Member e r => e (Sem r) a -> Sem r a #

Embed an effect into a Sem. This is used primarily via makeSem to implement smart constructors.