Maintainer | atloomis@math.arizona.edu |
---|---|
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
Three type classes for deterministically analyzing
Markov chains with known parameters.
Markov0
is intended to list possible outcomes,
Markov
should allow for more sophisticated analysis,
and MultiMarkov
is intended to make implementing
hidden Markov models easier.
See Examples for examples.
See README for a detailed description.
Synopsis
- class Eq m => Markov0 m where
- transition0 :: m -> [m -> m]
- step0 :: m -> [m]
- chain0 :: [m] -> [[m]]
- class (Combine t, Grouping t, Grouping m, Monoid t) => Markov t m where
- transition :: m -> [(t, m -> m)]
- step :: (t, m) -> [(t, m)]
- chain :: [(t, m)] -> [[(t, m)]]
- randomProduct :: (Real a, MonadRandom m) => [(a, b)] -> m (a, b)
- randomPath :: (Markov a b, Real a, RandomGen g) => (a, b) -> g -> [(a, b)]
- class (Combine m, Grouping m, Semigroup m) => MultiMarkov m where
- multiTransition :: m -> [m -> [m]]
- multiStep :: m -> [m]
- multiChain :: [m] -> [[m]]
- class Combine a where
- newtype Merge a = Merge a
- newtype Sum a = Sum a
- newtype Product a = Product a
- type (:*) a b = (a, b)
- (>*<) :: a -> b -> a :* b
- fromLists :: Eq b => [[a]] -> [b] -> b -> [(a, b -> b)]
Markov0
class Eq m => Markov0 m where Source #
A basic implementation of Markov chains.
Markov
class (Combine t, Grouping t, Grouping m, Monoid t) => Markov t m where Source #
An implementation of Markov chains.
To speed up chain
, try instead:
chain = DL.iterate' $ map summarize' . NE.group . DL.sort . concatMap step where summarize' xs@((_,b)NE.:|_) = (summarize . fmap fst $ xs, b)
Instances
Markov (Product Double) FillBin Source # | |
Markov (Product Double) Tidal Source # | |
Markov (Product Double) Urn Source # | |
Markov (Product Double) Simple Source # | |
Markov (Product Double) FromMatrix Source # | |
Defined in Markov.Examples transition :: FromMatrix -> [(Product Double, FromMatrix -> FromMatrix)] Source # step :: (Product Double, FromMatrix) -> [(Product Double, FromMatrix)] Source # chain :: [(Product Double, FromMatrix)] -> [[(Product Double, FromMatrix)]] Source # | |
Markov (Product Int) Simple Source # | |
Markov (Sum Int) Simple Source # | |
Markov (Sum Int, Product Rational) Extinction Source # | |
Defined in Markov.Examples transition :: Extinction -> [((Sum Int, Product Rational), Extinction -> Extinction)] Source # step :: ((Sum Int, Product Rational), Extinction) -> [((Sum Int, Product Rational), Extinction)] Source # chain :: [((Sum Int, Product Rational), Extinction)] -> [[((Sum Int, Product Rational), Extinction)]] Source # |
MultiMarkov
randomProduct :: (Real a, MonadRandom m) => [(a, b)] -> m (a, b) Source #
Randomly choose from a list by probability.
randomPath :: (Markov a b, Real a, RandomGen g) => (a, b) -> g -> [(a, b)] Source #
Returns a single realization of a Markov chain.
class (Combine m, Grouping m, Semigroup m) => MultiMarkov m where Source #
An implementation of Markov chains that allows multi-transition steps.
multiTransition :: m -> [m -> [m]] Source #
multiStep :: m -> [m] Source #
multiChain :: [m] -> [[m]] Source #
Instances
MultiMarkov ((Product Rational :* Merge String) :* Room) Source # | |
Defined in Markov.Examples multiTransition :: ((Product Rational :* Merge String) :* Room) -> [((Product Rational :* Merge String) :* Room) -> [(Product Rational :* Merge String) :* Room]] Source # multiStep :: ((Product Rational :* Merge String) :* Room) -> [(Product Rational :* Merge String) :* Room] Source # multiChain :: [(Product Rational :* Merge String) :* Room] -> [[(Product Rational :* Merge String) :* Room]] Source # | |
MultiMarkov ((Sum Int :* Product Rational) :* Extinction) Source # | |
Defined in Markov.Examples multiTransition :: ((Sum Int :* Product Rational) :* Extinction) -> [((Sum Int :* Product Rational) :* Extinction) -> [(Sum Int :* Product Rational) :* Extinction]] Source # multiStep :: ((Sum Int :* Product Rational) :* Extinction) -> [(Sum Int :* Product Rational) :* Extinction] Source # multiChain :: [(Sum Int :* Product Rational) :* Extinction] -> [[(Sum Int :* Product Rational) :* Extinction]] Source # |
Combine
class Combine a where Source #
Within equivalence classes, combine
should be associative,
commutative, and should be idempotent up to equivalence.
I.e. if x == y == z
,
(x `combine` y) `combine` z = x `combine` (y `combine` z)
x `combine` y = y `combine` x
x `combine` x == x
Instances
Combine Room Source # | |
Combine Extinction Source # | |
Defined in Markov.Examples combine :: Extinction -> Extinction -> Extinction Source # summarize :: NonEmpty Extinction -> Extinction Source # | |
Num a => Combine (Product a) Source # | |
Combine (Sum a) Source # | |
Combine (Merge a) Source # | |
(Combine a, Combine b) => Combine (a, b) Source # | |
(Combine a, Combine b, Combine c) => Combine (a, b, c) Source # | |
Values from a Monoid
which have the respective
binary operation applied each step.
E.g., strings with concatenation.
Merge a |
Instances
Enum a => Enum (Merge a) Source # | |
Eq a => Eq (Merge a) Source # | |
Fractional a => Fractional (Merge a) Source # | |
Num a => Num (Merge a) Source # | |
Show a => Show (Merge a) Source # | |
Generic (Merge a) Source # | |
Semigroup a => Semigroup (Merge a) Source # | |
Monoid a => Monoid (Merge a) Source # | |
Grouping a => Grouping (Merge a) Source # | |
Combine (Merge a) Source # | |
MultiMarkov ((Product Rational :* Merge String) :* Room) Source # | |
Defined in Markov.Examples multiTransition :: ((Product Rational :* Merge String) :* Room) -> [((Product Rational :* Merge String) :* Room) -> [(Product Rational :* Merge String) :* Room]] Source # multiStep :: ((Product Rational :* Merge String) :* Room) -> [(Product Rational :* Merge String) :* Room] Source # multiChain :: [(Product Rational :* Merge String) :* Room] -> [[(Product Rational :* Merge String) :* Room]] Source # | |
type Rep (Merge a) Source # | |
Values which are added each step. E.g., number of times a red ball is picked from an urn.
Sum a |
Instances
Values which are multiplied each step, and combined additively for equal states. E.g., probabilities.
Product a |
Instances
Misc
(>*<) :: a -> b -> a :* b infixl 5 Source #
Easier way to write nested 2-tuples,
since a >*< b >*< c >*< d
is much easier to read than
(((a,b),c),d)
.
Left associative, binds weaker than +
but stronger than ==
.
fromLists :: Eq b => [[a]] -> [b] -> b -> [(a, b -> b)] Source #
Create a transition function from a transition matrix. If [[a]] is an n x n matrix, length [b] should be n.