| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Control.Monad.Introspect.Class
Synopsis
- class (Representational r, MonadIntrospectTrans IdentityT r m) => MonadIntrospect (r :: (* -> *) -> *) (m :: * -> *) where
- introspect :: m (r m)
- substitute :: (r m -> r m) -> m a -> m a
- class (Monad m, MonadTrans t) => MonadIntrospectTrans (t :: (* -> *) -> * -> *) (r :: (* -> *) -> *) (m :: * -> *) | m -> t where
- introspectTrans :: m (r (t m))
- substituteTrans :: (r (t m) -> r (t m)) -> m a -> m a
- liftTransEnv :: (Representational r, Coercible m n) => r m -> r n
- liftTransMapper :: (Representational r, Coercible m n) => (r m -> r m) -> r n -> r n
Abstract interface
class (Representational r, MonadIntrospectTrans IdentityT r m) => MonadIntrospect (r :: (* -> *) -> *) (m :: * -> *) where Source #
A monad with introspection capability is able to query an environment r
that is parameterized by the monad itself, i.e. can contain effectful
functions.
The caveat is that sometimes the monad changes (e.g. we locally run a
transformer, or we globally run our transformer steck), so the monad in the
environment can "desync" from the ambient monad. This warrants a more general
class: MonadIntrospectTrans, of which MonadIntrospect is a special case.
The machinery sometimes requires newtype wrapping/unwrapping the monad that
goes to the environment. We use/require Coercible for that, as the
"functorial" operations are deemed expensive. The constraint
ensures that the environment can be coerced provided
the monad can be coerced.Representational r
Otherwise the interface is identical to that of
MonadReader.
Methods
introspect :: m (r m) Source #
Essentially ask.
substitute :: (r m -> r m) -> m a -> m a Source #
Essentially local.
Instances
| (Representational r, MonadIntrospectTrans (IdentityT :: (Type -> Type) -> Type -> Type) r m) => MonadIntrospect r m Source # | |
Defined in Control.Monad.Introspect.Class | |
class (Monad m, MonadTrans t) => MonadIntrospectTrans (t :: (* -> *) -> * -> *) (r :: (* -> *) -> *) (m :: * -> *) | m -> t where Source #
If the ambient monad is m and the environment r has additional effects
t, we can ask for that environment, or substitute it. Multiple (or zero)
effects can be combined into a single t with ComposeT (or IdentityT).
Methods
introspectTrans :: m (r (t m)) Source #
Essentially ask.
substituteTrans :: (r (t m) -> r (t m)) -> m a -> m a Source #
Essentially local.
Instances
Utility functions for coercing environments
liftTransEnv :: (Representational r, Coercible m n) => r m -> r n Source #
liftTransMapper :: (Representational r, Coercible m n) => (r m -> r m) -> r n -> r n Source #