hbayes-0.5.2: Bayesian Networks

Safe HaskellNone
LanguageHaskell2010

Bayes.Factor

Contents

Description

Factors

Synopsis

Factor

class Factor f where Source

A factor as used in graphical model It may or not be a probability distribution. So it has no reason to be normalized to 1

Methods

isScalarFactor :: f -> Bool Source

When all variables of a factor have been summed out, we have a scalar

emptyFactor :: f Source

An empty factor with no variable and no values

containsVariable :: f -> DV -> Bool Source

Check if a given discrete variable is contained in a factor

factorVariables :: f -> [DV] Source

Give the set of discrete variables used by the factor

factorMainVariable :: f -> DV Source

Return A in P(A | C D ...). It is making sense only if the factor is a conditional propbability table. It must always be in the vertex corresponding to A in the bayesian graph

factorWithVariables :: [DV] -> [Double] -> Maybe f Source

Create a new factors with given set of variables and a list of value for initialization. The creation may fail if the number of values is not coherent with the variables and their levels. For boolean variables ABC, the value must be given in order FFF, FFT, FTF, FTT ...

factorValue :: f -> [DVI] -> Double Source

Value of factor for a given set of variable instantitation. The variable instantion is like a multi-dimensional index.

factorStringValue :: f -> [DVI] -> String Source

String representation of a factor value

variablePosition :: f -> DV -> Maybe Int Source

Position of a discrete variable in te factor (p(AB) is differennt from p(BA) since values are not organized in same order in memory)

factorDimension :: f -> Int Source

Dimension of the factor (number of floating point values)

factorNorm :: f -> Double Source

Norm of the factor = sum of its values

factorScale :: Double -> f -> f Source

Scale the factor values by a given scaling factor

factorFromScalar :: Double -> f Source

Create a scalar factor with no variables

evidenceFrom :: [DVI] -> Maybe f Source

Create an evidence factor from an instantiation. If the instantiation is empty then we get nothing

isUsingSameVariablesAs :: f -> f -> Bool Source

Test if two factors are coding for the same probability dependence. It does not test if the factors are equal (same probabilities) but just if they involve the same variables so are linked to the same node in the Bayesian network

factorDivide :: f -> Double -> f Source

Divide all the factor values

factorToList :: f -> [Double] Source

factorProduct :: [f] -> f Source

Multiply factors.

factorProjectOut :: [DV] -> f -> f Source

Project out a factor. The variable in the DVSet are summed out

factorProjectTo :: [DV] -> f -> f Source

Project to. The variable are kept and other variables are removed

class Distribution d where Source

A distribution which can be used to create a factor

Methods

createFactor :: Factor f => [DV] -> d -> Maybe f Source

Create a factor from variables and a distributions for those variables

Instances

class MultiDimTable f where Source

Class used to display multidimensional tables

isomorphicFactor :: Factor f => f -> f -> Bool Source

Test equality of two factors taking into account the fact that the variables may be in a different order. In case there is a distinction between conditionned variable and conditionning variables (imposed from the exterior) then this comparison may not make sense. It is a comparison of function of several variables which no special interpretation of the meaning of the variables according to their position.

normedFactor :: Factor f => f -> f Source

Norm the factor

changeFactorInFunctor :: (Factor f, Functor m) => f -> m f -> m f Source

Change factor in a functor (only factor values should have been changed) It assumes that the variables of a factor are enough to identify it. If the functor is containing several factors with same set of variables then it won't give a meaningful result. So it should be used only on functor derived from a Bayesian Network.

class FactorContainer m where Source

Structure containing factors which can be replaced. It is making sense when the factors are related to the nodes of a Bayesian network.

Methods

changeFactor :: (IsBucketItem f, Factor f) => f -> m f -> m f Source

Instances

Set of variables

class Set s where Source

A Set of variables used in a factor. s is the set and a the variable

Methods

emptySet :: s a Source

Empty set

union :: Eq a => s a -> s a -> s a Source

Union of two sets

intersection :: Eq a => s a -> s a -> s a Source

Intersection of two sets

difference :: Eq a => s a -> s a -> s a Source

Difference of two sets

isEmpty :: s a -> Bool Source

Check if the set is empty

isElem :: Eq a => a -> s a -> Bool Source

Check if an element is member of the set

addElem :: Eq a => a -> s a -> s a Source

Add an element to the set

nbElements :: s a -> Int Source

Number of elements in the set

subset :: Eq a => s a -> s a -> Bool Source

Check if a set is subset of another one

equal :: Eq a => s a -> s a -> Bool Source

Check set equality

Instances

Set [] Source 

class BayesianVariable v => BayesianDiscreteVariable v where Source

A discrete variable has a number of levels which is required to size the factors

Methods

dimension :: v -> Int Source

dv :: v -> DV Source

class BayesianVariable v where Source

A Bayesian Variable is a variable part of Bayesian network and so which knows its position : the vertex.

Methods

vertex :: v -> Vertex Source

Implementation

newtype Vertex Source

Vertex type used to identify a vertex in a graph

Constructors

Vertex 

Fields

vertexId :: Int
 

Discrete variables and instantiations

data TDV s Source

A typed discrete variable

newtype DVSet s Source

A set of discrete variables The tag is used to check that an index is used with the right set of DV

Constructors

DVSet [DV] 

Instances

type DVISet = [DVI] Source

tdvi :: Enum s => DVI -> (TDV s, s) Source

Typed instantiation

tdv :: DV -> TDV s Source

Typed discrete variable

setDVValue :: DV -> Int -> DVI Source

Create a discrete variable instantiation for a given discrete variable

instantiationVariable :: DVI -> DV Source

Discrete variable from the instantiation

variableVertex :: LabeledVertex l => l -> Vertex Source

(=:) :: Instantiable d v r => d -> v -> r Source

Create a variable instantiation using values from an enumeration

forAllInstantiations :: DVSet s -> [[DVI]] Source

Generate all instantiations of variables The DVInt can be in any order so the tag s is not used

factorFromInstantiation :: Factor f => DVI -> f Source

Convert a variable instantation to a factor Useful to create evidence factors