goal-graphical-0.20: Optimization of latent variable and dynamical models with Goal
Safe HaskellNone
LanguageHaskell2010

Goal.Graphical.Models.Dynamic

Description

Statistical models where the observable biases depend on additional inputs.

Synopsis

Documentation

newtype LatentProcess f g y x z w Source #

A conditional Harmonium, where the observable biases of the Harmonium model depend on additional variables.

Constructors

LatentProcess (AffineHarmonium f y x z w, Affine g x w x) 

Instances

Instances details
(ConjugatedLikelihood g x x w w, Bilinear g x x, ConjugatedLikelihood f y x z w, Bilinear f y x, Map Natural g x x, Map Natural f x y, ExponentialFamily y, LegendreExponentialFamily z, LegendreExponentialFamily w) => ObservablyContinuous Natural (LatentProcess f g y x z w) Source # 
Instance details

Defined in Goal.Graphical.Models.Dynamic

Methods

logObservableDensities :: (Natural # LatentProcess f g y x z w) -> Observations (LatentProcess f g y x z w) -> [Double] Source #

observableDensities :: (Natural # LatentProcess f g y x z w) -> Observations (LatentProcess f g y x z w) -> [Double] Source #

(ExponentialFamily z, ExponentialFamily x, Map Natural f y x, Translation z y, Map Natural g x x, AbsolutelyContinuous Natural w, SamplePoint w ~ SamplePoint x, AbsolutelyContinuous Natural z, Translation w x) => AbsolutelyContinuous Natural (LatentProcess f g y x z w) Source # 
Instance details

Defined in Goal.Graphical.Models.Dynamic

Methods

logDensities :: Point Natural (LatentProcess f g y x z w) -> Sample (LatentProcess f g y x z w) -> [Double]

densities :: Point Natural (LatentProcess f g y x z w) -> Sample (LatentProcess f g y x z w) -> [Double]

(Manifold (AffineHarmonium f y x z w), Manifold (Affine g x w x)) => Manifold (LatentProcess f g y x z w) Source # 
Instance details

Defined in Goal.Graphical.Models.Dynamic

Associated Types

type Dimension (LatentProcess f g y x z w) :: Nat

(Manifold (AffineHarmonium f y x z w), Manifold (Affine g x w x)) => Product (LatentProcess f g y x z w) Source # 
Instance details

Defined in Goal.Graphical.Models.Dynamic

Associated Types

type First (LatentProcess f g y x z w)

type Second (LatentProcess f g y x z w)

Methods

join :: (c # First (LatentProcess f g y x z w)) -> (c # Second (LatentProcess f g y x z w)) -> c # LatentProcess f g y x z w

split :: (c # LatentProcess f g y x z w) -> (c # First (LatentProcess f g y x z w), c # Second (LatentProcess f g y x z w))

Manifold (LatentProcess f g y x z w) => Statistical (LatentProcess f g y x z w) Source # 
Instance details

Defined in Goal.Graphical.Models.Dynamic

Associated Types

type SamplePoint (LatentProcess f g y x z w)

(Manifold w, Manifold (g x x), Translation z y, Bilinear f y x) => Translation (LatentProcess f g y x z w) y Source # 
Instance details

Defined in Goal.Graphical.Models.Dynamic

Methods

(>+>) :: (c # LatentProcess f g y x z w) -> (c # y) -> c # LatentProcess f g y x z w

anchor :: (c # LatentProcess f g y x z w) -> c # y

type Dimension (LatentProcess f g y x z w) Source # 
Instance details

Defined in Goal.Graphical.Models.Dynamic

type Dimension (LatentProcess f g y x z w) = Dimension (AffineHarmonium f y x z w, Affine g x w x)
type First (LatentProcess f g y x z w) Source # 
Instance details

Defined in Goal.Graphical.Models.Dynamic

type First (LatentProcess f g y x z w) = First (AffineHarmonium f y x z w, Affine g x w x)
type Second (LatentProcess f g y x z w) Source # 
Instance details

Defined in Goal.Graphical.Models.Dynamic

type Second (LatentProcess f g y x z w) = Second (AffineHarmonium f y x z w, Affine g x w x)
type Observation (LatentProcess f g y x z w) Source # 
Instance details

Defined in Goal.Graphical.Models.Dynamic

type Observation (LatentProcess f g y x z w) = Sample z
type SamplePoint (LatentProcess f g y x z w) Source # 
Instance details

Defined in Goal.Graphical.Models.Dynamic

type SamplePoint (LatentProcess f g y x z w) = [SamplePoint (z, x)]

type HiddenMarkovModel n k = LatentProcess Tensor Tensor (Categorical n) (Categorical n) (Categorical k) (Categorical k) Source #

type SimpleKalmanFilter = LatentProcess Tensor Tensor NormalMean NormalMean Normal Normal Source #

type KalmanFilter n k = LatentProcess Tensor Tensor (MVNMean n) (MVNMean k) (MultivariateNormal n) (MultivariateNormal k) Source #

sampleLatentProcess :: (SamplePoint w ~ SamplePoint x, ExponentialFamily z, Translation w x, Translation z y, Map Natural g x x, ExponentialFamily x, Bilinear f x x, Generative Natural w, Generative Natural z, Bilinear g z x, Map Natural f y x) => Int -> (Natural # LatentProcess f g y x z w) -> Random (Sample (z, x)) Source #

Generate a realization of the observable and latent states from a given latent process.

Construction

joinLatentProcess :: (Manifold z, Manifold w, Manifold (f y x), Manifold (g x x)) => (c # w) -> (c # Affine f y z x) -> (c # Affine g x w x) -> c # LatentProcess f g y x z w Source #

Construct a LatentProcess from a prior, an emission distribution, and a transition distribution.

splitLatentProcess :: (Manifold z, Manifold w, Manifold (f y x), Manifold (g x x)) => (c # LatentProcess f g y x z w) -> (c # w, c # Affine f y z x, c # Affine g x w x) Source #

Split a LatentProcess into a prior, an emission distribution, and a transition distribution.

Inference

conjugatedFiltering :: (ConjugatedLikelihood g x x w w, Bilinear g x x, ConjugatedLikelihood f y x z w, Bilinear f y x, Map Natural g x x, Map Natural f x y) => (Natural # LatentProcess f g y x z w) -> Sample z -> [Natural # w] Source #

Filtering for latent processes based on conjugated distributions.

conjugatedSmoothing :: (ConjugatedLikelihood g x x w w, Bilinear g x x, ConjugatedLikelihood f y x z w, Bilinear f y x, Map Natural g x x, Map Natural f x y) => (Natural # LatentProcess f g y x z w) -> Sample z -> [Natural # w] Source #

Smoothing for latent processes based on conjugated distributions.

conjugatedSmoothing0 Source #

Arguments

:: (ConjugatedLikelihood g x x w w, Bilinear g x x, ConjugatedLikelihood f y x z w, Bilinear f y x, Map Natural g x x, Map Natural f x y) 
=> (Natural # w) 
-> (Natural # Affine f y z x)

Emission Distribution

-> (Natural # Affine g x w x)

Transition Distribution

-> Sample z 
-> ([Natural # w], [Natural # AffineHarmonium g x x w w]) 

A more low-level implementation of smoothing which also returns joint distributions over current and subsequent states.