Safe Haskell | None |
---|---|
Language | Haskell2010 |
- 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)
- 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
Transition
data Transition message s m a Source #
A Markov transition kernel.
Functor m => Functor (Transition message s m) Source # | |
Show (Transition msg s m a) Source # | |
:: Monad m | |
=> (s -> Prob m t) | Random generation |
-> (s -> t -> (a, s)) | (Output, Next state) |
-> (a -> s -> message) | Log message construction |
-> 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 :: t
is produced, using the current statex :: s
as input - output
z :: a
and next statex' :: s
are computed usingw
andx
- a logging message is constructed, using
z
andx'
as 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
:: 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.
:: 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
:: 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.