From c369591fe4a5a33501343add6d940723c8e708e8 Mon Sep 17 00:00:00 2001 From: Fabrizio Riguzzi Date: Sun, 10 Dec 2023 21:14:53 +0100 Subject: [PATCH] new docs --- docs/gen_pldoc.pl | 43 ++- docs/pldoc/cplint_util.html | 169 ++++++++-- docs/pldoc/lemur.html | 544 +++++++++++++++++++++++--------- docs/pldoc/mcintyre.html | 343 ++++++++++++++++++-- docs/pldoc/pita.html | 602 ++++++++++++++++++++++++++++++------ docs/pldoc/slipcover.html | 288 +++++++++++++---- 6 files changed, 1619 insertions(+), 370 deletions(-) diff --git a/docs/gen_pldoc.pl b/docs/gen_pldoc.pl index 3dacf40..2c2e416 100644 --- a/docs/gen_pldoc.pl +++ b/docs/gen_pldoc.pl @@ -1,20 +1,29 @@ -:- consult('../prolog/cplint_util'). -:- consult('../prolog/pita'). -:- consult('../prolog/mcintyre'). -:- consult('../prolog/slipcover'). -:- consult('../prolog/viterbi'). -:- consult('../prolog/kbest'). -:- consult('../prolog/pitaind'). -:- consult('../prolog/lemur'). +:- use_module(library(pldoc)). +:- use_module(library(doc_files)). +:- use_module(library(filesex)). -:- doc_save('../prolog/pita.pl',[doc_root('./pldoc'),index_file(pita)]). -:- doc_save('../prolog/mcintyre.pl',[doc_root('./pldoc'),index_file(mcintyre)]). -:- doc_save('../prolog/slipcover.pl',[doc_root('./pldoc'),index_file(slipcover)]). -:- doc_save('../prolog/viterbi.pl',[doc_root('./pldoc'),index_file(viterbi)]). -:- doc_save('../prolog/cplint_util.pl',[doc_root('./pldoc'),index_file(cplint_util)]). -:- doc_save('../prolog/kbest.pl',[doc_root('./pldoc'),index_file(kbest)]). -:- doc_save('../prolog/pitaind.pl',[doc_root('./pldoc'),index_file(pitaind)]). -:- doc_save('../prolog/lemur.pl',[doc_root('./pldoc'),index_file(lemur)]). +:- initialization(gen_doc, main). +doc_file(cplint_util). +doc_file(pita). +doc_file(mcintyre). +doc_file(slipcover). +doc_file(viterbi). +doc_file(kbest). +doc_file(pitaind). +doc_file(lemur). +load_all :- + ensure_loaded(library(clpr)), + forall(doc_file(File), + ( directory_file_path('../prolog', File, Path), + ensure_loaded(Path))). -:- halt. \ No newline at end of file +gen_doc :- + load_all, + Opts = [ doc_root('./pldoc'), + include_reexported(true) + ], + + forall(doc_file(File), + ( directory_file_path('../prolog', File, Path), + doc_save(Path, Opts))). \ No newline at end of file diff --git a/docs/pldoc/cplint_util.html b/docs/pldoc/cplint_util.html index 133ba77..414e11e 100644 --- a/docs/pldoc/cplint_util.html +++ b/docs/pldoc/cplint_util.html @@ -24,38 +24,151 @@

cplint_util.pl -- cplint_util<
 bar(+Probability:float, -Chart:dict) is det
The predicate returns a dict for rendering with c3 as a bar chart with a bar for the probability and a bar for one minus the probability.
+
 bar1(+Probability:float, -Chart:dict) is det
The predicate returns a dict for rendering with c3 as a bar chart with +a bar for the probability
+
 bar(+Successes:int, +Failures:int, -Chart:dict) is det
The predicate returns a dict for rendering with c3 as a bar chart with +a bar for the number of successes and a bar for the number of failures
+
 argbar(+Values:list, -Chart:dict) is det
Values is a list of pairs V-N where +V is the value and N is the number of samples +returning that value. +The predicate returns a dict for rendering with c3 as a bar chart with +a bar for each value V. +The size of the bar is given by N.
+
 to_atom(+In:pair, -Out:pair) is det
Given In=A0-N, to_atom/2 returns Out=A-N +where A is an atom representing A0
+
 histogram(+List:list, -Chart:dict) is det
Equivalent to histogram/3 with an empty option list.
+
 histogram(+List:list, -Chart:dict, +Options:list) is det
Draws a histogram of the samples in List. List must be a list of pairs of the form [V]-W or V-W +where V is a sampled value and W is its weight, or a list of values. + +

+Options is a list of options, the following are recognised by histogram/3:

+ +
+
min(+Min:float)
the minimum value of domain, default value the minimum in List
+
max(+Max:float)
the maximum value of domain, default value the maximum in List
+
nbins(+NBins:int)
the number of bins for dividing the domain, default value 40
+
+ +
+
 densities(+PriorList:list, +PostList:list, -Chart:dict) is det
Equivalent to densities/4 with an empty option list.
+
 densities(+PriorList:list, +PostList:list, -Chart:dict, +Options:list) is det
Draws a line chart of the density of two sets of samples, usually +prior and post observations. The samples from the prior are in PriorList +while the samples from the posterior are in PostList. +PriorList and PostList must be lists of pairs of the form [V]-W or V-W +where V is a sampled value and W is its weight, or lists of values V. +Options is a list of options, the following are recognised by histogram/3: + +
+
nbins(+NBins:int)
the number of bins for dividing the domain, default value 40 +*/
+
+ +
+
 density(+List:list, -Chart:dict) is det
Equivalent to density/3 with an empty option list.
+
 density(+List:list, -Chart:dict, +Options:list) is det
Draws a line chart of the density of a sets of samples. +The samples are in List +as pairs [V]-W or V-W where V is a value and W its weigth. + +

+Options is a list of options, the following are recognised by density/3:

+ +
+
min(+Min:float)
the minimum value of domain, default value the minimum in List
+
max(+Max:float)
the maximum value of domain, default value the maximum in List
+
nbins(+NBins:int)
the number of bins for dividing the domain, default value 40
-

Undocumented predicates

+
+
 density2d(+List:list, -Dens:list) is det
Equivalent to density2d/3 with an empty option list.
+
 density2d(+List:list, -Dens:list, +Options:list) is det
Returns a set of 3-dimensional points representing the plot of the +density of a sets of 2-dimensional samples. +The samples are in List +as pairs [X,Y]-W where (X,Y) is a point and W its weigth.

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

- -
-
 bar1(Arg1, Arg2)
-
 agg_val(Arg1, Arg2, Arg3)
-
 average(Arg1, Arg2)
-
 value_pair(Arg1, Arg2)
-
 density2d(Arg1, Arg2)
-
 densities(Arg1, Arg2, Arg3)
-
 bar(Arg1, Arg2, Arg3)
-
 swi_builtin(Arg1)
-
 to_atom(Arg1, Arg2)
-
 key_pair(Arg1, Arg2)
-
 density(Arg1, Arg2, Arg3)
-
 histogram(Arg1, Arg2, Arg3)
-
 histogram(Arg1, Arg2)
-
 std_dev(Arg1, Arg2)
-
 variance(Arg1, Arg2, Arg3)
-
 beta(Arg1, Arg2)
-
 to_pair(Arg1, Arg2)
-
 density(Arg1, Arg2)
-
 argbar(Arg1, Arg2)
-
 std_dev(Arg1, Arg2, Arg3)
-
 variance(Arg1, Arg2)
-
 bin(Arg1, Arg2, Arg3, Arg4, Arg5)
-
 density2d(Arg1, Arg2, Arg3)
-
 densities(Arg1, Arg2, Arg3, Arg4)
+Options is a list of options, the following are recognised by density2d/3:

+ +
+
xmin(+XMin:float)
the minimum value of the X domain, default value the minimum in List
+
xmax(-XMax:float)
the maximum value of the X domain, default value the maximum in List
+
ymin(-YMin:float)
the minimum value of the Y domain, default value the minimum in List
+
ymax(-YMax:float)
the maximum value of the Y domain, default value the maximum in List
+
nbins(+NBins:int)
the number of bins for dividing the X and Y domains, default value 40
+
+ +
+
 to_pair(+Pair:pair, -FlattenedPair:pair) is det
Given a pair E-W, returns a pair Ep-W where +Ep=EE if E=[EE], otherwise Ep=E
+
 key_pair(+Pair:pair, -Key:term) is det
Given a pair Key-Vaule, returns its first element Key
+
 value_pair(+Pair:pair, -Value:term) is det
Given a pair Key-Vaule, returns its second element Value
+
 bin(+N:int, +Values:list, +Lower:number, +BinWidth:number, -Couples:list) is det
Given a list of numeric Values, a Lower value and BinWidth, returns in Couples +a list of N pairs V-Freq where V is the midpoint of a bin and Freq is the number +of values that are inside the bin interval [V-BinWidth/2,V+BinWidth/2) +starting with the bin where V-BinWidth/2=Lower
+
 beta(+Alphas:list, -Beta:float) is det
Computes the value of the multivariate beta function for vector Alphas +https://en.wikipedia.org/wiki/Beta_function#Multivariate_beta_function +Alphas is a list of floats
+
 average(+Values:list, -Average:float) is det
Computes the average of Values. +Values can be +
    +
  • a list of numbers
  • +
  • a list of pairs number-weight, in which case each number is multiplied by the weight +before being summed
  • +
  • a list of lists, in which case lists are considered as matrices of numbers and averaged +element-wise
  • +
  • a list of pairs list-weight, in which case the list is considered as a matrix of numbers. +The matrix in each element of List must have the same dimension and are aggregated element- +wise
  • +
+
+
 agg_val(+Couple:atom, +PartialSum:number, -Sum:number) is det
Aggregate values by summation. The first argument is a couple _-N with +N the new value to sum to PartialSum
+
 variance(+Values:list, -Variance:float) is det
Computes the variance of Values. +Values can be +
    +
  • a list of numbers
  • +
  • a list of pairs number-weight, in which case each number is multiplied by the weight +before being considered
  • +
  • a list of pairs list-weight, in which case list is considered as a matrix of numbers. +The matrix in each element of List must have the same dimension and are aggregated element- +wise
  • +
+
+
 variance(+Values:list, -Average:float, -Variance:float) is det
Computes the variance the average of Values. +Values can be +
    +
  • a list of numbers
  • +
  • a list of pairs number-weight, in which case each number is multiplied by the weight +before being considered
  • +
  • a list of pairs list-weight, in which case list is considered as a matrix of numbers. +The matrix in each element of List must have the same dimension and are aggregated element- +wise
  • +
+
+
 std_dev(+Values:list, -Dev:float) is det
Computes the standard deviation of Values. +Values can be +
    +
  • a list of numbers
  • +
  • a list of pairs number-weight, in which case each number is multiplied by the weight +before being considered
  • +
  • a list of pairs list-weight, in which case list is considered as a matrix of numbers. +The matrix in each element of List must have the same dimension and are aggregated element- +wise
  • +
+
+
 std_dev(+Values:list, -Average:float, -Dev:float) is det
Computes the standard deviation and the average of Values. +Values can be +
    +
  • a list of numbers
  • +
  • a list of pairs number-weight, in which case each number is multiplied by the weight +before being considered
  • +
  • a list of pairs list-weight, in which case list is considered as a matrix of numbers. +The matrix in each element of List must have the same dimension and are aggregated element- +wise
  • +
+
+
 swi_builtin(+Goal:atom) is det
Succeeds if Goal is an atom whose predicate is defined in Prolog +(either builtin or defined in a standard library).
diff --git a/docs/pldoc/lemur.html b/docs/pldoc/lemur.html index 2ffd1fb..1b242db 100644 --- a/docs/pldoc/lemur.html +++ b/docs/pldoc/lemur.html @@ -41,40 +41,211 @@

lemur.pl -- lemur

 setting_lm(:Parameter:atom, -Value:term) is det
The predicate returns the value of a parameter For a list of parameters see https://friguzzi.github.io/cplint/
- - -

Re-exported predicates

- -

-The following predicates are exported from this file while their implementation is defined in imported modules or non-module files loaded by this module.

- -
-
 format2(+Module:atom, +Format, :Arguments) is det
The predicate calls format(Format,Arguments) if the verbosity is at least 2. +
 symmetric_dirichlet_sample(++Alpha:float, ++K:int, --Value:list) is det
Returns a Value sampled from a symmetric Dirichlet distribution with parameter Alpha. +K is the number of dimensions of the result.
+
 learn_params(+DB:list_of_atoms, +M:atom, +R0:probabilistic_program, -P:probabilistic_program, -Score:float) is det
The predicate learns the parameters of the program R0 and returns +the updated program in R and the score in Score. +DB contains the list of interpretations ids and M the module where +the data is stored.
+
 process_clauses(+InputClauses:list, +Module:atom, +Rules:list, -RulesOut:list, +Clauses:list, -ClausesOut:list) is det
InputClauses is a list of probabilistic clauses in input syntax. +The predicate translates them into the internal format. +RulesOut/Rules is a difference list of term of the form rule(R,HeadList,BodyList,Lit,Tun). +ClausesOut/Clauses is a difference list of clauses to be asserted.
+
 and(++Environment:int, ++A:int, ++B:int, --AandB:int) is det
Returns in AandB a pointer to a BDD belonging to environment Environment +representing the conjunction of BDDs A and B.
+
 end_em(++Context:int) is det
Terminates the context data structure for performing parameter learning. +Context is a pointer to a context data structure for performing +the EM algorithm. +Context must have been returned by a call to init_em/1. +It frees the memory occupied by Context.
+
 induce(:TrainFolds:list_of_atoms, -P:probabilistic_program) is det
The predicate performs structure learning using the folds indicated in +TrainFolds for training. +It returns in P the learned probabilistic program.
+
 gamma_sample(++Shape:float, ++Scale:float, --Value:float) is det
Returns a Value sampled from a gamma distribution with parameters Shape and Scale
+
 equalityc(++Environment:int, ++Variable:int, ++Value:int, --EBDD:couple) is det
Returns in EBDD a couple (Environment,BDD) where BDD belongs to environment Environment +and represents the equation Variable=Value.
+
 create_dot(++Env:int, ++BDD:int, ++File:string) is det
The predicate writes the BDD in dot format to +to file FileName.
+
 write_rules3(+Module:atom, +Rules:list, +Stream:atom) is det
The predicate write the rules in Rules on stream Stream if the verbosity is at least 3. Module is used to get the verbosity setting.
+
 write_rules2(+Module:atom, +Rules:list, +Stream:atom) is det
The predicate write the rules in Rules on stream Stream if the verbosity is at least 2. +Module is used to get the verbosity setting.
+
 ret_probc(++Environment:int, ++EBDD:couple, -Probability:float) is det
EBDD is a couple (Environment,BDD) +Returns the Probability of BDD belonging to environment Environment +Uses
+
 andc(++Environment:int, ++A:couple, ++B:couple, --AandB:couple) is semidet
A and B are couples (Environment, BDDA) and (Environment, BDDB) respectively +Returns in AandB a couple (Environment, BDDAandB) where BDDAandB is pointer to a BDD belonging to environment Environment +representing the conjunction of BDDs BDDA and BDDB. +fails if BDDB represents the zero function
+
 write2(+Module:atom, +Message:term) is det
The predicate calls write(Message) if the verbosity is at least 2. +Module is used to get the verbosity setting
+
 take_var_args(+ArgSpec:list, +TypeVars:list, -Vars:list) is det
The predicate returns in Vars the list of vars corresponding to +variables arguments in ArgSpec (those with argument specification ++type or -type). TypeVars is a list of terns of the form +Variable=Types as returnd by extract_type_vars/3.
+
 get_next_rule_number(+Module:atom, -R:integer) is det
The predicate returns the next rule number. Module is used to access local +data.
+
 equality(++Environment:int, ++Variable:int, ++Value:int, --BDD:int) is det
Returns in BDD the BDD belonging to environment Environment +that represents the equation Variable=Value.
+
 debug_cudd_var(++Environment:int, -Variable:out) is det
Prints the debug information which is the result of the call +of Cudd_ReadDead, Cudd_CheckZeroRef, Cudd_CheckKeys and +Cudd_DebugCheck(env->mgr));
+
 probability_dd(++Environment:int, ++BDD:int, --ADD:int) is det
Converts the BDD belonging to environment Environment into an ADD.
+
 add_query_var(++Environment:int, ++ProbabilityDistribution:list, ++Rule:int, -Variable:int) is det
Returns in Variable the index of a new random variable to be queried in MAP inference with +NumberOHeads values and probability distribution ProbabilityDistribution. +The variable belongs to Environment.
+
 make_dynamic(+Module:atom) is det
Makes the predicates required for learning dynamic.
 zero(++Environment:int, --Zero:int) is det
Returns in Zero a pointer to a BDD belonging to environment Environment representing the zero Boolean function.
+
 discrete_sample(++Theta:list, --Value:int) is det
Returns a Value sampled from a discrete distribution with parameters Theta. +Theta is a list of floating point numbers in [0,1] that sum to 1. +Value is in 0..(length(Theta)-1)
+
 sample(+N, List:list, -Sampled:list, -Rest:list) is det
Samples N elements from List and returns them in Sampled. +The rest of List is returned in Rest +If List contains less than N elements, Sampled is List and Rest +is [].
+
 get_sc_var_n(++M:atomic, ++Environment:int, ++Rule:int, ++Substitution:term, ++Probabilities:list, -Variable:int) is det
Returns the index Variable of the random variable associated to rule with +index Rule, grouding substitution Substitution and head distribution +Probabilities in environment Environment. +Differs from get_var_n/6 of pita because R can be ng(RN,Vals), indicating a rule for which +different instantiations get different parameters.
 init(--Environment:int) is det
Initializes a data structure for storing a single BDD. Returns an integer Environment that is a pointer to a data structure for storing a single BDD to be used for inference only (no learning).
+
 gauss_sample(++Mean:float, ++Variance:float, --Value:float) is det
Returns a Value sampled from a Gaussian distribution with parameters Mean and Variance
+
 setting_sc(:Parameter:atom, -Value:term) is det
The predicate returns the value of a parameter +For a list of parameters see +https://friguzzi.github.io/cplint/
+
 create_dot_string(++Env:int, ++BDD:int, -Dot:string) is det
The predicate returns the BDD in dot format.
+
 nl2(+Module:atom) is det
The predicate prints a newline if the verbosity is at least 2. +Module is used to get the verbosity setting.
+
 or_list(++ListOfBDDs:list, ++Environment, --BDD:int) is det
Returns in BDD a pointer to a BDD belonging to environment Environment +representing the disjunction of all the BDDs in ListOfBDDs
+
 format3(+Module:atom, +Format, :Arguments) is det
The predicate calls format(Format,Arguments) if the verbosity is at least 3. +Module is used to get the verbosity setting.
+
 orc(++A:couple, ++B:couple, --AorB:couple) is det
A and B are couples (Environment, BDDA) and (Environment, BDDB) respectively +Returns in AorB a couple (Environment, BDDAorB) where BDDAorB is pointer to a BDD belonging to environment Environment +representing the disjunction of BDDs BDDA and BDDB.
+
 delete_one(+List:list, -Rest:list, +Element:term) is nondet
As the library predicate delete(+List1, @Elem, -List2) but +Element is unified with the deleted element (so it can be +instantiated by the call).
+
 zeroc(++Environment:int, --Zero:couple) is det
Returns in Zero a couple (Environment,BDD) where BDD is pointer to a BDD belonging to environment Environment +representing the zero Boolean function
+
 banned_clause(+Module:atom, -Head:term, -Body:term) is nondet
The predicate checks whether Head:-Body is a banned clause, as specified +by the user in the input file. Module is the module of the input file.
+
 assert_all(+Terms:list, +Module:atom, -Refs:list) is det
The predicate asserts all terms in Terms in module Module using assertz(M:Term,Ref) and +returns the list of references in Refs
+
 add_prod(++Environment:int, ++ADDIn:int, ++Utility:float, --ADDOut:int) is det
Multiplies the ADD belonging to environment Environment +with the value Utility and stores the result in ADDOut.
+
 generate_body(+ModeDecs:list, +Module:atom, -BottomClauses:list) is det
Generates the body of bottom clauses and returns the bottom clauses in BottomClauses.
+
 ret_prob(++Environment:int, ++BDD:int, -Probability:float) is det
Returns the Probability of BDD belonging to environment Environment.
+
 ret_abd_prob(++Environment:int, ++BDD:int, -Probability:float, -Explanation:list) is det
Returns the abductive Explanation of BDD and its Probability. +BDD belongs to environment Environment.
+
 end(++Environment:int) is det
Terminates the environment data structure for storing a single BDD. +Environment is a pointer to a data structure returned by a call +to init/1.
+
 rules2terms(:R:list_of_rules, -T:tern) is det
The predicate translates a list of rules from the internal +representation format (rule/4 and def_rule/3) to the +LPAD syntax.
+
 test(:P:probabilistic_program, +TestFolds:list_of_atoms, -LL:float, -AUCROC:float, -ROC:dict, -AUCPR:float, -PR:dict) is det
The predicate takes as input in P a probabilistic program, +tests P on the folds indicated in TestFolds and returns the +log likelihood of the test examples in LL, the area under the Receiver +Operating Characteristic curve in AUCROC, a dict containing the points +of the ROC curve in ROC, the area under the Precision Recall curve in AUCPR +and a dict containing the points of the PR curve in PR
+
 one(++Environment:int, --One:int) is det
Returns in One a pointer to a BDD belonging to environment Environment +representing the one Boolean function.
+
 em(++Context:int, ++RuleInfo:list, ++ListOfBDDs:list, ++EA:float, ++ER:float, ++Iterations:int, -LL:float, -Parameters:list, -ExampleProbabilities:list) is det
NumberOfHeads is a list of terms, one for each rule. Each term is either +an integer, indicating the number +of head atoms in the rule, or a list [N] where N +is the number of head atoms. In the first case, the parameters of the rule are tunable, +in the latter they are fixed. + +

+Performs EM learning. +Takes as input the Context, information on the rules, +a list of BDDs each representing one example, +the minimum absolute difference EA and relative difference ER between the +log likelihood of examples in two different iterations and the maximum number of iterations +Iterations. +RuleInfo is a list of elements, one for each rule, with are either

+
    +
  • an integer, indicating the number of heads, in which case the parameters of the +corresponding rule should be randomized,
  • +
  • a list of floats, in which case the parameters should be set to those indicated +in the list and not changed during learning (fixed parameters)
  • +
  • [a list of floats], in which case the initial values of the parameters should +be set to those indicated +in the list and changed during learning (initial values of the parameters) +Returns the final log likelihood of examples LL, the list of new Parameters +and a list with the final probabilities of each example. +Parameters is a list whose elements are of the form [N,P] where N is the rule +number and P is a list of probabilities, one for each head atom of rule N, +in reverse order.
  • +
+
+
 initial_values(++Environment:int, ++Alpha:float) is det
Sets the type of parameter initialization for EM on Environment: +if Alpha is 0.0, it uses a truncated Dirichlet process +if Alpha is a float > 0.0, it uses a symmetric Dirichlet distribution +with that value as parameter
+
 member_eq(+List:list, +Element:term) is det
Checks the presence of Element in List. Equality is checked with ==.
+
 init_ex(++Context:int, --Environment:int) is det
Initializes an enviroment data structure for storing a BDD. +Context is an integer that is a pointer to a context data structure +created using init_em/1. +Returns an integer Environment that is a pointer to a data structure for +storing a single BDD to be used for the EM algorithm.
+
 uniform_sample(--Value:float) is det
Returns a Value sampled from a uniform distribution in [0,1]
+
 set_sc(:Parameter:atom, +Value:term) is det
The predicate sets the value of a parameter +For a list of parameters see +https://friguzzi.github.io/cplint/
+
 or_listc(++ListOfBDDs:list, ++Environment, --BDD:int) is det
Returns in BDD a couple (Env,B) with B a pointer to a +BDD belonging to environment Environment +representing the disjunction of all the BDDs in +ListOfBDDs (a list of couples (Env,BDD))
+
 nl3(+Module:atom) is det
The predicate prints a newline if the verbosity is at least 3. +Module is used to get the verbosity setting.
+
 list2or(+List:list, -Or:term) is det
+
list2or(-List:list, +Or:term) is det
The predicate succeeds when Or is a disjunction (using the ; operator) +of the terms in List
+
 format2(+Module:atom, +Format, :Arguments) is det
The predicate calls format(Format,Arguments) if the verbosity is at least 2. +Module is used to get the verbosity setting.
+
 retract_all(+Refs:list) is det
The predicate erases all references in Refs (using erase/1).
+
 bdd_notc(++Environment:int, ++EBDD:couple, --NotEBDD:couple) is det
EBDD is a couple (Environment,A) +Returns in NotEBDD a couple (Environment,NotA) where NotA is +pointer to a BDD belonging to environment Environment +representing the negation of BDD A
+
 onec(++Environment:int, --One:couple) is det
Returns in One a couple (Environment,BDD) where BDD is pointer to a BDD belonging to environment Environment +representing the one Boolean function
 extract_type_vars(+Literals:list, +Module:atom, +Types:term) is det
The predicate extracts the type of variables from the list of literals Literals. Types is a list of elements of the form Variable=Type
 linked_clause(+Literals:list, +Module:atom, +PrevLits:list) is det
The predicate checks whether Literals form a linked list of literals given that PrevLits are the previous literals. In a linked list of literals input variables of a literal are output variables in a previous literal.
-
 rand_seed(+Seed:int) is det
The pseudo-random number generator is initialized using the argument passed as Seed. -It calls the C function srand.
+
 zero_clause(+Module:atom, +PredSpec:pred_spec, -ZeroClause:term) is det
Generates the zero clause for predicate PredSpec. +Module is the module of the input file.
+
 add_sum(++Environment:int, ++ADD1:int, ++ADD2:int, --ADDOut:int) is det
Computes the sum of the two ADDs ADD1 ADD2 belonging to environment Environment. +The result in saved in ADDOut.
 generate_clauses_bg(+Rules:list, -Clauses:list) is det
The predicate generate clauses to be asserted in the database for the rules from the background. Rules is a list of term of the form def_rule(H,BodyList,_Lit). Clauses is a list of clauses to be asserted.
-
 make_query_var(++Environment:int, +Variable:int, --BDD:int) is det
Makes Variable belonging to Environment a query random variable for MAP inference. -Returns in BDD the diagram of the formula encoding the required constraints among the -Boolean random variable that represent Variable.
-
 retract_all(+Refs:list) is det
The predicate erases all references in Refs (using erase/1).
-
 orc(++A:couple, ++B:couple, --AorB:couple) is det
A and B are couples (Environment, BDDA) and (Environment, BDDB) respectively -Returns in AorB a couple (Environment, BDDAorB) where BDDAorB is pointer to a BDD belonging to environment Environment -representing the disjunction of BDDs BDDA and BDDB.
+
 add_abd_var(++Environment:int, ++ProbabilityDistribution:list, ++Rule:int, -Variable:int) is det
Returns in Variable the index of a new abducible random variable in Environment with +NumberOHeads values and probability distribution ProbabilityDistribution.
+
 bdd_not(++Environment:int, ++A:int, --NotA:int) is det
Returns in NotA a pointer to a BDD belonging to environment Environment +representing the negation of BDD A.
+
 list2and(+List:list, -And:term) is det
+
list2and(-List:list, +And:term) is det
The predicate succeeds when And is a conjunction (using the , operator) +of the terms in List
+
 end_ex(++Environment:int) is det
Terminates the evnironment data structure for storing a BDD. +Environment is a pointer to a data structure returned by init_ex/2. +It frees the memory occupied by the BDD.
+
 add_decision_var(++Environment:int, ++Rule:int, -Variable:int) is det
Returns in Variable the index of a new decision variable in Environment
+
 init_em(--Context:int) is det
Initializes a data structure for performing parameter learning. +It returns an integer in Context that is a pointer to a +context data structure for performing the EM algorithm.
+
 dirichlet_sample(++Alpha:list, --Value:list) is det
Returns a Value sampled from a Dirichlet distribution with parameters Alpha. +Alpha and Value are lists of floating point numbers of the same length.
 induce_par(:TrainFolds:list_of_atoms, -P:probabilistic_program) is det
The predicate learns the parameters of the program stored in the in/1 fact of the input file using the folds indicated in TrainFolds for training. It returns in P the input program with the updated parameters.
@@ -83,21 +254,24 @@

Re-exported predicates

the number of positive examples in NPos, the number of negative examples in NNeg, the log likelihood in LL and in Results a list containing the probabilistic result for each query contained in TestFolds. -
 ret_abd_prob(++Environment:int, ++BDD:int, -Probability:float, -Explanation:list) is det
Returns the abductive Explanation of BDD and its Probability. +
 rand_seed(+Seed:int) is det
The pseudo-random number generator is initialized using the argument passed as Seed. +It calls the C function srand.
+
 make_query_var(++Environment:int, +Variable:int, --BDD:int) is det
Makes Variable belonging to Environment a query random variable for MAP inference. +Returns in BDD the diagram of the formula encoding the required constraints among the +Boolean random variable that represent Variable.
+
 ret_map_prob(++Environment:int, ++BDD:int, -Probability:float, -MAPState:list) is det
Returns the MAP state MPAState of BDD and its Probability. BDD belongs to environment Environment.
-
 ret_prob(++Environment:int, ++BDD:int, -Probability:float) is det
Returns the Probability of BDD belonging to environment Environment.
-
 nl2(+Module:atom) is det
The predicate prints a newline if the verbosity is at least 2. -Module is used to get the verbosity setting.
 write3(+Module:atom, +Message:term) is det
The predicate calls write(Message) if the verbosity is at least 3. Module is used to get the verbosity setting.
-
 one(++Environment:int, --One:int) is det
Returns in One a pointer to a BDD belonging to environment Environment -representing the one Boolean function.
+
 andcnf(++Environment:int, ++A:couple, ++B:couple, --AandB:couple) is semidet
A and B are couples (Environment, BDDA) and (Environment, BDDB) respectively +Returns in AandB a couple (Environment, BDDAandB) where BDDAandB is pointer to a BDD belonging to environment Environment +representing the conjunction of BDDs BDDA and BDDB.
 remove_duplicates(+List1:list, -List2:list) is det
Removes duplicates from List1. Equality is checked with ==.
-
 init_ex(++Context:int, --Environment:int) is det
Initializes an enviroment data structure for storing a BDD. -Context is an integer that is a pointer to a context data structure -created using init_em/1. -Returns an integer Environment that is a pointer to a data structure for -storing a single BDD to be used for the EM algorithm.
+
 or(++Environment:int, ++A:int, ++B:int, --AorB:int) is det
Returns in AorB a pointer to a BDD belonging to environment Environment +representing the disjunction of BDDs A and B.
+
 tab(+Module:atom, +PredSpec:pred_spec, -TableSpec:term) is det
Records the fact that predicate PredSpec must be tabled and returns +the necessary term for the tabling directive in TableSpec. +Module is used to store the information in the correct module
 generate_clauses(+Rules0:list, +Module:atom, +StartingIndex:integer, -Rules:list, +Clauses:list, -ClausesOut:list) is det
The predicate generate the internal representation of rules to produce clauses to be asserted in the database. Rules0 is a list of term of the form rule(R,HeadList,BodyList,Lit,Tun). @@ -108,71 +282,132 @@

Re-exported predicates

 extract_fancy_vars(+Term:term, -Vars:list) is nondet
Given Term, it returns the list of all of its variables in the form 'VN'=Var where VN is an atom with N an increasing integer starting from 1 and Var a variable in Term.
+
 ret_strategy(++Environment:int, ++ADD:int, --Decision:list, --Cost:int) is det
Computes the optimal strategy given a pointer to the ADD belonging to environment Environment. +Decision is a list of selected facts, Cost is the total cost.
+
 add_var(++Environment:int, ++ProbabilityDistribution:list, ++Rule:int, -Variable:int) is det
Returns in Variable the index of a new random variable in Environment with +NumberOHeads values and probability distribution ProbabilityDistribution.
+
+ +

Re-exported predicates

+ +

+The following predicates are exported from this file while their implementation is defined in imported modules or non-module files loaded by this module.

+ +
+
 symmetric_dirichlet_sample(++Alpha:float, ++K:int, --Value:list) is det
Returns a Value sampled from a symmetric Dirichlet distribution with parameter Alpha. +K is the number of dimensions of the result.
+
 learn_params(+DB:list_of_atoms, +M:atom, +R0:probabilistic_program, -P:probabilistic_program, -Score:float) is det
The predicate learns the parameters of the program R0 and returns +the updated program in R and the score in Score. +DB contains the list of interpretations ids and M the module where +the data is stored.
+
 process_clauses(+InputClauses:list, +Module:atom, +Rules:list, -RulesOut:list, +Clauses:list, -ClausesOut:list) is det
InputClauses is a list of probabilistic clauses in input syntax. +The predicate translates them into the internal format. +RulesOut/Rules is a difference list of term of the form rule(R,HeadList,BodyList,Lit,Tun). +ClausesOut/Clauses is a difference list of clauses to be asserted.
+
 and(++Environment:int, ++A:int, ++B:int, --AandB:int) is det
Returns in AandB a pointer to a BDD belonging to environment Environment +representing the conjunction of BDDs A and B.
+
 end_em(++Context:int) is det
Terminates the context data structure for performing parameter learning. +Context is a pointer to a context data structure for performing +the EM algorithm. +Context must have been returned by a call to init_em/1. +It frees the memory occupied by Context.
+
 induce(:TrainFolds:list_of_atoms, -P:probabilistic_program) is det
The predicate performs structure learning using the folds indicated in +TrainFolds for training. +It returns in P the learned probabilistic program.
+
 gamma_sample(++Shape:float, ++Scale:float, --Value:float) is det
Returns a Value sampled from a gamma distribution with parameters Shape and Scale
+
 equalityc(++Environment:int, ++Variable:int, ++Value:int, --EBDD:couple) is det
Returns in EBDD a couple (Environment,BDD) where BDD belongs to environment Environment +and represents the equation Variable=Value.
 create_dot(++Env:int, ++BDD:int, ++File:string) is det
The predicate writes the BDD in dot format to to file FileName.
-
 rules2terms(:R:list_of_rules, -T:tern) is det
The predicate translates a list of rules from the internal -representation format (rule/4 and def_rule/3) to the -LPAD syntax.
-
 test(:P:probabilistic_program, +TestFolds:list_of_atoms, -LL:float, -AUCROC:float, -ROC:dict, -AUCPR:float, -PR:dict) is det
The predicate takes as input in P a probabilistic program, -tests P on the folds indicated in TestFolds and returns the -log likelihood of the test examples in LL, the area under the Receiver -Operating Characteristic curve in AUCROC, a dict containing the points -of the ROC curve in ROC, the area under the Precision Recall curve in AUCPR -and a dict containing the points of the PR curve in PR
-
 tab(+Module:atom, +PredSpec:pred_spec, -TableSpec:term) is det
Records the fact that predicate PredSpec must be tabled and returns -the necessary term for the tabling directive in TableSpec. -Module is used to store the information in the correct module
-
 set_sc(:Parameter:atom, +Value:term) is det
The predicate sets the value of a parameter -For a list of parameters see -https://friguzzi.github.io/cplint/
 write_rules3(+Module:atom, +Rules:list, +Stream:atom) is det
The predicate write the rules in Rules on stream Stream if the verbosity is at least 3. Module is used to get the verbosity setting.
-
 list2and(+List:list, -And:term) is det
-
list2and(-List:list, +And:term) is det
The predicate succeeds when And is a conjunction (using the , operator) -of the terms in List
-
 add_abd_var(++Environment:int, ++ProbabilityDistribution:list, ++Rule:int, -Variable:int) is det
Returns in Variable the index of a new abducible random variable in Environment with -NumberOHeads values and probability distribution ProbabilityDistribution.
-
 bdd_not(++Environment:int, ++A:int, --NotA:int) is det
Returns in NotA a pointer to a BDD belonging to environment Environment -representing the negation of BDD A.
-
 end(++Environment:int) is det
Terminates the environment data structure for storing a single BDD. -Environment is a pointer to a data structure returned by a call -to init/1.
+
 write_rules2(+Module:atom, +Rules:list, +Stream:atom) is det
The predicate write the rules in Rules on stream Stream if the verbosity is at least 2. +Module is used to get the verbosity setting.
+
 ret_probc(++Environment:int, ++EBDD:couple, -Probability:float) is det
EBDD is a couple (Environment,BDD) +Returns the Probability of BDD belonging to environment Environment +Uses
+
 andc(++Environment:int, ++A:couple, ++B:couple, --AandB:couple) is semidet
A and B are couples (Environment, BDDA) and (Environment, BDDB) respectively +Returns in AandB a couple (Environment, BDDAandB) where BDDAandB is pointer to a BDD belonging to environment Environment +representing the conjunction of BDDs BDDA and BDDB. +fails if BDDB represents the zero function
 write2(+Module:atom, +Message:term) is det
The predicate calls write(Message) if the verbosity is at least 2. Module is used to get the verbosity setting
-
 or(++Environment:int, ++A:int, ++B:int, --AorB:int) is det
Returns in AorB a pointer to a BDD belonging to environment Environment -representing the disjunction of BDDs A and B.
 take_var_args(+ArgSpec:list, +TypeVars:list, -Vars:list) is det
The predicate returns in Vars the list of vars corresponding to variables arguments in ArgSpec (those with argument specification +type or -type). TypeVars is a list of terns of the form Variable=Types as returnd by extract_type_vars/3.
-
 end_ex(++Environment:int) is det
Terminates the evnironment data structure for storing a BDD. -Environment is a pointer to a data structure returned by init_ex/2. -It frees the memory occupied by the BDD.
-
 make_dynamic(+Module:atom) is det
Makes the predicates required for learning dynamic.
-
 process_clauses(+InputClauses:list, +Module:atom, +Rules:list, -RulesOut:list, +Clauses:list, -ClausesOut:list) is det
InputClauses is a list of probabilistic clauses in input syntax. -The predicate translates them into the internal format. -RulesOut/Rules is a difference list of term of the form rule(R,HeadList,BodyList,Lit,Tun). -ClausesOut/Clauses is a difference list of clauses to be asserted.
-
 member_eq(+List:list, +Element:term) is det
Checks the presence of Element in List. Equality is checked with ==.
-
 create_dot_string(++Env:int, ++BDD:int, -Dot:string) is det
The predicate returns the BDD in dot format.
-
 init_em(--Context:int) is det
Initializes a data structure for performing parameter learning. -It returns an integer in Context that is a pointer to a -context data structure for performing the EM algorithm.
 get_next_rule_number(+Module:atom, -R:integer) is det
The predicate returns the next rule number. Module is used to access local data.
+
 equality(++Environment:int, ++Variable:int, ++Value:int, --BDD:int) is det
Returns in BDD the BDD belonging to environment Environment +that represents the equation Variable=Value.
+
 debug_cudd_var(++Environment:int, -Variable:out) is det
Prints the debug information which is the result of the call +of Cudd_ReadDead, Cudd_CheckZeroRef, Cudd_CheckKeys and +Cudd_DebugCheck(env->mgr));
+
 probability_dd(++Environment:int, ++BDD:int, --ADD:int) is det
Converts the BDD belonging to environment Environment into an ADD.
+
 add_query_var(++Environment:int, ++ProbabilityDistribution:list, ++Rule:int, -Variable:int) is det
Returns in Variable the index of a new random variable to be queried in MAP inference with +NumberOHeads values and probability distribution ProbabilityDistribution. +The variable belongs to Environment.
+
 make_dynamic(+Module:atom) is det
Makes the predicates required for learning dynamic.
+
 zero(++Environment:int, --Zero:int) is det
Returns in Zero a pointer to a BDD belonging to environment Environment +representing the zero Boolean function.
+
 discrete_sample(++Theta:list, --Value:int) is det
Returns a Value sampled from a discrete distribution with parameters Theta. +Theta is a list of floating point numbers in [0,1] that sum to 1. +Value is in 0..(length(Theta)-1)
 sample(+N, List:list, -Sampled:list, -Rest:list) is det
Samples N elements from List and returns them in Sampled. The rest of List is returned in Rest If List contains less than N elements, Sampled is List and Rest is [].
+
 get_sc_var_n(++M:atomic, ++Environment:int, ++Rule:int, ++Substitution:term, ++Probabilities:list, -Variable:int) is det
Returns the index Variable of the random variable associated to rule with +index Rule, grouding substitution Substitution and head distribution +Probabilities in environment Environment. +Differs from get_var_n/6 of pita because R can be ng(RN,Vals), indicating a rule for which +different instantiations get different parameters.
+
 init(--Environment:int) is det
Initializes a data structure for storing a single BDD. +Returns an integer Environment that is a pointer to a data structure for +storing a single BDD to be used for inference only (no learning).
+
 gauss_sample(++Mean:float, ++Variance:float, --Value:float) is det
Returns a Value sampled from a Gaussian distribution with parameters Mean and Variance
 setting_sc(:Parameter:atom, -Value:term) is det
The predicate returns the value of a parameter For a list of parameters see https://friguzzi.github.io/cplint/
-
 add_var(++Environment:int, ++ProbabilityDistribution:list, ++Rule:int, -Variable:int) is det
Returns in Variable the index of a new random variable in Environment with -NumberOHeads values and probability distribution ProbabilityDistribution.
-
 ret_map_prob(++Environment:int, ++BDD:int, -Probability:float, -MAPState:list) is det
Returns the MAP state MPAState of BDD and its Probability. -BDD belongs to environment Environment.
-
 write_rules2(+Module:atom, +Rules:list, +Stream:atom) is det
The predicate write the rules in Rules on stream Stream if the verbosity is at least 2. +
 create_dot_string(++Env:int, ++BDD:int, -Dot:string) is det
The predicate returns the BDD in dot format.
+
 nl2(+Module:atom) is det
The predicate prints a newline if the verbosity is at least 2. +Module is used to get the verbosity setting.
+
 or_list(++ListOfBDDs:list, ++Environment, --BDD:int) is det
Returns in BDD a pointer to a BDD belonging to environment Environment +representing the disjunction of all the BDDs in ListOfBDDs
+
 format3(+Module:atom, +Format, :Arguments) is det
The predicate calls format(Format,Arguments) if the verbosity is at least 3. Module is used to get the verbosity setting.
+
 orc(++A:couple, ++B:couple, --AorB:couple) is det
A and B are couples (Environment, BDDA) and (Environment, BDDB) respectively +Returns in AorB a couple (Environment, BDDAorB) where BDDAorB is pointer to a BDD belonging to environment Environment +representing the disjunction of BDDs BDDA and BDDB.
+
 delete_one(+List:list, -Rest:list, +Element:term) is nondet
As the library predicate delete(+List1, @Elem, -List2) but +Element is unified with the deleted element (so it can be +instantiated by the call).
+
 zeroc(++Environment:int, --Zero:couple) is det
Returns in Zero a couple (Environment,BDD) where BDD is pointer to a BDD belonging to environment Environment +representing the zero Boolean function
+
 banned_clause(+Module:atom, -Head:term, -Body:term) is nondet
The predicate checks whether Head:-Body is a banned clause, as specified +by the user in the input file. Module is the module of the input file.
+
 assert_all(+Terms:list, +Module:atom, -Refs:list) is det
The predicate asserts all terms in Terms in module Module using assertz(M:Term,Ref) and +returns the list of references in Refs
+
 add_prod(++Environment:int, ++ADDIn:int, ++Utility:float, --ADDOut:int) is det
Multiplies the ADD belonging to environment Environment +with the value Utility and stores the result in ADDOut.
+
 generate_body(+ModeDecs:list, +Module:atom, -BottomClauses:list) is det
Generates the body of bottom clauses and returns the bottom clauses in BottomClauses.
+
 ret_prob(++Environment:int, ++BDD:int, -Probability:float) is det
Returns the Probability of BDD belonging to environment Environment.
+
 ret_abd_prob(++Environment:int, ++BDD:int, -Probability:float, -Explanation:list) is det
Returns the abductive Explanation of BDD and its Probability. +BDD belongs to environment Environment.
+
 end(++Environment:int) is det
Terminates the environment data structure for storing a single BDD. +Environment is a pointer to a data structure returned by a call +to init/1.
+
 rules2terms(:R:list_of_rules, -T:tern) is det
The predicate translates a list of rules from the internal +representation format (rule/4 and def_rule/3) to the +LPAD syntax.
+
 test(:P:probabilistic_program, +TestFolds:list_of_atoms, -LL:float, -AUCROC:float, -ROC:dict, -AUCPR:float, -PR:dict) is det
The predicate takes as input in P a probabilistic program, +tests P on the folds indicated in TestFolds and returns the +log likelihood of the test examples in LL, the area under the Receiver +Operating Characteristic curve in AUCROC, a dict containing the points +of the ROC curve in ROC, the area under the Precision Recall curve in AUCPR +and a dict containing the points of the PR curve in PR
+
 one(++Environment:int, --One:int) is det
Returns in One a pointer to a BDD belonging to environment Environment +representing the one Boolean function.
 em(++Context:int, ++RuleInfo:list, ++ListOfBDDs:list, ++EA:float, ++ER:float, ++Iterations:int, -LL:float, -Parameters:list, -ExampleProbabilities:list) is det
NumberOfHeads is a list of terms, one for each rule. Each term is either an integer, indicating the number of head atoms in the rule, or a list [N] where N @@ -202,77 +437,108 @@

Re-exported predicates

in reverse order.
-
 delete_one(+List:list, -Rest:list, +Element:term) is nondet
As the library predicate delete(+List1, @Elem, -List2) but -Element is unified with the deleted element (so it can be -instantiated by the call).
+
 initial_values(++Environment:int, ++Alpha:float) is det
Sets the type of parameter initialization for EM on Environment: +if Alpha is 0.0, it uses a truncated Dirichlet process +if Alpha is a float > 0.0, it uses a symmetric Dirichlet distribution +with that value as parameter
+
 member_eq(+List:list, +Element:term) is det
Checks the presence of Element in List. Equality is checked with ==.
+
 init_ex(++Context:int, --Environment:int) is det
Initializes an enviroment data structure for storing a BDD. +Context is an integer that is a pointer to a context data structure +created using init_em/1. +Returns an integer Environment that is a pointer to a data structure for +storing a single BDD to be used for the EM algorithm.
+
 uniform_sample(--Value:float) is det
Returns a Value sampled from a uniform distribution in [0,1]
+
 set_sc(:Parameter:atom, +Value:term) is det
The predicate sets the value of a parameter +For a list of parameters see +https://friguzzi.github.io/cplint/
+
 or_listc(++ListOfBDDs:list, ++Environment, --BDD:int) is det
Returns in BDD a couple (Env,B) with B a pointer to a +BDD belonging to environment Environment +representing the disjunction of all the BDDs in +ListOfBDDs (a list of couples (Env,BDD))
+
 nl3(+Module:atom) is det
The predicate prints a newline if the verbosity is at least 3. +Module is used to get the verbosity setting.
 list2or(+List:list, -Or:term) is det
list2or(-List:list, +Or:term) is det
The predicate succeeds when Or is a disjunction (using the ; operator) of the terms in List
-
 banned_clause(+Module:atom, -Head:term, -Body:term) is nondet
The predicate checks whether Head:-Body is a banned clause, as specified -by the user in the input file. Module is the module of the input file.
-
 end_em(++Context:int) is det
Terminates the context data structure for performing parameter learning. -Context is a pointer to a context data structure for performing -the EM algorithm. -Context must have been returned by a call to init_em/1. -It frees the memory occupied by Context.
-
 and(++Environment:int, ++A:int, ++B:int, --AandB:int) is det
Returns in AandB a pointer to a BDD belonging to environment Environment -representing the conjunction of BDDs A and B.
-
 generate_body(+ModeDecs:list, +Module:atom, -BottomClauses:list) is det
Generates the body of bottom clauses and returns the bottom clauses in BottomClauses.
-
 get_sc_var_n(++M:atomic, ++Environment:int, ++Rule:int, ++Substitution:term, ++Probabilities:list, -Variable:int) is det
Returns the index Variable of the random variable associated to rule with -index Rule, grouding substitution Substitution and head distribution -Probabilities in environment Environment. -Differs from get_var_n/6 of pita because R can be ng(RN,Vals), indicating a rule for which -different instantiations get different parameters.
+
 format2(+Module:atom, +Format, :Arguments) is det
The predicate calls format(Format,Arguments) if the verbosity is at least 2. +Module is used to get the verbosity setting.
+
 retract_all(+Refs:list) is det
The predicate erases all references in Refs (using erase/1).
+
 bdd_notc(++Environment:int, ++EBDD:couple, --NotEBDD:couple) is det
EBDD is a couple (Environment,A) +Returns in NotEBDD a couple (Environment,NotA) where NotA is +pointer to a BDD belonging to environment Environment +representing the negation of BDD A
+
 onec(++Environment:int, --One:couple) is det
Returns in One a couple (Environment,BDD) where BDD is pointer to a BDD belonging to environment Environment +representing the one Boolean function
+
 extract_type_vars(+Literals:list, +Module:atom, +Types:term) is det
The predicate extracts the type of variables from the list of literals +Literals. Types is a list of elements of the form Variable=Type
+
 linked_clause(+Literals:list, +Module:atom, +PrevLits:list) is det
The predicate checks whether Literals form a linked list of literals +given that PrevLits are the previous literals. +In a linked list of literals input variables of a literal are output variables in +a previous literal.
 zero_clause(+Module:atom, +PredSpec:pred_spec, -ZeroClause:term) is det
Generates the zero clause for predicate PredSpec. Module is the module of the input file.
-
 assert_all(+Terms:list, +Module:atom, -Refs:list) is det
The predicate asserts all terms in Terms in module Module using assertz(M:Term,Ref) and -returns the list of references in Refs
-
 learn_params(+DB:list_of_atoms, +M:atom, +R0:probabilistic_program, -P:probabilistic_program, -Score:float) is det
The predicate learns the parameters of the program R0 and returns -the updated program in R and the score in Score. -DB contains the list of interpretations ids and M the module where -the data is stored.
-
 induce(:TrainFolds:list_of_atoms, -P:probabilistic_program) is det
The predicate performs structure learning using the folds indicated in -TrainFolds for training. -It returns in P the learned probabilistic program.
-
 nl3(+Module:atom) is det
The predicate prints a newline if the verbosity is at least 3. -Module is used to get the verbosity setting.
-
 equality(++Environment:int, ++Variable:int, ++Value:int, --BDD:int) is det
Returns in BDD the BDD belonging to environment Environment -that represents the equation Variable=Value.
-
 format3(+Module:atom, +Format, :Arguments) is det
The predicate calls format(Format,Arguments) if the verbosity is at least 3. +
 add_sum(++Environment:int, ++ADD1:int, ++ADD2:int, --ADDOut:int) is det
Computes the sum of the two ADDs ADD1 ADD2 belonging to environment Environment. +The result in saved in ADDOut.
+
 generate_clauses_bg(+Rules:list, -Clauses:list) is det
The predicate generate clauses to be +asserted in the database for the rules from the background. +Rules is a list of term of the form def_rule(H,BodyList,_Lit). +Clauses is a list of clauses to be asserted.
+
 add_abd_var(++Environment:int, ++ProbabilityDistribution:list, ++Rule:int, -Variable:int) is det
Returns in Variable the index of a new abducible random variable in Environment with +NumberOHeads values and probability distribution ProbabilityDistribution.
+
 bdd_not(++Environment:int, ++A:int, --NotA:int) is det
Returns in NotA a pointer to a BDD belonging to environment Environment +representing the negation of BDD A.
+
 list2and(+List:list, -And:term) is det
+
list2and(-List:list, +And:term) is det
The predicate succeeds when And is a conjunction (using the , operator) +of the terms in List
+
 end_ex(++Environment:int) is det
Terminates the evnironment data structure for storing a BDD. +Environment is a pointer to a data structure returned by init_ex/2. +It frees the memory occupied by the BDD.
+
 add_decision_var(++Environment:int, ++Rule:int, -Variable:int) is det
Returns in Variable the index of a new decision variable in Environment
+
 init_em(--Context:int) is det
Initializes a data structure for performing parameter learning. +It returns an integer in Context that is a pointer to a +context data structure for performing the EM algorithm.
+
 dirichlet_sample(++Alpha:list, --Value:list) is det
Returns a Value sampled from a Dirichlet distribution with parameters Alpha. +Alpha and Value are lists of floating point numbers of the same length.
+
 induce_par(:TrainFolds:list_of_atoms, -P:probabilistic_program) is det
The predicate learns the parameters of the program stored in the in/1 fact +of the input file using the folds indicated in TrainFolds for training. +It returns in P the input program with the updated parameters.
+
 test_prob(:P:probabilistic_program, +TestFolds:list_of_atoms, -NPos:int, -NNeg:int, -LL:float, -Results:list) is det
The predicate takes as input in P a probabilistic program, +tests P on the folds indicated in TestFolds and returns +the number of positive examples in NPos, the number of negative examples +in NNeg, the log likelihood in LL +and in Results a list containing the probabilistic result for each query contained in TestFolds.
+
 rand_seed(+Seed:int) is det
The pseudo-random number generator is initialized using the argument passed as Seed. +It calls the C function srand.
+
 make_query_var(++Environment:int, +Variable:int, --BDD:int) is det
Makes Variable belonging to Environment a query random variable for MAP inference. +Returns in BDD the diagram of the formula encoding the required constraints among the +Boolean random variable that represent Variable.
+
 ret_map_prob(++Environment:int, ++BDD:int, -Probability:float, -MAPState:list) is det
Returns the MAP state MPAState of BDD and its Probability. +BDD belongs to environment Environment.
+
 write3(+Module:atom, +Message:term) is det
The predicate calls write(Message) if the verbosity is at least 3. Module is used to get the verbosity setting.
-
 add_query_var(++Environment:int, ++ProbabilityDistribution:list, ++Rule:int, -Variable:int) is det
Returns in Variable the index of a new random variable to be queried in MAP inference with -NumberOHeads values and probability distribution ProbabilityDistribution. -The variable belongs to Environment.
-
- -

Undocumented predicates

- -

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

- -
-
 add_decision_var(Arg1, Arg2, Arg3)
-
 dirichlet_sample(Arg1, Arg2)
-
 zeroc(Arg1, Arg2)
-
 ret_strategy(Arg1, Arg2, Arg3, Arg4)
-
 probability_dd(Arg1, Arg2, Arg3)
-
 symmetric_dirichlet_sample(Arg1, Arg2, Arg3)
-
 gamma_sample(Arg1, Arg2, Arg3)
-
 bdd_notc(Arg1, Arg2, Arg3)
-
 onec(Arg1, Arg2)
-
 debug_cudd_var(Arg1, Arg2)
-
 discrete_sample(Arg1, Arg2)
-
 gauss_sample(Arg1, Arg2, Arg3)
-
 or_list(Arg1, Arg2, Arg3)
-
 andcnf(Arg1, Arg2, Arg3, Arg4)
-
 equalityc(Arg1, Arg2, Arg3, Arg4)
-
 add_prod(Arg1, Arg2, Arg3, Arg4)
-
 initial_values(Arg1, Arg2)
-
 uniform_sample(Arg1)
-
 or_listc(Arg1, Arg2, Arg3)
-
 ret_probc(Arg1, Arg2, Arg3)
-
 andc(Arg1, Arg2, Arg3, Arg4)
-
 add_sum(Arg1, Arg2, Arg3, Arg4)
+
 andcnf(++Environment:int, ++A:couple, ++B:couple, --AandB:couple) is semidet
A and B are couples (Environment, BDDA) and (Environment, BDDB) respectively +Returns in AandB a couple (Environment, BDDAandB) where BDDAandB is pointer to a BDD belonging to environment Environment +representing the conjunction of BDDs BDDA and BDDB.
+
 remove_duplicates(+List1:list, -List2:list) is det
Removes duplicates from List1. Equality is checked with ==.
+
 or(++Environment:int, ++A:int, ++B:int, --AorB:int) is det
Returns in AorB a pointer to a BDD belonging to environment Environment +representing the disjunction of BDDs A and B.
+
 tab(+Module:atom, +PredSpec:pred_spec, -TableSpec:term) is det
Records the fact that predicate PredSpec must be tabled and returns +the necessary term for the tabling directive in TableSpec. +Module is used to store the information in the correct module
+
 generate_clauses(+Rules0:list, +Module:atom, +StartingIndex:integer, -Rules:list, +Clauses:list, -ClausesOut:list) is det
The predicate generate the internal representation of rules to produce clauses to be +asserted in the database. +Rules0 is a list of term of the form rule(R,HeadList,BodyList,Lit,Tun). +Rules is a list of terms of the form +rule(N,HeadList,BodyList,Lit,Tun) where N is +an increasing index starting from StartingIndex. +ClausesOut/Clauses is a difference list of clauses to be asserted.
+
 extract_fancy_vars(+Term:term, -Vars:list) is nondet
Given Term, it returns the list of all of its variables +in the form 'VN'=Var where VN is an atom with N an increasing integer +starting from 1 and Var a variable in Term.
+
 ret_strategy(++Environment:int, ++ADD:int, --Decision:list, --Cost:int) is det
Computes the optimal strategy given a pointer to the ADD belonging to environment Environment. +Decision is a list of selected facts, Cost is the total cost.
+
 add_var(++Environment:int, ++ProbabilityDistribution:list, ++Rule:int, -Variable:int) is det
Returns in Variable the index of a new random variable in Environment with +NumberOHeads values and probability distribution ProbabilityDistribution.
diff --git a/docs/pldoc/mcintyre.html b/docs/pldoc/mcintyre.html index 8f27ad5..be4e463 100644 --- a/docs/pldoc/mcintyre.html +++ b/docs/pldoc/mcintyre.html @@ -438,6 +438,158 @@

mcintyre.pl -- mcintyre

This is a predicate for programs in the PRISM syntax
 swap(?Term1:term, ?Term2:term) is det
If Term1 is of the form A:B, then Term2 is of the form B:A.
 :Term:term ~= +B:term is det
equality predicate for distributional clauses
+
 to_pair(+Pair:pair, -FlattenedPair:pair) is det
Given a pair E-W, returns a pair Ep-W where +Ep=EE if E=[EE], otherwise Ep=E
+
 density(+List:list, -Chart:dict) is det
Equivalent to density/3 with an empty option list.
+
 histogram(+List:list, -Chart:dict) is det
Equivalent to histogram/3 with an empty option list.
+
 bar(+Probability:float, -Chart:dict) is det
The predicate returns a dict for rendering with c3 as a bar chart with +a bar for the probability and a bar for one minus the probability.
+
 std_dev(+Values:list, -Dev:float) is det
Computes the standard deviation of Values. +Values can be + +
+
 beta(+Alphas:list, -Beta:float) is det
Computes the value of the multivariate beta function for vector Alphas +https://en.wikipedia.org/wiki/Beta_function#Multivariate_beta_function +Alphas is a list of floats
+
 key_pair(+Pair:pair, -Key:term) is det
Given a pair Key-Vaule, returns its first element Key
+
 density(+List:list, -Chart:dict, +Options:list) is det
Draws a line chart of the density of a sets of samples. +The samples are in List +as pairs [V]-W or V-W where V is a value and W its weigth. + +

+Options is a list of options, the following are recognised by density/3:

+ +
+
min(+Min:float)
the minimum value of domain, default value the minimum in List
+
max(+Max:float)
the maximum value of domain, default value the maximum in List
+
nbins(+NBins:int)
the number of bins for dividing the domain, default value 40
+
+ +
+
 histogram(+List:list, -Chart:dict, +Options:list) is det
Draws a histogram of the samples in List. List must be a list of pairs of the form [V]-W or V-W +where V is a sampled value and W is its weight, or a list of values. + +

+Options is a list of options, the following are recognised by histogram/3:

+ +
+
min(+Min:float)
the minimum value of domain, default value the minimum in List
+
max(+Max:float)
the maximum value of domain, default value the maximum in List
+
nbins(+NBins:int)
the number of bins for dividing the domain, default value 40
+
+ +
+
 bar(+Successes:int, +Failures:int, -Chart:dict) is det
The predicate returns a dict for rendering with c3 as a bar chart with +a bar for the number of successes and a bar for the number of failures
+
 to_atom(+In:pair, -Out:pair) is det
Given In=A0-N, to_atom/2 returns Out=A-N +where A is an atom representing A0
+
 std_dev(+Values:list, -Average:float, -Dev:float) is det
Computes the standard deviation and the average of Values. +Values can be + +
+
 average(+Values:list, -Average:float) is det
Computes the average of Values. +Values can be + +
+
 value_pair(+Pair:pair, -Value:term) is det
Given a pair Key-Vaule, returns its second element Value
+
 density2d(+List:list, -Dens:list) is det
Equivalent to density2d/3 with an empty option list.
+
 densities(+PriorList:list, +PostList:list, -Chart:dict) is det
Equivalent to densities/4 with an empty option list.
+
 bar1(+Probability:float, -Chart:dict) is det
The predicate returns a dict for rendering with c3 as a bar chart with +a bar for the probability
+
 agg_val(+Couple:atom, +PartialSum:number, -Sum:number) is det
Aggregate values by summation. The first argument is a couple _-N with +N the new value to sum to PartialSum
+
 variance(+Values:list, -Variance:float) is det
Computes the variance of Values. +Values can be + +
+
 density2d(+List:list, -Dens:list, +Options:list) is det
Returns a set of 3-dimensional points representing the plot of the +density of a sets of 2-dimensional samples. +The samples are in List +as pairs [X,Y]-W where (X,Y) is a point and W its weigth. + +

+Options is a list of options, the following are recognised by density2d/3:

+ +
+
xmin(+XMin:float)
the minimum value of the X domain, default value the minimum in List
+
xmax(-XMax:float)
the maximum value of the X domain, default value the maximum in List
+
ymin(-YMin:float)
the minimum value of the Y domain, default value the minimum in List
+
ymax(-YMax:float)
the maximum value of the Y domain, default value the maximum in List
+
nbins(+NBins:int)
the number of bins for dividing the X and Y domains, default value 40
+
+ +
+
 bin(+N:int, +Values:list, +Lower:number, +BinWidth:number, -Couples:list) is det
Given a list of numeric Values, a Lower value and BinWidth, returns in Couples +a list of N pairs V-Freq where V is the midpoint of a bin and Freq is the number +of values that are inside the bin interval [V-BinWidth/2,V+BinWidth/2) +starting with the bin where V-BinWidth/2=Lower
+
 dump(+Target, -NewVars, -Constraints) is det
Returns in Constraints, the constraints that currently hold on +Target where all variables in Target are copied to new variables in +NewVars and the constraints are given on these new variables. In +short, you can safely manipulate NewVars and Constraints without +changing the constraints on Target.
+
 argbar(+Values:list, -Chart:dict) is det
Values is a list of pairs V-N where +V is the value and N is the number of samples +returning that value. +The predicate returns a dict for rendering with c3 as a bar chart with +a bar for each value V. +The size of the bar is given by N.
+
 densities(+PriorList:list, +PostList:list, -Chart:dict, +Options:list) is det
Draws a line chart of the density of two sets of samples, usually +prior and post observations. The samples from the prior are in PriorList +while the samples from the posterior are in PostList. +PriorList and PostList must be lists of pairs of the form [V]-W or V-W +where V is a sampled value and W is its weight, or lists of values V. +Options is a list of options, the following are recognised by histogram/3: + +
+
nbins(+NBins:int)
the number of bins for dividing the domain, default value 40 +*/
+
+ +
+
 variance(+Values:list, -Average:float, -Variance:float) is det
Computes the variance the average of Values. +Values can be + +
+
 swi_builtin(+Goal:atom) is det
Succeeds if Goal is an atom whose predicate is defined in Prolog +(either builtin or defined in a standard library).

Re-exported predicates

@@ -446,8 +598,158 @@

Re-exported predicates

The following predicates are exported from this file while their implementation is defined in imported modules or non-module files loaded by this module.

+
 to_pair(+Pair:pair, -FlattenedPair:pair) is det
Given a pair E-W, returns a pair Ep-W where +Ep=EE if E=[EE], otherwise Ep=E
+
 density(+List:list, -Chart:dict) is det
Equivalent to density/3 with an empty option list.
+
 histogram(+List:list, -Chart:dict) is det
Equivalent to histogram/3 with an empty option list.
 bar(+Probability:float, -Chart:dict) is det
The predicate returns a dict for rendering with c3 as a bar chart with a bar for the probability and a bar for one minus the probability.
+
 std_dev(+Values:list, -Dev:float) is det
Computes the standard deviation of Values. +Values can be +
    +
  • a list of numbers
  • +
  • a list of pairs number-weight, in which case each number is multiplied by the weight +before being considered
  • +
  • a list of pairs list-weight, in which case list is considered as a matrix of numbers. +The matrix in each element of List must have the same dimension and are aggregated element- +wise
  • +
+
+
 beta(+Alphas:list, -Beta:float) is det
Computes the value of the multivariate beta function for vector Alphas +https://en.wikipedia.org/wiki/Beta_function#Multivariate_beta_function +Alphas is a list of floats
+
 key_pair(+Pair:pair, -Key:term) is det
Given a pair Key-Vaule, returns its first element Key
+
 density(+List:list, -Chart:dict, +Options:list) is det
Draws a line chart of the density of a sets of samples. +The samples are in List +as pairs [V]-W or V-W where V is a value and W its weigth. + +

+Options is a list of options, the following are recognised by density/3:

+ +
+
min(+Min:float)
the minimum value of domain, default value the minimum in List
+
max(+Max:float)
the maximum value of domain, default value the maximum in List
+
nbins(+NBins:int)
the number of bins for dividing the domain, default value 40
+
+ +
+
 histogram(+List:list, -Chart:dict, +Options:list) is det
Draws a histogram of the samples in List. List must be a list of pairs of the form [V]-W or V-W +where V is a sampled value and W is its weight, or a list of values. + +

+Options is a list of options, the following are recognised by histogram/3:

+ +
+
min(+Min:float)
the minimum value of domain, default value the minimum in List
+
max(+Max:float)
the maximum value of domain, default value the maximum in List
+
nbins(+NBins:int)
the number of bins for dividing the domain, default value 40
+
+ +
+
 bar(+Successes:int, +Failures:int, -Chart:dict) is det
The predicate returns a dict for rendering with c3 as a bar chart with +a bar for the number of successes and a bar for the number of failures
+
 to_atom(+In:pair, -Out:pair) is det
Given In=A0-N, to_atom/2 returns Out=A-N +where A is an atom representing A0
+
 std_dev(+Values:list, -Average:float, -Dev:float) is det
Computes the standard deviation and the average of Values. +Values can be +
    +
  • a list of numbers
  • +
  • a list of pairs number-weight, in which case each number is multiplied by the weight +before being considered
  • +
  • a list of pairs list-weight, in which case list is considered as a matrix of numbers. +The matrix in each element of List must have the same dimension and are aggregated element- +wise
  • +
+
+
 average(+Values:list, -Average:float) is det
Computes the average of Values. +Values can be +
    +
  • a list of numbers
  • +
  • a list of pairs number-weight, in which case each number is multiplied by the weight +before being summed
  • +
  • a list of lists, in which case lists are considered as matrices of numbers and averaged +element-wise
  • +
  • a list of pairs list-weight, in which case the list is considered as a matrix of numbers. +The matrix in each element of List must have the same dimension and are aggregated element- +wise
  • +
+
+
 value_pair(+Pair:pair, -Value:term) is det
Given a pair Key-Vaule, returns its second element Value
+
 density2d(+List:list, -Dens:list) is det
Equivalent to density2d/3 with an empty option list.
+
 densities(+PriorList:list, +PostList:list, -Chart:dict) is det
Equivalent to densities/4 with an empty option list.
+
 bar1(+Probability:float, -Chart:dict) is det
The predicate returns a dict for rendering with c3 as a bar chart with +a bar for the probability
+
 agg_val(+Couple:atom, +PartialSum:number, -Sum:number) is det
Aggregate values by summation. The first argument is a couple _-N with +N the new value to sum to PartialSum
+
 variance(+Values:list, -Variance:float) is det
Computes the variance of Values. +Values can be +
    +
  • a list of numbers
  • +
  • a list of pairs number-weight, in which case each number is multiplied by the weight +before being considered
  • +
  • a list of pairs list-weight, in which case list is considered as a matrix of numbers. +The matrix in each element of List must have the same dimension and are aggregated element- +wise
  • +
+
+
 density2d(+List:list, -Dens:list, +Options:list) is det
Returns a set of 3-dimensional points representing the plot of the +density of a sets of 2-dimensional samples. +The samples are in List +as pairs [X,Y]-W where (X,Y) is a point and W its weigth. + +

+Options is a list of options, the following are recognised by density2d/3:

+ +
+
xmin(+XMin:float)
the minimum value of the X domain, default value the minimum in List
+
xmax(-XMax:float)
the maximum value of the X domain, default value the maximum in List
+
ymin(-YMin:float)
the minimum value of the Y domain, default value the minimum in List
+
ymax(-YMax:float)
the maximum value of the Y domain, default value the maximum in List
+
nbins(+NBins:int)
the number of bins for dividing the X and Y domains, default value 40
+
+ +
+
 bin(+N:int, +Values:list, +Lower:number, +BinWidth:number, -Couples:list) is det
Given a list of numeric Values, a Lower value and BinWidth, returns in Couples +a list of N pairs V-Freq where V is the midpoint of a bin and Freq is the number +of values that are inside the bin interval [V-BinWidth/2,V+BinWidth/2) +starting with the bin where V-BinWidth/2=Lower
+
 dump(+Target, -NewVars, -Constraints) is det
Returns in Constraints, the constraints that currently hold on +Target where all variables in Target are copied to new variables in +NewVars and the constraints are given on these new variables. In +short, you can safely manipulate NewVars and Constraints without +changing the constraints on Target.
+
 argbar(+Values:list, -Chart:dict) is det
Values is a list of pairs V-N where +V is the value and N is the number of samples +returning that value. +The predicate returns a dict for rendering with c3 as a bar chart with +a bar for each value V. +The size of the bar is given by N.
+
 densities(+PriorList:list, +PostList:list, -Chart:dict, +Options:list) is det
Draws a line chart of the density of two sets of samples, usually +prior and post observations. The samples from the prior are in PriorList +while the samples from the posterior are in PostList. +PriorList and PostList must be lists of pairs of the form [V]-W or V-W +where V is a sampled value and W is its weight, or lists of values V. +Options is a list of options, the following are recognised by histogram/3: + +
+
nbins(+NBins:int)
the number of bins for dividing the domain, default value 40 +*/
+
+ +
+
 variance(+Values:list, -Average:float, -Variance:float) is det
Computes the variance the average of Values. +Values can be +
    +
  • a list of numbers
  • +
  • a list of pairs number-weight, in which case each number is multiplied by the weight +before being considered
  • +
  • a list of pairs list-weight, in which case list is considered as a matrix of numbers. +The matrix in each element of List must have the same dimension and are aggregated element- +wise
  • +
+
+
 swi_builtin(+Goal:atom) is det
Succeeds if Goal is an atom whose predicate is defined in Prolog +(either builtin or defined in a standard library).

Undocumented predicates

@@ -456,43 +758,18 @@

Undocumented predicates

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

-
 bar1(Arg1, Arg2)
-
 sup(Arg1, Arg2, Arg3, Arg4)
-
 minimize(Arg1)
-
 agg_val(Arg1, Arg2, Arg3)
-
 average(Arg1, Arg2)
-
 value_pair(Arg1, Arg2)
-
 density2d(Arg1, Arg2)
-
 entailed(Arg1)
-
 densities(Arg1, Arg2, Arg3)
-
 bar(Arg1, Arg2, Arg3)
-
 sup(Arg1, Arg2)
-
 maximize(Arg1)
-
 swi_builtin(Arg1)
-
 to_atom(Arg1, Arg2)
-
 key_pair(Arg1, Arg2)
-
 density(Arg1, Arg2, Arg3)
+
 bb_inf(Arg1, Arg2, Arg3, Arg4, Arg5)
 ordering(Arg1)
-
 histogram(Arg1, Arg2, Arg3)
-
 histogram(Arg1, Arg2)
+
 sup(Arg1, Arg2)
 inf(Arg1, Arg2, Arg3, Arg4)
-
 bb_inf(Arg1, Arg2, Arg3, Arg4, Arg5)
-
 std_dev(Arg1, Arg2)
-
 variance(Arg1, Arg2, Arg3)
-
 beta(Arg1, Arg2)
-
 {Arg1}
-
 to_pair(Arg1, Arg2)
-
 density(Arg1, Arg2)
-
 dump(Arg1, Arg2, Arg3)
-
 argbar(Arg1, Arg2)
-
 bb_inf(Arg1, Arg2, Arg3)
+
 sup(Arg1, Arg2, Arg3, Arg4)
+
 entailed(Arg1)
 inf(Arg1, Arg2)
-
 std_dev(Arg1, Arg2, Arg3)
-
 variance(Arg1, Arg2)
-
 bin(Arg1, Arg2, Arg3, Arg4, Arg5)
-
 density2d(Arg1, Arg2, Arg3)
-
 densities(Arg1, Arg2, Arg3, Arg4)
 clp_type(Arg1, Arg2)
+
 bb_inf(Arg1, Arg2, Arg3)
+
 minimize(Arg1)
+
 {Arg1}
+
 maximize(Arg1)
diff --git a/docs/pldoc/pita.html b/docs/pldoc/pita.html index af6adca..47f7a2d 100644 --- a/docs/pldoc/pita.html +++ b/docs/pldoc/pita.html @@ -98,61 +98,432 @@

pita.pl -- pita

 setting_pita(:Parameter:atom, ?Value:term) is det
The predicate returns the value of a parameter For a list of parameters see https://friguzzi.github.io/cplint/
- - -

Re-exported predicates

- -

-The following predicates are exported from this file while their implementation is defined in imported modules or non-module files loaded by this module.

- -
+
 symmetric_dirichlet_sample(++Alpha:float, ++K:int, --Value:list) is det
Returns a Value sampled from a symmetric Dirichlet distribution with parameter Alpha. +K is the number of dimensions of the result.
+
 to_pair(+Pair:pair, -FlattenedPair:pair) is det
Given a pair E-W, returns a pair Ep-W where +Ep=EE if E=[EE], otherwise Ep=E
+
 and(++Environment:int, ++A:int, ++B:int, --AandB:int) is det
Returns in AandB a pointer to a BDD belonging to environment Environment +representing the conjunction of BDDs A and B.
+
 density(+List:list, -Chart:dict) is det
Equivalent to density/3 with an empty option list.
+
 end_em(++Context:int) is det
Terminates the context data structure for performing parameter learning. +Context is a pointer to a context data structure for performing +the EM algorithm. +Context must have been returned by a call to init_em/1. +It frees the memory occupied by Context.
+
 gamma_sample(++Shape:float, ++Scale:float, --Value:float) is det
Returns a Value sampled from a gamma distribution with parameters Shape and Scale
+
 histogram(+List:list, -Chart:dict) is det
Equivalent to histogram/3 with an empty option list.
+
 equalityc(++Environment:int, ++Variable:int, ++Value:int, --EBDD:couple) is det
Returns in EBDD a couple (Environment,BDD) where BDD belongs to environment Environment +and represents the equation Variable=Value.
+
 create_dot(++Env:int, ++BDD:int, ++File:string) is det
The predicate writes the BDD in dot format to +to file FileName.
+
 bar(+Probability:float, -Chart:dict) is det
The predicate returns a dict for rendering with c3 as a bar chart with +a bar for the probability and a bar for one minus the probability.
+
 ret_probc(++Environment:int, ++EBDD:couple, -Probability:float) is det
EBDD is a couple (Environment,BDD) +Returns the Probability of BDD belonging to environment Environment +Uses
+
 andc(++Environment:int, ++A:couple, ++B:couple, --AandB:couple) is semidet
A and B are couples (Environment, BDDA) and (Environment, BDDB) respectively +Returns in AandB a couple (Environment, BDDAandB) where BDDAandB is pointer to a BDD belonging to environment Environment +representing the conjunction of BDDs BDDA and BDDB. +fails if BDDB represents the zero function
+
 equality(++Environment:int, ++Variable:int, ++Value:int, --BDD:int) is det
Returns in BDD the BDD belonging to environment Environment +that represents the equation Variable=Value.
+
 std_dev(+Values:list, -Dev:float) is det
Computes the standard deviation of Values. +Values can be +
    +
  • a list of numbers
  • +
  • a list of pairs number-weight, in which case each number is multiplied by the weight +before being considered
  • +
  • a list of pairs list-weight, in which case list is considered as a matrix of numbers. +The matrix in each element of List must have the same dimension and are aggregated element- +wise
  • +
+
+
 debug_cudd_var(++Environment:int, -Variable:out) is det
Prints the debug information which is the result of the call +of Cudd_ReadDead, Cudd_CheckZeroRef, Cudd_CheckKeys and +Cudd_DebugCheck(env->mgr));
+
 add_query_var(++Environment:int, ++ProbabilityDistribution:list, ++Rule:int, -Variable:int) is det
Returns in Variable the index of a new random variable to be queried in MAP inference with +NumberOHeads values and probability distribution ProbabilityDistribution. +The variable belongs to Environment.
+
 beta(+Alphas:list, -Beta:float) is det
Computes the value of the multivariate beta function for vector Alphas +https://en.wikipedia.org/wiki/Beta_function#Multivariate_beta_function +Alphas is a list of floats
+
 probability_dd(++Environment:int, ++BDD:int, --ADD:int) is det
Converts the BDD belonging to environment Environment into an ADD.
 zero(++Environment:int, --Zero:int) is det
Returns in Zero a pointer to a BDD belonging to environment Environment representing the zero Boolean function.
+
 key_pair(+Pair:pair, -Key:term) is det
Given a pair Key-Vaule, returns its first element Key
+
 discrete_sample(++Theta:list, --Value:int) is det
Returns a Value sampled from a discrete distribution with parameters Theta. +Theta is a list of floating point numbers in [0,1] that sum to 1. +Value is in 0..(length(Theta)-1)
 init(--Environment:int) is det
Initializes a data structure for storing a single BDD. Returns an integer Environment that is a pointer to a data structure for storing a single BDD to be used for inference only (no learning).
-
 rand_seed(+Seed:int) is det
The pseudo-random number generator is initialized using the argument passed as Seed. -It calls the C function srand.
-
 make_query_var(++Environment:int, +Variable:int, --BDD:int) is det
Makes Variable belonging to Environment a query random variable for MAP inference. -Returns in BDD the diagram of the formula encoding the required constraints among the -Boolean random variable that represent Variable.
+
 density(+List:list, -Chart:dict, +Options:list) is det
Draws a line chart of the density of a sets of samples. +The samples are in List +as pairs [V]-W or V-W where V is a value and W its weigth. + +

+Options is a list of options, the following are recognised by density/3:

+ +
+
min(+Min:float)
the minimum value of domain, default value the minimum in List
+
max(+Max:float)
the maximum value of domain, default value the maximum in List
+
nbins(+NBins:int)
the number of bins for dividing the domain, default value 40
+
+ +
+
 gauss_sample(++Mean:float, ++Variance:float, --Value:float) is det
Returns a Value sampled from a Gaussian distribution with parameters Mean and Variance
+
 histogram(+List:list, -Chart:dict, +Options:list) is det
Draws a histogram of the samples in List. List must be a list of pairs of the form [V]-W or V-W +where V is a sampled value and W is its weight, or a list of values. + +

+Options is a list of options, the following are recognised by histogram/3:

+ +
+
min(+Min:float)
the minimum value of domain, default value the minimum in List
+
max(+Max:float)
the maximum value of domain, default value the maximum in List
+
nbins(+NBins:int)
the number of bins for dividing the domain, default value 40
+
+ +
+
 create_dot_string(++Env:int, ++BDD:int, -Dot:string) is det
The predicate returns the BDD in dot format.
+
 bar(+Successes:int, +Failures:int, -Chart:dict) is det
The predicate returns a dict for rendering with c3 as a bar chart with +a bar for the number of successes and a bar for the number of failures
+
 to_atom(+In:pair, -Out:pair) is det
Given In=A0-N, to_atom/2 returns Out=A-N +where A is an atom representing A0
+
 or_list(++ListOfBDDs:list, ++Environment, --BDD:int) is det
Returns in BDD a pointer to a BDD belonging to environment Environment +representing the disjunction of all the BDDs in ListOfBDDs
 orc(++A:couple, ++B:couple, --AorB:couple) is det
A and B are couples (Environment, BDDA) and (Environment, BDDB) respectively Returns in AorB a couple (Environment, BDDAorB) where BDDAorB is pointer to a BDD belonging to environment Environment representing the disjunction of BDDs BDDA and BDDB.
+
 zeroc(++Environment:int, --Zero:couple) is det
Returns in Zero a couple (Environment,BDD) where BDD is pointer to a BDD belonging to environment Environment +representing the zero Boolean function
+
 add_prod(++Environment:int, ++ADDIn:int, ++Utility:float, --ADDOut:int) is det
Multiplies the ADD belonging to environment Environment +with the value Utility and stores the result in ADDOut.
+
 std_dev(+Values:list, -Average:float, -Dev:float) is det
Computes the standard deviation and the average of Values. +Values can be +
    +
  • a list of numbers
  • +
  • a list of pairs number-weight, in which case each number is multiplied by the weight +before being considered
  • +
  • a list of pairs list-weight, in which case list is considered as a matrix of numbers. +The matrix in each element of List must have the same dimension and are aggregated element- +wise
  • +
+
+
 ret_prob(++Environment:int, ++BDD:int, -Probability:float) is det
Returns the Probability of BDD belonging to environment Environment.
+
 average(+Values:list, -Average:float) is det
Computes the average of Values. +Values can be +
    +
  • a list of numbers
  • +
  • a list of pairs number-weight, in which case each number is multiplied by the weight +before being summed
  • +
  • a list of lists, in which case lists are considered as matrices of numbers and averaged +element-wise
  • +
  • a list of pairs list-weight, in which case the list is considered as a matrix of numbers. +The matrix in each element of List must have the same dimension and are aggregated element- +wise
  • +
+
 ret_abd_prob(++Environment:int, ++BDD:int, -Probability:float, -Explanation:list) is det
Returns the abductive Explanation of BDD and its Probability. BDD belongs to environment Environment.
-
 ret_prob(++Environment:int, ++BDD:int, -Probability:float) is det
Returns the Probability of BDD belonging to environment Environment.
+
 value_pair(+Pair:pair, -Value:term) is det
Given a pair Key-Vaule, returns its second element Value
+
 end(++Environment:int) is det
Terminates the environment data structure for storing a single BDD. +Environment is a pointer to a data structure returned by a call +to init/1.
 one(++Environment:int, --One:int) is det
Returns in One a pointer to a BDD belonging to environment Environment representing the one Boolean function.
+
 em(++Context:int, ++RuleInfo:list, ++ListOfBDDs:list, ++EA:float, ++ER:float, ++Iterations:int, -LL:float, -Parameters:list, -ExampleProbabilities:list) is det
NumberOfHeads is a list of terms, one for each rule. Each term is either +an integer, indicating the number +of head atoms in the rule, or a list [N] where N +is the number of head atoms. In the first case, the parameters of the rule are tunable, +in the latter they are fixed. + +

+Performs EM learning. +Takes as input the Context, information on the rules, +a list of BDDs each representing one example, +the minimum absolute difference EA and relative difference ER between the +log likelihood of examples in two different iterations and the maximum number of iterations +Iterations. +RuleInfo is a list of elements, one for each rule, with are either

+
    +
  • an integer, indicating the number of heads, in which case the parameters of the +corresponding rule should be randomized,
  • +
  • a list of floats, in which case the parameters should be set to those indicated +in the list and not changed during learning (fixed parameters)
  • +
  • [a list of floats], in which case the initial values of the parameters should +be set to those indicated +in the list and changed during learning (initial values of the parameters) +Returns the final log likelihood of examples LL, the list of new Parameters +and a list with the final probabilities of each example. +Parameters is a list whose elements are of the form [N,P] where N is the rule +number and P is a list of probabilities, one for each head atom of rule N, +in reverse order.
  • +
+
+
 density2d(+List:list, -Dens:list) is det
Equivalent to density2d/3 with an empty option list.
+
 initial_values(++Environment:int, ++Alpha:float) is det
Sets the type of parameter initialization for EM on Environment: +if Alpha is 0.0, it uses a truncated Dirichlet process +if Alpha is a float > 0.0, it uses a symmetric Dirichlet distribution +with that value as parameter
 init_ex(++Context:int, --Environment:int) is det
Initializes an enviroment data structure for storing a BDD. Context is an integer that is a pointer to a context data structure created using init_em/1. Returns an integer Environment that is a pointer to a data structure for storing a single BDD to be used for the EM algorithm.
-
 create_dot(++Env:int, ++BDD:int, ++File:string) is det
The predicate writes the BDD in dot format to -to file FileName.
+
 densities(+PriorList:list, +PostList:list, -Chart:dict) is det
Equivalent to densities/4 with an empty option list.
+
 uniform_sample(--Value:float) is det
Returns a Value sampled from a uniform distribution in [0,1]
+
 or_listc(++ListOfBDDs:list, ++Environment, --BDD:int) is det
Returns in BDD a couple (Env,B) with B a pointer to a +BDD belonging to environment Environment +representing the disjunction of all the BDDs in +ListOfBDDs (a list of couples (Env,BDD))
+
 bar1(+Probability:float, -Chart:dict) is det
The predicate returns a dict for rendering with c3 as a bar chart with +a bar for the probability
+
 bdd_notc(++Environment:int, ++EBDD:couple, --NotEBDD:couple) is det
EBDD is a couple (Environment,A) +Returns in NotEBDD a couple (Environment,NotA) where NotA is +pointer to a BDD belonging to environment Environment +representing the negation of BDD A
+
 onec(++Environment:int, --One:couple) is det
Returns in One a couple (Environment,BDD) where BDD is pointer to a BDD belonging to environment Environment +representing the one Boolean function
+
 agg_val(+Couple:atom, +PartialSum:number, -Sum:number) is det
Aggregate values by summation. The first argument is a couple _-N with +N the new value to sum to PartialSum
+
 add_sum(++Environment:int, ++ADD1:int, ++ADD2:int, --ADDOut:int) is det
Computes the sum of the two ADDs ADD1 ADD2 belonging to environment Environment. +The result in saved in ADDOut.
 add_abd_var(++Environment:int, ++ProbabilityDistribution:list, ++Rule:int, -Variable:int) is det
Returns in Variable the index of a new abducible random variable in Environment with NumberOHeads values and probability distribution ProbabilityDistribution.
+
 variance(+Values:list, -Variance:float) is det
Computes the variance of Values. +Values can be +
    +
  • a list of numbers
  • +
  • a list of pairs number-weight, in which case each number is multiplied by the weight +before being considered
  • +
  • a list of pairs list-weight, in which case list is considered as a matrix of numbers. +The matrix in each element of List must have the same dimension and are aggregated element- +wise
  • +
+
 bdd_not(++Environment:int, ++A:int, --NotA:int) is det
Returns in NotA a pointer to a BDD belonging to environment Environment representing the negation of BDD A.
-
 end(++Environment:int) is det
Terminates the environment data structure for storing a single BDD. -Environment is a pointer to a data structure returned by a call -to init/1.
-
 bar(+Probability:float, -Chart:dict) is det
The predicate returns a dict for rendering with c3 as a bar chart with -a bar for the probability and a bar for one minus the probability.
-
 or(++Environment:int, ++A:int, ++B:int, --AorB:int) is det
Returns in AorB a pointer to a BDD belonging to environment Environment -representing the disjunction of BDDs A and B.
 end_ex(++Environment:int) is det
Terminates the evnironment data structure for storing a BDD. Environment is a pointer to a data structure returned by init_ex/2. It frees the memory occupied by the BDD.
-
 create_dot_string(++Env:int, ++BDD:int, -Dot:string) is det
The predicate returns the BDD in dot format.
+
 add_decision_var(++Environment:int, ++Rule:int, -Variable:int) is det
Returns in Variable the index of a new decision variable in Environment
 init_em(--Context:int) is det
Initializes a data structure for performing parameter learning. It returns an integer in Context that is a pointer to a context data structure for performing the EM algorithm.
+
 density2d(+List:list, -Dens:list, +Options:list) is det
Returns a set of 3-dimensional points representing the plot of the +density of a sets of 2-dimensional samples. +The samples are in List +as pairs [X,Y]-W where (X,Y) is a point and W its weigth. + +

+Options is a list of options, the following are recognised by density2d/3:

+ +
+
xmin(+XMin:float)
the minimum value of the X domain, default value the minimum in List
+
xmax(-XMax:float)
the maximum value of the X domain, default value the maximum in List
+
ymin(-YMin:float)
the minimum value of the Y domain, default value the minimum in List
+
ymax(-YMax:float)
the maximum value of the Y domain, default value the maximum in List
+
nbins(+NBins:int)
the number of bins for dividing the X and Y domains, default value 40
+
+ +
+
 dirichlet_sample(++Alpha:list, --Value:list) is det
Returns a Value sampled from a Dirichlet distribution with parameters Alpha. +Alpha and Value are lists of floating point numbers of the same length.
+
 bin(+N:int, +Values:list, +Lower:number, +BinWidth:number, -Couples:list) is det
Given a list of numeric Values, a Lower value and BinWidth, returns in Couples +a list of N pairs V-Freq where V is the midpoint of a bin and Freq is the number +of values that are inside the bin interval [V-BinWidth/2,V+BinWidth/2) +starting with the bin where V-BinWidth/2=Lower
+
 rand_seed(+Seed:int) is det
The pseudo-random number generator is initialized using the argument passed as Seed. +It calls the C function srand.
+
 argbar(+Values:list, -Chart:dict) is det
Values is a list of pairs V-N where +V is the value and N is the number of samples +returning that value. +The predicate returns a dict for rendering with c3 as a bar chart with +a bar for each value V. +The size of the bar is given by N.
+
 densities(+PriorList:list, +PostList:list, -Chart:dict, +Options:list) is det
Draws a line chart of the density of two sets of samples, usually +prior and post observations. The samples from the prior are in PriorList +while the samples from the posterior are in PostList. +PriorList and PostList must be lists of pairs of the form [V]-W or V-W +where V is a sampled value and W is its weight, or lists of values V. +Options is a list of options, the following are recognised by histogram/3: + +
+
nbins(+NBins:int)
the number of bins for dividing the domain, default value 40 +*/
+
+ +
+
 make_query_var(++Environment:int, +Variable:int, --BDD:int) is det
Makes Variable belonging to Environment a query random variable for MAP inference. +Returns in BDD the diagram of the formula encoding the required constraints among the +Boolean random variable that represent Variable.
+
 ret_map_prob(++Environment:int, ++BDD:int, -Probability:float, -MAPState:list) is det
Returns the MAP state MPAState of BDD and its Probability. +BDD belongs to environment Environment.
+
 andcnf(++Environment:int, ++A:couple, ++B:couple, --AandB:couple) is semidet
A and B are couples (Environment, BDDA) and (Environment, BDDB) respectively +Returns in AandB a couple (Environment, BDDAandB) where BDDAandB is pointer to a BDD belonging to environment Environment +representing the conjunction of BDDs BDDA and BDDB.
+
 or(++Environment:int, ++A:int, ++B:int, --AorB:int) is det
Returns in AorB a pointer to a BDD belonging to environment Environment +representing the disjunction of BDDs A and B.
+
 swi_builtin(+Goal:atom) is det
Succeeds if Goal is an atom whose predicate is defined in Prolog +(either builtin or defined in a standard library).
+
 ret_strategy(++Environment:int, ++ADD:int, --Decision:list, --Cost:int) is det
Computes the optimal strategy given a pointer to the ADD belonging to environment Environment. +Decision is a list of selected facts, Cost is the total cost.
+
 variance(+Values:list, -Average:float, -Variance:float) is det
Computes the variance the average of Values. +Values can be +
    +
  • a list of numbers
  • +
  • a list of pairs number-weight, in which case each number is multiplied by the weight +before being considered
  • +
  • a list of pairs list-weight, in which case list is considered as a matrix of numbers. +The matrix in each element of List must have the same dimension and are aggregated element- +wise
  • +
+
 add_var(++Environment:int, ++ProbabilityDistribution:list, ++Rule:int, -Variable:int) is det
Returns in Variable the index of a new random variable in Environment with NumberOHeads values and probability distribution ProbabilityDistribution.
-
 ret_map_prob(++Environment:int, ++BDD:int, -Probability:float, -MAPState:list) is det
Returns the MAP state MPAState of BDD and its Probability. +
+ +

Re-exported predicates

+ +

+The following predicates are exported from this file while their implementation is defined in imported modules or non-module files loaded by this module.

+ +
+
 symmetric_dirichlet_sample(++Alpha:float, ++K:int, --Value:list) is det
Returns a Value sampled from a symmetric Dirichlet distribution with parameter Alpha. +K is the number of dimensions of the result.
+
 to_pair(+Pair:pair, -FlattenedPair:pair) is det
Given a pair E-W, returns a pair Ep-W where +Ep=EE if E=[EE], otherwise Ep=E
+
 and(++Environment:int, ++A:int, ++B:int, --AandB:int) is det
Returns in AandB a pointer to a BDD belonging to environment Environment +representing the conjunction of BDDs A and B.
+
 density(+List:list, -Chart:dict) is det
Equivalent to density/3 with an empty option list.
+
 end_em(++Context:int) is det
Terminates the context data structure for performing parameter learning. +Context is a pointer to a context data structure for performing +the EM algorithm. +Context must have been returned by a call to init_em/1. +It frees the memory occupied by Context.
+
 gamma_sample(++Shape:float, ++Scale:float, --Value:float) is det
Returns a Value sampled from a gamma distribution with parameters Shape and Scale
+
 histogram(+List:list, -Chart:dict) is det
Equivalent to histogram/3 with an empty option list.
+
 equalityc(++Environment:int, ++Variable:int, ++Value:int, --EBDD:couple) is det
Returns in EBDD a couple (Environment,BDD) where BDD belongs to environment Environment +and represents the equation Variable=Value.
+
 create_dot(++Env:int, ++BDD:int, ++File:string) is det
The predicate writes the BDD in dot format to +to file FileName.
+
 bar(+Probability:float, -Chart:dict) is det
The predicate returns a dict for rendering with c3 as a bar chart with +a bar for the probability and a bar for one minus the probability.
+
 ret_probc(++Environment:int, ++EBDD:couple, -Probability:float) is det
EBDD is a couple (Environment,BDD) +Returns the Probability of BDD belonging to environment Environment +Uses
+
 andc(++Environment:int, ++A:couple, ++B:couple, --AandB:couple) is semidet
A and B are couples (Environment, BDDA) and (Environment, BDDB) respectively +Returns in AandB a couple (Environment, BDDAandB) where BDDAandB is pointer to a BDD belonging to environment Environment +representing the conjunction of BDDs BDDA and BDDB. +fails if BDDB represents the zero function
+
 equality(++Environment:int, ++Variable:int, ++Value:int, --BDD:int) is det
Returns in BDD the BDD belonging to environment Environment +that represents the equation Variable=Value.
+
 std_dev(+Values:list, -Dev:float) is det
Computes the standard deviation of Values. +Values can be +
    +
  • a list of numbers
  • +
  • a list of pairs number-weight, in which case each number is multiplied by the weight +before being considered
  • +
  • a list of pairs list-weight, in which case list is considered as a matrix of numbers. +The matrix in each element of List must have the same dimension and are aggregated element- +wise
  • +
+
+
 debug_cudd_var(++Environment:int, -Variable:out) is det
Prints the debug information which is the result of the call +of Cudd_ReadDead, Cudd_CheckZeroRef, Cudd_CheckKeys and +Cudd_DebugCheck(env->mgr));
+
 add_query_var(++Environment:int, ++ProbabilityDistribution:list, ++Rule:int, -Variable:int) is det
Returns in Variable the index of a new random variable to be queried in MAP inference with +NumberOHeads values and probability distribution ProbabilityDistribution. +The variable belongs to Environment.
+
 beta(+Alphas:list, -Beta:float) is det
Computes the value of the multivariate beta function for vector Alphas +https://en.wikipedia.org/wiki/Beta_function#Multivariate_beta_function +Alphas is a list of floats
+
 probability_dd(++Environment:int, ++BDD:int, --ADD:int) is det
Converts the BDD belonging to environment Environment into an ADD.
+
 zero(++Environment:int, --Zero:int) is det
Returns in Zero a pointer to a BDD belonging to environment Environment +representing the zero Boolean function.
+
 key_pair(+Pair:pair, -Key:term) is det
Given a pair Key-Vaule, returns its first element Key
+
 discrete_sample(++Theta:list, --Value:int) is det
Returns a Value sampled from a discrete distribution with parameters Theta. +Theta is a list of floating point numbers in [0,1] that sum to 1. +Value is in 0..(length(Theta)-1)
+
 init(--Environment:int) is det
Initializes a data structure for storing a single BDD. +Returns an integer Environment that is a pointer to a data structure for +storing a single BDD to be used for inference only (no learning).
+
 density(+List:list, -Chart:dict, +Options:list) is det
Draws a line chart of the density of a sets of samples. +The samples are in List +as pairs [V]-W or V-W where V is a value and W its weigth. + +

+Options is a list of options, the following are recognised by density/3:

+ +
+
min(+Min:float)
the minimum value of domain, default value the minimum in List
+
max(+Max:float)
the maximum value of domain, default value the maximum in List
+
nbins(+NBins:int)
the number of bins for dividing the domain, default value 40
+
+ +
+
 gauss_sample(++Mean:float, ++Variance:float, --Value:float) is det
Returns a Value sampled from a Gaussian distribution with parameters Mean and Variance
+
 histogram(+List:list, -Chart:dict, +Options:list) is det
Draws a histogram of the samples in List. List must be a list of pairs of the form [V]-W or V-W +where V is a sampled value and W is its weight, or a list of values. + +

+Options is a list of options, the following are recognised by histogram/3:

+ +
+
min(+Min:float)
the minimum value of domain, default value the minimum in List
+
max(+Max:float)
the maximum value of domain, default value the maximum in List
+
nbins(+NBins:int)
the number of bins for dividing the domain, default value 40
+
+ +
+
 create_dot_string(++Env:int, ++BDD:int, -Dot:string) is det
The predicate returns the BDD in dot format.
+
 bar(+Successes:int, +Failures:int, -Chart:dict) is det
The predicate returns a dict for rendering with c3 as a bar chart with +a bar for the number of successes and a bar for the number of failures
+
 to_atom(+In:pair, -Out:pair) is det
Given In=A0-N, to_atom/2 returns Out=A-N +where A is an atom representing A0
+
 or_list(++ListOfBDDs:list, ++Environment, --BDD:int) is det
Returns in BDD a pointer to a BDD belonging to environment Environment +representing the disjunction of all the BDDs in ListOfBDDs
+
 orc(++A:couple, ++B:couple, --AorB:couple) is det
A and B are couples (Environment, BDDA) and (Environment, BDDB) respectively +Returns in AorB a couple (Environment, BDDAorB) where BDDAorB is pointer to a BDD belonging to environment Environment +representing the disjunction of BDDs BDDA and BDDB.
+
 zeroc(++Environment:int, --Zero:couple) is det
Returns in Zero a couple (Environment,BDD) where BDD is pointer to a BDD belonging to environment Environment +representing the zero Boolean function
+
 add_prod(++Environment:int, ++ADDIn:int, ++Utility:float, --ADDOut:int) is det
Multiplies the ADD belonging to environment Environment +with the value Utility and stores the result in ADDOut.
+
 std_dev(+Values:list, -Average:float, -Dev:float) is det
Computes the standard deviation and the average of Values. +Values can be +
    +
  • a list of numbers
  • +
  • a list of pairs number-weight, in which case each number is multiplied by the weight +before being considered
  • +
  • a list of pairs list-weight, in which case list is considered as a matrix of numbers. +The matrix in each element of List must have the same dimension and are aggregated element- +wise
  • +
+
+
 ret_prob(++Environment:int, ++BDD:int, -Probability:float) is det
Returns the Probability of BDD belonging to environment Environment.
+
 average(+Values:list, -Average:float) is det
Computes the average of Values. +Values can be +
    +
  • a list of numbers
  • +
  • a list of pairs number-weight, in which case each number is multiplied by the weight +before being summed
  • +
  • a list of lists, in which case lists are considered as matrices of numbers and averaged +element-wise
  • +
  • a list of pairs list-weight, in which case the list is considered as a matrix of numbers. +The matrix in each element of List must have the same dimension and are aggregated element- +wise
  • +
+
+
 ret_abd_prob(++Environment:int, ++BDD:int, -Probability:float, -Explanation:list) is det
Returns the abductive Explanation of BDD and its Probability. BDD belongs to environment Environment.
+
 value_pair(+Pair:pair, -Value:term) is det
Given a pair Key-Vaule, returns its second element Value
+
 end(++Environment:int) is det
Terminates the environment data structure for storing a single BDD. +Environment is a pointer to a data structure returned by a call +to init/1.
+
 one(++Environment:int, --One:int) is det
Returns in One a pointer to a BDD belonging to environment Environment +representing the one Boolean function.
 em(++Context:int, ++RuleInfo:list, ++ListOfBDDs:list, ++EA:float, ++ER:float, ++Iterations:int, -LL:float, -Parameters:list, -ExampleProbabilities:list) is det
NumberOfHeads is a list of terms, one for each rule. Each term is either an integer, indicating the number of head atoms in the rule, or a list [N] where N @@ -182,72 +553,127 @@

Re-exported predicates

in reverse order.
-
 end_em(++Context:int) is det
Terminates the context data structure for performing parameter learning. -Context is a pointer to a context data structure for performing -the EM algorithm. -Context must have been returned by a call to init_em/1. -It frees the memory occupied by Context.
-
 and(++Environment:int, ++A:int, ++B:int, --AandB:int) is det
Returns in AandB a pointer to a BDD belonging to environment Environment -representing the conjunction of BDDs A and B.
-
 equality(++Environment:int, ++Variable:int, ++Value:int, --BDD:int) is det
Returns in BDD the BDD belonging to environment Environment -that represents the equation Variable=Value.
-
 add_query_var(++Environment:int, ++ProbabilityDistribution:list, ++Rule:int, -Variable:int) is det
Returns in Variable the index of a new random variable to be queried in MAP inference with -NumberOHeads values and probability distribution ProbabilityDistribution. -The variable belongs to Environment.
+
 density2d(+List:list, -Dens:list) is det
Equivalent to density2d/3 with an empty option list.
+
 initial_values(++Environment:int, ++Alpha:float) is det
Sets the type of parameter initialization for EM on Environment: +if Alpha is 0.0, it uses a truncated Dirichlet process +if Alpha is a float > 0.0, it uses a symmetric Dirichlet distribution +with that value as parameter
+
 init_ex(++Context:int, --Environment:int) is det
Initializes an enviroment data structure for storing a BDD. +Context is an integer that is a pointer to a context data structure +created using init_em/1. +Returns an integer Environment that is a pointer to a data structure for +storing a single BDD to be used for the EM algorithm.
+
 densities(+PriorList:list, +PostList:list, -Chart:dict) is det
Equivalent to densities/4 with an empty option list.
+
 uniform_sample(--Value:float) is det
Returns a Value sampled from a uniform distribution in [0,1]
+
 or_listc(++ListOfBDDs:list, ++Environment, --BDD:int) is det
Returns in BDD a couple (Env,B) with B a pointer to a +BDD belonging to environment Environment +representing the disjunction of all the BDDs in +ListOfBDDs (a list of couples (Env,BDD))
+
 bar1(+Probability:float, -Chart:dict) is det
The predicate returns a dict for rendering with c3 as a bar chart with +a bar for the probability
+
 bdd_notc(++Environment:int, ++EBDD:couple, --NotEBDD:couple) is det
EBDD is a couple (Environment,A) +Returns in NotEBDD a couple (Environment,NotA) where NotA is +pointer to a BDD belonging to environment Environment +representing the negation of BDD A
+
 onec(++Environment:int, --One:couple) is det
Returns in One a couple (Environment,BDD) where BDD is pointer to a BDD belonging to environment Environment +representing the one Boolean function
+
 agg_val(+Couple:atom, +PartialSum:number, -Sum:number) is det
Aggregate values by summation. The first argument is a couple _-N with +N the new value to sum to PartialSum
+
 add_sum(++Environment:int, ++ADD1:int, ++ADD2:int, --ADDOut:int) is det
Computes the sum of the two ADDs ADD1 ADD2 belonging to environment Environment. +The result in saved in ADDOut.
+
 add_abd_var(++Environment:int, ++ProbabilityDistribution:list, ++Rule:int, -Variable:int) is det
Returns in Variable the index of a new abducible random variable in Environment with +NumberOHeads values and probability distribution ProbabilityDistribution.
+
 variance(+Values:list, -Variance:float) is det
Computes the variance of Values. +Values can be +
    +
  • a list of numbers
  • +
  • a list of pairs number-weight, in which case each number is multiplied by the weight +before being considered
  • +
  • a list of pairs list-weight, in which case list is considered as a matrix of numbers. +The matrix in each element of List must have the same dimension and are aggregated element- +wise
  • +
+
+
 bdd_not(++Environment:int, ++A:int, --NotA:int) is det
Returns in NotA a pointer to a BDD belonging to environment Environment +representing the negation of BDD A.
+
 end_ex(++Environment:int) is det
Terminates the evnironment data structure for storing a BDD. +Environment is a pointer to a data structure returned by init_ex/2. +It frees the memory occupied by the BDD.
+
 add_decision_var(++Environment:int, ++Rule:int, -Variable:int) is det
Returns in Variable the index of a new decision variable in Environment
+
 init_em(--Context:int) is det
Initializes a data structure for performing parameter learning. +It returns an integer in Context that is a pointer to a +context data structure for performing the EM algorithm.
+
 density2d(+List:list, -Dens:list, +Options:list) is det
Returns a set of 3-dimensional points representing the plot of the +density of a sets of 2-dimensional samples. +The samples are in List +as pairs [X,Y]-W where (X,Y) is a point and W its weigth. + +

+Options is a list of options, the following are recognised by density2d/3:

+ +
+
xmin(+XMin:float)
the minimum value of the X domain, default value the minimum in List
+
xmax(-XMax:float)
the maximum value of the X domain, default value the maximum in List
+
ymin(-YMin:float)
the minimum value of the Y domain, default value the minimum in List
+
ymax(-YMax:float)
the maximum value of the Y domain, default value the maximum in List
+
nbins(+NBins:int)
the number of bins for dividing the X and Y domains, default value 40
-

Undocumented predicates

+
+
 dirichlet_sample(++Alpha:list, --Value:list) is det
Returns a Value sampled from a Dirichlet distribution with parameters Alpha. +Alpha and Value are lists of floating point numbers of the same length.
+
 bin(+N:int, +Values:list, +Lower:number, +BinWidth:number, -Couples:list) is det
Given a list of numeric Values, a Lower value and BinWidth, returns in Couples +a list of N pairs V-Freq where V is the midpoint of a bin and Freq is the number +of values that are inside the bin interval [V-BinWidth/2,V+BinWidth/2) +starting with the bin where V-BinWidth/2=Lower
+
 rand_seed(+Seed:int) is det
The pseudo-random number generator is initialized using the argument passed as Seed. +It calls the C function srand.
+
 argbar(+Values:list, -Chart:dict) is det
Values is a list of pairs V-N where +V is the value and N is the number of samples +returning that value. +The predicate returns a dict for rendering with c3 as a bar chart with +a bar for each value V. +The size of the bar is given by N.
+
 densities(+PriorList:list, +PostList:list, -Chart:dict, +Options:list) is det
Draws a line chart of the density of two sets of samples, usually +prior and post observations. The samples from the prior are in PriorList +while the samples from the posterior are in PostList. +PriorList and PostList must be lists of pairs of the form [V]-W or V-W +where V is a sampled value and W is its weight, or lists of values V. +Options is a list of options, the following are recognised by histogram/3: -

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

- -
-
 add_decision_var(Arg1, Arg2, Arg3)
-
 bar1(Arg1, Arg2)
-
 dirichlet_sample(Arg1, Arg2)
-
 agg_val(Arg1, Arg2, Arg3)
-
 average(Arg1, Arg2)
-
 value_pair(Arg1, Arg2)
-
 zeroc(Arg1, Arg2)
-
 density2d(Arg1, Arg2)
-
 ret_strategy(Arg1, Arg2, Arg3, Arg4)
-
 densities(Arg1, Arg2, Arg3)
-
 probability_dd(Arg1, Arg2, Arg3)
-
 bar(Arg1, Arg2, Arg3)
-
 symmetric_dirichlet_sample(Arg1, Arg2, Arg3)
-
 gamma_sample(Arg1, Arg2, Arg3)
-
 swi_builtin(Arg1)
-
 bdd_notc(Arg1, Arg2, Arg3)
-
 to_atom(Arg1, Arg2)
-
 key_pair(Arg1, Arg2)
-
 onec(Arg1, Arg2)
-
 density(Arg1, Arg2, Arg3)
-
 debug_cudd_var(Arg1, Arg2)
-
 histogram(Arg1, Arg2, Arg3)
-
 histogram(Arg1, Arg2)
-
 discrete_sample(Arg1, Arg2)
-
 gauss_sample(Arg1, Arg2, Arg3)
-
 or_list(Arg1, Arg2, Arg3)
-
 std_dev(Arg1, Arg2)
-
 variance(Arg1, Arg2, Arg3)
-
 beta(Arg1, Arg2)
-
 andcnf(Arg1, Arg2, Arg3, Arg4)
-
 equalityc(Arg1, Arg2, Arg3, Arg4)
-
 to_pair(Arg1, Arg2)
-
 add_prod(Arg1, Arg2, Arg3, Arg4)
-
 density(Arg1, Arg2)
-
 argbar(Arg1, Arg2)
-
 initial_values(Arg1, Arg2)
-
 uniform_sample(Arg1)
-
 std_dev(Arg1, Arg2, Arg3)
-
 variance(Arg1, Arg2)
-
 bin(Arg1, Arg2, Arg3, Arg4, Arg5)
-
 or_listc(Arg1, Arg2, Arg3)
-
 ret_probc(Arg1, Arg2, Arg3)
-
 andc(Arg1, Arg2, Arg3, Arg4)
-
 density2d(Arg1, Arg2, Arg3)
-
 add_sum(Arg1, Arg2, Arg3, Arg4)
-
 densities(Arg1, Arg2, Arg3, Arg4)
+
+
nbins(+NBins:int)
the number of bins for dividing the domain, default value 40 +*/
+
+ +
+
 make_query_var(++Environment:int, +Variable:int, --BDD:int) is det
Makes Variable belonging to Environment a query random variable for MAP inference. +Returns in BDD the diagram of the formula encoding the required constraints among the +Boolean random variable that represent Variable.
+
 ret_map_prob(++Environment:int, ++BDD:int, -Probability:float, -MAPState:list) is det
Returns the MAP state MPAState of BDD and its Probability. +BDD belongs to environment Environment.
+
 andcnf(++Environment:int, ++A:couple, ++B:couple, --AandB:couple) is semidet
A and B are couples (Environment, BDDA) and (Environment, BDDB) respectively +Returns in AandB a couple (Environment, BDDAandB) where BDDAandB is pointer to a BDD belonging to environment Environment +representing the conjunction of BDDs BDDA and BDDB.
+
 or(++Environment:int, ++A:int, ++B:int, --AorB:int) is det
Returns in AorB a pointer to a BDD belonging to environment Environment +representing the disjunction of BDDs A and B.
+
 swi_builtin(+Goal:atom) is det
Succeeds if Goal is an atom whose predicate is defined in Prolog +(either builtin or defined in a standard library).
+
 ret_strategy(++Environment:int, ++ADD:int, --Decision:list, --Cost:int) is det
Computes the optimal strategy given a pointer to the ADD belonging to environment Environment. +Decision is a list of selected facts, Cost is the total cost.
+
 variance(+Values:list, -Average:float, -Variance:float) is det
Computes the variance the average of Values. +Values can be +
    +
  • a list of numbers
  • +
  • a list of pairs number-weight, in which case each number is multiplied by the weight +before being considered
  • +
  • a list of pairs list-weight, in which case list is considered as a matrix of numbers. +The matrix in each element of List must have the same dimension and are aggregated element- +wise
  • +
+
+
 add_var(++Environment:int, ++ProbabilityDistribution:list, ++Rule:int, -Variable:int) is det
Returns in Variable the index of a new random variable in Environment with +NumberOHeads values and probability distribution ProbabilityDistribution.
diff --git a/docs/pldoc/slipcover.html b/docs/pldoc/slipcover.html index 0cd1109..436b2c5 100644 --- a/docs/pldoc/slipcover.html +++ b/docs/pldoc/slipcover.html @@ -136,59 +136,208 @@

slipcover.pl -- slipcover

Module is used to store the information in the correct module
 zero_clause(+Module:atom, +PredSpec:pred_spec, -ZeroClause:term) is det
Generates the zero clause for predicate PredSpec. Module is the module of the input file.
- - -

Re-exported predicates

- -

-The following predicates are exported from this file while their implementation is defined in imported modules or non-module files loaded by this module.

- -
+
 symmetric_dirichlet_sample(++Alpha:float, ++K:int, --Value:list) is det
Returns a Value sampled from a symmetric Dirichlet distribution with parameter Alpha. +K is the number of dimensions of the result.
+
 and(++Environment:int, ++A:int, ++B:int, --AandB:int) is det
Returns in AandB a pointer to a BDD belonging to environment Environment +representing the conjunction of BDDs A and B.
+
 end_em(++Context:int) is det
Terminates the context data structure for performing parameter learning. +Context is a pointer to a context data structure for performing +the EM algorithm. +Context must have been returned by a call to init_em/1. +It frees the memory occupied by Context.
+
 gamma_sample(++Shape:float, ++Scale:float, --Value:float) is det
Returns a Value sampled from a gamma distribution with parameters Shape and Scale
+
 equalityc(++Environment:int, ++Variable:int, ++Value:int, --EBDD:couple) is det
Returns in EBDD a couple (Environment,BDD) where BDD belongs to environment Environment +and represents the equation Variable=Value.
+
 create_dot(++Env:int, ++BDD:int, ++File:string) is det
The predicate writes the BDD in dot format to +to file FileName.
+
 ret_probc(++Environment:int, ++EBDD:couple, -Probability:float) is det
EBDD is a couple (Environment,BDD) +Returns the Probability of BDD belonging to environment Environment +Uses
+
 andc(++Environment:int, ++A:couple, ++B:couple, --AandB:couple) is semidet
A and B are couples (Environment, BDDA) and (Environment, BDDB) respectively +Returns in AandB a couple (Environment, BDDAandB) where BDDAandB is pointer to a BDD belonging to environment Environment +representing the conjunction of BDDs BDDA and BDDB. +fails if BDDB represents the zero function
+
 equality(++Environment:int, ++Variable:int, ++Value:int, --BDD:int) is det
Returns in BDD the BDD belonging to environment Environment +that represents the equation Variable=Value.
+
 debug_cudd_var(++Environment:int, -Variable:out) is det
Prints the debug information which is the result of the call +of Cudd_ReadDead, Cudd_CheckZeroRef, Cudd_CheckKeys and +Cudd_DebugCheck(env->mgr));
+
 add_query_var(++Environment:int, ++ProbabilityDistribution:list, ++Rule:int, -Variable:int) is det
Returns in Variable the index of a new random variable to be queried in MAP inference with +NumberOHeads values and probability distribution ProbabilityDistribution. +The variable belongs to Environment.
+
 probability_dd(++Environment:int, ++BDD:int, --ADD:int) is det
Converts the BDD belonging to environment Environment into an ADD.
 zero(++Environment:int, --Zero:int) is det
Returns in Zero a pointer to a BDD belonging to environment Environment representing the zero Boolean function.
+
 discrete_sample(++Theta:list, --Value:int) is det
Returns a Value sampled from a discrete distribution with parameters Theta. +Theta is a list of floating point numbers in [0,1] that sum to 1. +Value is in 0..(length(Theta)-1)
 init(--Environment:int) is det
Initializes a data structure for storing a single BDD. Returns an integer Environment that is a pointer to a data structure for storing a single BDD to be used for inference only (no learning).
-
 rand_seed(+Seed:int) is det
The pseudo-random number generator is initialized using the argument passed as Seed. -It calls the C function srand.
-
 make_query_var(++Environment:int, +Variable:int, --BDD:int) is det
Makes Variable belonging to Environment a query random variable for MAP inference. -Returns in BDD the diagram of the formula encoding the required constraints among the -Boolean random variable that represent Variable.
+
 gauss_sample(++Mean:float, ++Variance:float, --Value:float) is det
Returns a Value sampled from a Gaussian distribution with parameters Mean and Variance
+
 create_dot_string(++Env:int, ++BDD:int, -Dot:string) is det
The predicate returns the BDD in dot format.
+
 or_list(++ListOfBDDs:list, ++Environment, --BDD:int) is det
Returns in BDD a pointer to a BDD belonging to environment Environment +representing the disjunction of all the BDDs in ListOfBDDs
 orc(++A:couple, ++B:couple, --AorB:couple) is det
A and B are couples (Environment, BDDA) and (Environment, BDDB) respectively Returns in AorB a couple (Environment, BDDAorB) where BDDAorB is pointer to a BDD belonging to environment Environment representing the disjunction of BDDs BDDA and BDDB.
+
 zeroc(++Environment:int, --Zero:couple) is det
Returns in Zero a couple (Environment,BDD) where BDD is pointer to a BDD belonging to environment Environment +representing the zero Boolean function
+
 add_prod(++Environment:int, ++ADDIn:int, ++Utility:float, --ADDOut:int) is det
Multiplies the ADD belonging to environment Environment +with the value Utility and stores the result in ADDOut.
+
 ret_prob(++Environment:int, ++BDD:int, -Probability:float) is det
Returns the Probability of BDD belonging to environment Environment.
 ret_abd_prob(++Environment:int, ++BDD:int, -Probability:float, -Explanation:list) is det
Returns the abductive Explanation of BDD and its Probability. BDD belongs to environment Environment.
-
 ret_prob(++Environment:int, ++BDD:int, -Probability:float) is det
Returns the Probability of BDD belonging to environment Environment.
+
 end(++Environment:int) is det
Terminates the environment data structure for storing a single BDD. +Environment is a pointer to a data structure returned by a call +to init/1.
 one(++Environment:int, --One:int) is det
Returns in One a pointer to a BDD belonging to environment Environment representing the one Boolean function.
+
 em(++Context:int, ++RuleInfo:list, ++ListOfBDDs:list, ++EA:float, ++ER:float, ++Iterations:int, -LL:float, -Parameters:list, -ExampleProbabilities:list) is det
NumberOfHeads is a list of terms, one for each rule. Each term is either +an integer, indicating the number +of head atoms in the rule, or a list [N] where N +is the number of head atoms. In the first case, the parameters of the rule are tunable, +in the latter they are fixed. + +

+Performs EM learning. +Takes as input the Context, information on the rules, +a list of BDDs each representing one example, +the minimum absolute difference EA and relative difference ER between the +log likelihood of examples in two different iterations and the maximum number of iterations +Iterations. +RuleInfo is a list of elements, one for each rule, with are either

+
    +
  • an integer, indicating the number of heads, in which case the parameters of the +corresponding rule should be randomized,
  • +
  • a list of floats, in which case the parameters should be set to those indicated +in the list and not changed during learning (fixed parameters)
  • +
  • [a list of floats], in which case the initial values of the parameters should +be set to those indicated +in the list and changed during learning (initial values of the parameters) +Returns the final log likelihood of examples LL, the list of new Parameters +and a list with the final probabilities of each example. +Parameters is a list whose elements are of the form [N,P] where N is the rule +number and P is a list of probabilities, one for each head atom of rule N, +in reverse order.
  • +
+
+
 initial_values(++Environment:int, ++Alpha:float) is det
Sets the type of parameter initialization for EM on Environment: +if Alpha is 0.0, it uses a truncated Dirichlet process +if Alpha is a float > 0.0, it uses a symmetric Dirichlet distribution +with that value as parameter
 init_ex(++Context:int, --Environment:int) is det
Initializes an enviroment data structure for storing a BDD. Context is an integer that is a pointer to a context data structure created using init_em/1. Returns an integer Environment that is a pointer to a data structure for storing a single BDD to be used for the EM algorithm.
-
 create_dot(++Env:int, ++BDD:int, ++File:string) is det
The predicate writes the BDD in dot format to -to file FileName.
+
 uniform_sample(--Value:float) is det
Returns a Value sampled from a uniform distribution in [0,1]
+
 or_listc(++ListOfBDDs:list, ++Environment, --BDD:int) is det
Returns in BDD a couple (Env,B) with B a pointer to a +BDD belonging to environment Environment +representing the disjunction of all the BDDs in +ListOfBDDs (a list of couples (Env,BDD))
+
 bdd_notc(++Environment:int, ++EBDD:couple, --NotEBDD:couple) is det
EBDD is a couple (Environment,A) +Returns in NotEBDD a couple (Environment,NotA) where NotA is +pointer to a BDD belonging to environment Environment +representing the negation of BDD A
+
 onec(++Environment:int, --One:couple) is det
Returns in One a couple (Environment,BDD) where BDD is pointer to a BDD belonging to environment Environment +representing the one Boolean function
+
 add_sum(++Environment:int, ++ADD1:int, ++ADD2:int, --ADDOut:int) is det
Computes the sum of the two ADDs ADD1 ADD2 belonging to environment Environment. +The result in saved in ADDOut.
 add_abd_var(++Environment:int, ++ProbabilityDistribution:list, ++Rule:int, -Variable:int) is det
Returns in Variable the index of a new abducible random variable in Environment with NumberOHeads values and probability distribution ProbabilityDistribution.
 bdd_not(++Environment:int, ++A:int, --NotA:int) is det
Returns in NotA a pointer to a BDD belonging to environment Environment representing the negation of BDD A.
-
 end(++Environment:int) is det
Terminates the environment data structure for storing a single BDD. -Environment is a pointer to a data structure returned by a call -to init/1.
-
 or(++Environment:int, ++A:int, ++B:int, --AorB:int) is det
Returns in AorB a pointer to a BDD belonging to environment Environment -representing the disjunction of BDDs A and B.
 end_ex(++Environment:int) is det
Terminates the evnironment data structure for storing a BDD. Environment is a pointer to a data structure returned by init_ex/2. It frees the memory occupied by the BDD.
-
 create_dot_string(++Env:int, ++BDD:int, -Dot:string) is det
The predicate returns the BDD in dot format.
+
 add_decision_var(++Environment:int, ++Rule:int, -Variable:int) is det
Returns in Variable the index of a new decision variable in Environment
 init_em(--Context:int) is det
Initializes a data structure for performing parameter learning. It returns an integer in Context that is a pointer to a context data structure for performing the EM algorithm.
+
 dirichlet_sample(++Alpha:list, --Value:list) is det
Returns a Value sampled from a Dirichlet distribution with parameters Alpha. +Alpha and Value are lists of floating point numbers of the same length.
+
 rand_seed(+Seed:int) is det
The pseudo-random number generator is initialized using the argument passed as Seed. +It calls the C function srand.
+
 make_query_var(++Environment:int, +Variable:int, --BDD:int) is det
Makes Variable belonging to Environment a query random variable for MAP inference. +Returns in BDD the diagram of the formula encoding the required constraints among the +Boolean random variable that represent Variable.
+
 ret_map_prob(++Environment:int, ++BDD:int, -Probability:float, -MAPState:list) is det
Returns the MAP state MPAState of BDD and its Probability. +BDD belongs to environment Environment.
+
 andcnf(++Environment:int, ++A:couple, ++B:couple, --AandB:couple) is semidet
A and B are couples (Environment, BDDA) and (Environment, BDDB) respectively +Returns in AandB a couple (Environment, BDDAandB) where BDDAandB is pointer to a BDD belonging to environment Environment +representing the conjunction of BDDs BDDA and BDDB.
+
 or(++Environment:int, ++A:int, ++B:int, --AorB:int) is det
Returns in AorB a pointer to a BDD belonging to environment Environment +representing the disjunction of BDDs A and B.
+
 ret_strategy(++Environment:int, ++ADD:int, --Decision:list, --Cost:int) is det
Computes the optimal strategy given a pointer to the ADD belonging to environment Environment. +Decision is a list of selected facts, Cost is the total cost.
 add_var(++Environment:int, ++ProbabilityDistribution:list, ++Rule:int, -Variable:int) is det
Returns in Variable the index of a new random variable in Environment with NumberOHeads values and probability distribution ProbabilityDistribution.
-
 ret_map_prob(++Environment:int, ++BDD:int, -Probability:float, -MAPState:list) is det
Returns the MAP state MPAState of BDD and its Probability. +
+ +

Re-exported predicates

+ +

+The following predicates are exported from this file while their implementation is defined in imported modules or non-module files loaded by this module.

+ +
+
 symmetric_dirichlet_sample(++Alpha:float, ++K:int, --Value:list) is det
Returns a Value sampled from a symmetric Dirichlet distribution with parameter Alpha. +K is the number of dimensions of the result.
+
 and(++Environment:int, ++A:int, ++B:int, --AandB:int) is det
Returns in AandB a pointer to a BDD belonging to environment Environment +representing the conjunction of BDDs A and B.
+
 end_em(++Context:int) is det
Terminates the context data structure for performing parameter learning. +Context is a pointer to a context data structure for performing +the EM algorithm. +Context must have been returned by a call to init_em/1. +It frees the memory occupied by Context.
+
 gamma_sample(++Shape:float, ++Scale:float, --Value:float) is det
Returns a Value sampled from a gamma distribution with parameters Shape and Scale
+
 equalityc(++Environment:int, ++Variable:int, ++Value:int, --EBDD:couple) is det
Returns in EBDD a couple (Environment,BDD) where BDD belongs to environment Environment +and represents the equation Variable=Value.
+
 create_dot(++Env:int, ++BDD:int, ++File:string) is det
The predicate writes the BDD in dot format to +to file FileName.
+
 ret_probc(++Environment:int, ++EBDD:couple, -Probability:float) is det
EBDD is a couple (Environment,BDD) +Returns the Probability of BDD belonging to environment Environment +Uses
+
 andc(++Environment:int, ++A:couple, ++B:couple, --AandB:couple) is semidet
A and B are couples (Environment, BDDA) and (Environment, BDDB) respectively +Returns in AandB a couple (Environment, BDDAandB) where BDDAandB is pointer to a BDD belonging to environment Environment +representing the conjunction of BDDs BDDA and BDDB. +fails if BDDB represents the zero function
+
 equality(++Environment:int, ++Variable:int, ++Value:int, --BDD:int) is det
Returns in BDD the BDD belonging to environment Environment +that represents the equation Variable=Value.
+
 debug_cudd_var(++Environment:int, -Variable:out) is det
Prints the debug information which is the result of the call +of Cudd_ReadDead, Cudd_CheckZeroRef, Cudd_CheckKeys and +Cudd_DebugCheck(env->mgr));
+
 add_query_var(++Environment:int, ++ProbabilityDistribution:list, ++Rule:int, -Variable:int) is det
Returns in Variable the index of a new random variable to be queried in MAP inference with +NumberOHeads values and probability distribution ProbabilityDistribution. +The variable belongs to Environment.
+
 probability_dd(++Environment:int, ++BDD:int, --ADD:int) is det
Converts the BDD belonging to environment Environment into an ADD.
+
 zero(++Environment:int, --Zero:int) is det
Returns in Zero a pointer to a BDD belonging to environment Environment +representing the zero Boolean function.
+
 discrete_sample(++Theta:list, --Value:int) is det
Returns a Value sampled from a discrete distribution with parameters Theta. +Theta is a list of floating point numbers in [0,1] that sum to 1. +Value is in 0..(length(Theta)-1)
+
 init(--Environment:int) is det
Initializes a data structure for storing a single BDD. +Returns an integer Environment that is a pointer to a data structure for +storing a single BDD to be used for inference only (no learning).
+
 gauss_sample(++Mean:float, ++Variance:float, --Value:float) is det
Returns a Value sampled from a Gaussian distribution with parameters Mean and Variance
+
 create_dot_string(++Env:int, ++BDD:int, -Dot:string) is det
The predicate returns the BDD in dot format.
+
 or_list(++ListOfBDDs:list, ++Environment, --BDD:int) is det
Returns in BDD a pointer to a BDD belonging to environment Environment +representing the disjunction of all the BDDs in ListOfBDDs
+
 orc(++A:couple, ++B:couple, --AorB:couple) is det
A and B are couples (Environment, BDDA) and (Environment, BDDB) respectively +Returns in AorB a couple (Environment, BDDAorB) where BDDAorB is pointer to a BDD belonging to environment Environment +representing the disjunction of BDDs BDDA and BDDB.
+
 zeroc(++Environment:int, --Zero:couple) is det
Returns in Zero a couple (Environment,BDD) where BDD is pointer to a BDD belonging to environment Environment +representing the zero Boolean function
+
 add_prod(++Environment:int, ++ADDIn:int, ++Utility:float, --ADDOut:int) is det
Multiplies the ADD belonging to environment Environment +with the value Utility and stores the result in ADDOut.
+
 ret_prob(++Environment:int, ++BDD:int, -Probability:float) is det
Returns the Probability of BDD belonging to environment Environment.
+
 ret_abd_prob(++Environment:int, ++BDD:int, -Probability:float, -Explanation:list) is det
Returns the abductive Explanation of BDD and its Probability. BDD belongs to environment Environment.
+
 end(++Environment:int) is det
Terminates the environment data structure for storing a single BDD. +Environment is a pointer to a data structure returned by a call +to init/1.
+
 one(++Environment:int, --One:int) is det
Returns in One a pointer to a BDD belonging to environment Environment +representing the one Boolean function.
 em(++Context:int, ++RuleInfo:list, ++ListOfBDDs:list, ++EA:float, ++ER:float, ++Iterations:int, -LL:float, -Parameters:list, -ExampleProbabilities:list) is det
NumberOfHeads is a list of terms, one for each rule. Each term is either an integer, indicating the number of head atoms in the rule, or a list [N] where N @@ -218,48 +367,57 @@

Re-exported predicates

in reverse order.
-
 end_em(++Context:int) is det
Terminates the context data structure for performing parameter learning. -Context is a pointer to a context data structure for performing -the EM algorithm. -Context must have been returned by a call to init_em/1. -It frees the memory occupied by Context.
-
 and(++Environment:int, ++A:int, ++B:int, --AandB:int) is det
Returns in AandB a pointer to a BDD belonging to environment Environment -representing the conjunction of BDDs A and B.
-
 equality(++Environment:int, ++Variable:int, ++Value:int, --BDD:int) is det
Returns in BDD the BDD belonging to environment Environment -that represents the equation Variable=Value.
-
 add_query_var(++Environment:int, ++ProbabilityDistribution:list, ++Rule:int, -Variable:int) is det
Returns in Variable the index of a new random variable to be queried in MAP inference with -NumberOHeads values and probability distribution ProbabilityDistribution. -The variable belongs to Environment.
-
- -

Undocumented predicates

- -

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

- -
-
 add_decision_var(Arg1, Arg2, Arg3)
-
 dirichlet_sample(Arg1, Arg2)
-
 zeroc(Arg1, Arg2)
-
 ret_strategy(Arg1, Arg2, Arg3, Arg4)
-
 probability_dd(Arg1, Arg2, Arg3)
-
 symmetric_dirichlet_sample(Arg1, Arg2, Arg3)
-
 gamma_sample(Arg1, Arg2, Arg3)
-
 bdd_notc(Arg1, Arg2, Arg3)
-
 onec(Arg1, Arg2)
-
 debug_cudd_var(Arg1, Arg2)
-
 discrete_sample(Arg1, Arg2)
-
 gauss_sample(Arg1, Arg2, Arg3)
-
 or_list(Arg1, Arg2, Arg3)
-
 andcnf(Arg1, Arg2, Arg3, Arg4)
-
 equalityc(Arg1, Arg2, Arg3, Arg4)
-
 add_prod(Arg1, Arg2, Arg3, Arg4)
-
 initial_values(Arg1, Arg2)
-
 uniform_sample(Arg1)
-
 or_listc(Arg1, Arg2, Arg3)
-
 ret_probc(Arg1, Arg2, Arg3)
-
 andc(Arg1, Arg2, Arg3, Arg4)
-
 add_sum(Arg1, Arg2, Arg3, Arg4)
+
 initial_values(++Environment:int, ++Alpha:float) is det
Sets the type of parameter initialization for EM on Environment: +if Alpha is 0.0, it uses a truncated Dirichlet process +if Alpha is a float > 0.0, it uses a symmetric Dirichlet distribution +with that value as parameter
+
 init_ex(++Context:int, --Environment:int) is det
Initializes an enviroment data structure for storing a BDD. +Context is an integer that is a pointer to a context data structure +created using init_em/1. +Returns an integer Environment that is a pointer to a data structure for +storing a single BDD to be used for the EM algorithm.
+
 uniform_sample(--Value:float) is det
Returns a Value sampled from a uniform distribution in [0,1]
+
 or_listc(++ListOfBDDs:list, ++Environment, --BDD:int) is det
Returns in BDD a couple (Env,B) with B a pointer to a +BDD belonging to environment Environment +representing the disjunction of all the BDDs in +ListOfBDDs (a list of couples (Env,BDD))
+
 bdd_notc(++Environment:int, ++EBDD:couple, --NotEBDD:couple) is det
EBDD is a couple (Environment,A) +Returns in NotEBDD a couple (Environment,NotA) where NotA is +pointer to a BDD belonging to environment Environment +representing the negation of BDD A
+
 onec(++Environment:int, --One:couple) is det
Returns in One a couple (Environment,BDD) where BDD is pointer to a BDD belonging to environment Environment +representing the one Boolean function
+
 add_sum(++Environment:int, ++ADD1:int, ++ADD2:int, --ADDOut:int) is det
Computes the sum of the two ADDs ADD1 ADD2 belonging to environment Environment. +The result in saved in ADDOut.
+
 add_abd_var(++Environment:int, ++ProbabilityDistribution:list, ++Rule:int, -Variable:int) is det
Returns in Variable the index of a new abducible random variable in Environment with +NumberOHeads values and probability distribution ProbabilityDistribution.
+
 bdd_not(++Environment:int, ++A:int, --NotA:int) is det
Returns in NotA a pointer to a BDD belonging to environment Environment +representing the negation of BDD A.
+
 end_ex(++Environment:int) is det
Terminates the evnironment data structure for storing a BDD. +Environment is a pointer to a data structure returned by init_ex/2. +It frees the memory occupied by the BDD.
+
 add_decision_var(++Environment:int, ++Rule:int, -Variable:int) is det
Returns in Variable the index of a new decision variable in Environment
+
 init_em(--Context:int) is det
Initializes a data structure for performing parameter learning. +It returns an integer in Context that is a pointer to a +context data structure for performing the EM algorithm.
+
 dirichlet_sample(++Alpha:list, --Value:list) is det
Returns a Value sampled from a Dirichlet distribution with parameters Alpha. +Alpha and Value are lists of floating point numbers of the same length.
+
 rand_seed(+Seed:int) is det
The pseudo-random number generator is initialized using the argument passed as Seed. +It calls the C function srand.
+
 make_query_var(++Environment:int, +Variable:int, --BDD:int) is det
Makes Variable belonging to Environment a query random variable for MAP inference. +Returns in BDD the diagram of the formula encoding the required constraints among the +Boolean random variable that represent Variable.
+
 ret_map_prob(++Environment:int, ++BDD:int, -Probability:float, -MAPState:list) is det
Returns the MAP state MPAState of BDD and its Probability. +BDD belongs to environment Environment.
+
 andcnf(++Environment:int, ++A:couple, ++B:couple, --AandB:couple) is semidet
A and B are couples (Environment, BDDA) and (Environment, BDDB) respectively +Returns in AandB a couple (Environment, BDDAandB) where BDDAandB is pointer to a BDD belonging to environment Environment +representing the conjunction of BDDs BDDA and BDDB.
+
 or(++Environment:int, ++A:int, ++B:int, --AorB:int) is det
Returns in AorB a pointer to a BDD belonging to environment Environment +representing the disjunction of BDDs A and B.
+
 ret_strategy(++Environment:int, ++ADD:int, --Decision:list, --Cost:int) is det
Computes the optimal strategy given a pointer to the ADD belonging to environment Environment. +Decision is a list of selected facts, Cost is the total cost.
+
 add_var(++Environment:int, ++ProbabilityDistribution:list, ++Rule:int, -Variable:int) is det
Returns in Variable the index of a new random variable in Environment with +NumberOHeads values and probability distribution ProbabilityDistribution.