Maintainer | atloomis@math.arizona.edu |
---|---|
Stability | Experimental |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- class Eq m => Markov0 m where
- transition0 :: m -> [m -> m]
- step0 :: m -> [m]
- chain0 :: Markov0 m => [m] -> [[m]]
- class (Applicative t, Comonad t) => Markov t m where
- transition :: m -> [t (m -> m)]
- step :: t m -> [t m]
- sequential :: [m -> [t (m -> m)]]
- chain :: (Combine (t m), Grouping (t m), Markov t m) => [t m] -> [[t m]]
- class Combine a where
- newtype Merge a = Merge a
- newtype Sum a = Sum a
- newtype Product a = Product a
Markov0
Markov
class (Applicative t, Comonad t) => Markov t m where Source #
An implementation of Markov chains.
transition | step | sequential
transition :: m -> [t (m -> m)] Source #
sequential :: [m -> [t (m -> m)]] Source #
Instances
Markov ((,) (Product Rational, Merge String)) Room Source # | |
Markov ((,) (Sum Int, Product Rational)) Extinction Source # | |
Defined in Markov.Example transition :: Extinction -> [((Sum Int, Product Rational), Extinction -> Extinction)] Source # step :: ((Sum Int, Product Rational), Extinction) -> [((Sum Int, Product Rational), Extinction)] Source # sequential :: [Extinction -> [((Sum Int, Product Rational), Extinction -> Extinction)]] Source # | |
Markov ((,) (Product Double)) FillBin Source # | |
Markov ((,) (Product Double)) Tidal Source # | |
Markov ((,) (Product Double)) Urn Source # | |
Markov ((,) (Product Double)) Simple Source # | |
Markov ((,) (Product Double)) FromLists Source # | |
Markov ((,) (Product Int)) Simple Source # | |
Markov ((,) (Sum Int)) Simple 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 FillBin Source # | |
Combine Room Source # | |
Combine Tidal Source # | |
Combine Extinction Source # | |
Defined in Markov.Example combine :: Extinction -> Extinction -> Extinction Source # summarize :: NonEmpty Extinction -> Extinction Source # | |
Combine Urn Source # | |
Combine Simple Source # | |
Combine FromLists 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,
where different values mean states should not be combined.
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 # | |
Markov ((,) (Product Rational, Merge String)) Room Source # | |
type Rep (Merge a) Source # | |
Values which are added each step where different values mean states should not be combined. E.g., number of times a red ball is picked from an urn.
Sum a |
Instances
Enum a => Enum (Sum a) Source # | |
Eq a => Eq (Sum a) Source # | |
Fractional a => Fractional (Sum a) Source # | |
Num a => Num (Sum a) Source # | |
Show a => Show (Sum a) Source # | |
Generic (Sum a) Source # | |
Num a => Semigroup (Sum a) Source # | |
Num a => Monoid (Sum a) Source # | |
Grouping a => Grouping (Sum a) Source # | |
Combine (Sum a) Source # | |
Markov ((,) (Sum Int, Product Rational)) Extinction Source # | |
Defined in Markov.Example transition :: Extinction -> [((Sum Int, Product Rational), Extinction -> Extinction)] Source # step :: ((Sum Int, Product Rational), Extinction) -> [((Sum Int, Product Rational), Extinction)] Source # sequential :: [Extinction -> [((Sum Int, Product Rational), Extinction -> Extinction)]] Source # | |
Markov ((,) (Sum Int)) Simple Source # | |
type Rep (Sum a) Source # | |
Values which are multiplied each step, and combined additively for equal states. E.g., probabilities.
Product a |