| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
System.Random.MWC.Probability.Transition
Contents
- data Transition message s m a
- mkTransition :: Monad m => (s -> Prob m t) -> (s -> t -> (a, s)) -> (s -> t -> a -> 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)
- evalTransition :: Monad m => Handler m message -> Transition message s m a -> Int -> s -> Gen (PrimState m) -> m [a]
- execTransition :: Monad m => Handler m message -> Transition message s m a -> Int -> s -> Gen (PrimState m) -> m s
- stepConditional :: Monad m => (a -> s -> s -> Bool) -> (a -> s -> s -> l) -> (a -> s -> s -> r) -> Handler m message -> Transition message s m a -> s -> Gen (PrimState m) -> m (Either l r)
- withSeverity :: (t -> String) -> WithSeverity t -> String
- data WithSeverity a :: * -> * = WithSeverity {
- msgSeverity :: Severity
- discardSeverity :: a
- data Severity :: *
- type Handler (m :: * -> *) message = message -> m ()
- withFDHandler :: (MonadIO io, MonadMask io) => BatchingOptions -> Handle -> Double -> Int -> (Handler io (Doc ann) -> io a) -> io a
- data BatchingOptions :: * = BatchingOptions {}
- defaultBatchingOptions :: BatchingOptions
- withBatchedHandler :: (MonadIO io, MonadMask io) => BatchingOptions -> (NonEmpty message -> IO ()) -> (Handler io message -> io a) -> io a
- stdout :: Handle
- stderr :: Handle
Transition
data Transition message s m a Source #
A Markov transition kernel.
Instances
| Functor m => Functor (Transition message s m) Source # | |
| Show (Transition msg s m a) Source # | |
Arguments
| :: Monad m | |
| => (s -> Prob m t) | Generation of random data |
| -> (s -> t -> (a, s)) | (Output, Next state) |
| -> (s -> t -> a -> message) | Log message construction using (Next state, current random data, Output) |
| -> 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) | (Outputs, Final state) |
Run a Transition for a number of steps, while logging each iteration.
Returns both the list of outputs and the final state.
Specialized combinators
Arguments
| :: Monad m | |
| => Handler m message | |
| -> Transition message s m a | |
| -> Int | |
| -> s | |
| -> Gen (PrimState m) | |
| -> m [a] | Outputs |
Run a Transition for a number of steps, while logging each iteration.
Returns the list of outputs.
Arguments
| :: Monad m | |
| => Handler m message | |
| -> Transition message s m a | |
| -> Int | |
| -> s | |
| -> Gen (PrimState m) | |
| -> m s | Final state |
Run a Transition for a number of steps, while logging each iteration.
Returns the final state.
Conditional execution
Arguments
| :: Monad m | |
| => (a -> s -> s -> Bool) | Inputs: Model output, Current state, New state |
| -> (a -> s -> s -> l) | " |
| -> (a -> s -> s -> r) | " |
| -> Handler m message | |
| -> Transition message s m a | |
| -> s | Current state |
| -> Gen (PrimState m) | |
| -> m (Either l r) |
Perform one Transition and check output and updated state against the current state, producing an Either with the result of the comparison.
Can be useful for detecting early divergence or lack of convergence etc.
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
Log message severity
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. |
Handlers
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.
Arguments
| :: (MonadIO io, MonadMask io) | |
| => BatchingOptions | |
| -> Handle | The |
| -> Double | The |
| -> Int | The amount of characters per line. Lines longer than this will be pretty-printed across multiple lines if possible. |
| -> (Handler io (Doc ann) -> io a) | |
| -> io a |
withFDHandler creates a new Handler that will append a given file
descriptor (or Handle, as it is known in the "base" library). Note that
this Handler requires log messages to be of type Doc. This abstractly
specifies a pretty-printing for log lines. The two arguments two
withFDHandler determine how this pretty-printing should be realised
when outputting log lines.
These Handlers asynchronously log messages to the given file descriptor,
rather than blocking.
Batched logging
data BatchingOptions :: * #
Options that be used to configure withBatchingHandler.
Constructors
| BatchingOptions | |
Fields
| |
defaultBatchingOptions :: BatchingOptions #
Defaults for BatchingOptions
defaultBatchingOptions=BatchingOptions{flushMaxDelay= 1000000 ,flushMaxQueueSize= 100 ,blockWhenFull=True}
withBatchedHandler :: (MonadIO io, MonadMask io) => BatchingOptions -> (NonEmpty message -> IO ()) -> (Handler io message -> io a) -> io a #
Create a new batched handler. Batched handlers take batches of messages to log at once, which can be more performant than logging each individual message.
A batched handler flushes under three criteria:
- The flush interval has elapsed and the queue is not empty.
- The queue has become full and needs to be flushed.
- The scope of
withBatchedHandleris exited.
Batched handlers queue size and flush period can be configured via
BatchingOptions.