Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data Union (r :: EffectRow) (mWoven :: Type -> Type) a where
- data Weaving e mAfter resultType where
- type Member e r = MemberNoError e r
- type MemberWithError e r = (MemberNoError e r, WhenStuck (LocateEffect e r) (AmbiguousSend e r))
- weave :: (Functor s, Functor n) => s () -> (forall x. s (m x) -> n (s x)) -> (forall x. s x -> Maybe x) -> Union r m a -> Union r n (s a)
- hoist :: (forall x. m x -> n x) -> Union r m a -> Union r n a
- inj :: forall e r rInitial a. Member e r => e (Sem rInitial) a -> Union r (Sem rInitial) a
- injUsing :: forall e r rInitial a. ElemOf e r -> e (Sem rInitial) a -> Union r (Sem rInitial) a
- injWeaving :: forall e r m a. Member e r => Weaving e m a -> Union r m a
- weaken :: forall e r m a. Union r m a -> Union (e ': r) m a
- decomp :: Union (e ': r) m a -> Either (Union r m a) (Weaving e m a)
- prj :: forall e r m a. Member e r => Union r m a -> Maybe (Weaving e m a)
- prjUsing :: forall e r m a. ElemOf e r -> Union r m a -> Maybe (Weaving e m a)
- extract :: Union '[e] m a -> Weaving e m a
- absurdU :: Union '[] m a -> b
- decompCoerce :: Union (e ': r) m a -> Either (Union (f ': r) m a) (Weaving e m a)
- data ElemOf e r where
- membership :: Member e r => ElemOf e r
- sameMember :: forall e e' r. ElemOf e r -> ElemOf e' r -> Maybe (e :~: e')
- class KnownRow r
- tryMembership :: forall e r. (Typeable e, KnownRow r) => Maybe (ElemOf e r)
- extendMembershipLeft :: forall l r e. SList l -> ElemOf e r -> ElemOf e (Append l r)
- extendMembershipRight :: forall l r e. ElemOf e l -> ElemOf e (Append l r)
- injectMembership :: forall right e left mid. SList left -> SList mid -> ElemOf e (Append left right) -> ElemOf e (Append left (Append mid right))
- weakenList :: SList l -> Union r m a -> Union (Append l r) m a
- weakenMid :: forall right m a left mid. SList left -> SList mid -> Union (Append left right) m a -> Union (Append left (Append mid right)) m a
Documentation
data Union (r :: EffectRow) (mWoven :: Type -> Type) a where Source #
An extensible, type-safe union. The r
type parameter is a type-level
list of effects, any one of which may be held within the Union
.
data Weaving e mAfter resultType where Source #
Weaving | |
|
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
weave :: (Functor s, Functor n) => s () -> (forall x. s (m x) -> n (s x)) -> (forall x. s x -> Maybe x) -> Union r m a -> Union r n (s a) Source #
Building Unions
inj :: forall e r rInitial a. Member e r => e (Sem rInitial) a -> Union r (Sem rInitial) a Source #
Lift an effect e
into a Union
capable of holding it.
injUsing :: forall e r rInitial a. ElemOf e r -> e (Sem rInitial) a -> Union r (Sem rInitial) a Source #
Lift an effect e
into a Union
capable of holding it,
given an explicit proof that the effect exists in r
weaken :: forall e r m a. Union r m a -> Union (e ': r) m a Source #
Weaken a Union
so it is capable of storing a new sort of effect at the
head.
Using Unions
decomp :: Union (e ': r) m a -> Either (Union r m a) (Weaving e m a) Source #
Decompose a Union
. Either this union contains an effect e
---the head
of the r
list---or it doesn't.
prj :: forall e r m a. Member e r => Union r m a -> Maybe (Weaving e m a) Source #
Attempt to take an e
effect out of a Union
.
prjUsing :: forall e r m a. ElemOf e r -> Union r m a -> Maybe (Weaving e m a) Source #
Attempt to take an e
effect out of a Union
, given an explicit
proof that the effect exists in r
.
absurdU :: Union '[] m a -> b Source #
An empty union contains nothing, so this function is uncallable.
decompCoerce :: Union (e ': r) m a -> Either (Union (f ': r) m a) (Weaving e m a) Source #
Like decomp
, but allows for a more efficient
reinterpret
function.
Witnesses
data ElemOf e r where Source #
A proof that e
is an element of r
.
Due to technical reasons,
is not powerful enough to
prove ElemOf
e r
; however, it can still be used send actions of Member
e re
into r
by using subsumeUsing
.
Since: 1.3.0.0
membership :: Member e r => ElemOf e r Source #
Given
, extract a proof that Member
e re
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
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]
tryMembership'
Instances
KnownRow ('[] :: [a]) Source # | |
Defined in Polysemy.Internal.Union tryMembership' :: forall (e :: a0). Typeable e => Maybe (ElemOf e '[]) | |
(Typeable e, KnownRow r) => KnownRow (e ': r :: [a]) Source # | |
Defined in Polysemy.Internal.Union tryMembership' :: forall (e0 :: a0). 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
.
extendMembershipLeft :: forall l r e. SList l -> ElemOf e r -> ElemOf e (Append l r) Source #
Extends a proof that e
is an element of r
to a proof that e
is an
element of the concatenation of the lists l
and r
.
l
must be specified as a singleton list proof.
extendMembershipRight :: forall l r e. ElemOf e l -> ElemOf e (Append l r) Source #
Extends a proof that e
is an element of l
to a proof that e
is an
element of the concatenation of the lists l
and r
.
injectMembership :: forall right e left mid. SList left -> SList mid -> ElemOf e (Append left right) -> ElemOf e (Append left (Append mid right)) Source #
Extends a proof that e
is an element of left <> right
to a proof that
e
is an element of left <> mid <> right
.
Both left
and right
must be specified as singleton list proofs.
weakenList :: SList l -> Union r m a -> Union (Append l r) m a Source #
Weaken a Union
so it is capable of storing a number of new effects at
the head, specified as a singleton list proof.
weakenMid :: forall right m a left mid. SList left -> SList mid -> Union (Append left right) m a -> Union (Append left (Append mid right)) m a Source #
Weaken a Union
so it is capable of storing a number of new effects
somewhere within the previous effect list.
Both the prefix and the new effects are specified as singleton list proofs.