Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Turn a handler of multiple effects into an effectful operation.
Generalizes Effectful.Provider.
Since: 2.3.1.0
Synopsis
- data ProviderList (effects :: [Effect]) (input :: Type) (f :: Type -> Type) :: Effect
- type ProviderList_ effs input = ProviderList effs input Identity
- runProviderList :: KnownEffects effs => (forall r. input -> Eff (effs ++ es) r -> Eff es (f r)) -> Eff (ProviderList effs input f : es) a -> Eff es a
- runProviderList_ :: KnownEffects effs => (forall r. input -> Eff (effs ++ es) r -> Eff es r) -> Eff (ProviderList_ effs input : es) a -> Eff es a
- provideList :: forall effs f es a. ProviderList effs () f :> es => Eff (effs ++ es) a -> Eff es (f a)
- provideList_ :: forall effs es a. ProviderList_ effs () :> es => Eff (effs ++ es) a -> Eff es a
- provideListWith :: forall effs input f es a. ProviderList effs input f :> es => input -> Eff (effs ++ es) a -> Eff es (f a)
- provideListWith_ :: forall effs input es a. ProviderList_ effs input :> es => input -> Eff (effs ++ es) a -> Eff es a
- type family (xs :: [Effect]) ++ (ys :: [Effect]) :: [Effect] where ...
- class KnownEffects (es :: [Effect])
Effect
data ProviderList (effects :: [Effect]) (input :: Type) (f :: Type -> Type) :: Effect Source #
Provide a way to run a handler of multiple effects
with a given input
.
Note: f
can be used to alter the return type of the handler. If that's
unnecessary, use ProviderList_
.
Instances
type DispatchOf (ProviderList effs input f) Source # | |
Defined in Effectful.Provider.List | |
data StaticRep (ProviderList effs input f) Source # | |
Defined in Effectful.Provider.List data StaticRep (ProviderList effs input f) where
|
type ProviderList_ effs input = ProviderList effs input Identity Source #
A restricted variant of ProviderList
with unchanged return type of the
handler.
Handlers
:: KnownEffects effs | |
=> (forall r. input -> Eff (effs ++ es) r -> Eff es (f r)) | The handler. |
-> Eff (ProviderList effs input f : es) a | |
-> Eff es a |
Run the ProviderList
effect with a given handler.
:: KnownEffects effs | |
=> (forall r. input -> Eff (effs ++ es) r -> Eff es r) | The handler. |
-> Eff (ProviderList_ effs input : es) a | |
-> Eff es a |
Run the Provider
effect with a given handler that doesn't change its
return type.
Operations
provideList :: forall effs f es a. ProviderList effs () f :> es => Eff (effs ++ es) a -> Eff es (f a) Source #
Run the handler.
provideList_ :: forall effs es a. ProviderList_ effs () :> es => Eff (effs ++ es) a -> Eff es a Source #
Run the handler with unchanged return type.
:: forall effs input f es a. ProviderList effs input f :> es | |
=> input | The input to the handler. |
-> Eff (effs ++ es) a | |
-> Eff es (f a) |
Run the handler with a given input.
:: forall effs input es a. ProviderList_ effs input :> es | |
=> input | The input to the handler. |
-> Eff (effs ++ es) a | |
-> Eff es a |
Run the handler that doesn't change its return type with a given input.
Misc
type family (xs :: [Effect]) ++ (ys :: [Effect]) :: [Effect] where ... infixr 5 Source #
Append two type-level lists together.
class KnownEffects (es :: [Effect]) Source #
Calculate length of a list of known effects.
Instances
KnownEffects ('[] :: [Effect]) Source # | |
Defined in Effectful.Internal.Effect | |
KnownEffects es => KnownEffects (e ': es) Source # | |
Defined in Effectful.Internal.Effect |