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% File: /opt/PrologMUD/pack/logicmoo_base/prolog/logicmoo/util/logicmoo_util_dmsg.pl
   14:- module(dmsg,
   15          [ ansi_control_conv/2,
   16            with_output_to_each/2,
   17            ansicall/2,
   18            ansicall/3,
   19            ansicall0/3,
   20            ansicall1/3,
   21            ansifmt/2,
   22            ansifmt/3,
   23            
   24            colormsg/2,
   25            mesg_color/2,
   26            contains_atom/2,
   27            contrasting_color/2,
   28            defined_message_color/2,
   29
   30            format_to_message/3, 
   31            dfmt/1,dfmt/2,
   32            debugm/1,debugm/2,
   33            dmsg/1,dmsg/2,dmsg/3,
   34
   35          setLogLevel/2,
   36          logLevel/2,
   37               loggerFmtReal/3,
   38               loggerReFmt/2,
   39               logger_property/3,
   40
   41            univ_safe_2/2,
   42            cls/0,
   43            dmsg0/1,dmsg0/2,dmsg00/1,
   44            dmsg1/1,
   45            dmsg2/1,
   46            dmsg3/1,
   47            dmsg4/1,
   48            dmsg5/1,dmsg5/2,
   49            dmsg_hide/1,
   50            dmsg_hides_message/1,
   51            dmsg_show/1,
   52            dmsg_showall/1,
   53            dmsg_text_to_string_safe/2,
   54            dmsginfo/1,
   55          wdmsg/1,
   56          wdmsg/2,
   57            wdmsgl/1,
   58            wdmsgl/2,
   59            wdmsgl/3,
   60            
   61            
   62            
   63
   64            f_word/2,
   65            fg_color/2,
   66            flush_output_safe/0,
   67            flush_output_safe/1,
   68            fmt/1,fmt/2,fmt/3,
   69            fmt0/1,fmt0/2,fmt0/3,
   70            fmt9/1,
   71            fmt_ansi/1,
   72            fmt_or_pp/1,
   73            fmt_portray_clause/1,
   74            functor_color/2,
   75          get_indent_level/1,
   76            good_next_color/1,
   77            if_color_debug/0,
   78            if_color_debug/1,
   79            if_color_debug/2,
   80            in_cmt/1,
   81            indent_e/1,
   82            indent_to_spaces/2,
   83            is_sgr_on_code/1,
   84            is_tty/1,
   85            keep_line_pos_w_w/2,
   86            last_used_fg_color/1,
   87          matches_term/2,
   88          matches_term0/2,
   89            mesg_arg1/2,
   90            msg_to_string/2,
   91            next_color/1,
   92            portray_clause_w_vars/1,
   93            portray_clause_w_vars/2,
   94            portray_clause_w_vars/3,
   95            portray_clause_w_vars/4,
   96            predef_functor_color/2,
   97            prepend_each_line/2,
   98            print_prepended/2,
   99            print_prepended_lines/2,
  100            random_color/1,
  101            sformat/4,
  102            sgr_code_on_off/3,
  103            sgr_off_code/2,
  104            sgr_on_code/2,
  105            sgr_on_code0/2,
  106            to_stderror/1,
  107            tst_color/0,
  108            tst_color/1,
  109            tst_fmt/0,
  110            unliked_ctrl/1,
  111            vdmsg/2,
  112            withFormatter/4,
  113            with_all_dmsg/1,
  114            with_current_indent/1,
  115            with_dmsg/2,
  116            with_no_dmsg/1,
  117            with_no_dmsg/2,
  118            with_output_to_console/1,
  119            with_output_to_main/1,
  120            with_output_to_stream/2,
  121            with_show_dmsg/2,
  122
  123
  124% source_variables_lwv/1,
  125term_color0/2,
  126ansi_prop/2,
  127dmsg_log/3,
  128dmsg000/1,
  129
  130            writeFailureLog/2
  131          ]).  132:- multifile
  133        term_color0/2.  134:- meta_predicate
  135        ansicall(?, 0),
  136        ansicall(?, ?, 0),
  137        ansicall0(?, ?, 0),
  138        ansicall1(?, ?, 0),
  139        fmt_ansi(0),
  140        if_color_debug(0),
  141        if_color_debug(0, 0),
  142        in_cmt(0),
  143        keep_line_pos_w_w(?, 0),        
  144        prepend_each_line(?, 0),
  145        to_stderror(0),
  146        with_all_dmsg(0),
  147        with_current_indent(0),
  148        with_dmsg(?, 0),
  149        with_no_dmsg(0),
  150        with_no_dmsg(?, 0),
  151        with_output_to_console(0),
  152        with_output_to_main(0),
  153        with_output_to_stream(?, 0),
  154        with_show_dmsg(?, 0).  155
  156
  157univ_safe_2(A,B):- compound(A),compound_name_arity(A,F,0),!,F=..B.
  158univ_safe_2(A,B):- A=..B.
  159
  160:- meta_predicate if_defined_local(:,0).  161if_defined_local(G,Else):- current_predicate(_,G)->G;Else.
  162
  163:- module_transparent
  164        ansi_control_conv/2,
  165        ansifmt/2,
  166        ansifmt/3,
  167        colormsg/2,
  168        contrasting_color/2,
  169        defined_message_color/2,
  170        dfmt/1,
  171        dfmt/2,
  172        dmsg/3,
  173        dmsg0/1,
  174        dmsg0/2,
  175        dmsg1/1,
  176        dmsg2/1,
  177        dmsg3/1,
  178        dmsg4/1,
  179        dmsg5/1,
  180        dmsg5/2,
  181        dmsg_hide/1,
  182        dmsg_hides_message/1,
  183        dmsg_show/1,
  184        dmsg_showall/1,
  185        dmsg_text_to_string_safe/2,
  186        dmsginfo/1,
  187
  188        with_output_to_each/2,
  189        f_word/2,
  190        fg_color/2,
  191        flush_output_safe/0,
  192        flush_output_safe/1,
  193        fmt/1,
  194        fmt/2,
  195        fmt/3,
  196        fmt0/1,
  197        fmt0/2,
  198        fmt0/3,
  199        fmt9/1,
  200        fmt_or_pp/1,
  201        fmt_portray_clause/1,
  202        functor_color/2,
  203        get_indent_level/1,
  204        good_next_color/1,
  205        if_color_debug/0,
  206        indent_e/1,
  207        indent_to_spaces/2,
  208        is_sgr_on_code/1,
  209        is_tty/1,
  210        last_used_fg_color/1,
  211        mesg_arg1/2,
  212        
  213        msg_to_string/2,
  214        next_color/1,
  215        portray_clause_w_vars/1,
  216        portray_clause_w_vars/2,
  217        portray_clause_w_vars/3,
  218        portray_clause_w_vars/4,
  219        predef_functor_color/2,
  220        print_prepended/2,
  221        print_prepended_lines/2,
  222        random_color/1,
  223        sformat/4,
  224        sgr_code_on_off/3,
  225        sgr_off_code/2,
  226        sgr_on_code/2,
  227        sgr_on_code0/2,
  228        tst_color/0,
  229        tst_color/1,
  230        tst_fmt/0,
  231        unliked_ctrl/1,
  232        vdmsg/2,
  233        withFormatter/4,
  234        writeFailureLog/2.  235:- dynamic
  236        defined_message_color/2,
  237        term_color0/2.  238
  239
  240:- if(current_predicate(lmcode:combine_logicmoo_utils/0)).  241:- module(logicmoo_util_dmsg,
  242[  % when the predciates are not being moved from file to file the exports will be moved here
  243       ]).  244
  245:- else.  246
  247:- endif.  248
  249:- set_module(class(library)).  250
  251:- user:use_module(library(memfile)).  252:- user:use_module(first).  253%:- user:ensure_loaded(logicmoo_util_rtrace).
  254:- ensure_loaded(library(with_thread_local)).  255%:- user:ensure_loaded(logicmoo_util_loop_check).
  256
  257
  258
  259:- meta_predicate with_output_to_each(+,0).  260
  261with_output_to_each(Output,Goal):- Output= atom(A),!,
  262   current_output(Was),
  263   nb_setarg(1,Output,""),
  264   new_memory_file(Handle),
  265   open_memory_file(Handle,write,Stream,[free_on_close(true)]),
  266     scce_orig(set_output(Stream),
  267      setup_call_cleanup(true,Goal,
  268        (close(Stream),memory_file_to_atom(Handle,Atom),nb_setarg(1,Output,Atom),ignore(A=Atom))),
  269      (set_output(Was))).
  270
  271with_output_to_each(Output,Goal):- Output= string(A),!,
  272   current_output(Was),
  273   nb_setarg(1,Output,""),
  274   new_memory_file(Handle),
  275   open_memory_file(Handle,write,Stream,[free_on_close(true)]),
  276     scce_orig(set_output(Stream),
  277      setup_call_cleanup(true,Goal,
  278        (close(Stream),memory_file_to_string(Handle,Atom),nb_setarg(1,Output,Atom),ignore(A=Atom))),
  279      (set_output(Was))).
  280
  281with_output_to_each(Output,Goal):- 
  282   current_output(Was), scce_orig(set_output(Output),Goal,set_output(Was)).
  283    
  284
  285% ==========================================================
  286% Sending Notes
  287% ==========================================================
  288:- thread_local( tlbugger:tlbugger:dmsg_match/2).  289% = :- meta_predicate(with_all_dmsg(0)).
  290% = :- meta_predicate(with_show_dmsg(*,0)).
  291
  292
  293
  294%= 	 	 
 with_all_dmsg(:Goal) is nondet
Using All (debug)message.
  300with_all_dmsg(Goal):-
  301   locally(set_prolog_flag(dmsg_level,always),     
  302       locally( tlbugger:dmsg_match(show,_),Goal)).
  303
  304
  305
  306%= 	 	 
 with_show_dmsg(?TypeShown, :Goal) is nondet
Using Show (debug)message.
  312with_show_dmsg(TypeShown,Goal):-
  313  locally(set_prolog_flag(dmsg_level,always),
  314     locally( tlbugger:dmsg_match(showing,TypeShown),Goal)).
  315
  316% = :- meta_predicate(with_no_dmsg(0)).
  317
  318%= 	 	 
 with_no_dmsg(:Goal) is nondet
Using No (debug)message.
  325 % with_no_dmsg(Goal):- current_prolog_flag(dmsg_level,always),!,Goal.
  326with_no_dmsg(Goal):-locally(set_prolog_flag(dmsg_level,never),Goal).
  327
  328%= 	 	 
 with_no_dmsg(?TypeUnShown, :Goal) is nondet
Using No (debug)message.
  334with_no_dmsg(TypeUnShown,Goal):-
  335 locally(set_prolog_flag(dmsg_level,filter),
  336  locally( tlbugger:dmsg_match(hidden,TypeUnShown),Goal)).
  337
  338% dmsg_hides_message(_):- !,fail.
  339
  340%= 	 	 
 dmsg_hides_message(?C) is det
(debug)message Hides Message.
  346dmsg_hides_message(_):- current_prolog_flag(dmsg_level,never),!.
  347dmsg_hides_message(_):- current_prolog_flag(dmsg_level,always),!,fail.
  348dmsg_hides_message(C):-  tlbugger:dmsg_match(HideShow,Matcher),matches_term(Matcher,C),!,HideShow=hidden.
  349
  350:- export(matches_term/2).
 matches_term(?Filter, ?VALUE2) is det
Matches Term.
  356matches_term(Filter,_):- var(Filter),!.
  357matches_term(Filter,Term):- var(Term),!,Filter=var.
  358matches_term(Filter,Term):- ( \+ \+ (matches_term0(Filter,Term))),!.
 contains_atom(?V, ?A) is det
Contains Atom.
  364contains_atom(V,A):-sub_term(VV,V),nonvar(VV),cfunctor(VV,A,_).
 matches_term0(:TermFilter, ?Term) is det
Matches Term Primary Helper.
  370matches_term0(Filter,Term):- Term = Filter.
  371matches_term0(Filter,Term):- atomic(Filter),!,contains_atom(Term,Filter).
  372matches_term0(F/A,Term):- (var(A)->member(A,[0,1,2,3,4]);true), cfunctor(Filter,F,A), matches_term0(Filter,Term).
  373matches_term0(Filter,Term):- sub_term(STerm,Term),nonvar(STerm),call(call,matches_term0(Filter,STerm)),!.
  374
  375
  376%= 	 	 
 dmsg_hide(?Term) is det
(debug)message Hide.
  382dmsg_hide(isValueMissing):-!,set_prolog_flag(dmsg_level,never).
  383dmsg_hide(Term):-set_prolog_flag(dmsg_level,filter),sanity(nonvar(Term)),aina( tlbugger:dmsg_match(hidden,Term)),retractall( tlbugger:dmsg_match(showing,Term)),nodebug(Term).
  384
  385%= 	 	 
 dmsg_show(?Term) is det
(debug)message Show.
  391dmsg_show(isValueMissing):-!,set_prolog_flag(dmsg_level,always).
  392dmsg_show(Term):-set_prolog_flag(dmsg_level,filter),aina( tlbugger:dmsg_match(showing,Term)),ignore(retractall( tlbugger:dmsg_match(hidden,Term))),debug(Term).
  393
  394%= 	 	 
 dmsg_showall(?Term) is det
(debug)message Showall.
  400dmsg_showall(Term):-ignore(retractall( tlbugger:dmsg_match(hidden,Term))).
  401
  402
  403%= 	 	 
 indent_e(?X) is det
Indent E.
  409indent_e(0):-!.
  410indent_e(X):- X > 20, XX is X-20,!,indent_e(XX).
  411indent_e(X):- catchvvnt((X < 2),_,true),write(' '),!.
  412indent_e(X):-XX is X -1,!,write(' '), indent_e(XX).
  413
  414
  415%= 	 	 
 dmsg_text_to_string_safe(?Expr, ?Forms) is det
(debug)message Text Converted To String Safely Paying Attention To Corner Cases.
  421dmsg_text_to_string_safe(Expr,Forms):-on_x_fail(text_to_string(Expr,Forms)).
  422
  423% ===================================================================
  424% Lowlevel printng
  425% ===================================================================
  426:- multifile lmconf:term_to_message_string/2.  427:- dynamic lmconf:term_to_message_string/2.
 catchvvnt(:GoalT, ?E, :GoalF) is det
Catchvvnt.
  432catchvvnt(T,E,F):-catchv(quietly(T),E,F).
  433
  434:- meta_predicate(catchvvnt(0,?,0)).  435
  436%= 	 	 
 fmt0(?X, ?Y, ?Z) is det
Format Primary Helper.

fmt0(user_error,F,A):-!,get_main_error_stream(Err),!,format(Err,F,A). fmt0(current_error,F,A):-!,get_thread_current_error(Err),!,format(Err,F,A).

  444fmt0(X,Y,Z):-catchvvnt((format(X,Y,Z),flush_output_safe(X)),E,dfmt(E:format(X,Y))).
  445
  446%= 	 	 
 fmt0(?X, ?Y) is det
Format Primary Helper.
  452fmt0(X,Y):-catchvvnt((format(X,Y),flush_output_safe),E,dfmt(E:format(X,Y))).
  453
  454%= 	 	 
 fmt0(?X) is det
Format Primary Helper.
  460fmt0(X):- (atomic(X);is_list(X)), dmsg_text_to_string_safe(X,S),!,format('~w',[S]),!.
  461fmt0(X):- (atom(X) -> catchvvnt((format(X,[]),flush_output_safe),E,dmsg(E)) ; 
  462  (lmconf:term_to_message_string(X,M) -> 'format'('~q~N',[M]);fmt_or_pp(X))).
  463
  464%= 	 	 
 fmt(?X) is det
Format.
  470fmt(X):-fresh_line,fmt_ansi(fmt0(X)).
  471
  472%= 	 	 
 fmt(?X, ?Y) is det
Format.
  478fmt(X,Y):- fresh_line,fmt_ansi(fmt0(X,Y)),!.
  479
  480%= 	 	 
 fmt(?X, ?Y, ?Z) is det
Format.
  486fmt(X,Y,Z):- fmt_ansi(fmt0(X,Y,Z)),!.
  487
  488
  489
  490:- module_transparent((format_to_message)/3).  491
  492format_to_message(Format,Args,Info):- 
  493  on_xf_cont(((( sanity(is_list(Args))-> 
  494     format(string(Info),Format,Args);
  495     (format(string(Info),'~N~n~p +++++++++++++++++ ~p~n',[Format,Args])))))).
  496
  497
  498new_line_if_needed:- flush_output,format('~N',[]),flush_output.
  499
  500%= 	 	 
 fmt9(?Msg) is det
Fmt9.
  506fmt9(Msg):- new_line_if_needed, must(fmt90(Msg)),!,new_line_if_needed.
  507
  508fmt90(fmt0(F,A)):-on_x_fail(fmt0(F,A)),!.
  509fmt90(Msg):- on_x_fail(((string(Msg)),format(Msg,[fmt90_x1,fmt90_x2,fmt90_x3]))),!.
  510fmt90(Msg):- on_x_fail((with_output_to(string(S),
  511   on_x_fail(if_defined_local(portray_clause_w_vars(Msg),fail))),format('~s',[S]))),!.
  512fmt90(Msg):- on_x_fail(format('~p.',[Msg])),!.
  513fmt90(Msg):- writeq(fmt9(Msg)).
  514
  515% :-reexport(library(ansi_term)).
  516:- use_module(library(ansi_term)).  517
  518
  519%= 	 	 
 tst_fmt is det
Tst Format.
  525tst_fmt:- make,
  526 findall(R,(clause(ansi_term:sgr_code(R, _),_),ground(R)),List),
  527 ignore((
  528        ansi_term:ansi_color(FC, _),
  529        member(FG,[hfg(FC),fg(FC)]),
  530        % ansi_term:ansi_term:ansi_color(Key, _),
  531        member(BG,[hbg(default),bg(default)]),
  532        member(R,List),
  533        % random_member(R1,List),
  534    C=[reset,R,FG,BG],
  535  fresh_line,
  536  ansi_term:ansi_format(C,' ~q ~n',[C]),fail)).
  537
  538
  539
  540%= 	 	 
 fmt_ansi(:Goal) is nondet
Format Ansi.
  546fmt_ansi(Goal):-ansicall([reset,bold,hfg(white),bg(black)],Goal).
  547
  548
  549%= 	 	 
 fmt_portray_clause(?X) is det
Format Portray Clause.
  555fmt_portray_clause(X):- renumbervars_prev(X,Y),!, portray_clause(Y).
  556
  557
  558%= 	 	 
 fmt_or_pp(?X) is det
Format Or Pretty Print.
  564fmt_or_pp(portray((X:-Y))):-!,fmt_portray_clause((X:-Y)),!.
  565fmt_or_pp(portray(X)):- !,cfunctor(X,F,A),fmt_portray_clause((pp(F,A):-X)),!.
  566fmt_or_pp(X):-format('~q~N',[X]).
  567
  568
  569%= 	 	 
 with_output_to_console(:GoalX) is det
Using Output Converted To Console.
  575with_output_to_console(X):- get_main_error_stream(Err),!,with_output_to_stream(Err,X).
  576
  577%= 	 	 
 with_output_to_main(:GoalX) is det
Using Output Converted To Main.
  583with_output_to_main(X):- get_main_error_stream(Err),!,with_output_to_stream(Err,X).
  584
  585
  586%= 	 	 
 dfmt(?X) is det
Dfmt.
  592dfmt(X):- get_thread_current_error(Err),!,with_output_to_stream(Err,fmt(X)).
  593
  594%= 	 	 
 dfmt(?X, ?Y) is det
Dfmt.
  600dfmt(X,Y):- get_thread_current_error(Err), with_output_to_stream(Err,fmt(X,Y)).
  601
  602
  603%= 	 	 
 with_output_to_stream(?Stream, :Goal) is det
Using Output Converted To Stream.
  609with_output_to_stream(Stream,Goal):-
  610   current_output(Saved),
  611   scce_orig(set_output(Stream),
  612         Goal,
  613         set_output(Saved)).
  614
  615
  616%= 	 	 
 to_stderror(:Goal) is nondet
Converted To Stderror.
  622to_stderror(Goal):- get_thread_current_error(Err), with_output_to_stream(Err,Goal).
  623
  624
  625
  626:- dynamic dmsg_log/3.  627
  628
  629:- dynamic(logLevel/2).  630:- module_transparent(logLevel/2).  631:- multifile(logLevel/2).  632
  633
  634:- dynamic logger_property/2.  635
  636%= 	 	 
 logger_property(?VALUE1, ?VALUE2, ?VALUE3) is det
Logger Property.
  642logger_property(todo,once,true).
  643
  644
  645
  646%= 	 	 
 setLogLevel(?M, ?L) is det
Set Log Level.
  652setLogLevel(M,L):-retractall(logLevel(M,_)),(nonvar(L)->asserta(logLevel(M,L));true).
  653
  654
  655%= 	 	 
 logLevel(?S, ?Z) is det
Log Level.
  661logLevel(debug,ERR):-get_thread_current_error(ERR).
  662logLevel(error,ERR):-get_thread_current_error(ERR).
  663logLevel(private,none).
  664logLevel(S,Z):-current_stream(_X,write,Z),dtrace,stream_property(Z,alias(S)).
  665
  666
  667%= 	 	 
 loggerReFmt(?L, ?LRR) is det
Logger Re Format.
  673loggerReFmt(L,LRR):-logLevel(L,LR),L \==LR,!,loggerReFmt(LR,LRR),!.
  674loggerReFmt(L,L).
  675
  676
  677%= 	 	 
 loggerFmtReal(?S, ?F, ?A) is det
Logger Format Real.
  683loggerFmtReal(none,_F,_A):-!.
  684loggerFmtReal(S,F,A):-
  685  current_stream(_,write,S),
  686    fmt(S,F,A),
  687    flush_output_safe(S),!.
  688
  689
  690
  691:- thread_local tlbugger:is_with_dmsg/1.  692
  693
  694%= 	 	 
 with_dmsg(?Functor, :Goal) is det
Using (debug)message.
  700with_dmsg(Functor,Goal):-
  701   locally(tlbugger:is_with_dmsg(Functor),Goal).
  702
  703
  704:- use_module(library(listing)).  705
  706%= 	 	 
 sformat(?Str, ?Msg, ?Vs, ?Opts) is det
Sformat.
  712sformat(Str,Msg,Vs,Opts):- nonvar(Msg),cfunctor(Msg,':-',_),!,with_output_to_each(string(Str),
  713   (current_output(CO),portray_clause_w_vars(CO,Msg,Vs,Opts))).
  714sformat(Str,Msg,Vs,Opts):- with_output_to_each(chars(Codes),(current_output(CO),portray_clause_w_vars(CO,':-'(Msg),Vs,Opts))),append([_,_,_],PrintCodes,Codes),'sformat'(Str,'   ~s',[PrintCodes]),!.
  715
  716
  717free_of_attrs_dmsg(Term):- var(Term),!,(get_attrs(Term,Attrs)-> Attrs==[] ; true).
  718free_of_attrs_dmsg(Term):- term_attvars(Term,Vs),!,(Vs==[]->true;maplist(free_of_attrs_dmsg,Vs)).
  719
  720
  721:- use_module(library(listing)).  722
  723%= 	 	 
 portray_clause_w_vars(?Out, ?Msg, ?Vs, ?Options) is det
Portray Clause W Variables.
  730portray_clause_w_vars(Out,Msg,Vs,Options):- free_of_attrs_dmsg(Msg+Vs),!, portray_clause_w_vars5(Out,Msg,Vs,Options).
  731portray_clause_w_vars(Out,Msg,Vs,Options):- fail, if_defined_local(serialize_attvars_now(Msg+Vs,SMsg+SVs),fail),!,
  732     \+ \+ portray_clause_w_vars2(Out,SMsg,SVs,Options).
  733portray_clause_w_vars(Out,Msg,Vs,Options):- \+ \+ portray_clause_w_vars2(Out,Msg,Vs,Options).
  734 
  735portray_clause_w_vars2(Out,Msg,Vs,Options):- free_of_attrs_dmsg(Msg+Vs),!, portray_clause_w_vars5(Out,Msg,Vs,Options).
  736portray_clause_w_vars2(Out,Msg,Vs,Options):-
  737   term_attvars(Msg,AttVars),
  738   copy_term(Msg+AttVars,Msg+AttVars,Goals),
  739   portray_append_goals(Msg,Goals,GMsg),
  740   portray_clause_w_vars5(Out,GMsg,Vs,Options).
  741
  742portray_clause_w_vars5(Out,Msg,Vs,Options):-
  743  copy_term_nat(v(Msg,Vs,Options),v(CMsg,CVs,COptions)),
  744  portray_clause_w_vars55(Out,CMsg,CVs,COptions),!.
  745portray_clause_w_vars55(Out,Msg,Vs,Options):-
  746 \+ \+ (( 
  747 prolog_listing:do_portray_clause(Out,Msg,
  748  [variable_names(Vs),numbervars(true),
  749      attributes(ignore),
  750      character_escapes(true),quoted(true)|Options]))),!.
  751
  752is_var_name_goal(C):-compound(C),C=name_variable(_,_).
  753
  754portray_append_goals(Var,Goals,Var):- Goals==[],!.
  755portray_append_goals(Var,Goals,Var):- Goals==true,!.
  756portray_append_goals(Var,Goals,VarO):- exclude(is_var_name_goal,Goals,NewGoals)->Goals\==NewGoals,!,
  757   portray_append_goals(Var,NewGoals,VarO).
  758portray_append_goals(Var,Goals,(maplist(call,Goals),Var)):-var(Var),!.
  759portray_append_goals(H:-B,Goals,H:-CGMsg):-!,portray_append_goals(B,Goals,CGMsg).
  760portray_append_goals(H:B,Goals,H:CGMsg):-!,portray_append_goals(B,Goals,CGMsg).
  761portray_append_goals(Var,Goals,(maplist(call,Goals),Var)).
  762
  763%= 	 	 
 portray_clause_w_vars(?Msg, ?Vs, ?Options) is det
Portray Clause W Variables.
  769portray_clause_w_vars(Msg,Vs,Options):- portray_clause_w_vars(current_output,Msg,Vs,Options).
  770
  771%= 	 	 
 portray_clause_w_vars(?Msg, ?Options) is det
Portray Clause W Variables.
  777portray_clause_w_vars(Msg,Options):- source_variables_lwv(Msg,Vs),portray_clause_w_vars(current_output,Msg,Vs,Options).
  778
  779grab_varnames(Msg,Vs2):- term_attvars(Msg,AttVars),grab_varnames2(AttVars,Vs2).
  780
  781grab_varnames2([],[]):-!.
  782grab_varnames2([AttV|AttVS],Vs2):-
  783    grab_varnames2(AttVS,VsMid),!,
  784     (get_attr(AttV,vn,Name) -> Vs2 = [Name=AttV|VsMid] ; VsMid=       Vs2),!.
  785   
  786
  787
  788%= 	 	 
 source_variables_lwv(?AllS) is det
Source Variables Lwv.
  794source_variables_lwv(Msg,AllS):-
  795  (prolog_load_context(variable_names,Vs1);Vs1=[]),
  796   grab_varnames(Msg,Vs2),
  797   zotrace(catch((parent_goal('$toplevel':'$execute_goal2'(_, Vs3),_);Vs3=[]),_,Vs3=[])),
  798   ignore(Vs3=[]),
  799   append(Vs3,Vs2,Vs32),append(Vs32,Vs1,All),!,list_to_set(All,AllS).
  800   % set_varname_list( AllS).
  801
  802
  803
  804:- export(portray_clause_w_vars/1).  805
  806%= 	 	 
 portray_clause_w_vars(?Msg) is det
Portray Clause W Variables.
  812portray_clause_w_vars(Msg):- portray_clause_w_vars(Msg,[]),!.
  813
  814
  815%= 	 	 
 print_prepended(?Pre, ?S) is det
Print Prepended.
  821print_prepended(Pre,S):-atom_concat(L,' ',S),!,print_prepended(Pre,L).
  822print_prepended(Pre,S):-atom_concat(L,'\n',S),!,print_prepended(Pre,L).
  823print_prepended(Pre,S):-atom_concat('\n',L,S),!,print_prepended(Pre,L).
  824print_prepended(Pre,S):-atomics_to_string(L,'\n',S),print_prepended_lines(Pre,L).
  825
  826%= 	 	 
 print_prepended_lines(?Pre, :TermARG2) is det
Print Prepended Lines.
  832print_prepended_lines(_Pre,[]):- format('~N',[]).
  833print_prepended_lines(Pre,[H|T]):-format('~N~w~w',[Pre,H]),print_prepended_lines(Pre,T).
  834
  835
  836
  837%= 	 	 
 in_cmt(:Goal) is nondet
In Comment.
  844% in_cmt(Goal):- tlbugger:no_slow_io,!,format('~N/*~n',[]),call_cleanup(Goal,format('~N*/~n',[])).
  845in_cmt(Goal):- call_cleanup(prepend_each_line('% ',Goal),format('~N',[])).
  846
  847
  848%= 	 	 
 with_current_indent(:Goal) is nondet
Using Current Indent.
  854with_current_indent(Goal):- 
  855   get_indent_level(Indent), 
  856   indent_to_spaces(Indent,Space),
  857   prepend_each_line(Space,Goal).
  858
  859
  860%= 	 	 
 indent_to_spaces(:PRED3N, ?Out) is det
Indent Converted To Spaces.
  866indent_to_spaces(1,' '):-!.
  867indent_to_spaces(0,''):-!.
  868indent_to_spaces(2,'  '):-!.
  869indent_to_spaces(3,'   '):-!.
  870indent_to_spaces(N,Out):- 1 is N rem 2,!, N1 is N-1, indent_to_spaces(N1,Spaces),atom_concat(' ',Spaces,Out).
  871indent_to_spaces(N,Out):- N2 is N div 2, indent_to_spaces(N2,Spaces),atom_concat(Spaces,Spaces,Out).
  872
  873
  874%= 	 	 
 mesg_color(:TermT, ?C) is det
Mesg Color.
  880mesg_color(_,[reset]):-tlbugger:no_slow_io,!.
  881mesg_color(T,C):-var(T),!,C=[blink(slow),fg(red),hbg(black)],!.
  882mesg_color(T,C):- if_defined(is_sgr_on_code(T)),!,C=T.
  883mesg_color(T,C):-cyclic_term(T),!,C=[reset,blink(slow),bold].
  884mesg_color("",C):- !,C=[blink(slow),fg(red),hbg(black)],!.
  885mesg_color(T,C):- string(T),!,must(f_word(T,F)),!,functor_color(F,C).
  886mesg_color([_,_,_,T|_],C):-atom(T),mesg_color(T,C).
  887mesg_color([T|_],C):-atom(T),mesg_color(T,C).
  888mesg_color(T,C):-(atomic(T);is_list(T)), dmsg_text_to_string_safe(T,S),!,mesg_color(S,C).
  889mesg_color(T,C):-not(compound(T)),term_to_atom(T,A),!,mesg_color(A,C).
  890mesg_color(succeed(T),C):-nonvar(T),mesg_color(T,C).
  891% mesg_color((T),C):- \+ \+ ((predicate_property(T,meta_predicate(_)))),arg(_,T,E),compound(E),!,mesg_color(E,C).
  892mesg_color(=(T,_),C):-nonvar(T),mesg_color(T,C).
  893mesg_color(debug(T),C):-nonvar(T),mesg_color(T,C).
  894mesg_color(_:T,C):-nonvar(T),!,mesg_color(T,C).
  895mesg_color(:- T,C):-nonvar(T),!,mesg_color(T,C).
  896mesg_color(H :- T, [bold|C]):-nonvar(T),!,mesg_color(H,C).
  897mesg_color(T,C):-cfunctor(T,F,_),member(F,[color,ansi]),compound(T),arg(1,T,C),nonvar(C).
  898mesg_color(T,C):-cfunctor(T,F,_),member(F,[succeed,must,mpred_op_prolog]),compound(T),arg(1,T,E),nonvar(E),!,mesg_color(E,C).
  899mesg_color(T,C):-cfunctor(T,F,_),member(F,[fmt0,msg]),compound(T),arg(2,T,E),nonvar(E),!,mesg_color(E,C).
  900mesg_color(T,C):-predef_functor_color(F,C),mesg_arg1(T,F).
  901mesg_color(T,C):-nonvar(T),defined_message_color(F,C),matches_term(F,T),!.
  902mesg_color(T,C):-cfunctor(T,F,_),!,functor_color(F,C),!.
  903
  904
  905
  906%= 	 	 
 prepend_each_line(?Pre, :Goal) is nondet
Prepend Each Line.
  912prepend_each_line(Pre,Goal):-
  913  with_output_to_each(string(Str),Goal)*->once(print_prepended(Pre,Str)).
  914
  915:- meta_predicate if_color_debug(0).  916:- meta_predicate if_color_debug(0,0).  917
  918%= 	 	 
 if_color_debug is det
If Color Debug.
  924if_color_debug:-current_prolog_flag(dmsg_color,true).
  925
  926%= 	 	 
 if_color_debug(:Goal) is nondet
If Color Debug.
  932if_color_debug(Goal):- if_color_debug(Goal, true).
  933
  934%= 	 	 
 if_color_debug(:Goal, :GoalUnColor) is det
If Color Debug.
  940if_color_debug(Goal,UnColor):- if_color_debug->Goal;UnColor.
  941
  942
  943
  944color_line(C,N):- 
  945 zotrace((
  946  format('~N',[]),
  947    forall(between(1,N,_),ansi_format([fg(C)],"%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%\n",[])))).
  948
  949
  950
  951% % = :- export((portray_clause_w_vars/4,ansicall/3,ansi_control_conv/2)).
  952
  953:- thread_local(tlbugger:skipDumpST9/0).  954:- thread_local(tlbugger:skipDMsg/0).  955
  956% @(dmsg0(succeed(S_1)),[S_1=logic])
  957
  958
  959:- thread_local(tlbugger:no_slow_io/0).  960:- multifile(tlbugger:no_slow_io/0).  961%:- asserta(tlbugger:no_slow_io).
  962
  963:- create_prolog_flag(retry_undefined,none,[type(term),keep(true)]).  964
  965%= 	 	 
 dmsg(?C) is det
(debug)message.
  971dmsg(C):- zotrace((tlbugger:no_slow_io,!,writeln(main_error,dmsg(C)))).
  972dmsg(V):- zotrace((locally(set_prolog_flag(retry_undefined,none), if_defined_local(dmsg0(V),logicmoo_util_catch:ddmsg(V))))),!.
  973%dmsg(F,A):- zotrace((tlbugger:no_slow_io,on_x_fail(format(atom(S),F,A))->writeln(dmsg(S));writeln(dmsg_fail(F,A)))),!.
  974
  975:- system:import(dmsg/1).  976% system:dmsg(O):-logicmoo_util_dmsg:dmsg(O).
  977%= 	 	 
 dmsg(?F, ?A) is det
(debug)message.
  983dmsg(F,A):- locally(set_prolog_flag(retry_undefined, none),if_defined_local(dmsg0(F,A),logicmoo_util_catch:ddmsg(F,A))),!.
  984
  985with_output_to_main_error(G):- !,call(G).
  986
  987with_output_to_main_error(G):-
  988  set_prolog_flag(occurs_check,false),
  989  stream_property(Err,file_no(2)),
  990  with_output_to_each(Err,G).
  991/*
  992  ignore((get_thread_current_error(TErr),
  993    \+ same_streams(TErr,Err),
  994    with_output_to_each(TErr,G))).
  995  
  996same_streams(TErr,Err):- TErr==Err,!.
  997same_streams(TErr,Err):- stream_property(TErr,file_no(A)),stream_property(Err,file_no(B)),!,A==B.
  998*/
 wdmsg(?X) is semidet
Wdmsg.
 1004wdmsg(X):- zotrace(((current_prolog_flag(dmsg_level,never)->true;(show_source_location),
 1005 with_all_dmsg(dmsg(X))))),!.
 wdmsg(?F, ?X) is semidet
Wdmsg.
 1011wdmsg(_,_):- current_prolog_flag(dmsg_level,never),!.
 1012wdmsg(F,X):- quietly(ignore(with_all_dmsg(dmsg(F,X)))),!.
 wdmsg(?F, ?X) is semidet
Wdmsg.
 1019wdmsg(W,F,X):- quietly(ignore(with_all_dmsg(dmsg(W,F,X)))),!.
 1020
 1021
 1022:- meta_predicate wdmsgl(1,+). 1023:- meta_predicate wdmsgl(+,1,+).
 wdmsgl(?CNF) is det
Wdmsgl.
 1029wdmsgl(X):- zotrace(wdmsgl(fmt9,X)),!.
 1030wdmsgl(With,X):- (must((wdmsgl('',With,X)))),!.
 1031
 1032wdmsgl(NAME,With,CNF):- is_ftVar(CNF),!,call(With,NAME=CNF).
 1033wdmsgl(_,With,(C:-CNF)):- call(With,(C :-CNF)),!.
 1034wdmsgl(_,With,'==>'(CNF,C)):- call(With,(C :- (fwc, CNF))),!.
 1035wdmsgl(_,With,(NAME=CNF)):- wdmsgl(NAME,With,CNF),!.
 1036wdmsgl(NAME,With,CNF):- is_list(CNF),must_maplist_det(wdmsgl(NAME,With),CNF),!.
 1037wdmsgl('',With,(C:-CNF)):- call(With,(C :-CNF)),!.
 1038wdmsgl(NAME,With,(C:-CNF)):- call(With,(NAME: C :-CNF)),!.
 1039wdmsgl(NAME,With,(:-CNF)):- call(With,(NAME:-CNF)),!.
 1040wdmsgl(NAME,With,CNF):- call(With,NAME:-CNF),!.
 dmsginfo(?V) is det
Dmsginfo.
 1048dmsginfo(V):-dmsg(info(V)).
 1049
 1050%= 	 	 
 dmsg0(?F, ?A) is det
(debug)message Primary Helper.
 1056dmsg0(_,_):- current_prolog_flag(dmsg_level,never),!.
 1057dmsg0(F,A):- is_sgr_on_code(F),!,dmsg(ansi(F,A)),!.
 1058dmsg0(F,A):- with_output_to_main_error(dmsg(fmt0(F,A))),!.
 1059
 1060%= 	 	 
 vdmsg(?L, ?F) is det
Vdmsg.
 1066vdmsg(L,F):-loggerReFmt(L,LR),loggerFmtReal(LR,F,[]).
 1067
 1068%= 	 	 
 dmsg(?L, ?F, ?A) is det
(debug)message.
 1074dmsg(L,F,A):-loggerReFmt(L,LR),loggerFmtReal(LR,F,A).
 1075
 1076:- thread_local(tlbugger:in_dmsg/1). 1077:- dynamic tlbugger:dmsg_hook/1. 1078:- multifile tlbugger:dmsg_hook/1. 1079:- thread_local(t_l:no_kif_var_coroutines/1). 1080
 1081
 1082%= 	 	 
 dmsg0(?V) is det
(debug)message Primary Helper.
 1088dmsg0(V):-zotrace(locally(local_override(no_kif_var_coroutines,true),ignore(with_output_to_main_error(dmsg00(V))))),!.
 1089
 1090%= 	 	 
 dmsg00(?V) is det
(debug)message Primary Helper Primary Helper.
 1096dmsg00(V):-cyclic_term(V),!,writeln(cyclic_term),flush_output,writeln(V),!.
 1097dmsg00(V):- catch(dumpst:simplify_goal_printed(V,VV),_,fail),!,dmsg000(VV),!.
 1098dmsg00(V):- dmsg000(V),!.
 dmsg000(?V) is det
(debug)message Primary Helper Primary Helper Primary Helper.
 1105dmsg000(V):-
 1106 with_output_to_main_error(
 1107   (zotrace(format(string(K),'~p',[V])),
 1108   (tlbugger:in_dmsg(K)-> dmsg5(V);  % format_to_error('~N% ~q~n',[dmsg0(V)]) ;
 1109      asserta(tlbugger:in_dmsg(K),Ref),call_cleanup(dmsg1(V),erase(Ref))))),!.
 1110
 1111% = :- export(dmsg1/1).
 1112
 1113
 1114%= 	 	 
 dmsg1(?V) is det
(debug)message Secondary Helper.
 1120dmsg1(V):- tlbugger:is_with_dmsg(FP),!,univ_safe_2(FP,FPL),append(FPL,[V],VVL),univ_safe_2(VV,VVL),once(dmsg1(VV)).
 1121dmsg1(_):- current_prolog_flag(dmsg_level,never),!.
 1122dmsg1(V):- var(V),!,dmsg1(warn(dmsg_var(V))).
 1123dmsg1(NC):- cyclic_term(NC),!,dtrace,format_to_error('~N% ~q~n',[dmsg_cyclic_term_1]).
 1124dmsg1(NC):- tlbugger:skipDMsg,!,loop_check_early(dmsg2(NC),format_to_error('~N% ~q~n',[skipDMsg])),!.
 1125dmsg1(V):- locally(tlbugger:skipDMsg,((once(dmsg2(V)), ignore((tlbugger:dmsg_hook(V),fail))))),!.
 1126
 1127% = :- export(dmsg2/1).
 1128
 1129%= 	 	 
 dmsg2(:TermNC) is det
(debug)message Extended Helper.
 1135dmsg2(NC):- cyclic_term(NC),!,format_to_error('~N% ~q~n',[dmsg_cyclic_term_2]).
 1136dmsg2(NC):- var(NC),!,format_to_error('~N% DMSG VAR ~q~n',[NC]).
 1137dmsg2(skip_dmsg(_)):-!.
 1138%dmsg2(C):- \+ current_prolog_flag(dmsg_level,always), dmsg_hides_message(C),!.
 1139%dmsg2(trace_or_throw(V)):- dumpST(350),dmsg(warning,V),fail.
 1140%dmsg2(error(V)):- dumpST(250),dmsg(warning,V),fail.
 1141%dmsg2(warn(V)):- dumpST(150),dmsg(warning,V),fail.
 1142dmsg2(Msg):-zotrace((tlbugger:no_slow_io,!,dmsg3(Msg))),!.
 1143dmsg2(ansi(Ctrl,Msg)):- !, ansicall(Ctrl,dmsg3(Msg)).
 1144dmsg2(color(Ctrl,Msg)):- !, ansicall(Ctrl,dmsg3(Msg)).
 1145dmsg2(Msg):- mesg_color(Msg,Ctrl),ansicall(Ctrl,dmsg3(Msg)).
 1146
 1147
 1148%= 	 	 
 dmsg3(?C) is det
Dmsg3.
 1154dmsg3(C):- tlbugger:no_slow_io,!,writeln(dmsg3(C)).
 1155dmsg3(C):- strip_module(C,_,SM),
 1156  ((cfunctor(SM,Topic,_),debugging(Topic,_True_or_False),logger_property(Topic,once,true),!,
 1157      (dmsg_log(Topic,_Time,C) -> true ; ((get_time(Time),asserta(dmsg_log(todo,Time,C)),!,dmsg4(C)))))),!.
 1158
 1159dmsg3(C):-dmsg4(C),!.
 1160
 1161
 1162%= 	 	 
 dmsg4(?Msg) is det
Dmsg4.
 1168dmsg4(_):- current_prolog_flag(dmsg_level,never),!.
 1169dmsg4(_):- zotrace(show_source_location),fail.
 1170dmsg4(Msg):-dmsg5(Msg).
 1171
 1172
 1173%= 	 	 
 dmsg5(?Msg) is det
Dmsg5.
 1179dmsg5(Msg):- to_stderror(in_cmt(fmt9(Msg))).
 1180
 1181%= 	 	 
 dmsg5(?Msg, ?Args) is det
Dmsg5.
 1187dmsg5(Msg,Args):- dmsg5(fmt0(Msg,Args)).
 1188
 1189
 1190
 1191%= 	 	 
 get_indent_level(:PRED2Max) is det
Get Indent Level.
 1197get_indent_level(Max) :- if_prolog(swi,((prolog_current_frame(Frame),prolog_frame_attribute(Frame,level,FD)))),Depth is FD div 5,Max is min(Depth,40),!.
 1198get_indent_level(2):-!.
 1199
 1200
 1201/*
 1202ansifmt(+Attributes, +Format, +Args) is det
 1203Format text with ANSI attributes. This predicate behaves as format/2 using Format and Args, but if the current_output is a terminal, it adds ANSI escape sequences according to Attributes. For example, to print a text in bold cyan, do
 1204?- ansifmt([bold,fg(cyan)], 'Hello ~w', [world]).
 1205Attributes is either a single attribute or a list thereof. The attribute names are derived from the ANSI specification. See the source for sgr_code/2 for details. Some commonly used attributes are:
 1206
 1207bold
 1208underline
 1209fg(Color), bg(Color), hfg(Color), hbg(Color)
 1210Defined color constants are below. default can be used to access the default color of the terminal.
 1211
 1212black, red, green, yellow, blue, magenta, cyan, white
 1213ANSI sequences are sent if and only if
 1214
 1215The current_output has the property tty(true) (see stream_property/2).
 1216The Prolog flag color_term is true.
 1217
 1218ansifmt(Ctrl, Format, Args) :- ansifmt(current_output, Ctrl, Format, Args).
 1219
 1220ansifmt(Stream, Ctrl, Format, Args) :-
 1221     % we can "assume"
 1222        % ignore(((stream_property(Stream, tty(true)),current_prolog_flag(color_term, true)))), !,
 1223	(   is_list(Ctrl)
 1224	->  maplist(ansi_term:sgr_code_ex, Ctrl, Codes),
 1225	    atomic_list_concat(Codes, (';'), OnCode)
 1226	;   ansi_term:sgr_code_ex(Ctrl, OnCode)
 1227	),
 1228	'format'(string(Fmt), '\e[~~wm~w\e[0m', [Format]),
 1229        retractall(tlbugger:last_used_color(Ctrl)),asserta(tlbugger:last_used_color(Ctrl)),
 1230	'format'(Stream, Fmt, [OnCode|Args]),
 1231	flush_output,!.
 1232ansifmt(Stream, _Attr, Format, Args) :- 'format'(Stream, Format, Args).
 1233
 1234*/
 1235
 1236:- use_module(library(ansi_term)). 1237
 1238% = :- export(ansifmt/2).
 1239
 1240%= 	 	 
 ansifmt(?Ctrl, ?Fmt) is det
Ansifmt.
 1246ansifmt(Ctrl,Fmt):- colormsg(Ctrl,Fmt).
 1247% = :- export(ansifmt/3).
 1248
 1249%= 	 	 
 ansifmt(?Ctrl, ?F, ?A) is det
Ansifmt.
 1255ansifmt(Ctrl,F,A):- colormsg(Ctrl,(format(F,A))).
 1256
 1257
 1258
 1259%= 	 	 
 debugm(?X) is det
Debugm.
 1265debugm(X):-zotrace((compound(X),cfunctor(X,F,_),!,debugm(F,X))),!.
 1266debugm(X):-zotrace((debugm(X,X))).
 1267
 1268%= 	 	 
 debugm(?Why, ?Msg) is det
Debugm.
 1274debugm(Why,Msg):- dmsg(debugm(Why,Msg)),!,debugm0(Why,Msg).
 1275debugm0(Why,Msg):- zotrace(( \+ debugging(mpred), \+ debugging(Why), \+ debugging(mpred(Why)),!, debug(Why,'~N~p~n',[Msg]))),!.
 1276debugm0(Why,Msg):- zotrace(( debug(Why,'~N~p~n',[Msg]))),!.
 colormsg(?Ctrl, ?Msg) is det
Colormsg.
 1284colormsg(d,Msg):- mesg_color(Msg,Ctrl),!,colormsg(Ctrl,Msg).
 1285colormsg(Ctrl,Msg):- ansicall(Ctrl,fmt0(Msg)).
 1286
 1287% = :- export(ansicall/2).
 1288
 1289%= 	 	 
 ansicall(?Ctrl, :Goal) is nondet
Ansicall.
 1296% ansicall(_,Goal):-!,Goal.
 1297ansicall(Ctrl,Goal):- zotrace((current_output(Out), ansicall(Out,Ctrl,Goal))).
 1298
 1299
 1300%= 	 	 
 ansi_control_conv(?Ctrl, ?CtrlO) is det
Ansi Control Conv.
 1306ansi_control_conv(Ctrl,CtrlO):-tlbugger:no_slow_io,!,flatten([Ctrl],CtrlO),!.
 1307ansi_control_conv([],[]):-!.
 1308ansi_control_conv([H|T],HT):-!,ansi_control_conv(H,HH),!,ansi_control_conv(T,TT),!,flatten([HH,TT],HT),!.
 1309ansi_control_conv(warn,Ctrl):- !, ansi_control_conv(warning,Ctrl),!.
 1310ansi_control_conv(Level,Ctrl):- ansi_term:level_attrs(Level,Ansi),Level\=Ansi,!,ansi_control_conv(Ansi,Ctrl).
 1311ansi_control_conv(Color,Ctrl):- ansi_term:ansi_color(Color,_),!,ansi_control_conv(fg(Color),Ctrl).
 1312ansi_control_conv(Ctrl,CtrlO):-flatten([Ctrl],CtrlO),!.
 1313
 1314
 1315
 1316%= 	 	 
 is_tty(?Out) is det
If Is A Tty.
 1322:- multifile(tlbugger:no_colors/0). 1323:- thread_local(tlbugger:no_colors/0). 1324is_tty(Out):- \+ tlbugger:no_colors, \+ tlbugger:no_slow_io, is_stream(Out),stream_property(Out,tty(true)).
 1325
 1326
 1327%= 	 	 
 ansicall(?Out, ?UPARAM2, :Goal) is nondet
Ansicall.
 1333ansicall(Out,_,Goal):- \+ is_tty(Out),!,Goal.
 1334ansicall(_Out,_,Goal):- tlbugger:skipDumpST9,!,Goal.
 1335
 1336% in_pengines:- if_defined_local(relative_frame(source_context_module,pengines,_)).
 1337
 1338ansicall(_,_,Goal):-tlbugger:no_slow_io,!,Goal.
 1339ansicall(Out,CtrlIn,Goal):- once(ansi_control_conv(CtrlIn,Ctrl)),  CtrlIn\=Ctrl,!,ansicall(Out,Ctrl,Goal).
 1340ansicall(_,_,Goal):- if_defined_local(in_pengines,fail),!,Goal.
 1341ansicall(Out,Ctrl,Goal):-
 1342   retractall(tlbugger:last_used_color(_)),asserta(tlbugger:last_used_color(Ctrl)),ansicall0(Out,Ctrl,Goal),!.
 1343
 1344
 1345%= 	 	 
 ansicall0(?Out, ?Ctrl, :Goal) is nondet
Ansicall Primary Helper.
 1351ansicall0(Out,[Ctrl|Set],Goal):-!, ansicall0(Out,Ctrl,ansicall0(Out,Set,Goal)).
 1352ansicall0(_,[],Goal):-!,Goal.
 1353ansicall0(Out,Ctrl,Goal):-if_color_debug(ansicall1(Out,Ctrl,Goal),keep_line_pos_w_w(Out, Goal)).
 1354
 1355
 1356%= 	 	 
 ansicall1(?Out, ?Ctrl, :Goal) is nondet
Ansicall Secondary Helper.
 1362ansicall1(Out,Ctrl,Goal):-
 1363   zotrace((must(sgr_code_on_off(Ctrl, OnCode, OffCode)),!,
 1364     keep_line_pos_w_w(Out, (format(Out, '\e[~wm', [OnCode]))),
 1365	call_cleanup(Goal,
 1366           keep_line_pos_w_w(Out, (format(Out, '\e[~wm', [OffCode])))))).
 1367/*
 1368ansicall(S,Set,Goal):-
 1369     call_cleanup((
 1370         stream_property(S, tty(true)), current_prolog_flag(color_term, true), !,
 1371	(is_list(Ctrl) ->  maplist(sgr_code_on_off, Ctrl, Codes, OffCodes),
 1372          atomic_list_concat(Codes, (';'), OnCode) atomic_list_concat(OffCodes, (';'), OffCode) ;   sgr_code_on_off(Ctrl, OnCode, OffCode)),
 1373        keep_line_pos_w_w(S, (format(S,'\e[~wm', [OnCode])))),
 1374	call_cleanup(Goal,keep_line_pos_w_w(S, (format(S, '\e[~wm', [OffCode]))))).
 1375
 1376
 1377*/
 1378
 1379
 1380
 1381
 1382
 1383%= 	 	 
 keep_line_pos_w_w(?S, :GoalG) is det
Keep Line Pos.
 1389keep_line_pos_w_w(S, G) :-
 1390       (stream_property(S, position(Pos)),stream_position_data(line_position, Pos, LPos)) ->
 1391         call_cleanup(G, set_stream_line_position_safe(S, LPos)) ;
 1392         call(G).
 1393
 1394set_stream_line_position_safe(S,Pos):-
 1395  catch(set_stream(S, line_position(Pos)),E,dmsg(error(E))).
 1396
 1397:- multifile(tlbugger:term_color0/2). 1398:- dynamic(tlbugger:term_color0/2). 1399
 1400
 1401%tlbugger:term_color0(retract,magenta).
 1402%tlbugger:term_color0(retractall,magenta).
 1403
 1404%= 	 	 
 term_color0(?VALUE1, ?VALUE2) is det
Hook To [term_color0/2] For Module Logicmoo_util_dmsg. Term Color Primary Helper.
 1411tlbugger:term_color0(assertz,hfg(green)).
 1412tlbugger:term_color0(ainz,hfg(green)).
 1413tlbugger:term_color0(aina,hfg(green)).
 1414tlbugger:term_color0(mpred_op,hfg(blue)).
 1415
 1416
 1417
 1418%= 	 	 
 f_word(?T, ?A) is det
Functor Word.
 1424f_word("",""):-!.
 1425f_word(T,A):-concat_atom(List,' ',T),member(A,List),atom(A),atom_length(A,L),L>0,!.
 1426f_word(T,A):-concat_atom(List,'_',T),member(A,List),atom(A),atom_length(A,L),L>0,!.
 1427f_word(T,A):- string_to_atom(T,P),sub_atom(P,0,10,_,A),A\==P,!.
 1428f_word(T,A):- string_to_atom(T,A),!.
 1429
 1430
 1431%= 	 	 
 mesg_arg1(:TermT, ?TT) is det
Mesg Argument Secondary Helper.
 1437mesg_arg1(T,_TT):-var(T),!,fail.
 1438mesg_arg1(_:T,C):-nonvar(T),!,mesg_arg1(T,C).
 1439mesg_arg1(T,TT):-not(compound(T)),!,T=TT.
 1440mesg_arg1(T,C):-compound(T),arg(1,T,F),nonvar(F),!,mesg_arg1(F,C).
 1441mesg_arg1(T,F):-cfunctor(T,F,_).
 1442
 1443
 1444% = :- export(defined_message_color/2).
 1445:- dynamic(defined_message_color/2). 1446
 1447
 1448%= 	 	 
 defined_message_color(?A, ?B) is det
Defined Message Color.
 1454defined_message_color(todo,[fg(red),bg(black),underline]).
 1455%defined_message_color(error,[fg(red),hbg(black),bold]).
 1456defined_message_color(warn,[fg(black),hbg(red),bold]).
 1457defined_message_color(A,B):-tlbugger:term_color0(A,B).
 1458
 1459
 1460
 1461%= 	 	 
 predef_functor_color(?F, ?C) is det
Predef Functor Color.
 1467predef_functor_color(F,C):- defined_message_color(F,C),!.
 1468predef_functor_color(F,C):- defined_message_color(F/_,C),!.
 1469predef_functor_color(F,C):- tlbugger:term_color0(F,C),!.
 1470
 1471
 1472%= 	 	 
 functor_color(?F, ?C) is det
Functor Color.
 1478functor_color(F,C):- predef_functor_color(F,C),!.
 1479functor_color(F,C):- next_color(C),ignore(on_x_fail(assertz(tlbugger:term_color0(F,C)))),!.
 1480
 1481
 1482:- thread_local(tlbugger:last_used_color/1). 1483
 1484% tlbugger:last_used_color(pink).
 1485
 1486
 1487%= 	 	 
 last_used_fg_color(?LFG) is det
Last Used Fg Color.
 1493last_used_fg_color(LFG):-tlbugger:last_used_color(LU),fg_color(LU,LFG),!.
 1494last_used_fg_color(default).
 1495
 1496
 1497%= 	 	 
 good_next_color(?C) is det
Good Next Color.
 1503good_next_color(C):-var(C),!,trace_or_throw(var_good_next_color(C)),!.
 1504good_next_color(C):- last_used_fg_color(LFG),fg_color(C,FG),FG\=LFG,!.
 1505good_next_color(C):- not(unliked_ctrl(C)).
 1506
 1507
 1508%= 	 	 
 unliked_ctrl(?X) is det
Unliked Ctrl.
 1514unliked_ctrl(fg(blue)).
 1515unliked_ctrl(fg(black)).
 1516unliked_ctrl(fg(red)).
 1517unliked_ctrl(bg(white)).
 1518unliked_ctrl(hbg(white)).
 1519unliked_ctrl(X):-is_list(X),member(E,X),nonvar(E),unliked_ctrl(E).
 1520
 1521
 1522%= 	 	 
 fg_color(?LU, ?FG) is det
Fg Color.
 1528fg_color(LU,FG):-member(fg(FG),LU),FG\=white,!.
 1529fg_color(LU,FG):-member(hfg(FG),LU),FG\=white,!.
 1530fg_color(_,default).
 1531
 1532% = :- export(random_color/1).
 1533
 1534%= 	 	 
 random_color(?M) is det
Random Color.
 1540random_color([reset,M,FG,BG,font(Font)]):-Font is random(8),
 1541  findall(Cr,ansi_term:ansi_color(Cr, _),L),
 1542  random_member(E,L),
 1543  random_member(FG,[hfg(E),fg(E)]),not(unliked_ctrl(FG)),
 1544  contrasting_color(FG,BG), not(unliked_ctrl(BG)),
 1545  random_member(M,[bold,faint,reset,bold,faint,reset,bold,faint,reset]),!. % underline,negative
 1546
 1547
 1548% = :- export(tst_color/0).
 1549
 1550%= 	 	 
 tst_color is det
Tst Color.
 1556tst_color:- make, ignore((( between(1,20,_),random_member(Goal,[colormsg(C,cm(C)),dmsg(color(C,dm(C))),ansifmt(C,C)]),next_color(C),Goal,fail))).
 1557% = :- export(tst_color/1).
 1558
 1559%= 	 	 
 tst_color(?C) is det
Tst Color.
 1565tst_color(C):- make,colormsg(C,C).
 1566
 1567% = :- export(next_color/1).
 1568
 1569%= 	 	 
 next_color(:TermC) is det
Next Color.
 1575next_color(C):- between(1,10,_), random_color(C), good_next_color(C),!.
 1576next_color([underline|C]):- random_color(C),!.
 1577
 1578% = :- export(contrasting_color/2).
 1579
 1580%= 	 	 
 contrasting_color(?A, ?VALUE2) is det
Contrasting Color.
 1586contrasting_color(white,black).
 1587contrasting_color(A,default):-atom(A),A \= black.
 1588contrasting_color(fg(C),bg(CC)):-!,contrasting_color(C,CC),!.
 1589contrasting_color(hfg(C),bg(CC)):-!,contrasting_color(C,CC),!.
 1590contrasting_color(black,white).
 1591contrasting_color(default,default).
 1592contrasting_color(_,default).
 1593
 1594:- thread_local(ansi_prop/2). 1595
 1596
 1597
 1598%= 	 	 
 sgr_on_code(?Ctrl, :PRED7OnCode) is det
Sgr Whenever Code.
 1604sgr_on_code(Ctrl,OnCode):- sgr_on_code0(Ctrl,OnCode),!.
 1605sgr_on_code(_Foo,7):-!. %  zotrace((format_to_error('~NMISSING: ~q~n',[bad_sgr_on_code(Foo)]))),!.
 1606
 1607
 1608%= 	 	 
 is_sgr_on_code(?Ctrl) is det
If Is A Sgr Whenever Code.
 1614is_sgr_on_code(Ctrl):-zotrace(sgr_on_code0(Ctrl,_)),!.
 1615
 1616
 1617%= 	 	 
 sgr_on_code0(?Ctrl, :PRED6OnCode) is det
Sgr Whenever Code Primary Helper.
 1623sgr_on_code0(Ctrl,OnCode):- ansi_term:sgr_code(Ctrl,OnCode).
 1624sgr_on_code0(blink, 6).
 1625sgr_on_code0(-Ctrl,OffCode):-  nonvar(Ctrl), sgr_off_code(Ctrl,OffCode).
 1626
 1627
 1628%= 	 	 
 sgr_off_code(?Ctrl, :GoalOnCode) is det
Sgr Off Code.
 1634sgr_off_code(Ctrl,OnCode):-ansi_term:off_code(Ctrl,OnCode),!.
 1635sgr_off_code(- Ctrl,OnCode):- nonvar(Ctrl), sgr_on_code(Ctrl,OnCode),!.
 1636sgr_off_code(fg(_), CurFG):- (ansi_prop(fg,CurFG)->true;CurFG=39),!.
 1637sgr_off_code(bg(_), CurBG):- (ansi_prop(ng,CurBG)->true;CurBG=49),!.
 1638sgr_off_code(bold, 21).
 1639sgr_off_code(italic_and_franktur, 23).
 1640sgr_off_code(franktur, 23).
 1641sgr_off_code(italic, 23).
 1642sgr_off_code(underline, 24).
 1643sgr_off_code(blink, 25).
 1644sgr_off_code(blink(_), 25).
 1645sgr_off_code(negative, 27).
 1646sgr_off_code(conceal, 28).
 1647sgr_off_code(crossed_out, 29).
 1648sgr_off_code(framed, 54).
 1649sgr_off_code(overlined, 55).
 1650sgr_off_code(_,0).
 1651
 1652
 1653
 1654%= 	 	 
 sgr_code_on_off(?Ctrl, ?OnCode, ?OffCode) is det
Sgr Code Whenever Off.
 1660sgr_code_on_off(Ctrl,OnCode,OffCode):-sgr_on_code(Ctrl,OnCode),sgr_off_code(Ctrl,OffCode),!.
 1661sgr_code_on_off(Ctrl,OnCode,OffCode):-sgr_on_code(Ctrl,OnCode),sgr_off_code(Ctrl,OffCode),!.
 1662sgr_code_on_off(_Ctrl,_OnCode,[default]):-!.
 1663
 1664
 1665
 1666%= 	 	 
 msg_to_string(:TermVar, ?Str) is det
Msg Converted To String.
 1672msg_to_string(Var,Str):-var(Var),!,sformat(Str,'~q',[Var]),!.
 1673msg_to_string(portray(Msg),Str):- with_output_to_each(string(Str),(current_output(Out),portray_clause_w_vars(Out,Msg,[],[]))),!.
 1674msg_to_string(pp(Msg),Str):- sformat(Str,Msg,[],[]),!.
 1675msg_to_string(fmt(F,A),Str):-sformat(Str,F,A),!.
 1676msg_to_string(format(F,A),Str):-sformat(Str,F,A),!.
 1677msg_to_string(Msg,Str):-atomic(Msg),!,sformat(Str,'~w',[Msg]).
 1678msg_to_string(m2s(Msg),Str):-message_to_string(Msg,Str),!.
 1679msg_to_string(Msg,Str):-sformat(Str,Msg,[],[]),!.
 1680
 1681
 1682:- thread_local t_l:formatter_hook/4. 1683
 1684
 1685%= 	 	 
 withFormatter(?Lang, ?From, ?Vars, ?SForm) is det
Using Formatter.
 1691withFormatter(Lang,From,Vars,SForm):- t_l:formatter_hook(Lang,From,Vars,SForm),!.
 1692withFormatter(_Lang,From,_Vars,SForm):-sformat(SForm,'~w',[From]).
 1693
 1694
 1695%= 	 	 
 flush_output_safe is det
Flush Output Safely Paying Attention To Corner Cases.
 1701flush_output_safe:-ignore(catchv(flush_output,_,true)).
 1702
 1703%= 	 	 
 flush_output_safe(?X) is det
Flush Output Safely Paying Attention To Corner Cases.
 1709flush_output_safe(X):-ignore(catchv(flush_output(X),_,true)).
 1710
 1711
 1712%= 	 	 
 writeFailureLog(?E, ?X) is det
Write Failure Log.
 1718writeFailureLog(E,X):-
 1719  get_thread_current_error(ERR),
 1720		(fmt(ERR,'\n% error: ~q ~q\n',[E,X]),flush_output_safe(ERR),!,
 1721		%,true.
 1722		fmt('\n% error: ~q ~q\n',[E,X]),!,flush_output).
 1723
 1724%unknown(Old, autoload).
 1725
 1726
 1727
 1728
 1729%= 	 	 
 cls is det
Clauses.
 1735cls:- ignore(catch(system:shell(cls,0),_,fail)).
 1736
 1737:- use_module(library(random)). 1738%:- ensure_loaded(logicmoo_util_varnames).
 1739%:- ensure_loaded(logicmoo_util_catch).
 1740% :- autoload([verbose(false)]).
 1741
 1742/*
 1743:- 'mpred_trace_none'(fmt(_)).
 1744:- 'mpred_trace_none'(fmt(_,_)).
 1745:- 'mpred_trace_none'(dfmt(_)).
 1746:- 'mpred_trace_none'(dfmt(_,_)).
 1747:- 'mpred_trace_none'(dmsg(_)).
 1748:- 'mpred_trace_none'(dmsg(_,_)).
 1749:- 'mpred_trace_none'(portray_clause_w_vars(_)).
 1750*/
 1751
 1752:- ignore((source_location(S,_),prolog_load_context(module,M),module_property(M,class(library)),
 1753 forall(source_file(M:H,S),
 1754 ignore((cfunctor(H,F,A),
 1755  ignore(((\+ atom_concat('$',_,F),(export(F/A) , current_predicate(system:F/A)->true; system:import(M:F/A))))),
 1756  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]))))))))). 1757
 1758:- '$hide'(wdmsg(_)). 1759:- '$hide'(wdmsg(_,_)).