| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Polysemy.Internal
Synopsis
- newtype Sem r a = Sem {}
- type Member e r = MemberNoError e r
- type MemberWithError e r = (MemberNoError e r, WhenStuck (LocateEffect e r) (AmbiguousSend e r))
- type family Members es r :: Constraint where ...
- send :: Member e r => e (Sem r) a -> Sem r a
- sendUsing :: ElemOf e r -> e (Sem r) a -> Sem r a
- embed :: Member (Embed m) r => m a -> Sem r a
- run :: Sem '[] a -> a
- runM :: Monad m => Sem '[Embed m] a -> m a
- raise_ :: forall r r' a. Raise r r' => Sem r a -> Sem r' a
- class Raise (r :: EffectRow) (r' :: EffectRow) where- raiseUnion :: Union r m a -> Union r' m a
 
- raise :: forall e r a. Sem r a -> Sem (e ': r) a
- raiseUnder :: forall e2 e1 r a. Sem (e1 ': r) a -> Sem (e1 ': (e2 ': r)) a
- raiseUnder2 :: forall e2 e3 e1 r a. Sem (e1 ': r) a -> Sem (e1 ': (e2 ': (e3 ': r))) a
- raiseUnder3 :: forall e2 e3 e4 e1 r a. Sem (e1 ': r) a -> Sem (e1 ': (e2 ': (e3 ': (e4 ': r)))) a
- raise2Under :: forall e3 e1 e2 r a. Sem (e1 ': (e2 ': r)) a -> Sem (e1 ': (e2 ': (e3 ': r))) a
- raise3Under :: forall e4 e1 e2 e3 r a. Sem (e1 ': (e2 ': (e3 ': r))) a -> Sem (e1 ': (e2 ': (e3 ': (e4 ': r)))) a
- subsume_ :: forall r r' a. Subsume r r' => Sem r a -> Sem r' a
- class Subsume (r :: EffectRow) (r' :: EffectRow) where- subsumeUnion :: Union r m a -> Union r' m a
 
- subsume :: forall e r a. Member e r => Sem (e ': r) a -> Sem r a
- subsumeUsing :: forall e r a. ElemOf e r -> Sem (e ': r) a -> Sem r a
- newtype Embed m (z :: Type -> Type) a where
- usingSem :: Monad m => (forall x. Union r (Sem r) x -> m x) -> Sem r a -> m a
- liftSem :: Union r (Sem r) a -> Sem r a
- hoistSem :: (forall x. Union r (Sem r) x -> Union r' (Sem r') x) -> Sem r a -> Sem r' a
- type InterpreterFor e r = forall a. Sem (e ': r) a -> Sem r a
- (.@) :: Monad m => (forall x. Sem r x -> m x) -> (forall y. (forall x. Sem r x -> m x) -> Sem (e ': r) y -> Sem r y) -> Sem (e ': r) z -> m z
- (.@@) :: Monad m => (forall x. Sem r x -> m x) -> (forall y. (forall x. Sem r x -> m x) -> Sem (e ': r) y -> Sem r (f y)) -> Sem (e ': r) z -> m (f z)
Documentation
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 ->Semr 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 '[] aSem '[ Embed m ] aSem '[ Final m ] arun, runM, and
 runFinal.
Examples
As an example of keeping r polymorphic, we can consider the type
Member(StateString) r =>Semr ()
to be a program with access to
get::Semr Stringput:: String ->Semr ()
methods.
By also adding a
Member(ErrorBool) r
constraint on r, we gain access to the
throw:: Bool ->Semr acatch::Semr a -> (Bool ->Semr a) ->Semr a
functions as well.
In this sense, a Member (State s) rMonadState s mSem 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(OutputInt) r ,Member(OutputBool) r ) =>Semr () foo = dooutput@Int 5outputTrue
Notice that we must use -XTypeApplications to specify that we'd like to
 use the (Output Int) effect.
Since: 0.1.2.0
Instances
| Monad (Sem f) Source # | |
| Functor (Sem f) Source # | |
| Member Fixpoint r => MonadFix (Sem r) Source # | |
| Defined in Polysemy.Internal | |
| Member (Fail :: (Type -> Type) -> Type -> Type) r => MonadFail (Sem r) Source # | Since: 1.1.0.0 | 
| Defined in Polysemy.Internal | |
| Applicative (Sem f) Source # | |
| Member (Embed IO) r => MonadIO (Sem r) Source # | This instance will only lift  | 
| Defined in Polysemy.Internal | |
| Member NonDet r => Alternative (Sem r) Source # | |
| Member NonDet r => MonadPlus (Sem r) Source # | Since: 0.2.1.0 | 
| Citizen (Sem r a -> b) (Sem r a -> b) Source # | |
| Defined in Polysemy.Law | |
| Citizen (Sem r a) (Sem r a) Source # | |
| Defined in Polysemy.Law | |
type Member e r = MemberNoError e r Source #
A proof that the effect e is available somewhere inside of the effect
 stack r.
type MemberWithError e r = (MemberNoError e r, WhenStuck (LocateEffect e r) (AmbiguousSend e r)) Source #
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: 1.2.3.0
type family Members es r :: Constraint where ... Source #
Makes constraints of functions that use multiple effects shorter by
 translating single list of effects into multiple Member constraints:
foo ::Members'[OutputInt ,OutputBool ,StateString ] r =>Semr ()
translates into:
foo :: (Member(OutputInt) r ,Member(OutputBool) r ,Member(StateString) r ) =>Semr ()
Since: 0.1.2.0
sendUsing :: ElemOf e r -> e (Sem r) a -> Sem r a Source #
Embed an effect into a Sem, given an explicit proof
 that the effect exists in r.
This is useful in conjunction with tryMembership,
 in order to conditionally make use of effects.
embed :: Member (Embed m) r => m a -> Sem r a Source #
Embed a monadic action m in Sem.
Since: 1.0.0.0
raise_ :: forall r r' a. Raise r r' => Sem r a -> Sem r' a Source #
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: 1.4.0.0
class Raise (r :: EffectRow) (r' :: EffectRow) where Source #
See raise'.
Since: 1.4.0.0
Methods
raiseUnion :: Union r m a -> Union r' m a Source #
Instances
| (r' ~ (_0 ': r''), Raise r r'') => Raise r r' Source # | |
| Defined in Polysemy.Internal | |
| Raise r r Source # | |
| Defined in Polysemy.Internal | |
raiseUnder :: forall e2 e1 r a. Sem (e1 ': r) a -> Sem (e1 ': (e2 ': r)) a Source #
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 ::MemberBar r =>Sem(Foo ': r) a ->Semr a runBar ::Sem(Bar ': r) a ->Semr a
You can write:
runFoo ::Sem(Foo ': r) a ->Semr a runFoo = runBar -- Consume Bar . fooToBar -- Interpret Foo in terms of the new Bar .raiseUnder-- Introduces Bar under Foo
Since: 1.2.0.0
raiseUnder2 :: forall e2 e3 e1 r a. Sem (e1 ': r) a -> Sem (e1 ': (e2 ': (e3 ': r))) a Source #
Like raise, but introduces two new effects underneath the head of the
 list.
Since: 1.2.0.0
raiseUnder3 :: forall e2 e3 e4 e1 r a. Sem (e1 ': r) a -> Sem (e1 ': (e2 ': (e3 ': (e4 ': r)))) a Source #
Like raise, but introduces three new effects underneath the head of the
 list.
Since: 1.2.0.0
raise2Under :: forall e3 e1 e2 r a. Sem (e1 ': (e2 ': r)) a -> Sem (e1 ': (e2 ': (e3 ': r))) a Source #
Like raise, but introduces an effect two levels underneath the head of
 the list.
Since: 1.4.0.0
raise3Under :: forall e4 e1 e2 e3 r a. Sem (e1 ': (e2 ': (e3 ': r))) a -> Sem (e1 ': (e2 ': (e3 ': (e4 ': r)))) a Source #
Like raise, but introduces an effect three levels underneath the head
 of the list.
Since: 1.4.0.0
subsume_ :: forall r r' a. Subsume r r' => Sem r a -> Sem r' a Source #
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: 1.4.0.0
class Subsume (r :: EffectRow) (r' :: EffectRow) where Source #
See subsume_.
Since: 1.4.0.0
Methods
subsumeUnion :: Union r m a -> Union r' m a Source #
subsume :: forall e r a. Member e r => Sem (e ': r) a -> Sem r a Source #
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: 1.2.0.0
subsumeUsing :: forall e r a. ElemOf e r -> Sem (e ': r) a -> Sem r a Source #
Interprets an effect in terms of another identical effect, given an
 explicit proof that the effect exists in r.
This is useful in conjunction with tryMembership
 in order to conditionally make use of effects. For example:
tryListen ::KnownRowr =>Semr a -> Maybe (Semr ([Int], a)) tryListen m = casetryMembership@(Writer[Int]) of Just pr -> Just $subsumeUsingpr (listen(raisem)) _ -> Nothing
Since: 1.3.0.0
newtype Embed m (z :: Type -> Type) a where Source #
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(EmbedIO) r =>Semr ()
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: 1.0.0.0
usingSem :: Monad m => (forall x. Union r (Sem r) x -> m x) -> Sem r a -> m a Source #
Like runSem but flipped for better ergonomics sometimes.
type InterpreterFor e r = forall a. Sem (e ': r) a -> Sem r a Source #
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 =>InterpreterForTeletype r
Arguments
| :: Monad m | |
| => (forall x. Sem r x -> m x) | The lowering function, likely  | 
| -> (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
 - interpreters instead of Finallower- interpreters whenever
 possible.