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%:- if((prolog_load_context(source,F),prolog_load_context(file,F))).
   15%:- module(dmsg,[]).
   16%:- else.
   17%module(_,Y):- maplist(export,Y).
   18%:- endif.
   19
   20:- define_into_module(
   21  [ ansi_control_conv/2,
   22    % source_variables_lwv/1,
   23    %style_on_off/4,
   24    ansi_prop/2,
   25    ansicall/2,
   26    ansicall/3,
   27    ansicall_4/3,
   28    wdmsg_goal/2,
   29    ansicall_6/3,
   30    ansifmt/2,
   31    ansifmt/3,
   32    cls/0,
   33    colormsg/2,
   34    contains_atom/2,
   35    contrasting_color/2,
   36    debugm/1,debugm/2,
   37    defined_message_color/2,
   38    dfmt/1,dfmt/2,
   39    dis_pp/1,
   40    dmsg/1,dmsg/2,dmsg/3,
   41    dmsg0/1,
   42    dmsg00/1,
   43    dmsg000/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_log/3,
   52    dmsg_pretty/1,
   53    dmsg_show/1,
   54    dmsg_showall/1,
   55    dmsg_text_to_string_safe/2,
   56    dmsginfo/1,
   57    f_word/2,
   58    fg_color/2,
   59    flush_output_safe/0,
   60    flush_output_safe/1,
   61    fmt/1,fmt/2,fmt/3,
   62    fmt0/1,fmt0/2,fmt0/3,
   63    fmt9/1,
   64    fmt90/1,
   65    fmt_ansi/1,
   66    fmt_or_pp/1,
   67    fmt_portray_clause/1,
   68    format_to_message/3,
   69    functor_color/2,
   70    get_indent_level/1,
   71    good_next_color/1,
   72    if_color_debug/0,
   73    if_color_debug/1,
   74    if_color_debug/2,
   75    in_cmt/1,
   76    indent_e/1,
   77    indent_to_spaces/2,
   78    is_sgr_on_code/1,
   79    is_tty/1,
   80    keep_line_pos_w_w/2,
   81    last_used_fg_color/1,
   82    logger_property/3,
   83    loggerFmtReal/3,
   84    loggerReFmt/2,
   85    logLevel/2,
   86    matches_term/2,
   87    matches_term0/2,
   88    mesg_arg1/2,
   89    mesg_color/2,
   90    msg_to_string/2,
   91    next_color/1,
   92    once_in_while/1,
   93    portray_clause_w_vars/1,
   94    portray_clause_w_vars/2,
   95    portray_clause_w_vars/3,
   96    portray_clause_w_vars/4,
   97    predef_functor_color/2,
   98    prepend_each_line/2,
   99    print_prepended/2,
  100    print_prepended_lines/2,
  101    random_color/1,
  102    setLogLevel/2,
  103    sformat/4,
  104    sgr_code_on_off/3,
  105    sgr_off_code/2,
  106    sgr_on_code/2,
  107    sgr_on_code0/2,
  108    term_color0/2,
  109    to_stderror/1,
  110    tst_color/0,
  111    tst_color/1,
  112    tst_fmt/0,
  113    univ_safe_3/2,
  114    unliked_ctrl/1,
  115    vdmsg/2,
  116    wdmsg/1,
  117    wdmsg/2,
  118    wdmsgl/1,
  119    wdmsgl/2,
  120    wdmsgl/3,
  121    with_all_dmsg/1,
  122    with_current_indent/1,
  123    with_dmsg/2,
  124    with_no_dmsg/1,
  125    with_no_dmsg/2,
  126    with_output_to_console/1,
  127    with_output_to_each/2,
  128    with_output_to_main/1,
  129    with_output_to_stream/2,
  130    with_show_dmsg/2,
  131    writeFailureLog/2,
  132    withFormatter/4]).  133
  134:- multifile
  135        term_color0/2.  136:- meta_predicate
  137        ansicall(?, 0),
  138        ansicall(?, ?, 0),
  139        ansicall_4(?, ?, 0),
  140        ansicall_6(?, ?, 0),
  141        fmt_ansi(0),
  142        if_color_debug(0),
  143        if_color_debug(0, 0),
  144        in_cmt(0),
  145        keep_line_pos_w_w(?, 0),
  146        prepend_each_line(?, 0),
  147        to_stderror(0),
  148        with_all_dmsg(0),
  149        with_current_indent(0),
  150        with_dmsg(?, 0),
  151        with_no_dmsg(:),
  152        with_no_dmsg(?, :),
  153        with_output_to_console(0),
  154        with_output_to_main(0),
  155        with_output_to_stream(?, 0),
  156        with_show_dmsg(?, 0).  157
  158%:- expects_dialect(swi).
  159
  160:- use_module(library(lists)).  161/*lists:selectchk(Elem, List, Rest) :-
  162    select(Elem, List, Rest0),
  163    (!),
  164    Rest=Rest0.*/
  165%:- lists:export(selectchk/3).
  166:- use_module(library(option)).  167
  168:- autoload(library(apply),[maplist/2]).  169:- autoload(library(occurs),[sub_term/2]).  170:- autoload(library(memfile),[memory_file_to_atom/2]).  171:- autoload(library(debug),[debug/3]).  172:- autoload(library(error),[must_be/2]).  173:- autoload(library(lists),[member/2,nth1/3]).  174:- autoload(library(lists),[append/3]).  175%:- autoload(library(lists),[selectchk/3]).
  176
  177:- autoload(library(listing),[portray_clause/3,listing/1]).  178
  179:- thread_local(bfly_tl:bfly_setting/2).  180
  181use_html_styles:-!,fail.
  182use_html_styles:- notrace(use_html_styles0).
  183use_html_styles0 :- on_x_fail(t_l:print_mode(html)).
  184use_html_styles0 :- dis_pp(ansi),!,fail.
  185%use_html_styles0 :- on_x_fail(httpd_wrapper:http_current_request(_)),!.
  186%use_html_styles0 :- on_x_fail(pengines:pengine_self(_)),!.
  187use_html_styles0 :- current_predicate(is_butterfly_console/0), (inside_bfly_html_esc;is_butterfly_console),!.
  188%=
 style_on_off(Out, ?Ctrl, ?OnCode, ?OffCode) is det
Sgr Code Whenever Off.
  195dis_pp(ansi):- keep_going,!.
  196dis_pp(PP):- current_predicate(in_pp/1), in_pp(PP).
  197
  198using_style(Out,Ctrl,Goal,How):-
  199  notrace(style_emitter(Out,Emitter)),!,
  200  using_style_emitter(Emitter, Out,Ctrl,Goal,How),!.
  201
  202using_style_emitter(sgr,_Out,Ctrl,Goal,How):- fail,
  203  How = (with_output_to_each(string(S),
  204     (set_stream_ignore(current_output, tty(true)),call(Goal))),
  205          terminal_ansi_format([Ctrl],'~s',[S])), !.
  206
  207using_style_emitter(Emitter,Out,Ctrl,Goal,How):-
  208  cnvt_in_out(Emitter,Out,Ctrl,OnCode,OffCode),!,
  209  How = scce_orig((OnCode,!),once(Goal),(OffCode,!)).
  210
  211style_emitter(Out,NV):- nonvar(NV),style_emitter(Out,Var),!,NV==Var.
  212style_emitter(Out,none):- dis_pp(ansi), \+ is_tty(Out), !.
  213style_emitter(Out,sgr):- dis_pp(ansi), is_tty(Out), !.
  214style_emitter(_Out,html):- use_html_styles,!.
  215style_emitter(Out,sgr):- dis_pp(bfly), is_tty(Out), !.
  216style_emitter(_Out,none):- \+ use_html_styles.
  217
  218%cnvt_in_out(_, _Out,_Ctrl,true,true):- dis_pp(ansi),!.
  219cnvt_in_out(_, _Out,_Ctrl,true,true):- on_x_fail(httpd_wrapper:http_current_request(_)),!.
  220cnvt_in_out(none, _Out,_Ctrl,true,true).
  221cnvt_in_out(_,_Out,html,(in_pp(Was),pp_set(http)),pp_set(Was)).
  222cnvt_in_out(_,_Out,pp_set(PP),(in_pp(Was),pp_set(PP)),pp_set(Was)).
  223%cnvt_in_out(sgr, Out,Ctrl,enter_recording_stream(Out,Ctrl,S,H),exit_recording_stream(Out,Ctrl,S,H)).
  224cnvt_in_out(sgr, Out, Ctrl,OnCodeCall,OffCodeCall) :- sgr_code_on_off(Ctrl,OnCode,OffCode), into_oncode_call(Out,OnCode,OnCodeCall), into_oncode_call(Out,OffCode,OffCodeCall).
  225cnvt_in_out(sgr, Out,_Ctrl,true,OffCode):- into_oncode_call(Out,[default],OffCode),!.
  226%cnvt_in_out(html,_Out,C,(bfly_in,I),(O,bfly_out)):- toplevel_pp(bfly), \+ inside_bfly_html_esc, !, html_on_off(C,I,O),!. % @TODO bfly_out/0
  227%cnvt_in_out(html,_Out,C,(I),(O)):- toplevel_pp(bfly),html_on_off(C,I,O),!. % @TODO bfly_out/0
  228
  229cnvt_in_out(html,_Out,C,I,O):- html_on_off(C,I,O),!.
  230cnvt_in_out(_, _Out,_Ctrl,true,true):-!.
  231cnvt_in_out(Mode, _Out, Ctrl,true,true):- format(user_error,'~N% ~q.~n', [mising_ctrl(Mode, Ctrl)]).
  232
  233set_output_safe(Strm):- catch(set_output(Strm),_,true).
  234
  235enter_recording_stream(_Out,_Ctrl,H,S):- new_memory_file(H),open_memory_file(H,write,S),set_output_safe(S).
  236exit_recording_stream(Out,Ctrl,H,S):- set_output_safe(Out),close(S),memory_file_to_string(H,Str),terminal_ansi_format([Ctrl],'~s',[Str]).
  237
  238into_oncode_call(Out,OnCode,OnCodeCall):- OnCodeCall= smart_format(Out,'\e[~wm', [OnCode]).
  239
  240
  241wldmsg_0(_CM,ops):- !.
  242wldmsg_0(_CM,ops):-
  243 dzotrace((
  244 wldmsg_2('======================\\'),
  245 (prolog_load_context(stream,X)-> dmsgln(prolog_load_context(stream,X)) ; (current_input(X),dmsgln(current_input(X)))),
  246 ignore((
  247 fail,
  248 %dmsgln(forall(stream_property(X,_))),
  249 % call(stream_property(X,position(Pos))->
  250 prolog_load_context(module,LM),
  251 dmsgln(prolog_load_context(module,LM)),
  252 dmsgln(forall(LM:current_op(_,_,LM:if))),
  253 dmsgln(forall(LM:current_op(_,_,LM:then))),
  254 dmsgln(forall(LM:current_op(_,_,LM:'=>'))),
  255 dmsgln(forall(LM:current_op(_,_,LM:'==>'))),
  256 dmsgln(forall(LM:current_op(_,_,LM:'-'))),
  257 dmsgln(forall(prolog_load_context(_,_))))),
  258 strip_module(_,M,_),
  259 dmsgln(strip_module(M)),
  260 dmsgln(call('$current_source_module'(_SM))),
  261 dmsgln(call('$current_typein_module'(_TM))),
  262  (source_location(F,L)-> wldmsg_2(X=source_location(F,L)) ; wldmsg_2(no_source_location(X))),
  263   %dmsgln(forall(byte_count(X,_))),
  264   %dmsgln(forall(character_count(X,_))),
  265   dmsgln(forall(line_count(X,_))),
  266   dmsgln(forall(line_position(X,_))),
  267  wldmsg_2('======================/'))),
  268 !.
  269
  270wldmsg_0(_,CM:Goal):- !, wldmsg_0(CM,Goal).
  271wldmsg_0(_,forall(CM:Goal)):- callable(Goal), !,ignore((nonvar(Goal),wldmsg_0(CM,forall(Goal)))).
  272wldmsg_0(_,call(CM:Goal)):- callable(Goal), !,ignore((nonvar(Goal),wldmsg_0(CM,call(Goal)))).
  273wldmsg_0(CM,List):- is_list(List),!,maplist(wldmsg_0(CM),List).
  274wldmsg_0(CM,forall(Goal)):- callable(Goal), !, ignore((nonvar(Goal),forall(CM:call(Goal), wldmsg_1(Goal)))).
  275wldmsg_0(CM,call(Goal)):- callable(Goal), !, ignore((nonvar(Goal),CM:call(Goal), wldmsg_1(Goal))).
  276wldmsg_0(_,Info):-wldmsg_1(Info).
  277
  278wldmsg_1(List):- is_list(List),!,maplist(wldmsg_1,List).
  279wldmsg_1(Info):- compound(Info),compound_name_arguments(Info,F,[A]),!,wldmsg_1(F=A).
  280wldmsg_1(Info):- compound(Info),compound_name_arguments(Info,(-),[F,A]),!,wldmsg_1(F=A).
  281wldmsg_1(Info):-
  282  get_real_user_output(O),flush_output(O),smart_format(O,'~N',[]),flush_output(O),
  283  wldmsg_2(Info),!.
  284
  285
  286get_real_user_output(O):-stream_property(O,file_no(1)).
  287get_real_user_error(O):-stream_property(O,file_no(2)).
  288
  289:- export(same_streams/2).  290same_streams(X,Y):- dzotrace((into_stream(X,XX),into_stream(Y,YY),!,XX==YY)).
  291
  292into_stream(X,S):- dzotrace(into_stream_0(X,S)).
  293into_stream_0(file_no(N),XX):- !, stream_property(X,file_no(N)),!,X=XX.
  294into_stream_0(Atom,XX):- atom(Atom),stream_property(X,alias(Atom)),!,X =XX.
  295into_stream_0(S,XX):- atomic(S),is_stream(S),!,S = XX.
  296into_stream_0(S,XX):- stream_property(X,file_name(F)),F==S,!,X=XX.
  297
  298:- volatile(t_l:thread_local_error_stream/1).  299wldmsg_2(Info):- t_l:thread_local_error_stream(Err), output_to_x(Err,Info).
  300wldmsg_2(Info):- same_streams(current_output,file_no(1)), stream_property(X,file_no(1)), !, output_to_x(X,Info).
  301wldmsg_2(Info):- same_streams(current_output,file_no(2)), stream_property(X,file_no(2)), !, output_to_x(X,Info).
  302wldmsg_2(Info):- output_to_x(current_output,Info), stream_property(X,file_no(2)), !, output_to_x(X,Info).
  303
  304output_to_x(S,Info):- ignore(dzotrace(catch(output_to_x_0(S,Info),_,true))).
  305output_to_x_0(S,Info):- into_stream(S,X),!, flush_output(X),
  306  catch(smart_format(X,'~N% ~p~n',[Info]),_,smart_format(X,'~N% DMSGQ: ~q~n',[Info])),flush_output(X).
  307
  308:- export(prepend_trim/2).  309:- export(is_html_white_l/1).  310:- export(is_html_white_r/1).  311:- export(likely_folded/1).  312:- module_transparent(dmsgln/1).  313:- export(dmsgln/1).  314:- system:import(dmsgln/1).  315:- meta_predicate(dmsgln(:)).  316:- dynamic(dmsgln/1).  317:- module_transparent(dmsgln/1).  318:- export(dmsgln/1).  319:- system:import(dmsgln/1).  320:- meta_predicate(dmsgln(:)).  321dmsgln222(CMSpec):- strip_module(CMSpec,CM,Spec),!, ignore(dzotrace(wldmsg_0(CM,Spec))).
  322% system:dmsgln(List):-!,dzotrace(wldmsg_0(user,List)).
  323dmsgln(CMSpec):- strip_module(CMSpec,CM,Spec),!, ignore(dzotrace(wldmsg_0(CM,Spec))).
  324
  325
  326
  327univ_safe_3(A,B):- compound(A),compound_name_arity(A,F,0),!,F=..B.
  328univ_safe_3(A,B):- A=..B.
  329
  330:- meta_predicate if_defined_local(:,0).  331if_defined_local(G,Else):- current_predicate(_,G)->G;Else.
  332
  333:- module_transparent
  334        ansi_control_conv/2,
  335        ansifmt/2,
  336        ansifmt/3,
  337        colormsg/2,
  338        contrasting_color/2,
  339        defined_message_color/2,
  340        dfmt/1,
  341        dfmt/2,
  342        dmsg/1,dmsg/2,dmsg/3,
  343        dmsg0/1,
  344        dmsg1/1,
  345        dmsg2/1,
  346        dmsg3/1,
  347        dmsg4/1,
  348        dmsg5/1,
  349        %dmsg5/2,
  350        dmsg_hide/1,
  351        dmsg_hides_message/1,
  352        dmsg_show/1,
  353        dmsg_showall/1,
  354        dmsg_text_to_string_safe/2,
  355        dmsginfo/1,
  356
  357        with_output_to_each/2,
  358        f_word/2,
  359        fg_color/2,
  360        flush_output_safe/0,
  361        flush_output_safe/1,
  362        fmt/1,
  363        fmt/2,
  364        fmt/3,
  365        fmt0/1,
  366        fmt0/2,
  367        fmt0/3,
  368        fmt9/1,
  369        fmt_or_pp/1,
  370        fmt_portray_clause/1,
  371        functor_color/2,
  372        get_indent_level/1,
  373        good_next_color/1,
  374        if_color_debug/0,
  375        indent_e/1,
  376        indent_to_spaces/2,
  377        is_sgr_on_code/1,
  378        is_tty/1,
  379        last_used_fg_color/1,
  380        mesg_arg1/2,
  381
  382        msg_to_string/2,
  383        next_color/1,
  384        portray_clause_w_vars/1,
  385        portray_clause_w_vars/2,
  386        portray_clause_w_vars/3,
  387        portray_clause_w_vars/4,
  388        predef_functor_color/2,
  389        print_prepended/2,
  390        print_prepended_lines/2,
  391        random_color/1,
  392        sformat/4,
  393        %style_on_off/4,
  394        sgr_off_code/2,
  395        sgr_on_code/2,
  396        sgr_on_code0/2,
  397        tst_color/0,
  398        tst_color/1,
  399        tst_fmt/0,
  400        unliked_ctrl/1,
  401        vdmsg/2,
  402        withFormatter/4,
  403        writeFailureLog/2.  404:- dynamic
  405        defined_message_color/2,
  406        term_color0/2.  407
  408
  409:- if(current_predicate(lmcode:combine_logicmoo_utils/0)).  410:- module(logicmoo_util_dmsg,
  411[  % when the predciates are not being moved from file to file the exports will be moved here
  412       ]).  413
  414:- else.  415
  416:- endif.  417
  418:- set_module(class(library)).  419
  420:- user:use_module(library(memfile)).  421%:- user:use_module(first).
  422%:- user:ensure_loaded(logicmoo_util_rtrace).
  423:- ensure_loaded(library(logicmoo/each_call)).  424%:- user:ensure_loaded(logicmoo_util_loop_check).
  425
  426
  427:- meta_predicate(wets(?,0)).  428:- export(wets/2).  429wets(S,Goal):- var(S),!,with_error_to_string(S,Goal).
  430wets(S,Goal):- is_stream(S),!,with_error_to_stream(S,Goal).
  431wets(S,Goal):- compound(S), with_error_to(S,Goal).
  432
  433
  434:- meta_predicate with_error_to(+,0).  435with_error_to(Dest,Goal):-
  436  with_error_to_each(Dest,once(Goal)).
  437
  438:- meta_predicate with_error_to_string(+,0).  439with_error_to_stream(S,Goal):-
  440  with_ioe((
  441     (set_stream_ignore(S,alias(user_error)),
  442         set_stream_ignore(S,alias(current_error))),
  443     locally_tl(thread_local_error_stream(S),Goal))).
  444
  445:- meta_predicate wete(+,0).  446wete(Dst,Goal):- with_error_to_each(Dst,Goal).
  447:- meta_predicate with_error_to_each(+,0).  448with_error_to_each(Dest,Goal):- compound(Dest), \+ compound_name_arity(Dest,_,0),
  449  Dest=..[F,A],stream_u_type(F),!,
  450  Unset = (set_stream_ignore(Was,alias(current_error)),set_stream_ignore(Was,alias(user_error))),
  451  once((member(Alias,[user_error,current_error]),stream_property(Was,alias(Alias)))),
  452  Done = mfs_end(MFS,A),
  453  MFS = mfs(_,F,_,set_error_stream,Unset),
  454  call_cleanup(trusted_redo_call_cleanup(mfs_start(MFS),(Goal,Done),Done),Done).
  455
  456with_error_to_each(Dest,Goal):- with_error_to_stream(Dest,Goal).
  457
  458new_mfs(MFS):- MFS = mfs(Handle,_,Stream,_,_),
  459  new_memory_file(Handle), open_memory_file(Handle,write,Stream,[free_on_close(true)]).
  460
  461mfs_start(MFS):- \+compound(MFS),!,throw(mfs_start(MFS)).
  462mfs_start(MFS):-
  463  arg(2,MFS,F), arg(3,MFS,OS), arg(4,MFS,Set), NMFS= mfs(Handle,F,Stream,Set,_Unset),
  464  (is_stream(OS)
  465    -> Stream =OS
  466    ; (new_mfs(NMFS), nb_setarg(1,MFS,Handle),nb_setarg(3,MFS,Stream))),
  467 call(Set,Stream).
  468
  469set_error_stream(Stream):- set_stream_ignore(Stream,alias(current_error)),set_stream_ignore(Stream,alias(user_error)).
  470
  471mfs_end(MFS,A):-
  472  MFS = mfs(Handle,F,Stream,_Set,Unset),
  473  ignore((is_stream(Stream),close(Stream), mem_handle_to_substring(Handle,Str),substring_to_type(Str,F,A))),
  474  call(Unset).
  475
  476
  477
  478
  479stream_u_type(atom). stream_u_type(string). stream_u_type(codes). stream_u_type(chars).
  480
  481mem_handle_to_substring(Handle,String):- memory_file_to_string(Handle,String),!.
  482mem_handle_to_substring(Handle,SubString):-
  483  memory_file_line_position(Handle, _Line, _LinePos, Offset),
  484  %seek(Stream, 0, current, Offset)
  485  memory_file_substring(Handle, 0, Offset, _After, -SubString).
  486
  487substring_to_type(Str,atom,Atom):- atom_string(Atom,Str).
  488substring_to_type(Str,string,Str).
  489substring_to_type(Str,codes,Codes):- string_codes(Str,Codes).
  490substring_to_type(Str,chars,Chars):- string_chars(Str,Chars).
  491
  492mem_handle_to_type(Handle,atom,Atom):- !, memory_file_to_atom(Handle,Atom).
  493mem_handle_to_type(Handle,string,String):- !, memory_file_to_string(Handle,String).
  494mem_handle_to_type(Handle,codes,Codes):- !, memory_file_to_codes(Handle,Codes).
  495mem_handle_to_type(Handle,chars,Chars):- !, memory_file_to_string(Handle,Atom),string_chars(Atom,Chars).
  496
  497:- meta_predicate with_error_to_string(-,0).  498with_error_to_string(S,Goal):-
  499   new_memory_file(Handle),
  500   open_memory_file(Handle,write,Stream,[free_on_close(true)]),
  501   call_cleanup(with_error_to_each(Stream,Goal),
  502           (close(Stream),memory_file_to_string(Handle,S))).
  503
  504:- meta_predicate with_output_to_each(+,0).  505
  506with_output_to_each(Dest,Goal):- compound(Dest), \+ compound_name_arity(Dest,_,0),
  507  Dest=..[F,A],stream_u_type(F),!,
  508  current_output(Was),
  509  Unset = set_output_safe(Was),
  510  MFS = mfs(_,F,_,set_output_safe,Unset),
  511  Done = mfs_end(MFS,A),
  512  call_cleanup(trusted_redo_call_cleanup(mfs_start(MFS),(Goal,Done),Done),Done).
  513/*
  514with_output_to_each(Dest,Goal):- Dest=..[F,A],!,
  515   current_output(Was),
  516   nb_setarg(1,Dest,""),
  517   new_memory_file(Handle),
  518   open_memory_file(Handle,write,Stream,[free_on_close(true)]),
  519     scce_orig(set_output_safe(Stream),
  520      scce_orig(true,Goal,
  521        (close(Stream),mem_handle_to_type(Handle,F,Atom),nb_setarg(1,Dest,Atom),ignore(A=Atom))),
  522      (set_output_safe(Was))).
  523*/
  524with_output_to_each(Dest,Goal):-
  525   current_output(Was),
  526    scce_orig(set_output_safe(Dest),Goal,set_output_safe(Was)).
  527
  528
  529
  530% ==========================================================
  531% Sending Notes
  532% ==========================================================
  533:- thread_local( tlbugger:dmsg_match/2).  534% = :- meta_predicate(with_all_dmsg(0)).
  535% = :- meta_predicate(with_show_dmsg(*,0)).
  536
  537
  538
  539%=
 with_all_dmsg(:Goal) is nondet
Using All (debug)message.
  545with_all_dmsg(Goal):-
  546   locally(set_prolog_flag(dmsg_level,always),
  547       locally( tlbugger:dmsg_match(show,_),Goal)).
  548
  549
  550
  551%=
 with_show_dmsg(?TypeShown, :Goal) is nondet
Using Show (debug)message.
  557with_show_dmsg(TypeShown,Goal):-
  558  locally(set_prolog_flag(dmsg_level,always),
  559     locally( tlbugger:dmsg_match(showing,TypeShown),Goal)).
  560
  561% = :- meta_predicate(with_no_dmsg(0)).
  562
  563%=
 with_no_dmsg(:Goal) is nondet
Using No (debug)message.
  570 % with_no_dmsg(Goal):- current_prolog_flag(dmsg_level,always),!,Goal.
  571with_no_dmsg(Goal):-locally(set_prolog_flag(dmsg_level,never),Goal).
  572
  573%=
 with_no_dmsg(?TypeUnShown, :Goal) is nondet
Using No (debug)message.
  579with_no_dmsg(TypeUnShown,Goal):-
  580 locally(set_prolog_flag(dmsg_level,filter),
  581  locally( tlbugger:dmsg_match(hidden,TypeUnShown),Goal)).
  582
  583% dmsg_hides_message(_):- !,fail.
  584
  585%=
 dmsg_hides_message(?C) is det
(debug)message Hides Message.
  591dmsg_hides_message(_):- current_prolog_flag(dmsg_level,never),!.
  592dmsg_hides_message(_):- current_prolog_flag(dmsg_level,always),!,fail.
  593dmsg_hides_message(C):-  tlbugger:dmsg_match(HideShow,Matcher),matches_term(Matcher,C),!,HideShow=hidden.
  594
  595:- export(matches_term/2).
 matches_term(?Filter, ?VALUE2) is det
Matches Term.
  601matches_term(Filter,_):- var(Filter),!.
  602matches_term(Filter,Term):- var(Term),!,Filter=var.
  603matches_term(Filter,Term):- ( \+ \+ (matches_term0(Filter,Term))),!.
 contains_atom(?V, ?A) is det
Contains Atom.
  609contains_atom(V,A):-sub_term(VV,V),nonvar(VV),cfunctor(VV,A,_).
 matches_term0(:TermFilter, ?Term) is det
Matches Term Primary Helper.
  615matches_term0(Filter,Term):- Term = Filter.
  616matches_term0(Filter,Term):- atomic(Filter),!,contains_atom(Term,Filter).
  617matches_term0(F/A,Term):- (var(A)->member(A,[0,1,2,3,4]);true), cfunctor(Filter,F,A), matches_term0(Filter,Term).
  618matches_term0(Filter,Term):- sub_term(STerm,Term),nonvar(STerm),call(call,matches_term0(Filter,STerm)),!.
  619
  620hide_some_hiddens(P,P):- ((\+ compound(P));compound_name_arity(P,_,0)),!.
  621hide_some_hiddens(pfc_hide(_),pfc_hide($)):-!.
  622%hide_some_hiddens('{}'(_),'{}'($)):-!.
  623hide_some_hiddens(S,M):-
  624   compound_name_arguments(S,F,Args),
  625   must_maplist(hide_some_hiddens,Args,ArgsO),
  626   compound_name_arguments(M,F,ArgsO),!.
  627
  628
  629pretty_and_hide(In, Info):- dzotrace((pretty_numbervars(In,M),hide_some_hiddens(M,Info))),!.
  630
  631dmsg_pretty(In):- dzotrace( ignore( \+ \+   ( pretty_and_hide(In, Info),dmsg(Info)))).
  632
  633wdmsg_pretty(In):- !,notrace(in_cmt(format('~q',In))).
  634wdmsg_pretty(In):- \+ \+ dzotrace((pretty_and_hide(In, Info),wdmsg(Info))).
  635
  636wdmsg_pretty(F,In):- !,notrace(in_cmt(format(F,In))).
  637wdmsg_pretty(F,In):- \+ \+ dzotrace((pretty_and_hide(In, Info),wdmsg(F,Info))).
  638
  639%=
 dmsg_hide(?Term) is det
(debug)message Hide.
  645dmsg_hide(isValueMissing):-!,set_prolog_flag(dmsg_level,never).
  646dmsg_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).
  647
  648%=
 dmsg_show(?Term) is det
(debug)message Show.
  654dmsg_show(isValueMissing):-!,set_prolog_flag(dmsg_level,always).
  655dmsg_show(Term):-set_prolog_flag(dmsg_level,filter),aina( tlbugger:dmsg_match(showing,Term)),ignore(retractall( tlbugger:dmsg_match(hidden,Term))),debug(Term).
  656
  657%=
 dmsg_showall(?Term) is det
(debug)message Showall.
  663dmsg_showall(Term):-ignore(retractall( tlbugger:dmsg_match(hidden,Term))).
  664
  665
  666%=
 indent_e(?X) is det
Indent E.
  672indent_e(0):-!.
  673indent_e(X):- X > 20, XX is X-20,!,indent_e(XX).
  674indent_e(X):- catchvvnt((X < 2),_,true),write(' '),!.
  675indent_e(X):-XX is X -1,!,write(' '), indent_e(XX).
  676
  677
  678%=
 dmsg_text_to_string_safe(?Expr, ?Forms) is det
(debug)message Text Converted To String Safely Paying Attention To Corner Cases.
  684dmsg_text_to_string_safe(Expr,Forms):-on_x_fail(text_to_string(Expr,Forms)).
  685
  686% ===================================================================
  687% Lowlevel printng
  688% ===================================================================
  689:- multifile lmconf:term_to_message_string/2.  690:- dynamic lmconf:term_to_message_string/2.
 catchvvnt(:GoalT, ?E, :GoalF) is det
Catchvvnt.
  695catchvvnt(T,E,F):-catchv(quietly(T),E,F).
  696
  697:- meta_predicate(catchvvnt(0,?,0)).  698
  699%=
 fmt0(?X, ?Y, ?Z) is det
Format Primary Helper.

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

  707fmt0(X,Y,Z):-catchvvnt((smart_format(X,Y,Z),flush_output_safe(X)),E,dfmt(E:smart_format(X,Y))).
  708
  709%=
 fmt0(?X, ?Y) is det
Format Primary Helper.
  716is_regular_format_args(X,_):- \+ atomic(X),!,fail.
  717is_regular_format_args(X,Y):- (string(X);atom(Y)), atom_contains(X,'~').
  718is_regular_format_args(_,Y):- is_list(Y),!.
  719
  720system:smart_format(X,Y,Z):- format(X,Y,Z).
  721smart_format(X,Y):- smart_format([X,Y]).
  722
  723smart_format(DDD):- \+ is_list(DDD),!, format('~q',[DDD]).
  724
  725smart_format([X,Y]):- is_regular_format_args(X,Y),!,catch(format(X,Y),error(smart_format(A),B),writeq(smart_format(X,Y)=error(smart_format(A),B))),!.
  726smart_format([X|More]):- (compound(X);is_stream(X)),!,with_output_to_each(X,smart_format(More)),!.
  727smart_format([X,Y]):- smart_format(X-Y),!.
  728
  729:- export(smart_format/3).  730:- export(smart_format/2).  731:- export(smart_format/1).  732
  733fmt0(X,Y):-catchvvnt((smart_format(X,Y),flush_output_safe),E,dfmt(E:smart_format(X,Y))).
  734
  735%=
 fmt0(?X) is det
Format Primary Helper.
  741fmt0(X):- (atomic(X);is_list(X)), dmsg_text_to_string_safe(X,S),!,format('~w',[S]),!.
  742fmt0(X):- (atom(X) -> catchvvnt((smart_format(X,[]),flush_output_safe),E,dmsg(E)) ;
  743  (lmconf:term_to_message_string(X,M) -> 'smart_format'('~q~N',[M]);fmt_or_pp(X))).
  744
  745%=
 fmt(?X) is det
Format.
  751fmt(X):-fresh_line,fmt_ansi(fmt0(X)).
  752
  753%=
 fmt(?X, ?Y) is det
Format.
  759fmt(X,Y):- fresh_line,fmt_ansi(fmt0(X,Y)),!.
  760
  761%=
 fmt(?X, ?Y, ?Z) is det
Format.
  767fmt(X,Y,Z):- fmt_ansi(fmt0(X,Y,Z)),!.
  768
  769
  770
  771:- module_transparent((format_to_message)/3).  772
  773format_to_message(Format,Args,Info):-
  774  on_xf_cont(((( sanity(is_list(Args))->
  775     smart_format(string(Info),Format,Args);
  776     (smart_format(string(Info),'~N~n~p +++++++++++++++++ ~p~n',[Format,Args])))))).
  777
  778new_line_if_needed:- tracing,!.
  779new_line_if_needed:- ttyflush,format('~N',[]),flush_output.
  780
  781%=
 fmt9(?Msg) is det
Fmt9.
  787fmt9(Msg):- new_line_if_needed, must((fmt90(Msg))),!,new_line_if_needed.
  788
  789fmt90(fmt0(F,A)):-on_x_fail(fmt0(F,A)),!.
  790
  791fmt90(Msg):- on_x_fail(print_tree_maybe(Msg)),!.
  792%fmt90(Msg):- on_x_fail(print(Msg)),!.
  793fmt90(Msg):- dzotrace(on_x_fail(((string(Msg)),smart_format(Msg,[])))),!.
  794
  795fmt90(V):- on_x_fail(notrace(mesg_color(V,C))), catch(pprint_ecp(C, V),_,fail),!. % (dumpST,format('~N~q. % ~q. ~n',[fmt90(V),E]),fail)
  796fmt90(Msg):- on_x_fail((with_output_to(string(S),portray_clause_w_vars(Msg)))),format('~s',[S]),!.
  797fmt90(Msg):- dzotrace(on_x_fail(format('~p',[Msg]))),!.
  798fmt90(Msg):- dzotrace(writeq(fmt9(Msg))).
  799
  800print_tree_maybe(G):- compound(G),compound_name_arity(G,F,_), \+ current_op(_,_,F),!,
  801  print_tree(G).
  802
  803% :-reexport(library(ansi_term)).
  804% % % OFF :- system:use_module(library(ansi_term)).
  805
  806
  807%=
 tst_fmt is det
Tst Format.
  814tst_fmt:- tst_fmt(swish).
  815
  816tst_fmt(PP):- make,call(tst_fmt0(PP)).
  817
  818tst_fmt0(PP):-
  819 findall(R,(clause(ansi_term:sgr_code(R, _),_),ground(R)),List),
  820 ignore((
  821        ansi_term:ansi_color(FC, _),
  822        member(FG,[hfg(FC),fg(FC)]),
  823        % ansi_term:ansi_term:ansi_color(Key, _),
  824        member(BG,[hbg(default),bg(default)]),
  825        member(R,List),
  826        % random_member(R1,List),
  827    C=[reset,R,FG,BG],
  828  fresh_line,
  829  P = with_pp(PP,ansicall(C,format('~N% HTML: ~q~n',[C]))),
  830  with_pp(PP,ansicall(C,format('~N% ?- ~q. ~n',[P]))),
  831  % ansicall(C,format('~N% ansicall: ~q~n',[C])),
  832  \+ in_pp(http), terminal_ansi_format(C,'~N% ansi_term: ~q~n',[C]),
  833  fail)).
  834
  835
  836%=
 fmt_ansi(:Goal) is nondet
Format Ansi.
  842fmt_ansi(Goal):- (ansicall([reset,bold,hfg(white),bg(black)],ignore(Goal))->true;call(Goal)).
  843
  844
  845%=
 fmt_portray_clause(?X) is det
Format Portray Clause.
  851fmt_portray_clause(X):- renumbervars_prev(X,Y),!, portray_clause(Y).
  852
  853
  854%=
 fmt_or_pp(?X) is det
Format Or Pretty Print.
  860fmt_or_pp(portray((X:-Y))):-!,fmt_portray_clause((X:-Y)),!.
  861fmt_or_pp(portray(X)):- !,cfunctor(X,F,A),fmt_portray_clause((pp(F,A):-X)),!.
  862fmt_or_pp(X):-format('~q~N',[X]).
  863
  864
  865%=
 with_output_to_console(:GoalX) is det
Using Output Converted To Console.
  871with_output_to_console(X):- get_main_error_stream(Err),!,with_output_to_stream(Err,X).
  872
  873%=
 with_output_to_main(:GoalX) is det
Using Output Converted To Main.
  879with_output_to_main(X):- get_main_error_stream(Err),!,with_output_to_stream(Err,X).
  880
  881
  882%=
 dfmt(?X) is det
Dfmt.
  888dfmt(X):- get_thread_current_error(Err),!,with_output_to_stream(Err,fmt(X)).
  889
  890%=
 dfmt(?X, ?Y) is det
Dfmt.
  896dfmt(X,Y):- get_thread_current_error(Err), with_output_to_stream(Err,fmt(X,Y)).
  897
  898
  899%=
 with_output_to_stream(?Stream, :Goal) is det
Using Output Converted To Stream.
  905with_output_to_stream(Stream,Goal):- is_stream(Stream),!,
  906   current_output(Saved),
  907   scce_orig(set_output_safe(Stream),
  908         Goal,
  909         set_output_safe(Saved)).
  910with_output_to_stream(Prop,Goal):- compound(Prop), on_x_fail(stream_property(Stream,Prop)),!,
  911  with_output_to_stream(Stream,Goal).
  912with_output_to_stream(Out,Goal):- with_output_to_each(Out,Goal).
  913
  914
  915%=
 to_stderror(:Goal) is nondet
Converted To Stderror.
  921to_stderror(Goal):- get_thread_current_error(Err), with_output_to_stream(Err,Goal).
  922
  923
  924
  925:- dynamic dmsg_log/3.  926
  927
  928:- dynamic(logLevel/2).  929:- module_transparent(logLevel/2).  930:- multifile(logLevel/2).  931
  932
  933:- dynamic logger_property/2.  934
  935%=
 logger_property(?VALUE1, ?VALUE2, ?VALUE3) is det
Logger Property.
  941logger_property(todo,once,true).
  942
  943
  944
  945%=
 setLogLevel(?M, ?L) is det
Set Log Level.
  951setLogLevel(M,L):-retractall(logLevel(M,_)),(nonvar(L)->asserta(logLevel(M,L));true).
  952
  953
  954%=
 logLevel(?S, ?Z) is det
Log Level.
  960logLevel(debug,ERR):-get_thread_current_error(ERR).
  961logLevel(error,ERR):-get_thread_current_error(ERR).
  962logLevel(private,none).
  963logLevel(S,Z):-current_stream(_X,write,Z),dtrace,stream_property(Z,alias(S)).
  964
  965
  966%=
 loggerReFmt(?L, ?LRR) is det
Logger Re Format.
  972loggerReFmt(L,LRR):-logLevel(L,LR),L \==LR,!,loggerReFmt(LR,LRR),!.
  973loggerReFmt(L,L).
  974
  975
  976%=
 loggerFmtReal(?S, ?F, ?A) is det
Logger Format Real.
  982loggerFmtReal(none,_F,_A):-!.
  983loggerFmtReal(S,F,A):-
  984  current_stream(_,write,S),
  985    fmt(S,F,A),
  986    flush_output_safe(S),!.
  987
  988
  989
  990:- thread_local tlbugger:is_with_dmsg/1.  991
  992
  993%=
 with_dmsg(?Functor, :Goal) is det
Using (debug)message.
  999with_dmsg(Functor,Goal):-
 1000   locally(tlbugger:is_with_dmsg(Functor),Goal).
 1001
 1002
 1003% % % OFF :- system:use_module(library(listing)).
 1004
 1005%=
 sformat(?Str, ?Msg, ?Vs, ?Opts) is det
Sformat.
 1011sformat(Str,Msg,Vs,Opts):- nonvar(Msg),cfunctor(Msg,':-',_),!,with_output_to_each(string(Str),
 1012   (current_output(CO),portray_clause_w_vars(CO,Msg,Vs,Opts))).
 1013sformat(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]),!.
 1014
 1015
 1016free_of_attrs_dmsg(Term):- var(Term),!,(get_attrs(Term,Attrs)-> Attrs==[] ; true).
 1017free_of_attrs_dmsg(Term):- term_attvars(Term,Vs),!,(Vs==[]->true;maplist(free_of_attrs_dmsg,Vs)).
 1018
 1019
 1020% % % OFF :- system:use_module(library(listing)).
 1021
 1022%=
 portray_clause_w_vars(?Out, ?Msg, ?Vs, ?Options) is det
Portray Clause W Variables.
 1029portray_clause_w_vars(Out,Msg,Vs,Options):- free_of_attrs_dmsg(Msg+Vs),!, portray_clause_w_vars5(Out,Msg,Vs,Options).
 1030portray_clause_w_vars(Out,Msg,Vs,Options):- fail, if_defined_local(serialize_attvars_now(Msg+Vs,SMsg+SVs),fail),!,
 1031     \+ \+ portray_clause_w_vars2(Out,SMsg,SVs,Options).
 1032portray_clause_w_vars(Out,Msg,Vs,Options):- \+ \+ portray_clause_w_vars2(Out,Msg,Vs,Options).
 1033
 1034portray_clause_w_vars2(Out,Msg,Vs,Options):- free_of_attrs_dmsg(Msg+Vs),!, portray_clause_w_vars5(Out,Msg,Vs,Options).
 1035portray_clause_w_vars2(Out,Msg,Vs,Options):-
 1036   term_attvars(Msg,AttVars),
 1037   copy_term(Msg+AttVars,Msg+AttVars,Goals),
 1038   portray_append_goals(Msg,Goals,GMsg),
 1039   portray_clause_w_vars5(Out,GMsg,Vs,Options).
 1040
 1041portray_clause_w_vars5(Out,Msg,Vs,Options):-
 1042  copy_term_nat(v(Msg,Vs,Options),v(CMsg,CVs,COptions)),
 1043  portray_clause_w_vars55(Out,CMsg,CVs,COptions),!.
 1044portray_clause_w_vars55(Out,Msg,Vs,Options):-
 1045 \+ \+ ((
 1046 (var(Vs)-> prolog_load_context(variable_names,Vs);true),
 1047 prolog_listing:do_portray_clause(Out,Msg,
 1048  [variable_names(Vs),numbervars(true),
 1049      attributes(ignore),
 1050      character_escapes(true),fullstop(false),quoted(true)|Options]))),!.
 1051
 1052is_var_name_goal(C):-compound(C),C=name_variable(_,_).
 1053
 1054portray_append_goals(Var,Goals,Var):- Goals==[],!.
 1055portray_append_goals(Var,Goals,Var):- Goals==true,!.
 1056portray_append_goals(Var,Goals,VarO):- exclude(is_var_name_goal,Goals,NewGoals)->Goals\==NewGoals,!,
 1057   portray_append_goals(Var,NewGoals,VarO).
 1058portray_append_goals(Var,Goals,(maplist(call,Goals),Var)):-var(Var),!.
 1059portray_append_goals(H:-B,Goals,H:-CGMsg):-!,portray_append_goals(B,Goals,CGMsg).
 1060portray_append_goals(H:B,Goals,H:CGMsg):-!,portray_append_goals(B,Goals,CGMsg).
 1061portray_append_goals(Var,Goals,(maplist(call,Goals),Var)).
 1062
 1063
 1064
 1065%dzotrace(G):- notrace(G),!.
 1066dzotrace(G):- notrace(woi(no_bfly(G))),!.
 1067
 1068woi(G):- scce_orig(G,true,true).
 1069
 1070%=
 portray_clause_w_vars(?Msg, ?Vs, ?Options) is det
Portray Clause W Variables.
 1076portray_clause_w_vars(Msg,Vs,Options):- portray_clause_w_vars(current_output,Msg,Vs,Options).
 1077
 1078%=
 portray_clause_w_vars(?Msg, ?Options) is det
Portray Clause W Variables.
 1084portray_clause_w_vars(Msg,Options):- source_variables_lwv(Msg,Vs),portray_clause_w_vars(current_output,Msg,Vs,Options).
 1085
 1086:- export(portray_clause_w_vars/1). 1087
 1088%=
 portray_clause_w_vars(?Msg) is det
Portray Clause W Variables.
 1094portray_clause_w_vars(Msg):- portray_clause_w_vars(Msg,[]),!.
 1095
 1096
 1097%=
 print_prepended(?Pre, ?S) is det
Print Prepended.
 1103print_prepended(Pre,S):-prepend_trim(S,S0),atomics_to_string(L,'\n',S0),print_prepended_lines(Pre,L),!.
 1104
 1105is_html_white_l('\r').
 1106is_html_white_l('<br/>').
 1107is_html_white_l('<br>').
 1108is_html_white_l('<p>').
 1109is_html_white_l('<p/>').
 1110is_html_white_l('\n').
 1111
 1112is_html_white_r(' ').
 1113is_html_white_r('&nbsp;').
 1114is_html_white_r('\t').
 1115is_html_white_r(X):- is_html_white_l(X).
 1116
 1117prepend_trim(S,O):- is_html_white_l(W),atom_concat(W,L,S),!,prepend_trim(L,O).
 1118prepend_trim(S,O):- is_html_white_r(W),atom_concat(L,W,S),!,prepend_trim(L,O).
 1119prepend_trim(O,O).
 1120
 1121
 1122
 1123like_clause([S|Lines]):- (atom_contains(S,':-');atom_contains(S,'?-');(append(_,[E],Lines),atom_contains(E,'.'))),!.
 print_prepended_lines(?Pre, :TermARG2) is det
Print Prepended Lines.
 1130print_prepended_lines(_,[]):- !.
 1131print_prepended_lines(X,[Line]):- (X==guess; X==(block); X==line), !, cmt_override(LineC,_S,_E),print_prepended_line(LineC, Line).
 1132print_prepended_lines(X,Lines):- cmt_override(LineC,_S,_E), (X==line ; X == LineC), like_clause(Lines), print_prepended_lines0(LineC,Lines).
 1133print_prepended_lines(guess,Lines):- !,
 1134  (like_clause(Lines) -> print_prepended_lines(block,Lines);print_prepended_lines(line,Lines)).
 1135print_prepended_lines(block,[S|Lines]):- !, append(Mid,[E],Lines), % atom_contains(E,'.'),
 1136  cmt_override(_,S,End),
 1137  format('~N~w ',[S]),write(S),
 1138  print_prepended_lines0('   ',Mid),
 1139  format('~N ~w ~w~n',[E,End]).
 1140print_prepended_lines(Pre,A):- !, print_prepended_lines0(Pre,A).
 1141
 1142print_prepended_lines0(_Pre,[]).
 1143print_prepended_lines0(_Pre,['']):-!.
 1144print_prepended_lines0(Pre,[H|T]):- print_prepended_line(Pre,H),
 1145  print_prepended_lines0(Pre,T),!.
 1146
 1147print_prepended_line(line,S):- cmt_override(Line,_S,_E),!, print_prepended_line(Line,S).
 1148print_prepended_line(Pre,S):- prepend_trim(S,H),
 1149  ignore((H\=="",
 1150  line_pos(current_output,LPos1),new_line_if_needed,line_pos(current_output,LPos2),
 1151  (LPos1\==LPos2->format('~w~w',[Pre,H]); format('~w~w',[Pre,H])))).
 1152
 1153
 1154%=
 in_cmt(:Goal) is nondet
In Comment.
 1161% in_cmt(Goal):- tlbugger:no_slow_io,!,format('~N/*~n',[]),call_cleanup(Goal,format('~N*/~n',[])).
 1162% in_cmt(Goal):- use_html_styles,!, Goal.
 1163
 1164in_cmt(Goal):- in_cmt(guess,Goal).
 1165
 1166with_cmt_override(LineC,S,E,Goal):-
 1167   cmt_override(WLineC,WS,WE),
 1168   scce_orig(nb_setval(cmt_override,lse(LineC,S,E)),Goal,nb_setval(cmt_override,lse(WLineC,WS,WE))).
 1169cmt_override(LineC,S,E):- nb_current(cmt_override,lse(LineC,S,E)),!.
 1170cmt_override('%~ ','/*','*/').
 1171
 1172in_cmt(line,Goal):- !, maybe_bfly_html(prepend_each_line(line,Goal)),!.
 1173in_cmt(block,Goal):- cmt_override(_,S,E), !, maybe_bfly_html(scce_orig((write(' '),write(S),write(' ')), call(Goal),(write(' '),write(E),write(' ')))).
 1174in_cmt(guess,Goal):-
 1175   get_indent_level(Indent),
 1176   indent_to_spaces(Indent,Space),
 1177   wots(S,prepend_each_line(Space,Goal)),
 1178   trim2(S,SS),!,
 1179   %atomic_list_concat(SL,'\n',S),
 1180   ( atom_contains(SS,'\n')->in_cmt(block,write(S));in_cmt(line,write(S))).
 1181
 1182
 1183in_cmt(Block,Goal):- maybe_bfly_html(print_prepended_line(Block,Goal)),!.
 1184
 1185
 1186%=
 with_current_indent(:Goal) is nondet
Using Current Indent.

with_current_indent(Goal):- use_html_styles,!, Goal.

 1193with_current_indent(Goal):-
 1194   get_indent_level(Indent),
 1195   indent_to_spaces(Indent,Space),
 1196   prepend_each_line(Space,Goal).
 1197
 1198
 1199%=
 indent_to_spaces(:PRED3N, ?Out) is det
Indent Converted To Spaces.
 1205indent_to_spaces(1,' '):-!.
 1206indent_to_spaces(0,''):-!.
 1207indent_to_spaces(2,'  '):-!.
 1208indent_to_spaces(3,'   '):-!.
 1209indent_to_spaces(N,Out):- 1 is N rem 2,!, N1 is N-1, indent_to_spaces(N1,Spaces),atom_concat(' ',Spaces,Out).
 1210indent_to_spaces(N,Out):- N2 is N div 2, indent_to_spaces(N2,Spaces),atom_concat(Spaces,Spaces,Out).
 1211
 1212
 1213%=
 mesg_color(:TermT, ?C) is det
Mesg Color.
 1219mesg_color(_,[reset]):-tlbugger:no_slow_io,!.
 1220mesg_color(T,C):-var(T),!,C=[blink(slow),fg(red),hbg(black)],!.
 1221mesg_color(T,[fg(C)]):- atomic(T), into_color_name(T,C),!.
 1222mesg_color(T,C):- if_defined(is_sgr_on_code(T)),!,C=T.
 1223mesg_color(T,C):-cyclic_term(T),!,C=[reset,blink(slow),bold].
 1224mesg_color("",C):- !,C=[blink(slow),fg(red),hbg(black)],!.
 1225mesg_color([_,_,_,T|_],C):-atom(T),mesg_color(T,C).
 1226mesg_color(T,C):- string(T),!,(f_word(T,F)),!,functor_color(F,C).
 1227mesg_color(List,C):-is_list(List),member(T,List),atom(T),mesg_color(T,C),!.
 1228mesg_color([T|_],C):-nonvar(T),!,mesg_color(T,C),!.
 1229mesg_color(T,C):-(atomic(T);is_list(T)), dmsg_text_to_string_safe(T,S),!,mesg_color(S,C).
 1230mesg_color(T,C):-not(compound(T)),term_to_atom(T,A),!,mesg_color(A,C).
 1231mesg_color(succeed(T),C):-nonvar(T),mesg_color(T,C).
 1232% mesg_color((T),C):- \+ \+ ((predicate_property(T,meta_predicate(_)))),arg(_,T,E),compound(E),!,mesg_color(E,C).
 1233mesg_color(=(T,_),C):-nonvar(T),mesg_color(T,C).
 1234mesg_color(debug(T),C):-nonvar(T),mesg_color(T,C).
 1235mesg_color(_:T,C):-nonvar(T),!,mesg_color(T,C).
 1236mesg_color(:- T,C):-nonvar(T),!,mesg_color(T,C).
 1237mesg_color((H :- T), [bold|C]):-nonvar(T),!,mesg_color(H,C).
 1238mesg_color(T,C):-cfunctor(T,F,_),member(F,[color,ansi]),compound(T),arg(1,T,C),nonvar(C).
 1239mesg_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).
 1240mesg_color(T,C):-cfunctor(T,F,_),member(F,[fmt0,msg,smart_format,fmt]),compound(T),arg(2,T,E),nonvar(E),!,mesg_color(E,C).
 1241mesg_color(T,C):-predef_functor_color(F,C),mesg_arg1(T,F).
 1242mesg_color(T,C):-nonvar(T),defined_message_color(F,C),matches_term(F,T),!.
 1243mesg_color(T,C):-cfunctor(T,F,_),!,functor_color(F,C),!.
 1244
 1245
 1246
 1247%=
 prepend_each_line(?Pre, :Goal) is nondet
Prepend Each Line.
 1254maybe_print_prepended(Out,Pre,S):- atomics_to_string(L,'\n',S), maybe_print_pre_pended_L(Out,Pre,L).
 1255maybe_print_prepended(Out,_,[L]):- write(Out,L),!,flush_output(Out).
 1256maybe_print_prepended(Out,Pre,[H|L]):- write(Out,H),nl(Out),!,write(Out,Pre),maybe_print_pre_pended_L(Out,Pre,L).
 1257
 1258prepend_each_line(Pre,Goal):- fail,
 1259  current_predicate(predicate_streams:new_predicate_output_stream/2),!,
 1260  current_output(Out),
 1261  call(call,predicate_streams:new_predicate_output_stream([Data]>>maybe_print_prepended(Out,Pre,Data),Stream)),
 1262  set_stream_ignore(Stream,tty(true)),
 1263  %set_stream_ignore(Stream,buffer(false)),
 1264  %undo(ignore(catch(close(Stream),_,true))),!,
 1265  scce_orig(true,
 1266   (with_output_to_each(Stream,once(Goal)),flush_output(Stream)),
 1267    ignore(catch(close(Stream),_,true))),!.
 1268
 1269prepend_each_line(Pre,Goal):-
 1270  with_output_to_each(string(Str),Goal)*->once((print_prepended(Pre,Str),new_line_if_needed)).
 1271
 1272prepend_each_line1(Pre,Goal):-
 1273  wots(string(Str),Goal)*->once((print_prepended(Pre,Str),new_line_if_needed)).
 1274
 1275into_cmt(SSS,Cmt):-
 1276 cmt_override(Line,_,_),
 1277  wots(Cmt,print_prepended(Line, SSS)).
 1278
 1279:- meta_predicate if_color_debug(0). 1280:- meta_predicate if_color_debug(0,0). 1281
 1282%=
 if_color_debug is det
If Color Debug.
 1288if_color_debug:-current_prolog_flag(dmsg_color,true).
 1289
 1290%=
 if_color_debug(:Goal) is nondet
If Color Debug.
 1296if_color_debug(Goal):- if_color_debug(Goal, true).
 1297
 1298%=
 if_color_debug(:Goal, :GoalUnColor) is det
If Color Debug.
 1304if_color_debug(Goal,UnColor):- (if_color_debug->Goal;UnColor),!.
 1305
 1306
 1307
 1308color_line(C,N):-
 1309 dzotrace((
 1310  new_line_if_needed,
 1311    forall(between(1,N,_),ansi_term:
 1312      terminal_ansi_format([fg(C)],"%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%\n",[])))).
 1313
 1314
 1315
 1316% % = :- export((portray_clause_w_vars/4,ansicall/3,ansi_control_conv/2)).
 1317
 1318:- thread_local(tlbugger:skipDumpST9/0). 1319:- thread_local(tlbugger:skipDMsg/0). 1320
 1321% @(dmsg0(succeed(S_1)),[S_1=logic])
 1322
 1323
 1324:- thread_local(tlbugger:no_slow_io/0). 1325:- multifile(tlbugger:no_slow_io/0). 1326%:- asserta(tlbugger:no_slow_io).
 1327
 1328:- create_prolog_flag(retry_undefined,none,[type(term),keep(true)]). 1329
 1330
 1331:- thread_local(t_l:hide_dmsg/0). 1332%=
 dmsg(?C) is det
(debug)message.
 1338dmsg(_):- t_l:hide_dmsg, \+ tlbugger:no_slow_io, !.
 1339dmsg(C):- dzotrace((tlbugger:no_slow_io,!,stream_property(X,file_no(2)),writeln(X,dmsg(C)))).
 1340dmsg(V):- quietly(likely_folded((locally(set_prolog_flag(retry_undefined,none),
 1341  if_defined_local(dmsg0(V),logicmoo_util_catch:ddmsg(V)))))),!.
 1342%dmsg(F,A):- dzotrace((tlbugger:no_slow_io,on_x_fail(smart_format(atom(S),F,A))->writeln(dmsg(S));writeln(dmsg_fail(F,A)))),!.
 1343
 1344:- system:import(dmsg/1). 1345% system:dmsg(O):-logicmoo_util_dmsg(O).
 1346%=
 dmsg(?F, ?A) is det
(debug)message Primary Helper.
 1352dmsg(F,A):- transform_mesg(F,A,FA),!,dmsg(FA).
 1353
 1354transform_mesg(F,A,ansi(F,A)):- is_sgr_on_code(F),!.
 1355transform_mesg(warning,A,warning(A)).
 1356transform_mesg(error,A,error(A)).
 1357transform_mesg(info,A,info(A)).
 1358transform_mesg(information,A,A).
 1359transform_mesg(F,A,fmt0(F,A)).
 1360
 1361%dmsg(F,A):-
 1362%              if_defined_local(dmsg0(F,A),logicmoo_util_catch:ddmsg(F,A))),!.
 1363
 1364%with_output_to_main_error(G):- !,call(G).
 1365
 1366with_output_to_main_error(G):-
 1367  t_l:thread_local_error_stream(Where),!,
 1368  with_output_to_each(Where,G).
 1369with_output_to_main_error(G):-
 1370  with_output_to_real_main_error(G).
 1371
 1372%:- volatile(tmp:real_main_error/1).
 1373:- dynamic(tmp:real_main_error/1). 1374
 1375save_real_main_error:-
 1376 % volatile(tmp:real_main_error/1),
 1377  dynamic(tmp:real_main_error/1),
 1378  stream_property(Err,file_no(2)),
 1379  asserta(tmp:real_main_error(Err)).
 1380
 1381:- initialization(retractall(tmp:real_main_error(_)), prepare_state). 1382:- ignore(now_and_later(save_real_main_error)). 1383
 1384with_output_to_real_main_error(G):-
 1385  %set_prolog_flag(occurs_check,false),
 1386  %stream_property(Err,file_no(2)),!,
 1387  tmp:real_main_error(Err) -> with_output_to_each(Err,G); with_output_to_each(user_error,G).
 1388
 1389/*
 1390with_output_to_main_error(G):-
 1391  set_prolog_flag(occurs_check,false),
 1392  stream_property(Err,file_no(2)),
 1393  with_output_to_each(Err,G).
 1394  */
 1395/*
 1396  ignore((get_thread_current_error(TErr),
 1397    \+ same_streams(TErr,Err),
 1398    with_output_to_each(TErr,G))).
 1399
 1400same_streams(TErr,Err):- TErr==Err,!.
 1401same_streams(TErr,Err):- stream_property(TErr,file_no(A)),stream_property(Err,file_no(B)),!,A==B.
 1402*/
 1403:- b_setval('$lm_output_steam',[]). 1404:- nb_setval('$lm_output_steam',[]).
 wdmsg(?X) is semidet
Wdmsg.
 1409wdmsg(_):- ttyflush,current_prolog_flag(debug_level,0),current_prolog_flag(dmsg_level,never),!.
 1410wdmsg(X):- likely_folded(wdmsg_goal(in_cmt(line,fmt(X)),dmsg(X))).
 1411
 1412likely_folded(X):- dis_pp(bfly)->pretty_clauses:with_folding_depth(1,X);call(X).
 1413
 1414wdmsg_goal(G,G2):-
 1415  quietly((ignore(((format('~N'),ttyflush,with_all_dmsg(G2),format('~N'),ttyflush),
 1416  (fmt_visible_to_console -> true ;ignore(on_x_fail(with_output_to_main_error((G))))))))), !.
 1417
 1418fmt_visible_to_console:-
 1419  thread_self(main),
 1420  stream_property(Where,alias(current_output)),!,
 1421  fmt_visible_to_console(Where).
 1422
 1423fmt_visible_to_console(Where):- stream_property(Stderr,file_no(2)), same_streams(Where,Stderr),!.
 1424fmt_visible_to_console(Where):- stream_property(StdOut,file_no(1)), same_streams(Where,StdOut),!.
 1425%fmt_visible_to_console(Where):- stream_property(Where,tty(true)),!.
 wdmsg(?F, ?X) is semidet
Wdmsg.
 1434wdmsg(_,_):- current_prolog_flag(debug_level,0),current_prolog_flag(dmsg_level,never),!.
 1435wdmsg(F,X):- wdmsg_goal(in_cmt(fmt(F,X)),dmsg(F,X)).
 wdmsg(?F, ?X) is semidet
Wdmsg.
 1442wdmsg(W,F,X):- wdmsg_goal(in_cmt(line,fmt(F,X)),dmsg(W,F,X)).
 1443
 1444:- meta_predicate wdmsgl(1,+). 1445:- meta_predicate wdmsgl(+,1,+).
 wdmsgl(?CNF) is det
Wdmsgl.
 1451wdmsgl(X):- dzotrace(wdmsgl(fmt9,X)),!.
 1452wdmsgl(With,X):- (must((wdmsgl('',With,X)))),!.
 1453
 1454wdmsgl(NAME,With,CNF):- is_ftVar(CNF),!,call(With,NAME=CNF).
 1455wdmsgl(_,With,(C:-CNF)):- call(With,(C :-CNF)),!.
 1456%wdmsgl(_,With,'==>'(CNF,C)):- call(With,(C :- (fwc, CNF))),!.
 1457wdmsgl(_,With,(NAME=CNF)):- wdmsgl(NAME,With,CNF),!.
 1458wdmsgl(NAME,With,CNF):- is_list(CNF),must_maplist_det(wdmsgl(NAME,With),CNF),!.
 1459wdmsgl('',With,(C:-CNF)):- call(With,(C :-CNF)),!.
 1460wdmsgl(NAME,With,(C:-CNF)):- call(With,(NAME: C :-CNF)),!.
 1461wdmsgl(NAME,With,(:-CNF)):- call(With,(NAME:-CNF)),!.
 1462wdmsgl(NAME,With,CNF):- call(With,NAME:-CNF),!.
 dmsginfo(?V) is det
Dmsginfo.
 1470dmsginfo(V):-dmsg(info,V).
 1471
 1472%=
 vdmsg(?L, ?F) is det
Vdmsg.
 1479vdmsg(L,F):-loggerReFmt(L,LR),loggerFmtReal(LR,F,[]).
 1480
 1481%=
 dmsg(?L, ?F, ?A) is det
(debug)message.
 1487dmsg(L,F,A):-loggerReFmt(L,LR),loggerFmtReal(LR,F,A).
 1488
 1489:- thread_local(tlbugger:in_dmsg/1). 1490:- dynamic tlbugger:dmsg_hook/1. 1491:- multifile tlbugger:dmsg_hook/1. 1492:- thread_local(t_l:no_kif_var_coroutines/1). 1493
 1494
 1495%=
 dmsg0(?V) is det
(debug)message Primary Helper.
 1502dmsg0(V):-notrace((locally(local_override(no_kif_var_coroutines,true),
 1503   ignore(with_output_to_main_error(dmsg00(V)))))),!.
 1504
 1505%=
 dmsg00(?V) is det
(debug)message Primary Helper Primary Helper.
 1511dmsg00(V):-notrace(var(V)),!,dmsg00(dmsg_var(V)).
 1512dmsg00(V):-cyclic_term(V),!,writeln(cyclic_term),flush_output,writeln(V),!.
 1513dmsg00(call(Code)):- callable(Code), !, with_output_to(string(S),catch((dzotrace(Code)->TF=true;TF=failed),TF,true)),
 1514  (TF=true->dmsg(S);(smart_format(string(S2),'~Ndmsg(call(Code)) of ~q~n~q: ~s ~n',[Code,TF,S]),wdmsg(S2),!,fail)).
 1515dmsg00(V):- catch(dumpst:simplify_goal_printed(V,VV),_,fail),!,dmsg000(VV),!.
 1516dmsg00(V):- dmsg000(V),!.
 dmsg000(?V) is det
(debug)message Primary Helper Primary Helper Primary Helper.
 1524dmsg000(V):-
 1525 with_output_to_main_error(
 1526   (dzotrace(smart_format(string(K),'~p',[V])),
 1527   (tlbugger:in_dmsg(K)-> dmsg5(dmsg5(V));  % format_to_error('~N% ~q~n',[dmsg0(V)]) ;
 1528      asserta(tlbugger:in_dmsg(K),Ref),call_cleanup(dmsg1(V),erase(Ref))))),!.
 1529
 1530% = :- export(dmsg1/1).
 1531
 1532
 1533%=
 dmsg1(?V) is det
(debug)message Secondary Helper.
 1539dmsg1(V):- !, dmsg3(V).
 1540dmsg1(V):- var(V),!,dmsg1(warn(dmsg_var(V))).
 1541dmsg1(_):- current_prolog_flag(dmsg_level,never),!.
 1542dmsg1(V):- tlbugger:is_with_dmsg(FP),!,univ_safe_3(FP,FPL),append(FPL,[V],VVL),univ_safe_3(VV,VVL),once(dmsg1(VV)),!.
 1543dmsg1(NC):- cyclic_term(NC),!,dtrace,format_to_error('~N% ~q~n',[dmsg_cyclic_term_1]).
 1544dmsg1(NC):- tlbugger:skipDMsg,!,loop_check_early(dmsg2(NC),format_to_error('~N% ~q~n',[skipDMsg])),!.
 1545dmsg1(V):- locally(tlbugger:skipDMsg,((once(dmsg2(V)), ignore((tlbugger:dmsg_hook(V),fail))))),!.
 1546
 1547% = :- export(dmsg2/1).
 1548
 1549%=
 dmsg2(:TermNC) is det
(debug)message Extended Helper.
 1555dmsg2(NC):- cyclic_term(NC),!,format_to_error('~N% ~q~n',[dmsg_cyclic_term_2]).
 1556dmsg2(NC):- var(NC),!,format_to_error('~N% DMSG VAR ~q~n',[NC]).
 1557dmsg2(skip_dmsg(_)):-!.
 1558%dmsg2(C):- \+ current_prolog_flag(dmsg_level,always), dmsg_hides_message(C),!.
 1559%dmsg2(trace_or_throw(V)):- dumpST(350),dmsg(warning(V)),fail.
 1560%dmsg2(error(V)):- dumpST(250),dmsg(warning,V),fail.
 1561%dmsg2(warn(V)):- dumpST(150),dmsg(warning,V),fail.
 1562dmsg2(Msg):-quietly((tlbugger:no_slow_io,!,dmsg3(Msg))),!.
 1563dmsg2(color(Ctrl,Msg)):- !,  ansicall(Ctrl,without_color(dmsg3(Msg))).
 1564dmsg2(ansi(Ctrl,Msg)):- !,  ansicall(Ctrl,without_color(dmsg3(Msg))).
 1565dmsg2(Msg):- notrace(mesg_color(Msg,Ctrl)),with_color(ansicall(Ctrl,without_color(dmsg3(Msg)))).
 1566
 1567
 1568%=
 dmsg3(?C) is det
Dmsg3.
 1574dmsg3(C):- tlbugger:no_slow_io,!,writeln(dmsg3(C)).
 1575dmsg3(C):- strip_module(C,_,SM),
 1576  ((cfunctor(SM,Topic,_),debugging(Topic,_True_or_False),logger_property(Topic,once,true),!,
 1577      (dmsg_log(Topic,_Time,C) -> true ; ((get_time(Time),asserta(dmsg_log(todo,Time,C)),!,dmsg4(C)))))),!.
 1578
 1579dmsg3(C):-dmsg4(C),!.
 1580
 1581
 1582%=
 dmsg4(?Msg) is det
Dmsg4.
 1588dmsg4(_):- current_prolog_flag(dmsg_level,never),!.
 1589%dmsg4(Msg):- !,dmsg5(Msg).
 1590dmsg4(Msg):- mline_number,dmsg5(Msg).
 1591
 1592mline_number:-  dis_pp(bfly),!.
 1593mline_number:- (1 is random(5)),!,ignore(dzotrace(once(show_source_location))).
 1594mline_number.
 1595%=
 dmsg5(?Msg) is det
Dmsg5.
 1602dmsg5(Msg):- to_stderror(in_cmt(line,fmt9(Msg))).
 1603
 1604%=
 dmsg5(?Msg, ?Args) is det
Dmsg5.

dmsg5(Msg,Args):- dmsg5(fmt0(Msg,Args)).

 1614%=
 get_indent_level(:PRED2Max) is det
Get Indent Level.
 1620get_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),!.
 1621get_indent_level(2):-!.
 1622
 1623
 1624/*
 1625ansifmt(+Attributes, +Format, +Args) is det
 1626Format text with ANSI attributes. This predicate behaves as smart_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
 1627?- ansifmt([bold,fg(cyan)], 'Hello ~w', [world]).
 1628Attributes 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:
 1629
 1630bold
 1631underline
 1632fg(Color), bg(Color), hfg(Color), hbg(Color)
 1633Defined color constants are below. default can be used to access the default color of the terminal.
 1634
 1635black, red, green, yellow, blue, magenta, cyan, white
 1636ANSI sequences are sent if and only if
 1637
 1638The current_output has the property tty(true) (see stream_property/2).
 1639The Prolog flag color_term is true.
 1640
 1641ansifmt(Ctrl, Format, Args) :- ansifmt(current_output, Ctrl, Format, Args).
 1642
 1643ansifmt(Stream, Ctrl, Format, Args) :-
 1644     % we can "assume"
 1645        % ignore(((stream_property(Stream, tty(true)),current_prolog_flag(color_term, true)))), !,
 1646	(   is_list(Ctrl)
 1647	->  maplist(ansi_term:sgr_code_ex, Ctrl, Codes),
 1648	    atomic_list_concat(Codes, (';'), OnCode)
 1649	;   ansi_term:sgr_code_ex(Ctrl, OnCode)
 1650	),
 1651	'smart_format'(string(Fmt), '\e[~~wm~w\e[0m', [Format]),
 1652        retractall(tlbugger:last_used_color(Ctrl)),asserta(tlbugger:last_used_color(Ctrl)),
 1653	'smart_format'(Stream, Fmt, [OnCode|Args]),
 1654	flush_output,!.
 1655ansifmt(Stream, _Attr, Format, Args) :- 'smart_format'(Stream, Format, Args).
 1656
 1657*/
 1658
 1659% % % OFF :- system:use_module(library(ansi_term)).
 1660
 1661% = :- export(ansifmt/2).
 1662
 1663%=
 ansifmt(?Ctrl, ?Fmt) is det
Ansifmt.
 1669ansifmt(Ctrl,Fmt):- colormsg(Ctrl,Fmt).
 1670% = :- export(ansifmt/3).
 1671
 1672%=
 ansifmt(?Ctrl, ?F, ?A) is det
Ansifmt.
 1678ansifmt(Ctrl,F,A):- colormsg(Ctrl,(smart_format(F,A))).
 1679
 1680
 1681
 1682%=
 debugm(?X) is det
Debugm.
 1688debugm(X):-dzotrace((compound(X),cfunctor(X,F,_),!,debugm(F,X))),!.
 1689debugm(X):-dzotrace((debugm(X,X))).
 1690
 1691%=
 debugm(?Why, ?Msg) is det
Debugm.
 1697debugm(_,_):-dzotrace(current_prolog_flag(dmsg_level,never)),!.
 1698debugm(Why,Msg):- dzotrace((dmsg(debugm(Why,Msg)),!,debugm0(Why,Msg))).
 1699debugm0(Why,Msg):-
 1700   /*\+ debugging(mpred),*/
 1701   \+ debugging(Why), \+ debugging(mpred(Why)),!, debug(Why,'~N~p~n',[Msg]),!.
 1702debugm0(Why,Msg):- debug(Why,'~N~p~n',[Msg]),!.
 colormsg(?Ctrl, ?Msg) is det
Colormsg.
 1710colormsg(d,Msg):- notrace(mesg_color(Msg,Ctrl)),!,colormsg(Ctrl,Msg).
 1711colormsg(Ctrl,Msg):- ansicall(Ctrl,fmt0(Msg)).
 1712
 1713% = :- export(ansicall/2).
 1714
 1715%=
 ansicall(?Ctrl, :Goal) is nondet
Ansicall.
 1722% ansicall(_,Goal):-!,Goal.
 1723%ansicall(Ctrl,Goal):- dzotrace((current_output(Out), ansicall(Out,Ctrl,Goal))).
 1724ansicall(Ctrl,Goal):- ansicall(current_output,Ctrl,Goal),!.
 1725
 1726%in_color(Ctrl,Goal):- ansicall(Ctrl,Goal).
 1727
 1728
 1729%=
 ansi_control_conv(?Ctrl, ?CtrlO) is det
Ansi Control Conv.
 1735ansi_control_conv(Ctrl,CtrlO):-tlbugger:no_slow_io,!,flatten([Ctrl],CtrlO),!.
 1736ansi_control_conv(Ctrl,CtrlO):- ansi_control_conv0(Ctrl,CtrlOO),!,CtrlO=CtrlOO.
 1737ansi_control_conv0([],[]):-!.
 1738ansi_control_conv0(MC,Ctrl):- strip_module(MC,_,C),MC\==C,!,ansi_control_conv0(C,Ctrl).
 1739ansi_control_conv0(warn,Ctrl):- !, ansi_control_conv(warning,Ctrl),!.
 1740ansi_control_conv0(Level,Ctrl):- \+ ground(Level), !, flatten([Level],Ctrl),!.%ansi_control_conv0(Level,Ctrl):- ansi_term:level_attrs(Level,Ansi),Level\=Ansi,!,ansi_control_conv(Ansi,Ctrl).
 1741
 1742ansi_control_conv0(Color,Ctrl):- ansi_term:sgr_code(Color,_),!,Ctrl=Color.
 1743ansi_control_conv0(Color,Ctrl):- ansi_term:off_code(Color,_),!,Ctrl=Color.
 1744ansi_control_conv0(Color,Ctrl):- ansi_term:ansi_color(Color,_),!,ansi_control_conv0(fg(Color),Ctrl).
 1745ansi_control_conv0([H|T],HT):- ansi_control_conv(H,HH),!,ansi_control_conv(T,TT),!,flatten([HH,TT],HT),!.
 1746ansi_control_conv0(Ctrl,CtrlO):-flatten([Ctrl],CtrlO),!.
 1747
 1748
 1749
 1750%=
 is_tty(?Out) is det
If Is A Tty.
 1756:- multifile(tlbugger:no_colors/0). 1757:- thread_local(tlbugger:no_colors/0). 1758is_tty(Out):- \+ tlbugger:no_colors, \+ tlbugger:no_slow_io, is_stream(Out),stream_property(Out,tty(true)).
 1759
 1760use_tty(S,TTY):- \+ compound(S), is_stream(S), stream_property(S,tty(TTY)),!.
 1761use_tty(_,TTY):- stream_property(current_output,tty(TTY)),!.
 1762use_tty(_,false).
 1763
 1764:- meta_predicate(woto_tty(+,+,0)). 1765:- export(woto_tty/3). 1766woto_tty(S,TTY,Goal):- with_output_to_each(S,((set_stream_ignore(current_output,tty(TTY))),Goal)).
 1767
 1768:- meta_predicate(woto(+,0)). 1769:- export(woto/2). 1770woto(S,Goal):- once(use_tty(S,TTY);TTY=true),
 1771  get_stream_setup(Setup), woto_tty(S,TTY,(Setup,Goal)).
 1772
 1773get_stream_setup(S):- S = true,!.
 1774get_stream_setup(S):-
 1775 %G = (current_output(CO),maplist(call,Setup)),
 1776 G = maplist(ignore,Setup),
 1777 %S = (writeln(user_output,G),call(G)),
 1778 G = S,
 1779 Out = current_output,
 1780 Template = set_stream_ignore(Prop),
 1781  bagof(Template,(stream_setup(Prop),stream_property(Out,Prop)),Setup).
 1782
 1783set_stream_ignore(P):- ((current_output(S),set_stream_ignore(S,P)))->true;true.
 1784%set_stream_ignore(_,_):-!.
 1785set_stream_ignore(S,P):- ignore(notrace(catch(set_stream(S,P),E,(writeln(user_error,E=set_stream(S,P)))))).
 1786
 1787stream_setup(encoding(_)).
 1788stream_setup(tty(_)).
 1789stream_setup(representation_errors(_)).
 1790
 1791:- meta_predicate(wots(-,0)). 1792:- export(wots/2). 1793wots(S,Goal):-
 1794   (nb_current('$wots_stack',Was);Was=[]),
 1795   current_output(Out),
 1796     locally(nb_setval('$wots_stack',[Out|Was]),woto(string(S),Goal)).
 1797
 1798:- meta_predicate(wotso(0)). 1799:- export(wotso/1). 1800wotso(Goal):- !, call(Goal).
 1801wotso(Goal):- wots(S,Goal), ignore((S\=="",write(S))).
 1802
 1803:- meta_predicate(wote(0)). 1804:- export(wote/1). 1805wote(G):-stream_property(X,file_no(2)), with_output_to_each(X,G).
 1806
 1807:- meta_predicate(weto(0)). 1808%weto(G):- !, call(G).
 1809:- export(weto/1). 1810weto(G):-
 1811  stream_property(UE,alias(user_error)),
 1812  stream_property(CO,alias(current_output)),
 1813  UE==CO,!,call(G).
 1814
 1815weto(G):- !, with_error_to_each(current_output,G).
 1816weto(G):-
 1817  stream_property(UE,alias(user_error)),
 1818  stream_property(UO,alias(user_output)),
 1819  once(stream_property(CE,alias(current_error));CE=UE),
 1820  once(stream_property(CO,alias(current_output));current_output(CO)),!,
 1821  mscce_orig(
 1822     (set_stream_nop(CO,alias(user_error)),set_stream_nop(CO,alias(user_output)),
 1823         set_stream_nop(CO,alias(current_error)),set_stream_nop(CO,alias(current_output))),
 1824
 1825                locally_tl(thread_local_error_stream(CO),call(G)),
 1826
 1827     (set_stream_nop(UE,alias(user_error)),set_stream_nop(CE,alias(current_error)),
 1828         set_stream_nop(UO,alias(user_output)),set_stream_nop(CO,alias(current_output)))).
 1829weto(G):- call(G).
 1830
 1831set_stream_nop(S,P):- nop(set_stream(S,P)).
 1832
 1833:- meta_predicate(with_ioe(0)). 1834:- export(with_ioe/1). 1835with_ioe(G):-
 1836  stream_property(UE,alias(user_error)),
 1837  stream_property(UO,alias(user_output)),
 1838  once(stream_property(CE,alias(current_error));CE=UE),
 1839  once(stream_property(CO,alias(current_output));current_output(CO)),!,
 1840  scce_orig(true, G,
 1841     (set_stream_ignore(UE,alias(user_error)),set_stream_ignore(CE,alias(current_error)),
 1842         set_stream_ignore(UO,alias(user_output)),set_stream_ignore(CO,alias(current_output)))).
 1843
 1844
 1845%=
 ansicall(?Out, ?UPARAM2, :Goal) is nondet
Ansicall.

in_pengines:- if_defined_local(relative_frame(source_context_module,pengines,_)).

 1853ansicall(_,_,Goal):- (tlbugger:skipDumpST9;tlbugger:no_slow_io),!,call(Goal).
 1854%ansicall(Out,Ctrl,Goal):-  woto(Out,ansicall_2(current_output,Ctrl,Goal)).
 1855ansicall(Out,Ctrl,Goal):- Out == current_output,!,ansicall_2(Out,Ctrl,Goal).
 1856ansicall(Out,Ctrl,Goal):-  woto(Out,ansicall_2(current_output,Ctrl,Goal)).
 1857
 1858ansicall_2(Out,CtrlIn,Goal):- ((ansi_control_conv(CtrlIn,Ctrl);CtrlIn=Ctrl)),!,
 1859  ansicall_3(Out,Ctrl,Goal).
 1860%ansicall_2(Out,Ctrl,Goal):- \+ dis_pp(bfly), !, ansicall_3(Out,Ctrl,Goal).
 1861%ansicall_2(Out,Ctrl,Goal):- bfly_html_goal(ansicall_3(Out,Ctrl,Goal)).
 1862
 1863ansicall_3(Out,Ctrl,Goal):-
 1864   (quietly((retractall(tlbugger:last_used_color(_)),asserta(tlbugger:last_used_color(Ctrl)),!,ansicall_4(Out,Ctrl,Goal)))).
 1865
 1866%maybe_bfly_in_out(G):- on_x_fail(bfly_html_goal(G)),!.
 1867%maybe_bfly_in_out(G):- call(G).
 1868
 1869mUST_det_ll(X):- conjuncts_to_list(X,List),List\=[_],!,maplist(mUST_det_ll,List).
 1870mUST_det_ll(mUST_det_ll(X)):- !, mUST_det_ll(X).
 1871mUST_det_ll(X):- tracing,!,mUST_not_error(X).
 1872mUST_det_ll((X,Y,Z)):- !, (mUST_det_ll(X),mUST_det_ll(Y),mUST_det_ll(Z)).
 1873mUST_det_ll((X,Y)):- !, (mUST_det_ll(X)->mUST_det_ll(Y)).
 1874%mUST_det_ll(if_t(X,Y)):- !, if_t(mUST_not_error(X),mUST_det_ll(Y)).
 1875mUST_det_ll((A->X;Y)):- !,(mUST_not_error(A)->mUST_det_ll(X);mUST_det_ll(Y)).
 1876mUST_det_ll((A*->X;Y)):- !,(mUST_not_error(A)*->mUST_det_ll(X);mUST_det_ll(Y)).
 1877mUST_det_ll((X;Y)):- !, ((mUST_not_error(X);mUST_not_error(Y))->true;mUST_det_ll_failed(X;Y)).
 1878mUST_det_ll(\+ (X)):- !, (\+ mUST_not_error(X) -> true ; mUST_det_ll_failed(\+ X)).
 1879%mUST_det_ll((M:Y)):- nonvar(M), !, M:mUST_det_ll(Y).
 1880mUST_det_ll(once(A)):- !, once(mUST_det_ll(A)).
 1881mUST_det_ll(X):-
 1882  strip_module(X,M,P),functor(P,F,A),scce_orig(nop(trace(M:F/A,+fail)),(mUST_not_error(X)*->true;mUST_det_ll_failed(X)),
 1883    nop(trace(M:F/A,-fail))).
 1884
 1885mUST_not_error(X):- catch(X,E,(E=='$aborted'-> throw(E);(/*arcST,*/wdmsg(E=X),wdmsg(rRTrace(E)=X),rRTrace(X)))).
 1886
 1887mUST_det_ll_failed(X):- notrace,wdmsg(failed(X))/*,arcST*/,nortrace,trace,rRTrace(X),!.
 1888% mUST_det_ll(X):- mUST_det_ll(X),!.
 1889
 1890rRTrace(X):- !, rtrace(X).
 1891rRTrace(X):- notrace,nortrace, arcST, sleep(0.5), trace, (notrace(\+ current_prolog_flag(gui_tracer,true)) -> rtrace(X); (trace,call(X))).
 1892
 1893%=
 ansicall_4(?Out, ?Ctrl, :Goal) is nondet
Ansicall Primary Helper.
 1899ansicall_4(_,[],Goal):-!,call(Goal).
 1900ansicall_4(Out,[Ctrl|Set],Goal):-!, ansicall_4(Out,Ctrl,ansicall_4(Out,Set,mUST_det_ll(Goal))).
 1901ansicall_4(Out,Ctrl,Goal):- keep_line_pos_w_w(Out, ansicall_5(Out,Ctrl,mUST_det_ll(Goal))).
 1902
 1903ansicall_5(Out,Ctrl,Goal):- maybe_bfly_html(ansicall_6(Out,Ctrl,Goal)).
 1904
 1905:- meta_predicate(maybe_bfly_html(0)). 1906maybe_bfly_html(Goal):- current_predicate(ensure_pp/1)->ensure_pp(Goal);call(Goal).
 1907:- meta_predicate(no_bfly(0)). 1908no_bfly(Goal):- current_predicate(in_bfly/2)->in_bfly(f,Goal);call(Goal).
 1909
 1910:- export(maybe_bfly_html/1). 1911
 1912ansicall_6(Out,Ctrl,Goal):- quietly((must(using_style(Out,Ctrl,Goal,How)),!, call(How))).
 1913
 1914:- export(color_format/3). 1915color_format(MC,F,A):-
 1916 notrace(((ansi_control_conv(MC,CC2),
 1917   color_format2(CC2,F,A)))),!.
 1918
 1919:- b_setval('$lm_output_steam',[]). 1920:- nb_setval('$lm_output_steam',[]). 1921
 1922color_format2(C,F,A):-
 1923  (nb_current('$without_color',Was);Was=u),
 1924  (stream_property(current_output, tty(TTY)); TTY=u),
 1925  color_format3(TTY,Was,C,F,A).
 1926
 1927color_format3(_,true,_,F,A):- !, format(F,A).
 1928color_format3(_,false,C,F,A):- !, terminal_ansi_format(C,F,A).
 1929color_format3(_,_,C,F,A):- !, terminal_ansi_format(C,F,A).
 1930
 1931
 1932:- export(terminal_ansi_format/3). 1933%terminal_ansi_format(C,F,A):- ansicall_6(current_output,C,format(F,A)),!.
 1934terminal_ansi_format(Attr, Format, Args) :- terminal_ansi_format(current_output, Attr, Format, Args).
 1935
 1936terminal_ansi_format(Stream, Class, Format, Args):- terminal_ansi_goal(Stream, Class, format(Format, Args)),!.
 1937terminal_ansi_format(Stream, Class, Format, Args):- ansi_term:ansi_format(Stream, Class, Format, Args),!.
 1938
 1939terminal_ansi_goal(Stream, Class, Goal):-
 1940 ansi_term:(
 1941 class_attrs(Class, Attr),
 1942    phrase(sgr_codes_ex(Attr), Codes),
 1943    atomic_list_concat(Codes, ;, Code),
 1944    with_output_to_each(
 1945        Stream,
 1946        scce_orig(
 1947            keep_line_pos(current_output, format('\e[~wm', [Code])),
 1948            call(Goal),
 1949            keep_line_pos(current_output, format('\e[0m'))
 1950        )
 1951    ),
 1952    flush_output).
 1953
 1954
 1955
 1956%=
 keep_line_pos_w_w(?S, :GoalG) is det
Keep Line Pos.

keep_line_pos_w_w(_, G):-!,G.

 1963:- thread_local(bfly_tl:bfly_setting/2). 1964
 1965keep_line_pos_w_w(_, G) :- use_html_styles, !, call(G).
 1966keep_line_pos_w_w(_, G) :- !, call(G).
 1967keep_line_pos_w_w(S, G) :-
 1968      line_pos(S,LPos) ->
 1969         scce_orig(G, set_stream_line_position_safe(S, LPos)) ; call(G).
 1970
 1971line_pos(S,LPos):- stream_property(S, position(Pos)),stream_position_data(line_position, Pos, LPos).
 1972
 1973set_stream_line_position_safe(S,Pos):-
 1974  catch(set_stream_nop(S, line_position(Pos)),E,dmsg(error(E))).
 1975
 1976:- multifile(tlbugger:term_color0/2). 1977:- dynamic(tlbugger:term_color0/2). 1978
 1979
 1980%tlbugger:term_color0(retract,magenta).
 1981%tlbugger:term_color0(retractall,magenta).
 1982
 1983%=
 term_color0(?VALUE1, ?VALUE2) is det
Hook To [term_color0/2] For Module Logicmoo_util_dmsg. Term Color Primary Helper.
 1990tlbugger:term_color0(assertz,hfg(green)).
 1991tlbugger:term_color0(ainz,hfg(green)).
 1992tlbugger:term_color0(aina,hfg(green)).
 1993tlbugger:term_color0(mpred_op,hfg(blue)).
 1994
 1995
 1996
 1997%=
 f_word(?T, ?A) is det
Functor Word.
 2003f_word("",""):-!.
 2004f_word(T,A):-concat_atom(List,' ',T),lists:member(A,List),atom(A),atom_length(A,L),L>0,!.
 2005f_word(T,A):-concat_atom(List,'_',T),lists:member(A,List),atom(A),atom_length(A,L),L>0,!.
 2006f_word(T,A):- string_to_atom(T,P),sub_atom(P,0,10,_,A),A\==P,!.
 2007f_word(T,A):- string_to_atom(T,A),!.
 2008
 2009
 2010%=
 mesg_arg1(:TermT, ?TT) is det
Mesg Argument Secondary Helper.
 2016mesg_arg1(T,_TT):-var(T),!,fail.
 2017mesg_arg1(_:T,C):-nonvar(T),!,mesg_arg1(T,C).
 2018mesg_arg1(T,TT):-not(compound(T)),!,T=TT.
 2019mesg_arg1(T,C):-compound(T),arg(1,T,F),nonvar(F),!,mesg_arg1(F,C).
 2020mesg_arg1(T,F):-cfunctor(T,F,_).
 2021
 2022
 2023% = :- export(defined_message_color/2).
 2024:- dynamic(defined_message_color/2). 2025
 2026
 2027%=
 defined_message_color(?A, ?B) is det
Defined Message Color.
 2033defined_message_color(todo,[fg(red),bg(black),underline]).
 2034defined_message_color(error,[fg(red),hbg(black),bold]).
 2035defined_message_color(warn,[fg(black),hbg(red),bold]).
 2036defined_message_color(A,B):-tlbugger:term_color0(A,B).
 2037
 2038
 2039
 2040%=
 predef_functor_color(?F, ?C) is det
Predef Functor Color.
 2046predef_functor_color(F,C):- defined_message_color(F,C),!.
 2047predef_functor_color(F,C):- defined_message_color(F/_,C),!.
 2048predef_functor_color(F,C):- tlbugger:term_color0(F,C),!.
 2049
 2050
 2051%=
 functor_color(?F, ?C) is det
Functor Color.
 2057functor_color(F,C):- predef_functor_color(F,C),!.
 2058functor_color(F,C):- next_color(C),ignore(on_x_fail(assertz(tlbugger:term_color0(F,C)))),!.
 2059
 2060
 2061:- thread_local(tlbugger:last_used_color/1). 2062
 2063% tlbugger:last_used_color(pink).
 2064
 2065
 2066%=
 last_used_fg_color(?LFG) is det
Last Used Fg Color.
 2072last_used_fg_color(LFG):-tlbugger:last_used_color(LU),fg_color(LU,LFG),!.
 2073last_used_fg_color(default).
 2074
 2075
 2076%=
 good_next_color(?C) is det
Good Next Color.
 2082good_next_color(C):-var(C),!,trace_or_throw(var_good_next_color(C)),!.
 2083good_next_color(C):- last_used_fg_color(LFG),fg_color(C,FG),FG\=LFG,!.
 2084good_next_color(C):- not(unliked_ctrl(C)).
 2085
 2086
 2087%=
 unliked_ctrl(?X) is det
Unliked Ctrl.
 2093unliked_ctrl(fg(blue)).
 2094unliked_ctrl(fg(black)).
 2095unliked_ctrl(fg(red)).
 2096unliked_ctrl(bg(white)).
 2097unliked_ctrl(hbg(white)).
 2098unliked_ctrl(X):-is_list(X),member(E,X),nonvar(E),unliked_ctrl(E).
 2099
 2100
 2101%=
 fg_color(?LU, ?FG) is det
Fg Color.
 2107fg_color(LU,FG):-member(fg(FG),LU),FG\=white,!.
 2108fg_color(LU,FG):-member(hfg(FG),LU),FG\=white,!.
 2109fg_color(_,default).
 2110
 2111% = :- export(random_color/1).
 2112
 2113%=
 random_color(?M) is det
Random Color.
 2119random_color([reset,M,FG,BG,font(Font)]):-Font is random(8),
 2120  findall(Cr,ansi_term:ansi_color(Cr, _),L),
 2121  random_member(E,L),
 2122  random_member(FG,[hfg(E),fg(E)]),not(unliked_ctrl(FG)),
 2123  contrasting_color(FG,BG), not(unliked_ctrl(BG)),
 2124  random_member(M,[bold,faint,reset,bold,faint,reset,bold,faint,reset]),!. % underline,negative
 2125
 2126
 2127% = :- export(tst_color/0).
 2128
 2129%=
 tst_color is det
Tst Color.
 2135tst_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))).
 2136% = :- export(tst_color/1).
 2137
 2138%=
 tst_color(?C) is det
Tst Color.
 2144tst_color(C):- make,colormsg(C,C).
 2145
 2146% = :- export(next_color/1).
 2147
 2148%=
 next_color(:TermC) is det
Next Color.
 2154next_color(C):- between(1,10,_), random_color(C), good_next_color(C),!.
 2155next_color([underline|C]):- random_color(C),!.
 2156
 2157% = :- export(contrasting_color/2).
 2158
 2159%=
 contrasting_color(?A, ?VALUE2) is det
Contrasting Color.
 2165contrasting_color(white,black).
 2166contrasting_color(A,default):-atom(A),A \= black.
 2167contrasting_color(fg(C),bg(CC)):-!,contrasting_color(C,CC),!.
 2168contrasting_color(hfg(C),bg(CC)):-!,contrasting_color(C,CC),!.
 2169contrasting_color(black,white).
 2170contrasting_color(default,default).
 2171contrasting_color(_,default).
 2172
 2173:- thread_local(ansi_prop/2). 2174
 2175
 2176
 2177%=
 sgr_on_code(?Ctrl, :PRED7OnCode) is det
Sgr Whenever Code.
 2183sgr_on_code(Ctrl,OnCode):- sgr_on_code0(Ctrl,OnCode),!.
 2184sgr_on_code(_Foo,7):-!. %  dzotrace((format_to_error('~NMISSING: ~q~n',[bad_sgr_on_code(Foo)]))),!.
 2185
 2186
 2187%=
 is_sgr_on_code(?Ctrl) is det
If Is A Sgr Whenever Code.
 2193is_sgr_on_code(Ctrl):-dzotrace(sgr_on_code0(Ctrl,_)),!.
 2194
 2195
 2196%=
 sgr_on_code0(?Ctrl, :PRED6OnCode) is det
Sgr Whenever Code Primary Helper.
 2202sgr_on_code0(Ctrl,OnCode):- ansi_term:sgr_code(Ctrl,OnCode).
 2203sgr_on_code0(blink, 6).
 2204sgr_on_code0(-Ctrl,OffCode):-  nonvar(Ctrl), sgr_off_code(Ctrl,OffCode).
 2205
 2206
 2207%=
 sgr_off_code(?Ctrl, :GoalOnCode) is det
Sgr Off Code.
 2213sgr_off_code(Ctrl,OnCode):-ansi_term:off_code(Ctrl,OnCode),!.
 2214sgr_off_code(- Ctrl,OnCode):- nonvar(Ctrl), sgr_on_code(Ctrl,OnCode),!.
 2215sgr_off_code(fg(_), CurFG):- (ansi_prop(fg,CurFG)->true;CurFG=39),!.
 2216%sgr_off_code(bg(_), CurBG):- (ansi_prop(ng,CurBG)->true;CurBG=49),!.
 2217sgr_off_code(bg(_), CurBG):- (ansi_prop(bg,CurBG)->true;CurBG=49),!.
 2218sgr_off_code(bold, 21).
 2219sgr_off_code(italic_and_franktur, 23).
 2220sgr_off_code(franktur, 23).
 2221sgr_off_code(italic, 23).
 2222sgr_off_code(underline, 24).
 2223sgr_off_code(blink, 25).
 2224sgr_off_code(blink(_), 25).
 2225sgr_off_code(negative, 27).
 2226sgr_off_code(conceal, 28).
 2227sgr_off_code(crossed_out, 29).
 2228sgr_off_code(framed, 54).
 2229sgr_off_code(overlined, 55).
 2230sgr_off_code(_,0).
 2231
 2232
 2233style_tag(bold,strong).
 2234style_tag(italic,em).
 2235style_tag(underline,u).
 2236style_style(blink,"animation: blinker 0.6s linear infinite;").
 2237style_style(blink(_),"animation: blinker 0.6s linear infinite;").
 2238%style_style(reset,"all: initial;").
 2239%style_style(reset,"display: block").
 2240style_style(reset,"all: unset;").
 2241style_style(font(2),"filter: brightness(60%);").
 2242style_style(font(3),"font-style: italic;").
 2243style_style(font(7),"filter: invert(100%);").
 2244html_on_off(CC,format('<~w>',[C]),format('</~w>',[C])):- style_tag(CC,C).
 2245html_on_off(CC,format('<div style="~w">',[C]),write('</div>')):- style_style(CC,C).
 2246html_on_off(fg(CC),format('<font color="~w">',[C]),write('</font>')):- into_color_name(CC,C).
 2247html_on_off(hfg(CC),format('<font color="~w" style="filter: brightness(85%);">',[C]),write('</font>')):- into_color_name(CC,C).
 2248html_on_off(hbg(CC),format('<div style="background-color: ~w; filter: brightness(85%);">',[C]),write('</div>')):- into_color_name(CC,C).
 2249html_on_off(bg(CC),format('<div style="background-color: ~w;">',[C]),write('</div>')):- into_color_name(CC,C).
 2250html_on_off(CC,format('<font color="~w">',[C]),write('</font>')):- into_color_name(CC,C).
 2251html_on_off(C,format('<div class="~w">',[C]),write('</div>')).
 2252
 2253into_color_name(Default,initial):- Default==default,!.
 2254into_color_name(C,C):- atom(C), ansi_term:ansi_color(C,_).
 2255
 2256
 2257
 2258%=
 sgr_code_on_off(?Ctrl, ?OnCode, ?OffCode) is det
Sgr Code Whenever Off.
 2264sgr_code_on_off(Ctrl,OnCode,OffCode):-sgr_on_code(Ctrl,OnCode),sgr_off_code(Ctrl,OffCode),!.
 2265sgr_code_on_off(_Ctrl,_OnCode,[default]):-!.
 2266
 2267:- thread_local(t_l:once_shown/2). 2268once_in_while(G):- once_in(G,60*5).  % every 5 minutes
 2269once_in(G,Often):- term_to_atom(G,A),
 2270  (( \+ (t_l:once_shown(A,WasThen), When is WasThen+Often, get_time(Now), When < Now))
 2271   -> catch(G,_,fail) ; true),
 2272  retractall(t_l:once_shown(A,_)),
 2273  asserta(t_l:once_shown(A,Now)).
 2274
 2275
 2276
 2277%=
 msg_to_string(:TermVar, ?Str) is det
Msg Converted To String.
 2283msg_to_string(Var,Str):-var(Var),!,sformat(Str,'~q',[Var]),!.
 2284msg_to_string(portray(Msg),Str):- with_output_to_each(string(Str),(current_output(Out),portray_clause_w_vars(Out,Msg,[],[]))),!.
 2285msg_to_string(pp(Msg),Str):- sformat(Str,Msg,[],[]),!.
 2286msg_to_string(fmt(F,A),Str):-sformat(Str,F,A),!.
 2287msg_to_string(smart_format(F,A),Str):-sformat(Str,F,A),!.
 2288msg_to_string(Msg,Str):-atomic(Msg),!,sformat(Str,'~w',[Msg]).
 2289msg_to_string(m2s(Msg),Str):-message_to_string(Msg,Str),!.
 2290msg_to_string(Msg,Str):-sformat(Str,Msg,[],[]),!.
 2291
 2292
 2293:- thread_local t_l:formatter_hook/4. 2294
 2295
 2296%=
 withFormatter(?Lang, ?From, ?Vars, ?SForm) is det
Using Formatter.
 2302withFormatter(Lang,From,Vars,SForm):- t_l:formatter_hook(Lang,From,Vars,SForm),!.
 2303withFormatter(_Lang,From,_Vars,SForm):-sformat(SForm,'~w',[From]).
 2304
 2305
 2306%=
 flush_output_safe is det
Flush Output Safely Paying Attention To Corner Cases.
 2312flush_output_safe:-ignore(catch(flush_output,_,true)).
 2313
 2314%=
 flush_output_safe(?X) is det
Flush Output Safely Paying Attention To Corner Cases.
 2320flush_output_safe(X):-ignore(catch(flush_output(X),_,true)).
 2321
 2322
 2323%=
 writeFailureLog(?E, ?X) is det
Write Failure Log.
 2329writeFailureLog(E,X):-
 2330  get_thread_current_error(ERR),
 2331		(fmt(ERR,'\n% error: ~q ~q\n',[E,X]),flush_output_safe(ERR),!,
 2332		%,true.
 2333		fmt('\n% error: ~q ~q\n',[E,X]),!,flush_output).
 2334
 2335%unknown(Old, autoload).
 2336
 2337
 2338
 2339
 2340%=
 cls is det
Clauses.
 2346cls:- ignore(catch(system:shell(cls,0),_,fail)).
 2347
 2348% % % OFF
 2349:- system:use_module(library(error)). 2350:- system:use_module(library(random)). 2351:- system:use_module(library(terms)). 2352:- system:use_module(library(dif)). 2353:- system:use_module(library(ctypes)). 2354:- system:use_module(library(aggregate)). 2355:- system:use_module(library(pairs)). 2356:- system:use_module(library(option)). 2357%:- list_autoload.
 2358%:- autoload_all.
 2359%:- list_autoload.
 2360%:- ensure_loaded(logicmoo_util_varnames).
 2361%:- ensure_loaded(logicmoo_util_catch).
 2362% :- autoload_all([verbose(false)]).
 2363
 2364/*
 2365:- 'mpred_trace_none'(fmt(_)).
 2366:- 'mpred_trace_none'(fmt(_,_)).
 2367:- 'mpred_trace_none'(dfmt(_)).
 2368:- 'mpred_trace_none'(dfmt(_,_)).
 2369:- 'mpred_trace_none'(dmsg(_)).
 2370:- 'mpred_trace_none'(dmsg(_,_)).
 2371:- 'mpred_trace_none'(portray_clause_w_vars(_)).
 2372*/
 2373
 2374:- ignore((prolog_load_context(source,S),prolog_load_context(module,M),module_property(M,class(library)),
 2375 forall(source_file(M:H,S),
 2376 ignore((cfunctor(H,F,A),
 2377  ignore(((atom(F),\+ atom_concat('$',_,F),(export(F/A) , current_predicate(system:F/A)->true; system:import(M:F/A))))),
 2378  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]))))))))). 2379
 2380:- '$hide'(wdmsg/1). 2381:- '$hide'(wdmsg/2). 2382:- '$hide'(dmsg/1). 2383
 2384:- fixup_exports. 2385:- fixup_module_exports_now.