goal-probability-0.20: Optimization on manifolds of probability distributions with Goal
Safe HaskellNone
LanguageHaskell2010

Goal.Probability.Conditional

Description

Statistical models where the observations depend on known conditions.

Synopsis

Documentation

type SampleMap z x = Map (SamplePoint x) (Sample z) Source #

A synonym for Maps from Inputs to Outputs that matches the confusing, backwards style of Goal.

Markov Kernels

(>.>*) :: (Map Natural f y x, ExponentialFamily x) => (Natural # f y x) -> SamplePoint x -> Natural # y infix 8 Source #

Evalutes the given conditional distribution at a SamplePoint.

(>$>*) :: (Map Natural f y x, ExponentialFamily x) => (Natural # f y x) -> Sample x -> [Natural # y] infix 8 Source #

Mapped application of conditional distributions on a Sample.

(*<.<) :: (Map Natural f x y, Bilinear f y x, ExponentialFamily y) => SamplePoint y -> (Natural # f y x) -> Natural # x infix 8 Source #

Applies the transpose of a Bilinear Map to a SamplePoint.

(*<$<) :: (Map Natural f x y, Bilinear f y x, ExponentialFamily y) => Sample y -> (Natural # f y x) -> [Natural # x] infix 8 Source #

Mapped transpose application on a Sample.

Conditional Distributions

conditionalLogLikelihood Source #

Arguments

:: (ExponentialFamily x, Map Natural f y x, LogLikelihood Natural y t) 
=> [(t, SamplePoint x)]

Output/Input Pairs

-> (Natural # f y x)

Function

-> Double

conditional cross entropy estimate

The conditional logLikelihood for a conditional distribution.

conditionalLogLikelihoodDifferential Source #

Arguments

:: (ExponentialFamily x, LogLikelihood Natural y t, Propagate Natural f y x) 
=> [(t, SamplePoint x)]

Output/Input Pairs

-> (Natural # f y x)

Function

-> Mean # f y x

Differential

The conditional logLikelihoodDifferential for a conditional distribution.

conditionalDataMap Source #

Arguments

:: Ord x 
=> [(t, x)]

Output/Input Pairs

-> Map x [t]

Input Output map

Turns a list of input/output pairs into a Map, by collecting into lists the different outputs to each particular input.

kFoldMap :: Ord x => Int -> Map x [y] -> [(Map x [y], Map x [y])] Source #

Partition a conditional dataset into k > 1 (training,validation) pairs, where each dataset condition is partitioned to match its size.

kFoldMap' :: Ord x => Int -> Map x [y] -> [(Map x [y], Map x [y], Map x [y])] Source #

Partition a conditional dataset into k > 2 (training,test,validation) triplets, where each dataset condition is partitioned to match its size.

mapConditionalLogLikelihood Source #

Arguments

:: (ExponentialFamily x, Map Natural f y x, LogLikelihood Natural y t) 
=> Map (SamplePoint x) [t]

Output/Input Pairs

-> (Natural # f y x)

Function

-> Double

conditional cross entropy estimate

The conditional logLikelihood for a conditional distribution, where redundant conditions/inputs are combined. This can dramatically increase performance when the number of distinct conditions/inputs is small.

mapConditionalLogLikelihoodDifferential Source #

Arguments

:: (ExponentialFamily x, LogLikelihood Natural y t, Propagate Natural f y x, Ord (SamplePoint x)) 
=> Map (SamplePoint x) [t]

Output/Input Pairs

-> (Natural # f y x)

Function

-> Mean # f y x

Differential

The conditional logLikelihoodDifferential, where redundant conditions are combined. This can dramatically increase performance when the number of distinct conditions is small.

parMapConditionalLogLikelihood Source #

Arguments

:: (ExponentialFamily x, Map Natural f y x, LogLikelihood Natural y t) 
=> Map (SamplePoint x) [t]

Output/Input Pairs

-> (Natural # f y x)

Function

-> Double

conditional cross entropy estimate

The conditional logLikelihood for a conditional distribution, where redundant conditions/inputs are combined. This can dramatically increase performance when the number of distinct conditions/inputs is small.

parMapConditionalLogLikelihoodDifferential Source #

Arguments

:: (ExponentialFamily x, LogLikelihood Natural y t, Propagate Natural f y x, Ord (SamplePoint x)) 
=> Map (SamplePoint x) [t]

Output/Input Pairs

-> (Natural # f y x)

Function

-> Mean # f y x

Differential

The conditional logLikelihoodDifferential, where redundant conditions are combined. This can dramatically increase performance when the number of distinct conditions is small.