|
From: Fabrizio R. <rz...@us...> - 2008-06-08 18:11:42
|
Update of /cvsroot/yap/cplint In directory sc8-pr-cvs10.sourceforge.net:/tmp/cvs-serv1840 Modified Files: cplint_yap.c lpadsld.pl testlpadsld_gbtrue.pl Added Files: testlpadsldit.pl Log Message: Added iterative deepening Printing of Cudd information --- NEW FILE: testlpadsldit.pl --- /* LPAD and CP-Logic reasoning suite Copyright (c) 2007, Fabrizio Riguzzi Test file for lpadsld.pl, case where the body is grounded Use :-t. to execute the test */ :-source. :-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 iterative deepening lpadsld.yap~n~n",[]), files(F), statistics(runtime,[_,_]), set(ground_body,true), set(depth_bound,1), set(min_error,0.05), format("~nGround body~n~n",[]), test_filesi(F,ground_body(true)), statistics(runtime,[_,T]), T1 is T /1000, format("Test successful, time ~f secs.~n",[T1]). t:- format("Test unsuccessful.~n",[]). test_filesi([],_GB). test_filesi([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_alli(H,L), test_filesi(T,GB). test_alli(_F,[]). test_alli(F,[H|T]):- copy_term(H,NH), NH=(s(Q,_P),close_to('P',P)),!, format("~a ~p.~n",[F,NH]), si(Q,PL,PU,_Time),!, format("Lower bound ~f, Upper bound ~f~n",[PL,PU]), P>=PL-1e-7,P=<PU+1e-7, test_alli(F,T). test_alli(F,[H|T]):- copy_term(H,NH), NH=(sc(Q,E,_P),close_to('P',P)), format("~a ~p.~n",[F,NH]), sci(Q,E,PL,PU,_Time),!, format("Lower bound ~f, Upper bound ~f~n",[PL,PU]), P>=PL-1e-10,P=<PU+1e-10, test_alli(F,T). files([ exapprox,exrange, threesideddice, mendel, 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((s([on(3,1)],P),close_to(P,0.0987654320987654)),threesideddice,_). test((s([on(4,1)],P),close_to(P,0.0658436213991769)),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((sc([on(4,1)],[on(1,1)],P),close_to(P, 0.148148148148148)),threesideddice,_). test((sc([on(5,1)],[on(2,1)],P),close_to(P, 0.148148148148148)),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,_). Index: cplint_yap.c =================================================================== RCS file: /cvsroot/yap/cplint/cplint_yap.c,v retrieving revision 1.3 retrieving revision 1.4 diff -u -r1.3 -r1.4 --- cplint_yap.c 8 Jun 2008 08:38:36 -0000 1.3 +++ cplint_yap.c 8 Jun 2008 18:11:41 -0000 1.4 @@ -134,11 +134,11 @@ bVar2mVar=array_alloc(int,0); create_dot=YAP_IntOfTerm(arg4); createVars(variables,arg1,mgr,bVar2mVar,create_dot,inames); - Cudd_PrintInfo(mgr,stderr); + //Cudd_PrintInfo(mgr,stderr); /* automatic variable reordering, default method CUDD_REORDER_SIFT used */ - printf("status %d\n",Cudd_ReorderingStatus(mgr,&order)); - printf("order %d\n",order); + //printf("status %d\n",Cudd_ReorderingStatus(mgr,&order)); + //printf("order %d\n",order); Cudd_AutodynEnable(mgr,CUDD_REORDER_SAME); /* Cudd_AutodynEnable(mgr, CUDD_REORDER_RANDOM_PIVOT); Index: lpadsld.pl =================================================================== RCS file: /cvsroot/yap/cplint/lpadsld.pl,v retrieving revision 1.8 retrieving revision 1.9 diff -u -r1.8 -r1.9 --- lpadsld.pl 8 Jun 2008 08:38:36 -0000 1.8 +++ lpadsld.pl 8 Jun 2008 18:11:41 -0000 1.9 @@ -21,7 +21,8 @@ if true, both the head and the body of each clause will be grounded, otherwise only the head is grounded. In the case in which the body contains variables not appearing in the head, the body represents an existential event */ - +setting(min_error,0.01). +setting(depth_bound,4). /* end of list of parameters */ /* s(GoalsLIst,Prob) compute the probability of a list of goals @@ -98,6 +99,51 @@ format(user_error,"~nMemory after inference~n",[]), print_mem. +si(GoalsList,ProbL,ProbU,CPUTime):- + statistics(cputime,[_,_]), + setting(depth_bound,D), + solvei(GoalsList,D,ProbL,ProbU), + statistics(cputime,[_,CT]), + CPUTime is CT/1000. + + + +solvei(GoalsList,D,ProbL0,ProbU0):- + (setof(Deriv,find_deriv(GoalsList,D,Deriv),LDup)-> + rem_dup_lists(LDup,[],L), + % print_mem, + separate_ulb(L,[],LL,[],LU), + compute_prob_deriv(LL,ProbL), + compute_prob_deriv(LU,ProbU), + Err is ProbU-ProbL, + setting(min_error,ME), + (Err<ME-> + ProbU0=ProbU, + ProbL0=ProbL + ; + setting(depth_bound,DB), + D1 is D+DB, + solvei(GoalsList,D1,ProbL0,ProbU0) + ) + ; + % print_mem, + ProbL0=0.0, + ProbU0=0.0 + ). + +compute_prob_deriv(LL,ProbL):- + build_formula(LL,FormulaL,[],VarL,0,ConjL), + length(LL,NDL), + length(VarL,NVL), + %format(user_error,"Disjunctions :~d~nConjunctions: ~d~nVariables ~d~n",[NDL,ConjL,NVL]), + var2numbers(VarL,0,NewVarL), + (setting(save_dot,true)-> + % format("Variables: ~p~n",[VarL]), + compute_prob(NewVarL,FormulaL,ProbL,1) + ; + compute_prob(NewVarL,FormulaL,ProbL,0) + ). + print_mem:- statistics(global_stack,[GS,GSF]), statistics(local_stack,[LS,LSF]), @@ -111,6 +157,11 @@ find_deriv(GoalsList,Deriv):- solve(GoalsList,[],DerivDup), remove_duplicates(DerivDup,Deriv). + +find_deriv(GoalsList,DB,Deriv):- + solve(GoalsList,DB,[],DerivDup), + remove_duplicates(DerivDup,Deriv). + /* duplicate can appear in the C set because two different unistantiated clauses may become the same clause when instantiated */ @@ -146,6 +197,55 @@ format(user_error,"~nMemory after inference~n",[]), print_mem. +sci(Goals,Evidence,ProbL,ProbU,CPUTime):- + statistics(cputime,[_,_]), + setting(depth_bound,D), + solve_condi(Goals,Evidence,D,ProbL,ProbU), + statistics(cputime,[_,CT]), + CPUTime is CT/1000. + +solve_condi(Goals,Evidence,D,ProbL0,ProbU0):- + (call_residue(setof(DerivE,find_deriv(Evidence,D,DerivE),LDupE),_R0)-> + rem_dup_lists(LDupE,[],LE), + append(Evidence,Goals,EG), + (call_residue(setof(DerivGE,find_deriv(EG,D,DerivGE),LDupGE),_R1)-> + rem_dup_lists(LDupGE,[],LGE), + separate_ulb(LGE,[],LLGE,[],LUGE), + compute_prob_deriv(LLGE,ProbLGE), + compute_prob_deriv(LUGE,ProbUGE), + separate_ulb(LE,[],LLE,[],LUE), + compute_prob_deriv(LLE,ProbLE), + compute_prob_deriv(LUE,ProbUE), + ProbL is ProbLGE/ProbUE, + (ProbLE=0.0-> + ProbU1=1.0 + ; + ProbU1 is ProbUGE/ProbLE + ), + (ProbU1>1.0-> + ProbU=1.0 + ; + ProbU=ProbU1 + ), + Err is ProbU-ProbL, + setting(min_error,ME), + (Err<ME-> + ProbU0=ProbU, + ProbL0=ProbL + ; + setting(depth_bound,DB), + D1 is D+DB, + solve_condi(Goals,Evidence,D1,ProbL0,ProbU0) + ) + ; + ProbL0=0.0, + ProbU0=0.0 + ) + ; + ProbL0=undefined, + ProbU0=undefined + ). + /* sc(Goals,Evidence,Prob,Time1,Time2) 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 @@ -216,6 +316,11 @@ solve(GoalsList,D,DerivDup), remove_duplicates(DerivDup,Deriv). +find_deriv_GE(LD,GoalsList,DB,Deriv):- + member(D,LD), + solve(GoalsList,DB,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 @@ -295,6 +400,45 @@ find_rule(H,(R,S,N),B,CIn), solve_pres(R,S,N,B,T,CIn,COut). + +solve([],_DB,C,C):-!. + +solve(_G,0,C,[(_,pruned,_)|C]):-!. + +solve([\+ H |T],DB,CIn,COut):-!, + list2and(HL,H), + (setof(D,find_deriv(HL,DB,D),LDup)-> + rem_dup_lists(LDup,[],L), + separate_ulb(L,[],LB,[],UB), + (\+ LB=UB-> + + choose_clauses(CIn,LB,C0), + C1=[(_,pruned,_)|C0] + ; + choose_clauses(CIn,L,C1) + ), + solve(T,DB,C1,COut) + ; + solve(T,DB,CIn,COut) + ). +solve([H|T],DB,CIn,COut):- + builtin(H),!, + call(H), + solve(T,DB,CIn,COut). + +solve([H|T],DB,CIn,COut):- + def_rule(H,B), + append(B,T,NG), + DB1 is DB-1, + solve(NG,DB1,CIn,COut). + +solve([H|T],DB,CIn,COut):- + find_rule(H,(R,S,N),B,CIn), + DB1 is DB-1, + solve_pres(R,S,N,B,T,DB1,CIn,COut). + + + solve_pres(R,S,N,B,T,CIn,COut):- member_eq((N,R,S),CIn),!, append(B,T,NG), @@ -305,6 +449,16 @@ append(B,T,NG), solve(NG,C1,COut). +solve_pres(R,S,N,B,T,DB,CIn,COut):- + member_eq((N,R,S),CIn),!, + append(B,T,NG), + solve(NG,DB,CIn,COut). + +solve_pres(R,S,N,B,T,DB,CIn,COut):- + append(CIn,[(N,R,S)],C1), + append(B,T,NG), + solve(NG,DB,C1,COut). + build_initial_graph(N,G):- listN(0,N,Vert), add_vertices([],Vert,G). @@ -372,6 +526,7 @@ 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). @@ -380,6 +535,7 @@ R\==R1, not_already_present_with_a_different_head(N,R,S,T). + not_different(_N,_N1,S,S1):- S\=S1,!. @@ -415,6 +571,24 @@ impose_dif_cons(R,S,CIn), choose_clauses([(N1,R,S)|CIn],T,COut). +choose_clauses_DB(C,[],C). + +choose_clauses_DB(CIn,[D|T],COut):- + member((N,R,S),D), + ground((N,R,S)), + already_present_with_a_different_head(N,R,S,CIn),!, + choose_a_head(N,R,S,CIn,C1), + choose_clauses_DB(C1,T,COut). + +choose_clauses_DB(CIn,[D|T],COut):- + member((N,R,S),D), + ground((N,R,S)),!, + new_head(N,R,S,N1), + \+ already_present(N1,R,S,CIn), + impose_dif_cons(R,S,CIn), + choose_clauses_DB([(N1,R,S)|CIn],T,COut). + + impose_dif_cons(_R,_S,[]):-!. impose_dif_cons(R,S,[(_NH,R,SH)|T]):-!, @@ -511,6 +685,29 @@ member_subset(E,T). +separate_ulb([],L,L,U,U):-!. +/* +separate_ulb([H|T],L0,L1,U0,[H|U1]):- + member(pruned,H),!, + separate_ulb(T,L0,L1,U0,U1). +*/ +separate_ulb([H|T],L0,[H|L1],U0,[H|U1]):- + ground(H),!, + separate_ulb(T,L0,L1,U0,U1). + +separate_ulb([H|T],L0,L1,U0,[H1|U1]):- + get_ground(H,H1), + separate_ulb(T,L0,L1,U0,U1). + +get_ground([],[]):-!. + +get_ground([H|T],[H|T1]):- + ground(H),!, + get_ground(T,T1). + +get_ground([H|T],T1):- + get_ground(T,T1). + /* predicates for building the formula to be converted into a BDD */ @@ -536,8 +733,12 @@ build_term(D,F,VarIn,Var1), build_formula(TD,TF,Var1,VarOut). + build_term([],[],Var,Var). +build_term([(_,pruned,_)|TC],TF,VarIn,VarOut):-!, + build_term(TC,TF,VarIn,VarOut). + build_term([(N,R,S)|TC],[[NVar,N]|TF],VarIn,VarOut):- (nth0_eq(0,NVar,VarIn,(R,S))-> Var1=VarIn Index: testlpadsld_gbtrue.pl =================================================================== RCS file: /cvsroot/yap/cplint/testlpadsld_gbtrue.pl,v retrieving revision 1.3 retrieving revision 1.4 diff -u -r1.3 -r1.4 --- testlpadsld_gbtrue.pl 4 Dec 2007 18:30:34 -0000 1.3 +++ testlpadsld_gbtrue.pl 8 Jun 2008 18:11:41 -0000 1.4 @@ -21,6 +21,18 @@ TLow<V, V<THigh. +ti:- + format("~nTesting iterative deepening lpadsld.yap~n~n",[]), + files(F), + statistics(runtime,[_,_]), + set(ground_body,true), + format("~nGround body~n~n",[]), + test_filesi(F,ground_body(true)), + statistics(runtime,[_,T]), + T1 is T /1000, + format("Test successful, time ~f secs.~n",[T1]). +ti:- + format("Test unsuccessful.~n",[]). t:- format("~nTesting lpadsld.yap~n~n",[]), @@ -46,6 +58,16 @@ findall(A,test(A,H,GB),L), test_all(H,L), test_files(T,GB). +test_filesi([],_GB). + +test_filesi([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_alli(H,L), + test_filesi(T,GB). test_all(_F,[]). @@ -56,6 +78,16 @@ call(H),!, test_all(F,T). +test_alli(_F,[]). + +test_alli(F,[H|T]):- + copy_term(H,NH), + NH=(s(Q,P),close_to('P',_Prob)), + format("~a ~p.~n",[F,NH]), + si(Q,PL,PU,T),!, + format("Lower bound ~f, Upper bound ~f~n",[PL,PU]), + test_all(F,T). + files([paper_ref_not,paper_ref,female,exapprox,exrange,threesideddice, mendel,student,school_simple,school,coin2,ex,trigger,throws,light]). |