| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
System.Random.MWC.Probability.Transition
- data Transition message s m a
- mkTransition :: Monad m => (s -> Prob m t) -> (s -> t -> (a, s)) -> (a -> s -> message) -> Transition message s m a
- runTransition :: Monad m => Handler m message -> Transition message s m a -> Int -> s -> Gen (PrimState m) -> m [(a, s)]
- withSeverity :: (t -> String) -> WithSeverity t -> String
- type Handler (m :: * -> *) message = message -> m ()
- data WithSeverity a :: * -> * = WithSeverity {
- msgSeverity :: Severity
- discardSeverity :: a
- data Severity :: *
Transition
data Transition message s m a Source #
A Markov transition kernel.
Instances
| Functor m => Functor (Transition message s m) Source # | |
Arguments
| :: Monad m | |
| => (s -> Prob m t) | Random generation |
| -> (s -> t -> (a, s)) | (Output, Next state) |
| -> (a -> s -> message) | Log message generation |
| -> Transition message s m a |
Construct a Transition from sampling, state transformation and logging functions.
NB: The three function arguments are used in the order in which they appear here:
- a random sample
w :: tis produced, using the current statex :: sas input - output
z :: aand next statex' :: sare computed usingwandx - a logging message is constructed, using
zandx'as arguments.
Arguments
| :: Monad m | |
| => Handler m message | Logging handler |
| -> Transition message s m a | |
| -> Int | Number of iterations |
| -> s | Initial state |
| -> Gen (PrimState m) | PRNG |
| -> m [(a, s)] |
Run a Transition for a number of steps, while logging each iteration.
Helper functions
withSeverity :: (t -> String) -> WithSeverity t -> String Source #
Render a logging message along with an annotation of its severity.
Re-exported from `logging-effect`
type Handler (m :: * -> *) message = message -> m () #
Handlers are mechanisms to interpret the meaning of logging as an action
in the underlying monad. They are simply functions from log messages to
m-actions.
data WithSeverity a :: * -> * #
Add "Severity" information to a log message. This is often used to convey how significant a log message is.
Constructors
| WithSeverity | |
Fields
| |
Instances
| Functor WithSeverity | |
| Foldable WithSeverity | |
| Traversable WithSeverity | |
| Eq a => Eq (WithSeverity a) | |
| Ord a => Ord (WithSeverity a) | |
| Read a => Read (WithSeverity a) | |
| Show a => Show (WithSeverity a) | |
Classes of severity for log messages. These have been chosen to match
syslog severity levels
Constructors
| Emergency | System is unusable. By |
| Alert | Should be corrected immediately. |
| Critical | Critical conditions. |
| Error | Error conditions. |
| Warning | May indicate that an error will occur if action is not taken. |
| Notice | Events that are unusual, but not error conditions. |
| Informational | Normal operational messages that require no action. |
| Debug | Information useful to developers for debugging the application. |