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

Safe HaskellNone
LanguageHaskell2010

Polysemy.Internal.Union

Contents

Synopsis

Documentation

data Union (r :: EffectRow) (m :: 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.

Constructors

Union :: SNat n -> Weaving (IndexOf r n) m a -> Union r m a 
Instances
Functor (Union r m) Source # 
Instance details

Defined in Polysemy.Internal.Union

Methods

fmap :: (a -> b) -> Union r m a -> Union r m b #

(<$) :: a -> Union r m b -> Union r m a #

data Weaving e m a where Source #

Constructors

Weaving 

Fields

  • :: Functor f
     
  • => { weaveEffect :: e m a

    The original effect GADT originally lifted via send. There is an invariant that m ~ Sem r0, where r0 is the effect row that was in scope when this Weaving was originally created.

  •    , weaveState :: f ()

    A piece of state that other effects' interpreters have already woven through this Weaving. f is a Functor, so you can always fmap into this thing.

  •    , weaveDistrib :: forall x. f (m x) -> n (f x)

    Distribute f by transforming m into n. We have invariants on m and n, which means in actuality this function looks like f (Sem (Some ': Effects ': r) x) -> Sem r (f x).

  •    , weaveResult :: f a -> b

    Even though f a is the moral resulting type of Weaving, we can't expose that fact; such a thing would prevent Sem from being a Monad.

  •    , weaveInspect :: forall x. f x -> Maybe x

    A function for attempting to see inside an f. This is no guarantees that such a thing will succeed (for example, Error might have thrown.)

  •    } -> Weaving e n b
     
Instances
Functor (Weaving e m) Source # 
Instance details

Defined in Polysemy.Internal.Union

Methods

fmap :: (a -> b) -> Weaving e m a -> Weaving e m b #

(<$) :: a -> Weaving e m b -> Weaving e m a #

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 (IndexOf r (Found r e)) (AmbiguousSend r e)) Source #

weave :: (Functor s, Functor m, 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 #

hoist :: (Functor m, Functor n) => (forall x. m x -> n x) -> Union r m a -> Union r n a Source #

Building Unions

inj :: forall r e a m. (Functor m, Member e r) => e m a -> Union r m a Source #

Lift an effect e into a Union capable of holding it.

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.

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 a m. Member e r => Union r m a -> Maybe (Weaving e m a) Source #

Attempt to take an e effect out of a Union.

extract :: Union '[e] m a -> Weaving e m a Source #

Retrieve the last effect in a Union.

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 SNat :: Nat -> Type where Source #

A singleton for Nat.

Constructors

SZ :: SNat Z 
SS :: SNat n -> SNat (S n) 
Instances
TestEquality SNat Source # 
Instance details

Defined in Polysemy.Internal.Union

Methods

testEquality :: SNat a -> SNat b -> Maybe (a :~: b) #

data Nat Source #

The kind of type-level natural numbers.

Constructors

Z 
S Nat 
Instances
TestEquality SNat Source # 
Instance details

Defined in Polysemy.Internal.Union

Methods

testEquality :: SNat a -> SNat b -> Maybe (a :~: b) #