| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Control.Effect.Class
Documentation
class HFunctor h where Source #
Higher-order functors of kind (* -> *) -> (* -> *) map functors to functors.
All effects must be HFunctors.
Since: 1.0.0.0
Minimal complete definition
Nothing
Methods
hmap :: Functor m => (forall x. m x -> n x) -> h m a -> h n a Source #
Instances
| HFunctor Choose Source # | |
| HFunctor Empty Source # | |
| HFunctor Trace Source # | |
| HFunctor Fresh Source # | |
| HFunctor Cut Source # | |
| HFunctor Cull Source # | |
| HFunctor (Catch e) Source # | |
| HFunctor (Lift sig) Source # | |
| HFunctor (Reader r) Source # | |
| HFunctor (State s) Source # | |
| HFunctor (Throw e) Source # | |
| HFunctor (Writer w) Source # | |
| (HFunctor f, HFunctor g) => HFunctor (f :+: g) Source # | |
| HFunctor sub => HFunctor (Labelled label sub) Source # | |
class HFunctor sig => Effect sig where Source #
The class of effect types, which must:
- Be functorial in their last two arguments, and
- Support threading effects in higher-order positions through using the carrier’s suspended context.
All first-order effects (those without existential occurrences of m) admit a default definition of thread provided a Generic1 instance is available for the effect.
Since: 1.0.0.0
Minimal complete definition
Nothing
Methods
Arguments
| :: (Functor ctx, Monad m) | |
| => ctx () | The initial context. |
| -> (forall x. ctx (m x) -> n (ctx x)) | A handler for actions in a context, producing actions with a derived context. |
| -> sig m a | The effect to thread the handler through. |
| -> sig n (ctx a) |
Handle any effects in a signature by threading the algebra’s handler all the way through to the continuation, starting from some initial context.
The handler is expressed as a distributive law, and required to adhere to the following laws:
handler .fmappure=pure
handler .fmap(k=<<) = handler .fmapk<=<handler
respectively expressing that the handler does not alter the context of pure computations, and that the handler distributes over monadic composition.
Instances
| Effect Choose Source # | |
| Effect Empty Source # | |
| Effect Trace Source # | |
| Effect Fresh Source # | |
| Effect Cut Source # | |
| Effect Cull Source # | |
| Effect (Catch e) Source # | |
| Functor sig => Effect (Lift sig) Source # | |
| Effect (Reader r) Source # | |
| Effect (State s) Source # | |
| Effect (Throw e) Source # | |
| Effect (Writer w) Source # | |
| (Effect f, Effect g) => Effect (f :+: g) Source # | |
| Effect sub => Effect (Labelled label sub) Source # | |
Generic deriving of HFunctor & Effect instances.
class GHFunctor m m' rep rep' where Source #
Generic implementation of HFunctor.
Methods
ghmap :: Functor m => (forall x. m x -> m' x) -> rep a -> rep' a Source #
Generic implementation of hmap.
Instances
| GHFunctor m m' Par1 Par1 Source # | |
| GHFunctor m m' (U1 :: Type -> Type) (U1 :: Type -> Type) Source # | |
| GHFunctor m m' (V1 :: Type -> Type) (V1 :: Type -> Type) Source # | |
| HFunctor f => GHFunctor m m' (Rec1 (f m)) (Rec1 (f m')) Source # | |
| GHFunctor m m' (Rec1 m) (Rec1 m') Source # | |
| GHFunctor m m' (K1 R c :: Type -> Type) (K1 R c :: Type -> Type) Source # | |
| (GHFunctor m m' l l', GHFunctor m m' r r') => GHFunctor m m' (l :*: r) (l' :*: r') Source # | |
| (GHFunctor m m' l l', GHFunctor m m' r r') => GHFunctor m m' (l :+: r) (l' :+: r') Source # | |
| (Functor f, GHFunctor m m' g g') => GHFunctor m m' (f :.: g) (f :.: g') Source # | |
| GHFunctor m m' rep rep' => GHFunctor m m' (M1 i c rep) (M1 i c rep') Source # | |
class GEffect m m' rep rep' where Source #
Generic implementation of Effect.
Methods
gthread :: (Functor ctx, Monad m) => ctx () -> (forall x. ctx (m x) -> m' (ctx x)) -> rep a -> rep' (ctx a) Source #
Generic implementation of thread.
Instances
| GEffect m m' Par1 Par1 Source # | |
| GEffect m m' (U1 :: Type -> Type) (U1 :: Type -> Type) Source # | |
| GEffect m m' (V1 :: Type -> Type) (V1 :: Type -> Type) Source # | |
| Effect sig => GEffect m m' (Rec1 (sig m)) (Rec1 (sig m')) Source # | |
| GEffect m m' (Rec1 m) (Rec1 m') Source # | |
| GEffect m m' (K1 R c :: Type -> Type) (K1 R c :: Type -> Type) Source # | |
| (GEffect m m' l l', GEffect m m' r r') => GEffect m m' (l :*: r) (l' :*: r') Source # | |
| (GEffect m m' l l', GEffect m m' r r') => GEffect m m' (l :+: r) (l' :+: r') Source # | |
| (Functor f, GEffect m m' g g') => GEffect m m' (f :.: g) (f :.: g') Source # | |
| GEffect m m' rep rep' => GEffect m m' (M1 i c rep) (M1 i c rep') Source # | |