Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module contains the definition of the Eff
monad, which is basically an
, as well as
functions for manipulating the effect environment type Env
es -> IO
aEnv
. Most of the times, you won't need to use this module
directly; user-facing functionalities are all exported via the Cleff module.
This is an internal module and its API may change even between minor versions. Therefore you should be extra careful if you're to depend on this module.
Core types
newtype InternalHandler e Source #
The internal representation of effect handlers. This is just a natural transformation from the effect type
e (
to the effect monad Eff
es)
for any effect stack Eff
eses
.
In interpreting functions (see Cleff.Internal.Interpret), the user-facing Handler
type is transformed into
this type.
InternalHandler | |
|
Instances
Typeable e => Show (InternalHandler e) Source # |
|
Defined in Cleff.Internal.Monad showsPrec :: Int -> InternalHandler e -> ShowS # show :: InternalHandler e -> String # showList :: [InternalHandler e] -> ShowS # |
type Env = Mem InternalHandler Source #
The effect memironment that stores handlers of any effect present in the stack es
.
The extensible effect monad. A monad
is capable of performing any effect in the effect stack Eff
eses
,
which is a type-level list that holds all effects available. However, most of the times, for flexibility, es
should be a polymorphic type variable, and you should use the (:>)
and (:>>)
operators in constraints to
indicate what effects are in the stack. For example,
Reader
String
:>
es,State
Bool
:>
es =>Eff
esInteger
allows you to perform operations of the
effect and the Reader
String
effect in a computation returning an State
Bool
Integer
.
Instances
IOE :> es => MonadBase IO (Eff es) Source # | Compatibility instance; use |
Defined in Cleff.Internal.Base | |
IOE :> es => MonadBaseControl IO (Eff es) Source # | Compatibility instance; use |
Monad (Eff es) Source # | |
Functor (Eff es) Source # | |
MonadFix (Eff es) Source # | |
Defined in Cleff.Internal.Monad | |
Fail :> es => MonadFail (Eff es) Source # | |
Defined in Cleff.Fail | |
Applicative (Eff es) Source # | |
IOE :> es => MonadIO (Eff es) Source # | |
Defined in Cleff.Internal.Base | |
IOE :> es => MonadThrow (Eff es) Source # | |
Defined in Cleff.Internal.Base | |
IOE :> es => MonadCatch (Eff es) Source # | |
IOE :> es => MonadMask (Eff es) Source # | |
IOE :> es => PrimMonad (Eff es) Source # | |
IOE :> es => MonadUnliftIO (Eff es) Source # | |
Defined in Cleff.Internal.Base | |
Semigroup a => Semigroup (Eff es a) Source # | |
Monoid a => Monoid (Eff es a) Source # | |
type PrimState (Eff es) Source # | |
Defined in Cleff.Internal.Base | |
type StM (Eff es) a Source # | |
Defined in Cleff.Internal.Base |
Performing effect operations
class KnownList (es :: [k]) Source #
The list es
list is concrete, i.e. is of the form '[a1, a2, ..., an]
, i.e. is not a type variable.