markov-realization-0.1.0: Realizations of Markov chains.

Maintaineratloomis@math.arizona.edu
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Markov.Examples

Description

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

Synopsis

Documentation

newtype FromMatrix Source #

An example defined from a matrix.

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

Constructors

FromMatrix Char 
Instances
Eq FromMatrix Source # 
Instance details

Defined in Markov.Examples

Show FromMatrix Source # 
Instance details

Defined in Markov.Examples

Generic FromMatrix Source # 
Instance details

Defined in Markov.Examples

Associated Types

type Rep FromMatrix :: Type -> Type #

Grouping FromMatrix Source # 
Instance details

Defined in Markov.Examples

Markov (Product Double) FromMatrix Source # 
Instance details

Defined in Markov.Examples

type Rep FromMatrix Source # 
Instance details

Defined in Markov.Examples

type Rep FromMatrix = D1 (MetaData "FromMatrix" "Markov.Examples" "markov-realization-0.1.0-6GSvYD8yAhy2vCcDg5QqBj" True) (C1 (MetaCons "FromMatrix" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 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.Examples

Eq Simple Source # 
Instance details

Defined in Markov.Examples

Methods

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

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

Num Simple Source # 
Instance details

Defined in Markov.Examples

Ord Simple Source # 
Instance details

Defined in Markov.Examples

Show Simple Source # 
Instance details

Defined in Markov.Examples

Generic Simple Source # 
Instance details

Defined in Markov.Examples

Associated Types

type Rep Simple :: Type -> Type #

Methods

from :: Simple -> Rep Simple x #

to :: Rep Simple x -> Simple #

Grouping Simple Source # 
Instance details

Defined in Markov.Examples

Markov0 Simple Source # 
Instance details

Defined in Markov.Examples

Markov (Product Double) Simple Source # 
Instance details

Defined in Markov.Examples

Markov (Product Int) Simple Source # 
Instance details

Defined in Markov.Examples

Markov (Sum Int) Simple Source # 
Instance details

Defined in Markov.Examples

Methods

transition :: Simple -> [(Sum Int, Simple -> Simple)] Source #

step :: (Sum Int, Simple) -> [(Sum Int, Simple)] Source #

chain :: [(Sum Int, Simple)] -> [[(Sum Int, Simple)]] Source #

type Rep Simple Source # 
Instance details

Defined in Markov.Examples

type Rep Simple = D1 (MetaData "Simple" "Markov.Examples" "markov-realization-0.1.0-6GSvYD8yAhy2vCcDg5QqBj" True) (C1 (MetaCons "Simple" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))

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.

Constructors

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

Defined in Markov.Examples

Methods

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

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

Ord Urn Source # 
Instance details

Defined in Markov.Examples

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.Examples

Methods

showsPrec :: Int -> Urn -> ShowS #

show :: Urn -> String #

showList :: [Urn] -> ShowS #

Generic Urn Source # 
Instance details

Defined in Markov.Examples

Associated Types

type Rep Urn :: Type -> Type #

Methods

from :: Urn -> Rep Urn x #

to :: Rep Urn x -> Urn #

Grouping Urn Source # 
Instance details

Defined in Markov.Examples

Methods

grouping :: Group Urn #

Markov (Product Double) Urn Source # 
Instance details

Defined in Markov.Examples

type Rep Urn Source # 
Instance details

Defined in Markov.Examples

type Rep Urn = D1 (MetaData "Urn" "Markov.Examples" "markov-realization-0.1.0-6GSvYD8yAhy2vCcDg5QqBj" True) (C1 (MetaCons "Urn" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Int, Int))))

newtype Extinction Source #

This is the chain from the README.

Constructors

Extinction Int 
Instances
Eq Extinction Source # 
Instance details

Defined in Markov.Examples

Num Extinction Source # 
Instance details

Defined in Markov.Examples

Show Extinction Source # 
Instance details

Defined in Markov.Examples

Generic Extinction Source # 
Instance details

Defined in Markov.Examples

Associated Types

type Rep Extinction :: Type -> Type #

Semigroup Extinction Source # 
Instance details

Defined in Markov.Examples

Grouping Extinction Source # 
Instance details

Defined in Markov.Examples

Combine Extinction Source # 
Instance details

Defined in Markov.Examples

MultiMarkov ((Sum Int :* Product Rational) :* Extinction) Source # 
Instance details

Defined in Markov.Examples

Markov (Sum Int, Product Rational) Extinction Source # 
Instance details

Defined in Markov.Examples

type Rep Extinction Source # 
Instance details

Defined in Markov.Examples

type Rep Extinction = D1 (MetaData "Extinction" "Markov.Examples" "markov-realization-0.1.0-6GSvYD8yAhy2vCcDg5QqBj" True) (C1 (MetaCons "Extinction" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))

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.Examples

Methods

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

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

Ord Tidal Source # 
Instance details

Defined in Markov.Examples

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.Examples

Methods

showsPrec :: Int -> Tidal -> ShowS #

show :: Tidal -> String #

showList :: [Tidal] -> ShowS #

Generic Tidal Source # 
Instance details

Defined in Markov.Examples

Associated Types

type Rep Tidal :: Type -> Type #

Methods

from :: Tidal -> Rep Tidal x #

to :: Rep Tidal x -> Tidal #

Grouping Tidal Source # 
Instance details

Defined in Markov.Examples

Methods

grouping :: Group Tidal #

Markov (Product Double) Tidal Source # 
Instance details

Defined in Markov.Examples

type Rep Tidal Source # 
Instance details

Defined in Markov.Examples

type Rep Tidal = D1 (MetaData "Tidal" "Markov.Examples" "markov-realization-0.1.0-6GSvYD8yAhy2vCcDg5QqBj" False) (C1 (MetaCons "Tidal" PrefixI True) (S1 (MetaSel (Just "time") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Double) :*: S1 (MetaSel (Just "position") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))

newtype Room Source #

A hidden Markov model.

>>> filter (\((_,Merge xs),_) -> xs == "aaa") $ multiChain [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.Examples

Methods

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

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

Num Room Source # 
Instance details

Defined in Markov.Examples

Methods

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

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

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

negate :: Room -> Room #

abs :: Room -> Room #

signum :: Room -> Room #

fromInteger :: Integer -> Room #

Show Room Source # 
Instance details

Defined in Markov.Examples

Methods

showsPrec :: Int -> Room -> ShowS #

show :: Room -> String #

showList :: [Room] -> ShowS #

Generic Room Source # 
Instance details

Defined in Markov.Examples

Associated Types

type Rep Room :: Type -> Type #

Methods

from :: Room -> Rep Room x #

to :: Rep Room x -> Room #

Semigroup Room Source # 
Instance details

Defined in Markov.Examples

Methods

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

sconcat :: NonEmpty Room -> Room #

stimes :: Integral b => b -> Room -> Room #

Grouping Room Source # 
Instance details

Defined in Markov.Examples

Methods

grouping :: Group Room #

Combine Room Source # 
Instance details

Defined in Markov.Examples

MultiMarkov ((Product Rational :* Merge String) :* Room) Source # 
Instance details

Defined in Markov.Examples

type Rep Room Source # 
Instance details

Defined in Markov.Examples

type Rep Room = D1 (MetaData "Room" "Markov.Examples" "markov-realization-0.1.0-6GSvYD8yAhy2vCcDg5QqBj" True) (C1 (MetaCons "Room" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))

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.Examples

Methods

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

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

Ord FillBin Source # 
Instance details

Defined in Markov.Examples

Show FillBin Source # 
Instance details

Defined in Markov.Examples

Generic FillBin Source # 
Instance details

Defined in Markov.Examples

Associated Types

type Rep FillBin :: Type -> Type #

Methods

from :: FillBin -> Rep FillBin x #

to :: Rep FillBin x -> FillBin #

Grouping FillBin Source # 
Instance details

Defined in Markov.Examples

Markov (Product Double) FillBin Source # 
Instance details

Defined in Markov.Examples

type Rep FillBin Source # 
Instance details

Defined in Markov.Examples

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 pstates 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