Safe Haskell | None |
---|---|
Language | Haskell2010 |
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)
- 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 :: (FromListsN b b, CountableN b) => Dist (Either a b) -> Matrix Prob a b -> Dist b
- branchD :: (Num e, CountableDimensionsN a b, CountableDimensionsN c (Either b c), FromListsN c b, FromListsN a b, FromListsN a a, FromListsN b b, FromListsN c c, FromListsN b a, FromListsN b c, FromListsN (Either b c) b, FromListsN (Either b c) c) => Dist (Either a b) -> Matrix Prob a c -> Matrix Prob b c -> Dist c
- ifD :: (CountableDimensionsN a (Either () a), FromListsN a a, FromListsN a (), FromListsN () a, FromListsN (Either () a) a) => Dist Bool -> Dist a -> Dist a -> Dist a
- returnD :: forall a. (Enum a, FromListsN () a, Countable a) => a -> Dist a
- bindD :: Dist a -> Matrix Prob a b -> Dist b
- (??) :: (Enum a, Countable a, FromListsN () a) => (a -> Bool) -> Dist a -> Prob
- 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
Type synonym for column vector matrices. This represents a probability distribution.
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 #
fmapD :: (Liftable a b, CountableDimensionsN a b, FromListsN b a) => (a -> b) -> Dist a -> Dist b Source #
Functor instance
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
selectD :: (FromListsN b b, CountableN b) => Dist (Either a b) -> Matrix Prob a b -> Dist b Source #
Selective instance function
branchD :: (Num e, CountableDimensionsN a b, CountableDimensionsN c (Either b c), FromListsN c b, FromListsN a b, FromListsN a a, FromListsN b b, FromListsN c c, FromListsN b a, FromListsN b c, FromListsN (Either b c) b, FromListsN (Either b c) c) => Dist (Either a b) -> Matrix Prob a c -> Matrix Prob b c -> Dist c Source #
Chooses which of the two given effectful functions to apply to a given argument;
ifD :: (CountableDimensionsN a (Either () a), FromListsN a a, FromListsN a (), FromListsN () a, FromListsN (Either () a) a) => Dist Bool -> Dist a -> Dist a -> Dist a Source #
Branch on a Boolean value, skipping unnecessary computations.
returnD :: forall a. (Enum a, FromListsN () a, Countable a) => a -> Dist a Source #
Monad instance return
function
(??) :: (Enum a, Countable a, FromListsN () a) => (a -> Bool) -> Dist a -> Prob Source #
Extract probabilities given an Event.
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
toValues :: forall a. (Enum a, Countable a, FromListsN () a) => Dist a -> [(a, Prob)] Source #
Transforms a Dist
into a list of pairs.
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