Copyright | (c) 2021 Xy Ren |
---|---|
License | BSD3 |
Maintainer | xy.r@outlook.com |
Stability | unstable |
Portability | non-portable (GHC only) |
Safe Haskell | None |
Language | Haskell2010 |
This module contains the definition of the Eff
monad, as well as reexports of some shared utilities in the
internal modules. 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.
Synopsis
- newtype Eff es a = Eff {}
- type Effect = (Type -> Type) -> Type -> Type
- data Env (es :: [Effect]) = Env !(Stack es) !(RadixVec Any)
- newtype HandlerPtr (e :: Effect) = HandlerPtr {
- unHandlerPtr :: Int
- class (e :: Effect) :> (es :: [Effect])
- type family xs :>> es :: Constraint where ...
- class KnownList (es :: [Effect])
- class KnownList es => Subset (es :: [Effect]) (es' :: [Effect])
- type family xs ++ ys where ...
- type (~>) f g = forall a. f a -> g a
The Eff
monad
The extensible effects monad. The monad
is capable of performing any effect in the effect stack Eff
eses
,
which is a type-level list that holds all effects available.
The best practice is to always use a polymorphic type variable for the effect stack es
, and then use the type
operator (:>)
in constraints to indicate what effects are available in the stack. For example,
(Reader
String
:>
es,State
Bool
:>
es) =>Eff
esInteger
means you can perform operations of the
effect and the Reader
String
effect in a computation returning an State
Bool
Integer
. A convenient shorthand, (:>>)
, can also be used to indicate
multiple effects being in a stack:
'[Reader
String
,State
Bool
]:>>
es =>Eff
esInteger
The reason why you should always use a polymorphic effect stack as opposed to a concrete list of effects are that:
- it can contain other effects that are used by computations other than the current one, and
- it does not require you to run the effects in any particular order.
Eff | The effect monad receives an effect environment |
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 # | |
MonadZip (Eff es) Source # | Compatibility instance for Since: 0.2.1.0 |
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 | |
Bounded a => Bounded (Eff es a) Source # | Since: 0.2.1.0 |
Floating a => Floating (Eff es a) Source # | Since: 0.2.1.0 |
Defined in Cleff.Internal.Monad sqrt :: Eff es a -> Eff es a # (**) :: Eff es a -> Eff es a -> Eff es a # logBase :: Eff es a -> Eff es a -> Eff es a # asin :: Eff es a -> Eff es a # acos :: Eff es a -> Eff es a # atan :: Eff es a -> Eff es a # sinh :: Eff es a -> Eff es a # cosh :: Eff es a -> Eff es a # tanh :: Eff es a -> Eff es a # asinh :: Eff es a -> Eff es a # acosh :: Eff es a -> Eff es a # atanh :: Eff es a -> Eff es a # log1p :: Eff es a -> Eff es a # expm1 :: Eff es a -> Eff es a # | |
Fractional a => Fractional (Eff es a) Source # | Since: 0.2.1.0 |
Num a => Num (Eff es a) Source # | Since: 0.2.1.0 |
IsString a => IsString (Eff es a) Source # | Since: 0.2.1.0 |
Defined in Cleff.Internal.Monad fromString :: String -> Eff es a # | |
Semigroup a => Semigroup (Eff es a) Source # | Since: 0.2.1.0 |
Monoid a => Monoid (Eff es a) Source # | Since: 0.2.1.0 |
type PrimState (Eff es) Source # | |
Defined in Cleff.Internal.Base | |
type StM (Eff es) a Source # | |
Defined in Cleff.Internal.Base |
data Env (es :: [Effect]) Source #
The effect environment that corresponds effects in the stack to their respective handlers. This
structure simulates memory: handlers are retrieved via pointers (HandlerPtr
s), and for each effect in the stack
we can either change what pointer it uses or change the handler the pointer points to. The former is used for global
effect interpretation (reinterpretN
) and the latter for local interpretation (toEffWith
) in order to
retain correct HO semantics. For more details on this see https://github.com/re-xyr/cleff/issues/5.
newtype HandlerPtr (e :: Effect) Source #
A pointer to an effect handler.
Constraints
class (e :: Effect) :> (es :: [Effect]) infix 0 Source #
e
means the effect :>
ese
is present in the effect stack es
, and therefore can be send
ed in an
computation.Eff
es
Instances
(TypeError (ElemNotFound e) :: Constraint) => e :> ('[] :: [Effect]) Source # | |
Defined in Cleff.Internal.Stack reifyIndex :: Int | |
e :> es => e :> (e' ': es) Source # | |
Defined in Cleff.Internal.Stack reifyIndex :: Int | |
e :> (e ': es) Source # | The element closer to the head takes priority. |
Defined in Cleff.Internal.Stack reifyIndex :: Int |
type family xs :>> es :: Constraint where ... infix 0 Source #
class KnownList (es :: [Effect]) Source #
means the list KnownList
eses
is concrete, i.e. is of the form '[a1, a2, ..., an]
instead of a type
variable.
class KnownList es => Subset (es :: [Effect]) (es' :: [Effect]) Source #
es
is a subset of es'
, i.e. all elements of es
are in es'
.
Instances
Subset ('[] :: [Effect]) es Source # | |
Defined in Cleff.Internal.Stack reifyIndices :: [Int] | |
(Subset es es', e :> es') => Subset (e ': es) es' Source # | |
Defined in Cleff.Internal.Stack reifyIndices :: [Int] |