fused-effects-1.0.0.0: A fast, flexible, fused effect system.

Safe HaskellNone
LanguageHaskell2010

Control.Effect.Class

Contents

Description

Provides the HFunctor and Effect classes that effect types implement.

Since: 1.0.0.0

Synopsis

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 #

Higher-order functor map of a natural transformation over higher-order positions within the effect.

A definition for hmap over first-order effects can be derived automatically provided a Generic1 instance is available.

hmap :: (Functor m, Generic1 (h m), Generic1 (h n), GHFunctor m n (Rep1 (h m)) (Rep1 (h n))) => (forall x. m x -> n x) -> h m a -> h n a Source #

Higher-order functor map of a natural transformation over higher-order positions within the effect.

A definition for hmap over first-order effects can be derived automatically provided a Generic1 instance is available.

Instances
HFunctor Choose Source # 
Instance details

Defined in Control.Effect.Choose.Internal

Methods

hmap :: Functor m => (forall x. m x -> n x) -> Choose m a -> Choose n a Source #

HFunctor Empty Source # 
Instance details

Defined in Control.Effect.Empty.Internal

Methods

hmap :: Functor m => (forall x. m x -> n x) -> Empty m a -> Empty n a Source #

HFunctor Trace Source # 
Instance details

Defined in Control.Effect.Trace

Methods

hmap :: Functor m => (forall x. m x -> n x) -> Trace m a -> Trace n a Source #

HFunctor Fresh Source # 
Instance details

Defined in Control.Effect.Fresh

Methods

hmap :: Functor m => (forall x. m x -> n x) -> Fresh m a -> Fresh n a Source #

HFunctor Cut Source # 
Instance details

Defined in Control.Effect.Cut

Methods

hmap :: Functor m => (forall x. m x -> n x) -> Cut m a -> Cut n a Source #

HFunctor Cull Source # 
Instance details

Defined in Control.Effect.Cull

Methods

hmap :: Functor m => (forall x. m x -> n x) -> Cull m a -> Cull n a Source #

HFunctor (Catch e) Source # 
Instance details

Defined in Control.Effect.Catch.Internal

Methods

hmap :: Functor m => (forall x. m x -> n x) -> Catch e m a -> Catch e n a Source #

HFunctor (Lift sig) Source # 
Instance details

Defined in Control.Effect.Lift.Internal

Methods

hmap :: Functor m => (forall x. m x -> n x) -> Lift sig m a -> Lift sig n a Source #

HFunctor (Reader r) Source # 
Instance details

Defined in Control.Effect.Reader.Internal

Methods

hmap :: Functor m => (forall x. m x -> n x) -> Reader r m a -> Reader r n a Source #

HFunctor (State s) Source # 
Instance details

Defined in Control.Effect.State.Internal

Methods

hmap :: Functor m => (forall x. m x -> n x) -> State s m a -> State s n a Source #

HFunctor (Throw e) Source # 
Instance details

Defined in Control.Effect.Throw.Internal

Methods

hmap :: Functor m => (forall x. m x -> n x) -> Throw e m a -> Throw e n a Source #

HFunctor (Writer w) Source # 
Instance details

Defined in Control.Effect.Writer.Internal

Methods

hmap :: Functor m => (forall x. m x -> n x) -> Writer w m a -> Writer w n a Source #

(HFunctor f, HFunctor g) => HFunctor (f :+: g) Source # 
Instance details

Defined in Control.Effect.Sum

Methods

hmap :: Functor m => (forall x. m x -> n x) -> (f :+: g) m a -> (f :+: g) n a Source #

handleCoercible :: (HFunctor sig, Functor f, Coercible f g) => sig f a -> sig g a Source #

Thread a Coercible carrier through an HFunctor.

This is applicable whenever f is Coercible to g, e.g. simple newtypes.

Since: 1.0.0.0

class HFunctor sig => Effect sig where Source #

The class of effect types, which must:

  1. Be functorial in their last two arguments, and
  2. 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

thread Source #

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 . fmap pure = pure
handler . fmap (k =<<) = handler . fmap k <=< handler

respectively expressing that the handler does not alter the context of pure computations, and that the handler distributes over monadic composition.

thread Source #

Arguments

:: (Functor ctx, Monad m, Generic1 (sig m), Generic1 (sig n), GEffect m n (Rep1 (sig m)) (Rep1 (sig n))) 
=> 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 . fmap pure = pure
handler . fmap (k =<<) = handler . fmap k <=< 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 # 
Instance details

Defined in Control.Effect.Choose.Internal

Methods

thread :: (Functor ctx, Monad m) => ctx () -> (forall x. ctx (m x) -> n (ctx x)) -> Choose m a -> Choose n (ctx a) Source #

Effect Empty Source # 
Instance details

Defined in Control.Effect.Empty.Internal

Methods

thread :: (Functor ctx, Monad m) => ctx () -> (forall x. ctx (m x) -> n (ctx x)) -> Empty m a -> Empty n (ctx a) Source #

Effect Trace Source # 
Instance details

Defined in Control.Effect.Trace

Methods

thread :: (Functor ctx, Monad m) => ctx () -> (forall x. ctx (m x) -> n (ctx x)) -> Trace m a -> Trace n (ctx a) Source #

Effect Fresh Source # 
Instance details

Defined in Control.Effect.Fresh

Methods

thread :: (Functor ctx, Monad m) => ctx () -> (forall x. ctx (m x) -> n (ctx x)) -> Fresh m a -> Fresh n (ctx a) Source #

Effect Cut Source # 
Instance details

Defined in Control.Effect.Cut

Methods

thread :: (Functor ctx, Monad m) => ctx () -> (forall x. ctx (m x) -> n (ctx x)) -> Cut m a -> Cut n (ctx a) Source #

Effect Cull Source # 
Instance details

Defined in Control.Effect.Cull

Methods

thread :: (Functor ctx, Monad m) => ctx () -> (forall x. ctx (m x) -> n (ctx x)) -> Cull m a -> Cull n (ctx a) Source #

Effect (Catch e) Source # 
Instance details

Defined in Control.Effect.Catch.Internal

Methods

thread :: (Functor ctx, Monad m) => ctx () -> (forall x. ctx (m x) -> n (ctx x)) -> Catch e m a -> Catch e n (ctx a) Source #

Functor sig => Effect (Lift sig) Source # 
Instance details

Defined in Control.Effect.Lift.Internal

Methods

thread :: (Functor ctx, Monad m) => ctx () -> (forall x. ctx (m x) -> n (ctx x)) -> Lift sig m a -> Lift sig n (ctx a) Source #

Effect (Reader r) Source # 
Instance details

Defined in Control.Effect.Reader.Internal

Methods

thread :: (Functor ctx, Monad m) => ctx () -> (forall x. ctx (m x) -> n (ctx x)) -> Reader r m a -> Reader r n (ctx a) Source #

Effect (State s) Source # 
Instance details

Defined in Control.Effect.State.Internal

Methods

thread :: (Functor ctx, Monad m) => ctx () -> (forall x. ctx (m x) -> n (ctx x)) -> State s m a -> State s n (ctx a) Source #

Effect (Throw e) Source # 
Instance details

Defined in Control.Effect.Throw.Internal

Methods

thread :: (Functor ctx, Monad m) => ctx () -> (forall x. ctx (m x) -> n (ctx x)) -> Throw e m a -> Throw e n (ctx a) Source #

Effect (Writer w) Source # 
Instance details

Defined in Control.Effect.Writer.Internal

Methods

thread :: (Functor ctx, Monad m) => ctx () -> (forall x. ctx (m x) -> n (ctx x)) -> Writer w m a -> Writer w n (ctx a) Source #

(Effect f, Effect g) => Effect (f :+: g) Source # 
Instance details

Defined in Control.Effect.Sum

Methods

thread :: (Functor ctx, Monad m) => ctx () -> (forall x. ctx (m x) -> n (ctx x)) -> (f :+: g) m a -> (f :+: g) n (ctx a) 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 # 
Instance details

Defined in Control.Effect.Class

Methods

ghmap :: Functor m => (forall x. m x -> m' x) -> Par1 a -> Par1 a Source #

GHFunctor m m' (U1 :: Type -> Type) (U1 :: Type -> Type) Source # 
Instance details

Defined in Control.Effect.Class

Methods

ghmap :: Functor m => (forall x. m x -> m' x) -> U1 a -> U1 a Source #

GHFunctor m m' (V1 :: Type -> Type) (V1 :: Type -> Type) Source # 
Instance details

Defined in Control.Effect.Class

Methods

ghmap :: Functor m => (forall x. m x -> m' x) -> V1 a -> V1 a Source #

HFunctor f => GHFunctor m m' (Rec1 (f m)) (Rec1 (f m')) Source # 
Instance details

Defined in Control.Effect.Class

Methods

ghmap :: Functor m => (forall x. m x -> m' x) -> Rec1 (f m) a -> Rec1 (f m') a Source #

GHFunctor m m' (Rec1 m) (Rec1 m') Source # 
Instance details

Defined in Control.Effect.Class

Methods

ghmap :: Functor m => (forall x. m x -> m' x) -> Rec1 m a -> Rec1 m' a Source #

GHFunctor m m' (K1 R c :: Type -> Type) (K1 R c :: Type -> Type) Source # 
Instance details

Defined in Control.Effect.Class

Methods

ghmap :: Functor m => (forall x. m x -> m' x) -> K1 R c a -> K1 R c a Source #

(GHFunctor m m' l l', GHFunctor m m' r r') => GHFunctor m m' (l :*: r) (l' :*: r') Source # 
Instance details

Defined in Control.Effect.Class

Methods

ghmap :: Functor m => (forall x. m x -> m' x) -> (l :*: r) a -> (l' :*: r') a Source #

(GHFunctor m m' l l', GHFunctor m m' r r') => GHFunctor m m' (l :+: r) (l' :+: r') Source # 
Instance details

Defined in Control.Effect.Class

Methods

ghmap :: Functor m => (forall x. m x -> m' x) -> (l :+: r) a -> (l' :+: r') a Source #

(Functor f, GHFunctor m m' g g') => GHFunctor m m' (f :.: g) (f :.: g') Source # 
Instance details

Defined in Control.Effect.Class

Methods

ghmap :: Functor m => (forall x. m x -> m' x) -> (f :.: g) a -> (f :.: g') a Source #

GHFunctor m m' rep rep' => GHFunctor m m' (M1 i c rep) (M1 i c rep') Source # 
Instance details

Defined in Control.Effect.Class

Methods

ghmap :: Functor m => (forall x. m x -> m' x) -> M1 i c rep a -> M1 i c rep' a 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 # 
Instance details

Defined in Control.Effect.Class

Methods

gthread :: (Functor ctx, Monad m) => ctx () -> (forall x. ctx (m x) -> m' (ctx x)) -> Par1 a -> Par1 (ctx a) Source #

GEffect m m' (U1 :: Type -> Type) (U1 :: Type -> Type) Source # 
Instance details

Defined in Control.Effect.Class

Methods

gthread :: (Functor ctx, Monad m) => ctx () -> (forall x. ctx (m x) -> m' (ctx x)) -> U1 a -> U1 (ctx a) Source #

GEffect m m' (V1 :: Type -> Type) (V1 :: Type -> Type) Source # 
Instance details

Defined in Control.Effect.Class

Methods

gthread :: (Functor ctx, Monad m) => ctx () -> (forall x. ctx (m x) -> m' (ctx x)) -> V1 a -> V1 (ctx a) Source #

Effect sig => GEffect m m' (Rec1 (sig m)) (Rec1 (sig m')) Source # 
Instance details

Defined in Control.Effect.Class

Methods

gthread :: (Functor ctx, Monad m) => ctx () -> (forall x. ctx (m x) -> m' (ctx x)) -> Rec1 (sig m) a -> Rec1 (sig m') (ctx a) Source #

GEffect m m' (Rec1 m) (Rec1 m') Source # 
Instance details

Defined in Control.Effect.Class

Methods

gthread :: (Functor ctx, Monad m) => ctx () -> (forall x. ctx (m x) -> m' (ctx x)) -> Rec1 m a -> Rec1 m' (ctx a) Source #

GEffect m m' (K1 R c :: Type -> Type) (K1 R c :: Type -> Type) Source # 
Instance details

Defined in Control.Effect.Class

Methods

gthread :: (Functor ctx, Monad m) => ctx () -> (forall x. ctx (m x) -> m' (ctx x)) -> K1 R c a -> K1 R c (ctx a) Source #

(GEffect m m' l l', GEffect m m' r r') => GEffect m m' (l :*: r) (l' :*: r') Source # 
Instance details

Defined in Control.Effect.Class

Methods

gthread :: (Functor ctx, Monad m) => ctx () -> (forall x. ctx (m x) -> m' (ctx x)) -> (l :*: r) a -> (l' :*: r') (ctx a) Source #

(GEffect m m' l l', GEffect m m' r r') => GEffect m m' (l :+: r) (l' :+: r') Source # 
Instance details

Defined in Control.Effect.Class

Methods

gthread :: (Functor ctx, Monad m) => ctx () -> (forall x. ctx (m x) -> m' (ctx x)) -> (l :+: r) a -> (l' :+: r') (ctx a) Source #

(Functor f, GEffect m m' g g') => GEffect m m' (f :.: g) (f :.: g') Source # 
Instance details

Defined in Control.Effect.Class

Methods

gthread :: (Functor ctx, Monad m) => ctx () -> (forall x. ctx (m x) -> m' (ctx x)) -> (f :.: g) a -> (f :.: g') (ctx a) Source #

GEffect m m' rep rep' => GEffect m m' (M1 i c rep) (M1 i c rep') Source # 
Instance details

Defined in Control.Effect.Class

Methods

gthread :: (Functor ctx, Monad m) => ctx () -> (forall x. ctx (m x) -> m' (ctx x)) -> M1 i c rep a -> M1 i c rep' (ctx a) Source #