1/* Part of LogicMOO Base Logicmoo Debug Tools
    2% ===================================================================
    3% File '$FILENAME.pl'
    4% Purpose: An Implementation in SWI-Prolog of certain debugging tools
    5% Maintainer: Douglas Miles
    6% Contact: $Author: dmiles $@users.sourceforge.net ;
    7% Version: '$FILENAME.pl' 1.0.0
    8% Revision: $Revision: 1.1 $
    9% Revised At:  $Date: 2002/07/11 21:57:28 $
   10% Licience: LGPL
   11% ===================================================================
   12*/
   13
   14:- module(must_trace,
   15   [
   16      must/1, % Goal must succeed at least once once
   17      must_once/1, % Goal must succeed at most once
   18      must_det/1, % Goal must succeed determistically
   19      sanity/1,  % like assertion but adds trace control
   20      nop/1, % syntactic comment
   21      scce_orig/3,
   22      must_or_rtrace/1
   23    ]).   24
   25:- meta_predicate
   26        must(0),
   27        must_once(0),
   28        must_det(0),
   29        nop(*),
   30        sanity(0),
   31        must_or_rtrace(0),
   32        scce_orig(0,0,0).   33
   34:- set_module(class(library)).   35:- use_module(library(logicmoo_util_common)).   36:- use_module(library(logicmoo_util_startup)).   37
   38:- reexport(library(debug),[debug/3]).   39 
   40% TODO Make a speed,safety,debug Triangle instead of these flags
   41:- create_prolog_flag(runtime_must,debug,[type(term)]).
 must(:Goal) is nondet
Goal must succeed at least once once

Wrap must/1 over parts of your code you do not trust If your code fails.. it will rewind to your entry block (at the scope of this declaration) and invoke rtrace/1 . If there are 50 steps to your code, it will save you from pushing creep 50 times. Instead it turns off the leash to allow you to trace with your eyeballs instead of your fingers.

% must( :Goal) is semidet.

Must Be Successfull.

   58must(Goal):- (Goal*->true;must_0(Goal)).
   59must_0(Goal):- quietly(get_must(Goal,MGoal))-> call(MGoal).
   60
   61must_or_rtrace(P):- call(P) *-> true ; rtrace(P).
 get_must(?Goal, ?CGoal) is semidet
Get Must Be Successfull.
   68get_must(Goal,CGoal):- (skipWrapper ; tlbugger:skipMust),!,CGoal = Goal.
   69get_must(M:Goal,M:CGoal):- must_be(nonvar,Goal),!,get_must(Goal,CGoal).
   70get_must(quietly(Goal),quietly(CGoal)):- current_prolog_flag(runtime_safety,3), !, get_must(Goal,CGoal).
   71get_must(quietly(Goal),CGoal):- !,get_must((quietly(Goal)*->true;Goal),CGoal).
   72get_must(Goal,CGoal):- (tlbugger:show_must_go_on),!,CGoal=must_keep_going(Goal).
   73get_must(Goal,CGoal):- hide_non_user_console,!,get_must_type(rtrace,Goal,CGoal).
   74get_must(Goal,CGoal):- current_prolog_flag(runtime_must,How), How \== none, !, get_must_type(How,Goal,CGoal).
   75get_must(Goal,CGoal):- current_prolog_flag(runtime_debug,2), !, 
   76   (CGoal = (on_x_debug(Goal) *-> true; debugCallWhy(failed(on_f_debug(Goal)),Goal))).
   77get_must(Goal,CGoal):-
   78   (CGoal = (catchv(Goal,E,
   79     ignore_each(((dumpST_error(must_ERROR(E,Goal)), %set_prolog_flag(debug_on_error,true),
   80         rtrace(Goal),nortrace,dtrace(Goal),badfood(Goal)))))
   81         *-> true ; (dumpST,ignore_each(((dtrace(must_failed_F__A__I__L_(Goal),Goal),badfood(Goal))))))).
   82
   83
   84get_must_type(speed,Goal,Goal).
   85get_must_type(warning,Goal,show_failure(Goal)).
   86get_must_type(rtrace,Goal,on_f_rtrace(Goal)).
   87get_must_type(keep_going,Goal,must_keep_going(Goal)).
   88get_must_type(retry,Goal,must_retry(Goal)).
   89get_must_type(How,Goal,CGoal):- 
   90     (How == assertion -> CGoal = (Goal*->true;call(prolog_debug:assertion_failed(fail, must(Goal))));
   91     (How == error ; true ) 
   92       -> CGoal = (Goal*-> true; throw(failed_must(Goal)))).
   93
   94must_retry(Call):- 
   95   (repeat, (catchv(Call,E,(dmsg(E:Call),fail)) *-> true ; 
   96      catch((ignore(rtrace(Call)),leash(+all),visible(+all),
   97        repeat,wdmsg(failed(Call)),trace,Call,fail),'$aborted',true))).
   98
   99must_keep_going(Goal):- set_prolog_flag(debug_on_error,false),
  100  (catch(Goal,E,
  101      xnotrace(((dumpST_error(sHOW_MUST_go_on_xI__xI__xI__xI__xI_(E,Goal)),ignore(rtrace(Goal)),badfood(Goal)))))
  102            *-> true ;
  103              xnotrace(dumpST_error(sHOW_MUST_go_on_failed_F__A__I__L_(Goal))),ignore(rtrace(Goal)),badfood(Goal)).
  104
  105:- '$hide'(get_must/2).  106
  107
  108xnotrace(G):- G,!.
  109:- '$hide'(xnotrace/2).
 sanity(:Goal) is det
Optional Sanity Checking.

like assertion/1 but adds trace control

  118sanity(_):- notrace(current_prolog_flag(runtime_safety,0)),!.
  119% sanity(_):-!.
  120sanity(Goal):- \+ tracing,
  121   \+ current_prolog_flag(runtime_safety,3),
  122   \+ current_prolog_flag(runtime_debug,0),
  123   (current_prolog_flag(runtime_speed,S),S>1),
  124   !,
  125   (1 is random(10)-> must(Goal) ; true).
  126sanity(Goal):- quietly(Goal),!.
  127sanity(_):- break, dumpST,fail.
  128sanity(Goal):- tlbugger:show_must_go_on,!,dmsg(show_failure(sanity,Goal)).
  129sanity(Goal):- setup_call_cleanup(wdmsg(begin_FAIL_in(Goal)),rtrace(Goal),wdmsg(end_FAIL_in(Goal))),!,dtrace(assertion(Goal)).
 must_once(:Goal) is det
Goal must succeed at most once
  135must_once(Goal):- must(Goal),!.
 must_det(:Goal) is det
Goal must succeed determistically
  143% must_det(Goal):- current_prolog_flag(runtime_safety,0),!,must_once(Goal).
  144must_det(Goal):- \+ current_prolog_flag(runtime_safety,3),!,must_once(Goal).
  145must_det(Goal):- must_once(Goal),!.
  146/*
  147must_det(Goal):- must_once((Goal,deterministic(YN))),(YN==true->true;dmsg(warn(nondet_exit(Goal)))),!.
  148must_det(Goal):- must_once((Goal,deterministic(YN))),(YN==true->true;throw(nondet_exit(Goal))).
  149*/
 nop(:Goal) is det
Comments out code without losing syntax
  155nop(_).
  156
  157
  158/*
  159scce_orig(Setup,Goal,Cleanup):-
  160   \+ \+ '$sig_atomic'(Setup), 
  161   catch( 
  162     ((Goal, deterministic(DET)),
  163       '$sig_atomic'(Cleanup),
  164         (DET == true -> !
  165          ; (true;('$sig_atomic'(Setup),fail)))), 
  166      E, 
  167      ('$sig_atomic'(Cleanup),throw(E))). 
  168
  169:- abolish(system:scce_orig,3).
  170
  171
  172[debug]  ?- scce_orig( (writeln(a),trace,start_rtrace,rtrace) , (writeln(b),member(X,[1,2,3]),writeln(c)), writeln(d)).
  173a
  174b
  175c
  176d
  177X = 1 ;
  178a
  179c
  180d
  181X = 2 ;
  182a
  183c
  184d
  185X = 3.
  186
  187
  188*/
  189
  190scce_orig(Setup0,Goal,Cleanup0):-
  191  xnotrace((Cleanup = notrace('$sig_atomic'(Cleanup0)),Setup = xnotrace('$sig_atomic'(Setup0)))),
  192   \+ \+ Setup, !,
  193   (catch(Goal, E,(Cleanup,throw(E)))
  194      *-> (notrace(tracing)->(notrace,deterministic(DET));deterministic(DET)); (Cleanup,!,fail)),
  195     Cleanup,
  196     (DET == true -> ! ; (true;(Setup,fail))).
  197      
  198/*
  199scce_orig(Setup,Goal,Cleanup):-
  200   \+ \+ '$sig_atomic'(Setup), 
  201   catch( 
  202     ((Goal, deterministic(DET)),
  203       '$sig_atomic'(Cleanup),
  204         (DET == true -> !
  205          ; (true;('$sig_atomic'(Setup),fail)))), 
  206      E, 
  207      ('$sig_atomic'(Cleanup),throw(E))). 
  208*/
  209
  210:- ensure_loaded(library('first')).  211:- ensure_loaded(library('ucatch')).  212:- ensure_loaded(library('dmsg')).  213:- ensure_loaded(library('rtrace')).  214:- ensure_loaded(library('bugger')).  215:- ensure_loaded(library('dumpst')).  216:- ensure_loaded(library('frames')).  217
  218
  219
  220:- ignore((source_location(S,_),prolog_load_context(module,M),module_property(M,class(library)),
  221 forall(source_file(M:H,S),
  222 ignore((functor(H,F,A),
  223  ignore(((\+ atom_concat('$',_,F),(export(F/A) , current_predicate(system:F/A)->true; system:import(M:F/A))))),
  224  ignore(((\+ predicate_property(M:H,transparent), module_transparent(M:F/A), \+ atom_concat('__aux',_,F),debug(modules,'~N:- module_transparent((~q)/~q).~n',[F,A]))))))))).