maxent-learner-hw-0.2.0: Hayes and Wilson's maxent learning algorithm for phonotactic grammars.

Copyright© 2016-2017 George Steel and Peter Jurgec
LicenseGPL-2+
Maintainergeorge.steel@gmail.com
Safe HaskellNone
LanguageHaskell2010

Text.PhonotacticLearner.Util.Probability

Contents

Description

Data structures and functions for counting and probability.

Synopsis

Counting

newtype Multicount Source #

Monoid holding a list of integer counters which are summed independently

Constructors

MC 

Fields

Instances

getCounts :: Multicount -> [Int] Source #

Return the counts as a list of Ints

consMC :: Sum Int -> Multicount -> Multicount Source #

Add a new count to the head of the list

singleMC :: Sum Int -> Multicount Source #

Use a single coutner as a Multicount.

fromMC :: Multicount -> Vec Source #

Convert the counts to coordinates

Expectations

data Expectation v Source #

Expectation semiring as described by Eisner.

Represents an events contribution to the total expectation of a vector-valued variable. Addition takes the union of mutually exclusive events and multiplication either takes the intersection fo independent events or applies a conditional probability.

As a simple example, the expectation of the total value from rolling a 2 on a 6 sided die would be Exp (16) (26).

Constructors

Exp 

Fields

  • prob :: !Double

    Probability of event occuring.

  • exps :: !v

    Event's contribution to expectation of the variable

Instances

PackedDFA ExpDoubleDFST (Expectation Double) Source # 

Methods

numStates :: Ix sigma => ExpDoubleDFST sigma -> Int Source #

psegBounds :: Ix sigma => ExpDoubleDFST sigma -> (sigma, sigma) Source #

unpackDFA :: Ix sigma => ExpDoubleDFST sigma -> DFST Int sigma (Expectation Double) Source #

packDFA :: Ix sigma => Int16 -> Int16 -> (sigma, sigma) -> ((Int16, sigma) -> Int16) -> ((Int16, sigma) -> Expectation Double) -> (Int16 -> Expectation Double) -> ExpDoubleDFST sigma Source #

PackedDFA ExpVecDFST (Expectation Vec) Source # 

Methods

numStates :: Ix sigma => ExpVecDFST sigma -> Int Source #

psegBounds :: Ix sigma => ExpVecDFST sigma -> (sigma, sigma) Source #

unpackDFA :: Ix sigma => ExpVecDFST sigma -> DFST Int sigma (Expectation Vec) Source #

packDFA :: Ix sigma => Int16 -> Int16 -> (sigma, sigma) -> ((Int16, sigma) -> Int16) -> ((Int16, sigma) -> Expectation Vec) -> (Int16 -> Expectation Vec) -> ExpVecDFST sigma Source #

Eq v => Eq (Expectation v) Source # 
Show v => Show (Expectation v) Source # 
RingModule Double v => Semiring (Expectation v) Source # 
RingModule Double v => Additive (Expectation v) Source # 

normalizeExp :: RingModule Double v => Expectation v -> v Source #

Get the expectation conditional on the event actually occurring.

Sampling and Distributions

data Cdf a Source #

Cumulative distribution table that can be sampled easily.

Instances

Show a => Show (Cdf a) Source # 

Methods

showsPrec :: Int -> Cdf a -> ShowS #

show :: Cdf a -> String #

showList :: [Cdf a] -> ShowS #

massToCdf :: [(a, Double)] -> Cdf a Source #

Generate a CDF which from a list of outcomes and their relative probabilities (their sum will eb normalized and does not have to be 1).

sampleCdf :: (RandomGen g, MonadState g m) => Cdf a -> m a Source #

Sample a random variable according to a Cdf, gets the random generator state from the monad.

uniformSample :: Cdf a -> Int -> [(a, Int)] Source #

Deterministically sample n points spaced throughout the distribution. Used when the number of samples greatly outnumbers the number of outcomes.

upperConfidenceOE :: Double -> Double -> Double Source #

Get the upper confidence bound of Observed/Expected