polysemy-1.3.0.0: Higher-order, low-boilerplate, zero-cost free monads.

Safe HaskellNone
LanguageHaskell2010

Polysemy.Membership

Contents

Synopsis

Witnesses

data ElemOf e r where Source #

A proof that e is an element of r.

Due to technical reasons, ElemOf e r is not powerful enough to prove Member e r; however, it can still be used send actions of e into r by using subsumeUsing.

Since: 1.3.0.0

Constructors

Here :: ElemOf e (e ': r)

e is located at the head of the list.

There :: ElemOf e r -> ElemOf e (e' ': r)

e is located somewhere in the tail of the list.

membership :: Member e r => ElemOf e r Source #

Given Member e r, extract a proof that e is an element of r.

sameMember :: forall e e' r. ElemOf e r -> ElemOf e' r -> Maybe (e :~: e') Source #

Checks if two membership proofs are equal. If they are, then that means that the effects for which membership is proven must also be equal.

Checking membership

class KnownRow r Source #

A class for effect rows whose elements are inspectable.

This constraint is eventually satisfied as r is instantied to a monomorphic list. (E.g when r becomes something like '[State Int, Output String, Embed IO])

Minimal complete definition

tryMembership'

Instances
KnownRow ([] :: [a]) Source # 
Instance details

Defined in Polysemy.Internal.Union

Methods

tryMembership' :: Typeable e => Maybe (ElemOf e [])

(Typeable e, KnownRow r) => KnownRow (e ': r :: [a]) Source # 
Instance details

Defined in Polysemy.Internal.Union

Methods

tryMembership' :: Typeable e0 => Maybe (ElemOf e0 (e ': r))

tryMembership :: forall e r. (Typeable e, KnownRow r) => Maybe (ElemOf e r) Source #

Extracts a proof that e is an element of r if that is indeed the case; otherwise returns Nothing.

Using membership

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 :: KnownRow r => Sem r a -> Maybe (Sem r ([Int], a))
tryListen m = case tryMembership @(Writer [Int]) of
  Just pr -> Just $ subsumeUsing pr (listen (raise m))
  _       -> Nothing

Since: 1.3.0.0

interceptUsing Source #

Arguments

:: FirstOrder e "interceptUsing" 
=> ElemOf e r

A proof that the handled effect exists in r. This can be retrieved through membership or tryMembership.

-> (forall x m. e m 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 

A variant of intercept that accepts an explicit proof that the effect is in the effect stack rather then requiring a Member constraint.

This is useful in conjunction with tryMembership in order to conditionally perform intercept.

Since: 1.3.0.0

interceptUsingH Source #

Arguments

:: ElemOf e r

A proof that the handled effect exists in r. This can be retrieved through membership or tryMembership.

-> (forall x m. e m x -> Tactical e m r x)

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

-> Sem r a

Unlike interpretH, interceptUsingH does not consume any effects.

-> Sem r a 

A variant of interceptH that accepts an explicit proof that the effect is in the effect stack rather then requiring a Member constraint.

This is useful in conjunction with tryMembership in order to conditionally perform interceptH.

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

Since: 1.3.0.0