Stability | experimental |
---|---|
Portability | non-portable (multi-parameter type classes, generalized newtype deriving, flexible instances) |
Safe Haskell | None |
Language | Haskell2010 |
Extensions |
|
Control.Monad.Markov.Internal
Description
A Markov chain monad, built on top of MonadRandom
.
The interface is defined by MonadMarkov
.
For example code, see the "example" directory.
Synopsis
- newtype MarkovT s m a = MarkovT {}
- type MarkovStd s = MarkovR s StdGen
- type MarkovStdT s m = MarkovRT s StdGen m
- type MarkovR s g = MarkovT s (Rand g)
- type MarkovRT s g m = MarkovT s (RandT g m)
- type Markov s a = MarkovT s Identity a
- type TransTable a = a -> [(a, Rational)]
- newtype MarkovT s m a = MarkovT {}
- withMarkovT :: (s -> s) -> MarkovT s m a -> MarkovT s m a
- evalMarkovT :: Monad m => MarkovT s m a -> s -> TransTable s -> m a
- evalMarkov :: Markov s a -> s -> TransTable s -> a
- runMarkovT :: MarkovT s m a -> s -> TransTable s -> m (a, s)
- runMarkov :: Markov s a -> s -> TransTable s -> (a, s)
- runMarkovRT :: Functor m => MarkovRT s g m a -> g -> s -> TransTable s -> m (a, g, s)
- runMarkovR :: MarkovR s g a -> g -> s -> TransTable s -> (a, g, s)
- runMarkovStdT :: Functor m => MarkovStdT s m a -> Int -> s -> TransTable s -> m (a, StdGen, s)
- runMarkovStd :: MarkovStd s a -> Int -> s -> TransTable s -> (a, StdGen, s)
- evalMarkovRT :: Monad m => MarkovRT s g m a -> g -> s -> TransTable s -> m a
- evalMarkovR :: MarkovR s g a -> g -> s -> TransTable s -> a
- evalMarkovStdT :: Monad m => MarkovStdT s m a -> Int -> s -> TransTable s -> m a
- evalMarkovStd :: MarkovStd s a -> Int -> s -> TransTable s -> a
- evalMarkovIO :: MarkovStdT s IO a -> s -> TransTable s -> IO a
- module Control.Monad.Markov.Class
Documentation
newtype MarkovT s m a Source #
A monad transformer which adds access to a state and a probabilistic transition function to an existing monad.
Parameterized by:
s
- The state.m
- The inner monad.
The return
function leaves the state unchanged, while >>=
uses
the final state of the first computation as the initial state of
the second.
Instances
MonadRandom m => MonadMarkov s (MarkovT s m) Source # | |
Defined in Control.Monad.Markov.Internal | |
Monad m => Monad (MarkovT s m) Source # | |
Functor m => Functor (MarkovT s m) Source # | |
Monad m => Applicative (MarkovT s m) Source # | |
Defined in Control.Monad.Markov.Internal | |
MonadPlus m => MonadPlus (MarkovT s m) Source # | |
MonadIO m => MonadIO (MarkovT s m) Source # | |
Defined in Control.Monad.Markov.Internal | |
MonadRandom m => MonadRandom (MarkovT s m) Source # | |
Defined in Control.Monad.Markov.Internal | |
MonadInterleave m => MonadInterleave (MarkovT s m) Source # | |
Defined in Control.Monad.Markov.Internal Methods interleave :: MarkovT s m a -> MarkovT s m a # | |
MonadPlus m => Alternative (MarkovT s m) Source # | |
type MarkovStd s = MarkovR s StdGen Source #
Basic Markov monad, using the standard random generator StdGen
type MarkovStdT s m = MarkovRT s StdGen m Source #
Markov monad transformer, using the standard random generator
type MarkovR s g = MarkovT s (Rand g) Source #
Basic markov monad laid over the RandT
random value monad.
type MarkovRT s g m = MarkovT s (RandT g m) Source #
Markov monad transformer, laid over the RandT
random
value monad.
type TransTable a = a -> [(a, Rational)] Source #
a transition function, from a state, to a weighted list of states. The total weight of states must not be 0.
newtype MarkovT s m a Source #
A monad transformer which adds access to a state and a probabilistic transition function to an existing monad.
Parameterized by:
s
- The state.m
- The inner monad.
The return
function leaves the state unchanged, while >>=
uses
the final state of the first computation as the initial state of
the second.
Instances
MonadRandom m => MonadMarkov s (MarkovT s m) Source # | |
Defined in Control.Monad.Markov.Internal | |
Monad m => Monad (MarkovT s m) Source # | |
Functor m => Functor (MarkovT s m) Source # | |
Monad m => Applicative (MarkovT s m) Source # | |
Defined in Control.Monad.Markov.Internal | |
MonadPlus m => MonadPlus (MarkovT s m) Source # | |
MonadIO m => MonadIO (MarkovT s m) Source # | |
Defined in Control.Monad.Markov.Internal | |
MonadRandom m => MonadRandom (MarkovT s m) Source # | |
Defined in Control.Monad.Markov.Internal | |
MonadInterleave m => MonadInterleave (MarkovT s m) Source # | |
Defined in Control.Monad.Markov.Internal Methods interleave :: MarkovT s m a -> MarkovT s m a # | |
MonadPlus m => Alternative (MarkovT s m) Source # | |
withMarkovT :: (s -> s) -> MarkovT s m a -> MarkovT s m a Source #
withMarkovT f m
executes action m
on a state modified by applying
f
.
Arguments
:: Monad m | |
=> MarkovT s m a | computation to execute |
-> s | initial state |
-> TransTable s | transition function to use |
-> m a |
Evaluate a Markov chain computation with a given initial state and transition table, and return the final value, discarding the final state.
Arguments
:: Markov s a | computation to execute |
-> s | initial state |
-> TransTable s | transition function to use |
-> a |
Evaluate a Markov chain computation with a given initial state and transition table, and return the final value, discarding the final state.
Arguments
:: MarkovT s m a | computation to execute |
-> s | initial state |
-> TransTable s | transition function to use |
-> m (a, s) |
Unwrap a Markov monad computation as a function.
Arguments
:: Markov s a | computation to execute |
-> s | initial state |
-> TransTable s | transition function to use |
-> (a, s) |
Unwrap a Markov
monad computation as a function.
Arguments
:: Functor m | |
=> MarkovRT s g m a | computation to execute |
-> g | generator to use |
-> s | initial state |
-> TransTable s | transition function to use |
-> m (a, g, s) |
Run a Markov computation using the generator g
,
returning the result, the updated generator, and the
the final state.
Arguments
:: MarkovR s g a | computation to execute |
-> g | generator to use |
-> s | initial state |
-> TransTable s | transition function to use |
-> (a, g, s) |
Run a Markov computation using the generator g
,
returning the result, the updated generator, and the
the final state.
Arguments
:: Functor m | |
=> MarkovStdT s m a | computation to execute |
-> Int | seed for generator |
-> s | initial state |
-> TransTable s | transition function to use |
-> m (a, StdGen, s) |
Run a Markov computation
using the random number
generator used by getStdRandom
,
initialised with the seed seed
,
returning the result, the updated generator, and the
the final state.
Arguments
:: MarkovStd s a | computation to execute |
-> Int | seed for generator |
-> s | initial state |
-> TransTable s | transition function to use |
-> (a, StdGen, s) |
Run a Markov computation
using the random number
generator used by getStdRandom
,
initialised with the seed seed
,
returning the result, the updated generator, and the
the final state.
Arguments
:: Monad m | |
=> MarkovRT s g m a | computation to execute |
-> g | generator to use |
-> s | initial state |
-> TransTable s | transition function to use |
-> m a |
Evaluate a MarkovRT
computation using the random generator g
.
Arguments
:: MarkovR s g a | computation to execute |
-> g | generator to use |
-> s | initial state |
-> TransTable s | transition function to use |
-> a |
Evaluate a MarkovR
computation using the random generator g
.
Arguments
:: Monad m | |
=> MarkovStdT s m a | computation to execute |
-> Int | seed for generator |
-> s | initial state |
-> TransTable s | transition function to use |
-> m a |
Evaluate a MarkovRT
computation using the standard random generator,
initialized with seed
.
Arguments
:: MarkovStd s a | computation to execute |
-> Int | seed for generator |
-> s | initial state |
-> TransTable s | transition function to use |
-> a |
Evaluate a MarkovRT
computation using the standard random generator,
initialized with seed
.
Arguments
:: MarkovStdT s IO a | computation to execute |
-> s | initial state |
-> TransTable s | transition function to use |
-> IO a |
module Control.Monad.Markov.Class