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

This module performs learning over Logic Programs with Annotated Disjunctions and CP-Logic programs. It performs both parameter and structure learning.

See https://friguzzi.github.io/cplint/ for details.

Reexports bddem

author
- Fabrizio Riguzzi, Elena Bellodi
license
- Artistic License 2.0
 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.
 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
 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.
 make_dynamic(+Module:atom) is det
Makes the predicates required for learning dynamic.
 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.
 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.
 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.
 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
 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
 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 [].
 generate_body(+ModeDecs:list, +Module:atom, -BottomClauses:list) is det
Generates the body of bottom clauses and returns the bottom clauses in BottomClauses.
 remove_duplicates(+List1:list, -List2:list) is det
Removes duplicates from List1. Equality is checked with ==.
 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.
 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.
 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
 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.
 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.
 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).
 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
 retract_all(+Refs:list) is det
The predicate erases all references in Refs (using erase/1).
 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.
 get_next_rule_number(+Module:atom, -R:integer) is det
The predicate returns the next rule number. Module is used to access local data.
 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/
 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/
 member_eq(+List:list, +Element:term) is det
Checks the presence of Element in List. Equality is checked with ==.
 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.
 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.
 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.
 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
 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.
 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.
 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.
 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.
 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.
 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.
 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.
 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
 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.

Undocumented predicates

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

 init_em(Arg1)
 init_ex(Arg1, Arg2)
 init(Arg1)
 end_em(Arg1)
 end_ex(Arg1)
 end(Arg1)
 one(Arg1, Arg2)
 zero(Arg1, Arg2)
 and(Arg1, Arg2, Arg3, Arg4)
 or(Arg1, Arg2, Arg3, Arg4)
 bdd_not(Arg1, Arg2, Arg3)
 ret_prob(Arg1, Arg2, Arg3)
 equality(Arg1, Arg2, Arg3, Arg4)
 add_var(Arg1, Arg2, Arg3, Arg4)
 add_abd_var(Arg1, Arg2, Arg3, Arg4)
 ret_abd_prob(Arg1, Arg2, Arg3, Arg4)
 add_query_var(Arg1, Arg2, Arg3, Arg4)
 ret_map_prob(Arg1, Arg2, Arg3, Arg4)
 onec(Arg1, Arg2)
 zeroc(Arg1, Arg2)
 andc(Arg1, Arg2, Arg3, Arg4)
 andcnf(Arg1, Arg2, Arg3, Arg4)
 bdd_notc(Arg1, Arg2, Arg3)
 orc(Arg1, Arg2, Arg3)
 ret_probc(Arg1, Arg2, Arg3)
 equalityc(Arg1, Arg2, Arg3, Arg4)
 or_list(Arg1, Arg2, Arg3)
 or_listc(Arg1, Arg2, Arg3)
 make_query_var(Arg1, Arg2, Arg3)
 create_dot(Arg1, Arg2, Arg3)
 create_dot_string(Arg1, Arg2, Arg3)
 em(Arg1, Arg2, Arg3, Arg4, Arg5, Arg6, Arg7, Arg8, Arg9)
 rand_seed(Arg1)
 gamma_sample(Arg1, Arg2, Arg3)
 gauss_sample(Arg1, Arg2, Arg3)
 uniform_sample(Arg1)
 dirichlet_sample(Arg1, Arg2)
 symmetric_dirichlet_sample(Arg1, Arg2, Arg3)
 discrete_sample(Arg1, Arg2)
 initial_values(Arg1, Arg2)
 add_decision_var(Arg1, Arg2, Arg3)
 probability_dd(Arg1, Arg2, Arg3)
 add_prod(Arg1, Arg2, Arg3, Arg4)
 add_sum(Arg1, Arg2, Arg3, Arg4)
 ret_strategy(Arg1, Arg2, Arg3, Arg4)
 debug_cudd_var(Arg1, Arg2)