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% File: /opt/PrologMUD/pack/logicmoo_base/prolog/logicmoo/util/logicmoo_util_catch.pl
   15:- module(ucatch,[]).   16
   17:- define_into_module(
   18          [ !/1,
   19            addLibraryDir/0,
   20            get_main_error_stream/1,
   21            get_thread_current_error/1,
   22            source_variables_l/1,
   23            as_clause_no_m/3,
   24            as_clause_w_m/4,
   25            as_clause_w_m/5,
   26            source_module/1,
   27            bad_functor/1,
   28            main_self/1,
   29            set_main_error/0,
   30            find_main_eror/1,
   31            call_each/2,
   32            set_mains/0,
   33            current_why/1,
   34            thread_self_main/0,
   35            badfood/1,
   36            unsafe_safe/2,
   37            % quietly/1,
   38            doall_and_fail/1,
   39            quietly_must/1,
   40            on_x_f/3,
   41
   42            keep_going/0,keep_going0/0,
   43            must/1,
   44            show_current_source_location/0,
   45            varnames_load_context/1,
   46            current_mfl4/4,
   47            current_source_location/2,
   48            hide_trace/1,
   49            (block)/2,
   50            (block3)/3,
   51            with_current_why/2,
   52            %bubbled_ex/1,
   53            %bubbled_ex_check/1,
   54            catchv/3,
   55            flag_call/1,
   56            flag_call0/1,
   57            current_source_file/1,current_source_location0/2,
   58            lmcache:current_main_error_stream/1,
   59            lmcache:thread_current_input/2,
   60            dbgsubst/4,
   61            dbgsubst0/4,
   62            ddmsg/1,
   63            ddmsg/2,
   64            ddmsg_call/1,
   65            det_lm/2,
   66            dif_safe/2,
   67            dumpST_error/1,
   68            errx/0,
   69            format_to_error/2,
   70            fresh_line_to_err/0,
   71            functor_catch/3,
   72            functor_safe/3,
   73            
   74            ib_multi_transparent33/1,
   75            if_defined/1,if_defined/2,
   76            input_key/1,
   77            is_ftCompound/1,%ftCompound/1, 
   78            not_ftCompound/1,
   79            is_ftNameArity/2,
   80            is_ftNonvar/1, % ftNonvar/1,ftVar/1,
   81            is_ftVar/1,
   82
   83            is_main_thread/0,
   84            is_pdt_like/0,
   85            is_release/0,
   86            need_speed/0,
   87            allow_unsafe_code/0,
   88            keep/2,
   89            loading_file/1,
   90            on_x_log_throw/1,
   91            %on_x_log_throwEach/1,
   92            on_x_log_cont/1,
   93            on_x_log_fail/1,
   94            skip_failx_u/1,
   95            on_xf_log_cont/1,
   96            on_xf_log_cont_l/1,
   97            maplist_safe/2,
   98            maplist_safe/3,
   99            module_functor/4,
  100
  101            trace_or_throw/1,
  102            trace_or_throw/1,
  103
  104            %must/1,
  105            must2/2,
  106            must_det_u/1,
  107            %must_det_dead/2,
  108            must_l/1,
  109
  110            must_det_l/1,
  111            must_det_l_pred/2,
  112            call_must_det/2,
  113            call_each_det/2,
  114            p_call/2,
  115
  116            nd_dbgsubst/4,
  117            nd_dbgsubst1/5,
  118            nd_dbgsubst2/4,
  119
  120            not_is_release/0,
  121            one_must/2,
  122            one_must_det/2,
  123            % sanity/1,
  124            sanity2/2,
  125            save_streams/0,
  126            save_streams/1,
  127            set_block_exit/2,
  128            showHiddens/0,
  129            show_new_src_location/1,
  130            show_new_src_location/2,
  131            show_source_location/0,
  132            skipWrapper/0,
  133            slow_sanity/1,
  134            strip_arity/3,
  135            strip_f_module/2,
  136            get_thread_current_error/1,
  137            throwNoLib/0,
  138            to_m_f_arity_pi/5,
  139            to_mpi_matcher/2,
  140            to_pi0/3,
  141            warn_bad_functor/1,
  142            when_defined/1,
  143            with_main_error_to_output/1,
  144            with_current_io/1,
  145            with_error_to_main/1,
  146            with_dmsg_to_main/1,
  147            with_main_input/1,
  148            with_main_io/1,
  149            with_preds/6,
  150            without_must/1,
  151            hide_non_user_console/0,
  152            y_must/2,
  153            vsubst/4,
  154            must_find_and_call/1
  155
  156
  157          ]).  158
  159%:- include(ucatch).
  160:- include(first).  161
  162
  163:- thread_local tlbugger:show_must_go_on/1.  164
  165keep_going:- notrace(keep_going0).
  166
  167keep_going0:- getenv(keep_going,'-k').
  168keep_going0:- non_user_console.
  169keep_going0:- tlbugger:show_must_go_on(X)->X==true,!.
  170keep_going0:- current_prolog_flag(runtime_must,keep_going),!.
  171%keep_going0:- current_prolog_flag(debug_on_error,true), !, fail.
  172
  173
  174% % % OFF :- system:use_module((dmsg)).
  175% % % OFF :- system:use_module(library(must_sanity)).
  176
  177vsubst(In,B,A,Out):-var(In),!,(In==B->Out=A;Out=In).
  178vsubst(In,B,A,Out):-subst(In,B,A,Out).
  179
  180% % % % OFF :- system:use_module(logicmoo_util_prolog_streams).
  181:- thread_self(Goal),assert(lmcache:thread_main(user,Goal)).  182
  183main_self(main).
  184main_self(W):-atom(W),atom_concat('pdt_',_,W),!.
  185main_self(W):-atom(W),atom_concat('client',_,W),!.
  186main_self(W):-lmcache:thread_main(user,W),!.
  187
  188thread_self_main:- notrace((thread_self(W),!,main_self(W))).
 hide_non_user_console is semidet
Not User Console.
  194hide_non_user_console:-thread_self_main,!,fail.
  195hide_non_user_console:-current_input(In),stream_property(In,tty(true)),!,fail.
  196hide_non_user_console:-current_prolog_flag(debug_threads,true),!,fail.
  197hide_non_user_console:-current_input(In),stream_property(In, close_on_abort(true)).
  198hide_non_user_console:-current_input(In),stream_property(In, close_on_exec(true)).
  199
  200
  201
  202
  203/*
  204:- if(\+ current_predicate(system:nop/1)).
  205:- user:ensure_loaded(logicmoo_util_supp).
  206:- endif.
  207*/
  208
  209
  210:- meta_predicate
  211
  212
  213		block3(+, :, ?),
  214		catchv(0, ?, 0),
  215
  216		if_defined(:),
  217		if_defined(+, 0),
  218		ddmsg_call(0),
  219
  220                on_xf_log_cont(0),
  221
  222		skip_failx_u(0),
  223		on_xf_log_cont_l(0),
  224		on_x_log_throw(0),
  225                with_current_why(*,0),
  226                with_only_current_why(*,0),
  227
  228
  229		on_x_log_cont(0),
  230		on_x_log_fail(0),
  231
  232
  233        % must(0),
  234        must2(+,0),
  235        must_find_and_call(0),
  236        must_det_u(0),
  237        %must_det_dead(0, 0),
  238
  239        must_det_l(0),
  240        must_det_l_pred(1,+),
  241        call_must_det(1,+),       
  242        call_each_det(1,+),
  243        call_each(1,+),
  244        p_call(*,+),
  245
  246        must_l(0),
  247        one_must(0, 0),
  248        one_must_det(0, 0),
  249        unsafe_safe(0,0),
  250        % sanity(0),
  251        sanity2(+,0),
  252        slow_sanity(0),
  253        to_mpi_matcher(?, ?),
  254        when_defined(:),
  255        with_main_error_to_output(0),
  256        with_current_io(0),
  257        with_dmsg_to_main(0),
  258        with_error_to_main(0),
  259        with_main_input(0),
  260        with_main_io(0),
  261        with_preds(?, ?, ?, ?, ?, 0),
  262        without_must(0),
  263        %on_x_log_throwEach(0),
  264        y_must(?, 0).  265
  266:- module_transparent
  267        !/1,
  268        addLibraryDir/0,
  269        as_clause_no_m/3,
  270        as_clause_w_m/4,
  271        as_clause_w_m/5,
  272        bad_functor/1,
  273        badfood/1,
  274        (block)/2,
  275        %bubbled_ex/1,
  276        %bubbled_ex_check/1,
  277        current_source_file/1,
  278        lmcache:current_main_error_stream/1,
  279        dbgsubst/4,
  280        dbgsubst0/4,
  281        ddmsg/1,
  282        ddmsg/2,
  283        det_lm/2,
  284        dif_safe/2,
  285        errx/0,
  286        format_to_error/2,
  287        fresh_line_to_err/0,
  288        functor_catch/3,
  289        functor_safe/3,
  290        with_current_why/2,
  291        ib_multi_transparent33/1,
  292        input_key/1,
  293        is_ftCompound/1,
  294        not_ftCompound/1,
  295        is_ftNameArity/2,
  296        is_ftNonvar/1,
  297        is_ftVar/1,
  298        is_main_thread/0,
  299        is_pdt_like/0,
  300        is_release/0,
  301        keep/2,
  302        loading_file/1,
  303        %on_x_log_throwEach/1,
  304        maplist_safe/2,
  305        maplist_safe/3,
  306        module_functor/4,
  307
  308        nd_dbgsubst/4,
  309        nd_dbgsubst1/5,
  310        nd_dbgsubst2/4,
  311        not_is_release/0,
  312        save_streams/0,
  313        save_streams/1,
  314        set_block_exit/2,
  315        showHiddens/0,
  316        show_new_src_location/1,
  317        show_new_src_location/2,
  318
  319            on_xf_log_cont/1,
  320            on_xf_log_cont_l/1,
  321            skip_failx_u/1,
  322            p_call/2,
  323
  324        show_source_location/0,
  325        skipWrapper/0,
  326        skipWrapper0/0,
  327        strip_arity/3,
  328        strip_f_module/2,
  329        get_thread_current_error/1,
  330        throwNoLib/0,
  331        to_m_f_arity_pi/5,
  332        to_pi0/3,
  333        warn_bad_functor/1.  334
  335:- meta_predicate
  336   doall_and_fail(0),
  337   quietly_must(0).  338
  339:- set_module(class(library)).  340
  341%:- prolog_listing:use_module(library(listing)).
  342
  343:- use_module(library(occurs)).  344:- use_module(library(gensym)).  345:- use_module(library(when)).  346
  347
  348:- use_module(library(backcomp)).  349:- use_module(library(debug)).  350:- use_module(library(occurs)).  351:- use_module(library(check)).  352:- use_module(library(edinburgh)).  353:- use_module(library(debug)).  354:- use_module(library(prolog_stack)).  355:- use_module(library(make)).  356
  357
  358% :- use_module(library(gui_tracer)).
  359:- use_module(library(system)).  360:- use_module(library(socket)).  361:- use_module(library(readutil)).  362:- abolish(system:time/1).  363:- use_module(library(statistics)).  364:- use_module(library(codesio)).  365:- use_module(library(charsio)).  366:- use_module(library(ssl)).  367:- use_module(library(prolog_codewalk)).  368:- use_module(library(prolog_source)).  369:- use_module(library(date)).  370%:- use_module(library(editline)).
  371%:- system:use_module(library(listing)).
  372%:- unload_file(library(listing)).
  373:- multifile(prolog_listing:or_layout/1).  374:- dynamic(prolog_listing:or_layout/1).  375:- multifile(prolog_listing:clause_term/4).  376:- dynamic(prolog_listing:clause_term/4).

logicmoo_util_catch - catch-like bocks

Tracer modes:

quietly/1 - turn off tracer if already on but still dtrace on failure must/1 - dtrace on failure rtrace/1 - non interactive debug sanity/1 - run in quietly/1 when problems were detected previously otherwise skippable slow_sanity/1+hide_trace/1 assertion/1 - throw on failure hide_trace/1 - hide dtrace temporarily slow_sanity/1 - skip unless in developer mode

*/

  394:- thread_local( tlbugger:old_no_repeats/0).  395:- thread_local( tlbugger:skip_bugger/0).  396:- thread_local( tlbugger:dont_skip_bugger/0).  397
  398:-meta_predicate(skip_failx_u(*)).  399skip_failx_u(G):- must_det_l(G).
  400% skip_failx_u(G):-call_each_det([baseKB:call_u,on_xf_log_cont,notrace],G).
  401
  402
  403
  404%=
 is_pdt_like is semidet
If Is A Pdt Like.
  410is_pdt_like:-thread_property(_,alias(pdt_console_server)).
  411is_pdt_like:-lmcache:thread_main(user,Goal),!,Goal \= main.
  412
  413
  414%=
 is_main_thread is semidet
If Is A Main Thread.
  420is_main_thread:-lmcache:thread_main(user,Goal),!,thread_self(Goal).
  421is_main_thread:-thread_self_main,!.
  422
  423:- thread_local(tlbugger:no_colors/0).  424:- thread_local(t_l:thread_local_error_stream/1).  425:- volatile(t_l:thread_local_error_stream/1).  426
  427:- is_pdt_like-> assert(tlbugger:no_colors); true.  428
  429
  430% = :- meta_predicate(with_main_error_to_output(0)).
  431
  432%=
 with_main_error_to_output(:Goal) is semidet
Using Main Error Converted To Output.
  438with_main_error_to_output(Goal):-
  439 current_output(Out),
  440  locally_tl(thread_local_error_stream(Out),Goal).
  441
  442
  443with_current_io(Goal):-
  444  current_input(IN),current_output(OUT),get_thread_current_error(Err),
  445  scce_orig(set_prolog_IO(IN,OUT,Err),Goal,set_prolog_IO(IN,OUT,Err)).
  446
  447:- thread_local(t_l:hide_dmsg/0).  448
  449% with_no_output(Goal):- !, Goal.
  450with_no_output(Goal):-
  451 locally_tl(hide_dmsg,
  452  with_output_to(string(_), 
  453     with_some_output_to(main_error,
  454      current_output,
  455       with_user_error_to(current_output,
  456        locally_tl(thread_local_error_stream(current_output),
  457         with_user_output_to(current_output, 
  458          with_dmsg_to_main(Goal))))))).
  459
  460with_user_error_to(Where,Goal):-
  461  with_some_output_to(user_error,Where,Goal).
  462
  463with_user_output_to(Where,Goal):-
  464  with_some_output_to(user_output,Where,Goal).
  465
  466into_stream_alias(Some,Alias):- into_stream(Some,S),stream_property(S,alias(Alias)),!.
  467into_stream_alias(Some,Some).
  468
  469with_some_output_to(SomeAlias,Where,Goal):- 
  470   into_stream_alias(SomeAlias,Alias), 
  471   with_alias_output_to(Alias,Where,Goal).
  472
  473with_alias_output_to(Alias,Where,Goal):- 
  474   stream_property(ErrWas,alias(Alias)),
  475   new_memory_file(MF), open_memory_file(MF,write,Stream),
  476   scce_orig(set_stream(Stream,alias(Alias)),Goal,set_stream(ErrWas,alias(Alias))),
  477   close(Stream),
  478   memory_file_to_string(MF,Data),
  479   with_output_to(Where,write(Data)).
  480
  481
  482
  483with_dmsg_to_main(Goal):-
  484  get_main_error_stream(Err),
  485   locally_tl(thread_local_error_stream(Err),Goal).
  486
  487with_error_to_main(Goal):-
  488  get_main_error_stream(Err),current_error_stream_ucatch(ErrWas),Err==ErrWas,!,Goal.
  489with_error_to_main(Goal):- 
  490  get_main_error_stream(Err),current_error_stream_ucatch(ErrWas),
  491   locally_tl(thread_local_error_stream(Err),
  492   scce_orig(set_stream(Err,alias(user_error)),Goal,set_stream(ErrWas,alias(user_error)))).
 set_thread_current_error(Id, ?Err) is det
Thread Current Error Stream.
  502set_thread_error_stream(Id,Err):-
  503   ( \+ atom(Err)->asserta_new(lmcache:thread_current_error_stream(Id,Err));true),
  504   (thread_self(Id)->asserta(t_l:thread_local_error_stream(Err));true).
 get_thread_current_error(?Err) is det
Thread Current Error Stream.
  511:- export(get_thread_current_error/1).  512get_thread_current_error(Err):- t_l:thread_local_error_stream(Err),!.
  513get_thread_current_error(Err):- thread_self(ID),lmcache:thread_current_error_stream(ID,Err),!.
  514get_thread_current_error(Err):- !,Err=user_error.
  515get_thread_current_error(Err):- stream_property(user_error,file_no(F)),\+ stream_property(main_error,file_no(F)),!,Err=user_error.
  516get_thread_current_error(Err):- get_thread_current_error0(Err),!.
  517get_thread_current_error(Err):- get_main_error_stream(Err),!.
  518
  519get_thread_current_error0(Err):- get_thread_user_error1(Err),stream_property(Err,file_no(FileNo)),FileNo>2,!.
  520get_thread_current_error0(Err):- get_thread_user_error1(Err),!.
  521
  522get_thread_user_error1(Err):- get_thread_user_error2(user_error,Err).
  523% get_thread_user_error1(Err):- get_thread_user_error2(Err,Err).
  524get_thread_user_error1(Err):- get_thread_user_error2(current_error,Err).
  525
  526get_thread_user_error2(ErrName,Err):- nonvar(ErrName),
  527   stream_property(ErrName,file_no(FileNo)),
  528   stream_property(ErrName,output),FileNo\==2,
  529   current_output(Out),stream_property(Out,file_no(FileNo)),
  530   stream_property(Err,file_no(FileNo)),\+ current_input(Err).
  531get_thread_user_error2(ErrName,Err):-
  532   current_output(Out),stream_property(Out,file_no(FileNo)),
  533   stream_property(Err,file_no(FileNo)),
  534   stream_property(Err,output),FileNo\==2,
  535   ignore((stream_property(Err,alias(ErrName)))),ignore((Err=ErrName)).
  536get_thread_user_error2(ErrName,Err):- nonvar(ErrName), stream_property(Err,alias(ErrName)),stream_property(Err,output),!.
 get_main_error_stream(?Err) is det
Current Main Error Stream.
  544get_main_error_stream(Err):- stream_property(Err,alias(main_error)),!.
  545get_main_error_stream(Err):- lmcache:thread_main(user,ID),lmcache:thread_current_error_stream(ID,Err),!.
  546get_main_error_stream(Err):- stream_property(Err,file_no(2)),!.
  547get_main_error_stream(Err):- stream_property(Err,alias(user_error)),!.
  548get_main_error_stream(Err):- thread_call_blocking_one(main,get_thread_current_error(Err)).
  549
  550thread_call_blocking_one(Thread,G):- thread_self(Self),
  551  thread_signal(Thread,
  552   catch(( (G,deterministic(YN),true) 
  553    -> thread_send_message(Self,thread_call_blocking_one(Thread,G,fail,true))
  554     ; thread_send_message(Self,thread_call_blocking_one(Thread,G,true,YN))),
  555     E,thread_send_message(Self,thread_call_blocking_one(Thread,G,throw(E),true)))),
  556   thread_get_message(thread_call_blocking_one(Thread,G,TF,_R)),!,call(TF).
  557
  558
  559%=
 format_to_error(?F, ?A) is semidet
Format Converted To Error.
  565format_to_error(F,A):-F==error,!,format_to_error('~q',A).
  566format_to_error(F,A):- \+ is_list(A),!,format_to_error(F,[A]).
  567format_to_error(F,A):-get_thread_current_error(Err),!,format(Err,F,A).
  568
  569%=
 fresh_line_to_err is semidet
Fresh Line Converted To Err.
  575fresh_line_to_err:- zotrace((flush_output_safe,get_thread_current_error(Err),format(Err,'~N',[]),flush_output_safe(Err))).
  576
  577:- dynamic(lmcache:thread_current_input/2).  578:- volatile(lmcache:thread_current_input/2).  579
  580:- dynamic(lmcache:thread_current_error_stream/2).  581:- volatile(lmcache:thread_current_error_stream/2).  582
  583%=
 save_streams is semidet
Save Streams.
  589save_streams:- thread_self(ID),save_streams(ID),!.
  590
  591set_mains:-
  592       stream_property(In, alias(user_input)),set_stream(In,alias(main_input)),
  593       stream_property(Out, alias(user_output)),set_stream(Out,alias(main_output)),
  594       find_main_eror(Err),set_stream(Err,alias(main_error)), 
  595       set_stream(Err,alias(current_error)),set_stream(Err, alias(user_error)).
  596
  597find_main_eror(Err):-stream_property(Err, file_no(2)).
  598find_main_eror(Err):-stream_property(Err, alias(user_error)).
  599find_main_eror(Err):-stream_property(Err, alias(main_error)).
  600find_main_eror(Err):-stream_property(Err, alias(current_error)).
  601find_main_eror(user_error).
  602
  603set_main_error:- thread_self_main->set_mains;true.
  604
  605
  606current_error_stream_ucatch(Err):-
  607  stream_property(Err,alias(current_error))-> true;  % when we set it
  608  stream_property(Err,alias(user_error)) -> true;
  609  stream_property(Err,file_no(2)).
  610
  611
  612:- autoload(library(backcomp),[thread_at_exit/1]).
 save_streams(?ID) is semidet
Save Streams.

save_streams(_):-!.

  619save_streams(ID):-
  620  retractall((lmcache:thread_current_input(ID,_))),
  621  retractall((lmcache:thread_current_error_stream(ID,_))),
  622  current_input(In),asserta(lmcache:thread_current_input(ID,In)),
  623  thread_at_exit(retractall((lmcache:thread_current_input(ID,_)))),
  624  thread_at_exit(retractall((lmcache:thread_current_error_stream(ID,_)))),
  625  (stream_property(Err, alias(user_error));current_error_stream_ucatch(Err)),
  626              asserta(lmcache:thread_current_error_stream(ID,Err)).
  627
  628
  629:- meta_predicate(with_main_input(0)).
 with_main_input(:Goal) is semidet
Using Main Input.
  635with_main_input(Goal):-
  636    current_output(OutPrev),current_input(InPrev),stream_property(ErrPrev,alias(user_error)),
  637    lmcache:thread_main(user,ID),lmcache:thread_current_input(ID,In),lmcache:thread_current_error_stream(ID,Err),
  638    scce_orig(set_prolog_IO(In,OutPrev,Err),Goal,set_prolog_IO(InPrev,OutPrev,ErrPrev)).
  639
  640
  641%=
 with_main_io(:Goal) is semidet
Using Main Input/output.
  647 with_main_io(Goal):-
  648    current_output(OutPrev),
  649    current_input(InPrev),
  650    stream_property(ErrPrev,alias(user_error)),
  651    lmcache:thread_main(user,ID),
  652     lmcache:thread_current_input(ID,In),
  653       lmcache:thread_current_error_stream(ID,Err),
  654    scce_orig(set_prolog_IO(In,Err,Err),Goal,set_prolog_IO(InPrev,OutPrev,ErrPrev)).
  655
  656
  657% bugger_debug=never turns off just debugging about the debugger
  658% dmsg_level=never turns off all the rest of debugging
  659% ddmsg(_):-current_prolog_flag(bugger_debug,false),!.
  660% ddmsg(D):- current_predicate(_:wdmsg/1),wdmsg(D),!.
  661
  662%=
 ddmsg(?D) is semidet
Ddmsg.
  668ddmsg(D):- ddmsg("~N~q~n",[D]).
  669%ddmsg(F,A):- current_predicate(_:wdmsg/2),wdmsg(F,A),!.
  670
  671%=
 ddmsg(?F, ?A) is semidet
Ddmsg.
  677ddmsg(F,A):- format_to_error(F,A),!.
  678
  679%=
 ddmsg_call(:GoalD) is semidet
Ddmsg Call.
  685ddmsg_call(D):- ( (ddmsg(ddmsg_call(D)),call(D),ddmsg(ddmsg_exit(D))) *-> true ; ddmsg(ddmsg_failed(D))).
  686:- module_transparent(ddmsg_call/1).
 doall_and_fail(:Goal) is semidet
Doall And Fail.
  694doall_and_fail(Call):- time_call(once(doall(Call))),fail.
  695:- module_transparent(doall_and_fail/1).  696
  697
  698quietly_must(G):- quietly(must(G)).
  699:- module_transparent(quietly_must/1).  700
  701:- module_transparent((if_defined/1,if_defined/2)).
 if_defined(?G) is semidet
If Defined.
  707:- module_transparent(if_defined/1).  708:- export(if_defined/1).  709if_defined(Goal):- if_defined(Goal,((dmsg(warn_undefined(Goal)),!,fail))).
 if_defined(?Goal, :GoalElse) is semidet
If Defined Else.
  715:- module_transparent(if_defined/2).  716:- export(if_defined/2).  717if_defined((A,B),Else):-!, if_defined(A,Else),if_defined(B,Else).
  718if_defined(Goal,Else):- current_predicate(_,Goal)*->Goal;Else.
  719% if_defined(M:Goal,Else):- !, current_predicate(_,OM:Goal),!,OM:Goal;Else.
  720%if_defined(Goal,  Else):- current_predicate(_,OM:Goal)->OM:Goal;Else.
  721
  722
  723
  724
  725
  726:- meta_predicate when_defined(:).  727:- export(when_defined/1).  728
  729%=
 when_defined(?Goal) is semidet
When Defined.
  735when_defined(Goal):-if_defined(Goal,true).
  736
  737:- if(current_predicate(run_sanity_tests/0)).  738:- listing(lmcache:thread_current_error_stream/2).  739:- endif.  740
  741% = :- meta_predicate(to_mpi_matcher(?,?)).
  742
  743%=
 to_mpi_matcher(?P, ?M) is semidet
Converted To Predicate Indicator.
  749context_modulez(M):-nonvar(M),!.
  750context_modulez(V):-context_module(M),visible_import_module(M,V).
  751
  752visible_import_module(M,V):- M == any,!,current_module(V).
  753visible_import_module(M,V):- M == exact,!,context_module(V).
  754visible_import_module(M,V):- M == direct,!,context_module(C),import_module(C,V).
  755visible_import_module(M,V):- M == inherit,!,context_module(C),default_module(C,V).
  756visible_import_module(M,V):- M == V,!.
  757%visible_import_module(_,V):- V == baseKB.
  758visible_import_module(M,V):- \+ atom(M),!,V=M.
  759visible_import_module(M,V):- import_module(M,V).
  760visible_import_module(M,V):- default_module(M,V), M\==V, \+ import_module(M,V).
  761
  762
  763to_mpi_matcher(P,Matcher):-var(P),!,context_modulez(M),to_mpi_matcher(M:P,Matcher).
  764to_mpi_matcher(Name/Arity, Matcher) :- atom(Name),integer(Arity),functor(Head, Name, Arity),!,
  765 to_mpi_matcher(Head,Matcher).
  766to_mpi_matcher(M:P,M:P):- var(M),!,to_mpi_matcher(P,M:P).
  767%to_mpi_matcher(M:P,MP):- var(P),!,to_mpi_matcher(M:P,MP).
  768
  769to_mpi_matcher(CFind,WPI):- 
  770 strip_module(CFind,SC,Find),
  771 (CFind==Find -> C = any ; C = SC),
  772 locally(set_prolog_flag(runtime_debug,0),
  773   ((once(catch(match_predicates(CFind,Found),_,fail)),Found=[_|_],
  774    findall(WPI,
  775    ((member(M:F/A,Found),
  776      functor(PI,F,A),
  777     (predicate_property(M:PI,imported_from(W)) -> true ; W=M),
  778      visible_import_module(C,W),
  779      WPI = W:PI, 
  780      \+ predicate_property(WPI,imported_from(_)))),
  781     Remaining)))),
  782     Remaining=[_|_],!,
  783     sort(Remaining,Set),     
  784     member(WPI,Set).
  785     
  786
  787%to_mpi_matcher(M:Find,MPI):-context_modulez(M),to_pi0(M,Find,MPI).
  788%to_mpi_matcher(M:PI, Head) :- !, to_mpi_matcher(PI, Head).
  789%to_mpi_matcher(Find,M:PI):-context_modulez(M),to_pi0(M,Find,M:PI).
  790
  791to_pi0(M,Find,M:PI):- atom(Find),!,when(nonvar(PI),(nonvar(PI),functor(PI,Find,_))).
  792to_pi0(M,Find/A,M:PI):-var(Find),number(A),!,when(nonvar(PI),(nonvar(PI),functor(PI,_,A))).
  793to_pi0(M,Find,PI):-get_pi(Find,PI0),!,(PI0\=(_:_)->(context_modulez(M),PI=(M:PI0));PI=PI0).
  794
  795
  796%=
 to_pi0(?M, :TermFind, :TermPI) is semidet
Converted To Predicate Indicator Primary Helper.
  803:- thread_local(t_l:last_src_loc/2).  804
  805%=
 input_key(?K) is semidet
Input Key.
  811input_key(K):-thread_self(K).
  812
  813
  814%=
 show_new_src_location(?FL) is semidet
Show New Src Location.
  820show_new_src_location(FL):-input_key(K),!,show_new_src_location(K,FL).
  821
  822
  823%=
 show_new_src_location(?K, ?FL) is semidet
Show New Src Location.
  829show_new_src_location(_,F:_):-F==user_input,!.
  830show_new_src_location(K,FL):- t_l:last_src_loc(K,FL),!.
  831show_new_src_location(K,FL):- retractall(t_l:last_src_loc(K,_)),format_to_error('~N%~~ ~w ~n',[FL]),!,asserta(t_l:last_src_loc(K,FL)).
  832
  833
  834:- thread_local(t_l:current_why_source/1).  835
  836
  837%=
 sl_to_filename(?W, ?W) is semidet
Sl Converted To Filename.
  843sl_to_filename(W,W):-atom(W),exists_file_safe(W).
  844sl_to_filename(W,W):-atom(W),!.
  845sl_to_filename(mfl4(_VarNameZ,_,F,_),F):-atom(F),!.
  846sl_to_filename(_:W,W):-atom(W),!.
  847sl_to_filename(W,W).
  848sl_to_filename(W,To):-nonvar(To),To=(W:_),atom(W),!.
  849
  850
  851
  852                 
  853
  854
  855%=
 current_source_file(-CtxColonLinePos) is semidet
Current Source Location.
  861current_source_file(F:L):- current_source_location(W,L), sl_to_filename(W,F),!.
  862current_source_file(F):- F = unknown.
  863
  864
  865source_ctx(B:L):- must((current_source_file(F:L),file_base_name(F,B))).
  866
  867%=
 current_source_location0(-Ctx, -LinePos) is semidet
Current Source Location Primary Helper.
  873current_source_location(F,L):- notrace((clause(current_source_location0(F,L),Body),notrace(catch(Body,_,fail)))),!.
  874
  875sub_why(Sub,Sub).
  876sub_why(Sub,Why):- compound(Why),Why=(A,B),(sub_why(Sub,A);sub_why(Sub,B)).
  877
  878current_source_location0(F,L):- current_why_data(Data),sub_why(Sub,Data), \+ is_list(Data), compound(Sub),Sub=mfl4(_,_,F,L),!.
  879current_source_location0(F,why):- t_l:current_why_source(F).
  880current_source_location0(F,L):- source_location(F,L),!.
  881current_source_location0(F,L):- prolog_load_context(stream,S),line_or_char_count(S,L),stream_property(S,file_name(F)),!.
  882current_source_location0(F,L):- loading_file(F),stream_property(S,file_name(F)),line_or_char_count(S,L),!.
  883current_source_location0(F,L):- prolog_load_context(file,F),!,ignore((prolog_load_context(stream,S),!,line_or_char_count(S,L))),!.
  884current_source_location0(F,L):- loading_file(F),L= (-1).
  885current_source_location0(F,L):- current_input(S),stream_property(S,alias(F)),line_or_char_count(S,L).
  886current_source_location0(F,L):- current_filesource(F),ignore((prolog_load_context(stream,S),!,line_or_char_count(S,L))),!.
  887% current_source_location0(F,L):- prolog_load_context(file,F),current_input(S),line_position(S,L),!.
  888current_source_location0(M,module):- source_module(M),!.
  889current_source_location0(M,typein):- '$current_typein_module'(M).
  890
  891line_or_char_count(S,_):- \+ is_stream(S),!,fail.
  892line_or_char_count(S,L):- on_x_fail((stream_property(S,position(P)),stream_position_data(line_count,P,L))),!.
  893line_or_char_count(S,L):- on_x_fail(line_count(S,L)),L\==0,!.
  894line_or_char_count(S,L):- on_x_fail(line_position(S,L)),L\==1,!.
  895line_or_char_count(S,L):- on_x_fail(character_count(S,C)),L is -C.
  896
  897:-export(current_why/1).  898:-module_transparent(current_why/1).  899
  900%=
 current_why(?Why) is semidet
Current Generation Of Proof.
  906current_why(Why):- current_why_data(Why).
  907current_why(mfl4(VarNameZ,M,F,L)):- notrace(current_mfl4(VarNameZ,M,F,L)).
  908
  909current_mfl4(VarNameZ,M,F,L):- current_mfl(M,F,L),ignore(varnames_load_context(VarNameZ)).
  910
  911current_mfl(M,F,L):- 
  912 current_source_file(F:L),!,
  913 calc_source_module(M),
  914  ignore((var(L),L=module(M))).
  915
  916calc_source_module(M):- source_module(M),clause_b(mtHybrid(M)),!.
  917calc_source_module(M):- clause_b(defaultAssertMt(M)),!.
  918calc_source_module(M):- source_module(M).
  919
  920:- thread_local(t_l:current_why_source/1).  921
  922current_why_data(Why):- nb_current('$current_why',wp(Why,_P)).
  923current_why_data(Why):- t_l:current_why_source(Why).
  924
  925varnames_load_context(VarNameZ):- 
  926  prolog_load_context(variable_names,Vars),
  927  varnames_to_lazy_unifiable(Vars,VarNameZ).
  928
  929varnames_to_lazy_unifiable(Vars,VarNameZ):- Vars==[],!,VarNameZ=_.
  930varnames_to_lazy_unifiable(Vars,VarNameZ):- nonvar(Vars) -> Vars=VarNameZ;
  931   freeze(Vars,can_maybe_varname(Vars,VarNameZ)).
  932
  933can_maybe_varname(Vars1,Vars2):- ignore(Vars1=Vars2).
Restart and Save the Well-founded Semantic Reason while executing code.
  940with_only_current_why(Why,Prolog):- 
  941  (nb_current('$current_why',WAS);WAS=[])-> 
  942   setup_call_cleanup(b_setval('$current_why',wp(Why,Prolog)),
  943    (call(Prolog),b_setval('$current_why',WAS)),
  944     b_setval('$current_why',WAS)).
Save Well-founded Semantic Reason recursively while executing code.
  950with_current_why(S,Call):-
  951  current_why(UU),
  952  (s_in_why(S,UU) -> Call;  with_only_current_why((S,UU),Call)).
  953
  954s_in_why(S,UU):- S=@=UU,!.
  955s_in_why(_,UU):- \+ compound(UU),!,fail.
  956s_in_why(S,(U1,U2)):- !, (s_in_why(S,U1);s_in_why(S,U2)).
  957s_in_why(S,[U1|U2]):- !, (s_in_why(S,U1);s_in_why(S,U2)).
  958s_in_why(S,UU):- sub_goal(U,UU),S=@=U,!.
  959sub_goal(U,UU):- sub_term(U,UU),nonvar(U), U\==UU.
  960
  961:- thread_initialization(nb_setval('$current_why',[])).  962
  963% source_module(M):-!,M=u.
  964:- export(source_module/1).  965:- module_transparent(source_module/1).  966
  967%=
 source_module(?M) is semidet
Source Module.
  973source_module(M):- nonvar(M),!,source_module(M0),!,(M0=M).
  974source_module(M):- \+ source_location(_,_),!, '$current_typein_module'(M).
  975source_module(M):- '$current_source_module'(M),!.
  976source_module(M):- '$set_source_module'(M,M),!.
  977source_module(M):- strip_module(_,M,_).
  978source_module(M):- loading_module(M),!.
  979
  980:- thread_local(t_l:last_source_file/1).  981:- export(loading_file/1).  982
  983%=
 loading_file(?FIn) is semidet
Loading File.
  989loading_file(FIn):- (quietly((((source_file0(F) *-> (retractall(t_l:last_source_file(_)),asserta(t_l:last_source_file(F))) ; (fail,t_l:last_source_file(F)))),!,F=FIn))).
  990
  991%=
 source_file0(?F) is semidet
Source File Primary Helper.
  997source_file0(F):-source_location(F,_).
  998source_file0(F):-prolog_load_context(file, F).
  999source_file0(F):-prolog_load_context(source, F).
 1000source_file0(F):-seeing(S),is_stream(S),stream_property(S,file_name(F)),exists_file_safe(F).
 1001source_file0(F):-prolog_load_context(stream, S),stream_property(S,file_name(F)),exists_file_safe(F).
 1002source_file0(F):-findall(E,catch((stream_property( S,mode(read)),stream_property(S,file_name(E)),exists_file_safe(E),
 1003  line_count(S,Goal),Goal>0),_,fail),L),last(L,F).
 1004
 1005
 1006:-export(source_variables_l/1). 1007
 1008%=
 source_variables_l(?AllS) is semidet
Source Variables (list Version).
 1014source_variables_l(AllS):-
 1015 quietly((
 1016  (prolog_load_context(variable_names,Vs1);Vs1=[]),
 1017  (get_varname_list(Vs2);Vs2=[]),
 1018  uexecute_goal_vs(Vs3),
 1019  ignore(Vs3=[]),
 1020  append([Vs1,Vs2,Vs3],All),list_to_set(All,AllS),
 1021  set_varname_list(AllS))).
 1022
 1023uexecute_goal_vs(Vs):- uexecute_goal_vs0(Vs),!.
 1024uexecute_goal_vs([]).
 1025uexecute_goal_vs0(Vs):- notrace(catch(ucatch_parent_goal('$toplevel':'$execute_goal2'(_,Vs,_)),_,fail)).
 1026uexecute_goal_vs0(Vs):- notrace(catch(ucatch_parent_goal('$toplevel':'$execute_goal2'(_,Vs)),_,fail)).
 1027
 1028
 1029%=
 show_source_location is semidet
Show Source Location.
 1038:-export( show_source_location/0). 1039show_source_location:- current_prolog_flag(dmsg_level,never),!.
 1040%show_source_location:- quietly((tlbugger:no_slow_io)),!.
 1041show_source_location:- get_source_location(FL)->show_new_src_location(FL),!. 
 1042show_source_location:- if_interactive((dumpST,dtrace)).
 1043
 1044:- thread_local(t_l:last_shown_current_source_location/1). 1045
 1046show_current_source_location:- ignore((get_source_location(FL),!, show_current_source_location(FL))).
 1047show_current_source_location(FL):- t_l:last_shown_current_source_location(FL),!,
 1048                                   retractall(t_l:last_shown_current_source_location(_)),
 1049                                   public_file_link(FL,FLO),
 1050                                   format_to_error('~N%~~ FILE: ~w ~N',[FLO]),!.
 1051show_current_source_location(FL):- retractall(t_l:last_shown_current_source_location(_)),
 1052                                   asserta(t_l:last_shown_current_source_location(FL)),!,
 1053                                   public_file_link(FL,FLO),
 1054                                   format_to_error('~N%~~ FIlE: ~w ~N',[FLO]),!. 
 1055
 1056get_source_location(FL):- current_source_file(FL),nonvar(FL),!.
 1057get_source_location(F:L):- source_location(F,L),!.
 1058get_source_location(get_source_location_unknown).
 1059
 1060
 1061% :- ensure_loaded(hook_database).
 1062
 1063:- dynamic(lmconf:http_file_stem/2). 1064lmconf:http_file_stem('lib/swipl',"https://logicmoo.org:2082/gitlab/logicmoo/logicmoo_workspace/-/tree/master/docker/rootfs/usr/local/lib/swipl").
 1065lmconf:http_file_stem('swi-prolog/pack',"https://logicmoo.org:2082/gitlab/logicmoo/logicmoo_workspace/-/edit/master/packs_sys").
 1066lmconf:http_file_stem(logicmoo_workspace,"https://logicmoo.org:2082/gitlab/logicmoo/logicmoo_workspace/-/edit/master").
 1067lmconf:http_file_stem('~',"https://logicmoo.org:2082/gitlab/logicmoo/prologmud_server/-/tree/master").
 1068
 1069:- export(ensure_compute_file_link/2). 1070:- export(public_file_link/2). 1071:- export(maybe_compute_file_link/2). 1072
 1073ensure_compute_file_link(S,URL):- \+ ( nb_current('$inprint_message', Messages), Messages\==[] ), maybe_compute_file_link(S,URL),!.
 1074ensure_compute_file_link(S,S).
 1075
 1076maybe_compute_file_link(_,_):- !, fail.
 1077maybe_compute_file_link(S,O):- atom(S),!, lmconf:http_file_stem(F,R),atomic_list_concat([_,A],F,S),!,atom_concat(R,A,O).
 1078maybe_compute_file_link(S:L,O):- integer(L),!,maybe_compute_file_link(S,F),format(atom(O),'~w#L~w',[F,L]).
 1079
 1080public_file_link(MG,MG):-!.
 1081public_file_link(S,O):-   \+ ( nb_current('$inprint_message', Messages), Messages\==[] ), maybe_compute_file_link(S,M),into_link(S,M,O).
 1082public_file_link(MG,MG).
 1083
 1084into_link(_,M,O):- format(atom(O),'* ~w ',[M]),!.
 1085into_link(S,M,O):- format(atom(O),'<a href="~w"><pre>~q</pre></a>',[M,S]).
 1086
 1087:-export( as_clause_no_m/3). 1088
 1089%=
 as_clause_no_m(?MHB, ?H, ?B) is semidet
Converted To Clause No Module.
 1095as_clause_no_m( MHB,  H, B):- strip_module(MHB,_M,HB), expand_to_hb( HB,  MH, MB),strip_module(MH,_M2H,H),strip_module(MB,_M2B,B).
 1096
 1097%=
 as_clause_w_m(?MHB, ?M, ?H, ?B) is semidet
Converted To Clause W Module.
 1103as_clause_w_m(MHB, M, H, B):-  as_clause_w_m(MHB, M1H, H, B, M2B), (M1H==user->M2B=M;M1H=M).
 1104
 1105%=
 as_clause_w_m(?MHB, ?M1H, ?H, ?B, ?M2B) is semidet
Converted To Clause W Module.
 1111as_clause_w_m(MHB, M1H, H, B, M2B):-  expand_to_hb( MHB,  MH, MB),strip_module(MH,M1H,H),strip_module(MB,M2B,B).
 1112
 1113:- export(is_ftCompound/1).
 is_ftNameArity(+F, +A) is semidet
If Is A Format Type of a Compound specifier
 1119is_ftNameArity(F,A):-integer(A), atom(F), (F \= (/)),A>=0.
 is_ftCompound(?Goal) is semidet
If Is A Format Type Compound.
 1125is_ftCompound(Goal):-compound(Goal),\+ is_ftVar(Goal).
 not_ftCompound(?InOut) is semidet
Not Compound.
 1131not_ftCompound(A):- \+ is_ftCompound(A).
 1132
 1133:- export(is_ftVar/1). 1134:- export(is_ftVar0/1).
 is_ftVar(:TermV) is semidet
If Is A Format Type Variable.
 1140is_ftVar(V):- notrace(is_ftVar0(V)).
 1141is_ftVar0(V):- \+ compound(V),!,var(V).
 1142is_ftVar0('$VAR'(_)).
 1143is_ftVar0('aVar'(_,_)).
 1144%:- mpred_trace_nochilds(is_ftVar/1).
 1145
 1146
 1147% quotedDefnIff
 1148/*
 1149:- dynamic(baseKB:ftVar/1).
 1150baseKB:ftVar(X):- ucatch:is_ftVar(X).
 1151:- export(baseKB:ftVar/1).
 1152:- system:import(baseKB:ftVar/1).
 1153
 1154:- dynamic(baseKB:ftCompound/1).
 1155baseKB:ftCompound(X):- ucatch:is_ftCompound(X).
 1156:- export(baseKB:ftCompound/1).
 1157:- system:import(baseKB:ftCompound/1).
 1158:- baseKB:export(baseKB:ftCompound/1).
 1159
 1160:- dynamic(baseKB:ftNonvar/1).
 1161baseKB:ftNonvar(X):- ucatch:is_ftNonvar(X).
 1162:- export(baseKB:ftNonvar/1).
 1163:- system:import(baseKB:ftNonvar/1).
 1164*/
 1165%=
 is_ftNonvar(?V) is semidet
If Is A Format Type Nonvar.
 1171is_ftNonvar(V):- \+ is_ftVar(V).
 1172
 1173
 1174%================================================================
 1175% maplist/[2,3]
 1176% this must succeed  maplist_safe(=,[Goal,Goal,Goal],[1,2,3]).
 1177% well if its not "maplist" what shall we call it?
 1178%================================================================
 1179% so far only the findall version works .. the other runs out of local stack!?
 1180
 1181:- export((   maplist_safe/2,
 1182   maplist_safe/3)). 1183
 1184
 1185%=
 maplist_safe(?Pred, ?LIST) is semidet
Maplist Safely Paying Attention To Corner Cases.
 1191maplist_safe(_Pred,[]):-!.
 1192maplist_safe(Pred,LIST):-findall(E,(member(E,LIST), on_f_debug(apply(Pred,[E]))),LISTO),!, ignore(LIST=LISTO),!.
 1193% though this should been fine %  maplist_safe(Pred,[A|B]):- copy_term(Pred+A, Pred0+A0), on_f_debug(once(call(Pred0,A0))),     maplist_safe(Pred,B),!.
 1194
 1195
 1196%=
 maplist_safe(?Pred, ?LISTIN, ?LIST) is semidet
Maplist Safely Paying Attention To Corner Cases.
 1202maplist_safe(_Pred,[],[]):-!.
 1203maplist_safe(Pred,LISTIN, LIST):-!, findall(EE, ((member(E,LISTIN),on_f_debug(apply(Pred,[E,EE])))), LISTO),  ignore(LIST=LISTO),!.
 1204% though this should been fine % maplist_safe(Pred,[A|B],OUT):- copy_term(Pred+A, Pred0+A0), debugOnFailureEach(once(call(Pred0,A0,AA))),  maplist_safe(Pred,B,BB), !, ignore(OUT=[AA|BB]).
 1205
 1206
 1207
 1208:- export(bad_functor/1). 1209
 1210%=
 bad_functor(?L) is semidet
Bad Functor.
 1216bad_functor(L) :- arg(_,v('|',[],':','/'),L). % .
 1217
 1218:- export(warn_bad_functor/1). 1219
 1220%=
 warn_bad_functor(?L) is semidet
Warn Bad Functor.
 1226warn_bad_functor(L):-ignore((notrace(bad_functor(L)),!,dtrace,call(ddmsg(bad_functor(L))),break)).
 1227
 1228:- export(strip_f_module/2). 1229
 1230%=
 strip_f_module(?P, ?PA) is semidet
Strip Functor Module.
 1236strip_f_module(_:P,FA):-nonvar(P),!,strip_f_module(P,F),!,F=FA.
 1237strip_f_module(P,PA):-atom(P),!,P=PA.
 1238
 1239strip_f_module(P,FA):- is_list(P),catch(text_to_string(P,S),_,fail),!,maybe_notrace(atom_string(F,S)),!,F=FA.
 1240strip_f_module(P,FA):- quietly(string(P);atomic(P)), maybe_notrace(atom_string(F,P)),!,F=FA.
 1241strip_f_module(P,P).
 1242
 1243% use catchv/3 to replace catch/3 works around SWI specific issues arround using $abort/0 and block/3
 1244% (catch/3 allows you to have these exceptions bubble up past your catch block handlers)
 1245% = :- meta_predicate((catchv(0, ?, 0))).
 1246% = :- meta_predicate((catchv(0, ?, 0))).
 1247:- export((catchv/3)).
 catchv(:Goal, ?E, :GoalRecovery) is nondet
Like catch/3 but rethrows block/2 and $abort/0.
 1254catchv(Goal,E,Recovery):- 
 1255   nonvar(E) 
 1256   -> catch(Goal,E,Recovery); % normal mode (the user knows what they want)
 1257   catch(Goal,E,(rethrow_bubbled(E),Recovery)). % prevents promiscous mode
 1258
 1259:-export(catchv/3). 1260:-system:import(catchv/3).
 bubbled_ex(?Ex) is det
Bubbled Exception.
 1267bubbled_ex('$aborted').
 1268bubbled_ex('time_limit_exceeded').
 1269bubbled_ex('$time_limit_exceeded').
 1270bubbled_ex(block(_,_)).
 rethrow_bubbled(?E) is det
Bubbled Exception Check.
 1277rethrow_bubbled(E):- ( \+ bubbled_ex(E)),!.
 1278rethrow_bubbled(E):-throw(E).
 1279
 1280
 1281
 1282:- export(functor_catch/3). 1283
 1284%=
 functor_catch(?P, ?F, ?A) is semidet
Functor Catch.
 1290functor_catch(P,F,A):- catchv(functor(P,F,A),_,compound_name_arity(P,F,A)).
 1291% functor_catch(F,F,0):-atomic(F),!.
 1292% functor_catch(P,F,A):-catchv(compound_name_arity(P,F,A),E,(ddmsg(E:functor(P,F,A)),dtrace)).
 1293
 1294
 1295:- export(functor_safe/3). 1296
 1297%=
 functor_safe(?P, ?F, ?A) is semidet
Functor Safely Paying Attention To Corner Cases.
 1303functor_safe(P,F,A):- (compound(P)->compound_name_arity(P,F,A);functor(P,F,A)),sanity(warn_bad_functor(F)).
 1304% functor_safe(P,F,A):- catchv(functor(P,F,A),_,compound_name_arity(P,F,A)).
 1305% functor_safe(P,F,A):- catchv(compound_name_arity(P,F,A),_,functor(P,F,A)).
 1306/*
 1307% functor_safe(P,F,A):-var(P),A==0,compound_name_arguments(P,F,[]),!.
 1308functor_safe(P,F,A):-var(P),A==0,!,P=F,!.
 1309functor_safe(P,F,A):-functor_safe0(P,F,A),!.
 1310functor_safe0(M:P,M:F,A):-var(P),atom(M),functor_catch(P,F,A),!,warn_bad_functor(F).
 1311functor_safe0(P,F,A):-var(P),strip_f_module(F,F0),functor_catch(P,F0,A),!,warn_bad_functor(F).
 1312functor_safe0(P,F,0):- quietly(string(P);atomic(P)), maybe_notrace(atom_string(F,P)),warn_bad_functor(F).
 1313functor_safe_compound((_,_),',',2).
 1314functor_safe_compound([_|_],'.',2).
 1315functor_safe_compound(_:P,F,A):- functor_catch(P,F,A),!.
 1316functor_safe_compound(P,F,A):- functor_catch(P,F,A).
 1317functor_safe_compound(P,F,A):- var(F),strip_f_module(P,P0),!,functor_catch(P0,F0,A),strip_f_module(F0,F),!.
 1318functor_safe_compound(P,F,A):- strip_f_module(P,P0),strip_f_module(F,F0),!,functor_catch(P0,F0,A).
 1319*/
 1320
 1321% block3(test, (repeat, !(test), fail))).
 1322:- meta_predicate block3(+, :, ?). 1323
 1324%=
 block3(+Name, ?Goal, ?Var) is semidet
Block.
 1330block3(Name, Goal, Var) :- Goal, keep(Name, Var).	% avoid last-call and GC
 1331
 1332%=
 keep(?VALUE1, ?VALUE2) is semidet
Keep.
 1338keep(_, _).
 1339
 1340%=
 set_block_exit(?Name, ?Value) is semidet
Set Block Exit.
 1346set_block_exit(Name, Value) :-  prolog_current_frame(Frame),  prolog_frame_attribute(Frame, parent_goal,  mcall:block3(Name, _, Value)).
 1347
 1348
 1349:- export(ucatch_parent_goal/1). 1350ucatch_parent_goal(M:Goal):- 
 1351  prolog_current_frame(F),
 1352  prolog_frame_attribute(F, parent, FP),
 1353  prolog_frame_attribute(FP, parent_goal, M:Goal).
 1354%=
 block(?Name, ?Goal) is semidet
Block.
 1360block(Name, Goal) :-  block3(Name, Goal, Var),  (   Var == !  ->  !  ;   true  ).
 1361
 1362%=
 !(?Name) is semidet
!.
 1368!(Name) :- set_block_exit(Name, !).
 1369
 1370:- export((block3/3,
 1371            set_block_exit/2,
 1372            (block)/2,
 1373            !/1 )). 1374
 1375:- dynamic(buggerFile/1). 1376:- abolish(buggerFile/1),prolog_load_context(source,D),asserta(buggerFile(D)). 1377
 1378
 1379% hasLibrarySupport :- absolute_file_name('logicmoo_util_library.pl',File),exists_file_safe(File).
 1380
 1381
 1382%=
 throwNoLib is semidet
Throw No Lib.
 1388throwNoLib:- dtrace,absolute_file_name('.',Here), buggerFile(BuggerFile), listing(user:library_directory), trace_or_throw(error(existence_error(url, BuggerFile), context(_, status(404, [BuggerFile, from( Here) ])))).
 1389
 1390:- dynamic(buggerDir/1). 1391:- abolish(buggerDir/1),prolog_load_context(directory,D),asserta(buggerDir(D)). 1392
 1393
 1394%=
 addLibraryDir is semidet
Add Library Dir.
 1400addLibraryDir :- buggerDir(Here),atom_concat(Here,'/..',UpOne), absolute_file_name(UpOne,AUpOne),asserta(user:library_directory(AUpOne)).
 1401
 1402% if not has library suport, add this direcotry as a library directory
 1403% :-not(hasLibrarySupport) -> addLibraryDir ; true .
 1404
 1405% :-hasLibrarySupport->true;throwNoLib.
 1406
 1407
 1408
 1409
 1410
 1411%=
 ib_multi_transparent33(?MT) is semidet
Ib Multi Transparent33.
 1417ib_multi_transparent33(MT):-multifile(MT),module_transparent(MT),dynamic_safe(MT).
 1418
 1419
 1420%=
 dif_safe(?Agent, ?Obj) is semidet
Dif Safely Paying Attention To Corner Cases.
 1426dif_safe(Agent,Obj):- (var(Agent);var(Obj)),!.
 1427dif_safe(Agent,Obj):- Agent\==Obj.
 1428
 1429% hide Pred from tracing
 1430
 1431%=
 to_m_f_arity_pi(?Term, ?M, ?F, ?A, ?PI) is semidet
Converted To Module Functor Arity Predicate Indicator.
 1437to_m_f_arity_pi(M:Plain,M,F,A,PI):-!,to_m_f_arity_pi(Plain,M,F,A,PI).
 1438to_m_f_arity_pi(Term,M,F,A,PI):- strip_module(Term,M,Plain),Plain\==Term,!,to_m_f_arity_pi(Plain,M,F,A,PI).
 1439to_m_f_arity_pi(F/A,_M,F,A,PI):-functor_safe(PI,F,A),!.
 1440to_m_f_arity_pi(PI,_M,F,A,PI):-functor_safe(PI,F,A).
 1441
 1442
 1443%=
 with_preds(?H, ?M, ?F, ?A, ?PI, :Goal) is semidet
Using Predicates.
 1449with_preds((H,Y),M,F,A,PI,Goal):-!,with_preds(H,M,F,A,PI,Goal),with_preds(Y,M,F,A,PI,Goal).
 1450with_preds([H],M,F,A,PI,Goal):-!,with_preds(H,M,F,A,PI,Goal).
 1451with_preds([H|Y],M,F,A,PI,Goal):-!,with_preds(H,M,F,A,PI,Goal),with_preds(Y,M,F,A,PI,Goal).
 1452with_preds(M:H,_M,F,A,PI,Goal):-!, with_preds(H,M,F,A,PI,Goal).
 1453with_preds(H,M,F,A,PI,Goal):-forall(to_m_f_arity_pi(H,M,F,A,PI),Goal).
 1454
 1455
 1456
 1457% ===================================================================
 1458% Substitution based on ==
 1459% ===================================================================
 1460% Usage: dbgsubst(+Fml,+Goal,+Sk,?FmlSk)
 1461
 1462:- export(dbgsubst/4). 1463
 1464%=
 dbgsubst(?A, ?B, ?Goal, ?A) is semidet
Dbgsubst.
 1470dbgsubst(A,B,Goal,A):- B==Goal,!.
 1471dbgsubst(A,B,Goal,D):-var(A),!,ddmsg(dbgsubst(A,B,Goal,D)),dumpST,dtrace(dbgsubst0(A,B,Goal,D)).
 1472dbgsubst(A,B,Goal,D):-dbgsubst0(A,B,Goal,D).
 1473
 1474
 1475%=
 dbgsubst0(?A, ?B, ?Goal, ?D) is semidet
Dbgsubst Primary Helper.
 1481dbgsubst0(A,B,Goal,D):-
 1482      catchv(quietly(nd_dbgsubst(A,B,Goal,D)),E,(dumpST,ddmsg(E:nd_dbgsubst(A,B,Goal,D)),fail)),!.
 1483dbgsubst0(A,_B,_C,A).
 1484
 1485
 1486%=
 nd_dbgsubst(?Var, ?VarS, ?SUB, ?SUB) is semidet
Nd Dbgsubst.
 1492nd_dbgsubst(  Var, VarS,SUB,SUB ) :- Var==VarS,!.
 1493nd_dbgsubst(  P, Goal,Sk, P1 ) :- functor_safe(P,_,N),nd_dbgsubst1( Goal, Sk, P, N, P1 ).
 1494
 1495univ_safe_2(A,B):- compound(A),compound_name_arity(A,F,0),!,F=..B.
 1496univ_safe_2(A,B):- A=..B.
 1497
 1498
 1499%=
 nd_dbgsubst1(?Goal, ?Sk, ?P, ?N, ?P1) is semidet
Nd Dbgsubst Secondary Helper.
 1505nd_dbgsubst1( _,  _, P, 0, P  ).
 1506nd_dbgsubst1( Goal, Sk, P, N, P1 ) :- N > 0,univ_safe_2( P, [F|Args]),
 1507            nd_dbgsubst2( Goal, Sk, Args, ArgS ),
 1508            nd_dbgsubst2( Goal, Sk, [F], [FS] ),
 1509            univ_safe_2(P1 , [FS|ArgS]).
 1510
 1511
 1512%=
 nd_dbgsubst2(?X, ?Sk, ?L, ?L) is semidet
Nd Dbgsubst Extended Helper.
 1518nd_dbgsubst2( _,  _, [], [] ).
 1519nd_dbgsubst2( Goal, Sk, [A|As], [Sk|AS] ) :- Goal == A, !, nd_dbgsubst2( Goal, Sk, As, AS).
 1520nd_dbgsubst2( Goal, Sk, [A|As], [A|AS]  ) :- var(A), !, nd_dbgsubst2( Goal, Sk, As, AS).
 1521nd_dbgsubst2( Goal, Sk, [A|As], [Ap|AS] ) :- nd_dbgsubst( A,Goal,Sk,Ap ),nd_dbgsubst2( Goal, Sk, As, AS).
 1522nd_dbgsubst2( _X, _Sk, L, L ).
 1523
 1524
 1525
 1526%=========================================
 1527% Module Utils
 1528%=========================================
 1529
 1530%=
 module_functor(?PredImpl, ?Module, ?Pred, ?Arity) is semidet
Module Functor.
 1536module_functor(PredImpl,Module,Pred,Arity):-strip_module(PredImpl,Module,NewPredImpl),strip_arity(NewPredImpl,Pred,Arity).
 1537
 1538
 1539%=
 strip_arity(?PredImpl, ?Pred, ?Arity) is semidet
Strip Arity.
 1545strip_arity(Pred/Arity,Pred,Arity).
 1546strip_arity(PredImpl,Pred,Arity):-functor_safe(PredImpl,Pred,Arity).
 1547
 1548/*
 1549
 1550debug(+Topic, +Format, +Arguments)
 1551Prints a message using format(Format, Arguments) if Topic unies with a topic
 1552enabled with debug/1.
 1553debug/nodebug(+Topic [>le])
 1554Enables/disables messages for which Topic unies. If >le is added, the debug
 1555messages are appended to the given le.
 1556assertion(:Goal)
 1557Assumes that Goal is true. Prints a stack-dump and traps to the debugger otherwise.
 1558This facility is derived from the assert() macro as used in Goal, renamed
 1559for obvious reasons.
 1560*/
 1561:- meta_predicate with_preds(?,?,?,?,?,0). 1562
 1563
 1564
 1565%set_prolog_flag(N,V):-!,nop(set_prolog_flag(N,V)).
 1566
 1567
 1568% have to load this module here so we dont take ownership of prolog_exception_hook/4.
 1569:- set_prolog_flag(generate_debug_info, true). 1570% have to load this module here so we dont take ownership of prolog_exception_hook/4.
 1571
 1572% :- ensure_loaded(library(backcomp)).
 1573:- ensure_loaded(library(ansi_term)). 1574:- ensure_loaded(library(check)). 1575:- ensure_loaded(library(debug)). 1576:- ensure_loaded(library(lists)). 1577:- ensure_loaded(library(make)). 1578:- ensure_loaded(library(system)). 1579:- ensure_loaded(library(apply)). 1580
 1581:- thread_local(t_l:session_id/1). 1582:- multifile(t_l:session_id/1). 1583
 1584:- thread_local(tlbugger:no_colors/0). 1585
 1586
 1587% =========================================================================
 1588
 1589
 1590%=
 trace_or_throw(?E) is semidet
Trace or throw.
 1596:- export(trace_or_throw/1). 1597trace_or_throw(E):- hide_non_user_console,quietly((thread_self(Self),wdmsg(thread_trace_or_throw(Self+E)),!,throw(abort),
 1598                    thread_exit(trace_or_throw(E)))).
 1599
 1600
 1601trace_or_throw(E):- wdmsg(trace_or_throw(E)),if_interactive((trace,break),true),dtrace((dtrace,throw(E))).
 1602
 1603 %:-interactor.
 1604
 1605
 1606% false = hide this wrapper
 1607
 1608%=
 showHiddens is semidet
Show Hiddens.
 1614showHiddens:-true.
 1615
 1616:- meta_predicate on_x_log_fail(0). 1617:- export(on_x_log_fail/1). 1618
 1619%=
 on_x_log_fail(:Goal) is semidet
If there If Is A an exception in :Goal goal then log fail.
 1625on_x_log_fail(Goal):- catchv(Goal,E,(dmsg(E:Goal),fail)).
 1626
 1627on_xf_log_cont(Goal):- (on_x_log_cont(Goal)*->true;dmsg(on_f_log_cont(Goal))).
 1628
 1629on_xf_log_cont_l(Goal):- call_each_det(on_xf_log_cont,Goal).
 1630
 1631% -- CODEBLOCK
 1632
 1633:- export(on_x_log_throw/1). 1634:- export(on_x_log_cont/1). 1635
 1636%=
 on_x_log_throw(:Goal) is semidet
If there If Is A an exception in :Goal goal then log throw.
 1642on_x_log_throw(Goal):- catchv(Goal,E,(ddmsg(on_x_log_throw(E,Goal)),throw(E))).
 1643%on_x_log_throwEach(Goal):-with_each(1,on_x_log_throw,Goal).
 1644
 1645%=
 on_x_log_cont(:Goal) is semidet
If there If Is A an exception in :Goal goal then log cont.
 1651on_x_log_cont(Goal):- catchv( (Goal*->true;ddmsg(failed_on_x_log_cont(Goal))),E,ddmsg(E:Goal)).
 1652
 1653:- thread_local( tlbugger:skipMust/0). 1654%MAIN tlbugger:skipMust.
 1655
 1656
 1657:- export(errx/0). 1658
 1659%=
 errx is semidet
Errx.
 1665errx:-on_x_debug((ain(tlbugger:dont_skip_bugger),do_gc,dumpST(10))),!.
 1666
 1667:- thread_local(tlbugger:rtracing/0). 1668
 1669
 1670
 1671/*
 1672
 1673A value 0 means that the corresponding quality is totally unimportant, and 3 that the quality is extremely important; 
 16741 and 2 are intermediate values, with 1 the neutral value. (quality 3) can be abbreviated to quality.
 1675
 1676*/
 1677compute_q_value(N,N):- number(N),!.
 1678compute_q_value(false,0).
 1679compute_q_value(fail,0).
 1680compute_q_value(never,0).
 1681compute_q_value(neutral,1).
 1682compute_q_value(true,2).
 1683compute_q_value(quality,3).
 1684compute_q_value(Flag,Value):-current_prolog_flag(Flag,M),!,compute_q_value(M,Value).
 1685compute_q_value(N,1):- atom(N).
 1686compute_q_value(N,V):- compound(N), catch(V is N,_,fail).
 1687
 1688/*
 1689
 1690Name                        Meaning
 1691---------------------       --------------------------------
 1692logicmoo_compilation_speed  speed of the compilation process   
 1693
 1694runtime_debug              ease of debugging                  
 1695logicmoo_space              both code size and run-time space  
 1696
 1697runtime_safety             run-time error checking            
 1698runtime_speed              speed of the object code
 1699
 1700unsafe_speedups      speed up that are possibily
 1701
 1702*/
 1703flag_call(FlagHowValue):-zotrace(flag_call0(FlagHowValue)).
 1704flag_call0(Flag = Quality):- compute_q_value(Quality,Value),!, set_prolog_flag(Flag,Value).
 1705flag_call0(Flag == Quality):-
 1706  current_prolog_flag(Flag,Current),!,
 1707  compute_q_value(Quality,QValue),
 1708  compute_q_value(Current,CValue),
 1709  QValue==CValue,!.
 1710flag_call0(FlagHowValue):- univ_safe_2(FlagHowValue,[How,Flag,Value]),
 1711    current_prolog_flag(Flag,QVal),compute_q_value(Value,VValue),!,call(How,QVal,VValue).
 1712
 1713
 1714
 1715%=
 skipWrapper is semidet
Skip Wrapper.
 1722% false = use this wrapper, true = code is good and avoid using this wrapper
 1723:- export(skipWrapper/0). 1724
 1725% skipWrapper:-!.
 1726skipWrapper:- zotrace((bugger:skipWrapper0)).
 1727% skipWrapper:- tracing,!.
 1728
 1729skipWrapper0:- current_prolog_flag(bugger,false),!.
 1730skipWrapper0:- tracing, \+ tlbugger:rtracing,!.
 1731skipWrapper0:- tlbugger:dont_skip_bugger,!,fail.
 1732%skipWrapper0:- flag_call(runtime_debug true) ,!,fail.
 1733%skipWrapper0:- current_prolog_flag(unsafe_speedups , true) ,!.
 1734skipWrapper0:- tlbugger:skip_bugger,!.
 1735%skipWrapper0:- is_release,!.
 1736%skipWrapper0:- 1 is random(5),!.
 1737%skipWrapper0:- tlbugger:skipMust,!.
 1738
 1739:- '$hide'(skipWrapper/0). 1740
 1741%MAIN tlbugger:skip_bugger.
 1742
 1743
 1744% = :- meta_predicate(one_must(0,0)).
 1745
 1746%=
 one_must(:GoalMCall, :GoalOnFail) is semidet
One Must Be Successfull.
 1752one_must(MCall,OnFail):-  call(MCall) *->  true ; call(OnFail).
 1753
 1754
 1755
 1756%=
 must_det_u(:Goal) is semidet
Must Be Successfull Deterministic.
 1763%must_det_u(Goal):- !,maybe_notrace(Goal),!.
 1764must_det_u(Goal):- (quietly(Goal)->!;(ignore(rtrace(Goal)),break)).
 1765
 1766
 1767%=
 one_must_det(:Goal, :GoalOnFail) is semidet
One Must Be Successfull Deterministic.
 1773one_must_det(Goal,_OnFail):-Goal,!.
 1774one_must_det(_Call,OnFail):-OnFail,!.
 1775
 1776
 1777%=
 must_det_dead(:Goal, :GoalOnFail) is semidet
Must Be Successfull Deterministic.

must_det_dead(Goal,OnFail):- trace_or_throw(deprecated(must_det_u(Goal,OnFail))),Goal,!. must_det_dead(_Call,OnFail):-OnFail.

 1786:- module_transparent(must_det_l/1). 1787
 1788%=
 must_det_l(:GoalMGoal) is semidet
Must Be Successfull Deterministic (list Version).
 1794:- export(must_det_l/1). 1795must_det_l(Goal):- call_each_det(must_det_u,Goal).
 1796
 1797must_det_l_pred(Pred,Rest):- tlbugger:skip_bugger,!,call(Pred,Rest).
 1798must_det_l_pred(Pred,Rest):- call_each_det(call_must_det(Pred),Rest).
 1799
 1800call_must_det(Pred,Arg):- must_det_u(call(Pred,Arg)),!.
 1801
 1802is_call_var(Goal):- strip_module(Goal,_,P),var(P).
 1803
 1804
 1805call_each(Pred,Goal):- call_each_det(Pred,Goal).
 1806
 1807call_each_det(Pred,Goal):- notrace(is_call_var(Pred);is_call_var(Goal)),!,trace_or_throw(var_call_each(Pred,Goal)),!.
 1808call_each_det(Pred,[Goal]):- !, dmsg(trace_syntax(call_each_det(Pred,[Goal]))),!,call_each_det(Pred,Goal).
 1809call_each_det(Pred,[Goal|List]):- !, dmsg(trace_syntax(call_each_det(Pred,[Goal|List]))), !, call_each_det(Pred,Goal),!,call_each_det(Pred,List).
 1810% call_each_det(Pred,Goal1):-tlbugger:skip_bugger,!,p_call(Pred,Goal1).
 1811call_each_det(Pred,M:(Goal1,!)):-!, call_each_det(Pred,M:Goal1),!.
 1812call_each_det(Pred,M:(Goal1,!,Goal2)):-!, call_each_det(Pred,M:Goal1),!,call_each_det(Pred,M:Goal2).
 1813call_each_det(Pred,M:(Goal1,Goal2)):-!, call_each_det(Pred,M:Goal1),!,call_each_det(Pred,M:Goal2).
 1814call_each_det(Pred,(Goal1,!)):-!, call_each_det(Pred,Goal1),!.
 1815call_each_det(Pred,(Goal1,!,Goal2)):- !, call_each_det(Pred,Goal1),!,call_each_det(Pred,Goal2).
 1816call_each_det(Pred,(Goal1,Goal2)):- !, call_each_det(Pred,Goal1),!,call_each_det(Pred,Goal2).
 1817call_each_det(Pred,forall(Goal1,Goal2)):- !, forall(Goal1,call_each_det(Pred,Goal2)).
 1818call_each_det(Pred,Goal):- p_call(Pred,Goal),!.
 1819
 1820% p_call(Pred,_:M:Goal):-!,p_call(Pred,M:Goal).
 1821p_call([Pred1|PredS],Goal):-!,p_call(Pred1,Goal),p_call(PredS,Goal).
 1822p_call((Pred1,PredS),Goal):-!,p_call(Pred1,Goal),p_call(PredS,Goal).
 1823p_call((Pred1;PredS),Goal):-!,p_call(Pred1,Goal);p_call(PredS,Goal).
 1824p_call(Pred,Goal):-call(Pred,Goal).
 1825
 1826must_find_and_call(G):-must(G).
 1827
 1828:- module_transparent(det_lm/2). 1829
 1830%=
 det_lm(?M, ?Goal) is semidet
Deterministic Lm.
 1836det_lm(M,(Goal,List)):- !,Goal,!,det_lm(M,List).
 1837det_lm(M,Goal):-M:Goal,!.
 1838
 1839:- module_transparent(must_l/1). 1840
 1841%=
 must_l(:Goal) is semidet
Must Be Successfull (list Version).
 1847must_l(Goal):- skipWrapper,!,call(Goal).
 1848must_l(Goal):- var(Goal),trace_or_throw(var_must_l(Goal)),!.
 1849must_l((A,!,B)):-!,must(A),!,must_l(B).
 1850must_l((A,B)):-!,must((A,deterministic(Det),true,(Det==true->(!,must_l(B));B))).
 1851must_l(Goal):- must(Goal).
 1852
 1853
 1854:- thread_local tlbugger:skip_use_slow_sanity/0. 1855:- asserta((tlbugger:skip_use_slow_sanity:-!)). 1856
 1857% thread locals should defaults to false  tlbugger:skip_use_slow_sanity.
 1858
 1859
 1860%=
 slow_sanity(:Goal) is semidet
Slow Optional Sanity Checking.
 1866slow_sanity(Goal):- ( tlbugger:skip_use_slow_sanity ; must(Goal)),!.
 1867
 1868
 1869:- meta_predicate(hide_trace(0)). 1870
 1871hide_trace(G):- %JUNIT \+ tracing,
 1872 !,call(G).
 1873hide_trace(G):- !,call(G).
 1874hide_trace(G):- skipWrapper,!,call(G).
 1875hide_trace(G):-
 1876 restore_trace((
 1877   quietly(
 1878      ignore((tracing,
 1879      visible(-all),
 1880      visible(-unify),
 1881      visible(+exception),
 1882      maybe_leash(-all),
 1883      maybe_leash(+exception)))),G)).
 1884
 1885:- meta_predicate(on_x_f(0,0,0)). 1886on_x_f(G,X,F):-catchv(G,E,(dumpST,wdmsg(E),X)) *-> true ; F .
 1887
 1888% :- meta_predicate quietly(0).
 1889
 1890% quietly(G):- skipWrapper,!,call(G).
 1891% quietly(G):- !,quietly(G).
 1892% quietly(G):- !, on_x_f((G),setup_call_cleanup(wdmsg(begin_eRRor_in(G)),rtrace(G),wdmsg(end_eRRor_in(G))),fail).
 1893/*quietly(G):- on_x_f(hide_trace(G),
 1894                     setup_call_cleanup(wdmsg(begin_eRRor_in(G)),rtrace(G),wdmsg(end_eRRor_in(G))),
 1895                     fail).
 1896*/
 1897
 1898:- if(current_prolog_flag(optimise,true)). 1899is_recompile:-fail.
 1900:- else. 1901is_recompile:-fail.
 1902:- endif. 1903
 1904% -- CODEBLOCK
 1905% :- export(7sanity/1).
 1906% = :- meta_predicate(sanity(0)).
 1907
 1908
 1909
 1910compare_results(N+NVs,O+OVs):-
 1911   NVs=@=OVs -> true; trace_or_throw(compare_results(N,O)).
 1912
 1913allow_unsafe_code :- fail.
 1914
 1915unsafe_safe(_,O):- \+ allow_unsafe_code, !, call(O).
 1916unsafe_safe(N,O):- on_diff_throw(N,O).
 1917
 1918on_diff_throw(_G1,G2):- call(G2).
 1919
 1920:- export(need_speed/0). 1921need_speed:-current_prolog_flag(unsafe_speedups , true) .
 1922
 1923:- export(is_release/0).
 is_release is semidet
If Is A Release.
 1928is_release:- current_prolog_flag(unsafe_speedups, false) ,!,fail.
 1929is_release:- !,fail.
 1930is_release:- current_prolog_flag(unsafe_speedups , true) ,!.
 1931is_release:- notrace((\+ flag_call(runtime_debug == true) , \+ (1 is random(4)))).
 not_is_release is semidet
Not If Is A Release.
 1939:- export(not_is_release/0). 1940not_is_release:- \+ is_release.
 1941
 1942
 1943%=
 badfood(?MCall) is semidet
Badfood.
 1949badfood(MCall):- numbervars(MCall,0,_,[functor_name('VAR_______________________x0BADF00D'),attvar(bind),singletons(false)]),dumpST.
 1950
 1951% -- CODEBLOCK
 1952:- export(without_must/1). 1953% = :- meta_predicate(without_must(0)).
 1954
 1955
 1956%=
 without_must(:Goal) is semidet
Without Must Be Successfull.
 1962without_must(Goal):- locally(tlbugger:skipMust,Goal).
 1963
 1964% -- CODEBLOCK
 1965:- export(y_must/2). 1966:- meta_predicate (y_must(?,0)). 1967
 1968%=
 y_must(?Y, :Goal) is semidet
Y Must Be Successfull.
 1974y_must(Y,Goal):- catchv(Goal,E,(wdmsg(E:must_xI__xI__xI__xI__xI_(Y,Goal)),fail)) *-> true ; dtrace(y_must(Y,Goal)).
 1975
 1976% -- CODEBLOCK
 1977% :- export(must/1).
 1978%:- meta_predicate(must(0)).
 1979%:- meta_predicate(must(0)).
 1980
 1981%=
 1982
 1983
 1984dumpST_error(Msg):- notrace((ddmsg(error,Msg),dumpST,wdmsg(error,Msg))).
 1985
 1986
 1987:- thread_self_main->true;writeln(user_error,not_thread_self_main_consulting_ucatch). 1988:- save_streams. 1989:- initialization(save_streams,now). 1990:- initialization(save_streams,after_load). 1991:- initialization(save_streams,restore). 1992:- thread_initialization(save_streams). 1993
 1994
 1995:- setup_call_cleanup(true,set_main_error,notrace). 1996:- initialization(set_main_error). 1997:- initialization(set_main_error,after_load). 1998:- initialization(set_main_error,restore). 1999:- notrace. 2000
 2001%:- 'mpred_trace_none'(ddmsg(_)).
 2002%:- 'mpred_trace_none'(ddmsg(_,_)).
 2003
 2004
 2005sanity2(_Loc,Goal):- sanity(Goal).
 2006must2(_Loc,Goal):- must(Goal).
 2007
 2008ge_expand_goal(G,G):- \+ compound(G),!,fail.
 2009ge_expand_goal(G,GO):- expand_goal(G,GO).
 2010
 2011% ge_must_sanity(sanity(_),true).
 2012% ge_must_sanity(must(Goal),GoalO):-ge_expand_goal(Goal,GoalO).
 2013% ge_must_sanity(find_and_call(Goal),GoalO):-ge_expand_goal(Goal,GoalO).
 2014
 2015% ge_must_sanity(sanity(Goal),nop(sanity(GoalO))):- ge_expand_goal(Goal,GoalO).
 2016% ge_must_sanity(must(Goal),(GoalO*->true;debugCallWhy(failed_must(Goal,FL),GoalO))):- source_ctx(FL),ge_expand_goal(Goal,GoalO).
 2017
 2018ge_must_sanity(P,O):- univ_safe_2(P,[F,Arg]),nonvar(Arg),ge_must_sanity(F,Arg,O).
 2019
 2020ge_must_sanity(sanity,Goal,sanity2(FL,Goal)):- source_ctx(FL).
 2021ge_must_sanity(must,Goal,must2(FL,Goal)):- source_ctx(FL).
 2022% ge_must_sanity(must_det_l,Goal,must2(FL,Goal)):- source_ctx(FL).
 2023
 2024system:goal_expansion(I,P,O,P):- notrace((compound(I), source_location(_,_))),
 2025  (prolog_load_context(module, Module),default_module(Module,ucatch)),
 2026  once(ge_must_sanity(I,O))->I \== O.
 2027
 2028:- dynamic(inlinedPred/1). 2029
 2030/*
 2031system:goal_expansion(I,O):- fail, compound(I),functor(I,F,A),inlinedPred(F/A),
 2032  source_location(File,L),clause(I,Body),O= (file_line(F,begin,File,L),Body,file_line(F,end,File,L)).
 2033*/
 2034
 2035file_line(F,What,File,L):- (debugging(F)->wdmsg(file_line(F,What,File,L));true).
 2036
 2037
 2038:- ignore((source_location(S,_1),prolog_load_context(module,M),module_property(M,class(library)),
 2039 forall(source_file(M:H,S),
 2040 ignore((functor(H,F,A),
 2041  ignore(((\+ atom_concat('$',_,F),(export(F/A) , current_predicate(system:F/A)->true; system:import(M:F/A))))),
 2042  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]))))))))). 2043
 2044% :- set_prolog_flag(compile_meta_arguments,true).
 2045
 2046:- include(dumpst). 2047:- include(dmsg). 2048:- fixup_exports.