This module performs learning over Logic Programs with Annotated
Disjunctions and CP-Logic programs.
It performs both parameter and structure learning.
See https://github.com/friguzzi/cplint/blob/master/doc/manual.pdf or
http://ds.ing.unife.it/~friguzzi/software/cplint-swi/manual.html for
details.
- author
- - Fabrizio Riguzzi, Elena Bellodi
- copyright
- - Fabrizio Riguzzi, Elena Bellodi
- license
- - Artistic License 2.0
-  induce_lift(: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_lift(: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_lift(: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.
-  sort_rules(+RulesIn:list_of_rules, -RulesOut:list_of_rules) is det
- The predicate sorts RulesIn according to the probability of the rules
-  induce_par_lift(: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.
-  induce_par_kg(:P:probabilistic_program, -P1: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.
-  filter_rules(:RulesIn:list_of_rules, -RulesOut:list_of_rules) is det
- The predicate removes the rules with a probability below or equal to the min_probparmeter.
-  filter_rules(+RulesIn:list_of_rules, -RulesOut:list_of_rules, +Min_prob:float) is det
- The predicate removes from the rules with a probability below or equal to Min_prob.
-  remove_zero(+RulesIn:list_of_rules, -RulesOut:list_of_rules) is det
- The predicate removes the rules with a probability of 0.0.
-  set_lift(:Parameter:atom, +Value:term) is det
- The predicate sets the value of a parameter
For a list of parameters see
https://friguzzi.github.io/liftcover/
-  setting_lift(:Parameter:atom, -Value:term) is det
- The predicate returns the value of a parameter
For a list of parameters see
https://friguzzi.github.io/liftcover/
-  explain_lift(:At:atom, -Exp:list) is multi
- The predicate returns the explanation of atom At given by the
input program. The first argument of At should be the model name.
The explanation is a list of pairs (P-Ex) where P is the probability
in the head of a rule H:P:-B and Ex is a true grounding of B.
-  explain_lift(:At:atom, +Program:probabilistic_program, -Exp:list) is multi
- The predicate returns the explanation of atom At given by Program.
-  hits_at_k(:Folds:list_of_atoms, +TargetPred:predicate, +Arg:int, +K:int, -HitsAtK:float, -FilteredHitsAtK:float) is det
- Returns the Hits@K and filtered Hits@K of the target predicate TargetPred on the list of folds Folds
for the argument in position Arg.
-  hits_at_k(:Folds:list_of_atoms, +TargetPred:predicate, +Arg:int, +Prog:probabilistic_program, +K:int, -Hits:float, -FilteredHits:float) is det
- Returns the Hits@K and filtered Hits@K of the target predicate TargetPred on the list of folds Folds
for the argument in position Arg computed over Prog.
-  inst_exs(:Folds:list, +TargetPred:PredSpec, +Arg:int, +ProbabilisticProgram:list_of_probabilistic_clauses) is det
- The predicate prints the list of answers for all the triples in Folds for predicate
TaragetPredwhere argument in position Arg has been replaced by a variable.
-  rank_exs(:Folds:list, +TargetPred:PredSpec, +Arg:int, +ProbabilisticProgram:list_of_probabilistic_clauses) is det
- The predicate prints the list of answers for all the triples in Folds for predicate
TaragetPredwhere argument in position Arg has been replaced by a variable.
-  rank_ex(:At:atom, +ProbabilisticProgram:list_of_probabilistic_clauses, +Arg:int) is det
- The predicate prints the list of answers for the query At where
argument in position Arg has been replaced by a variable.
The first argument of At should be the model name.
-  rank_answer(:At:atom, +Arg:integer, -Rank:float) is det
- The predicate returns the rank of the constant in argument Arg of At in the
list of answers for the query At.
-  rank_answer(:At:atom, +Arg:integer, +Prog:probabilistic_program, -Rank:float) is det
- The predicate returns the rank of the constant in argument Arg of At in the
list of answers for the query At asked using the program Prog.
-  ranked_answers(:At:atom, +Var:var, -RankedAnswers:list) is multi
- The predicate returns a list of answers for the query At.
Var should be a variable in At. RankedAnswers is a list of pairs
(P-A) where P is the probability of the answer At{Var/A}.
The list is sorted in decreasing order of probability.
The first argument of At should be the model name.
The query is asked to the input program.
-  ranked_answers(:At:atom, +Var:var, +Prog:probabilistic_program, -RankedAnswers:list) is multi
- As ranked_answers/3 but the query is asked to the program Prog.
-  rank(:Element:term, +OrderedList:list, -Rank:float) is det
- The predicate returns the rank of Element in the list OrderedList.
Group of records with the same value are assigned the average of the ranks.
OrderedList is a list of pairs (S - E) where S is the score and E is the element.
https://pandas.pydata.org/pandas-docs/stable/reference/api/pandas.DataFrame.rank.html 
-  prob_lift(:At:atom, -P:float) is multi
- The predicate computes the probability of atom At given by the
input program. The first argument of At should be the model name.
If At contains variables, the predicate returns
all the instantiaions of At with their probabilities in backtracking.
-  prob_lift(:At:atom, +Program:probabilistic_program, -P:float) is multi
- The predicate computes the probability of atom At given by Program.
The first argument of At should be the model name.
If At contains variables, the predicate returns
all the instantiaions of At with their probabilities in backtracking.
Undocumented predicates
The following predicates are exported, but not or incorrectly documented.
-  induce_par_pos_kg(Arg1, Arg2)
-  compute_stats_kg(Arg1, Arg2)
-  compute_stats_pos_kg(Arg1, Arg2)
-  compute_par_kg(Arg1, Arg2, Arg3)
-  write_rules_kg(Arg1)
-  write_rules_kg(Arg1, Arg2)
-  write_rules_anyburl(Arg1, Arg2)
-  read_rules_anyburl(Arg1, Arg2)
-  rules_for_rel(Arg1, Arg2, Arg3)