/* output commands for acl1_1.pl version 1 */ title(File,FileOut,Stream):- max_spec_steps(Spec), der_depth(Der), beamsize(B), ver(V), verbosity(Ver), verapp(Vapp), min_cov(MC), stopping_acc(A), format(Stream,"~N/*~NM-ACL ver ~a AbdProofProc. ver ~a~N\c Input file: ~a, Output file: ~a~N", [V,Vapp,File,FileOut]), format(Stream,"Max spec steps=~w, Beamsize=~w, Derivation depth=~w,\c Verbosity=~w, ~NMin cov=~w, Accuracy stopping threshold=~3f~N", [Spec,B,Der,Ver,MC,A]), eplus(Eplus), length(Eplus,Np), eminus(Eminus), length(Eminus,Nm), format(Stream,"~w positive examples, ~w negative examples~N*/~N", [Np,Nm]). print_number_neg(Eminus):- length(Eminus,L), verbosity(V), V>0, format("Negative examples: ~w~N",[L]). print_list([],_Stream):-!. print_list([[Cl,Np,Npa,Nm,Nma,Epc,Epac,Emac,NewDelta]|T],Stream):- print_list(T,Stream), format(Stream," ~N",[]), print_clause(Stream,Cl,yes,yes,Np,Npa,Nm,Nma,Epc,Epac,Emac,NewDelta). print_new_clause(Cl,GC,LC,Np,Npa,Nm,Nma, Epc,Epac,Emac,NewDelta):- verbosity(V), V>0, format(" ~N ~NGenerated Clause:~N",[]), print_clause(user_output,Cl,GC,LC,Np,Npa,Nm,Nma,Epc,Epac,Emac,NewDelta), (V>3-> get0(_) ; true ). print_clause(Stream,rule(H,B,Name),GC,LC,_Np,_Npa,_Nm,_Nma, Epc,Epac,Emac,NewDelta):- print_single_clause(Stream,H,B), format(Stream,"/* Name: ~a GC: ~a, LC: ~a \c ~NCovered positive examples: ~p~N\c Covered positive abduced examples: ~p~N\c Covered negative abduced examples: ~p~N\c Abduced literals: ~p */~N ~N", [Name,GC,LC, Epc,Epac,Emac,NewDelta]). print_single_clause(Stream,H,B):- list2and(B,Ba), writevars(Stream,(H:-Ba)),write(Stream,'.'),nl(Stream). print_backtracked_clauses(Stream):- findall(Clause,backtracked(Clause),L), format(Stream,"/* Backtracked clauses ~N",[]), print_list_backtracked(L,Stream), format(Stream," ~N*/~N",[]). print_list_backtracked([],_Stream):-!. print_list_backtracked([rule(H,B,Name)|T],Stream):- print_list(T,Stream), format(Stream," ~N",[]), format(Stream,"~a: ",[Name]), print_single_clause(Stream,H,B). print_ex_rem(Eplus,EplusA,Eminus):- verbosity(V), V>0, format("Current training set~N",[]), length(Eplus,Lp), format("Positive examples: N+ =~w~NE+ =~p~N~N",[Lp,Eplus]), length(EplusA,LpA), format("Abduced positive examples: Na+=~w~NEa+=~p~N~N",[LpA,EplusA]), length(Eminus,Lm), format("Abduced negative examples: Na-=~w~NEa-=~p~N~N",[Lm,Eminus]). print_agenda([]):-!, verbosity(V), (V>3-> get0(_) ; true ). print_agenda([H|T]):- format("[~p,~3f,~a,~a,~w,~w,~w,~w,~i]~N",H), print_agenda(T). print_max_spec_steps(Nmax):- verbosity(V), V>1, format("Reached the max number ~w of specializing steps~N",[Nmax]). print_refinements:- verbosity(V), V>1, format(" ~NRefinements added to agenda: ~N",[]). print_spec_step(N):- verbosity(V), V>1, format(" ~NSpecializing step n.~w.",[N]). print_current_agenda(Agenda):- verbosity(V), V>2, format(" ~NCurrent Agenda:~N",[]), print_agenda(Agenda). print_refinement([rule(H,B1,Name),Value,GC,LC,Np,Npa,Nm,Nma]):- verbosity(V), V>1, format("[~p,~3f,~a,~a,~w,~w,~w,~w]~N", [rule(H,B1,Name),Value,GC,LC,Np,Npa,Nm,Nma]). print_loc_cons(Cl,Value):- verbosity(V), V>1, format("New locally consistent clause found:~N\c ~p Value=~w",[Cl,Value]). print_backtracking(ClauseList):- verbosity(V), V>0, format("Backtracking: retracting clauses~N",[]), print_bkt_cl(ClauseList). print_bkt_cl([]):- format(" ~N",[]). print_bkt_cl([N|T]):- rule(H,B,N,Epa,Emc), format("~p~N",[rule(H,B,N,Epa,Emc)]), print_bkt_cl(T). writevars(Stream,X) :- freshcopy(X,Y), numbervars(Y,0,_L), write(Stream,Y). % freshcopy(+X,-Y) % get a copy of term X with fresh variables freshcopy(X,Y) :- assert(newcopy(X)), retract(newcopy(Y)), !.