1:- encoding(utf8).
    2:- module(
    3  debug_ext,
    4  [
    5    dcg_debug/2,        % +Flag, :Dcg_0
    6    debug_call/2,       % +Flag, :Goal_0
    7    debug_dict/2,       % +Flag, +Dict
    8    debug_phrase/2,     % +Flag, :Dcg_0
    9    debug_time/2,       % +Flag, +Message
   10    format_debug/2,     % +Flag, +Format
   11    format_debug/3,     % +Flag, +Out, +Format
   12    format_debug/4,     % +Flag, +Out, +Format, +Args
   13    format_interval/2,  % +Index, +Interval
   14    format_interval/5,  % +Index, +Interval, +Out, +Format, +Args
   15    indent_debug/3,     % +Mode, +Flag, +Format
   16    indent_debug/4,     % +Mode, +Flag, +Format, +Args
   17    json_write_debug/2, % +Flag, +Dict
   18    json_write_debug/3  % +Flag, +Out, +Dict
   19  ]
   20).   21:- reexport(library(debug)).

Extended support for debugging

*/

   27:- use_module(library(error)).   28:- use_module(library(http/json)).   29
   30:- use_module(library(dcg)).   31:- use_module(library(print_ext)).   32
   33:- meta_predicate
   34    dcg_debug(+, //),
   35    debug_call(+, 0),
   36    debug_phrase(+, //).   37
   38:- thread_local
   39   debug_indent/1.   40
   41debug_indent(0).
 dcg_debug(+Flag, :Dcg_0) is det
Write the first generation of Dcg_0 as a debug message under the given Flag.
   52dcg_debug(Flag, Dcg_0) :-
   53  debugging(Flag), !,
   54  once(string_phrase(Dcg_0, String)),
   55  debug(Flag, String, []).
   56dcg_debug(_, _).
 debug_call(+Flag:compound, :Goal_0) is det
   62debug_call(Flag, Goal_0) :-
   63  with_output_to(string(String), Goal_0),
   64  debug(Flag, "~s", [String]).
 debug_dict(+Flag:compound, +Dict:dict) is det
   70debug_dict(Flag, Dict) :-
   71  debugging(Flag), !,
   72  with_output_to(string(String), print_term(Dict)),
   73  debug(Flag, "~s", [String]).
   74debug_dict(_, _).
 debug_phrase(+Flag:compound, :Dcg_0) is det
   80debug_phrase(Flag, Dcg_0) :-
   81  dcg_with_output_to(string(String), Dcg_0),
   82  debug(Flag, "~s", [String]).
 debug_time(+Flag:compound, +Message:string) is det
   88debug_time(Flag, Msg) :-
   89  debugging(Flag), !,
   90  get_time(Time),
   91  debug(Flag, Msg, [Time]).
   92debug_time(_, _).
 format_debug(+Flag:term, +Format:string) is det
 format_debug(+Flag:term, +Format:string, +Args:list(term)) is det
 format_debug(+Flag:term, +Out:ostream, +Format:string, +Arguments:list(term)) is det
Allows a line of text to be written to an output stream and -- optionally -- to a debug stream as well.

‘Format’ and ‘Arguments’ are used to compose a line of text. The newline character is automatically added at the end.

Debug information is displayed by calling ‘debug(Flag)’ (see library ‘debug’). ‘Flag’ can be an atom or a compound term.

  109format_debug(Flag, Format) :-
  110  format_debug(Flag, current_output, Format).
  111
  112
  113format_debug(Flag, Out, Format) :-
  114  format_debug(Flag, Out, Format, []).
  115
  116
  117format_debug(Flag, Out, Format, Args) :-
  118  format(Out, Format, Args),
  119  nl(Out),
  120  debug(Flag, Format, Args).
 format_interval(+Index:nonneg, +Interval:nonneg) is det
 format_interval(+Index:nonneg, +Interval:nonneg, +Out, +Format:atom, +Argumentss:list) is det
Only emit a message with a certain interval.
  129format_interval(Index, Interval) :-
  130  format_interval(Index, Interval, user_output, "~D\n", [Index]).
  131
  132
  133format_interval(Index, Interval, Out, Format, Args) :-
  134  Index mod Interval =:= 0, !,
  135  format(Out, Format, Args).
  136format_interval(_, _, _, _, _).
 indent_debug(+Mode:oneof([-1,0,1]), +Flag:compound, +Format:string) is det
 indent_debug(+Mode:oneof([-1,0,1]), +Flag:compound, +Format:string, +Args:list(term)) is det
  144indent_debug(Mode, Flag, Format) :-
  145  indent_debug(Mode, Flag, Format, []).
  146
  147
  148indent_debug(Mode, Flag, Format, Args) :-
  149  debugging(Flag), !,
  150  must_be(oneof([-1,0,1]), Mode),
  151  (retract(debug_indent(N1)) -> N2 is max(0, N1 + Mode) ; N2 = Mode),
  152  assert(debug_indent(N2)),
  153  format(string(Msg1), Format, Args),
  154  (Mode =:= -1 -> N = N1 ; N = N2),
  155  dcg_with_output_to(string(Msg2), msg1(Mode, N, Msg1)),
  156  debug(Flag, "~s", [Msg2]).
  157indent_debug(_, _, _, _).
  158
  159msg1(_, 0, Msg) --> !,
  160  atom(Msg).
  161msg1(Diff, 1, Msg) --> !,
  162  msg_diff1(Diff),
  163  "─",
  164  atom(Msg).
  165msg1(Diff, N1, Msg) -->
  166  ({N1 =:= 1} -> msg_diff2(Diff), "─" ; "│ "),
  167  {N2 is N1 - 1},
  168  msg1(Diff, N2, Msg).
  169
  170msg_diff1(1) --> !, "┌".
  171msg_diff1(0) --> !, "─".
  172msg_diff1(-1) --> "└".
  173
  174msg_diff2(1) --> !, "├".
  175msg_diff2(0) --> !, "└".
  176msg_diff2(-1) --> "└".
 json_write_debug(+Flag:term, +Dict:dict) is det
 json_write_debug(+Flag:term, +Out:ostream, +Dict:dict) is det
  183json_write_debug(Flag, Dict) :-
  184  json_write_debug(Flag, current_output, Dict).
  185
  186
  187json_write_debug(Flag, Out, Dict) :-
  188  debugging(Flag), !,
  189  with_output_to(string(String), json_write_dict(current_output, Dict)),
  190  debug(Flag, "~s", [String]),
  191  format(Out, "~s", [String]).
  192json_write_debug(_, Out, Dict) :-
  193  json_write_dict(Out, Dict)