View source with raw comments or as raw
    1/*  Part of SWI-Prolog
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        J.Wielemaker@vu.nl
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (c)  2014-2023, University of Amsterdam
    7                              VU University Amsterdam
    8                              CWI, Amsterdam
    9                              SWI-Prolog Solutions b.v.
   10    All rights reserved.
   11
   12    Redistribution and use in source and binary forms, with or without
   13    modification, are permitted provided that the following conditions
   14    are met:
   15
   16    1. Redistributions of source code must retain the above copyright
   17       notice, this list of conditions and the following disclaimer.
   18
   19    2. Redistributions in binary form must reproduce the above copyright
   20       notice, this list of conditions and the following disclaimer in
   21       the documentation and/or other materials provided with the
   22       distribution.
   23
   24    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   25    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   26    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   27    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   28    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   29    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   30    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   31    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   32    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   33    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   34    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   35    POSSIBILITY OF SUCH DAMAGE.
   36*/
   37
   38:- module(prolog_pretty_print,
   39          [ print_term/2        % +Term, +Options
   40          ]).   41:- autoload(library(option),
   42            [merge_options/3, select_option/3, select_option/4,
   43             option/2, option/3]).

Pretty Print Prolog terms

This module is a first start of what should become a full-featured pretty printer for Prolog terms with many options and parameters. Eventually, it should replace portray_clause/1 and various other special-purpose predicates.

To be done
- This is just a quicky. We need proper handling of portray/1, avoid printing very long terms multiple times, spacing (around operators), etc.
- Use a record for the option-processing.
- The current approach is far too simple, often resulting in illegal terms. */
   62:- predicate_options(print_term/2, 2,
   63                     [ output(stream),
   64                       right_margin(integer),
   65                       left_margin(integer),
   66                       tab_width(integer),
   67                       indent_arguments(integer),
   68                       auto_indent_arguments(integer),
   69                       operators(boolean),
   70                       write_options(list),
   71                       fullstop(boolean),
   72                       nl(boolean)
   73                     ]).
 print_term(+Term, +Options) is det
Pretty print a Prolog term. The following options are processed:
output(+Stream)
Define the output stream. Default is user_output
right_margin(?Column)
Width of a line. If the output is a tty and tty_size/2 can produce a size the default is the number of columns minus 8. Otherwise the default is 72 characters. If the Column is unbound it is unified with the computed value.
left_margin(+Integer)
Left margin for continuation lines. Default is the current line position or 0 if that is not available.
tab_width(+Integer)
Distance between tab-stops. Default is 8 characters.
indent_arguments(+Spec)
Defines how arguments of compound terms are placed. Defined values are:
false
Simply place them left to right (no line-breaks)
true
Place them vertically, aligned with the open bracket (not implemented)
auto (default)
As horizontal if line-width is not exceeded, vertical otherwise. See also auto_indent_arguments(Int)
An integer
Place them vertically aligned, <N> spaces to the right of the beginning of the head.
auto_indent_arguments(+Integer)
Used by indent_arguments(auto) to decide whether to introduce a newline after the `(` or not. If specified and > 0, this provides the default integer for indent_arguments(Int). The "hanging" mode is used if otherwise the indentation increment is twice this value.
operators(+Boolean)
This is the inverse of the write_term/3 option ignore_ops. Default is to respect them.
write_options(+List)
List of options passed to write_term/3 for terms that are not further processed. Default:
    [ numbervars(true),
      quoted(true),
      portray(true)
    ]
fullstop(Boolean)
If true (default false), add a full stop (.) to the output.
nl(Boolean)
If true (default false), add a newline to the output.
  129print_term(Term, Options) :-
  130    defaults(Defs0),
  131    select_option(write_options(WrtDefs), Defs0, Defs),
  132    select_option(write_options(WrtUser), Options, Options1, []),
  133    merge_options(WrtUser, WrtDefs, WrtOpts),
  134    merge_options(Options1, Defs, Options2),
  135    Options3 = [write_options(WrtOpts)|Options2],
  136    default_margin(Options3, Options4),
  137    \+ \+ print_term_2(Term, Options4).
  138
  139print_term_2(Term, Options) :-
  140    prepare_term(Term, Template, Cycles, Constraints),
  141    option(write_options(WrtOpts), Options),
  142    option(max_depth(MaxDepth), WrtOpts, infinite),
  143
  144    dict_create(Context, #, [max_depth(MaxDepth)|Options]),
  145    pp(Template, Context, Options),
  146    print_extra(Cycles, Context, 'where', Options),
  147    print_extra(Constraints, Context, 'with constraints', Options),
  148    (   option(fullstop(true), Options)
  149    ->  option(output(Out), Options),
  150        put_char(Out, '.')
  151    ;   true
  152    ),
  153    (   option(nl(true), Options)
  154    ->  option(output(Out2), Options),
  155        nl(Out2)
  156    ;   true
  157    ).
  158
  159print_extra([], _, _, _) :- !.
  160print_extra(List, Context, Comment, Options) :-
  161    option(output(Out), Options),
  162    format(Out, ', % ~w', [Comment]),
  163    context(Context, indent, Indent),
  164    NewIndent is Indent+4,
  165    modify_context(Context, [indent=NewIndent], Context1),
  166    print_extra_2(List, Context1, Options).
  167
  168print_extra_2([H|T], Context, Options) :-
  169    option(output(Out), Options),
  170    context(Context, indent, Indent),
  171    indent(Out, Indent, Options),
  172    pp(H, Context, Options),
  173    (   T == []
  174    ->  true
  175    ;   format(Out, ',', []),
  176        print_extra_2(T, Context, Options)
  177    ).
 prepare_term(+Term, -Template, -Cycles, -Constraints)
Prepare a term, possibly holding cycles and constraints for printing.
  185prepare_term(Term, Template, Cycles, Constraints) :-
  186    term_attvars(Term, []),
  187    !,
  188    Constraints = [],
  189    '$factorize_term'(Term, Template, Factors),
  190    bind_non_cycles(Factors, 1, Cycles),
  191    numbervars(Template+Cycles+Constraints, 0, _,
  192               [singletons(true)]).
  193prepare_term(Term, Template, Cycles, Constraints) :-
  194    copy_term(Term, Copy, Constraints),
  195    '$factorize_term'(Copy, Template, Factors),
  196    bind_non_cycles(Factors, 1, Cycles),
  197    numbervars(Template+Cycles+Constraints, 0, _,
  198               [singletons(true)]).
  199
  200
  201bind_non_cycles([], _, []).
  202bind_non_cycles([V=Term|T], I, L) :-
  203    unify_with_occurs_check(V, Term),
  204    !,
  205    bind_non_cycles(T, I, L).
  206bind_non_cycles([H|T0], I, [H|T]) :-
  207    H = ('$VAR'(Name)=_),
  208    atom_concat('_S', I, Name),
  209    I2 is I + 1,
  210    bind_non_cycles(T0, I2, T).
  211
  212
  213defaults([ output(user_output),
  214           depth(0),
  215           indent_arguments(auto),
  216           auto_indent_arguments(4),
  217           operators(true),
  218           write_options([ quoted(true),
  219                           numbervars(true),
  220                           portray(true),
  221                           attributes(portray)
  222                         ]),
  223           priority(1200)
  224         ]).
  225
  226default_margin(Options0, Options) :-
  227    default_right_margin(Options0, Options1),
  228    default_indent(Options1, Options).
  229
  230default_right_margin(Options0, Options) :-
  231    option(right_margin(Margin), Options0),
  232    !,
  233    (   var(Margin)
  234    ->  tty_right_margin(Options0, Margin)
  235    ;   true
  236    ),
  237    Options = Options0.
  238default_right_margin(Options0, [right_margin(Margin)|Options0]) :-
  239    tty_right_margin(Options0, Margin).
  240
  241tty_right_margin(Options, Margin) :-
  242    option(output(Output), Options),
  243    stream_property(Output, tty(true)),
  244    catch(tty_size(_Rows, Columns), error(_,_), fail),
  245    !,
  246    Margin is Columns - 8.
  247tty_right_margin(_, 72).
  248
  249default_indent(Options0, Options) :-
  250    option(output(Output), Options0),
  251    (   stream_property(Output, position(Pos))
  252    ->  stream_position_data(line_position, Pos, Column)
  253    ;   Column = 0
  254    ),
  255    option(left_margin(LM), Options0, Column),
  256    Options = [indent(LM)|Options0].
  257
  258
  259                 /*******************************
  260                 *             CONTEXT          *
  261                 *******************************/
  262
  263context(Ctx, Name, Value) :-
  264    get_dict(Name, Ctx, Value).
  265
  266modify_context(Ctx0, Mapping, Ctx) :-
  267    Ctx = Ctx0.put(Mapping).
  268
  269dec_depth(Ctx, Ctx) :-
  270    context(Ctx, max_depth, infinite),
  271    !.
  272dec_depth(Ctx0, Ctx) :-
  273    ND is Ctx0.max_depth - 1,
  274    Ctx = Ctx0.put(max_depth, ND).
  275
  276
  277                 /*******************************
  278                 *              PP              *
  279                 *******************************/
  280
  281pp(Primitive, Ctx, Options) :-
  282    (   atomic(Primitive)
  283    ;   var(Primitive)
  284    ;   Primitive = '$VAR'(Var),
  285        (   integer(Var)
  286        ;   atom(Var)
  287        )
  288    ),
  289    !,
  290    pprint(Primitive, Ctx, Options).
  291pp(Portray, _Ctx, Options) :-
  292    option(write_options(WriteOptions), Options),
  293    option(portray(true), WriteOptions),
  294    option(output(Out), Options),
  295    with_output_to(Out, user:portray(Portray)),
  296    !.
  297pp(List, Ctx, Options) :-
  298    List = [_|_],
  299    !,
  300    context(Ctx, indent, Indent),
  301    context(Ctx, depth, Depth),
  302    option(output(Out), Options),
  303    option(indent_arguments(IndentStyle), Options),
  304    (   (   IndentStyle == false
  305        ->  true
  306        ;   IndentStyle == auto,
  307            print_width(List, Width, Options),
  308            option(right_margin(RM), Options),
  309            Indent + Width < RM
  310        )
  311    ->  pprint(List, Ctx, Options)
  312    ;   format(Out, '[ ', []),
  313        Nindent is Indent + 2,
  314        NDepth is Depth + 1,
  315        modify_context(Ctx, [indent=Nindent, depth=NDepth, priority=999], NCtx),
  316        pp_list_elements(List, NCtx, Options),
  317        indent(Out, Indent, Options),
  318        format(Out, ']', [])
  319    ).
  320pp(Dict, Ctx, Options) :-
  321    is_dict(Dict),
  322    !,
  323    dict_pairs(Dict, Tag, Pairs),
  324    option(output(Out), Options),
  325    option(indent_arguments(IndentStyle), Options),
  326    context(Ctx, indent, Indent),
  327    (   IndentStyle == false ; Pairs == []
  328    ->  pprint(Dict, Ctx, Options)
  329    ;   IndentStyle == auto,
  330        print_width(Dict, Width, Options),
  331        option(right_margin(RM), Options),
  332        Indent + Width < RM         % fits on a line, simply write
  333    ->  pprint(Dict, Ctx, Options)
  334    ;   compound_indent(Out, '~q{ ', Tag, Indent, Nindent, Options),
  335        context(Ctx, depth, Depth),
  336        NDepth is Depth + 1,
  337        modify_context(Ctx, [indent=Nindent, depth=NDepth], NCtx0),
  338        dec_depth(NCtx0, NCtx),
  339        pp_dict_args(Pairs, NCtx, Options),
  340        BraceIndent is Nindent - 2,         % '{ '
  341        indent(Out, BraceIndent, Options),
  342        write(Out, '}')
  343    ).
  344pp(Term, Ctx, Options) :-               % handle operators
  345    compound(Term),
  346    compound_name_arity(Term, Name, Arity),
  347    current_op(Prec, Type, Name),
  348    match_op(Type, Arity, Kind, Prec, Left, Right),
  349    option(operators(true), Options),
  350    !,
  351    quoted_op(Name, QName),
  352    option(output(Out), Options),
  353    context(Ctx, indent, Indent),
  354    context(Ctx, depth, Depth),
  355    context(Ctx, priority, CPrec),
  356    NDepth is Depth + 1,
  357    modify_context(Ctx, [depth=NDepth], Ctx1),
  358    dec_depth(Ctx1, Ctx2),
  359    LeftOptions  = Ctx2.put(priority, Left),
  360    FuncOptions  = Ctx2.put(embrace, never),
  361    RightOptions = Ctx2.put(priority, Right),
  362    (   Kind == prefix
  363    ->  arg(1, Term, Arg),
  364        (   (   space_op(Name)
  365            ;   need_space(Name, Arg, FuncOptions, RightOptions)
  366            )
  367        ->  Space = ' '
  368        ;   Space = ''
  369        ),
  370        (   CPrec >= Prec
  371        ->  format(atom(Buf), '~w~w', [QName, Space]),
  372            atom_length(Buf, AL),
  373            NIndent is Indent + AL,
  374            write(Out, Buf),
  375            modify_context(Ctx2, [indent=NIndent, priority=Right], Ctx3),
  376            pp(Arg, Ctx3, Options)
  377        ;   format(atom(Buf), '(~w~w', [QName,Space]),
  378            atom_length(Buf, AL),
  379            NIndent is Indent + AL,
  380            write(Out, Buf),
  381            modify_context(Ctx2, [indent=NIndent, priority=Right], Ctx3),
  382            pp(Arg, Ctx3, Options),
  383            format(Out, ')', [])
  384        )
  385    ;   Kind == postfix
  386    ->  arg(1, Term, Arg),
  387        (   (   space_op(Name)
  388            ;   need_space(Name, Arg, FuncOptions, LeftOptions)
  389            )
  390        ->  Space = ' '
  391        ;   Space = ''
  392        ),
  393        (   CPrec >= Prec
  394        ->  modify_context(Ctx2, [priority=Left], Ctx3),
  395            pp(Arg, Ctx3, Options),
  396            format(Out, '~w~w', [Space,QName])
  397        ;   format(Out, '(', []),
  398            NIndent is Indent + 1,
  399            modify_context(Ctx2, [indent=NIndent, priority=Left], Ctx3),
  400            pp(Arg, Ctx3, Options),
  401            format(Out, '~w~w)', [Space,QName])
  402        )
  403    ;   arg(1, Term, Arg1),             % Infix operators
  404        arg(2, Term, Arg2),
  405        (   print_width(Term, Width, Options),
  406            option(right_margin(RM), Options),
  407            Indent + Width < RM
  408        ->  ToWide = false,
  409            (   (   space_op(Name)
  410                ;   need_space(Arg1, Name, LeftOptions, FuncOptions)
  411                ;   need_space(Name, Arg2, FuncOptions, RightOptions)
  412                )
  413            ->  Space = ' '
  414            ;   Space = ''
  415            )
  416        ;   ToWide = true,
  417            (   (   is_solo(Name)
  418                ;   space_op(Name)
  419                )
  420            ->  Space = ''
  421            ;   Space = ' '
  422            )
  423        ),
  424        (   CPrec >= Prec
  425        ->  (   ToWide == true,
  426                infix_list(Term, Name, List),
  427                List == [_,_|_]
  428            ->  Pri is min(Left,Right),
  429                modify_context(Ctx2, [space=Space, priority=Pri], Ctx3),
  430                pp_infix_list(List, QName, 2, Ctx3, Options)
  431            ;   modify_context(Ctx2, [priority=Left], Ctx3),
  432                pp(Arg1, Ctx3, Options),
  433                format(Out, '~w~w~w', [Space,QName,Space]),
  434                modify_context(Ctx2, [priority=Right], Ctx4),
  435                pp(Arg2, Ctx4, Options)
  436            )
  437        ;   (   ToWide == true,
  438                infix_list(Term, Name, List),
  439                List = [_,_|_]
  440            ->  Pri is min(Left,Right),
  441                format(Out, '( ', []),
  442                NIndent is Indent + 2,
  443                modify_context(Ctx2,
  444                           [space=Space, indent=NIndent, priority=Pri],
  445                               Ctx3),
  446                pp_infix_list(List, QName, 0, Ctx3, Options),
  447                indent(Out, Indent, Options),
  448                format(Out, ')', [])
  449            ;   format(Out, '(', []),
  450                NIndent is Indent + 1,
  451                modify_context(Ctx2, [indent=NIndent, priority=Left], Ctx3),
  452                pp(Arg1, Ctx3, Options),
  453                format(Out, '~w~w~w', [Space,QName,Space]),
  454                modify_context(Ctx2, [priority=Right], Ctx4),
  455                pp(Arg2, Ctx4, Options),
  456                format(Out, ')', [])
  457            )
  458        )
  459    ).
  460pp(Term, Ctx, Options) :-               % compound
  461    option(output(Out), Options),
  462    option(indent_arguments(IndentStyle), Options),
  463    context(Ctx, indent, Indent),
  464    (   IndentStyle == false
  465    ->  pprint(Term, Ctx, Options)
  466    ;   IndentStyle == auto,
  467        print_width(Term, Width, Options),
  468        option(right_margin(RM), Options),
  469        Indent + Width < RM         % fits on a line, simply write
  470    ->  pprint(Term, Ctx, Options)
  471    ;   compound_name_arguments(Term, Name, Args),
  472        compound_indent(Out, '~q(', Name, Indent, Nindent, Options),
  473        context(Ctx, depth, Depth),
  474        NDepth is Depth + 1,
  475        modify_context(Ctx,
  476                       [indent=Nindent, depth=NDepth, priority=999],
  477                       NCtx0),
  478        dec_depth(NCtx0, NCtx),
  479        pp_compound_args(Args, NCtx, Options),
  480        write(Out, ')')
  481    ).
  482
  483compound_indent(Out, Format, Functor, Indent, Nindent, Options) :-
  484    option(indent_arguments(IndentStyle), Options),
  485    format(string(Buf2), Format, [Functor]),
  486    write(Out, Buf2),
  487    atom_length(Buf2, FunctorIndent),
  488    (   IndentStyle == auto,
  489        option(auto_indent_arguments(IndentArgs), Options),
  490        IndentArgs > 0,
  491        FunctorIndent > IndentArgs*2
  492    ->  true
  493    ;   IndentArgs = IndentStyle
  494    ),
  495    (   integer(IndentArgs)
  496    ->  Nindent is Indent + IndentArgs,
  497        (   FunctorIndent > IndentArgs
  498        ->  indent(Out, Nindent, Options)
  499        ;   true
  500        )
  501    ;   Nindent is Indent + FunctorIndent
  502    ).
  503
  504
  505quoted_op(Op, Atom) :-
  506    is_solo(Op),
  507    !,
  508    Atom = Op.
  509quoted_op(Op, Q) :-
  510    format(atom(Q), '~q', [Op]).
 infix_list(+Term, ?Op, -List) is semidet
True when List is a list of subterms of Term that are the result of the nested infix operator Op. Deals both with xfy and yfx operators.
  518infix_list(Term, Op, List) :-
  519    phrase(infix_list(Term, Op), List).
  520
  521infix_list(Term, Op) -->
  522    { compound(Term),
  523      compound_name_arity(Term, Op, 2)
  524    },
  525    (   {current_op(_Pri, xfy, Op)}
  526    ->  { arg(1, Term, H),
  527          arg(2, Term, Term2)
  528        },
  529        [H],
  530        infix_list(Term2, Op)
  531    ;   {current_op(_Pri, yfx, Op)}
  532    ->  { arg(1, Term, Term2),
  533          arg(2, Term, T)
  534        },
  535        infix_list(Term2, Op),
  536        [T]
  537    ).
  538infix_list(Term, Op) -->
  539    {atom(Op)},                      % we did something before
  540    [Term].
  541
  542pp_infix_list([H|T], QName, IncrIndent, Ctx, Options) =>
  543    pp(H, Ctx, Options),
  544    context(Ctx, space, Space),
  545    (   T == []
  546    ->  true
  547    ;   option(output(Out), Options),
  548        format(Out, '~w~w', [Space,QName]),
  549        context(Ctx, indent, Indent),
  550        NIndent is Indent+IncrIndent,
  551        indent(Out, NIndent, Options),
  552        modify_context(Ctx, [indent=NIndent], Ctx2),
  553        pp_infix_list(T, QName, 0, Ctx2, Options)
  554    ).
 pp_list_elements(+List, +Ctx, +Options) is det
Print the elements of a possibly open list as a vertical list.
  561pp_list_elements(_, Ctx, Options) :-
  562    context(Ctx, max_depth, 0),
  563    !,
  564    option(output(Out), Options),
  565    write(Out, '...').
  566pp_list_elements([H|T], Ctx0, Options) :-
  567    dec_depth(Ctx0, Ctx),
  568    pp(H, Ctx, Options),
  569    (   T == []
  570    ->  true
  571    ;   nonvar(T),
  572        T = [_|_]
  573    ->  option(output(Out), Options),
  574        write(Out, ','),
  575        context(Ctx, indent, Indent),
  576        indent(Out, Indent, Options),
  577        pp_list_elements(T, Ctx, Options)
  578    ;   option(output(Out), Options),
  579        context(Ctx, indent, Indent),
  580        indent(Out, Indent-2, Options),
  581        write(Out, '| '),
  582        pp(T, Ctx, Options)
  583    ).
  584
  585
  586pp_compound_args([], _, _).
  587pp_compound_args([H|T], Ctx, Options) :-
  588    pp(H, Ctx, Options),
  589    (   T == []
  590    ->  true
  591    ;   T = [_|_]
  592    ->  option(output(Out), Options),
  593        write(Out, ','),
  594        context(Ctx, indent, Indent),
  595        indent(Out, Indent, Options),
  596        pp_compound_args(T, Ctx, Options)
  597    ;   option(output(Out), Options),
  598        context(Ctx, indent, Indent),
  599        indent(Out, Indent-2, Options),
  600        write(Out, '| '),
  601        pp(T, Ctx, Options)
  602    ).
  603
  604
  605:- if(current_predicate(is_dict/1)).  606pp_dict_args([Name-Value|T], Ctx, Options) :-
  607    option(output(Out), Options),
  608    line_position(Out, Pos0),
  609    pp(Name, Ctx, Options),
  610    write(Out, ':'),
  611    line_position(Out, Pos1),
  612    context(Ctx, indent, Indent),
  613    Indent2 is Indent + Pos1-Pos0,
  614    modify_context(Ctx, [indent=Indent2], Ctx2),
  615    pp(Value, Ctx2, Options),
  616    (   T == []
  617    ->  true
  618    ;   option(output(Out), Options),
  619        write(Out, ','),
  620        indent(Out, Indent, Options),
  621        pp_dict_args(T, Ctx, Options)
  622    ).
  623:- endif.  624
  625%       match_op(+Type, +Arity, +Precedence, -LeftPrec, -RightPrec
  626
  627match_op(fx,    1, prefix,  P, _, R) :- R is P - 1.
  628match_op(fy,    1, prefix,  P, _, P).
  629match_op(xf,    1, postfix, P, L, _) :- L is P - 1.
  630match_op(yf,    1, postfix, P, P, _).
  631match_op(xfx,   2, infix,   P, A, A) :- A is P - 1.
  632match_op(xfy,   2, infix,   P, L, P) :- L is P - 1.
  633match_op(yfx,   2, infix,   P, P, R) :- R is P - 1.
 indent(+Out, +Indent, +Options)
Newline and indent to the indicated column. Respects the option tab_width. Default is 8. If the tab-width equals zero, indentation is emitted using spaces.
  642indent(Out, Indent, Options) :-
  643    option(tab_width(TW), Options, 8),
  644    nl(Out),
  645    (   TW =:= 0
  646    ->  tab(Out, Indent)
  647    ;   Tabs is Indent // TW,
  648        Spaces is Indent mod TW,
  649        forall(between(1, Tabs, _), put(Out, 9)),
  650        tab(Out, Spaces)
  651    ).
 print_width(+Term, -W, +Options) is det
Width required when printing `normally' left-to-right.
  657print_width(Term, W, Options) :-
  658    option(right_margin(RM), Options),
  659    option(write_options(WOpts), Options),
  660    (   catch(write_length(Term, W, [max_length(RM)|WOpts]),
  661              error(_,_), fail)      % silence uncaught exceptions from
  662    ->  true                         % nested portray callbacks
  663    ;   W = RM
  664    ).
 pprint(+Term, +Context, +Options)
The bottom-line print-routine.
  670pprint(Term, Ctx, Options) :-
  671    option(output(Out), Options),
  672    pprint(Out, Term, Ctx, Options).
  673
  674pprint(Out, Term, Ctx, Options) :-
  675    option(write_options(WriteOptions), Options),
  676    context(Ctx, max_depth, MaxDepth),
  677    (   MaxDepth == infinite
  678    ->  write_term(Out, Term, WriteOptions)
  679    ;   MaxDepth =< 0
  680    ->  format(Out, '...', [])
  681    ;   write_term(Out, Term, [max_depth(MaxDepth)|WriteOptions])
  682    ).
  683
  684
  685		 /*******************************
  686		 *    SHARED WITH term_html.pl	*
  687		 *******************************/
 is_op1(+Name, -Type, -Priority, -ArgPriority, +Options) is semidet
True if Name is an operator taking one argument of Type.
  694is_op1(Name, Type, Pri, ArgPri, Options) :-
  695    operator_module(Module, Options),
  696    current_op(Pri, OpType, Module:Name),
  697    argpri(OpType, Type, Pri, ArgPri),
  698    !.
  699
  700argpri(fx, prefix,  Pri0, Pri) :- Pri is Pri0 - 1.
  701argpri(fy, prefix,  Pri,  Pri).
  702argpri(xf, postfix, Pri0, Pri) :- Pri is Pri0 - 1.
  703argpri(yf, postfix, Pri,  Pri).
 is_op2(+Name, -LeftPri, -Pri, -RightPri, +Options) is semidet
True if Name is an operator taking two arguments of Type.
  709is_op2(Name, LeftPri, Pri, RightPri, Options) :-
  710    operator_module(Module, Options),
  711    current_op(Pri, Type, Module:Name),
  712    infix_argpri(Type, LeftPri, Pri, RightPri),
  713    !.
  714
  715infix_argpri(xfx, ArgPri, Pri, ArgPri) :- ArgPri is Pri - 1.
  716infix_argpri(yfx, Pri, Pri, ArgPri) :- ArgPri is Pri - 1.
  717infix_argpri(xfy, ArgPri, Pri, Pri) :- ArgPri is Pri - 1.
 need_space(@Term1, @Term2, +LeftOptions, +RightOptions)
True if a space is needed between Term1 and Term2 if they are printed using the given option lists.
  725need_space(T1, T2, _, _) :-
  726    (   is_solo(T1)
  727    ;   is_solo(T2)
  728    ),
  729    !,
  730    fail.
  731need_space(T1, T2, LeftOptions, RightOptions) :-
  732    end_code_type(T1, TypeR, LeftOptions.put(side, right)),
  733    end_code_type(T2, TypeL, RightOptions.put(side, left)),
  734    \+ no_space(TypeR, TypeL).
  735
  736no_space(punct, _).
  737no_space(_, punct).
  738no_space(quote(R), quote(L)) :-
  739    !,
  740    R \== L.
  741no_space(alnum, symbol).
  742no_space(symbol, alnum).
 end_code_type(+Term, -Code, Options)
True when code is the first/last character code that is emitted by printing Term using Options.
  749end_code_type(_, Type, Options) :-
  750    MaxDepth = Options.max_depth,
  751    integer(MaxDepth),
  752    Options.depth >= MaxDepth,
  753    !,
  754    Type = symbol.
  755end_code_type(Term, Type, Options) :-
  756    primitive(Term, _),
  757    !,
  758    quote_atomic(Term, S, Options),
  759    end_type(S, Type, Options).
  760end_code_type(Dict, Type, Options) :-
  761    is_dict(Dict, Tag),
  762    !,
  763    (   Options.side == left
  764    ->  end_code_type(Tag, Type, Options)
  765    ;   Type = punct
  766    ).
  767end_code_type('$VAR'(Var), Type, Options) :-
  768    Options.get(numbervars) == true,
  769    !,
  770    format(string(S), '~W', ['$VAR'(Var), [numbervars(true)]]),
  771    end_type(S, Type, Options).
  772end_code_type(List, Type, _) :-
  773    (   List == []
  774    ;   List = [_|_]
  775    ),
  776    !,
  777    Type = punct.
  778end_code_type(OpTerm, Type, Options) :-
  779    compound_name_arity(OpTerm, Name, 1),
  780    is_op1(Name, OpType, Pri, ArgPri, Options),
  781    \+ Options.get(ignore_ops) == true,
  782    !,
  783    (   Pri > Options.priority
  784    ->  Type = punct
  785    ;   op_or_arg(OpType, Options.side, OpArg),
  786        (   OpArg == op
  787        ->  end_code_type(Name, Type, Options)
  788        ;   arg(1, OpTerm, Arg),
  789            arg_options(Options, ArgOptions),
  790            end_code_type(Arg, Type, ArgOptions.put(priority, ArgPri))
  791        )
  792    ).
  793end_code_type(OpTerm, Type, Options) :-
  794    compound_name_arity(OpTerm, Name, 2),
  795    is_op2(Name, LeftPri, Pri, _RightPri, Options),
  796    \+ Options.get(ignore_ops) == true,
  797    !,
  798    (   Pri > Options.priority
  799    ->  Type = punct
  800    ;   arg(1, OpTerm, Arg),
  801        arg_options(Options, ArgOptions),
  802        end_code_type(Arg, Type, ArgOptions.put(priority, LeftPri))
  803    ).
  804end_code_type(Compound, Type, Options) :-
  805    compound_name_arity(Compound, Name, _),
  806    end_code_type(Name, Type, Options).
  807
  808op_or_arg(prefix,  left,  op).
  809op_or_arg(prefix,  right, arg).
  810op_or_arg(postfix, left,  arg).
  811op_or_arg(postfix, right, op).
  812
  813
  814
  815end_type(S, Type, Options) :-
  816    number(S),
  817    !,
  818    (   (S < 0 ; S == -0.0),
  819        Options.side == left
  820    ->  Type = symbol
  821    ;   Type = alnum
  822    ).
  823end_type(S, Type, Options) :-
  824    Options.side == left,
  825    !,
  826    left_type(S, Type).
  827end_type(S, Type, _) :-
  828    right_type(S, Type).
  829
  830left_type(S, Type), atom(S) =>
  831    sub_atom(S, 0, 1, _, Start),
  832    syntax_type(Start, Type).
  833left_type(S, Type), string(S) =>
  834    sub_string(S, 0, 1, _, Start),
  835    syntax_type(Start, Type).
  836left_type(S, Type), blob(S, _) =>
  837    syntax_type("<", Type).
  838
  839right_type(S, Type), atom(S) =>
  840    sub_atom(S, _, 1, 0, End),
  841    syntax_type(End, Type).
  842right_type(S, Type), string(S) =>
  843    sub_string(S, _, 1, 0, End),
  844    syntax_type(End, Type).
  845right_type(S, Type), blob(S, _) =>
  846    syntax_type(")", Type).
  847
  848syntax_type("\"", quote(double)) :- !.
  849syntax_type("\'", quote(single)) :- !.
  850syntax_type("\`", quote(back))   :- !.
  851syntax_type(S, Type) :-
  852    string_code(1, S, C),
  853    (   code_type(C, prolog_identifier_continue)
  854    ->  Type = alnum
  855    ;   code_type(C, prolog_symbol)
  856    ->  Type = symbol
  857    ;   code_type(C, space)
  858    ->  Type = layout
  859    ;   Type = punct
  860    ).
  861
  862is_solo(Var) :-
  863    var(Var), !, fail.
  864is_solo(',').
  865is_solo(';').
  866is_solo('!').
 primitive(+Term, -Class) is semidet
True if Term is a primitive term, rendered using the CSS class Class.
  873primitive(Term, Type) :- var(Term),      !, Type = 'pl-avar'.
  874primitive(Term, Type) :- atom(Term),     !, Type = 'pl-atom'.
  875primitive(Term, Type) :- blob(Term,_),   !, Type = 'pl-blob'.
  876primitive(Term, Type) :- string(Term),   !, Type = 'pl-string'.
  877primitive(Term, Type) :- integer(Term),  !, Type = 'pl-int'.
  878primitive(Term, Type) :- rational(Term), !, Type = 'pl-rational'.
  879primitive(Term, Type) :- float(Term),    !, Type = 'pl-float'.
 operator_module(-Module, +Options) is det
Find the module for evaluating operators.
  885operator_module(Module, Options) :-
  886    Module = Options.get(module),
  887    !.
  888operator_module(TypeIn, _) :-
  889    '$current_typein_module'(TypeIn).
 arg_options(+Options, -OptionsOut) is det
Increment depth in Options.
  895arg_options(Options, Options.put(depth, NewDepth)) :-
  896    NewDepth is Options.depth+1.
  897
  898quote_atomic(Float, String, Options) :-
  899    float(Float),
  900    Format = Options.get(float_format),
  901    !,
  902    format(string(String), Format, [Float]).
  903quote_atomic(Plain, Plain, _) :-
  904    number(Plain),
  905    !.
  906quote_atomic(Plain, String, Options) :-
  907    Options.get(quoted) == true,
  908    !,
  909    (   Options.get(embrace) == never
  910    ->  format(string(String), '~q', [Plain])
  911    ;   format(string(String), '~W', [Plain, Options])
  912    ).
  913quote_atomic(Var, String, Options) :-
  914    var(Var),
  915    !,
  916    format(string(String), '~W', [Var, Options]).
  917quote_atomic(Plain, Plain, _).
  918
  919space_op(:-)