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

Control.Effect.Fail

Description

An effect providing failure with an error message.

This effect is invoked through the fail method from MonadFail.

Predefined carriers:

Since: 0.1.0.0

Synopsis

Fail effect

type Fail = Throw String Source #

Since: 0.1.0.0

pattern Fail :: String -> Fail m k Source #

Since: 1.0.0.0

class Monad m => MonadFail (m :: Type -> Type) where #

When a value is bound in do-notation, the pattern on the left hand side of <- might not match. In this case, this class provides a function to recover.

A Monad without a MonadFail instance may only be used in conjunction with pattern that always match, such as newtypes, tuples, data types with only a single data constructor, and irrefutable patterns (~pat).

Instances of MonadFail should satisfy the following law: fail s should be a left zero for >>=,

fail s >>= f  =  fail s

If your Monad is also MonadPlus, a popular definition is

fail _ = mzero

Since: base-4.9.0.0

Methods

fail :: String -> m a #

Instances

Instances details
MonadFail P

Since: base-4.9.0.0

Instance details

Defined in Text.ParserCombinators.ReadP

Methods

fail :: String -> P a #

MonadFail ReadP

Since: base-4.9.0.0

Instance details

Defined in Text.ParserCombinators.ReadP

Methods

fail :: String -> ReadP a #

MonadFail IO

Since: base-4.9.0.0

Instance details

Defined in Control.Monad.Fail

Methods

fail :: String -> IO a #

MonadFail Maybe

Since: base-4.9.0.0

Instance details

Defined in Control.Monad.Fail

Methods

fail :: String -> Maybe a #

MonadFail []

Since: base-4.9.0.0

Instance details

Defined in Control.Monad.Fail

Methods

fail :: String -> [a] #

MonadFail (ST s)

Since: base-4.11.0.0

Instance details

Defined in GHC.ST

Methods

fail :: String -> ST s a #

MonadFail m => MonadFail (ChooseC m) Source # 
Instance details

Defined in Control.Carrier.Choose.Church

Methods

fail :: String -> ChooseC m a #

MonadFail m => MonadFail (CullC m) Source # 
Instance details

Defined in Control.Carrier.Cull.Church

Methods

fail :: String -> CullC m a #

MonadFail m => MonadFail (CutC m) Source # 
Instance details

Defined in Control.Carrier.Cut.Church

Methods

fail :: String -> CutC m a #

MonadFail m => MonadFail (EmptyC m) Source # 
Instance details

Defined in Control.Carrier.Empty.Church

Methods

fail :: String -> EmptyC m a #

MonadFail m => MonadFail (EmptyC m) Source #

EmptyC passes MonadFail operations along to the underlying monad m, rather than interpreting it as a synonym for empty à la MaybeT.

Instance details

Defined in Control.Carrier.Empty.Maybe

Methods

fail :: String -> EmptyC m a #

Algebra sig m => MonadFail (FailC m) Source # 
Instance details

Defined in Control.Carrier.Fail.Either

Methods

fail :: String -> FailC m a #

MonadFail m => MonadFail (FreshC m) Source # 
Instance details

Defined in Control.Carrier.Fresh.Church

Methods

fail :: String -> FreshC m a #

MonadFail m => MonadFail (FreshC m) Source # 
Instance details

Defined in Control.Carrier.Fresh.Strict

Methods

fail :: String -> FreshC m a #

MonadFail m => MonadFail (LiftC m) Source # 
Instance details

Defined in Control.Carrier.Lift

Methods

fail :: String -> LiftC m a #

MonadFail m => MonadFail (NonDetC m) Source # 
Instance details

Defined in Control.Carrier.NonDet.Church

Methods

fail :: String -> NonDetC m a #

MonadFail m => MonadFail (TraceC m) Source # 
Instance details

Defined in Control.Carrier.Trace.Ignoring

Methods

fail :: String -> TraceC m a #

MonadFail m => MonadFail (TraceC m) Source # 
Instance details

Defined in Control.Carrier.Trace.Printing

Methods

fail :: String -> TraceC m a #

MonadFail m => MonadFail (TraceC m) Source # 
Instance details

Defined in Control.Carrier.Trace.Returning

Methods

fail :: String -> TraceC m a #

Monad m => MonadFail (MaybeT m) 
Instance details

Defined in Control.Monad.Trans.Maybe

Methods

fail :: String -> MaybeT m a #

MonadFail f => MonadFail (Ap f)

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Methods

fail :: String -> Ap f a #

MonadFail m => MonadFail (ErrorC e m) Source # 
Instance details

Defined in Control.Carrier.Error.Church

Methods

fail :: String -> ErrorC e m a #

MonadFail m => MonadFail (ErrorC e m) Source # 
Instance details

Defined in Control.Carrier.Error.Either

Methods

fail :: String -> ErrorC e m a #

MonadFail m => MonadFail (ReaderC r m) Source # 
Instance details

Defined in Control.Carrier.Reader

Methods

fail :: String -> ReaderC r m a #

MonadFail m => MonadFail (StateC s m) Source # 
Instance details

Defined in Control.Carrier.State.Church

Methods

fail :: String -> StateC s m a #

MonadFail m => MonadFail (StateC s m) Source # 
Instance details

Defined in Control.Carrier.State.Lazy

Methods

fail :: String -> StateC s m a #

MonadFail m => MonadFail (StateC s m) Source # 
Instance details

Defined in Control.Carrier.State.Strict

Methods

fail :: String -> StateC s m a #

MonadFail m => MonadFail (ThrowC e m) Source # 
Instance details

Defined in Control.Carrier.Throw.Either

Methods

fail :: String -> ThrowC e m a #

MonadFail m => MonadFail (WriterC w m) Source # 
Instance details

Defined in Control.Carrier.Writer.Church

Methods

fail :: String -> WriterC w m a #

MonadFail m => MonadFail (WriterC w m) Source # 
Instance details

Defined in Control.Carrier.Writer.Strict

Methods

fail :: String -> WriterC w m a #

MonadFail m => MonadFail (ExceptT e m) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

fail :: String -> ExceptT e m a #

MonadFail m => MonadFail (IdentityT m) 
Instance details

Defined in Control.Monad.Trans.Identity

Methods

fail :: String -> IdentityT m a #

MonadFail m => MonadFail (ReaderT r m) 
Instance details

Defined in Control.Monad.Trans.Reader

Methods

fail :: String -> ReaderT r m a #

MonadFail m => MonadFail (StateT s m) 
Instance details

Defined in Control.Monad.Trans.State.Lazy

Methods

fail :: String -> StateT s m a #

MonadFail m => MonadFail (StateT s m) 
Instance details

Defined in Control.Monad.Trans.State.Strict

Methods

fail :: String -> StateT s m a #

MonadFail m => MonadFail (WriterT w m) 
Instance details

Defined in Control.Monad.Trans.Writer.CPS

Methods

fail :: String -> WriterT w m a #

(Monoid w, MonadFail m) => MonadFail (WriterT w m) 
Instance details

Defined in Control.Monad.Trans.Writer.Lazy

Methods

fail :: String -> WriterT w m a #

(Monoid w, MonadFail m) => MonadFail (WriterT w m) 
Instance details

Defined in Control.Monad.Trans.Writer.Strict

Methods

fail :: String -> WriterT w m a #

MonadFail m => MonadFail (InterpretC s sig m) Source # 
Instance details

Defined in Control.Carrier.Interpret

Methods

fail :: String -> InterpretC s sig m a #

MonadFail (sub m) => MonadFail (Labelled label sub m) Source # 
Instance details

Defined in Control.Effect.Labelled

Methods

fail :: String -> Labelled label sub m a #

MonadFail m => MonadFail (UnderLabel label sub m) Source # 
Instance details

Defined in Control.Effect.Labelled

Methods

fail :: String -> UnderLabel label sub m a #

MonadFail m => MonadFail (RWST r w s m) 
Instance details

Defined in Control.Monad.Trans.RWS.CPS

Methods

fail :: String -> RWST r w s m a #

(Monoid w, MonadFail m) => MonadFail (RWST r w s m) 
Instance details

Defined in Control.Monad.Trans.RWS.Lazy

Methods

fail :: String -> RWST r w s m a #

(Monoid w, MonadFail m) => MonadFail (RWST r w s m) 
Instance details

Defined in Control.Monad.Trans.RWS.Strict

Methods

fail :: String -> RWST r w s m a #

Re-exports

class Monad m => Algebra sig m | m -> sig Source #

The class of carriers (results) for algebras (effect handlers) over signatures (effects), whose actions are given by the alg method.

Since: 1.0.0.0

Minimal complete definition

alg

Instances

Instances details
Algebra Choose NonEmpty Source # 
Instance details

Defined in Control.Algebra

Methods

alg :: forall ctx (n :: Type -> Type) a. Functor ctx => Handler ctx n NonEmpty -> Choose n a -> ctx () -> NonEmpty (ctx a) Source #

Algebra Empty Maybe Source # 
Instance details

Defined in Control.Algebra

Methods

alg :: forall ctx (n :: Type -> Type) a. Functor ctx => Handler ctx n Maybe -> Empty n a -> ctx () -> Maybe (ctx a) Source #

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 #

Algebra sig m => Algebra sig (Ap m) Source #

This instance permits effectful actions to be lifted into the Ap monad given a monoidal return type, which can provide clarity when chaining calls to mappend.

mappend <$> act1 <*> (mappend <$> act2 <*> act3)

is equivalent to

getAp (act1 <> act2 <> act3)

Since: 1.0.1.0

Instance details

Defined in Control.Algebra

Methods

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

Algebra sig m => Algebra sig (Alt m) Source #

This instance permits effectful actions to be lifted into the Alt monad, which eases the invocation of repeated alternation with <|>:

a <|> b <|> c <|> d

is equivalent to

getAlt (mconcat [a, b, c, d])

Since: 1.0.1.0

Instance details

Defined in Control.Algebra

Methods

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

Algebra sig m => Algebra sig (IdentityT m) Source # 
Instance details

Defined in Control.Algebra

Methods

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

Algebra (Lift Identity) Identity Source # 
Instance details

Defined in Control.Algebra

Methods

alg :: forall ctx (n :: Type -> Type) a. Functor ctx => Handler ctx n Identity -> Lift Identity n a -> ctx () -> Identity (ctx a) Source #

Algebra (Lift IO) IO Source # 
Instance details

Defined in Control.Algebra

Methods

alg :: forall ctx (n :: Type -> Type) a. Functor ctx => Handler ctx n IO -> Lift IO n a -> ctx () -> IO (ctx 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 #

Monad m => Algebra (Lift m) (LiftC m) Source # 
Instance details

Defined in Control.Carrier.Lift

Methods

alg :: forall ctx (n :: Type -> Type) a. Functor ctx => Handler ctx n (LiftC m) -> Lift m n a -> ctx () -> LiftC m (ctx a) Source #

Monoid w => Algebra (Writer w) ((,) w) Source # 
Instance details

Defined in Control.Algebra

Methods

alg :: forall ctx (n :: Type -> Type) a. Functor ctx => Handler ctx n ((,) w) -> Writer w n a -> ctx () -> (w, ctx a) Source #

Algebra (Reader r) ((->) r) Source # 
Instance details

Defined in Control.Algebra

Methods

alg :: forall ctx (n :: Type -> Type) a. Functor ctx => Handler ctx n ((->) r) -> Reader r n a -> ctx () -> r -> 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 (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 (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 (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 (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) (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 (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.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 (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 (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 #

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 #

(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.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 (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 => 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) (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 (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 (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 (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 (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.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) (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 (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, 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 #

(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) (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 #

(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 #

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 #

(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 #

(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 #

type Has eff sig m = (Members eff sig, Algebra sig m) Source #

m is a carrier for sig containing eff.

Note that if eff is a sum, it will be decomposed into multiple Member constraints. While this technically allows one to combine multiple unrelated effects into a single Has constraint, doing so has two significant drawbacks:

  1. Due to a problem with recursive type families, this can lead to significantly slower compiles.
  2. It defeats ghc’s warnings for redundant constraints, and thus can lead to a proliferation of redundant constraints as code is changed.

Since: 1.0.0.0

run :: Identity a -> a Source #

Run an action exhausted of effects to produce its final result value.

Since: 1.0.0.0