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

Safe HaskellNone
LanguageHaskell2010

Polysemy.Internal.Union

Contents

Synopsis

Documentation

data Union (r :: [(* -> *) -> * -> *]) (m :: * -> *) 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 

Fields

  • :: SNat n

    A proof that the effect is actually in r.

  • -> Yo (IndexOf r n) m a

    The effect to wrap. The functions prj and decomp can help retrieve this value later.

  • -> Union r m a
     
Instances
Effect (Union r) Source # 
Instance details

Defined in Polysemy.Internal.Union

Methods

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

weave :: (Functor s, Functor m, Functor n) => s () -> (forall x. s (m x) -> n (s 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 #

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 Yo e m a where Source #

Constructors

Yo :: Functor f => e m a -> f () -> (forall x. f (m x) -> n (f x)) -> (f a -> b) -> Yo e n b 
Instances
Effect (Yo e) Source # 
Instance details

Defined in Polysemy.Internal.Union

Methods

fmap' :: (a -> b) -> Yo e m a -> Yo e m b Source #

weave :: (Functor s, Functor m, Functor n) => s () -> (forall x. s (m x) -> n (s x)) -> Yo e m a -> Yo e n (s a) Source #

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

Functor (Yo e m) Source # 
Instance details

Defined in Polysemy.Internal.Union

Methods

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

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

liftYo :: Functor m => e m a -> Yo e m a Source #

type Member e r = Member' e r Source #

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

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 :: 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) (Yo 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 (Yo e m a) Source #

Attempt to take an e effect out of a Union.

extract :: Union '[e] m a -> Yo 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) (Yo e m a) Source #

Like decomp, but allows for a more efficient reinterpret function.

Witnesses

data SNat :: Nat -> * 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) #