Did you know ... Search Documentation:
Pack pha -- prolog/pha.pl
PublicShow source

This is a more or less complete reimplementation of David Poole's probabilistic Horn abudction.

The mechanism for declaring and using random variables has been changed. Instead of using disjoint declarations in the PHA program file, you should use rv declarations, which look like this:

rv( RVTerm, [ Prob1:Value1, Prob2:Value2, ...].

Where RVTerm is an arbitrary term idenitfying the random variable, possibly using variables to stand for parameters of the random variable, and Value1, Value2 etc are arbitrary terms which can only contain variables that are in RVTerm. You can also compute the distribution for an RV using an ordinary Prolog clause, eg

rv( uniform(N), Dist) :- P is 1/N, findall(P:V, between(1,N,V), Dist).

Then, to query an random variable, use

RVTerm := Value

RVTerm must be a ground term unifying with one of the random variables, and Value can be non-ground. This makes is much harder to go wrong with variables and use of functors in assumable hypotheses.

Types

In the following, rv(A) and head are not formally defined. Syntactically, they are abitrary terms. A term of type rv(A) denotes the name of random variable as found in the first argument of an rv/2 declartion and whose values are of type A. Then, an assumption is an assertion about the value of a random variable, so

assumption ---> rv(A) := A.

A head is any term that is found in the head position in the rule database. The type goal is a supertype of assumption and head and can be defined syntactically by the following predicate:

goal(X) :- rv(X,_); rule(X,_).
goal((X,Y)) :- goal(X), goal(Y).
goal(true).

A program in the object language consists of a sequence of statements, where

rv_head(A) ---> rv( rv(A), list(weighted(A))).
statement ---> rv( rv(A), list(weighted(A)))
             ; (rv_head(A) :- prolog_body)
             ; (head :- goal)
             ; head.

Usage

To load a model, use load(FileSpec), where Spec is a file specification using the SWI Prolog's file search path mechanism. An extension of 'pha' is assumed.

To get an interactive shell to work with a model, you can use run_belief/1 with dcgshell as the command: this gives you a stateful top-level, where the state is managed by a DCG and the commands are interpreted as DCG goals. The DCG goal load//1 is available for loading models in the belief DCG.

?- use_module(library(dcg_shell)).
?- run_belief(dcgshell).
user: call_dcg (dcg) >> load(pack(pha/models/alarm)).

At this point, you can now declare observations in the form of PHA goals which are known to be true. The system computes the possible explanations for these observations and their probabilities. Observations are cumulative. For example:

user: call_dcg (dcg) >> prob(fire(yes),P).
user: call_dcg (dcg) >> prob(fire(yes)|smoke(yes),P).
user: call_dcg (dcg) >> observe(alarm(yes)).
user: call_dcg (dcg) >> prob(fire(yes),P).
user: call_dcg (dcg) >> explain(fire(yes)).
 run_belief(+P:phrase(belief_stack)) is det
Starts a DCG shell with an empty belief stack, then runs the given DCG command.
 load(+F:FileSpec)// is det
Clears old program, loads new one, and removes all observations.
 observe(+G:goal)// is det
Adds a new observation.
 unobserve// is semidet
Removes the last observation, fails if only nil belief is left.
 unobserve_all// is det
Removes all observations.
 goals// is det
Prints all the observations on the stack, latest first.
 prob(+G:goal, -P:interval)// is det
Computes the probabilty (to within default tolerance) of Goal given all observations, or if Goal = G1 | G2, temporarily adds G2 as an observation before computing the probability of G1.
 joint(+Tol:tolerance, -P:interval(prob))// is semidet
 joint(-P:interval(prob))// is semidet
Computes an approximation to the joint probability of all the observations so far.
 explanations(+Epsilon:prob)// is det
Prints enough explanations of the current observations to account for all but Epsilon of the probability mass.
 explanation(-Ex:explanation)// is nondet
Unifies Ex with an explanation for all observations, finds other explanations on backtracking.
 explain(+G:goal)// is nondet
Prints an explanation for G given the observations so far. Produces other explanations on backtracking.

Undocumented predicates

The following predicates are exported, but not or incorrectly documented.

 joint(Arg1, Arg2, Arg3)
 load(Arg1)
 edit(Arg1, Arg2)