Copyright | Copyright 2022 Shea Levy. |
---|---|
License | Apache-2.0 |
Maintainer | shea@shealevy.com |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Core typeclass for an mtl-style handling of EventBackend
s.
See Observe.Event.Explicit for an explicit, function-based
interface.
Synopsis
- class (forall r s. Monad (em r s), Monad (BackendMonad em)) => MonadEvent em where
- type BackendMonad em :: Type -> Type
- liftBackendMonad :: BackendMonad em a -> em r s a
- backend :: em r s (EnvBackend em r s)
- withModifiedBackend :: (EnvBackend em r s -> EnvBackend em r' s') -> em r' s' a -> em r s a
- type EnvBackend em = EventBackend (BackendMonad em)
- newtype TransEventMonad t em r s a = TransEventMonad {
- unTransEventMonad :: t (em r s) a
- newtype EventT m r s a = EventT (ReaderT (EventBackend m r s) m a)
- runEventT :: Monad m => EventT m r s a -> EventBackend m r s -> m a
- eventLift :: forall m r s. Applicative m => StatelessControlTransformation m (EventT m r s)
- type EventMonadKind = ReferenceKind -> SelectorKind -> FunctorKind
- type ReferenceKind = Type
- type SelectorKind = Type -> Type
- type FunctorKind = Type -> Type
Documentation
class (forall r s. Monad (em r s), Monad (BackendMonad em)) => MonadEvent em where Source #
Monads suitable for Event
-based instrumentation, with implicit EventBackend
management.
See Observe.Event.Explicit for Event
-based instrumentation with explicit EventBackend
passing.
Note that em
is an indexed monad of EventMonadKind
.
type BackendMonad em :: Type -> Type Source #
The monad of the implicitly carried EventBackend
liftBackendMonad :: BackendMonad em a -> em r s a Source #
backend :: em r s (EnvBackend em r s) Source #
Access the implicitly carried EventBackend
:: (EnvBackend em r s -> EnvBackend em r' s') | Modify the Note that the modification may change the reference and selector types. |
-> em r' s' a | Action to run with the modified backend available. |
-> em r s a |
Run an instrumented action with a modified EventBackend
Instances
type EnvBackend em = EventBackend (BackendMonad em) Source #
The type of the implicit EventBackend
of a MonadEvent
newtype TransEventMonad t em r s a Source #
Apply a MonadTrans
former to an EventMonadKind
to get a transformed EventMonadKind
When t
is MonadTransControl
and em
is MonadEvent
, TransEventMonad
t
em
is
MonadEvent
and has all of the relevant instances conferred by t
.
TransEventMonad | |
|
Instances
EventT
newtype EventT m r s a Source #
Make a monad into a MonadEvent
.
EventT (ReaderT (EventBackend m r s) m a) |
Instances
runEventT :: Monad m => EventT m r s a -> EventBackend m r s -> m a Source #
Run an EventT
with an initial EventBackend
.
eventLift :: forall m r s. Applicative m => StatelessControlTransformation m (EventT m r s) Source #
Lift m
into EventT
m
.
Kind aliases
type EventMonadKind = ReferenceKind -> SelectorKind -> FunctorKind Source #
The kind of indexed monads aware of Event
instrumentation
See MonadEvent
.
type ReferenceKind = Type Source #
The kind of Event
references