monad-markov-0.1.0.0: Markov process monad

Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Control.Monad.Markov

Description

A Markov chain monad, built on top of https://hackage.haskell.org/package/MonadRandom.

The interface is defined by MonadMarkov.

For example code, see the "example" directory.

Synopsis

Documentation

class Monad m => MonadMarkov s m where Source #

An interface to Markov process monads.

Minimal complete definition

nextState

Methods

nextState :: m s Source #

given the current state and transition table, return a new state.

Instances
(MonadMarkov s m, RandomGen g) => MonadMarkov s (RandT g m) Source # 
Instance details

Defined in Control.Monad.Markov.Class

Methods

nextState :: RandT g m s Source #

MonadRandom m => MonadMarkov s (MarkovT s m) Source # 
Instance details

Defined in Control.Monad.Markov.Internal

Methods

nextState :: MarkovT s m s 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 Markov s a = MarkovT s Identity a Source #

A basic Markov 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.

data 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 # 
Instance details

Defined in Control.Monad.Markov.Internal

Methods

nextState :: MarkovT s m s Source #

Monad m => Monad (MarkovT s m) Source # 
Instance details

Defined in Control.Monad.Markov.Internal

Methods

(>>=) :: MarkovT s m a -> (a -> MarkovT s m b) -> MarkovT s m b #

(>>) :: MarkovT s m a -> MarkovT s m b -> MarkovT s m b #

return :: a -> MarkovT s m a #

fail :: String -> MarkovT s m a #

Functor m => Functor (MarkovT s m) Source # 
Instance details

Defined in Control.Monad.Markov.Internal

Methods

fmap :: (a -> b) -> MarkovT s m a -> MarkovT s m b #

(<$) :: a -> MarkovT s m b -> MarkovT s m a #

Monad m => Applicative (MarkovT s m) Source # 
Instance details

Defined in Control.Monad.Markov.Internal

Methods

pure :: a -> MarkovT s m a #

(<*>) :: MarkovT s m (a -> b) -> MarkovT s m a -> MarkovT s m b #

liftA2 :: (a -> b -> c) -> MarkovT s m a -> MarkovT s m b -> MarkovT s m c #

(*>) :: MarkovT s m a -> MarkovT s m b -> MarkovT s m b #

(<*) :: MarkovT s m a -> MarkovT s m b -> MarkovT s m a #

MonadPlus m => MonadPlus (MarkovT s m) Source # 
Instance details

Defined in Control.Monad.Markov.Internal

Methods

mzero :: MarkovT s m a #

mplus :: MarkovT s m a -> MarkovT s m a -> MarkovT s m a #

MonadIO m => MonadIO (MarkovT s m) Source # 
Instance details

Defined in Control.Monad.Markov.Internal

Methods

liftIO :: IO a -> MarkovT s m a #

MonadRandom m => MonadRandom (MarkovT s m) Source # 
Instance details

Defined in Control.Monad.Markov.Internal

Methods

getRandomR :: Random a => (a, a) -> MarkovT s m a #

getRandom :: Random a => MarkovT s m a #

getRandomRs :: Random a => (a, a) -> MarkovT s m [a] #

getRandoms :: Random a => MarkovT s m [a] #

MonadInterleave m => MonadInterleave (MarkovT s m) Source # 
Instance details

Defined in Control.Monad.Markov.Internal

Methods

interleave :: MarkovT s m a -> MarkovT s m a #

MonadPlus m => Alternative (MarkovT s m) Source # 
Instance details

Defined in Control.Monad.Markov.Internal

Methods

empty :: MarkovT s m a #

(<|>) :: MarkovT s m a -> MarkovT s m a -> MarkovT s m a #

some :: MarkovT s m a -> MarkovT s m [a] #

many :: MarkovT s m a -> MarkovT s m [a] #

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.

evalMarkovT Source #

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.

evalMarkov Source #

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.

runMarkovT Source #

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.

runMarkov Source #

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.

runMarkovRT Source #

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.

runMarkovR Source #

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.

runMarkovStdT Source #

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.

runMarkovStd Source #

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.

evalMarkovRT Source #

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.

evalMarkovR Source #

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.

evalMarkovStdT Source #

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.

evalMarkovStd Source #

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.

evalMarkovIO Source #

Arguments

:: MarkovStdT s IO a

computation to execute

-> s

initial state

-> TransTable s

transition function to use

-> IO a 

Evaluate a Markov computation in the IO monad, using the standard random generator supplied by getStdGen.