polysemy-zoo-0.8.0.0: Experimental, user-contributed effects and interpreters for polysemy
Safe HaskellNone
LanguageHaskell2010

Polysemy.Several

Contents

Synopsis

Data

data HList a where Source #

A list capable of storing values of different types. Like the Sem type, it uses a type level list to keep track of what's stored inside. Creating an HList looks like:

1 ::: "test" ::: True ::: HNil

Constructors

HNil :: HList '[] 
(:::) :: a -> HList (b :: [Type]) -> HList (a ': b) infixr 5 

type family TypeMap (f :: a -> b) (xs :: [a]) where ... Source #

A map function over type level lists. For example, the following two lines are equivalent:

TypeMap Reader [Int, String, False]
[Reader Int, Reader String, Reader Bool]

Equations

TypeMap _ '[] = '[] 
TypeMap f (x ': xs) = f x ': TypeMap f xs 

type family TypeConcat (a :: [t]) (b :: [t]) where ... Source #

Like ++ but at the type level. The following two lines are equivalent:

TypeConcat [Int, String] [Bool]
[Int, String, Bool]

Equations

TypeConcat '[] b = b 
TypeConcat (a ': as) b = a ': TypeConcat as b 

runSeveral :: (forall r' k x. k -> Sem (e k ': r') x -> Sem r' x) -> HList t -> Sem (TypeConcat (TypeMap e t) r) a -> Sem r a Source #

A helper function for building new runners which accept HLists intsead of individual elements. If you would normally write

f 5 . f "Text" . f True

then this function can turn that into

runSeveral f (True ::: "Text" ::: 5 ::: HNil)

For example, a runReaders function could be implemented as:

runReaders :: HList t -> Sem (TypeConcat (TypeMap Reader t) r) a -> Sem r a
runReaders = runSeveral runReader

Likewise, runStates could be the following if you didn't want the returned state:

runStates :: HList t -> Sem (TypeConcat (TypeMap State t) r) a -> Sem r a
runStates = runSeveral (fmap (fmap snd) . runState)