fused-effects-1.1.1.2: A fast, flexible, fused effect system.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Control.Effect.Sum

Description

Operations on sums, combining effects into a signature.

Since: 0.1.0.0

Synopsis

Membership

class Member (sub :: (Type -> Type) -> Type -> Type) sup where Source #

The class of types present in a signature.

This is based on Wouter Swierstra’s design described in Data types à la carte. As described therein, overlapping instances are required in order to distinguish e.g. left-occurrence from right-recursion.

It should not generally be necessary for you to define new Member instances, but these are not specifically prohibited if you wish to get creative.

Since: 0.1.0.0

Methods

inj :: sub m a -> sup m a Source #

Inject a member of a signature into the signature.

Instances

Instances details
Member t t Source #

Reflexivity: t is a member of itself.

Instance details

Defined in Control.Effect.Sum

Methods

inj :: forall (m :: Type -> Type) a. t m a -> t m a Source #

Member l r => Member l (l' :+: r) Source #

Right-recursion: if t is a member of r, we can inject it into r in O(n), followed by lifting that into l :+: r in O(1).

Instance details

Defined in Control.Effect.Sum

Methods

inj :: forall (m :: Type -> Type) a. l m a -> (l' :+: r) m a Source #

Member l (l :+: r) Source #

Left-occurrence: if t is at the head of a signature, we can inject it in O(1).

Instance details

Defined in Control.Effect.Sum

Methods

inj :: forall (m :: Type -> Type) a. l m a -> (l :+: r) m a Source #

Member t (l1 :+: (l2 :+: r)) => Member t ((l1 :+: l2) :+: r) Source #

Left-recursion: if t is a member of l1 :+: l2 :+: r, then we can inject it into (l1 :+: l2) :+: r by injection into a right-recursive signature, followed by left-association.

Instance details

Defined in Control.Effect.Sum

Methods

inj :: forall (m :: Type -> Type) a. t m a -> ((l1 :+: l2) :+: r) m a Source #

type family Members sub sup :: Constraint where ... Source #

Decompose sums on the left into multiple Member constraints.

Note that while this, and by extension Has, can be used to group together multiple membership checks into a single (composite) constraint, large signatures on the left can slow compiles down due to a problem with recursive type families.

Since: 1.0.0.0

Equations

Members (l :+: r) u = (Members l u, Members r u) 
Members t u = Member t u 

Sums

data (f :+: g) (m :: Type -> Type) k infixr 4 Source #

Higher-order sums are used to combine multiple effects into a signature, typically by chaining on the right.

Constructors

L (f m k) 
R (g m k) 

Instances

Instances details
Algebra NonDet [] Source # 
Instance details

Defined in Control.Algebra

Methods

alg :: forall ctx (n :: Type -> Type) a. Functor ctx => Handler ctx n [] -> NonDet n a -> ctx () -> [ctx a] Source #

LabelledMember label l r => LabelledMember (label :: k) l (l' :+: r) Source #

Right-recursion: if t is a member of r, we can inject it into r in O(n), followed by lifting that into l :+: r in O(1).

Instance details

Defined in Control.Effect.Labelled

Methods

injLabelled :: forall (m :: Type -> Type) a. Labelled label l m a -> (l' :+: r) m a Source #

LabelledMember (label :: k) l (Labelled label l :+: r) Source #

Left-occurrence: if t is at the head of a signature, we can inject it in O(1).

Instance details

Defined in Control.Effect.Labelled

Methods

injLabelled :: forall (m :: Type -> Type) a. Labelled label l m a -> (Labelled label l :+: r) m a Source #

LabelledMember label t (l1 :+: (l2 :+: r)) => LabelledMember (label :: k) t ((l1 :+: l2) :+: r) Source #

Left-recursion: if t is a member of l1 :+: l2 :+: r, then we can inject it into (l1 :+: l2) :+: r by injection into a right-recursive signature, followed by left-association.

Instance details

Defined in Control.Effect.Labelled

Methods

injLabelled :: forall (m :: Type -> Type) a. Labelled label t m a -> ((l1 :+: l2) :+: r) m a Source #

Member l r => Member l (l' :+: r) Source #

Right-recursion: if t is a member of r, we can inject it into r in O(n), followed by lifting that into l :+: r in O(1).

Instance details

Defined in Control.Effect.Sum

Methods

inj :: forall (m :: Type -> Type) a. l m a -> (l' :+: r) m a Source #

Member l (l :+: r) Source #

Left-occurrence: if t is at the head of a signature, we can inject it in O(1).

Instance details

Defined in Control.Effect.Sum

Methods

inj :: forall (m :: Type -> Type) a. l m a -> (l :+: r) m a Source #

Member t (l1 :+: (l2 :+: r)) => Member t ((l1 :+: l2) :+: r) Source #

Left-recursion: if t is a member of l1 :+: l2 :+: r, then we can inject it into (l1 :+: l2) :+: r by injection into a right-recursive signature, followed by left-association.

Instance details

Defined in Control.Effect.Sum

Methods

inj :: forall (m :: Type -> Type) a. t m a -> ((l1 :+: l2) :+: r) m a Source #

Algebra (Error e) (Either e) Source # 
Instance details

Defined in Control.Algebra

Methods

alg :: forall ctx (n :: Type -> Type) a. Functor ctx => Handler ctx n (Either e) -> Error e n a -> ctx () -> Either e (ctx a) Source #

Algebra sig m => Algebra (Choose :+: sig) (ChooseC m) Source # 
Instance details

Defined in Control.Carrier.Choose.Church

Methods

alg :: forall ctx (n :: Type -> Type) a. Functor ctx => Handler ctx n (ChooseC m) -> (Choose :+: sig) n a -> ctx () -> ChooseC m (ctx a) Source #

Algebra sig m => Algebra (Empty :+: sig) (MaybeT m) Source # 
Instance details

Defined in Control.Algebra

Methods

alg :: forall ctx (n :: Type -> Type) a. Functor ctx => Handler ctx n (MaybeT m) -> (Empty :+: sig) n a -> ctx () -> MaybeT m (ctx a) Source #

Algebra sig m => Algebra (Empty :+: sig) (EmptyC m) Source # 
Instance details

Defined in Control.Carrier.Empty.Maybe

Methods

alg :: forall ctx (n :: Type -> Type) a. Functor ctx => Handler ctx n (EmptyC m) -> (Empty :+: sig) n a -> ctx () -> EmptyC m (ctx a) Source #

Algebra sig m => Algebra (Empty :+: sig) (EmptyC m) Source # 
Instance details

Defined in Control.Carrier.Empty.Church

Methods

alg :: forall ctx (n :: Type -> Type) a. Functor ctx => Handler ctx n (EmptyC m) -> (Empty :+: sig) n a -> ctx () -> EmptyC m (ctx a) Source #

Algebra sig m => Algebra (NonDet :+: sig) (NonDetC m) Source # 
Instance details

Defined in Control.Carrier.NonDet.Church

Methods

alg :: forall ctx (n :: Type -> Type) a. Functor ctx => Handler ctx n (NonDetC m) -> (NonDet :+: sig) n a -> ctx () -> NonDetC m (ctx a) Source #

(MonadIO m, Algebra sig m) => Algebra (Trace :+: sig) (TraceC m) Source # 
Instance details

Defined in Control.Carrier.Trace.Printing

Methods

alg :: forall ctx (n :: Type -> Type) a. Functor ctx => Handler ctx n (TraceC m) -> (Trace :+: sig) n a -> ctx () -> TraceC m (ctx a) Source #

Algebra sig m => Algebra (Trace :+: sig) (TraceC m) Source # 
Instance details

Defined in Control.Carrier.Trace.Ignoring

Methods

alg :: forall ctx (n :: Type -> Type) a. Functor ctx => Handler ctx n (TraceC m) -> (Trace :+: sig) n a -> ctx () -> TraceC m (ctx a) Source #

Algebra sig m => Algebra (Trace :+: sig) (TraceC m) Source # 
Instance details

Defined in Control.Carrier.Trace.Returning

Methods

alg :: forall ctx (n :: Type -> Type) a. Functor ctx => Handler ctx n (TraceC m) -> (Trace :+: sig) n a -> ctx () -> TraceC m (ctx a) Source #

Algebra sig m => Algebra (Fail :+: sig) (FailC m) Source # 
Instance details

Defined in Control.Carrier.Fail.Either

Methods

alg :: forall ctx (n :: Type -> Type) a. Functor ctx => Handler ctx n (FailC m) -> (Fail :+: sig) n a -> ctx () -> FailC m (ctx a) Source #

Algebra sig m => Algebra (Fresh :+: sig) (FreshC m) Source # 
Instance details

Defined in Control.Carrier.Fresh.Strict

Methods

alg :: forall ctx (n :: Type -> Type) a. Functor ctx => Handler ctx n (FreshC m) -> (Fresh :+: sig) n a -> ctx () -> FreshC m (ctx a) Source #

Algebra sig m => Algebra (Fresh :+: sig) (FreshC m) Source # 
Instance details

Defined in Control.Carrier.Fresh.Church

Methods

alg :: forall ctx (n :: Type -> Type) a. Functor ctx => Handler ctx n (FreshC m) -> (Fresh :+: sig) n a -> ctx () -> FreshC m (ctx a) Source #

Algebra sig m => Algebra (Cut :+: (NonDet :+: sig)) (CutC m) Source # 
Instance details

Defined in Control.Carrier.Cut.Church

Methods

alg :: forall ctx (n :: Type -> Type) a. Functor ctx => Handler ctx n (CutC m) -> (Cut :+: (NonDet :+: sig)) n a -> ctx () -> CutC m (ctx a) Source #

Algebra sig m => Algebra (Cull :+: (NonDet :+: sig)) (CullC m) Source # 
Instance details

Defined in Control.Carrier.Cull.Church

Methods

alg :: forall ctx (n :: Type -> Type) a. Functor ctx => Handler ctx n (CullC m) -> (Cull :+: (NonDet :+: sig)) n a -> ctx () -> CullC m (ctx a) Source #

Algebra sig m => Algebra (Reader r :+: sig) (ReaderT r m) Source # 
Instance details

Defined in Control.Algebra

Methods

alg :: forall ctx (n :: Type -> Type) a. Functor ctx => Handler ctx n (ReaderT r m) -> (Reader r :+: sig) n a -> ctx () -> ReaderT r m (ctx a) Source #

Algebra sig m => Algebra (Reader r :+: sig) (ReaderC r m) Source # 
Instance details

Defined in Control.Carrier.Reader

Methods

alg :: forall ctx (n :: Type -> Type) a. Functor ctx => Handler ctx n (ReaderC r m) -> (Reader r :+: sig) n a -> ctx () -> ReaderC r m (ctx a) Source #

Algebra sig m => Algebra (State s :+: sig) (StateT s m) Source # 
Instance details

Defined in Control.Algebra

Methods

alg :: forall ctx (n :: Type -> Type) a. Functor ctx => Handler ctx n (StateT s m) -> (State s :+: sig) n a -> ctx () -> StateT s m (ctx a) Source #

Algebra sig m => Algebra (State s :+: sig) (StateT s m) Source # 
Instance details

Defined in Control.Algebra

Methods

alg :: forall ctx (n :: Type -> Type) a. Functor ctx => Handler ctx n (StateT s m) -> (State s :+: sig) n a -> ctx () -> StateT s m (ctx a) Source #

Algebra sig m => Algebra (State s :+: sig) (StateC s m) Source # 
Instance details

Defined in Control.Carrier.State.Strict

Methods

alg :: forall ctx (n :: Type -> Type) a. Functor ctx => Handler ctx n (StateC s m) -> (State s :+: sig) n a -> ctx () -> StateC s m (ctx a) Source #

Algebra sig m => Algebra (State s :+: sig) (StateC s m) Source # 
Instance details

Defined in Control.Carrier.State.Lazy

Methods

alg :: forall ctx (n :: Type -> Type) a. Functor ctx => Handler ctx n (StateC s m) -> (State s :+: sig) n a -> ctx () -> StateC s m (ctx a) Source #

Algebra sig m => Algebra (State s :+: sig) (StateC s m) Source # 
Instance details

Defined in Control.Carrier.State.Church

Methods

alg :: forall ctx (n :: Type -> Type) a. Functor ctx => Handler ctx n (StateC s m) -> (State s :+: sig) n a -> ctx () -> StateC s m (ctx a) Source #

Algebra sig m => Algebra (Throw e :+: sig) (ThrowC e m) Source # 
Instance details

Defined in Control.Carrier.Throw.Either

Methods

alg :: forall ctx (n :: Type -> Type) a. Functor ctx => Handler ctx n (ThrowC e m) -> (Throw e :+: sig) n a -> ctx () -> ThrowC e m (ctx a) Source #

Algebra sig m => Algebra (Error e :+: sig) (ExceptT e m) Source # 
Instance details

Defined in Control.Algebra

Methods

alg :: forall ctx (n :: Type -> Type) a. Functor ctx => Handler ctx n (ExceptT e m) -> (Error e :+: sig) n a -> ctx () -> ExceptT e m (ctx a) Source #

Algebra sig m => Algebra (Error e :+: sig) (ErrorC e m) Source # 
Instance details

Defined in Control.Carrier.Error.Either

Methods

alg :: forall ctx (n :: Type -> Type) a. Functor ctx => Handler ctx n (ErrorC e m) -> (Error e :+: sig) n a -> ctx () -> ErrorC e m (ctx a) Source #

Algebra sig m => Algebra (Error e :+: sig) (ErrorC e m) Source # 
Instance details

Defined in Control.Carrier.Error.Church

Methods

alg :: forall ctx (n :: Type -> Type) a. Functor ctx => Handler ctx n (ErrorC e m) -> (Error e :+: sig) n a -> ctx () -> ErrorC e m (ctx a) Source #

(Algebra sig m, Monoid w) => Algebra (Writer w :+: sig) (WriterT w m) Source # 
Instance details

Defined in Control.Algebra

Methods

alg :: forall ctx (n :: Type -> Type) a. Functor ctx => Handler ctx n (WriterT w m) -> (Writer w :+: sig) n a -> ctx () -> WriterT w m (ctx a) Source #

(Algebra sig m, Monoid w) => Algebra (Writer w :+: sig) (WriterT w m) Source # 
Instance details

Defined in Control.Algebra

Methods

alg :: forall ctx (n :: Type -> Type) a. Functor ctx => Handler ctx n (WriterT w m) -> (Writer w :+: sig) n a -> ctx () -> WriterT w m (ctx a) Source #

(Algebra sig m, Monoid w) => Algebra (Writer w :+: sig) (WriterT w m) Source # 
Instance details

Defined in Control.Algebra

Methods

alg :: forall ctx (n :: Type -> Type) a. Functor ctx => Handler ctx n (WriterT w m) -> (Writer w :+: sig) n a -> ctx () -> WriterT w m (ctx a) Source #

(Monoid w, Algebra sig m) => Algebra (Writer w :+: sig) (WriterC w m) Source # 
Instance details

Defined in Control.Carrier.Writer.Strict

Methods

alg :: forall ctx (n :: Type -> Type) a. Functor ctx => Handler ctx n (WriterC w m) -> (Writer w :+: sig) n a -> ctx () -> WriterC w m (ctx a) Source #

(Algebra sig m, Monoid w) => Algebra (Writer w :+: sig) (WriterC w m) Source # 
Instance details

Defined in Control.Carrier.Writer.Church

Methods

alg :: forall ctx (n :: Type -> Type) a. Functor ctx => Handler ctx n (WriterC w m) -> (Writer w :+: sig) n a -> ctx () -> WriterC w m (ctx a) Source #

(Reifies s (Interpreter eff m), Algebra sig m) => Algebra (eff :+: sig) (InterpretC s eff m) Source # 
Instance details

Defined in Control.Carrier.Interpret

Methods

alg :: forall ctx (n :: Type -> Type) a. Functor ctx => Handler ctx n (InterpretC s eff m) -> (eff :+: sig) n a -> ctx () -> InterpretC s eff m (ctx a) Source #

(LabelledMember label sub sig, Algebra sig m) => Algebra (sub :+: sig) (UnderLabel label sub m) Source # 
Instance details

Defined in Control.Effect.Labelled

Methods

alg :: forall ctx (n :: Type -> Type) a. Functor ctx => Handler ctx n (UnderLabel label sub m) -> (sub :+: sig) n a -> ctx () -> UnderLabel label sub m (ctx a) Source #

(Algebra sig m, Monoid w) => Algebra (Reader r :+: (Writer w :+: (State s :+: sig))) (RWST r w s m) Source # 
Instance details

Defined in Control.Algebra

Methods

alg :: forall ctx (n :: Type -> Type) a. Functor ctx => Handler ctx n (RWST r w s m) -> (Reader r :+: (Writer w :+: (State s :+: sig))) n a -> ctx () -> RWST r w s m (ctx a) Source #

(Algebra sig m, Monoid w) => Algebra (Reader r :+: (Writer w :+: (State s :+: sig))) (RWST r w s m) Source # 
Instance details

Defined in Control.Algebra

Methods

alg :: forall ctx (n :: Type -> Type) a. Functor ctx => Handler ctx n (RWST r w s m) -> (Reader r :+: (Writer w :+: (State s :+: sig))) n a -> ctx () -> RWST r w s m (ctx a) Source #

(Algebra sig m, Monoid w) => Algebra (Reader r :+: (Writer w :+: (State s :+: sig))) (RWST r w s m) Source # 
Instance details

Defined in Control.Algebra

Methods

alg :: forall ctx (n :: Type -> Type) a. Functor ctx => Handler ctx n (RWST r w s m) -> (Reader r :+: (Writer w :+: (State s :+: sig))) n a -> ctx () -> RWST r w s m (ctx a) Source #

Algebra (eff :+: sig) (sub m) => Algebra (Labelled label eff :+: sig) (Labelled label sub m) Source # 
Instance details

Defined in Control.Effect.Labelled

Methods

alg :: forall ctx (n :: Type -> Type) a. Functor ctx => Handler ctx n (Labelled label sub m) -> (Labelled label eff :+: sig) n a -> ctx () -> Labelled label sub m (ctx a) Source #

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

Defined in Control.Effect.Sum

Methods

fmap :: (a -> b) -> (f :+: g) m a -> (f :+: g) m b #

(<$) :: a -> (f :+: g) m b -> (f :+: g) m a #

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

Defined in Control.Effect.Sum

Methods

fold :: Monoid m0 => (f :+: g) m m0 -> m0 #

foldMap :: Monoid m0 => (a -> m0) -> (f :+: g) m a -> m0 #

foldMap' :: Monoid m0 => (a -> m0) -> (f :+: g) m a -> m0 #

foldr :: (a -> b -> b) -> b -> (f :+: g) m a -> b #

foldr' :: (a -> b -> b) -> b -> (f :+: g) m a -> b #

foldl :: (b -> a -> b) -> b -> (f :+: g) m a -> b #

foldl' :: (b -> a -> b) -> b -> (f :+: g) m a -> b #

foldr1 :: (a -> a -> a) -> (f :+: g) m a -> a #

foldl1 :: (a -> a -> a) -> (f :+: g) m a -> a #

toList :: (f :+: g) m a -> [a] #

null :: (f :+: g) m a -> Bool #

length :: (f :+: g) m a -> Int #

elem :: Eq a => a -> (f :+: g) m a -> Bool #

maximum :: Ord a => (f :+: g) m a -> a #

minimum :: Ord a => (f :+: g) m a -> a #

sum :: Num a => (f :+: g) m a -> a #

product :: Num a => (f :+: g) m a -> a #

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

Defined in Control.Effect.Sum

Methods

traverse :: Applicative f0 => (a -> f0 b) -> (f :+: g) m a -> f0 ((f :+: g) m b) #

sequenceA :: Applicative f0 => (f :+: g) m (f0 a) -> f0 ((f :+: g) m a) #

mapM :: Monad m0 => (a -> m0 b) -> (f :+: g) m a -> m0 ((f :+: g) m b) #

sequence :: Monad m0 => (f :+: g) m (m0 a) -> m0 ((f :+: g) m a) #

(Eq (f m k), Eq (g m k)) => Eq ((f :+: g) m k) Source # 
Instance details

Defined in Control.Effect.Sum

Methods

(==) :: (f :+: g) m k -> (f :+: g) m k -> Bool #

(/=) :: (f :+: g) m k -> (f :+: g) m k -> Bool #

(Ord (f m k), Ord (g m k)) => Ord ((f :+: g) m k) Source # 
Instance details

Defined in Control.Effect.Sum

Methods

compare :: (f :+: g) m k -> (f :+: g) m k -> Ordering #

(<) :: (f :+: g) m k -> (f :+: g) m k -> Bool #

(<=) :: (f :+: g) m k -> (f :+: g) m k -> Bool #

(>) :: (f :+: g) m k -> (f :+: g) m k -> Bool #

(>=) :: (f :+: g) m k -> (f :+: g) m k -> Bool #

max :: (f :+: g) m k -> (f :+: g) m k -> (f :+: g) m k #

min :: (f :+: g) m k -> (f :+: g) m k -> (f :+: g) m k #

(Show (f m k), Show (g m k)) => Show ((f :+: g) m k) Source # 
Instance details

Defined in Control.Effect.Sum

Methods

showsPrec :: Int -> (f :+: g) m k -> ShowS #

show :: (f :+: g) m k -> String #

showList :: [(f :+: g) m k] -> ShowS #

reassociateSumL :: (l1 :+: (l2 :+: r)) m a -> ((l1 :+: l2) :+: r) m a Source #

Reassociate a right-nested sum leftwards.

Since: 1.0.2.0