Copyright | (c) Armando Santos 2019-2020 |
---|---|
Maintainer | armandoifsantos@gmail.com |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
LAoP is a library for algebraic (inductive) construction and manipulation of matrices in Haskell. See my Msc Thesis for the motivation behind the library, the underlying theory, and implementation details.
This module exports a type synonym Dist
that represents a stochastic distribution
matrix and several distribution construction
functions.
Synopsis
- newtype Dist a = D (Matrix Prob () a)
- type Prob = Double
- type Countable a = KnownNat (Count a)
- type CountableN a = KnownNat (Count (Normalize a))
- type CountableDimensionsN a b = (CountableN a, CountableN b)
- type FromListsN a b = FromLists Prob (Normalize a) (Normalize b)
- type Liftable a b = (Bounded a, Bounded b, Enum a, Enum b, Eq b, Num Prob, Ord Prob)
- type TrivialP a b = Normalize (a, b) ~ Normalize (Normalize a, Normalize b)
- type TrivialE a b = Normalize (Either a b) ~ Either (Normalize a) (Normalize b)
- fmapD :: (Liftable a b, CountableDimensionsN a b, FromListsN b a) => (a -> b) -> Dist a -> Dist b
- unitD :: Dist ()
- multD :: (CountableDimensionsN a b, CountableN (a, b), FromListsN (a, b) a, FromListsN (a, b) b, TrivialP a b) => Dist a -> Dist b -> Dist (a, b)
- selectD :: (TrivialE a b, FromListsN b b, CountableN b) => Dist (Either a b) -> Matrix Prob a b -> Dist b
- returnD :: forall a. (Enum a, FromListsN () a, Countable a) => a -> Dist a
- bindD :: Dist a -> Matrix Prob a b -> Dist b
- choose :: FromListsN () a => Prob -> Dist a
- shape :: FromListsN () a => (Prob -> Prob) -> [a] -> Dist a
- linear :: FromListsN () a => [a] -> Dist a
- uniform :: FromListsN () a => [a] -> Dist a
- negExp :: FromListsN () a => [a] -> Dist a
- normal :: FromListsN () a => [a] -> Dist a
- toValues :: forall a. (Enum a, Countable a, FromListsN () a) => Dist a -> [(a, Prob)]
- prettyDist :: forall a. (Show a, Enum a, Countable a, FromListsN () a) => Dist a -> String
- prettyPrintDist :: forall a. (Show a, Enum a, Countable a, FromListsN () a) => Dist a -> IO ()
Documentation
If the sum of the rows of a column matrix is equal to 1 then this stochastic matrix can be seen as a probability distribution.
This module is still experimental but it's
already possible to model probabilistic programming
problems with it. Import Nat
or Type
to access LAoP matrix combinators and then all you have
to do is to define your sample space, either by creating a new data
type or by abstracting it out via Natural
.
Write manipulation functions and promote them to matrices via
fromF
or fromF'
and you're good to go!
Dist
and Prob
type synonyms
Type synonym for column vector matrices. This represents a probability distribution.
Constraint type synonyms
type Countable a = KnownNat (Count a) Source #
Constraint type synonyms to keep the type signatures less convoluted
type CountableDimensionsN a b = (CountableN a, CountableN b) Source #
Functor instance equivalent functions
fmapD :: (Liftable a b, CountableDimensionsN a b, FromListsN b a) => (a -> b) -> Dist a -> Dist b Source #
Functor instance
Applicative equivalent functions
multD :: (CountableDimensionsN a b, CountableN (a, b), FromListsN (a, b) a, FromListsN (a, b) b, TrivialP a b) => Dist a -> Dist b -> Dist (a, b) Source #
Applicative/Monoidal instance mult
function
Selective equivalent functions
selectD :: (TrivialE a b, FromListsN b b, CountableN b) => Dist (Either a b) -> Matrix Prob a b -> Dist b Source #
Selective instance function
Monad equivalent functions
returnD :: forall a. (Enum a, FromListsN () a, Countable a) => a -> Dist a Source #
Monad instance return
function
Distribution construction functions
shape :: FromListsN () a => (Prob -> Prob) -> [a] -> Dist a Source #
Creates a distribution given a shape function
linear :: FromListsN () a => [a] -> Dist a Source #
Constructs a Linear distribution
uniform :: FromListsN () a => [a] -> Dist a Source #
Constructs an Uniform distribution
negExp :: FromListsN () a => [a] -> Dist a Source #
Constructs an Negative Exponential distribution
normal :: FromListsN () a => [a] -> Dist a Source #
Constructs an Normal distribution
Converto to list of pairs
toValues :: forall a. (Enum a, Countable a, FromListsN () a) => Dist a -> [(a, Prob)] Source #
Transforms a Dist
into a list of pairs.
Pretty print distribution
prettyDist :: forall a. (Show a, Enum a, Countable a, FromListsN () a) => Dist a -> String Source #
Pretty a distribution
prettyPrintDist :: forall a. (Show a, Enum a, Countable a, FromListsN () a) => Dist a -> IO () Source #
Pretty Print a distribution