markov-realization-0.4: Realizations of Markov chains.

Maintaineratloomis@math.arizona.edu
StabilityExperimental
Safe HaskellNone
LanguageHaskell2010

Markov.Example

Description

Several examples of Markov chains. It is probably more helpful to read the source code than the Haddock documentation.

Synopsis

Documentation

newtype FromLists Source #

An example defined from a matrix.

>>> chain [pure (FromMatrix 't') :: (Product Double, FromMatrix)] !! 100
[ (0.5060975609756099,'a')
, (0.201219512195122,'t')
, (0.29268292682926833,'l') ]

Constructors

FromLists Char 

newtype Simple Source #

A simple random walk. Possible outcomes of the first three steps:

>>> take 3 $ chain0 [Simple 0]
[ [0]
, [-1,1]
, [-2,0,2] ]

Probability of each outcome:

>>> take 3 $ chain [pure 0 :: (Product Double, Simple)]
[ [(1.0,0)]
, [(0.5,-1),(0.5,1)]
, [(0.25,-2),(0.5,0),(0.25,2)] ]

Number of ways to achieve each outcome:

>>> take 3 $ chain [pure 0 :: (Product Int, Simple)]
[ [(1,0)]
, [(1,-1),(1,1)]
, [(1,-2),(2,0),(1,2)] ]

Number of times pred was applied, allowing steps in place (id) for more interesting output:

>>> chain [pure 0 :: (Sum Int, Simple)] !! 2
[ (2,-2), (1,-1), (1,0), (0,0), (0,1), (0,2) ]

Constructors

Simple Int 
Instances
Enum Simple Source # 
Instance details

Defined in Markov.Example

Eq Simple Source # 
Instance details

Defined in Markov.Example

Methods

(==) :: Simple -> Simple -> Bool #

(/=) :: Simple -> Simple -> Bool #

Num Simple Source # 
Instance details

Defined in Markov.Example

Ord Simple Source # 
Instance details

Defined in Markov.Example

Show Simple Source # 
Instance details

Defined in Markov.Example

Combine Simple Source # 
Instance details

Defined in Markov.Example

Markov0 Simple Source # 
Instance details

Defined in Markov.Example

Markov ((,) (Product Double)) Simple Source # 
Instance details

Defined in Markov.Example

Markov ((,) (Product Int)) Simple Source # 
Instance details

Defined in Markov.Example

Markov ((,) (Sum Int)) Simple Source # 
Instance details

Defined in Markov.Example

newtype Urn Source #

An urn contains balls of two colors. At each step, a ball is chosen uniformly at random from the urn and a ball of the same color is added.

>>> randomPath (mkStdGen 70) (Urn (2,5)) !! 8 :: (Product Double, Urn)
(0.1648351648351649, Urn (2,13))

Constructors

Urn (Int, Int) 
Instances
Eq Urn Source # 
Instance details

Defined in Markov.Example

Methods

(==) :: Urn -> Urn -> Bool #

(/=) :: Urn -> Urn -> Bool #

Ord Urn Source # 
Instance details

Defined in Markov.Example

Methods

compare :: Urn -> Urn -> Ordering #

(<) :: Urn -> Urn -> Bool #

(<=) :: Urn -> Urn -> Bool #

(>) :: Urn -> Urn -> Bool #

(>=) :: Urn -> Urn -> Bool #

max :: Urn -> Urn -> Urn #

min :: Urn -> Urn -> Urn #

Show Urn Source # 
Instance details

Defined in Markov.Example

Methods

showsPrec :: Int -> Urn -> ShowS #

show :: Urn -> String #

showList :: [Urn] -> ShowS #

Combine Urn Source # 
Instance details

Defined in Markov.Example

Markov [] ((,) (Product Double)) Urn Source # 
Instance details

Defined in Markov.Example

Markov ((,) (Product Double)) Urn Source # 
Instance details

Defined in Markov.Example

data Tidal Source #

A time inhomogenous random walk that vaguely models tides by periodically switching directions and falling back from a shore at the origin.

Constructors

Tidal 

Fields

Instances
Eq Tidal Source # 
Instance details

Defined in Markov.Example

Methods

(==) :: Tidal -> Tidal -> Bool #

(/=) :: Tidal -> Tidal -> Bool #

Ord Tidal Source # 
Instance details

Defined in Markov.Example

Methods

compare :: Tidal -> Tidal -> Ordering #

(<) :: Tidal -> Tidal -> Bool #

(<=) :: Tidal -> Tidal -> Bool #

(>) :: Tidal -> Tidal -> Bool #

(>=) :: Tidal -> Tidal -> Bool #

max :: Tidal -> Tidal -> Tidal #

min :: Tidal -> Tidal -> Tidal #

Show Tidal Source # 
Instance details

Defined in Markov.Example

Methods

showsPrec :: Int -> Tidal -> ShowS #

show :: Tidal -> String #

showList :: [Tidal] -> ShowS #

Combine Tidal Source # 
Instance details

Defined in Markov.Example

Markov ((,) (Product Double)) Tidal Source # 
Instance details

Defined in Markov.Example

newtype Room Source #

A hidden Markov model.

>>> :{ filter (\((_,Merge xs),_) -> xs == "aaa") $ chain
       [1 >*< Merge "" >*< 1 :: Product Rational :* Merge String :* Room] !! 3
    :}
[ ((3243 % 200000,"aaa"),Room 1)
, ((9729 % 500000,"aaa"),Room 2)
, ((4501 % 250000,"aaa"),Room 3) ]

Given that all three tokens recieved were "a", there is a probability of approximately 0.34 that the current room is Room 3.

Constructors

Room Int 
Instances
Eq Room Source # 
Instance details

Defined in Markov.Example

Methods

(==) :: Room -> Room -> Bool #

(/=) :: Room -> Room -> Bool #

Num Room Source # 
Instance details

Defined in Markov.Example

Methods

(+) :: Room -> Room -> Room #

(-) :: Room -> Room -> Room #

(*) :: Room -> Room -> Room #

negate :: Room -> Room #

abs :: Room -> Room #

signum :: Room -> Room #

fromInteger :: Integer -> Room #

Ord Room Source # 
Instance details

Defined in Markov.Example

Methods

compare :: Room -> Room -> Ordering #

(<) :: Room -> Room -> Bool #

(<=) :: Room -> Room -> Bool #

(>) :: Room -> Room -> Bool #

(>=) :: Room -> Room -> Bool #

max :: Room -> Room -> Room #

min :: Room -> Room -> Room #

Show Room Source # 
Instance details

Defined in Markov.Example

Methods

showsPrec :: Int -> Room -> ShowS #

show :: Room -> String #

showList :: [Room] -> ShowS #

Combine Room Source # 
Instance details

Defined in Markov.Example

Markov ((,) (Product Rational, Merge String)) Room Source # 
Instance details

Defined in Markov.Example

data FillBin Source #

A collection of bins with gaps between them. At each step an empty space is chosen form a bin or from a gap. If it is in a bin, the space is filled. If it is in a gap, it is assigned to an adjacent bin, which expands to contain it and any intervening spaces, and then the space filled.

Instances
Eq FillBin Source # 
Instance details

Defined in Markov.Example

Methods

(==) :: FillBin -> FillBin -> Bool #

(/=) :: FillBin -> FillBin -> Bool #

Ord FillBin Source # 
Instance details

Defined in Markov.Example

Show FillBin Source # 
Instance details

Defined in Markov.Example

Combine FillBin Source # 
Instance details

Defined in Markov.Example

Markov ((,) (Product Double)) FillBin Source # 
Instance details

Defined in Markov.Example

initial :: [Int] -> FillBin Source #

Create state where all bins start as (0,0).

>>> initial [5,7,0]
5 (0,0) 7 (0,0) 0

expectedLoss :: (Fractional a, Markov ((,) (Product a)) FillBin) => [Product a :* FillBin] -> a Source #

Expected loss of a set of states of [FillBin]. Loss is the \(l^2\) distance between a finished state and a state with perfectly balanced bins.

>>> expectedLoss [pure $ initial [1,0,3] :: (Product Double, FillBin)]
2.0