hbayes-0.5.2: Bayesian Networks

Safe HaskellNone
LanguageHaskell2010

Bayes

Contents

Description

Bayesian Network Library.

It is a very preliminary version. It has only been tested on very simple examples where it worked. It should be considered as experimental and not used in any production work.

Synopsis

Graph

Graph classes

class Graph g where Source

Graph class used for graph processing algorithms. A graph processing algorithm does not have to know how the graph is implemented nor if it is directed or undirected

Methods

addVertex :: Vertex -> b -> g a b -> g a b Source

Add a new vertex

removeVertex :: Vertex -> g a b -> g a b Source

Remove a vertex

vertexValue :: g a b -> Vertex -> Maybe b Source

Get the vertex value if the vertex is found in the graph

changeVertexValue :: Vertex -> b -> g a b -> Maybe (g a b) Source

Change the vertex value if the vertex is found in the graph

someVertex :: g a b -> Maybe Vertex Source

Generate a "random" vertex

hasNoVertices :: g a b -> Bool Source

Check is the graph has no vertrex

allVertices :: g a b -> [Vertex] Source

Generate all vertices

allVertexValues :: g a b -> [b] Source

Get all the values

allNodes :: g a b -> [(Vertex, b)] Source

Get all nodes

isLinkedWithAnEdge :: g a b -> Vertex -> Vertex -> Bool Source

Check if two vertices are linked by a vertex

addEdge :: Edge -> a -> g a b -> g a b Source

Add an edge

removeEdge :: Edge -> g a b -> g a b Source

Remove an dedge

edgeVertices :: g a b -> Edge -> Maybe (Vertex, Vertex) Source

Vertices for an edge

edgeValue :: g a b -> Edge -> Maybe a Source

Edge value if the edge is found in the graph

someEdge :: g a b -> Maybe Edge Source

Return a "random" edge

hasNoEdges :: g a b -> Bool Source

Check if the graph has no edges

endVertex :: g a b -> Edge -> Maybe Vertex Source

One extremity of the edge (which is the end only for directed edge)

startVertex :: g a b -> Edge -> Maybe Vertex Source

One extremity of the edge (which is the start only for directed edge)

allEdges :: g a b -> [Edge] Source

All edges of the graph

allEdgeValues :: g a b -> [a] Source

All values of the graph

emptyGraph :: g a b Source

Returns an empty graph

isEmpty :: g a b -> Bool Source

Check if the graph is empty

oriented :: g a b -> Bool Source

Check if the graph is oriented

neighbors :: g a b -> Vertex -> Maybe [Vertex] Source

All the neighbors of a vertex

Instances

Graph UndirectedSG Source

SimpleGraph is an instance of Graph.

Graph DirectedSG Source

SimpleGraph is an instance of Graph.

class Graph g => UndirectedGraph g where Source

Undirected graph

Methods

edges :: g a b -> Vertex -> Maybe [Edge] Source

class Graph g => DirectedGraph g where Source

Directed graph

Methods

ingoing :: g a b -> Vertex -> Maybe [Edge] Source

outgoing :: g a b -> Vertex -> Maybe [Edge] Source

class FoldableWithVertex g where Source

The foldable class is limited. For a graph g we may need the vertex in addition to the value

Methods

foldrWithVertex :: (Vertex -> a -> b -> b) -> b -> g c a -> b Source

Fold with vertex

foldlWithVertex' :: (b -> Vertex -> a -> b) -> b -> g c a -> b Source

class FunctorWithVertex g where Source

Methods

fmapWithVertex :: (Vertex -> a -> b) -> g c a -> g c b Source

fmapWithVertexM :: Monad m => (Vertex -> a -> m b) -> g c a -> m (g c b) Source

class Graph g => NamedGraph g where Source

A named graph is a graph where the vertices have a name. This name is not a vertex value. Putting this name in the vertex value would make algorithm less readable. A vertex name is only useful to display the graph. Labeled graph has a different meaning in graph theory.

Methods

addLabeledVertex :: String -> Vertex -> b -> g a b -> g a b Source

Add a vertex with a vertex name in addition to the value

vertexLabel :: g a b -> Vertex -> Maybe String Source

Returns the vertex label

Graph Monad

data GraphMonad g e f a Source

Graph monad. The monad used to simplify the description of a new graph g is the graph type. e the edge type. f the node type (generally a Factor)

type GMState g e f = (AuxiliaryState, g e f) Source

The state of the graph monad : the graph and auxiliary data useful during the construction

graphNode :: NamedGraph g => String -> f -> GraphMonad g e f Vertex Source

Add a node in the graph using the graph monad

runGraph :: Graph g => GraphMonad g e f a -> (a, g e f) Source

execGraph :: Graph g => GraphMonad g e f a -> g e f Source

evalGraph :: Graph g => GraphMonad g e f a -> a Source

getNewEmptyVariable :: NamedGraph g => Maybe String -> f -> GraphMonad g e f Vertex Source

Generate a new unique unamed empty variable

isRoot :: DirectedGraph g => g a b -> Vertex -> Bool Source

rootNode :: DirectedGraph g => g a b -> Maybe Vertex Source

Get the root node for the graph

parentNodes :: DirectedGraph g => g a b -> Vertex -> [Vertex] Source

Return the parents of a node

childrenNodes :: DirectedGraph g => g a b -> Vertex -> [Vertex] Source

Return the children of a node

markovBlanket :: DirectedGraph g => g a b -> Vertex -> [Vertex] Source

Return the Markov blanket of a node

Support functions for Graph constructions

data Vertex Source

Vertex type used to identify a vertex in a graph

data Edge Source

Edge type used to identify and edge in a graph

edge :: Vertex -> Vertex -> Edge Source

Create an edge description

newEdge :: Graph g => Vertex -> Vertex -> e -> GraphMonad g e f () Source

Add a new labeled edge to the graph

getVertex :: Graph g => String -> GraphMonad g e f (Maybe Vertex) Source

Get a named vertex from the graph monad

edgeEndPoints :: Edge -> (Vertex, Vertex) Source

Endpoints of an edge

connectedGraph :: Graph g => g a b -> Bool Source

Check if the graph is connected

dag :: DirectedGraph g => g a b -> Bool Source

Check if the graph is a directed Acyclic graph

printGraphValues :: (Graph (SimpleGraph n), Show b) => SimpleGraph n e b -> IO () Source

Print the values of the graph vertices

SimpleGraph implementation

The SimpleGraph type

type DirectedSG = SimpleGraph DE Source

Directed simple graph

type UndirectedSG = SimpleGraph UE Source

Undirected simple graph

type SBN f = DirectedSG () f Source

An implementation of the BayesianNetwork using the simple graph and no value for the edges

varMap :: SimpleGraph n e v -> Map String Vertex Source

Get the variable name mapping

displaySimpleGraph :: (Vertex -> n -> Maybe String) -> (Vertex -> n -> Maybe String) -> (Edge -> e -> Maybe String) -> (Edge -> e -> Maybe String) -> SimpleGraph local e n -> String Source

Bayesian network

type BayesianNetwork g f = g () f Source

Bayesian network. g must be a directed graph and f a factor

Testing