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

This module provides access PRISM, a Prolog-based probabilistic programming system. PRISM runs under B-Prolog, so this module provides ways to manage and communicate with a PRISM/B-Prolog child process.

Most of the flags that affect learning and inference are managed explicitly and statelessly by the relevant procedures. The states of switches (distributions and pseudocounts) must still be managed by the user, but they can easily be maniplated using sw_get/3 and sw_set/3.

Flags which are still effective statefully are:

  • flags to do with information and progress display
  • default parameters for switches
  • explanation graph housekeeping
  • sort_hindsight
  • log_scale affects explanation, viterbi and learning

Starting PRISM

?- use_module(library(prism)).
?- prism_start(path(prism),'prism.log').
?- #X is 2+2. % as PRISM - sanity check
?- load_prism('some_test_program.psm').
?- prism_show(_). % check prism.log for output

You may find it useful to run tail -f prism.log in a terminal to keep an eye on PRISMs output messages.

Types used in this module:

prism_goal   % a callable term
prism_state  % term describing state of PRISM
filename     % a literal absolute or relative filename
filespec     % path to file using search path mechanism.
To be done
- Add some sample PRISM programs and utilities.
 prism_start(+Exec:filespec, +LogFile:filename) is det
 prism_start(+LogFile:filename) is det
 prism_start is det
Start PRISM as a child process. Exec should be a standard filespec pointing to the PRISM executable. % Output from PRISM is recorded to LogFile. PRISM immediately runs bprepl.pl, which receives queries on stdin and replies on stdout. Any currently running PRISM % is closed first. If not supplied, executable is set to path(prism). If not supplied, log file is 'prism.log'.
 prism_is_running is semidet
Succeeds if an instance of prism is running.
 prism_restart is det
Restart the current PRISM process, which must be a child as created by prism_start/0 or prism_start/2. The current state is saved and restored to the new PRISM process.
 prism_recover is det
Try to restart from saved state if there is one. Recovery state can be saved from prism_restart/0 and prism_restore_state/1.
 prism_close is det
Close the current PRISM process.
 prism(Goal:prism_goal) is semidet
Submit query to PRISM process and get reply. Goal is a normal Prolog goal which submitted to PRISM. It is run as by once/1 and any bindings returned.
 prism_nd(Goal:prism_goal) is nondet
Submit nondeterministic query to PRISM. The goal in run in PRISM via findall/3. All the results are returned and retrieved on backtracking in this predicate.
 # Goal:prism_goal is semidet
Unary prefix operator, equivalent to prism/1.
 ##(Goal:prism_goal) is semidet
Unary prefix operator, equivalent to prism_nd/1.
 prism_state_get(-S:prism_state) is det
Get the current state of the PRISM system into a Prolog term S. Can be restored using prism_state_set/1.
 prism_state_set(+S:prism_state) is det
Set the current state of the PRISM system to that described in S. State can be obtained using prism_state_get/1 or prism_state/2.
 prism_dynamic(+Predicates) is det
Registers predicates as dynamic predicates in PRISM. These are then declared as dynamic automatically whenever PRISM is started.
 load_bprolog(+Name:filename) is det
Compile and link a B-Prolog source file.
 load_prism(+Name:filespec, +Opts:list(oneof([neg]))) is det
 load_prism(+Name:filespec) is det
Compile and link a PRISM source file. If file extension is ommitted, then '.psm' is assumed. There is only one option currently: if neg is included in the option list, the program is assumed to include negation a failure predicate, and is loaded via prismn/1.
 sw_values(+S:switch(A), -V:list(A)) is semidet
sw_values(-S:switch(A), -V:list(A)) is nondet
True when S is a registered switch and V is its list of values.
 sw_get(+PType:param_type, +S:switch, -I:switch_params) is semidet
sw_get(-PType:param_type, -S:switch, -I:switch_params) is nondet
Gets information on probability distribution or pseudocounts for a switch. Fails if the switch parameters are unset.
 sw_set(+PType:param_type, +S:switch, +H:switch_params) is det
Set a switch's parameters depending on PType.
 sw_fix(+PType:param_type, S:switch) is det
Fixes the distribution or pseudocounts for the named switch. This prevents the setting from changing during learning.
 sw_unfix(+PType:param_type, S:switch) is det
Unfixes the distribution or pseudocounts for the named switch. This allows the setting to change during learning.
 sw_set_to_mean(+S:switch) is det
 sw_set_to_mean(+S:switch, +Offset:float) is det
Sets a switch's distribution to the mean of the Dirichlet distribution whose parameters come from the current 'counts' setting of the switch. Off, if present, is added to all the pseudocounts. Also sets the probabilities' 'fixed' states to match that of the pseudocounts.
 sw_set_to_sample(+S:switch) is det
 sw_set_to_sample(+S:switch, Offset:float) is det
Sample a new discrete distribution for a switch's parameters from a Dirichlet distribution whose parameters come from the current 'counts' setting of the switch. Off, if present, is added to all the pseudocounts. This uses the undocumented sample_Dirichlet/5 predicate from library(plrand).
 prism_sample(Goal:prism_goal) is semidet
Sample from distribution specified by PRISM goal.
 prism_sample_n(+N:nat, Goal:cond_goal, Results:list(prism_goal)) is det
Multiple samples from distribution specified by PRISM goal. Goal can be an ordinary PRISM goal or a conditional goal of the form (Goal|Cond), where Cond is an ordinary Prolog goal. Returns a list of copies of the called goal with return values filled in.
 prob(Goal:prism_goal, -P:float) is det
Compute probability of given goal.
 explain(Goal:prism_goal, -Graph) is det
Gets explanation graph for given goal.
 explain_probs(+Type:oneof([inside,outside,viterbi,in_out]), Goal:prism_goal, -Graph) is det
Gets explanation graph annoted with probabilities for given goal. The explanation types map to a PRISM commands as follows:
 hindsight(TopGoal:prism_goal, SubGoal:prism_goal, -Probs:list(pair(prism_goal,float))) is nondet
Computes probabilities of subgoals unifying with SubGoal for a given top goal. Matches different subgoals on backtracking. hindsight(Q,R,P) :- prism(hindsight(Q,R,P1)), maplist(list_pair,P1,P).
 hindsight_agg(TopGoal:prism_goal, SubGoal:prism_goal, -Probs:list(list(pair(prism_goal,float)))) is det
Computes total probability of all subgoals unifying with SubGoal for a given top goal. NB. this functionality can be replicated in a more idiomatic way using hindsight/3 and SWI Prolog's library(aggregate).
 chindsight(TopGoal:prism_goal, SubGoal:prism_goal, -Probs:list(pair(prism_goal,float))) is nondet
Computes conditional probabilities of matching subgoals given that the top goal is true. Same as hindsight/3 but with probabilities divided by the probabality of the top goal. chindsight(Q,R,P) :- prism(chindsight(Q,R,P1)), maplist(list_pair,P1,P).
 chindsight_agg(TopGoal:prism_goal, SubGoal:prism_goal, -Probs:list(list(pair(prism_goal,float)))) is det
Computes aggregate conditional probability of matching subgoals given that the top goal is true. Same as chindsight_agg/3 but with probabilities divided by the probabality of the top goal. NB. this functionality can be replicated in a more idiomatic way using hindsight/3 and SWI Prolog's library(aggregate).
 viterbi(+N:nat, Goal:prism_goal, -P:float, +Opts:list(viterbi_opt)) is nondet
Compute probabilities of N most probable explanation for Goal. Options can be as follows:
viterbi_opt ---> ground(bool)        % [false] whether or not to ground variable in Goal
               ; mode(oneof([ml,vb]) % [ml]  use probs (ml) or counts (vb)
               ; rerank(nat)         % [10]  number of explanations for reranking
               .
 viterbi_expl(+N:nat, Goal:prism_goal, -P:float, +Opts:list(viterbi_opt), -G:graph) is nondet
Compute probabilities of N most probable explanation for Goal and also produce graphs for each. See viterbi/4 for options.
 viterbi_tree(+N:nat, Goal:prism_goal, -P:float, +Opts:list(viterbi_opt), -T:tree) is nondet
Compute probabilities of N most probable explanation for Goal, as viterbi_expl/5, but produce a tree instead of a graph by using viterbi_graph_to_tree/2. also produce tree for each. See viterbi/4 for options.
 viterbi_graph_to_tree(+G:graph, -T:tree) is det
Computes Viterbi tree for a given Viterbi explanation graph. Graph comes from one of the viterbi or n_viterbi predicates.
 print_graph(+G:graph) is det
Prints an explanation graph on PRISM's user output stream.
 print_tree(+G:tree) is det
Prints a Viterbi tree PRISM's user output stream.
 prism_learn(+Method:learn_method, +GG:list(goal), +Opts:list(learn_opt), -Scores:list(learn_score)) is det
Learn model parameters from a list of goals.
 learn_method ---> map(Init:oneof([none,random,noisy(Std)]))
                 ; vb(Init:oneof([none,perturb(Std),reset,noisy(Std),Pt:oneof([on,off]))
                 ; vb_pm(Init:oneof([none,perturb(Std),reset,noisy(Std))
                 .

For MAP learning, the Init option determines how switch probabilities are initialised; the values have the following meanings:

none
Switch probabilities begin with their current values.
random
Probabilities are set to random values
noisy(Std:nonneg)
Probabilities are drawn from rectified Gaussian with given standard deviation.

For VB learning, initialisation methods are as follows

none
Learning continues from current pseudocounts (ie evidence accumulates).
perturb(Std:nonneg)
Current values have rectified Gaussian noise added
reset
Hyperparameters are set to value of default_sw_a flag.
noisy(Std:nonneg)
Hyperparameters are set to value of default_sw_a plus some noise.

Method vb_pm is like vb except that switch parameters are set to their posterior means after learning.

Valid options are (with defaults in comments):

 learn_opt ---> daem(oneof([off,sched(Init,Rate)])) % on
              ; epsilon(nonneg)                     % 0.0001
              ; max_iterate(nonneg)                 % default
              ; restart(natural)                    % 1
              .

 learn_score ---> log_prior(float)    % only for map learning
                ; log_post(float)     % only for map learning
                ; log_lik(float)
                ; free_energy(float)  % only for VB learning
                .
 prism_flag_set(+Name:flag(A), +Value:A) is det
Set value of the named PRISM flag.
 prism_flag_get(+Name:flag(A), -Value:A) is det
prism_flag_get(-Name:flag(A), -Value:A) is nondet
Get value of the named PRISM flag or of all flags in turn.
 prism_flag(+Name:flag(A), -A:type, -Description) is det
prism_flag(?Name:flag(A), ?A:type, ?Description) is nondet
Contains information about all the PRISM flags.
 prism_flag_affects(-Name:flag(_), -Subsystem) is nondet
Relation between flag names and the subsytem affected, which can be one of display, initialisation (of switches), explanation, vitberbi, hindsight or learning.
 prism_show(+Subsystem:oneof([values,probs,counts,goals,flags])) is det
prism_show(-Subsystem:oneof([values,probs,counts,goals,flags,stats])) is nondet
Causes PRISM to print information to its output stream. By default, this appears in a file 'prism.log' in the directory where PRISM was started.
 prism_statistics(+StatName, -Value) is semidet
prism_statistics(-StatName, -Value) is nondet
Get values of various statistics on inference, learning, and the explanation graph.
 prism_statistics(+Subsytem, +StatName, -Value) is semidet
prism_statistics(-Subsystem, -StatName, -Value) is nondet
Get values of various statistics on a PRISM subsytem, which can be one of infer, learn or graph.

Undocumented predicates

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

 prism_start
 prism_start(Arg1)
 load_prism(Arg1)
 sw_set_to_sample(Arg1, Arg2)
 sw_set_to_mean(Arg1, Arg2)