1:- encoding(utf8).
    2:- module(
    3  print_ext,
    4  [
    5    ansi_format/2,        % +Attributes, +String
    6    call_print/1,         % :Goal_1
    7    call_print_boolean/1, % :Goal_0
    8    dcg_ansi_format/2,    % +Attributes, :Dcg_0
    9    print_boolean/1,      % +Boolean
   10    print_json/1,         % +Dict
   11    print_json/2,         % +Indent, +Dict
   12    print_file_peek/2,    % +File, +Length
   13    print_file_peek/3,    % +File, +Length, +Attributes
   14    print_stream_peek/2,  % +In, +Length
   15    print_stream_peek/3,  % +In, +Length, +Attributes
   16    print_term/1,         % +Term
   17   %print_term/2,         % +Term, +Options
   18    print_term_nl/1,      % +Term
   19    print_term_nl/2,      % +Term, +Options
   20    print_term_nl/3       % +Out, +Term, +Options
   21  ]
   22).   23:- reexport(library(ansi_term)).   24:- reexport(library(pprint)).

Support for printing

*/

   30:- use_module(library(call_ext)).   31:- use_module(library(dcg)).   32:- use_module(library(dict)).   33:- use_module(library(file_ext)).   34:- use_module(library(string_ext)).   35
   36:- meta_predicate
   37    call_print(1),
   38    call_print_boolean(0),
   39    dcg_ansi_format(+, //).
 ansi_format(+Attributes:list(compound), +String:string) is det
   47ansi_format(Attrs, String) :-
   48  ansi_format(Attrs, String, []).
 call_print(:Goal_1) is det
   54call_print(Goal_1) :-
   55  catch(call(Goal_1, Term), Error, true),
   56  (var(Error) -> print_term(Term) ; print_message(warning, Error)).
 call_print_boolean(:Goal_0) is det
   62call_print_boolean(Goal_0) :-
   63  call_boolean(Goal_0, Boolean),
   64  print_boolean(Boolean).
 dcg_ansi_format(+Attributes:list(compound), :Dcg_0) is det
   70dcg_ansi_format(Attrs, Dcg_0) :-
   71  string_phrase(Dcg_0, String),
   72  ansi_format(Attrs, String, []).
 print_boolean(+Boolean:boolean) is det
   78print_boolean(false) :-
   79  format("❌").
   80print_boolean(true) :-
   81  format("✓").
 print_json(+Dict:dict) is det
 print_json(+Indent:nonneg, +Dict:dict) is det
   88print_json(Dict) :-
   89  print_json(0, Dict).
   90
   91
   92print_json(N1, Dict) :-
   93  is_dict(Dict), !,
   94  dict_pairs(Dict, Pairs),
   95  format("{\n"),
   96  N2 is N1 + 1,
   97  print_dict_pairs(N2, Pairs),
   98  print_tab(N1),
   99  format("}").
  100print_json(_, Str) :-
  101  string(Str), !,
  102  format('"~s"', [Str]).
  103print_json(_, Term) :-
  104  format("~w", [Term]).
  105
  106print_dict_pair(N, Key-Value) :-
  107  print_tab(N),
  108  format("~a: ", [Key]),
  109  print_json(N, Value).
  110
  111print_dict_pairs(N, [H]) :- !,
  112  print_dict_pair(N, H),
  113  format("\n").
  114print_dict_pairs(N, [H|T]) :-
  115  print_dict_pair(N, H),
  116  format(",\n"),
  117  print_dict_pairs(N, T).
  118
  119print_tab(0) :- !.
  120print_tab(N1) :-
  121  format("  "),
  122  N2 is N1 - 1,
  123  print_tab(N2).
 print_file_peek(+File:atom, +Length:nonneg) is det
 print_file_peek(+File:atom, +Length:nonneg, +Attributes:list(compound)) is det
  130print_file_peek(File, Length) :-
  131  print_file_peek(File, Length, options{}).
  132
  133
  134print_file_peek(File, Length1, Attributes) :-
  135  Length2 is Length1 + 5,
  136  peek_file(File, Length2, String),
  137  print_string_(String, Length1, Attributes).
 print_stream_peek(+In:istream, Length:nonneg) is det
 print_stream_peek(+In:istream, Length:nonneg, +Attributes:list(compound)) is det
  144print_stream_peek(In, Length) :-
  145  print_stream_peek(In, Length, options{}).
  146
  147
  148print_stream_peek(In, Length1, Attributes) :-
  149  Length2 is Length1 + 5,
  150  peek_string(In, Length2, String),
  151  print_string_(String, Length1, Attributes).
 print_term(+Term:term) is det
  157print_term(Term) :-
  158  print_term(Term, []).
 print_term_nl(+Term:term) is det
 print_term_nl(+Term:term, +Options:options) is det
 print_term_nl(+Out:blob, +Term:term, +Options:options) is det
  166print_term_nl(Term) :-
  167  print_term_nl(Term, options{}).
  168
  169
  170print_term_nl(Term, Options) :-
  171  print_term(Term, Options),
  172  nl.
  173
  174
  175print_term_nl(Out, Term, Options) :-
  176  with_output_to(
  177    Out,
  178    (
  179      print_term(Term, Options),
  180      nl
  181    )
  182  ).
  183
  184
  185
  186% SHARED CODE %
  187
  188print_string_(String1, Length, Attributes) :-
  189  string_ellipsis(String1, Length, String2),
  190  (   Attributes == []
  191  ->  format("~s", [String2])
  192  ;   ansi_format(Attributes, String2)
  193  )