2is_sicstus:- \+ current_prolog_flag(version_data,swi(_,_,_,_)).
    3
    4?- is_sicstus -> prolog_flag(single_var_warnings,_,off) ; true.    5
    6?- is_sicstus -> ensure_loaded(ec_common_sicstus) ; ensure_loaded(ec_common_swi).    7
    8:- style_check(-singleton).    9/* Emulates the writenl(1) function */
   10
   11% =========================================
   12% Axiom Access
   13% =========================================
   14
   15:- module_transparent(ec_current_domain/1).   16:- export(ec_current_domain/1).   17:- system:import(ec_current_domain/1).   18
   19:- module_transparent(ec_current_domain_bi/1).   20:- export(ec_current_domain_bi/1).   21:- system:import(ec_current_domain_bi/1).   22
   23:- module_transparent(ec_current_domain_db/1).   24:- export(ec_current_domain_db/1).   25:- system:import(ec_current_domain_db/1).   26
   27:- module_transparent(user:ec_current_domain_db/2).   28:- dynamic(user:ec_current_domain_db/2).   29:- export(user:ec_current_domain_db/2).   30:- system:import(user:ec_current_domain_db/2).   31
   32
   33:- module_transparent(system:axiom/2).   34system:axiom(X,Y):- ec_current_domain_bi(axiom(X,Y)).
   35:- lock_predicate(system:axiom/2).   36
   37:- module_transparent(system:abducible/1).   38system:abducible(A):- ec_current_domain_bi(abducible(A)).
   39:- lock_predicate(system:abducible/1).   40
   41:- module_transparent(system:executable/1).   42system:executable(A):- ec_current_domain_bi(executable(A)).
   43:- lock_predicate(system:executable/1).   44
   45
   46:- reexport(library(ec_planner/ec_loader)).   47
   48ec_predicate_template(Var):- ec_current_domain(predicate(Pred)), functor(Pred,F,A), functor(Var,F,A).
   49
   50ec_current_domain(Var):- notrace(var(Var)),!,ec_predicate_template(Var),ec_current_domain(Var).
   51ec_current_domain(Var):- ec_current_domain_bi(Var).
   52%ec_current_domain(Var):- ec_current_domain_db(Var).
   53
   54ec_current_domain_bi(Var):- notrace(var(Var)),!, throw(ec_current_domain_var(Var)).
   55%ec_current_domain_bi(axiom(G,Gs)):- !, axiom(G,Gs).
   56ec_current_domain_bi(G):- ec_current_domain_db(G).
   57ec_current_domain_bi(executable(G)):- var(G), ec_current_domain_bi(event(Ax)), functor(G,F,A), functor(Ax,F,A).
   58ec_current_domain_bi(executable(G)):- compound(G), functor(G,F,A), functor(Ax,F,A), ec_current_domain_bi(event(Ax)).
   59
   60ec_current_domain_db(G):- user:ec_current_domain_db(G, _REF).
   61:- lock_predicate(ec_current_domain_db/1).   62 
   63
   64% =========================================
   65% Test Decls
   66% =========================================
   67
   68fail_solve_goal(G,R):- \+ abdemo_solve(G,R).
   69
   70:- export(ec_prove/1).   71ec_prove(G):-
   72  abdemo_solve(G,_).
   73
   74:- export(abdemo_solve/2).   75abdemo_solve(Gs,R):- abdemo_solve(Gs,R,1,4).
   76:- export(abdemo_solve/4).   77abdemo_solve(Gs,R,H,L):- 
   78  When = now,
   79  must(fix_goal(When,Gs,Gs0)), !,
   80  must(fix_time_args(When,Gs0,Gss)), !,  
   81  dbginfo(all, [nl,realGoal=Gss,nl]),
   82  abdemo_special(depth(H,L), Gss, R).
   83
   84:- meta_predicate test_body(*,0,*,*).   85test_body(N,(Was=G,Body),Info,Vs):- Was==N,!, copy_term(G,NewN),!,Was=G, test_body(NewN,(Body),Info,Vs).
   86test_body(N,true,Info,Vs):- !, test_body(N,abdemo_solve(N,R),Info,['R'=R|Vs]).
   87test_body(N,Body,Info,Vs):-
   88   dbginfo(verbose, nl(2)),
   89   dbginfo(verbose, [Info,nl(1)]),
   90   %dbginfo(all,['body'=Body,nl(2)]),
   91   % copy_term(Body,BodyA),
   92   maybe_nl, write('START OUTPUT of '), write(N), write(' >>>>>'),
   93   maybe_nl, 
   94   ticks(Z1),   
   95   (call(Body)-> (Passed = true) ; Passed = '?!?!??!FAILED!?!?!?'),
   96   ticks(Z2), TotalTime is (Z2-Z1)/1000, 
   97   maybe_nl, write('<<<<< ENDOF OUTPUT of '), write(N),nl,
   98   dbginfo(verbose, nl(2)),
   99   % dbginfo(all,['bodyAgain'=BodyA, nl, nl, Vs]),
  100   dbginfo(all,Vs),
  101   maybe_nl, nl, 
  102   (Passed == true -> ansi_format(fg(cyan),'!!!PASSED!!! ~w time=~w',[N,TotalTime]) ;
  103     (ansi_format(hfg(red),'~p ~w time=~w',[Passed,N,TotalTime]),sleep(1.0))),
  104   nl,
  105   dbginfo(verbose, nl(2)).
  106
  107run_tests:- 
  108  clause_w_names(do_test(N),Body,_Ref,File,Vs),
  109  once(test_body(N,Body,File,Vs)),
  110  fail.
  111run_tests:- current_prolog_flag(debug,false) -> halt(7) ; true.
  112:- export(run_tests/0).  113
  114% =========================================
  115% Debug Info
  116% =========================================
  117
  118:- use_module('./ec_reader').  119
  120:- set_ec_option(verbose, all).  121:- set_ec_option(extreme, false).  122:- set_ec_option(debug, failure).  123
  124is_dbginfo(N):- var(N),!, fail.
  125is_dbginfo(N=V):- !, etmp:ec_option(N, V).
  126is_dbginfo(not(N)):- !, \+ is_dbginfo(N).
  127is_dbginfo(N):- is_list(N), !, maplist(is_dbginfo,N).
  128is_dbginfo(N):- etmp:ec_option(N, false),!,fail.
  129is_dbginfo(N):- etmp:ec_option(verbose, N),!.
  130
  131
  132maybe_nl:- notrace(format('~N',[])).
  133
  134dbginfo(NV, G):- notrace(tracing), !,notrace,dbginfo(NV, G),notrace(trace).
  135dbginfo(NV, G):- \+ is_dbginfo(NV) -> true ; dbginfo(G). 
  136:- export(dbginfo/1).  137dbginfo_else(NV,G,E):- is_dbginfo(NV) -> dbginfo(G); dbginfo(E).
  138
  139:- meta_predicate catch_ignore(0).  140catch_ignore(G):- ignore(catch(G,E,wdmsg(E))),!.
  141
  142dbginfo(G):- notrace(tracing),!,notrace,dbginfo(G),notrace(trace).
  143dbginfo(Var):- var(Var),!, maybe_nl, format('ListVAR = ~p~n',[Var]).
  144dbginfo([]):- !, maybe_nl. 
  145dbginfo(call(G)):- !, catch_ignore(G).
  146dbginfo({G}):- !, maybe_nl, catch_ignore(G).
  147dbginfo([A|B]):- !, maybe_nl, dbginfo(A), maybe_nl, dbginfo(B),!.
  148dbginfo(N=V):- !, maybe_nl, catch_ignore(portray_clause(var(N):-V)).
  149dbginfo(nl):- !, maybe_nl, nl.
  150dbginfo(nl(N)):- !, maybe_nl, catch_ignore(forall(between(0,N,_),nl)).
  151dbginfo(fmt(F,A)):- !, catch_ignore(format(F,A)).
  152dbginfo(afmt(Ansi,F,A)):- !, catch_ignore(ansi_format(Ansi,F,A)).
  153dbginfo(NV):- catch_ignore(portray_clause(:- NV)), !.
  154:- export(dbginfo/1).  155
  156
  157% =========================================
  158% Plan Portrayal
  159% =========================================
  160
  161write_plan_len(A,B):- length(A,AL), length(B,BL),write_plan(AL,BL).
  162write_plan(HA,BA):- write('Plan: '), write(HA), write('-'), write(BA), write('    ').
  163/* Emulates the writenl(1) function */
  164
  165%writeNoln(A) :-  write(A),!.
  166writeNoln(_).
  167
  168writenl(_).
  169
  170writeYesln(_)