removing old files
git-svn-id: https://yap.svn.sf.net/svnroot/yap/trunk@2018 b08c6af1-5177-4d33-ba66-4b1c6b8b522a
This commit is contained in:
parent
8fb01d6607
commit
dd38b5706f
@ -1,722 +0,0 @@
|
|||||||
/*
|
|
||||||
LPAD and CP-Logic interpreter
|
|
||||||
|
|
||||||
Copyright (c) 2007, Fabrizio Riguzzi
|
|
||||||
|
|
||||||
*/
|
|
||||||
|
|
||||||
:-dynamic rule/4,def_rule/2,setting/2.
|
|
||||||
|
|
||||||
:-use_module(library(lists)).
|
|
||||||
:-use_module(library(ugraphs)).
|
|
||||||
|
|
||||||
:-load_foreign_files(['cplint'],[],init_my_predicates).
|
|
||||||
|
|
||||||
/* start of list of parameters that can be set by the user with
|
|
||||||
set(Parameter,Value) */
|
|
||||||
setting(epsilon_parsing,0.00001).
|
|
||||||
setting(savedot,false).
|
|
||||||
/* end of list of parameters */
|
|
||||||
|
|
||||||
/* s(GoalsLIst,Prob) compute the probability of a list of goals
|
|
||||||
GoalsLis can have variables, s returns in backtracking all the solutions with their
|
|
||||||
corresponding probability */
|
|
||||||
s(GoalsList,Prob):-
|
|
||||||
solve(GoalsList,Prob).
|
|
||||||
|
|
||||||
|
|
||||||
solve(GoalsList,Prob):-
|
|
||||||
setof(Deriv,find_deriv(GoalsList,Deriv),LDup),
|
|
||||||
rem_dup_lists(LDup,L),
|
|
||||||
build_formula(L,Formula,[],Var),
|
|
||||||
var2numbers(Var,0,NewVar),
|
|
||||||
(setting(savedot,true)->
|
|
||||||
format("Variables: ~p~n",[Var]),
|
|
||||||
compute_prob(NewVar,Formula,Prob,1)
|
|
||||||
;
|
|
||||||
compute_prob(NewVar,Formula,Prob,0)
|
|
||||||
).
|
|
||||||
|
|
||||||
solve(GoalsList,0):-
|
|
||||||
\+ find_deriv(GoalsList,_Deriv).
|
|
||||||
|
|
||||||
find_deriv(GoalsList,Deriv):-
|
|
||||||
solve(GoalsList,[],DerivDup),
|
|
||||||
remove_duplicates(DerivDup,Deriv).
|
|
||||||
/* duplicate can appear in the C set because two different unistantiated clauses may become the
|
|
||||||
same clause when instantiated */
|
|
||||||
|
|
||||||
/* sc(Goals,Evidence,Prob) compute the conditional probability of the list of goals
|
|
||||||
Goals given the list of goals Evidence
|
|
||||||
Goals and Evidence can have variables, sc returns in backtracking all the solutions with their
|
|
||||||
corresponding probability
|
|
||||||
if it fails, the conditional probability is undefined
|
|
||||||
*/
|
|
||||||
sc(Goals,Evidence,Prob):-
|
|
||||||
solve_cond(Goals,Evidence,Prob).
|
|
||||||
|
|
||||||
solve_cond(Goals,Evidence,Prob):-
|
|
||||||
setof(DerivE,find_deriv(Evidence,DerivE),LDupE),
|
|
||||||
rem_dup_lists(LDupE,LE),
|
|
||||||
build_formula(LE,FormulaE,[],VarE),
|
|
||||||
var2numbers(VarE,0,NewVarE),
|
|
||||||
compute_prob(NewVarE,FormulaE,ProbE,0),
|
|
||||||
solve_cond_goals(Goals,LE,ProbGE),
|
|
||||||
Prob is ProbGE/ProbE.
|
|
||||||
|
|
||||||
solve_cond_goals(Goals,LE,ProbGE):-
|
|
||||||
setof(DerivGE,find_deriv_GE(LE,Goals,DerivGE),LDupGE),
|
|
||||||
rem_dup_lists(LDupGE,LGE),
|
|
||||||
build_formula(LGE,FormulaGE,[],VarGE),
|
|
||||||
var2numbers(VarGE,0,NewVarGE),
|
|
||||||
call_compute_prob(NewVarGE,FormulaGE,ProbGE).
|
|
||||||
|
|
||||||
solve_cond_goals(Goals,LE,0):-
|
|
||||||
\+ find_deriv_GE(LE,Goals,_DerivGE).
|
|
||||||
|
|
||||||
call_compute_prob(NewVarGE,FormulaGE,ProbGE):-
|
|
||||||
(setting(savedot,true)->
|
|
||||||
format("Variables: ~p~n",[NewVarGE]),
|
|
||||||
compute_prob(NewVarGE,FormulaGE,ProbGE,1)
|
|
||||||
;
|
|
||||||
compute_prob(NewVarGE,FormulaGE,ProbGE,0)
|
|
||||||
).
|
|
||||||
|
|
||||||
find_deriv_GE(LD,GoalsList,Deriv):-
|
|
||||||
member(D,LD),
|
|
||||||
solve(GoalsList,D,DerivDup),
|
|
||||||
remove_duplicates(DerivDup,Deriv).
|
|
||||||
|
|
||||||
/* solve(GoalsList,CIn,COut) takes a list of goals and an input C set
|
|
||||||
and returns an output C set
|
|
||||||
The C set is a list of triple (N,R,S) where
|
|
||||||
- N is the index of the head atom used, starting from 0
|
|
||||||
- R is the index of the non ground rule used, starting from 1
|
|
||||||
- S is the substitution of rule R, in the form of a list whose elements
|
|
||||||
are of the form 'VarName'=value
|
|
||||||
*/
|
|
||||||
solve([],C,C):-!.
|
|
||||||
|
|
||||||
solve([bagof(V,EV^G,L)|T],CIn,COut):-!,
|
|
||||||
list2and(GL,G),
|
|
||||||
bagof((V,C),EV^solve(GL,CIn,C),LD),
|
|
||||||
length(LD,N),
|
|
||||||
build_initial_graph(N,GrIn),
|
|
||||||
build_graph(LD,0,GrIn,Gr),
|
|
||||||
clique(Gr,Clique),
|
|
||||||
build_Cset(LD,Clique,L,[],C1),
|
|
||||||
remove_duplicates_eq(C1,C2),
|
|
||||||
solve(T,C2,COut).
|
|
||||||
|
|
||||||
solve([bagof(V,G,L)|T],CIn,COut):-!,
|
|
||||||
list2and(GL,G),
|
|
||||||
bagof((V,C),solve(GL,CIn,C),LD),
|
|
||||||
length(LD,N),
|
|
||||||
build_initial_graph(N,GrIn),
|
|
||||||
build_graph(LD,0,GrIn,Gr),
|
|
||||||
clique(Gr,Clique),
|
|
||||||
build_Cset(LD,Clique,L,[],C1),
|
|
||||||
remove_duplicates_eq(C1,C2),
|
|
||||||
solve(T,C2,COut).
|
|
||||||
|
|
||||||
|
|
||||||
solve([setof(V,EV^G,L)|T],CIn,COut):-!,
|
|
||||||
list2and(GL,G),
|
|
||||||
setof((V,C),EV^solve(GL,CIn,C),LD),
|
|
||||||
length(LD,N),
|
|
||||||
build_initial_graph(N,GrIn),
|
|
||||||
build_graph(LD,0,GrIn,Gr),
|
|
||||||
clique(Gr,Clique),
|
|
||||||
build_Cset(LD,Clique,L1,[],C1),
|
|
||||||
remove_duplicates(L1,L),
|
|
||||||
solve(T,C1,COut).
|
|
||||||
|
|
||||||
solve([setof(V,G,L)|T],CIn,COut):-!,
|
|
||||||
list2and(GL,G),
|
|
||||||
setof((V,C),solve(GL,CIn,C),LD),
|
|
||||||
length(LD,N),
|
|
||||||
build_initial_graph(N,GrIn),
|
|
||||||
build_graph(LD,0,GrIn,Gr),
|
|
||||||
clique(Gr,Clique),
|
|
||||||
build_Cset(LD,Clique,L1,[],C1),
|
|
||||||
remove_duplicates(L1,L),
|
|
||||||
solve(T,C1,COut).
|
|
||||||
|
|
||||||
solve([\+ H |T],CIn,COut):-!,
|
|
||||||
list2and(HL,H),
|
|
||||||
(setof(D,find_deriv(HL,D),LDup)->
|
|
||||||
rem_dup_lists(LDup,L),
|
|
||||||
choose_clauses(CIn,L,C1),
|
|
||||||
solve(T,C1,COut)
|
|
||||||
;
|
|
||||||
solve(T,CIn,COut)
|
|
||||||
).
|
|
||||||
|
|
||||||
solve([H|T],CIn,COut):-
|
|
||||||
builtin(H),!,
|
|
||||||
call(H),
|
|
||||||
solve(T,CIn,COut).
|
|
||||||
|
|
||||||
solve([H|T],CIn,COut):-
|
|
||||||
def_rule(H,B),
|
|
||||||
append(B,T,NG),
|
|
||||||
solve(NG,CIn,COut).
|
|
||||||
|
|
||||||
solve([H|T],CIn,COut):-
|
|
||||||
find_rule(H,(R,S,N),B,CIn),
|
|
||||||
solve_pres(R,S,N,B,T,CIn,COut).
|
|
||||||
|
|
||||||
solve_pres(R,S,N,B,T,CIn,COut):-
|
|
||||||
member_eq((N,R,S),CIn),!,
|
|
||||||
append(B,T,NG),
|
|
||||||
solve(NG,CIn,COut).
|
|
||||||
|
|
||||||
solve_pres(R,S,N,B,T,CIn,COut):-
|
|
||||||
append(CIn,[(N,R,S)],C1),
|
|
||||||
append(B,T,NG),
|
|
||||||
solve(NG,C1,COut).
|
|
||||||
|
|
||||||
build_initial_graph(N,G):-
|
|
||||||
listN(0,N,Vert),
|
|
||||||
add_vertices([],Vert,G).
|
|
||||||
|
|
||||||
|
|
||||||
build_graph([],_N,G,G).
|
|
||||||
|
|
||||||
build_graph([(_V,C)|T],N,GIn,GOut):-
|
|
||||||
N1 is N+1,
|
|
||||||
compatible(C,T,N,N1,GIn,G1),
|
|
||||||
build_graph(T,N1,G1,GOut).
|
|
||||||
|
|
||||||
compatible(_C,[],_N,_N1,G,G).
|
|
||||||
|
|
||||||
compatible(C,[(_V,H)|T],N,N1,GIn,GOut):-
|
|
||||||
(compatible(C,H)->
|
|
||||||
add_edges(GIn,[N-N1,N1-N],G1)
|
|
||||||
;
|
|
||||||
G1=GIn
|
|
||||||
),
|
|
||||||
N2 is N1 +1,
|
|
||||||
compatible(C,T,N,N2,G1,GOut).
|
|
||||||
|
|
||||||
compatible([],_C).
|
|
||||||
|
|
||||||
compatible([(N,R,S)|T],C):-
|
|
||||||
not_present_with_a_different_head(N,R,S,C),
|
|
||||||
compatible(T,C).
|
|
||||||
|
|
||||||
not_present_with_a_different_head(_N,_R,_S,[]).
|
|
||||||
|
|
||||||
not_present_with_a_different_head(N,R,S,[(N,R,S)|T]):-!,
|
|
||||||
not_present_with_a_different_head(N,R,S,T).
|
|
||||||
|
|
||||||
not_present_with_a_different_head(N,R,S,[(_N1,R,S1)|T]):-
|
|
||||||
S\=S1,!,
|
|
||||||
not_present_with_a_different_head(N,R,S,T).
|
|
||||||
|
|
||||||
not_present_with_a_different_head(N,R,S,[(_N1,R1,_S1)|T]):-
|
|
||||||
R\=R1,
|
|
||||||
not_present_with_a_different_head(N,R,S,T).
|
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
build_Cset(_LD,[],[],C,C).
|
|
||||||
|
|
||||||
build_Cset(LD,[H|T],[V|L],CIn,COut):-
|
|
||||||
nth0(H,LD,(V,C)),
|
|
||||||
append(C,CIn,C1),
|
|
||||||
build_Cset(LD,T,L,C1,COut).
|
|
||||||
|
|
||||||
|
|
||||||
/* find_rule(G,(R,S,N),Body,C) takes a goal G and the current C set and
|
|
||||||
returns the index R of a disjunctive rule resolving with G together with
|
|
||||||
the index N of the resolving head, the substitution S and the Body of the
|
|
||||||
rule */
|
|
||||||
find_rule(H,(R,S,N),Body,C):-
|
|
||||||
rule(R,S,_,Head,Body),
|
|
||||||
member_head(H,Head,0,N),
|
|
||||||
not_already_present_with_a_different_head(N,R,S,C).
|
|
||||||
|
|
||||||
find_rule(H,(R,S,Number),Body,C):-
|
|
||||||
rule(R,S,_,uniform(H:1/_Num,_P,Number),Body),
|
|
||||||
not_already_present_with_a_different_head(Number,R,S,C).
|
|
||||||
|
|
||||||
not_already_present_with_a_different_head(_N,_R,_S,[]).
|
|
||||||
|
|
||||||
not_already_present_with_a_different_head(N,R,S,[(N1,R,S1)|T]):-
|
|
||||||
not_different(N,N1,S,S1),!,
|
|
||||||
not_already_present_with_a_different_head(N,R,S,T).
|
|
||||||
|
|
||||||
not_already_present_with_a_different_head(N,R,S,[(_N1,R1,_S1)|T]):-
|
|
||||||
R\==R1,
|
|
||||||
not_already_present_with_a_different_head(N,R,S,T).
|
|
||||||
|
|
||||||
not_different(_N,_N1,S,S1):-
|
|
||||||
S\=S1,!.
|
|
||||||
|
|
||||||
not_different(N,N1,S,S1):-
|
|
||||||
N\=N1,!,
|
|
||||||
dif(S,S1).
|
|
||||||
|
|
||||||
not_different(N,N,S,S).
|
|
||||||
|
|
||||||
|
|
||||||
member_head(H,[(H:_P)|_T],N,N).
|
|
||||||
|
|
||||||
member_head(H,[(_H:_P)|T],NIn,NOut):-
|
|
||||||
N1 is NIn+1,
|
|
||||||
member_head(H,T,N1,NOut).
|
|
||||||
|
|
||||||
/* choose_clauses(CIn,LC,COut) takes as input the current C set and
|
|
||||||
the set of C sets for a negative goal and returns a new C set that
|
|
||||||
excludes all the derivations for the negative goals */
|
|
||||||
choose_clauses(C,[],C).
|
|
||||||
|
|
||||||
choose_clauses(CIn,[D|T],COut):-
|
|
||||||
member((N,R,S),D),
|
|
||||||
instantiation_present_with_the_same_head(N,R,S,CIn),
|
|
||||||
choose_a_different_head(N,R,S,T,CIn,COut).
|
|
||||||
|
|
||||||
choose_a_different_head(N,R,S,D,CIn,COut):-
|
|
||||||
/* cases 1 and 2 of Select */
|
|
||||||
choose_a_head(N,R,S,CIn,C1),
|
|
||||||
choose_clauses(C1,D,COut).
|
|
||||||
|
|
||||||
choose_a_different_head(N,R,S,D,CIn,COut):-
|
|
||||||
/* case 3 of Select */
|
|
||||||
new_head(N,R,S,N1),
|
|
||||||
\+ already_present(N1,R,S,CIn),
|
|
||||||
choose_clauses([(N1,R,S)|CIn],D,COut).
|
|
||||||
|
|
||||||
/* instantiation_present_with_the_same_head(N,R,S,C)
|
|
||||||
takes rule R with substitution S and selected head N and a C set
|
|
||||||
and asserts dif constraints for all the clauses in C of which RS
|
|
||||||
is an instantitation and have the same head selected */
|
|
||||||
instantiation_present_with_the_same_head(_N,_R,_S,[]).
|
|
||||||
|
|
||||||
instantiation_present_with_the_same_head(N,R,S,[(NH,R,SH)|T]):-
|
|
||||||
\+ \+ S=SH,
|
|
||||||
dif(N,NH),
|
|
||||||
instantiation_present_with_the_same_head(N,R,S,T).
|
|
||||||
|
|
||||||
instantiation_present_with_the_same_head(N,R,S,[(NH,R,SH)|T]):-
|
|
||||||
\+ \+ S=SH,
|
|
||||||
N=NH,!,
|
|
||||||
dif(S,SH),
|
|
||||||
instantiation_present_with_the_same_head(N,R,S,T).
|
|
||||||
|
|
||||||
instantiation_present_with_the_same_head(N,R,S,[_H|T]):-
|
|
||||||
instantiation_present_with_the_same_head(N,R,S,T).
|
|
||||||
|
|
||||||
/* case 1 of Select: a more general rule is present in C with
|
|
||||||
a different head, instantiate it */
|
|
||||||
choose_a_head(N,R,S,[(NH,R,SH)|T],[(NH,R,SH)|T]):-
|
|
||||||
S=SH,
|
|
||||||
dif(N,NH).
|
|
||||||
|
|
||||||
/* case 2 of Select: a more general rule is present in C with
|
|
||||||
a different head, ensure that they do not generate the same
|
|
||||||
ground clause */
|
|
||||||
choose_a_head(N,R,S,[(NH,R,SH)|T],[(NH,R,S),(NH,R,SH)|T]):-
|
|
||||||
\+ \+ S=SH, S\==SH,
|
|
||||||
dif(N,NH),
|
|
||||||
dif(S,SH).
|
|
||||||
|
|
||||||
choose_a_head(N,R,S,[H|T],[H|T1]):-
|
|
||||||
choose_a_head(N,R,S,T,T1).
|
|
||||||
|
|
||||||
/* select a head different from N for rule R with
|
|
||||||
substitution S, return it in N1 */
|
|
||||||
new_head(N,R,S,N1):-
|
|
||||||
rule(R,S,Numbers,Head,_Body),
|
|
||||||
Head\=uniform(_,_,_),!,
|
|
||||||
nth0(N, Numbers, _Elem, Rest),
|
|
||||||
member(N1,Rest).
|
|
||||||
|
|
||||||
new_head(N,R,S,N1):-
|
|
||||||
rule(R,S,Numbers,uniform(_A:1/Tot,_L,_Number),_Body),
|
|
||||||
listN(0,Tot,Numbers),
|
|
||||||
nth0(N, Numbers, _Elem, Rest),
|
|
||||||
member(N1,Rest).
|
|
||||||
|
|
||||||
/* checks that a rule R with head N and selection S is already
|
|
||||||
present in C (or a generalization of it is in C) */
|
|
||||||
already_present(N,R,S,[(N,R,SH)|_T]):-
|
|
||||||
S=SH.
|
|
||||||
|
|
||||||
already_present(N,R,S,[_H|T]):-
|
|
||||||
already_present(N,R,S,T).
|
|
||||||
|
|
||||||
/* rem_dup_lists removes the C sets that are a superset of
|
|
||||||
another C sets further on in the list of C sets */
|
|
||||||
rem_dup_lists([],[]).
|
|
||||||
|
|
||||||
rem_dup_lists([H|T],T1):-
|
|
||||||
member_subset(H,T),!,
|
|
||||||
rem_dup_lists(T,T1).
|
|
||||||
|
|
||||||
rem_dup_lists([H|T],[H|T1]):-
|
|
||||||
rem_dup_lists(T,T1).
|
|
||||||
|
|
||||||
member_subset(E,[H|_T]):-
|
|
||||||
subset_my(H,E),!.
|
|
||||||
|
|
||||||
member_subset(E,[_H|T]):-
|
|
||||||
member_subset(E,T).
|
|
||||||
|
|
||||||
/* predicates for building the formula to be converted into a BDD */
|
|
||||||
|
|
||||||
/* build_formula(LC,Formula,VarIn,VarOut) takes as input a set of C sets
|
|
||||||
LC and a list of Variables VarIn and returns the formula and a new list
|
|
||||||
of variables VarOut
|
|
||||||
Formula is of the form [Term1,...,Termn]
|
|
||||||
Termi is of the form [Factor1,...,Factorm]
|
|
||||||
Factorj is of the form (Var,Value) where Var is the index of
|
|
||||||
the multivalued variable Var and Value is the index of the value
|
|
||||||
*/
|
|
||||||
build_formula([],[],Var,Var).
|
|
||||||
|
|
||||||
build_formula([D|TD],[F|TF],VarIn,VarOut):-
|
|
||||||
build_term(D,F,VarIn,Var1),
|
|
||||||
build_formula(TD,TF,Var1,VarOut).
|
|
||||||
|
|
||||||
build_term([],[],Var,Var).
|
|
||||||
|
|
||||||
build_term([(N,R,S)|TC],[[NVar,N]|TF],VarIn,VarOut):-
|
|
||||||
(nth0_eq(0,NVar,VarIn,(R,S))->
|
|
||||||
Var1=VarIn
|
|
||||||
;
|
|
||||||
append(VarIn,[(R,S)],Var1),
|
|
||||||
length(VarIn,NVar)
|
|
||||||
),
|
|
||||||
build_term(TC,TF,Var1,VarOut).
|
|
||||||
|
|
||||||
/* nth0_eq(PosIn,PosOut,List,El) takes as input a List,
|
|
||||||
an element El and an initial position PosIn and returns in PosOut
|
|
||||||
the position in the List that contains an element exactly equal to El
|
|
||||||
*/
|
|
||||||
nth0_eq(N,N,[H|_T],El):-
|
|
||||||
H==El,!.
|
|
||||||
|
|
||||||
nth0_eq(NIn,NOut,[_H|T],El):-
|
|
||||||
N1 is NIn+1,
|
|
||||||
nth0_eq(N1,NOut,T,El).
|
|
||||||
|
|
||||||
/* var2numbers converts a list of couples (Rule,Substitution) into a list
|
|
||||||
of triples (N,NumberOfHeadsAtoms,ListOfProbabilities), where N is an integer
|
|
||||||
starting from 0 */
|
|
||||||
var2numbers([],_N,[]).
|
|
||||||
|
|
||||||
var2numbers([(R,S)|T],N,[[N,ValNumber,Probs]|TNV]):-
|
|
||||||
find_probs(R,S,Probs),
|
|
||||||
length(Probs,ValNumber),
|
|
||||||
N1 is N+1,
|
|
||||||
var2numbers(T,N1,TNV).
|
|
||||||
|
|
||||||
find_probs(R,S,Probs):-
|
|
||||||
rule(R,S,_N,Head,_Body),
|
|
||||||
get_probs(Head,Probs).
|
|
||||||
|
|
||||||
get_probs(uniform(_A:1/Num,_P,_Number),ListP):-
|
|
||||||
Prob is 1/Num,
|
|
||||||
list_el(Num,Prob,ListP).
|
|
||||||
|
|
||||||
get_probs([],[]).
|
|
||||||
|
|
||||||
get_probs([_H:P|T],[P1|T1]):-
|
|
||||||
P1 is P,
|
|
||||||
get_probs(T,T1).
|
|
||||||
|
|
||||||
list_el(0,_P,[]):-!.
|
|
||||||
|
|
||||||
list_el(N,P,[P|T]):-
|
|
||||||
N1 is N-1,
|
|
||||||
list_el(N1,P,T).
|
|
||||||
|
|
||||||
/* end of predicates for building the formula to be converted into a BDD */list_el(0,_P,[]):-!.
|
|
||||||
|
|
||||||
|
|
||||||
/* start of predicates for parsing an input file containing a program */
|
|
||||||
|
|
||||||
/* p(File) parses the file File.cpl. It can be called more than once without
|
|
||||||
exiting yap */
|
|
||||||
p(File):-
|
|
||||||
parse(File).
|
|
||||||
|
|
||||||
parse(File):-
|
|
||||||
atom_concat(File,'.cpl',FilePl),
|
|
||||||
open(FilePl,read,S),
|
|
||||||
read_clauses(S,C),
|
|
||||||
close(S),
|
|
||||||
retractall(rule(_,_,_,_,_)),
|
|
||||||
retractall(def_rule(_,_)),
|
|
||||||
process_clauses(C,1).
|
|
||||||
|
|
||||||
process_clauses([(end_of_file,[])],_N).
|
|
||||||
|
|
||||||
process_clauses([((H:-B),V)|T],N):-
|
|
||||||
H=uniform(A,P,L),!,
|
|
||||||
list2and(BL,B),
|
|
||||||
process_body(BL,V,V1),
|
|
||||||
remove_vars([P],V1,V2),
|
|
||||||
append(BL,[length(L,Tot),nth0(Number,L,P)],BL1),
|
|
||||||
append(V2,['Tot'=Tot],V3),
|
|
||||||
assertz(rule(N,V3,_NH,uniform(A:1/Tot,L,Number),BL1)),
|
|
||||||
N1 is N+1,
|
|
||||||
process_clauses(T,N1).
|
|
||||||
|
|
||||||
process_clauses([((H:-B),V)|T],N):-
|
|
||||||
H=(_;_),!,
|
|
||||||
list2or(HL1,H),
|
|
||||||
process_head(HL1,HL),
|
|
||||||
list2and(BL,B),
|
|
||||||
process_body(BL,V,V1),
|
|
||||||
length(HL,LH),
|
|
||||||
listN(0,LH,NH),
|
|
||||||
assertz(rule(N,V1,NH,HL,BL)),
|
|
||||||
N1 is N+1,
|
|
||||||
process_clauses(T,N1).
|
|
||||||
|
|
||||||
process_clauses([((H:-B),V)|T],N):-
|
|
||||||
H=(_:_),!,
|
|
||||||
list2or(HL1,H),
|
|
||||||
process_head(HL1,HL),
|
|
||||||
list2and(BL,B),
|
|
||||||
process_body(BL,V,V1),
|
|
||||||
length(HL,LH),
|
|
||||||
listN(0,LH,NH),
|
|
||||||
assertz(rule(N,V1,NH,HL,BL)),
|
|
||||||
N1 is N+1,
|
|
||||||
process_clauses(T,N1).
|
|
||||||
|
|
||||||
process_clauses([((H:-B),_V)|T],N):-!,
|
|
||||||
list2and(BL,B),
|
|
||||||
assert(def_rule(H,BL)),
|
|
||||||
process_clauses(T,N).
|
|
||||||
|
|
||||||
process_clauses([(H,V)|T],N):-
|
|
||||||
H=(_;_),!,
|
|
||||||
list2or(HL1,H),
|
|
||||||
process_head(HL1,HL),
|
|
||||||
length(HL,LH),
|
|
||||||
listN(0,LH,NH),
|
|
||||||
assertz(rule(N,V,NH,HL,[])),
|
|
||||||
N1 is N+1,
|
|
||||||
process_clauses(T,N1).
|
|
||||||
|
|
||||||
process_clauses([(H,V)|T],N):-
|
|
||||||
H=(_:_),!,
|
|
||||||
list2or(HL1,H),
|
|
||||||
process_head(HL1,HL),
|
|
||||||
length(HL,LH),
|
|
||||||
listN(0,LH,NH),
|
|
||||||
assertz(rule(N,V,NH,HL,[])),
|
|
||||||
N1 is N+1,
|
|
||||||
process_clauses(T,N1).
|
|
||||||
|
|
||||||
process_clauses([(H,_V)|T],N):-
|
|
||||||
assert(def_rule(H,[])),
|
|
||||||
process_clauses(T,N).
|
|
||||||
|
|
||||||
/* if the annotation in the head are not ground, the null atom is not added
|
|
||||||
and the eventual formulas are not evaluated */
|
|
||||||
|
|
||||||
process_head(HL,NHL):-
|
|
||||||
(ground_prob(HL)->
|
|
||||||
process_head_ground(HL,0,NHL)
|
|
||||||
;
|
|
||||||
NHL=HL
|
|
||||||
).
|
|
||||||
|
|
||||||
ground_prob([]).
|
|
||||||
|
|
||||||
ground_prob([_H:PH|T]):-
|
|
||||||
ground(PH),
|
|
||||||
ground_prob(T).
|
|
||||||
|
|
||||||
process_head_ground([H:PH],P,[H:PH1|Null]):-
|
|
||||||
PH1 is PH,
|
|
||||||
PNull is 1-P-PH1,
|
|
||||||
setting(epsilon_parsing,Eps),
|
|
||||||
EpsNeg is - Eps,
|
|
||||||
PNull > EpsNeg,
|
|
||||||
(PNull>Eps->
|
|
||||||
Null=['':PNull]
|
|
||||||
;
|
|
||||||
Null=[]
|
|
||||||
).
|
|
||||||
|
|
||||||
process_head_ground([H:PH|T],P,[H:PH1|NT]):-
|
|
||||||
PH1 is PH,
|
|
||||||
P1 is P+PH1,
|
|
||||||
process_head_ground(T,P1,NT).
|
|
||||||
|
|
||||||
/* setof must have a goal of the form B^G where B is a term containing the existential variables */
|
|
||||||
process_body([],V,V).
|
|
||||||
|
|
||||||
process_body([setof(A,B^_G,_L)|T],VIn,VOut):-!,
|
|
||||||
get_var(A,VA),
|
|
||||||
get_var(B,VB),
|
|
||||||
remove_vars(VA,VIn,V1),
|
|
||||||
remove_vars(VB,V1,V2),
|
|
||||||
process_body(T,V2,VOut).
|
|
||||||
|
|
||||||
process_body([setof(A,_G,_L)|T],VIn,VOut):-!,
|
|
||||||
get_var(A,VA),
|
|
||||||
remove_vars(VA,VIn,V1),
|
|
||||||
process_body(T,V1,VOut).
|
|
||||||
|
|
||||||
process_body([bagof(A,B^_G,_L)|T],VIn,VOut):-!,
|
|
||||||
get_var(A,VA),
|
|
||||||
get_var(B,VB),
|
|
||||||
remove_vars(VA,VIn,V1),
|
|
||||||
remove_vars(VB,V1,V2),
|
|
||||||
process_body(T,V2,VOut).
|
|
||||||
|
|
||||||
process_body([bagof(A,_G,_L)|T],VIn,VOut):-!,
|
|
||||||
get_var(A,VA),
|
|
||||||
remove_vars(VA,VIn,V1),
|
|
||||||
process_body(T,V1,VOut).
|
|
||||||
|
|
||||||
process_body([_H|T],VIn,VOut):-!,
|
|
||||||
process_body(T,VIn,VOut).
|
|
||||||
|
|
||||||
get_var_list([],[]).
|
|
||||||
|
|
||||||
get_var_list([H|T],[H|T1]):-
|
|
||||||
var(H),!,
|
|
||||||
get_var_list(T,T1).
|
|
||||||
|
|
||||||
get_var_list([H|T],VarOut):-!,
|
|
||||||
get_var(H,Var),
|
|
||||||
append(Var,T1,VarOut),
|
|
||||||
get_var_list(T,T1).
|
|
||||||
|
|
||||||
get_var(A,[A]):-
|
|
||||||
var(A),!.
|
|
||||||
|
|
||||||
get_var(A,V):-
|
|
||||||
A=..[_F|Args],
|
|
||||||
get_var_list(Args,V).
|
|
||||||
|
|
||||||
remove_vars([],V,V).
|
|
||||||
|
|
||||||
remove_vars([H|T],VIn,VOut):-
|
|
||||||
delete_var(H,VIn,V1),
|
|
||||||
remove_vars(T,V1,VOut).
|
|
||||||
|
|
||||||
delete_var(_H,[],[]).
|
|
||||||
|
|
||||||
delete_var(V,[VN=Var|T],[VN=Var|T1]):-
|
|
||||||
V\==Var,!,
|
|
||||||
delete_var(V,T,T1).
|
|
||||||
|
|
||||||
delete_var(_V,[_H|T],T).
|
|
||||||
|
|
||||||
read_clauses(S,[(Cl,V)|Out]):-
|
|
||||||
read_term(S,Cl,[variable_names(V)]),
|
|
||||||
(Cl=end_of_file->
|
|
||||||
Out=[]
|
|
||||||
;
|
|
||||||
read_clauses(S,Out)
|
|
||||||
).
|
|
||||||
|
|
||||||
listN(N,N,[]):-!.
|
|
||||||
|
|
||||||
listN(NIn,N,[NIn|T]):-
|
|
||||||
N1 is NIn+1,
|
|
||||||
listN(N1,N,T).
|
|
||||||
/* end of predicates for parsing an input file containing a program */
|
|
||||||
|
|
||||||
/* start of utility predicates */
|
|
||||||
list2or([X],X):-
|
|
||||||
X\=;(_,_),!.
|
|
||||||
|
|
||||||
list2or([H|T],(H ; Ta)):-!,
|
|
||||||
list2or(T,Ta).
|
|
||||||
|
|
||||||
list2and([X],X):-
|
|
||||||
X\=(_,_),!.
|
|
||||||
|
|
||||||
list2and([H|T],(H,Ta)):-!,
|
|
||||||
list2and(T,Ta).
|
|
||||||
|
|
||||||
member_eq(A,[H|_T]):-
|
|
||||||
A==H.
|
|
||||||
|
|
||||||
member_eq(A,[_H|T]):-
|
|
||||||
member_eq(A,T).
|
|
||||||
|
|
||||||
subset_my([],_).
|
|
||||||
|
|
||||||
subset_my([H|T],L):-
|
|
||||||
member_eq(H,L),
|
|
||||||
subset_my(T,L).
|
|
||||||
|
|
||||||
remove_duplicates_eq([],[]).
|
|
||||||
|
|
||||||
remove_duplicates_eq([H|T],T1):-
|
|
||||||
member_eq(H,T),!,
|
|
||||||
remove_duplicates_eq(T,T1).
|
|
||||||
|
|
||||||
remove_duplicates_eq([H|T],[H|T1]):-
|
|
||||||
remove_duplicates_eq(T,T1).
|
|
||||||
|
|
||||||
builtin(_A is _B).
|
|
||||||
builtin(_A > _B).
|
|
||||||
builtin(_A < _B).
|
|
||||||
builtin(_A >= _B).
|
|
||||||
builtin(_A =< _B).
|
|
||||||
builtin(_A =:= _B).
|
|
||||||
builtin(_A =\= _B).
|
|
||||||
builtin(true).
|
|
||||||
builtin(false).
|
|
||||||
builtin(_A = _B).
|
|
||||||
builtin(_A==_B).
|
|
||||||
builtin(_A\=_B).
|
|
||||||
builtin(_A\==_B).
|
|
||||||
builtin(length(_L,_N)).
|
|
||||||
builtin(member(_El,_L)).
|
|
||||||
builtin(average(_L,_Av)).
|
|
||||||
builtin(max_list(_L,_Max)).
|
|
||||||
builtin(min_list(_L,_Max)).
|
|
||||||
builtin(nth0(_,_,_)).
|
|
||||||
builtin(nth(_,_,_)).
|
|
||||||
average(L,Av):-
|
|
||||||
sum_list(L,Sum),
|
|
||||||
length(L,N),
|
|
||||||
Av is Sum/N.
|
|
||||||
|
|
||||||
clique(Graph,Clique):-
|
|
||||||
vertices(Graph,Candidates),
|
|
||||||
extend_cycle(Graph,Candidates,[],[],Clique).
|
|
||||||
|
|
||||||
extend_cycle(G,[H|T],Not,CS,CSOut):-
|
|
||||||
neighbours(H, G, Neigh),
|
|
||||||
intersection(Neigh,T,NewCand),
|
|
||||||
intersection(Neigh,Not,NewNot),
|
|
||||||
extend(G,NewCand,NewNot,[H|CS],CSOut).
|
|
||||||
|
|
||||||
extend_cycle(G,[H|T],Not,CS,CSOut):-
|
|
||||||
extend_cycle(G,T,[H|Not],CS,CSOut).
|
|
||||||
|
|
||||||
extend(_G,[],[],CompSub,CompSub):-!.
|
|
||||||
|
|
||||||
extend(G,Cand,Not,CS,CSOut):-
|
|
||||||
extend_cycle(G,Cand,Not,CS,CSOut).
|
|
||||||
|
|
||||||
intersection([],_Y,[]).
|
|
||||||
|
|
||||||
intersection([H|T],Y,[H|Z]):-
|
|
||||||
member(H,Y),!,
|
|
||||||
intersection(T,Y,Z).
|
|
||||||
|
|
||||||
intersection([_H|T],Y,Z):-
|
|
||||||
intersection(T,Y,Z).
|
|
||||||
|
|
||||||
/* set(Par,Value) can be used to set the value of a parameter */
|
|
||||||
set(Parameter,Value):-
|
|
||||||
retract(setting(Parameter,_)),
|
|
||||||
assert(setting(Parameter,Value)).
|
|
||||||
|
|
||||||
/* end of utility predicates */
|
|
@ -1,546 +0,0 @@
|
|||||||
@Book{Lloyd,
|
|
||||||
author = {J. W. Lloyd},
|
|
||||||
title = {Foundations of Logic Programming},
|
|
||||||
edition = {2nd extended},
|
|
||||||
isbn = {3-540-18199-7},
|
|
||||||
publisher = {Springer-Verlag},
|
|
||||||
year = {1987},
|
|
||||||
}
|
|
||||||
|
|
||||||
@MISC{Str05-pc,
|
|
||||||
author = {J. Struyf},
|
|
||||||
year = {2005},
|
|
||||||
note = {Personal communication},
|
|
||||||
}
|
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
@MISC{Sri05-web,
|
|
||||||
author = {A. Srinivasan},
|
|
||||||
title = {Aleph},
|
|
||||||
year = {2004},
|
|
||||||
note = {http://web.comlab.ox.ac.uk/oucl/research/areas/machlearn/Aleph/aleph_toc.html},
|
|
||||||
}
|
|
||||||
|
|
||||||
|
|
||||||
@article{RaeDeh97-ML,
|
|
||||||
Author = "De Raedt, L. and Dehaspe, L.",
|
|
||||||
Title = "Clausal discovery",
|
|
||||||
Journal = "Machine Learning",
|
|
||||||
Year = 1997,
|
|
||||||
pages ={99--146},
|
|
||||||
number={2--3},
|
|
||||||
volume ={26}
|
|
||||||
}
|
|
||||||
|
|
||||||
@BOOK{GreVal85-book,
|
|
||||||
author = {S. Greco and P. Valabrega},
|
|
||||||
title = {Lezioni di Matematica: Algebra Lineare},
|
|
||||||
volume = {1},
|
|
||||||
publisher = {Levrotto e Bella},
|
|
||||||
year = {1985},
|
|
||||||
address = {Torino, Italy},
|
|
||||||
}
|
|
||||||
@BOOK{NiedeW97-book,
|
|
||||||
author = {S. Nienhuys-Cheng and R. de Wolf},
|
|
||||||
title = {Foundations of Inductive Logic Programming},
|
|
||||||
publisher = {Springer},
|
|
||||||
year = {1997},
|
|
||||||
number = {1228},
|
|
||||||
series = {Lecture Notes in Artificial Intelligence},
|
|
||||||
address = {Berlin, Germany},
|
|
||||||
}
|
|
||||||
|
|
||||||
|
|
||||||
@techreport{VenVer03-TR,
|
|
||||||
author = {J. Vennekens and S. Verbaeten},
|
|
||||||
title = {Logic Programs With Annotated Disjunctions},
|
|
||||||
year = {2003},
|
|
||||||
institution = {K. U. Leuven},
|
|
||||||
number = {CW386},
|
|
||||||
note = {\href{http://www.cs.kuleuven.ac.be/\%7Ejoost/techrep.ps}{http://www.cs.kuleuven.ac.be/\%7Ejoost/techrep.ps}},
|
|
||||||
}
|
|
||||||
@BOOK{LobMinRaj92-book,
|
|
||||||
author = {J. Lobo and J. Minker and A. Rajasekar},
|
|
||||||
title = {Foundations of Disjunctive Logic Programming},
|
|
||||||
publisher = {{MIT} Press},
|
|
||||||
year = {1992},
|
|
||||||
address = {Cambridge, Massachusetts},
|
|
||||||
}
|
|
||||||
|
|
||||||
|
|
||||||
@inProceedings{VenVer04-ICLP04-IC,
|
|
||||||
author = {J. Vennekens and S. Verbaeten and M. Bruynooghe},
|
|
||||||
title = {Logic Programs With Annotated Disjunctions},
|
|
||||||
booktitle = {The 20th International Conference on Logic Programming ({ICLP} 2004)},
|
|
||||||
year = {2004},
|
|
||||||
note={\href{http://www.cs.kuleuven.ac.be/\%7Ejoost/}{http://www.cs.kuleuven.ac.be/\%7Ejoost/}},
|
|
||||||
}
|
|
||||||
Institute for Artificial Intelligence, Vienna, TR-95-09, 1995.
|
|
||||||
@techreport{Hol03-TR,
|
|
||||||
author = {C. Holzbaur},
|
|
||||||
title = {{OFAI} clp(q,r) Manual, Edition 1.3.3 },
|
|
||||||
year = {1995},
|
|
||||||
institution = {Austrian Research Institute for Artificial Intelligence},
|
|
||||||
number = {TR-95-09},
|
|
||||||
address={Vienna},
|
|
||||||
}
|
|
||||||
|
|
||||||
@ARTICLE{NgSub92-InfCom-IJ,
|
|
||||||
author = {R. T. Ng and V. S. Subrahmanian},
|
|
||||||
title = {Probabilistic Logic Programming},
|
|
||||||
journal = {Information and Computation},
|
|
||||||
year = {1992},
|
|
||||||
volume = {101},
|
|
||||||
number = {2},
|
|
||||||
pages = {150--201},
|
|
||||||
}
|
|
||||||
@inProceedings{KerDeR01-ILP01-IC,
|
|
||||||
author = {K. Kersting and L. De Raedt},
|
|
||||||
title = {Towards Combining Inductive Logic Programming and Bayesian Networks},
|
|
||||||
booktitle = {Inductive Logic Programming ({ILP} 2001)},
|
|
||||||
year = {2001},
|
|
||||||
editor = {C. Rouveirol and M. Sebag},
|
|
||||||
publisher={Springer-Verlag},
|
|
||||||
series={{LNAI}},
|
|
||||||
number={2157}
|
|
||||||
}
|
|
||||||
|
|
||||||
@inProceedings{KerDeR00-ILP00-IC,
|
|
||||||
author = {K. Kersting and L. De Raedt},
|
|
||||||
title = {Bayesian Logic Programs},
|
|
||||||
booktitle = {Inductive Logic Programming ({ILP} 2000), Work in Progress Track},
|
|
||||||
year = {2000},
|
|
||||||
url={http://SunSITE.Informatik.RWTH-Aachen.DE/Publications/CEUR-WS/Vol-35/},
|
|
||||||
}
|
|
||||||
@techreport{KerDeR01-TR,
|
|
||||||
author = {K. Kersting and L. De Raedt},
|
|
||||||
title = {Bayesian Logic Programs},
|
|
||||||
year = {2001},
|
|
||||||
institution = {Institute for Computer Science, University of Freiburg},
|
|
||||||
number = {151},
|
|
||||||
address={Freiburg, Germany},
|
|
||||||
month ={April},
|
|
||||||
}
|
|
||||||
@incollection{GetFri01-BC,
|
|
||||||
author = {L. Getoor and N. Friedman and D. Koller and A. Pfeffer},
|
|
||||||
title = {Learning Probabilistic Relational Models},
|
|
||||||
booktitle = {Relational Data Mining},
|
|
||||||
publisher = {Springer-Verlag},
|
|
||||||
year = {2001},
|
|
||||||
editor ={Saso Dzeroski and Nada Lavrac},
|
|
||||||
address = {Berlin},
|
|
||||||
}
|
|
||||||
@ARTICLE{NgoHad97-TheoCS-IJ,
|
|
||||||
author = {L. Ngo and P. Haddaway},
|
|
||||||
title = {Answering Queries from Context-Sensitive Probabilistic
|
|
||||||
Knowledge Bases},
|
|
||||||
journal = {Theoretical Computer Science},
|
|
||||||
year = {1997},
|
|
||||||
volume = {171},
|
|
||||||
number = {1--2},
|
|
||||||
pages = {147-177},
|
|
||||||
}
|
|
||||||
@ARTICLE{Poo97-ArtInt-IJ,
|
|
||||||
author = {D. Poole},
|
|
||||||
title = {The {I}ndependent {C}hoice {L}ogic for Modelling Multiple Agents under
|
|
||||||
Uncertainty},
|
|
||||||
journal = {Artificial Intelligence},
|
|
||||||
year = {1997},
|
|
||||||
volume = {94},
|
|
||||||
number = {1--2},
|
|
||||||
pages = {7--56},
|
|
||||||
}
|
|
||||||
@article{mugg:mi17:slplearn,
|
|
||||||
TITLE = "Learning Stochastic Logic Programs",
|
|
||||||
AUTHOR = "S. H. Muggleton",
|
|
||||||
YEAR = 2000,
|
|
||||||
JOURNAL = "Electronic Transactions in Artificial Intelligence",
|
|
||||||
VOLUME = 4,
|
|
||||||
NUMBER = "041",
|
|
||||||
URL = "http://www.ida.liu.se/ext/epa/cis/2000/041/tcover.html" }
|
|
||||||
|
|
||||||
@inProceedings{Cus00-UAI00-IC,
|
|
||||||
author = {J. Cussens},
|
|
||||||
title = {Stochastic logic programs: Sampling, inference and applications},
|
|
||||||
booktitle = {Uncertainty in Artificial Intelligence ({UAI} 2000)},
|
|
||||||
year = {2000},
|
|
||||||
publisher={Morgan Kaufmann},
|
|
||||||
address= {San Francisco, CA},
|
|
||||||
pages= {115--122},
|
|
||||||
}
|
|
||||||
|
|
||||||
@inProceedings{Sat98-MD-IW,
|
|
||||||
author = {Sato, T.},
|
|
||||||
title = {Modeling scientific theories as PRISM programs},
|
|
||||||
booktitle = {{ECAI98} Workshop on Machine Discovery},
|
|
||||||
year = {1998},
|
|
||||||
pages= {37--45},
|
|
||||||
}
|
|
||||||
@inProceedings{Sat95-ICLP-IC,
|
|
||||||
author = { Sato, T.},
|
|
||||||
title = {A statistical learning method for logic programs with distribution semantics},
|
|
||||||
booktitle = {12th International Conference on Logic Programming ({ICLP} 1995)},
|
|
||||||
year = {1995},
|
|
||||||
pages= {715–-729},
|
|
||||||
}
|
|
||||||
@inProceedings{SanPagQaz03-UAI-IC,
|
|
||||||
author = {Santos Costa, V. and D. Page and M. Qazi and J. Cussens},
|
|
||||||
title = {{CLP(BN)}: Constraint Logic Programming for Probabilistic Knowledge},
|
|
||||||
booktitle = {Uncertainty in Artificial Intelligence ({UAI} 2003)},
|
|
||||||
year = {2003},
|
|
||||||
}
|
|
||||||
@inProceedings{Blo03-MRDM-IW,
|
|
||||||
author = {H. Blockeel},
|
|
||||||
title = {Prolog for First-Order Bayesian Networks: A Meta-intepreter Approach},
|
|
||||||
booktitle = {Multi-Relational Data Mining ({MRDM} 2003)},
|
|
||||||
year = {2003},
|
|
||||||
}
|
|
||||||
@INPROCEEDINGS{Ngo96-UAI-IC,
|
|
||||||
AUTHOR = "Ngo, L. ",
|
|
||||||
TITLE = "Probabilistic Disjunctive Logic Programming",
|
|
||||||
BOOKTITLE = "Uncertainty in Artificial Intelligence ({UAI} 1996)",
|
|
||||||
PUBLISHER = "Morgan Kaufmann Publishers",
|
|
||||||
ADDRESS = "San Francisco, CA",
|
|
||||||
YEAR = "1996",
|
|
||||||
PAGES = "397--404"
|
|
||||||
}
|
|
||||||
@article{Getoor+al:JMLR02,
|
|
||||||
author = "L. Getoor and N. Friedman and D. Koller and B.
|
|
||||||
Taskar",
|
|
||||||
journal = {Journal of Machine Learning Research},
|
|
||||||
title = "Learning probabilistic models of Relational Structure",
|
|
||||||
volume = 3,
|
|
||||||
month = {December},
|
|
||||||
pages = {679-707},
|
|
||||||
year = "2002",
|
|
||||||
}
|
|
||||||
|
|
||||||
@ARTICLE{well-founded,
|
|
||||||
author = {Van Gelder, A. and K. A. Ross and J. S. Schlipf},
|
|
||||||
title = {The Well-founded Semantics for General Logic Programs},
|
|
||||||
journal = {Journal of the {ACM}},
|
|
||||||
volume = {38},
|
|
||||||
number = {3},
|
|
||||||
pages = {620--650},
|
|
||||||
year = {1991}
|
|
||||||
}
|
|
||||||
@inProceedings{stable-models,
|
|
||||||
author = {M. Gelfond and V. Lifschitz},
|
|
||||||
title = {The Stable Model Semantics for Logic Programming},
|
|
||||||
booktitle = {Proceedings of the 5th Int. Conf. on Logic Programming},
|
|
||||||
editor = {R. Kowalski and K. A. Bowen},
|
|
||||||
year = 1988,
|
|
||||||
publisher = {{MIT} Press},
|
|
||||||
pages = {1070--1080}
|
|
||||||
}
|
|
||||||
@INCOLLECTION{Cla78,
|
|
||||||
author = {K. L. Clark},
|
|
||||||
title = {Negation as Failure},
|
|
||||||
booktitle= {Logic and Databases},
|
|
||||||
publisher = {Plenum Press},
|
|
||||||
year = 1978
|
|
||||||
}
|
|
||||||
|
|
||||||
|
|
||||||
@inproceedings{DeRKerKim-ILP06,
|
|
||||||
author = {De Raedt, L. and K. Kersting and A. Kimmig and K. Revoredo and H. Toivonen},
|
|
||||||
title = {Revising Probabilistic Prolog Programs},
|
|
||||||
booktitle = {Proceedings of the 16th International Conference on Inductive Logic Programming},
|
|
||||||
year = {2007},
|
|
||||||
publisher = {Springer},
|
|
||||||
number = {4455},
|
|
||||||
series = {LNAI},
|
|
||||||
}
|
|
||||||
|
|
||||||
@inproceedings{Rig-ILP06,
|
|
||||||
author={F. Riguzzi},
|
|
||||||
title={{ALLPAD}: Approximate Learning of Logic Programs with Annotated Disjunctions},
|
|
||||||
booktitle={Proceedings of the 16th International Conference on Inductive Logic Programming},
|
|
||||||
year={2007},
|
|
||||||
publisher={Springer},
|
|
||||||
number={4455},
|
|
||||||
series = {LNAI},
|
|
||||||
}
|
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
@inproceedings{DBLP:conf/ijcai/RaedtKT07,
|
|
||||||
author = {De Raedt, L. and
|
|
||||||
A. Kimmig and
|
|
||||||
H. Toivonen},
|
|
||||||
title = {ProbLog: A Probabilistic Prolog and Its Application in Link
|
|
||||||
Discovery.},
|
|
||||||
booktitle = {Proceedings of the 20th International Joint
|
|
||||||
Conference on Artificial Intelligence},
|
|
||||||
year = {2007},
|
|
||||||
pages = {2462-2467},
|
|
||||||
ee = {http://www.ijcai.org/papers07/Papers/IJCAI07-396.pdf},
|
|
||||||
bibsource = {DBLP, http://dblp.uni-trier.de}
|
|
||||||
}
|
|
||||||
|
|
||||||
|
|
||||||
@article{DBLP:journals/ngc/AptB91,
|
|
||||||
author = {K. R. Apt and
|
|
||||||
M. Bezem},
|
|
||||||
title = {Acyclic Programs.},
|
|
||||||
journal = {New Generation Comput.},
|
|
||||||
volume = {9},
|
|
||||||
number = {3/4},
|
|
||||||
year = {1991},
|
|
||||||
pages = {335-364},
|
|
||||||
bibsource = {DBLP, http://dblp.uni-trier.de}
|
|
||||||
}
|
|
||||||
|
|
||||||
@article{DBLP:journals/jlp/Fitting85a,
|
|
||||||
author = {M. Fitting},
|
|
||||||
title = {A Kripke-Kleene Semantics for Logic Programs.},
|
|
||||||
journal = {J. Log. Program.},
|
|
||||||
volume = {2},
|
|
||||||
number = {4},
|
|
||||||
year = {1985},
|
|
||||||
pages = {295-312},
|
|
||||||
bibsource = {DBLP, http://dblp.uni-trier.de}
|
|
||||||
}
|
|
||||||
@inproceedings{DBLP:conf/ki/HitzlerW02,
|
|
||||||
author = {P. Hitzler and
|
|
||||||
M. Wendt},
|
|
||||||
title = {The Well-Founded Semantics Is a Stratified Fitting Semantics.},
|
|
||||||
booktitle = {Annual
|
|
||||||
German Conference on AI, ({KI} 2002)},
|
|
||||||
year = {2002},
|
|
||||||
pages = {205-221},
|
|
||||||
publisher = {Springer},
|
|
||||||
series = {LNCS},
|
|
||||||
number = {2479},
|
|
||||||
ee = {http://link.springer.de/link/service/series/0558/bibs/2479/24790205.htm},
|
|
||||||
bibsource = {DBLP, http://dblp.uni-trier.de}
|
|
||||||
}
|
|
||||||
|
|
||||||
|
|
||||||
@inProceedings{FieBloRamBru-MRDM04,
|
|
||||||
author={D. Fierens and H. Blockeel and J. Ramon and M. Bruynooghe},
|
|
||||||
title={Logical Bayesian networks},
|
|
||||||
booktitle={Multi-Relational Data Mining ({MRDM} 2004)},
|
|
||||||
pages={19--30},
|
|
||||||
year={2004},
|
|
||||||
}
|
|
||||||
|
|
||||||
@inProceedings{Blo04-ILP04WIP-IC,
|
|
||||||
author = {H. Blockeel},
|
|
||||||
title = {Probabilistic logical models for Mendel's
|
|
||||||
experiments: An exercise},
|
|
||||||
booktitle = {Inductive Logic Programming ({ILP} 2004), Work in Progress Track},
|
|
||||||
year = {2004},
|
|
||||||
}
|
|
||||||
|
|
||||||
@techreport{Rig06-TR,
|
|
||||||
author = {F. Riguzzi},
|
|
||||||
title = {{ALLPAD}: Approximate Learning of Logic Programs With Annotated Disjunctions},
|
|
||||||
year = {2006},
|
|
||||||
institution = {University of Ferrara},
|
|
||||||
number = {CS-2006-01},
|
|
||||||
note = {http://www.ing.unife.it/aree\_ricerca/informazione/cs/technical\_reports/CS-2006-01.pdf},
|
|
||||||
}
|
|
||||||
|
|
||||||
|
|
||||||
@inproceedings{DBLP:conf/ismis/DehaspeR96,
|
|
||||||
author = {L. Dehaspe and
|
|
||||||
L. De Raedt},
|
|
||||||
title = {{DLAB}: A Declarative Language Bias Formalism.},
|
|
||||||
booktitle = {International Symposium on Methodologies for Intelligent Systems,
|
|
||||||
({ISMIS} 1996)},
|
|
||||||
editor = {Z. W. Ras and
|
|
||||||
M. Michalewicz},
|
|
||||||
year = {1996},
|
|
||||||
publisher = {Springer},
|
|
||||||
series = {LNCS},
|
|
||||||
number = {1079},
|
|
||||||
isbn = {3-540-61286-6},
|
|
||||||
pages = {613-622},
|
|
||||||
bibsource = {DBLP, http://dblp.uni-trier.de}
|
|
||||||
}
|
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
@MISC{Sri05-web-mlj,
|
|
||||||
author = {A. Srinivasan},
|
|
||||||
title = {Aleph},
|
|
||||||
year = {2004},
|
|
||||||
note = {http://web.comlab.ox.ac.uk/oucl/research/ areas/machlearn/Aleph/aleph\_toc.html},
|
|
||||||
}
|
|
||||||
|
|
||||||
@incollection{Prz88-Chapter,
|
|
||||||
author = {T. C. Przymusinski},
|
|
||||||
title = {On the declarative semantics of deductive databases and logic programs},
|
|
||||||
booktitle = {Foundations of deductive databases and logic programming},
|
|
||||||
year = {1988},
|
|
||||||
isbn = {0-934613-40-0},
|
|
||||||
pages = {193--216},
|
|
||||||
editor = {J. Minker},
|
|
||||||
publisher = {Morgan Kaufmann Publishers Inc.},
|
|
||||||
address = {San Francisco, CA, USA},
|
|
||||||
}
|
|
||||||
@article{DBLP:journals/ml/TurcotteMS01,
|
|
||||||
author = {M. Turcotte and
|
|
||||||
S. Muggleton and
|
|
||||||
M. J. E. Sternberg},
|
|
||||||
title = {The Effect of Relational Background Knowledge on Learning
|
|
||||||
of Protein Three-Dimensional Fold Signatures.},
|
|
||||||
journal = {Machine Learning},
|
|
||||||
volume = {43},
|
|
||||||
number = {1/2},
|
|
||||||
year = {2001},
|
|
||||||
pages = {81-95},
|
|
||||||
bibsource = {DBLP, http://dblp.uni-trier.de}
|
|
||||||
}
|
|
||||||
@inproceedings{DBLP:conf/psb/KerstingRKR03,
|
|
||||||
author = {K. Kersting and
|
|
||||||
T. Raiko and
|
|
||||||
S. Kramer and
|
|
||||||
L. De Raedt},
|
|
||||||
title = {Towards Discovering Structural Signatures of Protein Folds
|
|
||||||
Based on Logical Hidden Markov Models.},
|
|
||||||
booktitle = {Pacific Symposium on Biocomputing},
|
|
||||||
year = {2003},
|
|
||||||
pages = {192-203},
|
|
||||||
ee = {http://helix-web.stanford.edu/psb03/kersting.pdf},
|
|
||||||
bibsource = {DBLP, http://dblp.uni-trier.de}
|
|
||||||
}
|
|
||||||
@inproceedings{DBLP:conf/dis/StolleKR05,
|
|
||||||
author = {C. Stolle and
|
|
||||||
A. Karwath and
|
|
||||||
L. De Raedt},
|
|
||||||
title = {CLASSIC'CL: An Integrated ILP System.},
|
|
||||||
booktitle = {Discovery Science, ({DS} 2005)},
|
|
||||||
publisher = {Springer},
|
|
||||||
series = {LNCS},
|
|
||||||
number = {3735},
|
|
||||||
year = {2005},
|
|
||||||
ee = {http://dx.doi.org/10.1007/11563983_31},
|
|
||||||
bibsource = {DBLP, http://dblp.uni-trier.de}
|
|
||||||
}
|
|
||||||
|
|
||||||
@article{DBLP:journals/datamine/MannilaT97,
|
|
||||||
author = {H. Mannila and
|
|
||||||
H. Toivonen},
|
|
||||||
title = {Levelwise Search and Borders of Theories in Knowledge Discovery.},
|
|
||||||
journal = {Data Min. Knowl. Discov.},
|
|
||||||
volume = {1},
|
|
||||||
number = {3},
|
|
||||||
year = {1997},
|
|
||||||
pages = {241-258},
|
|
||||||
bibsource = {DBLP, http://dblp.uni-trier.de}
|
|
||||||
}
|
|
||||||
@inproceedings{DBLP:conf/ecml/KerstingG04,
|
|
||||||
author = {K. Kersting and
|
|
||||||
T. G{\"a}rtner},
|
|
||||||
title = {Fisher Kernels for Logical Sequences.},
|
|
||||||
booktitle = {Machine Learning, ({ECML} 2004)},
|
|
||||||
year = {2004},
|
|
||||||
publisher = {Springer},
|
|
||||||
series = {LNCS},
|
|
||||||
number = {3201},
|
|
||||||
pages = {205-216},
|
|
||||||
ee = {http://springerlink.metapress.com/openurl.asp?genre=article{\&}issn=0302-9743{\&}volume=3201{\&}spage=205},
|
|
||||||
bibsource = {DBLP, http://dblp.uni-trier.de}
|
|
||||||
}
|
|
||||||
@inproceedings{KerstingECML06,
|
|
||||||
author = {B. Gutmann and K. Kersting},
|
|
||||||
title = {{TildeCRF}: Conditional Random Fields for Logical Sequences.},
|
|
||||||
booktitle = {Machine Learning, ({ECML} 2006)},
|
|
||||||
year = {2006},
|
|
||||||
publisher = {Springer},
|
|
||||||
series = {LNCS},
|
|
||||||
}
|
|
||||||
@article{KerstingJAIR06,
|
|
||||||
author = {K. Kersting and L. De Raedt and T. Raik},
|
|
||||||
title = {Logical Hidden Markov Models.},
|
|
||||||
journal = {Journal of Artificial Intelligence Research},
|
|
||||||
volume = {25},
|
|
||||||
year = {2006},
|
|
||||||
pages = {425-456},
|
|
||||||
}
|
|
||||||
@inproceedings{Rig04-ILP04-IC-short,
|
|
||||||
author = "F. Riguzzi",
|
|
||||||
title = "Learning Logic Programs with Annotated Disjunctions",
|
|
||||||
booktitle = "Inductive Logic Programming, ({ILP} 2004)",
|
|
||||||
year = "2004",
|
|
||||||
month={September},
|
|
||||||
publisher={Springer},
|
|
||||||
series ={LNCS},
|
|
||||||
number = {3194},
|
|
||||||
pages={270--287},
|
|
||||||
url = {http://www.ing.unife.it/docenti/FabrizioRiguzzi/Papers/Rig-ILP04.pdf},
|
|
||||||
isbn={3-540-22941-8},
|
|
||||||
issn={0302-9743},
|
|
||||||
doi={10.1007/b10011},
|
|
||||||
}
|
|
||||||
@inproceedings{VenDenBru-JELIA06,
|
|
||||||
author = "J. Vennekens and M. Denecker and M. Bruynooghe",
|
|
||||||
title = "Representing Causal Information about a
|
|
||||||
Probabilistic Process",
|
|
||||||
booktitle = "10th European Conference on Logics in Artificial Intelligence, JELIA 2006",
|
|
||||||
year = "2006",
|
|
||||||
month={September},
|
|
||||||
publisher={Springer},
|
|
||||||
series ={LNAI},
|
|
||||||
}
|
|
||||||
|
|
||||||
@article{Bry-TC86,
|
|
||||||
author={R. E. Bryant},
|
|
||||||
title={Graph-based algorithms for boolean function manipulation},
|
|
||||||
journal={ IEEE Trans. on Computers},
|
|
||||||
volume={35},
|
|
||||||
number={8},
|
|
||||||
pages={677-691},
|
|
||||||
year={1986},
|
|
||||||
}
|
|
||||||
|
|
||||||
@inproceedings{MilDre-ISML02-IC,
|
|
||||||
title={On the construction of multiple-valued decision diagrams},
|
|
||||||
author={Miller, D. M. and Drechsler, R.},
|
|
||||||
booktitle={Proceedings 32nd IEEE International Symposium on
|
|
||||||
Multiple-Valued Logic},
|
|
||||||
year={2002},
|
|
||||||
pages={245-253},
|
|
||||||
}
|
|
||||||
|
|
||||||
@article{LauSpi-JRS88,
|
|
||||||
author={Lauritzen, S. and Spiegelhalter, D. J.},
|
|
||||||
year={1988},
|
|
||||||
title={Local Computations with Probabilities on Graphical Structures and Their Application to Expert Systems},
|
|
||||||
journal={Journal of the Royal Statistical Society},
|
|
||||||
volume={B, 50},
|
|
||||||
number={2},
|
|
||||||
pages={157-224},
|
|
||||||
}
|
|
||||||
@inproceedings{Rig-AIIA07-IC,
|
|
||||||
author={
|
|
||||||
Fabrizio Riguzzi },
|
|
||||||
title={A Top Down Interpreter for LPAD and CP-logic},
|
|
||||||
booktitle={10th Congress of the Italian Association for Artificial Intelligence},
|
|
||||||
year={2007},
|
|
||||||
publisher={Springer},
|
|
||||||
note={\href{http://www.ing.unife.it/docenti/FabrizioRiguzzi/Papers/Rig-AIIA07.pdf}{http://www.ing.unife.it/docenti/FabrizioRiguzzi/Papers/Rig-AIIA07.pdf}}
|
|
||||||
}
|
|
||||||
|
|
||||||
}
|
|
||||||
@inproceedings{Rig-RCRA07-IC,
|
|
||||||
author={
|
|
||||||
Fabrizio Riguzzi },
|
|
||||||
title={A Top Down Interpreter for LPAD and CP-logic},
|
|
||||||
booktitle={The 14th RCRA workshop
|
|
||||||
Experimental Evaluation of Algorithms for
|
|
||||||
Solving Problems with Combinatorial Explosion},
|
|
||||||
year={2007},
|
|
||||||
note={\href{http://pst.istc.cnr.it/RCRA07/articoli/P19-riguzzi-RCRA07.pdf}{http://pst.istc.cnr.it/RCRA07/articoli/P19-riguzzi-RCRA07.pdf}}
|
|
||||||
}
|
|
||||||
|
|
||||||
@unpublished{CP-logic-unp,
|
|
||||||
author={Joost Vennekens and Marc Denecker and Maurice Bruynooge},
|
|
||||||
title={Extending the Role of Causality in Probabilistic Modeling},
|
|
||||||
year={2006},
|
|
||||||
note={\href{http://www.cs.kuleuven.ac.be/\%7Ejoost/cplogic.pdf}{http://www.cs.kuleuven.ac.be/\%7Ejoost/cplogic.pdf}},
|
|
||||||
}
|
|
@ -1,722 +0,0 @@
|
|||||||
/*
|
|
||||||
LPAD and CP-Logic interpreter
|
|
||||||
|
|
||||||
Copyright (c) 2007, Fabrizio Riguzzi
|
|
||||||
|
|
||||||
*/
|
|
||||||
|
|
||||||
:-dynamic rule/4,def_rule/2,setting/2.
|
|
||||||
|
|
||||||
:-use_module(library(lists)).
|
|
||||||
:-use_module(library(ugraphs)).
|
|
||||||
|
|
||||||
:-load_foreign_files(['cplint'],[],init_my_predicates).
|
|
||||||
|
|
||||||
/* start of list of parameters that can be set by the user with
|
|
||||||
set(Parameter,Value) */
|
|
||||||
setting(epsilon_parsing,0.00001).
|
|
||||||
setting(savedot,false).
|
|
||||||
/* end of list of parameters */
|
|
||||||
|
|
||||||
/* s(GoalsLIst,Prob) compute the probability of a list of goals
|
|
||||||
GoalsLis can have variables, s returns in backtracking all the solutions with their
|
|
||||||
corresponding probability */
|
|
||||||
s(GoalsList,Prob):-
|
|
||||||
solve(GoalsList,Prob).
|
|
||||||
|
|
||||||
|
|
||||||
solve(GoalsList,Prob):-
|
|
||||||
setof(Deriv,find_deriv(GoalsList,Deriv),LDup),
|
|
||||||
rem_dup_lists(LDup,L),
|
|
||||||
build_formula(L,Formula,[],Var),
|
|
||||||
var2numbers(Var,0,NewVar),
|
|
||||||
(setting(savedot,true)->
|
|
||||||
format("Variables: ~p~n",[Var]),
|
|
||||||
compute_prob(NewVar,Formula,Prob,1)
|
|
||||||
;
|
|
||||||
compute_prob(NewVar,Formula,Prob,0)
|
|
||||||
).
|
|
||||||
|
|
||||||
solve(GoalsList,0):-
|
|
||||||
\+ find_deriv(GoalsList,_Deriv).
|
|
||||||
|
|
||||||
find_deriv(GoalsList,Deriv):-
|
|
||||||
solve(GoalsList,[],DerivDup),
|
|
||||||
remove_duplicates(DerivDup,Deriv).
|
|
||||||
/* duplicate can appear in the C set because two different unistantiated clauses may become the
|
|
||||||
same clause when instantiated */
|
|
||||||
|
|
||||||
/* sc(Goals,Evidence,Prob) compute the conditional probability of the list of goals
|
|
||||||
Goals given the list of goals Evidence
|
|
||||||
Goals and Evidence can have variables, sc returns in backtracking all the solutions with their
|
|
||||||
corresponding probability
|
|
||||||
if it fails, the conditional probability is undefined
|
|
||||||
*/
|
|
||||||
sc(Goals,Evidence,Prob):-
|
|
||||||
solve_cond(Goals,Evidence,Prob).
|
|
||||||
|
|
||||||
solve_cond(Goals,Evidence,Prob):-
|
|
||||||
setof(DerivE,find_deriv(Evidence,DerivE),LDupE),
|
|
||||||
rem_dup_lists(LDupE,LE),
|
|
||||||
build_formula(LE,FormulaE,[],VarE),
|
|
||||||
var2numbers(VarE,0,NewVarE),
|
|
||||||
compute_prob(NewVarE,FormulaE,ProbE,0),
|
|
||||||
solve_cond_goals(Goals,LE,ProbGE),
|
|
||||||
Prob is ProbGE/ProbE.
|
|
||||||
|
|
||||||
solve_cond_goals(Goals,LE,ProbGE):-
|
|
||||||
setof(DerivGE,find_deriv_GE(LE,Goals,DerivGE),LDupGE),
|
|
||||||
rem_dup_lists(LDupGE,LGE),
|
|
||||||
build_formula(LGE,FormulaGE,[],VarGE),
|
|
||||||
var2numbers(VarGE,0,NewVarGE),
|
|
||||||
call_compute_prob(NewVarGE,FormulaGE,ProbGE).
|
|
||||||
|
|
||||||
solve_cond_goals(Goals,LE,0):-
|
|
||||||
\+ find_deriv_GE(LE,Goals,_DerivGE).
|
|
||||||
|
|
||||||
call_compute_prob(NewVarGE,FormulaGE,ProbGE):-
|
|
||||||
(setting(savedot,true)->
|
|
||||||
format("Variables: ~p~n",[NewVarGE]),
|
|
||||||
compute_prob(NewVarGE,FormulaGE,ProbGE,1)
|
|
||||||
;
|
|
||||||
compute_prob(NewVarGE,FormulaGE,ProbGE,0)
|
|
||||||
).
|
|
||||||
|
|
||||||
find_deriv_GE(LD,GoalsList,Deriv):-
|
|
||||||
member(D,LD),
|
|
||||||
solve(GoalsList,D,DerivDup),
|
|
||||||
remove_duplicates(DerivDup,Deriv).
|
|
||||||
|
|
||||||
/* solve(GoalsList,CIn,COut) takes a list of goals and an input C set
|
|
||||||
and returns an output C set
|
|
||||||
The C set is a list of triple (N,R,S) where
|
|
||||||
- N is the index of the head atom used, starting from 0
|
|
||||||
- R is the index of the non ground rule used, starting from 1
|
|
||||||
- S is the substitution of rule R, in the form of a list whose elements
|
|
||||||
are of the form 'VarName'=value
|
|
||||||
*/
|
|
||||||
solve([],C,C):-!.
|
|
||||||
|
|
||||||
solve([bagof(V,EV^G,L)|T],CIn,COut):-!,
|
|
||||||
list2and(GL,G),
|
|
||||||
bagof((V,C),EV^solve(GL,CIn,C),LD),
|
|
||||||
length(LD,N),
|
|
||||||
build_initial_graph(N,GrIn),
|
|
||||||
build_graph(LD,0,GrIn,Gr),
|
|
||||||
clique(Gr,Clique),
|
|
||||||
build_Cset(LD,Clique,L,[],C1),
|
|
||||||
remove_duplicates_eq(C1,C2),
|
|
||||||
solve(T,C2,COut).
|
|
||||||
|
|
||||||
solve([bagof(V,G,L)|T],CIn,COut):-!,
|
|
||||||
list2and(GL,G),
|
|
||||||
bagof((V,C),solve(GL,CIn,C),LD),
|
|
||||||
length(LD,N),
|
|
||||||
build_initial_graph(N,GrIn),
|
|
||||||
build_graph(LD,0,GrIn,Gr),
|
|
||||||
clique(Gr,Clique),
|
|
||||||
build_Cset(LD,Clique,L,[],C1),
|
|
||||||
remove_duplicates_eq(C1,C2),
|
|
||||||
solve(T,C2,COut).
|
|
||||||
|
|
||||||
|
|
||||||
solve([setof(V,EV^G,L)|T],CIn,COut):-!,
|
|
||||||
list2and(GL,G),
|
|
||||||
setof((V,C),EV^solve(GL,CIn,C),LD),
|
|
||||||
length(LD,N),
|
|
||||||
build_initial_graph(N,GrIn),
|
|
||||||
build_graph(LD,0,GrIn,Gr),
|
|
||||||
clique(Gr,Clique),
|
|
||||||
build_Cset(LD,Clique,L1,[],C1),
|
|
||||||
remove_duplicates(L1,L),
|
|
||||||
solve(T,C1,COut).
|
|
||||||
|
|
||||||
solve([setof(V,G,L)|T],CIn,COut):-!,
|
|
||||||
list2and(GL,G),
|
|
||||||
setof((V,C),solve(GL,CIn,C),LD),
|
|
||||||
length(LD,N),
|
|
||||||
build_initial_graph(N,GrIn),
|
|
||||||
build_graph(LD,0,GrIn,Gr),
|
|
||||||
clique(Gr,Clique),
|
|
||||||
build_Cset(LD,Clique,L1,[],C1),
|
|
||||||
remove_duplicates(L1,L),
|
|
||||||
solve(T,C1,COut).
|
|
||||||
|
|
||||||
solve([\+ H |T],CIn,COut):-!,
|
|
||||||
list2and(HL,H),
|
|
||||||
(setof(D,find_deriv(HL,D),LDup)->
|
|
||||||
rem_dup_lists(LDup,L),
|
|
||||||
choose_clauses(CIn,L,C1),
|
|
||||||
solve(T,C1,COut)
|
|
||||||
;
|
|
||||||
solve(T,CIn,COut)
|
|
||||||
).
|
|
||||||
|
|
||||||
solve([H|T],CIn,COut):-
|
|
||||||
builtin(H),!,
|
|
||||||
call(H),
|
|
||||||
solve(T,CIn,COut).
|
|
||||||
|
|
||||||
solve([H|T],CIn,COut):-
|
|
||||||
def_rule(H,B),
|
|
||||||
append(B,T,NG),
|
|
||||||
solve(NG,CIn,COut).
|
|
||||||
|
|
||||||
solve([H|T],CIn,COut):-
|
|
||||||
find_rule(H,(R,S,N),B,CIn),
|
|
||||||
solve_pres(R,S,N,B,T,CIn,COut).
|
|
||||||
|
|
||||||
solve_pres(R,S,N,B,T,CIn,COut):-
|
|
||||||
member_eq((N,R,S),CIn),!,
|
|
||||||
append(B,T,NG),
|
|
||||||
solve(NG,CIn,COut).
|
|
||||||
|
|
||||||
solve_pres(R,S,N,B,T,CIn,COut):-
|
|
||||||
append(CIn,[(N,R,S)],C1),
|
|
||||||
append(B,T,NG),
|
|
||||||
solve(NG,C1,COut).
|
|
||||||
|
|
||||||
build_initial_graph(N,G):-
|
|
||||||
listN(0,N,Vert),
|
|
||||||
add_vertices([],Vert,G).
|
|
||||||
|
|
||||||
|
|
||||||
build_graph([],_N,G,G).
|
|
||||||
|
|
||||||
build_graph([(_V,C)|T],N,GIn,GOut):-
|
|
||||||
N1 is N+1,
|
|
||||||
compatible(C,T,N,N1,GIn,G1),
|
|
||||||
build_graph(T,N1,G1,GOut).
|
|
||||||
|
|
||||||
compatible(_C,[],_N,_N1,G,G).
|
|
||||||
|
|
||||||
compatible(C,[(_V,H)|T],N,N1,GIn,GOut):-
|
|
||||||
(compatible(C,H)->
|
|
||||||
add_edges(GIn,[N-N1,N1-N],G1)
|
|
||||||
;
|
|
||||||
G1=GIn
|
|
||||||
),
|
|
||||||
N2 is N1 +1,
|
|
||||||
compatible(C,T,N,N2,G1,GOut).
|
|
||||||
|
|
||||||
compatible([],_C).
|
|
||||||
|
|
||||||
compatible([(N,R,S)|T],C):-
|
|
||||||
not_present_with_a_different_head(N,R,S,C),
|
|
||||||
compatible(T,C).
|
|
||||||
|
|
||||||
not_present_with_a_different_head(_N,_R,_S,[]).
|
|
||||||
|
|
||||||
not_present_with_a_different_head(N,R,S,[(N,R,S)|T]):-!,
|
|
||||||
not_present_with_a_different_head(N,R,S,T).
|
|
||||||
|
|
||||||
not_present_with_a_different_head(N,R,S,[(_N1,R,S1)|T]):-
|
|
||||||
S\=S1,!,
|
|
||||||
not_present_with_a_different_head(N,R,S,T).
|
|
||||||
|
|
||||||
not_present_with_a_different_head(N,R,S,[(_N1,R1,_S1)|T]):-
|
|
||||||
R\=R1,
|
|
||||||
not_present_with_a_different_head(N,R,S,T).
|
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
build_Cset(_LD,[],[],C,C).
|
|
||||||
|
|
||||||
build_Cset(LD,[H|T],[V|L],CIn,COut):-
|
|
||||||
nth0(H,LD,(V,C)),
|
|
||||||
append(C,CIn,C1),
|
|
||||||
build_Cset(LD,T,L,C1,COut).
|
|
||||||
|
|
||||||
|
|
||||||
/* find_rule(G,(R,S,N),Body,C) takes a goal G and the current C set and
|
|
||||||
returns the index R of a disjunctive rule resolving with G together with
|
|
||||||
the index N of the resolving head, the substitution S and the Body of the
|
|
||||||
rule */
|
|
||||||
find_rule(H,(R,S,N),Body,C):-
|
|
||||||
rule(R,S,_,Head,Body),
|
|
||||||
member_head(H,Head,0,N),
|
|
||||||
not_already_present_with_a_different_head(N,R,S,C).
|
|
||||||
|
|
||||||
find_rule(H,(R,S,Number),Body,C):-
|
|
||||||
rule(R,S,_,uniform(H:1/_Num,_P,Number),Body),
|
|
||||||
not_already_present_with_a_different_head(Number,R,S,C).
|
|
||||||
|
|
||||||
not_already_present_with_a_different_head(_N,_R,_S,[]).
|
|
||||||
|
|
||||||
not_already_present_with_a_different_head(N,R,S,[(N1,R,S1)|T]):-
|
|
||||||
not_different(N,N1,S,S1),!,
|
|
||||||
not_already_present_with_a_different_head(N,R,S,T).
|
|
||||||
|
|
||||||
not_already_present_with_a_different_head(N,R,S,[(_N1,R1,_S1)|T]):-
|
|
||||||
R\==R1,
|
|
||||||
not_already_present_with_a_different_head(N,R,S,T).
|
|
||||||
|
|
||||||
not_different(_N,_N1,S,S1):-
|
|
||||||
S\=S1,!.
|
|
||||||
|
|
||||||
not_different(N,N1,S,S1):-
|
|
||||||
N\=N1,!,
|
|
||||||
dif(S,S1).
|
|
||||||
|
|
||||||
not_different(N,N,S,S).
|
|
||||||
|
|
||||||
|
|
||||||
member_head(H,[(H:_P)|_T],N,N).
|
|
||||||
|
|
||||||
member_head(H,[(_H:_P)|T],NIn,NOut):-
|
|
||||||
N1 is NIn+1,
|
|
||||||
member_head(H,T,N1,NOut).
|
|
||||||
|
|
||||||
/* choose_clauses(CIn,LC,COut) takes as input the current C set and
|
|
||||||
the set of C sets for a negative goal and returns a new C set that
|
|
||||||
excludes all the derivations for the negative goals */
|
|
||||||
choose_clauses(C,[],C).
|
|
||||||
|
|
||||||
choose_clauses(CIn,[D|T],COut):-
|
|
||||||
member((N,R,S),D),
|
|
||||||
instantiation_present_with_the_same_head(N,R,S,CIn),
|
|
||||||
choose_a_different_head(N,R,S,T,CIn,COut).
|
|
||||||
|
|
||||||
choose_a_different_head(N,R,S,D,CIn,COut):-
|
|
||||||
/* cases 1 and 2 of Select */
|
|
||||||
choose_a_head(N,R,S,CIn,C1),
|
|
||||||
choose_clauses(C1,D,COut).
|
|
||||||
|
|
||||||
choose_a_different_head(N,R,S,D,CIn,COut):-
|
|
||||||
/* case 3 of Select */
|
|
||||||
new_head(N,R,S,N1),
|
|
||||||
\+ already_present(N1,R,S,CIn),
|
|
||||||
choose_clauses([(N1,R,S)|CIn],D,COut).
|
|
||||||
|
|
||||||
/* instantiation_present_with_the_same_head(N,R,S,C)
|
|
||||||
takes rule R with substitution S and selected head N and a C set
|
|
||||||
and asserts dif constraints for all the clauses in C of which RS
|
|
||||||
is an instantitation and have the same head selected */
|
|
||||||
instantiation_present_with_the_same_head(_N,_R,_S,[]).
|
|
||||||
|
|
||||||
instantiation_present_with_the_same_head(N,R,S,[(NH,R,SH)|T]):-
|
|
||||||
\+ \+ S=SH,
|
|
||||||
dif(N,NH),
|
|
||||||
instantiation_present_with_the_same_head(N,R,S,T).
|
|
||||||
|
|
||||||
instantiation_present_with_the_same_head(N,R,S,[(NH,R,SH)|T]):-
|
|
||||||
\+ \+ S=SH,
|
|
||||||
N=NH,!,
|
|
||||||
dif(S,SH),
|
|
||||||
instantiation_present_with_the_same_head(N,R,S,T).
|
|
||||||
|
|
||||||
instantiation_present_with_the_same_head(N,R,S,[_H|T]):-
|
|
||||||
instantiation_present_with_the_same_head(N,R,S,T).
|
|
||||||
|
|
||||||
/* case 1 of Select: a more general rule is present in C with
|
|
||||||
a different head, instantiate it */
|
|
||||||
choose_a_head(N,R,S,[(NH,R,SH)|T],[(NH,R,SH)|T]):-
|
|
||||||
S=SH,
|
|
||||||
dif(N,NH).
|
|
||||||
|
|
||||||
/* case 2 of Select: a more general rule is present in C with
|
|
||||||
a different head, ensure that they do not generate the same
|
|
||||||
ground clause */
|
|
||||||
choose_a_head(N,R,S,[(NH,R,SH)|T],[(NH,R,S),(NH,R,SH)|T]):-
|
|
||||||
\+ \+ S=SH, S\==SH,
|
|
||||||
dif(N,NH),
|
|
||||||
dif(S,SH).
|
|
||||||
|
|
||||||
choose_a_head(N,R,S,[H|T],[H|T1]):-
|
|
||||||
choose_a_head(N,R,S,T,T1).
|
|
||||||
|
|
||||||
/* select a head different from N for rule R with
|
|
||||||
substitution S, return it in N1 */
|
|
||||||
new_head(N,R,S,N1):-
|
|
||||||
rule(R,S,Numbers,Head,_Body),
|
|
||||||
Head\=uniform(_,_,_),!,
|
|
||||||
nth0(N, Numbers, _Elem, Rest),
|
|
||||||
member(N1,Rest).
|
|
||||||
|
|
||||||
new_head(N,R,S,N1):-
|
|
||||||
rule(R,S,Numbers,uniform(_A:1/Tot,_L,_Number),_Body),
|
|
||||||
listN(0,Tot,Numbers),
|
|
||||||
nth0(N, Numbers, _Elem, Rest),
|
|
||||||
member(N1,Rest).
|
|
||||||
|
|
||||||
/* checks that a rule R with head N and selection S is already
|
|
||||||
present in C (or a generalization of it is in C) */
|
|
||||||
already_present(N,R,S,[(N,R,SH)|_T]):-
|
|
||||||
S=SH.
|
|
||||||
|
|
||||||
already_present(N,R,S,[_H|T]):-
|
|
||||||
already_present(N,R,S,T).
|
|
||||||
|
|
||||||
/* rem_dup_lists removes the C sets that are a superset of
|
|
||||||
another C sets further on in the list of C sets */
|
|
||||||
rem_dup_lists([],[]).
|
|
||||||
|
|
||||||
rem_dup_lists([H|T],T1):-
|
|
||||||
member_subset(H,T),!,
|
|
||||||
rem_dup_lists(T,T1).
|
|
||||||
|
|
||||||
rem_dup_lists([H|T],[H|T1]):-
|
|
||||||
rem_dup_lists(T,T1).
|
|
||||||
|
|
||||||
member_subset(E,[H|_T]):-
|
|
||||||
subset_my(H,E),!.
|
|
||||||
|
|
||||||
member_subset(E,[_H|T]):-
|
|
||||||
member_subset(E,T).
|
|
||||||
|
|
||||||
/* predicates for building the formula to be converted into a BDD */
|
|
||||||
|
|
||||||
/* build_formula(LC,Formula,VarIn,VarOut) takes as input a set of C sets
|
|
||||||
LC and a list of Variables VarIn and returns the formula and a new list
|
|
||||||
of variables VarOut
|
|
||||||
Formula is of the form [Term1,...,Termn]
|
|
||||||
Termi is of the form [Factor1,...,Factorm]
|
|
||||||
Factorj is of the form (Var,Value) where Var is the index of
|
|
||||||
the multivalued variable Var and Value is the index of the value
|
|
||||||
*/
|
|
||||||
build_formula([],[],Var,Var).
|
|
||||||
|
|
||||||
build_formula([D|TD],[F|TF],VarIn,VarOut):-
|
|
||||||
build_term(D,F,VarIn,Var1),
|
|
||||||
build_formula(TD,TF,Var1,VarOut).
|
|
||||||
|
|
||||||
build_term([],[],Var,Var).
|
|
||||||
|
|
||||||
build_term([(N,R,S)|TC],[[NVar,N]|TF],VarIn,VarOut):-
|
|
||||||
(nth0_eq(0,NVar,VarIn,(R,S))->
|
|
||||||
Var1=VarIn
|
|
||||||
;
|
|
||||||
append(VarIn,[(R,S)],Var1),
|
|
||||||
length(VarIn,NVar)
|
|
||||||
),
|
|
||||||
build_term(TC,TF,Var1,VarOut).
|
|
||||||
|
|
||||||
/* nth0_eq(PosIn,PosOut,List,El) takes as input a List,
|
|
||||||
an element El and an initial position PosIn and returns in PosOut
|
|
||||||
the position in the List that contains an element exactly equal to El
|
|
||||||
*/
|
|
||||||
nth0_eq(N,N,[H|_T],El):-
|
|
||||||
H==El,!.
|
|
||||||
|
|
||||||
nth0_eq(NIn,NOut,[_H|T],El):-
|
|
||||||
N1 is NIn+1,
|
|
||||||
nth0_eq(N1,NOut,T,El).
|
|
||||||
|
|
||||||
/* var2numbers converts a list of couples (Rule,Substitution) into a list
|
|
||||||
of triples (N,NumberOfHeadsAtoms,ListOfProbabilities), where N is an integer
|
|
||||||
starting from 0 */
|
|
||||||
var2numbers([],_N,[]).
|
|
||||||
|
|
||||||
var2numbers([(R,S)|T],N,[[N,ValNumber,Probs]|TNV]):-
|
|
||||||
find_probs(R,S,Probs),
|
|
||||||
length(Probs,ValNumber),
|
|
||||||
N1 is N+1,
|
|
||||||
var2numbers(T,N1,TNV).
|
|
||||||
|
|
||||||
find_probs(R,S,Probs):-
|
|
||||||
rule(R,S,_N,Head,_Body),
|
|
||||||
get_probs(Head,Probs).
|
|
||||||
|
|
||||||
get_probs(uniform(_A:1/Num,_P,_Number),ListP):-
|
|
||||||
Prob is 1/Num,
|
|
||||||
list_el(Num,Prob,ListP).
|
|
||||||
|
|
||||||
get_probs([],[]).
|
|
||||||
|
|
||||||
get_probs([_H:P|T],[P1|T1]):-
|
|
||||||
P1 is P,
|
|
||||||
get_probs(T,T1).
|
|
||||||
|
|
||||||
list_el(0,_P,[]):-!.
|
|
||||||
|
|
||||||
list_el(N,P,[P|T]):-
|
|
||||||
N1 is N-1,
|
|
||||||
list_el(N1,P,T).
|
|
||||||
|
|
||||||
/* end of predicates for building the formula to be converted into a BDD */list_el(0,_P,[]):-!.
|
|
||||||
|
|
||||||
|
|
||||||
/* start of predicates for parsing an input file containing a program */
|
|
||||||
|
|
||||||
/* p(File) parses the file File.cpl. It can be called more than once without
|
|
||||||
exiting yap */
|
|
||||||
p(File):-
|
|
||||||
parse(File).
|
|
||||||
|
|
||||||
parse(File):-
|
|
||||||
atom_concat(File,'.cpl',FilePl),
|
|
||||||
open(FilePl,read,S),
|
|
||||||
read_clauses(S,C),
|
|
||||||
close(S),
|
|
||||||
retractall(rule(_,_,_,_,_)),
|
|
||||||
retractall(def_rule(_,_)),
|
|
||||||
process_clauses(C,1).
|
|
||||||
|
|
||||||
process_clauses([(end_of_file,[])],_N).
|
|
||||||
|
|
||||||
process_clauses([((H:-B),V)|T],N):-
|
|
||||||
H=uniform(A,P,L),!,
|
|
||||||
list2and(BL,B),
|
|
||||||
process_body(BL,V,V1),
|
|
||||||
remove_vars([P],V1,V2),
|
|
||||||
append(BL,[length(L,Tot),nth0(Number,L,P)],BL1),
|
|
||||||
append(V2,['Tot'=Tot],V3),
|
|
||||||
assertz(rule(N,V3,_NH,uniform(A:1/Tot,L,Number),BL1)),
|
|
||||||
N1 is N+1,
|
|
||||||
process_clauses(T,N1).
|
|
||||||
|
|
||||||
process_clauses([((H:-B),V)|T],N):-
|
|
||||||
H=(_;_),!,
|
|
||||||
list2or(HL1,H),
|
|
||||||
process_head(HL1,HL),
|
|
||||||
list2and(BL,B),
|
|
||||||
process_body(BL,V,V1),
|
|
||||||
length(HL,LH),
|
|
||||||
listN(0,LH,NH),
|
|
||||||
assertz(rule(N,V1,NH,HL,BL)),
|
|
||||||
N1 is N+1,
|
|
||||||
process_clauses(T,N1).
|
|
||||||
|
|
||||||
process_clauses([((H:-B),V)|T],N):-
|
|
||||||
H=(_:_),!,
|
|
||||||
list2or(HL1,H),
|
|
||||||
process_head(HL1,HL),
|
|
||||||
list2and(BL,B),
|
|
||||||
process_body(BL,V,V1),
|
|
||||||
length(HL,LH),
|
|
||||||
listN(0,LH,NH),
|
|
||||||
assertz(rule(N,V1,NH,HL,BL)),
|
|
||||||
N1 is N+1,
|
|
||||||
process_clauses(T,N1).
|
|
||||||
|
|
||||||
process_clauses([((H:-B),_V)|T],N):-!,
|
|
||||||
list2and(BL,B),
|
|
||||||
assert(def_rule(H,BL)),
|
|
||||||
process_clauses(T,N).
|
|
||||||
|
|
||||||
process_clauses([(H,V)|T],N):-
|
|
||||||
H=(_;_),!,
|
|
||||||
list2or(HL1,H),
|
|
||||||
process_head(HL1,HL),
|
|
||||||
length(HL,LH),
|
|
||||||
listN(0,LH,NH),
|
|
||||||
assertz(rule(N,V,NH,HL,[])),
|
|
||||||
N1 is N+1,
|
|
||||||
process_clauses(T,N1).
|
|
||||||
|
|
||||||
process_clauses([(H,V)|T],N):-
|
|
||||||
H=(_:_),!,
|
|
||||||
list2or(HL1,H),
|
|
||||||
process_head(HL1,HL),
|
|
||||||
length(HL,LH),
|
|
||||||
listN(0,LH,NH),
|
|
||||||
assertz(rule(N,V,NH,HL,[])),
|
|
||||||
N1 is N+1,
|
|
||||||
process_clauses(T,N1).
|
|
||||||
|
|
||||||
process_clauses([(H,_V)|T],N):-
|
|
||||||
assert(def_rule(H,[])),
|
|
||||||
process_clauses(T,N).
|
|
||||||
|
|
||||||
/* if the annotation in the head are not ground, the null atom is not added
|
|
||||||
and the eventual formulas are not evaluated */
|
|
||||||
|
|
||||||
process_head(HL,NHL):-
|
|
||||||
(ground_prob(HL)->
|
|
||||||
process_head_ground(HL,0,NHL)
|
|
||||||
;
|
|
||||||
NHL=HL
|
|
||||||
).
|
|
||||||
|
|
||||||
ground_prob([]).
|
|
||||||
|
|
||||||
ground_prob([_H:PH|T]):-
|
|
||||||
ground(PH),
|
|
||||||
ground_prob(T).
|
|
||||||
|
|
||||||
process_head_ground([H:PH],P,[H:PH1|Null]):-
|
|
||||||
PH1 is PH,
|
|
||||||
PNull is 1-P-PH1,
|
|
||||||
setting(epsilon_parsing,Eps),
|
|
||||||
EpsNeg is - Eps,
|
|
||||||
PNull > EpsNeg,
|
|
||||||
(PNull>Eps->
|
|
||||||
Null=['':PNull]
|
|
||||||
;
|
|
||||||
Null=[]
|
|
||||||
).
|
|
||||||
|
|
||||||
process_head_ground([H:PH|T],P,[H:PH1|NT]):-
|
|
||||||
PH1 is PH,
|
|
||||||
P1 is P+PH1,
|
|
||||||
process_head_ground(T,P1,NT).
|
|
||||||
|
|
||||||
/* setof must have a goal of the form B^G where B is a term containing the existential variables */
|
|
||||||
process_body([],V,V).
|
|
||||||
|
|
||||||
process_body([setof(A,B^_G,_L)|T],VIn,VOut):-!,
|
|
||||||
get_var(A,VA),
|
|
||||||
get_var(B,VB),
|
|
||||||
remove_vars(VA,VIn,V1),
|
|
||||||
remove_vars(VB,V1,V2),
|
|
||||||
process_body(T,V2,VOut).
|
|
||||||
|
|
||||||
process_body([setof(A,_G,_L)|T],VIn,VOut):-!,
|
|
||||||
get_var(A,VA),
|
|
||||||
remove_vars(VA,VIn,V1),
|
|
||||||
process_body(T,V1,VOut).
|
|
||||||
|
|
||||||
process_body([bagof(A,B^_G,_L)|T],VIn,VOut):-!,
|
|
||||||
get_var(A,VA),
|
|
||||||
get_var(B,VB),
|
|
||||||
remove_vars(VA,VIn,V1),
|
|
||||||
remove_vars(VB,V1,V2),
|
|
||||||
process_body(T,V2,VOut).
|
|
||||||
|
|
||||||
process_body([bagof(A,_G,_L)|T],VIn,VOut):-!,
|
|
||||||
get_var(A,VA),
|
|
||||||
remove_vars(VA,VIn,V1),
|
|
||||||
process_body(T,V1,VOut).
|
|
||||||
|
|
||||||
process_body([_H|T],VIn,VOut):-!,
|
|
||||||
process_body(T,VIn,VOut).
|
|
||||||
|
|
||||||
get_var_list([],[]).
|
|
||||||
|
|
||||||
get_var_list([H|T],[H|T1]):-
|
|
||||||
var(H),!,
|
|
||||||
get_var_list(T,T1).
|
|
||||||
|
|
||||||
get_var_list([H|T],VarOut):-!,
|
|
||||||
get_var(H,Var),
|
|
||||||
append(Var,T1,VarOut),
|
|
||||||
get_var_list(T,T1).
|
|
||||||
|
|
||||||
get_var(A,[A]):-
|
|
||||||
var(A),!.
|
|
||||||
|
|
||||||
get_var(A,V):-
|
|
||||||
A=..[_F|Args],
|
|
||||||
get_var_list(Args,V).
|
|
||||||
|
|
||||||
remove_vars([],V,V).
|
|
||||||
|
|
||||||
remove_vars([H|T],VIn,VOut):-
|
|
||||||
delete_var(H,VIn,V1),
|
|
||||||
remove_vars(T,V1,VOut).
|
|
||||||
|
|
||||||
delete_var(_H,[],[]).
|
|
||||||
|
|
||||||
delete_var(V,[VN=Var|T],[VN=Var|T1]):-
|
|
||||||
V\==Var,!,
|
|
||||||
delete_var(V,T,T1).
|
|
||||||
|
|
||||||
delete_var(_V,[_H|T],T).
|
|
||||||
|
|
||||||
read_clauses(S,[(Cl,V)|Out]):-
|
|
||||||
read_term(S,Cl,[variable_names(V)]),
|
|
||||||
(Cl=end_of_file->
|
|
||||||
Out=[]
|
|
||||||
;
|
|
||||||
read_clauses(S,Out)
|
|
||||||
).
|
|
||||||
|
|
||||||
listN(N,N,[]):-!.
|
|
||||||
|
|
||||||
listN(NIn,N,[NIn|T]):-
|
|
||||||
N1 is NIn+1,
|
|
||||||
listN(N1,N,T).
|
|
||||||
/* end of predicates for parsing an input file containing a program */
|
|
||||||
|
|
||||||
/* start of utility predicates */
|
|
||||||
list2or([X],X):-
|
|
||||||
X\=;(_,_),!.
|
|
||||||
|
|
||||||
list2or([H|T],(H ; Ta)):-!,
|
|
||||||
list2or(T,Ta).
|
|
||||||
|
|
||||||
list2and([X],X):-
|
|
||||||
X\=(_,_),!.
|
|
||||||
|
|
||||||
list2and([H|T],(H,Ta)):-!,
|
|
||||||
list2and(T,Ta).
|
|
||||||
|
|
||||||
member_eq(A,[H|_T]):-
|
|
||||||
A==H.
|
|
||||||
|
|
||||||
member_eq(A,[_H|T]):-
|
|
||||||
member_eq(A,T).
|
|
||||||
|
|
||||||
subset_my([],_).
|
|
||||||
|
|
||||||
subset_my([H|T],L):-
|
|
||||||
member_eq(H,L),
|
|
||||||
subset_my(T,L).
|
|
||||||
|
|
||||||
remove_duplicates_eq([],[]).
|
|
||||||
|
|
||||||
remove_duplicates_eq([H|T],T1):-
|
|
||||||
member_eq(H,T),!,
|
|
||||||
remove_duplicates_eq(T,T1).
|
|
||||||
|
|
||||||
remove_duplicates_eq([H|T],[H|T1]):-
|
|
||||||
remove_duplicates_eq(T,T1).
|
|
||||||
|
|
||||||
builtin(_A is _B).
|
|
||||||
builtin(_A > _B).
|
|
||||||
builtin(_A < _B).
|
|
||||||
builtin(_A >= _B).
|
|
||||||
builtin(_A =< _B).
|
|
||||||
builtin(_A =:= _B).
|
|
||||||
builtin(_A =\= _B).
|
|
||||||
builtin(true).
|
|
||||||
builtin(false).
|
|
||||||
builtin(_A = _B).
|
|
||||||
builtin(_A==_B).
|
|
||||||
builtin(_A\=_B).
|
|
||||||
builtin(_A\==_B).
|
|
||||||
builtin(length(_L,_N)).
|
|
||||||
builtin(member(_El,_L)).
|
|
||||||
builtin(average(_L,_Av)).
|
|
||||||
builtin(max_list(_L,_Max)).
|
|
||||||
builtin(min_list(_L,_Max)).
|
|
||||||
builtin(nth0(_,_,_)).
|
|
||||||
builtin(nth(_,_,_)).
|
|
||||||
average(L,Av):-
|
|
||||||
sum_list(L,Sum),
|
|
||||||
length(L,N),
|
|
||||||
Av is Sum/N.
|
|
||||||
|
|
||||||
clique(Graph,Clique):-
|
|
||||||
vertices(Graph,Candidates),
|
|
||||||
extend_cycle(Graph,Candidates,[],[],Clique).
|
|
||||||
|
|
||||||
extend_cycle(G,[H|T],Not,CS,CSOut):-
|
|
||||||
neighbours(H, G, Neigh),
|
|
||||||
intersection(Neigh,T,NewCand),
|
|
||||||
intersection(Neigh,Not,NewNot),
|
|
||||||
extend(G,NewCand,NewNot,[H|CS],CSOut).
|
|
||||||
|
|
||||||
extend_cycle(G,[H|T],Not,CS,CSOut):-
|
|
||||||
extend_cycle(G,T,[H|Not],CS,CSOut).
|
|
||||||
|
|
||||||
extend(_G,[],[],CompSub,CompSub):-!.
|
|
||||||
|
|
||||||
extend(G,Cand,Not,CS,CSOut):-
|
|
||||||
extend_cycle(G,Cand,Not,CS,CSOut).
|
|
||||||
|
|
||||||
intersection([],_Y,[]).
|
|
||||||
|
|
||||||
intersection([H|T],Y,[H|Z]):-
|
|
||||||
member(H,Y),!,
|
|
||||||
intersection(T,Y,Z).
|
|
||||||
|
|
||||||
intersection([_H|T],Y,Z):-
|
|
||||||
intersection(T,Y,Z).
|
|
||||||
|
|
||||||
/* set(Par,Value) can be used to set the value of a parameter */
|
|
||||||
set(Parameter,Value):-
|
|
||||||
retract(setting(Parameter,_)),
|
|
||||||
assert(setting(Parameter,Value)).
|
|
||||||
|
|
||||||
/* end of utility predicates */
|
|
@ -1,263 +0,0 @@
|
|||||||
/*
|
|
||||||
|
|
||||||
Program for computing the probability of a query directly according to the
|
|
||||||
semantics
|
|
||||||
|
|
||||||
Copyright (c) 2007, Fabrizio Riguzzi
|
|
||||||
|
|
||||||
|
|
||||||
*/
|
|
||||||
:-use_module(library(lists)).
|
|
||||||
:-dynamic setting/2.
|
|
||||||
:-set_prolog_flag(unknown,fail).
|
|
||||||
|
|
||||||
|
|
||||||
setting(epsilon,0.00001).
|
|
||||||
setting(test_builtins,false).
|
|
||||||
|
|
||||||
solve(GoalsList,Prob):-
|
|
||||||
s(GoalsList,Prob).
|
|
||||||
|
|
||||||
|
|
||||||
s(GoalsList,Prob):-
|
|
||||||
program_names(L),
|
|
||||||
list2and(GoalsList,Goals),
|
|
||||||
run_query(L,Goals,0,Prob).
|
|
||||||
|
|
||||||
run_query([],_G,P,P).
|
|
||||||
|
|
||||||
run_query([Prog|T],Goal,PIn,POut):-
|
|
||||||
elab_conj(Prog,Goal,Goal1),
|
|
||||||
call(Goal1),
|
|
||||||
prob(Prog,P),
|
|
||||||
P1 is PIn+P,
|
|
||||||
run_query(T,Goal,P1,POut).
|
|
||||||
|
|
||||||
run_query([Prog|T],Goal,PIn,POut):-
|
|
||||||
elab_conj(Prog,Goal,Goal1),
|
|
||||||
\+ call(Goal1),
|
|
||||||
run_query(T,Goal,PIn,POut).
|
|
||||||
|
|
||||||
p(File):-
|
|
||||||
atom_concat(File,'.uni',FileUni),
|
|
||||||
consult(FileUni),
|
|
||||||
atom_concat(File,'.cpl',FilePl),
|
|
||||||
open(FilePl,read,S),
|
|
||||||
read_clauses(S,C),
|
|
||||||
close(S),
|
|
||||||
process_clauses(C,ClausesVar),
|
|
||||||
instantiate(ClausesVar,[],Clauses),
|
|
||||||
assert(program(1)),
|
|
||||||
assert(program_names([])),
|
|
||||||
create_programs(Clauses).
|
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
create_programs(Clauses):-
|
|
||||||
create_single_program(Clauses,1,Program),
|
|
||||||
retract(program(N)),
|
|
||||||
number_codes(N,NC),
|
|
||||||
atom_codes(NA,NC),
|
|
||||||
atom_concat(p,NA,Name),
|
|
||||||
N1 is N+1,
|
|
||||||
assert(program(N1)),
|
|
||||||
format("Writing program ~d~n",[N]),
|
|
||||||
write_program(Name,Program),
|
|
||||||
retract(program_names(L)),
|
|
||||||
append(L,[Name],L1),
|
|
||||||
assert(program_names(L1)),
|
|
||||||
fail.
|
|
||||||
|
|
||||||
create_programs(_).
|
|
||||||
|
|
||||||
write_program(_Name,[]).
|
|
||||||
|
|
||||||
write_program(Name,[(H:-B)|T]):-
|
|
||||||
elab_conj(Name,H,H1),
|
|
||||||
elab_conj(Name,B,B1),
|
|
||||||
assertz((H1:-B1)),
|
|
||||||
write_program(Name,T).
|
|
||||||
|
|
||||||
elab_conj(_Name,true,true):-!.
|
|
||||||
|
|
||||||
elab_conj(Name,\+(B),\+(B1)):-!,
|
|
||||||
elab_conj(Name,B,B1).
|
|
||||||
|
|
||||||
elab_conj(Name,(BL,Rest),(BL1,Rest1)):-!,
|
|
||||||
elab_conj(Name,BL,BL1),
|
|
||||||
elab_conj(Name,Rest,Rest1).
|
|
||||||
|
|
||||||
elab_conj(Name,bagof(V,EV^G,L),bagof(V,EV^GL,L)):-!,
|
|
||||||
elab_conj(Name,G,GL).
|
|
||||||
|
|
||||||
elab_conj(Name,bagof(V,G,L),bagof(V,GL,L)):-!,
|
|
||||||
elab_conj(Name,G,GL).
|
|
||||||
|
|
||||||
elab_conj(Name,setof(V,EV^G,L),setof(V,EV^GL,L)):-!,
|
|
||||||
elab_conj(Name,G,GL).
|
|
||||||
|
|
||||||
elab_conj(Name,setof(V,G,L),setof(V,GL,L)):-!,
|
|
||||||
elab_conj(Name,G,GL).
|
|
||||||
|
|
||||||
elab_conj(Name,findall(V,G,L),findall(V,GL,L)):-!,
|
|
||||||
elab_conj(Name,G,GL).
|
|
||||||
|
|
||||||
elab_conj(_Name,A,A):-
|
|
||||||
bg(A),!.
|
|
||||||
|
|
||||||
elab_conj(_Name,A,A):-
|
|
||||||
builtin(A),!.
|
|
||||||
|
|
||||||
elab_conj(Name,Lit,Lit1):-
|
|
||||||
Lit\=(_,_),
|
|
||||||
Lit=..[Pred|Args],
|
|
||||||
Lit1=..[Pred,Name|Args].
|
|
||||||
|
|
||||||
|
|
||||||
create_single_program([],P,[(prob(P):-true)]).
|
|
||||||
|
|
||||||
create_single_program([r(H,B)|T],PIn,[(HA:-B)|T1]):-
|
|
||||||
member((HA:P),H),
|
|
||||||
P1 is PIn*P,
|
|
||||||
create_single_program(T,P1,T1).
|
|
||||||
|
|
||||||
instantiate([],C,C).
|
|
||||||
|
|
||||||
instantiate([r(V,H,B)|T],CIn,COut):-
|
|
||||||
findall(r(H,BOut),instantiate_clause(V,H,B,BOut),L),
|
|
||||||
append(CIn,L,C1),
|
|
||||||
instantiate(T,C1,COut).
|
|
||||||
|
|
||||||
check_body([],[]).
|
|
||||||
|
|
||||||
check_body([H|T],TOut):-
|
|
||||||
builtin(H),setting(test_builtins,true),!,
|
|
||||||
call(H),
|
|
||||||
check_body(T,TOut).
|
|
||||||
|
|
||||||
check_body([H|T],[H|TOut]):-
|
|
||||||
check_body(T,TOut).
|
|
||||||
|
|
||||||
|
|
||||||
instantiate_clause([],_H,B,BOut):-
|
|
||||||
list2and(BL,B),
|
|
||||||
check_body(BL,BLOut),
|
|
||||||
list2and(BLOut,BOut).
|
|
||||||
|
|
||||||
|
|
||||||
instantiate_clause([VarName=Var|T],H,BIn,BOut):-
|
|
||||||
universe(VarNames,U),
|
|
||||||
member(VarName,VarNames),
|
|
||||||
member(Var,U),
|
|
||||||
instantiate_clause(T,H,BIn,BOut).
|
|
||||||
|
|
||||||
instantiate_clause([VarName=_Var|T],H,BIn,BOut):-
|
|
||||||
\+ varName_present(VarName),!,
|
|
||||||
instantiate_clause(T,H,BIn,BOut).
|
|
||||||
|
|
||||||
varName_present(VarName):-
|
|
||||||
universe(VarNames,_U), member(VarName,VarNames).
|
|
||||||
|
|
||||||
process_clauses([(end_of_file,[])],[]).
|
|
||||||
|
|
||||||
process_clauses([((H:-B),V)|T],[r(V,HL,B)|T1]):-
|
|
||||||
H=(_;_),!,
|
|
||||||
list2or(HL1,H),
|
|
||||||
process_head(HL1,0,HL),
|
|
||||||
process_clauses(T,T1).
|
|
||||||
|
|
||||||
process_clauses([((H:-B),V)|T],[r(V,HL,B)|T1]):-
|
|
||||||
H=(_:_),!,
|
|
||||||
list2or(HL1,H),
|
|
||||||
process_head(HL1,0,HL),
|
|
||||||
process_clauses(T,T1).
|
|
||||||
|
|
||||||
process_clauses([((H:-B),V)|T],[r(V,[H:1],B)|T1]):-!,
|
|
||||||
process_clauses(T,T1).
|
|
||||||
|
|
||||||
process_clauses([(H,V)|T],[r(V,HL,true)|T1]):-
|
|
||||||
H=(_;_),!,
|
|
||||||
list2or(HL1,H),
|
|
||||||
process_head(HL1,0,HL),
|
|
||||||
process_clauses(T,T1).
|
|
||||||
|
|
||||||
process_clauses([(H,V)|T],[r(V,HL,true)|T1]):-
|
|
||||||
H=(_:_),!,
|
|
||||||
list2or(HL1,H),
|
|
||||||
process_head(HL1,0,HL),
|
|
||||||
process_clauses(T,T1).
|
|
||||||
|
|
||||||
process_clauses([(H,V)|T],[r(V,[H:1],true)|T1]):-
|
|
||||||
process_clauses(T,T1).
|
|
||||||
|
|
||||||
process_head([H:PH],P,[H:PH1|Null]):-
|
|
||||||
PH1 is PH,
|
|
||||||
PNull is 1-P-PH1,
|
|
||||||
setting(epsilon,Eps),
|
|
||||||
EpsNeg is - Eps,
|
|
||||||
PNull > EpsNeg,
|
|
||||||
(PNull>Eps->
|
|
||||||
Null=['':PNull]
|
|
||||||
;
|
|
||||||
Null=[]
|
|
||||||
).
|
|
||||||
|
|
||||||
process_head([H:PH|T],P,[H:PH1|NT]):-
|
|
||||||
PH1 is PH,
|
|
||||||
P1 is P+PH1,
|
|
||||||
process_head(T,P1,NT).
|
|
||||||
|
|
||||||
read_clauses(S,[(Cl,V)|Out]):-
|
|
||||||
read_term(S,Cl,[variable_names(V)]),
|
|
||||||
(Cl=end_of_file->
|
|
||||||
Out=[]
|
|
||||||
;
|
|
||||||
read_clauses(S,Out)
|
|
||||||
).
|
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
list2or([X],X):-
|
|
||||||
X\=;(_,_),!.
|
|
||||||
|
|
||||||
list2or([H|T],(H ; Ta)):-!,
|
|
||||||
list2or(T,Ta).
|
|
||||||
|
|
||||||
|
|
||||||
list2and([],true):-!.
|
|
||||||
|
|
||||||
list2and([X],X):-
|
|
||||||
X\=(_,_),!.
|
|
||||||
|
|
||||||
list2and([H|T],(H,Ta)):-!,
|
|
||||||
list2and(T,Ta).
|
|
||||||
|
|
||||||
builtin(_A is _B).
|
|
||||||
builtin(_A > _B).
|
|
||||||
builtin(_A < _B).
|
|
||||||
builtin(_A >= _B).
|
|
||||||
builtin(_A =< _B).
|
|
||||||
builtin(_A =:= _B).
|
|
||||||
builtin(_A =\= _B).
|
|
||||||
builtin(true).
|
|
||||||
builtin(false).
|
|
||||||
builtin(_A = _B).
|
|
||||||
builtin(_A==_B).
|
|
||||||
builtin(_A\=_B).
|
|
||||||
builtin(_A\==_B).
|
|
||||||
|
|
||||||
bg(member(_El,_L)).
|
|
||||||
bg(average(_L,_Av)).
|
|
||||||
bg(max_list(_L,_Max)).
|
|
||||||
bg(min_list(_L,_Max)).
|
|
||||||
|
|
||||||
average(L,Av):-
|
|
||||||
sum_list(L,Sum),
|
|
||||||
length(L,N),
|
|
||||||
Av is Sum/N.
|
|
||||||
|
|
||||||
/* set(Par,Value) can be used to set the value of a parameter */
|
|
||||||
set(Parameter,Value):-
|
|
||||||
retract(setting(Parameter,_)),
|
|
||||||
assert(setting(Parameter,Value)).
|
|
||||||
|
|
@ -1,263 +0,0 @@
|
|||||||
/*
|
|
||||||
|
|
||||||
Program for computing the probability of a query directly according to the
|
|
||||||
semantics
|
|
||||||
|
|
||||||
Copyright (c) 2007, Fabrizio Riguzzi
|
|
||||||
|
|
||||||
|
|
||||||
*/
|
|
||||||
:-use_module(library(lists)).
|
|
||||||
:-dynamic setting/2.
|
|
||||||
:-set_prolog_flag(unknown,fail).
|
|
||||||
|
|
||||||
|
|
||||||
setting(epsilon,0.00001).
|
|
||||||
setting(test_builtins,false).
|
|
||||||
|
|
||||||
solve(GoalsList,Prob):-
|
|
||||||
s(GoalsList,Prob).
|
|
||||||
|
|
||||||
|
|
||||||
s(GoalsList,Prob):-
|
|
||||||
program_names(L),
|
|
||||||
list2and(GoalsList,Goals),
|
|
||||||
run_query(L,Goals,0,Prob).
|
|
||||||
|
|
||||||
run_query([],_G,P,P).
|
|
||||||
|
|
||||||
run_query([Prog|T],Goal,PIn,POut):-
|
|
||||||
elab_conj(Prog,Goal,Goal1),
|
|
||||||
call(Goal1),
|
|
||||||
prob(Prog,P),
|
|
||||||
P1 is PIn+P,
|
|
||||||
run_query(T,Goal,P1,POut).
|
|
||||||
|
|
||||||
run_query([Prog|T],Goal,PIn,POut):-
|
|
||||||
elab_conj(Prog,Goal,Goal1),
|
|
||||||
\+ call(Goal1),
|
|
||||||
run_query(T,Goal,PIn,POut).
|
|
||||||
|
|
||||||
p(File):-
|
|
||||||
atom_concat(File,'.uni',FileUni),
|
|
||||||
consult(FileUni),
|
|
||||||
atom_concat(File,'.cpl',FilePl),
|
|
||||||
open(FilePl,read,S),
|
|
||||||
read_clauses(S,C),
|
|
||||||
close(S),
|
|
||||||
process_clauses(C,ClausesVar),
|
|
||||||
instantiate(ClausesVar,[],Clauses),
|
|
||||||
assert(program(1)),
|
|
||||||
assert(program_names([])),
|
|
||||||
create_programs(Clauses).
|
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
create_programs(Clauses):-
|
|
||||||
create_single_program(Clauses,1,Program),
|
|
||||||
retract(program(N)),
|
|
||||||
number_codes(N,NC),
|
|
||||||
atom_codes(NA,NC),
|
|
||||||
atom_concat(p,NA,Name),
|
|
||||||
N1 is N+1,
|
|
||||||
assert(program(N1)),
|
|
||||||
format("Writing program ~d~n",[N]),
|
|
||||||
write_program(Name,Program),
|
|
||||||
retract(program_names(L)),
|
|
||||||
append(L,[Name],L1),
|
|
||||||
assert(program_names(L1)),
|
|
||||||
fail.
|
|
||||||
|
|
||||||
create_programs(_).
|
|
||||||
|
|
||||||
write_program(_Name,[]).
|
|
||||||
|
|
||||||
write_program(Name,[(H:-B)|T]):-
|
|
||||||
elab_conj(Name,H,H1),
|
|
||||||
elab_conj(Name,B,B1),
|
|
||||||
assertz((H1:-B1)),
|
|
||||||
write_program(Name,T).
|
|
||||||
|
|
||||||
elab_conj(_Name,true,true):-!.
|
|
||||||
|
|
||||||
elab_conj(Name,\+(B),\+(B1)):-!,
|
|
||||||
elab_conj(Name,B,B1).
|
|
||||||
|
|
||||||
elab_conj(Name,(BL,Rest),(BL1,Rest1)):-!,
|
|
||||||
elab_conj(Name,BL,BL1),
|
|
||||||
elab_conj(Name,Rest,Rest1).
|
|
||||||
|
|
||||||
elab_conj(Name,bagof(V,EV^G,L),bagof(V,EV^GL,L)):-!,
|
|
||||||
elab_conj(Name,G,GL).
|
|
||||||
|
|
||||||
elab_conj(Name,bagof(V,G,L),bagof(V,GL,L)):-!,
|
|
||||||
elab_conj(Name,G,GL).
|
|
||||||
|
|
||||||
elab_conj(Name,setof(V,EV^G,L),setof(V,EV^GL,L)):-!,
|
|
||||||
elab_conj(Name,G,GL).
|
|
||||||
|
|
||||||
elab_conj(Name,setof(V,G,L),setof(V,GL,L)):-!,
|
|
||||||
elab_conj(Name,G,GL).
|
|
||||||
|
|
||||||
elab_conj(Name,findall(V,G,L),findall(V,GL,L)):-!,
|
|
||||||
elab_conj(Name,G,GL).
|
|
||||||
|
|
||||||
elab_conj(_Name,A,A):-
|
|
||||||
bg(A),!.
|
|
||||||
|
|
||||||
elab_conj(_Name,A,A):-
|
|
||||||
builtin(A),!.
|
|
||||||
|
|
||||||
elab_conj(Name,Lit,Lit1):-
|
|
||||||
Lit\=(_,_),
|
|
||||||
Lit=..[Pred|Args],
|
|
||||||
Lit1=..[Pred,Name|Args].
|
|
||||||
|
|
||||||
|
|
||||||
create_single_program([],P,[(prob(P):-true)]).
|
|
||||||
|
|
||||||
create_single_program([r(H,B)|T],PIn,[(HA:-B)|T1]):-
|
|
||||||
member((HA:P),H),
|
|
||||||
P1 is PIn*P,
|
|
||||||
create_single_program(T,P1,T1).
|
|
||||||
|
|
||||||
instantiate([],C,C).
|
|
||||||
|
|
||||||
instantiate([r(V,H,B)|T],CIn,COut):-
|
|
||||||
findall(r(H,BOut),instantiate_clause(V,H,B,BOut),L),
|
|
||||||
append(CIn,L,C1),
|
|
||||||
instantiate(T,C1,COut).
|
|
||||||
|
|
||||||
check_body([],[]).
|
|
||||||
|
|
||||||
check_body([H|T],TOut):-
|
|
||||||
builtin(H),setting(test_builtins,true),!,
|
|
||||||
call(H),
|
|
||||||
check_body(T,TOut).
|
|
||||||
|
|
||||||
check_body([H|T],[H|TOut]):-
|
|
||||||
check_body(T,TOut).
|
|
||||||
|
|
||||||
|
|
||||||
instantiate_clause([],_H,B,BOut):-
|
|
||||||
list2and(BL,B),
|
|
||||||
check_body(BL,BLOut),
|
|
||||||
list2and(BLOut,BOut).
|
|
||||||
|
|
||||||
|
|
||||||
instantiate_clause([VarName=Var|T],H,BIn,BOut):-
|
|
||||||
universe(VarNames,U),
|
|
||||||
member(VarName,VarNames),
|
|
||||||
member(Var,U),
|
|
||||||
instantiate_clause(T,H,BIn,BOut).
|
|
||||||
|
|
||||||
instantiate_clause([VarName=_Var|T],H,BIn,BOut):-
|
|
||||||
\+ varName_present(VarName),!,
|
|
||||||
instantiate_clause(T,H,BIn,BOut).
|
|
||||||
|
|
||||||
varName_present(VarName):-
|
|
||||||
universe(VarNames,_U), member(VarName,VarNames).
|
|
||||||
|
|
||||||
process_clauses([(end_of_file,[])],[]).
|
|
||||||
|
|
||||||
process_clauses([((H:-B),V)|T],[r(V,HL,B)|T1]):-
|
|
||||||
H=(_;_),!,
|
|
||||||
list2or(HL1,H),
|
|
||||||
process_head(HL1,0,HL),
|
|
||||||
process_clauses(T,T1).
|
|
||||||
|
|
||||||
process_clauses([((H:-B),V)|T],[r(V,HL,B)|T1]):-
|
|
||||||
H=(_:_),!,
|
|
||||||
list2or(HL1,H),
|
|
||||||
process_head(HL1,0,HL),
|
|
||||||
process_clauses(T,T1).
|
|
||||||
|
|
||||||
process_clauses([((H:-B),V)|T],[r(V,[H:1],B)|T1]):-!,
|
|
||||||
process_clauses(T,T1).
|
|
||||||
|
|
||||||
process_clauses([(H,V)|T],[r(V,HL,true)|T1]):-
|
|
||||||
H=(_;_),!,
|
|
||||||
list2or(HL1,H),
|
|
||||||
process_head(HL1,0,HL),
|
|
||||||
process_clauses(T,T1).
|
|
||||||
|
|
||||||
process_clauses([(H,V)|T],[r(V,HL,true)|T1]):-
|
|
||||||
H=(_:_),!,
|
|
||||||
list2or(HL1,H),
|
|
||||||
process_head(HL1,0,HL),
|
|
||||||
process_clauses(T,T1).
|
|
||||||
|
|
||||||
process_clauses([(H,V)|T],[r(V,[H:1],true)|T1]):-
|
|
||||||
process_clauses(T,T1).
|
|
||||||
|
|
||||||
process_head([H:PH],P,[H:PH1|Null]):-
|
|
||||||
PH1 is PH,
|
|
||||||
PNull is 1-P-PH1,
|
|
||||||
setting(epsilon,Eps),
|
|
||||||
EpsNeg is - Eps,
|
|
||||||
PNull > EpsNeg,
|
|
||||||
(PNull>Eps->
|
|
||||||
Null=['':PNull]
|
|
||||||
;
|
|
||||||
Null=[]
|
|
||||||
).
|
|
||||||
|
|
||||||
process_head([H:PH|T],P,[H:PH1|NT]):-
|
|
||||||
PH1 is PH,
|
|
||||||
P1 is P+PH1,
|
|
||||||
process_head(T,P1,NT).
|
|
||||||
|
|
||||||
read_clauses(S,[(Cl,V)|Out]):-
|
|
||||||
read_term(S,Cl,[variable_names(V)]),
|
|
||||||
(Cl=end_of_file->
|
|
||||||
Out=[]
|
|
||||||
;
|
|
||||||
read_clauses(S,Out)
|
|
||||||
).
|
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
list2or([X],X):-
|
|
||||||
X\=;(_,_),!.
|
|
||||||
|
|
||||||
list2or([H|T],(H ; Ta)):-!,
|
|
||||||
list2or(T,Ta).
|
|
||||||
|
|
||||||
|
|
||||||
list2and([],true):-!.
|
|
||||||
|
|
||||||
list2and([X],X):-
|
|
||||||
X\=(_,_),!.
|
|
||||||
|
|
||||||
list2and([H|T],(H,Ta)):-!,
|
|
||||||
list2and(T,Ta).
|
|
||||||
|
|
||||||
builtin(_A is _B).
|
|
||||||
builtin(_A > _B).
|
|
||||||
builtin(_A < _B).
|
|
||||||
builtin(_A >= _B).
|
|
||||||
builtin(_A =< _B).
|
|
||||||
builtin(_A =:= _B).
|
|
||||||
builtin(_A =\= _B).
|
|
||||||
builtin(true).
|
|
||||||
builtin(false).
|
|
||||||
builtin(_A = _B).
|
|
||||||
builtin(_A==_B).
|
|
||||||
builtin(_A\=_B).
|
|
||||||
builtin(_A\==_B).
|
|
||||||
|
|
||||||
bg(member(_El,_L)).
|
|
||||||
bg(average(_L,_Av)).
|
|
||||||
bg(max_list(_L,_Max)).
|
|
||||||
bg(min_list(_L,_Max)).
|
|
||||||
|
|
||||||
average(L,Av):-
|
|
||||||
sum_list(L,Sum),
|
|
||||||
length(L,N),
|
|
||||||
Av is Sum/N.
|
|
||||||
|
|
||||||
/* set(Par,Value) can be used to set the value of a parameter */
|
|
||||||
set(Parameter,Value):-
|
|
||||||
retract(setting(Parameter,_)),
|
|
||||||
assert(setting(Parameter,Value)).
|
|
||||||
|
|
184
cplint/test.yap
184
cplint/test.yap
@ -1,184 +0,0 @@
|
|||||||
/*
|
|
||||||
LPAD and CP-Logic interpreter test program
|
|
||||||
|
|
||||||
Copyright (c) 2007, Fabrizio Riguzzi
|
|
||||||
|
|
||||||
use
|
|
||||||
:-t.
|
|
||||||
to execute the test
|
|
||||||
|
|
||||||
*/
|
|
||||||
:-use_module(library(cplint)).
|
|
||||||
|
|
||||||
|
|
||||||
epsilon(0.000001).
|
|
||||||
|
|
||||||
close_to(V,T):-
|
|
||||||
epsilon(E),
|
|
||||||
TLow is T-E,
|
|
||||||
THigh is T+E,
|
|
||||||
TLow<V,
|
|
||||||
V<THigh.
|
|
||||||
|
|
||||||
|
|
||||||
t:-
|
|
||||||
files(F),
|
|
||||||
statistics(runtime,[_,_]),
|
|
||||||
test_files(F),
|
|
||||||
statistics(runtime,[_,T]),
|
|
||||||
T1 is T /1000,
|
|
||||||
format("Time ~f secs~n",[T1]).
|
|
||||||
|
|
||||||
test_files([]).
|
|
||||||
|
|
||||||
test_files([H|T]):-
|
|
||||||
format("~a~n",[H]),
|
|
||||||
library_directory(LD),
|
|
||||||
atom_concat(LD,'/cplint/examples/',ExDir),
|
|
||||||
atom_concat(ExDir,H,NH),
|
|
||||||
p(NH),
|
|
||||||
findall(A,test(A,H),L),
|
|
||||||
test_all(H,L),
|
|
||||||
test_files(T).
|
|
||||||
|
|
||||||
test_all(_F,[]).
|
|
||||||
|
|
||||||
test_all(F,[H|T]):-
|
|
||||||
copy_term(H,NH),
|
|
||||||
NH=(Query,close_to('P',Prob)),
|
|
||||||
format("~a ~p.~n",[F,NH]),
|
|
||||||
call(H),
|
|
||||||
test_all(F,T).
|
|
||||||
|
|
||||||
|
|
||||||
files([paper_ref_not,paper_ref,female,esapprox,esrange,threesideddice,
|
|
||||||
mendel,student,school_simple,school,coin2,es]).
|
|
||||||
|
|
||||||
test((s([\+ cites_cited(c1,p1)],P),close_to(P,0.7)),paper_ref_not).
|
|
||||||
test((s([cites_citing(c1,p1)],P),close_to(P,0.14)),paper_ref_not).
|
|
||||||
|
|
||||||
|
|
||||||
test((s([cites_cited(c1,p1)],P),close_to(P,0.181333333)),paper_ref).
|
|
||||||
test((s([cites_cited(c1,p2)],P),close_to(P,0.181333333)),paper_ref).
|
|
||||||
test((s([cites_cited(c1,p4)],P),close_to(P,0.181333333)),paper_ref).
|
|
||||||
test((s([cites_cited(c1,p3)],P),close_to(P,0.228)),paper_ref).
|
|
||||||
test((s([cites_cited(c1,p5)],P),close_to(P,0.228)),paper_ref).
|
|
||||||
|
|
||||||
|
|
||||||
test((s([female(f)],P),close_to(P,0.6)),female).
|
|
||||||
test((s([male(f)],P),close_to(P,0.4)),female).
|
|
||||||
|
|
||||||
test((s([a],P),close_to(P,0.1719)),esapprox).
|
|
||||||
|
|
||||||
test((s([a(1)],P),close_to(P,0.2775)),esrange).
|
|
||||||
test((s([a(2)],P),close_to(P,0.36)),esrange).
|
|
||||||
|
|
||||||
test((s([on(0,1)],P),close_to(P,0.333333333333333)),threesideddice).
|
|
||||||
test((s([on(1,1)],P),close_to(P,0.222222222222222)),threesideddice).
|
|
||||||
test((s([on(2,1)],P),close_to(P,0.148148147703704)),threesideddice).
|
|
||||||
|
|
||||||
test((sc([on(2,1)],[on(0,1)],P),close_to(P,0.222222222222222)),threesideddice).
|
|
||||||
test((sc([on(2,1)],[on(1,1)],P),close_to(P,0.333333333333333)),threesideddice).
|
|
||||||
|
|
||||||
|
|
||||||
test((s([cg(s,1,p)],P),close_to(P,0.75)),mendel).
|
|
||||||
test((s([cg(s,1,w)],P),close_to(P,0.25)),mendel).
|
|
||||||
test((s([cg(s,2,p)],P),close_to(P,0.25)),mendel).
|
|
||||||
test((s([cg(s,2,w)],P),close_to(P,0.75)),mendel).
|
|
||||||
test((s([cg(f,2,w)],P),close_to(P,0.5)),mendel).
|
|
||||||
test((s([cg(s,2,w)],P),close_to(P,0.75)),mendel).
|
|
||||||
|
|
||||||
test((s([a],P),close_to(P,0.226)),es).
|
|
||||||
|
|
||||||
test((s([heads(coin1)],P),close_to(P,0.51)),coin2).
|
|
||||||
test((s([heads(coin2)],P),close_to(P,0.51)),coin2).
|
|
||||||
|
|
||||||
test((s([tails(coin1)],P),close_to(P,0.49)),coin2).
|
|
||||||
test((s([tails(coin2)],P),close_to(P,0.49)),coin2).
|
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
test((s([student_rank(jane_doe,h)],P),close_to(P,0.465)),student).
|
|
||||||
test((s([student_rank(jane_doe,l)],P),close_to(P,0.535)),student).
|
|
||||||
|
|
||||||
test((s([course_rat(phil101,h)],P),close_to(P,0.330656)),student).
|
|
||||||
test((s([course_rat(phil101,l)],P),close_to(P,0.669344)),student).
|
|
||||||
|
|
||||||
|
|
||||||
test((s([professor_ability(p0,h)],P),close_to(P,0.5)),school).
|
|
||||||
test((s([professor_ability(p0,m)],P),close_to(P,0.4)),school).
|
|
||||||
test((s([professor_ability(p0,l)],P),close_to(P,0.1)),school).
|
|
||||||
|
|
||||||
|
|
||||||
test((s([professor_popularity(p0,h)],P),close_to(P,0.531)),school).
|
|
||||||
test((s([professor_popularity(p0,l)],P),close_to(P,0.175)),school).
|
|
||||||
test((s([professor_popularity(p0,m)],P),close_to(P,0.294)),school).
|
|
||||||
|
|
||||||
test((sc([professor_ability(p0,h)],[professor_popularity(p0,h)],P),close_to(P,0.847457627118644)),school).
|
|
||||||
test((sc([professor_ability(p0,l)],[professor_popularity(p0,h)],P),close_to(P,0.00188323917137476)),school).
|
|
||||||
test((sc([professor_ability(p0,m)],[professor_popularity(p0,h)],P),close_to(P,0.150659133709981)),school).
|
|
||||||
|
|
||||||
test((sc([professor_popularity(p0,h)],[professor_ability(p0,h)],P),close_to(P,0.9)),school).
|
|
||||||
test((sc([professor_popularity(p0,l)],[professor_ability(p0,h)],P),close_to(P,0.01)),school).
|
|
||||||
test((sc([professor_popularity(p0,m)],[professor_ability(p0,h)],P),close_to(P,0.09)),school).
|
|
||||||
|
|
||||||
test(( s([registration_grade(r0,1)],P),close_to(P,0.06675)),school).
|
|
||||||
test(( s([registration_grade(r0,2)],P),close_to(P,0.16575)),school).
|
|
||||||
test(( s([registration_grade(r0,3)],P),close_to(P, 0.356)),school).
|
|
||||||
test(( s([registration_grade(r0,4)],P),close_to(P,0.4115)),school).
|
|
||||||
|
|
||||||
test((sc([registration_grade(r0,1)],[registration_course(r0,C), course_difficulty(C,h)],P),close_to(P,0.15)),school).
|
|
||||||
test((sc([registration_grade(r0,2)],[registration_course(r0,C), course_difficulty(C,h)],P),close_to(P,0.285)),school).
|
|
||||||
test((sc([registration_grade(r0,3)],[registration_course(r0,C), course_difficulty(C,h)],P),close_to(P,0.424)),school).
|
|
||||||
test((sc([registration_grade(r0,4)],[registration_course(r0,C), course_difficulty(C,h)],P),close_to(P,0.141)),school).
|
|
||||||
|
|
||||||
test((sc([registration_grade(r0,1)], [registration_course(r0,C), course_difficulty(C,h), registration_student(r0,S), student_intelligence(S,h)],P),close_to(P,0.05)),school).
|
|
||||||
test((sc([registration_grade(r0,2)], [registration_course(r0,C), course_difficulty(C,h), registration_student(r0,S), student_intelligence(S,h)],P),close_to(P,0.15)),school).
|
|
||||||
test((sc([registration_grade(r0,3)], [registration_course(r0,C), course_difficulty(C,h), registration_student(r0,S), student_intelligence(S,h)],P),close_to(P,0.6)),school).
|
|
||||||
test((sc([registration_grade(r0,4)], [registration_course(r0,C), course_difficulty(C,h), registration_student(r0,S), student_intelligence(S,h)],P),close_to(P,0.2)),school).
|
|
||||||
|
|
||||||
test((sc([registration_grade(r0,1)],[registration_course(r0,C), course_difficulty(C,l), registration_student(r0,S), student_intelligence(S,h)],P),close_to(P,0.01)),school).
|
|
||||||
test((sc([registration_grade(r0,2)],[registration_course(r0,C), course_difficulty(C,l), registration_student(r0,S), student_intelligence(S,h)],P),close_to(P,0.02)),school).
|
|
||||||
test((sc([registration_grade(r0,3)],[registration_course(r0,C), course_difficulty(C,l), registration_student(r0,S), student_intelligence(S,h)],P),close_to(P,0.12)),school).
|
|
||||||
test((sc([registration_grade(r0,4)],[registration_course(r0,C), course_difficulty(C,l), registration_student(r0,S), student_intelligence(S,h)],P),close_to(P,0.85)),school).
|
|
||||||
|
|
||||||
test((s([registration_satisfaction(r0,1)],P),close_to(P,0.15197525)),school).
|
|
||||||
test((s([registration_satisfaction(r0,2)],P),close_to(P,0.1533102)),school).
|
|
||||||
test((s([registration_satisfaction(r0,3)],P),close_to(P,0.6947145)),school).
|
|
||||||
|
|
||||||
test((sc([registration_satisfaction(r0,1)],[ registration_student(r0,S), student_intelligence(S,h)],P),close_to(P,0.0959225)),school).
|
|
||||||
test((sc([registration_satisfaction(r0,2)],[ registration_student(r0,S), student_intelligence(S,h)],P),close_to(P,0.124515)),school).
|
|
||||||
test((sc([registration_satisfaction(r0,3)],[ registration_student(r0,S), student_intelligence(S,h)],P),close_to(P,0.7795625)),school).
|
|
||||||
|
|
||||||
test((sc([registration_satisfaction(r0,1)],[registration_grade(r0,4)],P),close_to(P,0.04)),school).
|
|
||||||
test((sc([registration_satisfaction(r0,2)],[registration_grade(r0,4)],P),close_to(P,0.06)),school).
|
|
||||||
test((sc([registration_satisfaction(r0,3)],[registration_grade(r0,4)],P),close_to(P,0.9)),school).
|
|
||||||
|
|
||||||
test((sc([registration_satisfaction(r0,1)],[registration_grade(r0,1)],P),close_to(P,0.528)),school).
|
|
||||||
test((sc([registration_satisfaction(r0,2)],[registration_grade(r0,1)],P),close_to(P,0.167)),school).
|
|
||||||
test((sc([registration_satisfaction(r0,3)],[registration_grade(r0,1)],P),close_to(P,0.305)),school).
|
|
||||||
|
|
||||||
test((sc([ registration_grade(r0,1)],[registration_satisfaction(r0,3)],P),close_to(P,0.0293052037923492)),school).
|
|
||||||
test((sc([ registration_grade(r0,2)],[registration_satisfaction(r0,3)],P),close_to(P, 0.114760451955444)),school).
|
|
||||||
test((sc([ registration_grade(r0,3)],[registration_satisfaction(r0,3)],P),close_to(P,0.322837654892765)),school).
|
|
||||||
test((sc([ registration_grade(r0,4)],[registration_satisfaction(r0,3)],P),close_to(P,0.533096689359442)),school).
|
|
||||||
|
|
||||||
test((s([course_rating(c0,h)],P),close_to(P,0.5392099)),school).
|
|
||||||
test((s([course_rating(c0,l)],P),close_to(P, 0.2)),school).
|
|
||||||
test((s([course_rating(c0,m)],P),close_to(P,0.2607901)),school).
|
|
||||||
|
|
||||||
test((sc([course_difficulty(c0,h)],[course_rating(c0,h)],P),close_to(P,0.235185778302661)),school).
|
|
||||||
test((sc([course_difficulty(c0,l)],[course_rating(c0,h)],P),close_to(P,0.259096503977393)),school).
|
|
||||||
test((sc([course_difficulty(c0,m)],[course_rating(c0,h)],P),close_to(P,0.505717717719945)),school).
|
|
||||||
|
|
||||||
test((s([course_difficulty(c0,h)],P),close_to(P,0.25)),school).
|
|
||||||
test((s([course_difficulty(c0,l)],P),close_to(P,0.25)),school).
|
|
||||||
test((s([course_difficulty(c0,m)],P),close_to(P,0.5)),school).
|
|
||||||
|
|
||||||
|
|
||||||
test((s([student_ranking(s0,h)],P),close_to(P,0.6646250000000005)),school_simple).
|
|
||||||
test((s([student_ranking(s0,l)],P),close_to(P,0.33537499999999987)),school_simple).
|
|
||||||
|
|
||||||
:-t.
|
|
||||||
|
|
||||||
:-halt.
|
|
@ -1,216 +0,0 @@
|
|||||||
/*
|
|
||||||
LPAD and CP-Logic interpreter test program
|
|
||||||
|
|
||||||
Copyright (c) 2007, Fabrizio Riguzzi
|
|
||||||
|
|
||||||
use
|
|
||||||
:-t.
|
|
||||||
to execute the test
|
|
||||||
|
|
||||||
*/
|
|
||||||
:-use_module(library(lpadsld)).
|
|
||||||
|
|
||||||
|
|
||||||
epsilon(0.000001).
|
|
||||||
|
|
||||||
close_to(V,T):-
|
|
||||||
epsilon(E),
|
|
||||||
TLow is T-E,
|
|
||||||
THigh is T+E,
|
|
||||||
TLow<V,
|
|
||||||
V<THigh.
|
|
||||||
|
|
||||||
|
|
||||||
t:-
|
|
||||||
format("~nTesting lpadsld.yap~n~n",[]),
|
|
||||||
files(F),
|
|
||||||
statistics(runtime,[_,_]),
|
|
||||||
set(ground_body,false),
|
|
||||||
format("~nNon ground body~n~n",[]),
|
|
||||||
test_files(F,ground_body(false)),
|
|
||||||
set(ground_body,true),
|
|
||||||
format("~nGround body~n~n",[]),
|
|
||||||
test_files(F,ground_body(true)),
|
|
||||||
statistics(runtime,[_,T]),
|
|
||||||
T1 is T /1000,
|
|
||||||
format("Test successful, time ~f secs.~n",[T1]).
|
|
||||||
|
|
||||||
t:-
|
|
||||||
format("Test unsuccessful.",[]).
|
|
||||||
|
|
||||||
test_files([],_GB).
|
|
||||||
|
|
||||||
test_files([H|T],GB):-
|
|
||||||
library_directory(LD),
|
|
||||||
atom_concat(LD,'/cplint/examples/',ExDir),
|
|
||||||
atom_concat(ExDir,H,NH),
|
|
||||||
p(NH),!,
|
|
||||||
findall(A,test(A,H,GB),L),
|
|
||||||
test_all(H,L),
|
|
||||||
test_files(T,GB).
|
|
||||||
|
|
||||||
test_all(_F,[]).
|
|
||||||
|
|
||||||
test_all(F,[H|T]):-
|
|
||||||
copy_term(H,NH),
|
|
||||||
NH=(_Query,close_to('P',_Prob)),
|
|
||||||
format("~a ~p.~n",[F,NH]),
|
|
||||||
call(H),!,
|
|
||||||
test_all(F,T).
|
|
||||||
|
|
||||||
|
|
||||||
files([paper_ref_not,paper_ref,female,exapprox,exrange,threesideddice,
|
|
||||||
mendel,student,school_simple,school,coin2,ex,trigger,throws,light]).
|
|
||||||
|
|
||||||
test((s([death],P),close_to(P,0.305555555555556)),trigger,_).
|
|
||||||
|
|
||||||
test((s([throws(mary),throws(john),break],P),close_to(P,0.46)),throws,_).
|
|
||||||
test((s([throws(mary),throws(john),\+break],P),close_to(P,0.04)),throws,_).
|
|
||||||
test((s([\+ throws(mary),throws(john),break],P),close_to(P,0.3)),throws,_).
|
|
||||||
test((s([\+ throws(mary),throws(john),\+ break],P),close_to(P,0.2)),throws,_).
|
|
||||||
|
|
||||||
test((s([push,replace],P),close_to(P,0.5)),light,_).
|
|
||||||
test((s([push,light],P),close_to(P,0.5)),light,_).
|
|
||||||
test((s([push,light,replace],P),close_to(P,0)),light,_).
|
|
||||||
test((s([light,replace],P),close_to(P,0)),light,_).
|
|
||||||
test((s([light],P),close_to(P,0.5)),light,_).
|
|
||||||
test((s([replace],P),close_to(P,0.5)),light,_).
|
|
||||||
|
|
||||||
|
|
||||||
test((s([\+ cites_cited(c1,p1)],P),close_to(P,0.7)),paper_ref_not,_).
|
|
||||||
test((s([cites_citing(c1,p1)],P),close_to(P,0.14)),paper_ref_not,_).
|
|
||||||
|
|
||||||
|
|
||||||
test((s([cites_cited(c1,p1)],P),close_to(P,0.181333333)),paper_ref,_).
|
|
||||||
test((s([cites_cited(c1,p2)],P),close_to(P,0.181333333)),paper_ref,_).
|
|
||||||
test((s([cites_cited(c1,p4)],P),close_to(P,0.181333333)),paper_ref,_).
|
|
||||||
test((s([cites_cited(c1,p3)],P),close_to(P,0.228)),paper_ref,_).
|
|
||||||
test((s([cites_cited(c1,p5)],P),close_to(P,0.228)),paper_ref,_).
|
|
||||||
|
|
||||||
|
|
||||||
test((s([female(f)],P),close_to(P,0.6)),female,_).
|
|
||||||
test((s([male(f)],P),close_to(P,0.4)),female,_).
|
|
||||||
|
|
||||||
test((s([a],P),close_to(P,0.1719)),exapprox,ground_body(true)).
|
|
||||||
test((s([a],P),close_to(P,0.099)),exapprox,ground_body(false)).
|
|
||||||
|
|
||||||
test((s([a(1)],P),close_to(P,0.2775)),exrange,_).
|
|
||||||
test((s([a(2)],P),close_to(P,0.36)),exrange,_).
|
|
||||||
|
|
||||||
test((s([on(0,1)],P),close_to(P,0.333333333333333)),threesideddice,_).
|
|
||||||
test((s([on(1,1)],P),close_to(P,0.222222222222222)),threesideddice,_).
|
|
||||||
test((s([on(2,1)],P),close_to(P,0.148148147703704)),threesideddice,_).
|
|
||||||
|
|
||||||
test((sc([on(2,1)],[on(0,1)],P),close_to(P,0.222222222222222)),threesideddice,_).
|
|
||||||
test((sc([on(2,1)],[on(1,1)],P),close_to(P,0.333333333333333)),threesideddice,_).
|
|
||||||
|
|
||||||
|
|
||||||
test((s([cg(s,1,p)],P),close_to(P,0.75)),mendel,_).
|
|
||||||
test((s([cg(s,1,w)],P),close_to(P,0.25)),mendel,_).
|
|
||||||
test((s([cg(s,2,p)],P),close_to(P,0.25)),mendel,_).
|
|
||||||
test((s([cg(s,2,w)],P),close_to(P,0.75)),mendel,_).
|
|
||||||
test((s([cg(f,2,w)],P),close_to(P,0.5)),mendel,_).
|
|
||||||
test((s([cg(s,2,w)],P),close_to(P,0.75)),mendel,_).
|
|
||||||
|
|
||||||
test((s([a],P),close_to(P,0.226)),ex,_).
|
|
||||||
|
|
||||||
test((s([heads(coin1)],P),close_to(P,0.51)),coin2,_).
|
|
||||||
test((s([heads(coin2)],P),close_to(P,0.51)),coin2,_).
|
|
||||||
|
|
||||||
test((s([tails(coin1)],P),close_to(P,0.49)),coin2,_).
|
|
||||||
test((s([tails(coin2)],P),close_to(P,0.49)),coin2,_).
|
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
test((s([student_rank(jane_doe,h)],P),close_to(P,0.465)),student,_).
|
|
||||||
test((s([student_rank(jane_doe,l)],P),close_to(P,0.535)),student,_).
|
|
||||||
|
|
||||||
test((s([course_rat(phil101,h)],P),close_to(P,0.330656)),student,_).
|
|
||||||
test((s([course_rat(phil101,l)],P),close_to(P,0.669344)),student,_).
|
|
||||||
|
|
||||||
|
|
||||||
test((s([professor_ability(p0,h)],P),close_to(P,0.5)),school,_).
|
|
||||||
test((s([professor_ability(p0,m)],P),close_to(P,0.4)),school,_).
|
|
||||||
test((s([professor_ability(p0,l)],P),close_to(P,0.1)),school,_).
|
|
||||||
|
|
||||||
|
|
||||||
test((s([professor_popularity(p0,h)],P),close_to(P,0.531)),school,_).
|
|
||||||
test((s([professor_popularity(p0,l)],P),close_to(P,0.175)),school,_).
|
|
||||||
test((s([professor_popularity(p0,m)],P),close_to(P,0.294)),school,_).
|
|
||||||
|
|
||||||
test((sc([professor_ability(p0,h)],[professor_popularity(p0,h)],P),close_to(P,0.847457627118644)),school,_).
|
|
||||||
test((sc([professor_ability(p0,l)],[professor_popularity(p0,h)],P),close_to(P,0.00188323917137476)),school,_).
|
|
||||||
test((sc([professor_ability(p0,m)],[professor_popularity(p0,h)],P),close_to(P,0.150659133709981)),school,_).
|
|
||||||
|
|
||||||
test((sc([professor_popularity(p0,h)],[professor_ability(p0,h)],P),close_to(P,0.9)),school,_).
|
|
||||||
test((sc([professor_popularity(p0,l)],[professor_ability(p0,h)],P),close_to(P,0.01)),school,_).
|
|
||||||
test((sc([professor_popularity(p0,m)],[professor_ability(p0,h)],P),close_to(P,0.09)),school,_).
|
|
||||||
|
|
||||||
test(( s([registration_grade(r0,1)],P),close_to(P,0.06675)),school,_).
|
|
||||||
test(( s([registration_grade(r0,2)],P),close_to(P,0.16575)),school,_).
|
|
||||||
test(( s([registration_grade(r0,3)],P),close_to(P, 0.356)),school,_).
|
|
||||||
test(( s([registration_grade(r0,4)],P),close_to(P,0.4115)),school,_).
|
|
||||||
|
|
||||||
test((sc([registration_grade(r0,1)],[registration_course(r0,C), course_difficulty(C,h)],P),close_to(P,0.15)),school,_).
|
|
||||||
test((sc([registration_grade(r0,2)],[registration_course(r0,C), course_difficulty(C,h)],P),close_to(P,0.285)),school,_).
|
|
||||||
test((sc([registration_grade(r0,3)],[registration_course(r0,C), course_difficulty(C,h)],P),close_to(P,0.424)),school,_).
|
|
||||||
test((sc([registration_grade(r0,4)],[registration_course(r0,C), course_difficulty(C,h)],P),close_to(P,0.141)),school,_).
|
|
||||||
|
|
||||||
test((sc([registration_grade(r0,1)], [registration_course(r0,C), course_difficulty(C,h),
|
|
||||||
registration_student(r0,S), student_intelligence(S,h)],P),close_to(P,0.05)),school,_).
|
|
||||||
test((sc([registration_grade(r0,2)], [registration_course(r0,C), course_difficulty(C,h),
|
|
||||||
registration_student(r0,S), student_intelligence(S,h)],P),close_to(P,0.15)),school,_).
|
|
||||||
test((sc([registration_grade(r0,3)], [registration_course(r0,C), course_difficulty(C,h),
|
|
||||||
registration_student(r0,S), student_intelligence(S,h)],P),close_to(P,0.6)),school,_).
|
|
||||||
test((sc([registration_grade(r0,4)], [registration_course(r0,C), course_difficulty(C,h),
|
|
||||||
registration_student(r0,S), student_intelligence(S,h)],P),close_to(P,0.2)),school,_).
|
|
||||||
|
|
||||||
test((sc([registration_grade(r0,1)],[registration_course(r0,C), course_difficulty(C,l),
|
|
||||||
registration_student(r0,S), student_intelligence(S,h)],P),close_to(P,0.01)),school,_).
|
|
||||||
test((sc([registration_grade(r0,2)],[registration_course(r0,C), course_difficulty(C,l),
|
|
||||||
registration_student(r0,S), student_intelligence(S,h)],P),close_to(P,0.02)),school,_).
|
|
||||||
test((sc([registration_grade(r0,3)],[registration_course(r0,C), course_difficulty(C,l),
|
|
||||||
registration_student(r0,S), student_intelligence(S,h)],P),close_to(P,0.12)),school,_).
|
|
||||||
test((sc([registration_grade(r0,4)],[registration_course(r0,C), course_difficulty(C,l),
|
|
||||||
registration_student(r0,S), student_intelligence(S,h)],P),close_to(P,0.85)),school,_).
|
|
||||||
|
|
||||||
test((s([registration_satisfaction(r0,1)],P),close_to(P,0.15197525)),school,_).
|
|
||||||
test((s([registration_satisfaction(r0,2)],P),close_to(P,0.1533102)),school,_).
|
|
||||||
test((s([registration_satisfaction(r0,3)],P),close_to(P,0.6947145)),school,_).
|
|
||||||
|
|
||||||
test((sc([registration_satisfaction(r0,1)],[ registration_student(r0,S),
|
|
||||||
student_intelligence(S,h)],P),close_to(P,0.0959225)),school,_).
|
|
||||||
test((sc([registration_satisfaction(r0,2)],[ registration_student(r0,S),
|
|
||||||
student_intelligence(S,h)],P),close_to(P,0.124515)),school,_).
|
|
||||||
test((sc([registration_satisfaction(r0,3)],[ registration_student(r0,S),
|
|
||||||
student_intelligence(S,h)],P),close_to(P,0.7795625)),school,_).
|
|
||||||
|
|
||||||
test((sc([registration_satisfaction(r0,1)],[registration_grade(r0,4)],P),close_to(P,0.04)),school,_).
|
|
||||||
test((sc([registration_satisfaction(r0,2)],[registration_grade(r0,4)],P),close_to(P,0.06)),school,_).
|
|
||||||
test((sc([registration_satisfaction(r0,3)],[registration_grade(r0,4)],P),close_to(P,0.9)),school,_).
|
|
||||||
|
|
||||||
test((sc([registration_satisfaction(r0,1)],[registration_grade(r0,1)],P),close_to(P,0.528)),school,_).
|
|
||||||
test((sc([registration_satisfaction(r0,2)],[registration_grade(r0,1)],P),close_to(P,0.167)),school,_).
|
|
||||||
test((sc([registration_satisfaction(r0,3)],[registration_grade(r0,1)],P),close_to(P,0.305)),school,_).
|
|
||||||
|
|
||||||
test((sc([ registration_grade(r0,1)],[registration_satisfaction(r0,3)],P),close_to(P,0.0293052037923492)),school,_).
|
|
||||||
test((sc([ registration_grade(r0,2)],[registration_satisfaction(r0,3)],P),close_to(P, 0.114760451955444)),school,_).
|
|
||||||
test((sc([ registration_grade(r0,3)],[registration_satisfaction(r0,3)],P),close_to(P,0.322837654892765)),school,_).
|
|
||||||
test((sc([ registration_grade(r0,4)],[registration_satisfaction(r0,3)],P),close_to(P,0.533096689359442)),school,_).
|
|
||||||
|
|
||||||
test((s([course_rating(c0,h)],P),close_to(P,0.5392099)),school,_).
|
|
||||||
test((s([course_rating(c0,l)],P),close_to(P, 0.2)),school,_).
|
|
||||||
test((s([course_rating(c0,m)],P),close_to(P,0.2607901)),school,_).
|
|
||||||
|
|
||||||
test((sc([course_difficulty(c0,h)],[course_rating(c0,h)],P),close_to(P,0.235185778302661)),school,_).
|
|
||||||
test((sc([course_difficulty(c0,l)],[course_rating(c0,h)],P),close_to(P,0.259096503977393)),school,_).
|
|
||||||
test((sc([course_difficulty(c0,m)],[course_rating(c0,h)],P),close_to(P,0.505717717719945)),school,_).
|
|
||||||
|
|
||||||
test((s([course_difficulty(c0,h)],P),close_to(P,0.25)),school,_).
|
|
||||||
test((s([course_difficulty(c0,l)],P),close_to(P,0.25)),school,_).
|
|
||||||
test((s([course_difficulty(c0,m)],P),close_to(P,0.5)),school,_).
|
|
||||||
|
|
||||||
|
|
||||||
test((s([student_ranking(s0,h)],P),close_to(P,0.6646250000000005)),school_simple,_).
|
|
||||||
test((s([student_ranking(s0,l)],P),close_to(P,0.33537499999999987)),school_simple,_).
|
|
||||||
|
|
@ -1,183 +0,0 @@
|
|||||||
/*
|
|
||||||
LPAD and CP-Logic interpreter test program
|
|
||||||
|
|
||||||
Copyright (c) 2007, Fabrizio Riguzzi
|
|
||||||
|
|
||||||
use
|
|
||||||
:-t.
|
|
||||||
to execute the test
|
|
||||||
|
|
||||||
*/
|
|
||||||
:-use_module(library(lpadsld)).
|
|
||||||
|
|
||||||
|
|
||||||
epsilon(0.000001).
|
|
||||||
|
|
||||||
close_to(V,T):-
|
|
||||||
epsilon(E),
|
|
||||||
TLow is T-E,
|
|
||||||
THigh is T+E,
|
|
||||||
TLow<V,
|
|
||||||
V<THigh.
|
|
||||||
|
|
||||||
|
|
||||||
t:-
|
|
||||||
files(F),
|
|
||||||
statistics(runtime,[_,_]),
|
|
||||||
test_files(F),
|
|
||||||
statistics(runtime,[_,T]),
|
|
||||||
T1 is T /1000,
|
|
||||||
format("Test successful, time ~f secs.~n",[T1]).
|
|
||||||
|
|
||||||
t:-
|
|
||||||
format("Test unsuccessful.",[]).
|
|
||||||
|
|
||||||
test_files([]).
|
|
||||||
|
|
||||||
test_files([H|T]):-
|
|
||||||
library_directory(LD),
|
|
||||||
atom_concat(LD,'/cplint/examples/',ExDir),
|
|
||||||
atom_concat(ExDir,H,NH),
|
|
||||||
p(NH),!,
|
|
||||||
findall(A,test(A,H),L),
|
|
||||||
test_all(H,L),
|
|
||||||
test_files(T).
|
|
||||||
|
|
||||||
test_all(_F,[]).
|
|
||||||
|
|
||||||
test_all(F,[H|T]):-
|
|
||||||
copy_term(H,NH),
|
|
||||||
NH=(Query,close_to('P',Prob)),
|
|
||||||
format("~a ~p.~n",[F,NH]),
|
|
||||||
call(H),!,
|
|
||||||
test_all(F,T).
|
|
||||||
|
|
||||||
|
|
||||||
files([paper_ref_not,paper_ref,female,esapprox,esrange,threesideddice,
|
|
||||||
mendel,student,school_simple,school,coin2,es]).
|
|
||||||
|
|
||||||
test((s([\+ cites_cited(c1,p1)],P),close_to(P,0.7)),paper_ref_not).
|
|
||||||
test((s([cites_citing(c1,p1)],P),close_to(P,0.14)),paper_ref_not).
|
|
||||||
|
|
||||||
|
|
||||||
test((s([cites_cited(c1,p1)],P),close_to(P,0.181333333)),paper_ref).
|
|
||||||
test((s([cites_cited(c1,p2)],P),close_to(P,0.181333333)),paper_ref).
|
|
||||||
test((s([cites_cited(c1,p4)],P),close_to(P,0.181333333)),paper_ref).
|
|
||||||
test((s([cites_cited(c1,p3)],P),close_to(P,0.228)),paper_ref).
|
|
||||||
test((s([cites_cited(c1,p5)],P),close_to(P,0.228)),paper_ref).
|
|
||||||
|
|
||||||
|
|
||||||
test((s([female(f)],P),close_to(P,0.6)),female).
|
|
||||||
test((s([male(f)],P),close_to(P,0.4)),female).
|
|
||||||
|
|
||||||
test((s([a],P),close_to(P,0.1719)),esapprox).
|
|
||||||
|
|
||||||
test((s([a(1)],P),close_to(P,0.2775)),esrange).
|
|
||||||
test((s([a(2)],P),close_to(P,0.36)),esrange).
|
|
||||||
|
|
||||||
test((s([on(0,1)],P),close_to(P,0.333333333333333)),threesideddice).
|
|
||||||
test((s([on(1,1)],P),close_to(P,0.222222222222222)),threesideddice).
|
|
||||||
test((s([on(2,1)],P),close_to(P,0.148148147703704)),threesideddice).
|
|
||||||
|
|
||||||
test((sc([on(2,1)],[on(0,1)],P),close_to(P,0.222222222222222)),threesideddice).
|
|
||||||
test((sc([on(2,1)],[on(1,1)],P),close_to(P,0.333333333333333)),threesideddice).
|
|
||||||
|
|
||||||
|
|
||||||
test((s([cg(s,1,p)],P),close_to(P,0.75)),mendel).
|
|
||||||
test((s([cg(s,1,w)],P),close_to(P,0.25)),mendel).
|
|
||||||
test((s([cg(s,2,p)],P),close_to(P,0.25)),mendel).
|
|
||||||
test((s([cg(s,2,w)],P),close_to(P,0.75)),mendel).
|
|
||||||
test((s([cg(f,2,w)],P),close_to(P,0.5)),mendel).
|
|
||||||
test((s([cg(s,2,w)],P),close_to(P,0.75)),mendel).
|
|
||||||
|
|
||||||
test((s([a],P),close_to(P,0.226)),es).
|
|
||||||
|
|
||||||
test((s([heads(coin1)],P),close_to(P,0.51)),coin2).
|
|
||||||
test((s([heads(coin2)],P),close_to(P,0.51)),coin2).
|
|
||||||
|
|
||||||
test((s([tails(coin1)],P),close_to(P,0.49)),coin2).
|
|
||||||
test((s([tails(coin2)],P),close_to(P,0.49)),coin2).
|
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
test((s([student_rank(jane_doe,h)],P),close_to(P,0.465)),student).
|
|
||||||
test((s([student_rank(jane_doe,l)],P),close_to(P,0.535)),student).
|
|
||||||
|
|
||||||
test((s([course_rat(phil101,h)],P),close_to(P,0.330656)),student).
|
|
||||||
test((s([course_rat(phil101,l)],P),close_to(P,0.669344)),student).
|
|
||||||
|
|
||||||
|
|
||||||
test((s([professor_ability(p0,h)],P),close_to(P,0.5)),school).
|
|
||||||
test((s([professor_ability(p0,m)],P),close_to(P,0.4)),school).
|
|
||||||
test((s([professor_ability(p0,l)],P),close_to(P,0.1)),school).
|
|
||||||
|
|
||||||
|
|
||||||
test((s([professor_popularity(p0,h)],P),close_to(P,0.531)),school).
|
|
||||||
test((s([professor_popularity(p0,l)],P),close_to(P,0.175)),school).
|
|
||||||
test((s([professor_popularity(p0,m)],P),close_to(P,0.294)),school).
|
|
||||||
|
|
||||||
test((sc([professor_ability(p0,h)],[professor_popularity(p0,h)],P),close_to(P,0.847457627118644)),school).
|
|
||||||
test((sc([professor_ability(p0,l)],[professor_popularity(p0,h)],P),close_to(P,0.00188323917137476)),school).
|
|
||||||
test((sc([professor_ability(p0,m)],[professor_popularity(p0,h)],P),close_to(P,0.150659133709981)),school).
|
|
||||||
|
|
||||||
test((sc([professor_popularity(p0,h)],[professor_ability(p0,h)],P),close_to(P,0.9)),school).
|
|
||||||
test((sc([professor_popularity(p0,l)],[professor_ability(p0,h)],P),close_to(P,0.01)),school).
|
|
||||||
test((sc([professor_popularity(p0,m)],[professor_ability(p0,h)],P),close_to(P,0.09)),school).
|
|
||||||
|
|
||||||
test(( s([registration_grade(r0,1)],P),close_to(P,0.06675)),school).
|
|
||||||
test(( s([registration_grade(r0,2)],P),close_to(P,0.16575)),school).
|
|
||||||
test(( s([registration_grade(r0,3)],P),close_to(P, 0.356)),school).
|
|
||||||
test(( s([registration_grade(r0,4)],P),close_to(P,0.4115)),school).
|
|
||||||
|
|
||||||
test((sc([registration_grade(r0,1)],[registration_course(r0,C), course_difficulty(C,h)],P),close_to(P,0.15)),school).
|
|
||||||
test((sc([registration_grade(r0,2)],[registration_course(r0,C), course_difficulty(C,h)],P),close_to(P,0.285)),school).
|
|
||||||
test((sc([registration_grade(r0,3)],[registration_course(r0,C), course_difficulty(C,h)],P),close_to(P,0.424)),school).
|
|
||||||
test((sc([registration_grade(r0,4)],[registration_course(r0,C), course_difficulty(C,h)],P),close_to(P,0.141)),school).
|
|
||||||
|
|
||||||
test((sc([registration_grade(r0,1)], [registration_course(r0,C), course_difficulty(C,h), registration_student(r0,S), student_intelligence(S,h)],P),close_to(P,0.05)),school).
|
|
||||||
test((sc([registration_grade(r0,2)], [registration_course(r0,C), course_difficulty(C,h), registration_student(r0,S), student_intelligence(S,h)],P),close_to(P,0.15)),school).
|
|
||||||
test((sc([registration_grade(r0,3)], [registration_course(r0,C), course_difficulty(C,h), registration_student(r0,S), student_intelligence(S,h)],P),close_to(P,0.6)),school).
|
|
||||||
test((sc([registration_grade(r0,4)], [registration_course(r0,C), course_difficulty(C,h), registration_student(r0,S), student_intelligence(S,h)],P),close_to(P,0.2)),school).
|
|
||||||
|
|
||||||
test((sc([registration_grade(r0,1)],[registration_course(r0,C), course_difficulty(C,l), registration_student(r0,S), student_intelligence(S,h)],P),close_to(P,0.01)),school).
|
|
||||||
test((sc([registration_grade(r0,2)],[registration_course(r0,C), course_difficulty(C,l), registration_student(r0,S), student_intelligence(S,h)],P),close_to(P,0.02)),school).
|
|
||||||
test((sc([registration_grade(r0,3)],[registration_course(r0,C), course_difficulty(C,l), registration_student(r0,S), student_intelligence(S,h)],P),close_to(P,0.12)),school).
|
|
||||||
test((sc([registration_grade(r0,4)],[registration_course(r0,C), course_difficulty(C,l), registration_student(r0,S), student_intelligence(S,h)],P),close_to(P,0.85)),school).
|
|
||||||
|
|
||||||
test((s([registration_satisfaction(r0,1)],P),close_to(P,0.15197525)),school).
|
|
||||||
test((s([registration_satisfaction(r0,2)],P),close_to(P,0.1533102)),school).
|
|
||||||
test((s([registration_satisfaction(r0,3)],P),close_to(P,0.6947145)),school).
|
|
||||||
|
|
||||||
test((sc([registration_satisfaction(r0,1)],[ registration_student(r0,S), student_intelligence(S,h)],P),close_to(P,0.0959225)),school).
|
|
||||||
test((sc([registration_satisfaction(r0,2)],[ registration_student(r0,S), student_intelligence(S,h)],P),close_to(P,0.124515)),school).
|
|
||||||
test((sc([registration_satisfaction(r0,3)],[ registration_student(r0,S), student_intelligence(S,h)],P),close_to(P,0.7795625)),school).
|
|
||||||
|
|
||||||
test((sc([registration_satisfaction(r0,1)],[registration_grade(r0,4)],P),close_to(P,0.04)),school).
|
|
||||||
test((sc([registration_satisfaction(r0,2)],[registration_grade(r0,4)],P),close_to(P,0.06)),school).
|
|
||||||
test((sc([registration_satisfaction(r0,3)],[registration_grade(r0,4)],P),close_to(P,0.9)),school).
|
|
||||||
|
|
||||||
test((sc([registration_satisfaction(r0,1)],[registration_grade(r0,1)],P),close_to(P,0.528)),school).
|
|
||||||
test((sc([registration_satisfaction(r0,2)],[registration_grade(r0,1)],P),close_to(P,0.167)),school).
|
|
||||||
test((sc([registration_satisfaction(r0,3)],[registration_grade(r0,1)],P),close_to(P,0.305)),school).
|
|
||||||
|
|
||||||
test((sc([ registration_grade(r0,1)],[registration_satisfaction(r0,3)],P),close_to(P,0.0293052037923492)),school).
|
|
||||||
test((sc([ registration_grade(r0,2)],[registration_satisfaction(r0,3)],P),close_to(P, 0.114760451955444)),school).
|
|
||||||
test((sc([ registration_grade(r0,3)],[registration_satisfaction(r0,3)],P),close_to(P,0.322837654892765)),school).
|
|
||||||
test((sc([ registration_grade(r0,4)],[registration_satisfaction(r0,3)],P),close_to(P,0.533096689359442)),school).
|
|
||||||
|
|
||||||
test((s([course_rating(c0,h)],P),close_to(P,0.5392099)),school).
|
|
||||||
test((s([course_rating(c0,l)],P),close_to(P, 0.2)),school).
|
|
||||||
test((s([course_rating(c0,m)],P),close_to(P,0.2607901)),school).
|
|
||||||
|
|
||||||
test((sc([course_difficulty(c0,h)],[course_rating(c0,h)],P),close_to(P,0.235185778302661)),school).
|
|
||||||
test((sc([course_difficulty(c0,l)],[course_rating(c0,h)],P),close_to(P,0.259096503977393)),school).
|
|
||||||
test((sc([course_difficulty(c0,m)],[course_rating(c0,h)],P),close_to(P,0.505717717719945)),school).
|
|
||||||
|
|
||||||
test((s([course_difficulty(c0,h)],P),close_to(P,0.25)),school).
|
|
||||||
test((s([course_difficulty(c0,l)],P),close_to(P,0.25)),school).
|
|
||||||
test((s([course_difficulty(c0,m)],P),close_to(P,0.5)),school).
|
|
||||||
|
|
||||||
|
|
||||||
test((s([student_ranking(s0,h)],P),close_to(P,0.6646250000000005)),school_simple).
|
|
||||||
test((s([student_ranking(s0,l)],P),close_to(P,0.33537499999999987)),school_simple).
|
|
||||||
|
|
Reference in New Issue
Block a user