| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Avail.Internal
Description
Synopsis
- newtype M m a = UnsafeLift (m a)
- type Effect = (Type -> Type) -> Constraint
- class KnownList (Superclasses e) => IsEff (e :: Effect) where
- type Superclasses e :: [Effect]
- class Eff' (e :: Effect) where
- instEffect :: Proxy e
- type Eff (e :: Effect) = (Eff' e, Effs (Superclasses e))
- type family Effs (es :: [Effect]) :: Constraint where ...
- newtype InstEff e a = InstEff (Eff' e => a)
- rip' :: forall e a. (Eff' e => a) -> a
- rip :: forall e a. IsEff e => (Eff e => a) -> a
- class KnownList (es :: [Effect]) where
- unM :: M m a -> m a
- runM :: forall es m a. KnownList es => (Effs es => M m a) -> m a
Documentation
The M monad transformer acts as a barrier of effects. For example, for a monad type App and any
effect typeclass MonadOvO that App has an instance of, the constraint Eff MonadOvO is required to perform
the methods of MonadOvO in the monad as defined for the M AppApp monad.
In particular, M is expected to be used on a concrete monad instead of a polymorphic one. This is
particularly good in terms of program performance, and generally means instead of writing this:
f ::MonadStateIntm => m ()
You should write
f ::Eff(MonadStateInt) =>MApp ()
where App is a monad stack of your choice that has support of . This also
means there is no MonadState IntMonadTrans instance for M.
Note: you should not define instances of M for effect typeclasses directly by hand as that is error-prone
and may create holes in effect management. For defining instances of effect typeclasses for M, check out
the Avail.Derive module and specifically the avail and avail' TH functions.
Also keep in mind that typeclasses inside mtl, exceptions, unliftio, monad-control and capability work
with M out-of-the-box so no instance for them is needed to be defined on M by you.
Constructors
| UnsafeLift (m a) | Unsafely lift an |
Instances
type Effect = (Type -> Type) -> Constraint Source #
The kind of effect typeclasses, i.e. those that define a set of operations on a monad. Examples include
MonadIO and MonadReader.
This type is the same as the Capability type in capability.
class KnownList (Superclasses e) => IsEff (e :: Effect) Source #
Any Effect being used with avail should have an instance of this class. Specifically, this class stores
the superclasses of effect typeclasses. For example, MonadUnliftIO has a superclass
MonadIO.
You won't need to define instances of this by hand; instead, use the avail' Template Haskell function.
Instances
class Eff' (e :: Effect) where Source #
The primitive phantom effect constraint that does not take superclasses into account. You should not use this
directly; use Eff or Effs instead. Additionally, you definitely shouldn't define instances for this class.
Minimal complete definition
Nothing
Methods
instEffect :: Proxy e Source #
The dummy method of the phantom typeclass, to be instantiated via the reflection trick in rip'.
type Eff (e :: Effect) = (Eff' e, Effs (Superclasses e)) Source #
The constraint that indicates an effect is available for use, i.e. you can perform methods defined by instances
of the effect typeclass e in a M monad.
type family Effs (es :: [Effect]) :: Constraint where ... Source #
The newtype wrapper used to circumvent the impredicative problem of GHC and perform the reflection trick in
rip'. You have no reason to use this directly.
rip' :: forall e a. (Eff' e => a) -> a Source #
Brutally rip off an Eff' constraint, a la
the reflection trick.
This is highly unsafe in terms of effect management.
class KnownList (es :: [Effect]) where Source #
The list of effect typeclasses es is known at compile time. This is required for functions like runM.
Minimal complete definition
Nothing
runM :: forall es m a. KnownList es => (Effs es => M m a) -> m a Source #
Unwrap the M monad into the underlying concrete monad and also eliminating Eff constraints. You need
TypeApplications in order to specify the list of Effects you want to eliminate Eff constraints for:
runM @'[MonadReader Env, MonadState Store, MonadError MyErr] app
Note that functions like (&) generally does not work with this function; either apply directly or
use ($) only.