View source with formatted 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)  2009-2021, University of Amsterdam
    7                              CWI, Amsterdam
    8                              SWI-Prolog Solutions b.v.
    9    All rights reserved.
   10
   11    Redistribution and use in source and binary forms, with or without
   12    modification, are permitted provided that the following conditions
   13    are met:
   14
   15    1. Redistributions of source code must retain the above copyright
   16       notice, this list of conditions and the following disclaimer.
   17
   18    2. Redistributions in binary form must reproduce the above copyright
   19       notice, this list of conditions and the following disclaimer in
   20       the documentation and/or other materials provided with the
   21       distribution.
   22
   23    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   24    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   25    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   26    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   27    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   28    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   29    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   30    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   31    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   32    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   33    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   34    POSSIBILITY OF SUCH DAMAGE.
   35*/
   36
   37:- module(portray_text,
   38          [ portray_text/1,             % +Bool
   39            set_portray_text/2,         % +Name, +Value
   40            set_portray_text/3,         % +Name, ?Old, +Value
   41
   42            '$portray_text_enabled'/1
   43          ]).   44:- autoload(library(error), [must_be/2, domain_error/2]).   45
   46:- multifile
   47    is_text_code/1.                     % +Integer
   48
   49/** <module> Portray text
   50
   51SWI-Prolog has the special string data   type.  However, in Prolog, text
   52may be represented more traditionally as a list of character-codes, i.e.
   53(small) integers (in SWI-Prolog  specifically,   those  are Unicode code
   54points). This results in  output  like   the  following  (here using the
   55backquote notation which maps text to a list of codes):
   56
   57```
   58?- writeln(`hello`).
   59[104, 101, 108, 108, 111]
   60
   61?- atom_codes("hello",X).
   62X = [104,101,108,108,111].
   63```
   64
   65Unless you know the Unicode tables by   heart, this is pretty unpleasant
   66for debugging. Loading library(portray_text)  makes   the  toplevel  and
   67debugger consider certain lists of integers as   text  and print them as
   68text.  This  is  called  "portraying".   Of  course,  interpretation  is
   69imperfect as there is no way to tell in general whether `[65,66]` should
   70written as =|`AB`|= or as `[65,66]`. Therefore  it is important that the
   71user be aware of the fact that this   conversion is enabled. This is why
   72this library must be loaded explicitly.
   73
   74To be able to copy the printed representation and paste it back, printed
   75text is enclosed in _back quotes_  if current_prolog_flag/2 for the flag
   76`back_quotes` is `codes` (the default), and  enclosed in _double quotes_
   77otherwise.   Certain   control   characters   are     printed   out   in
   78backslash-escaped form.
   79
   80The default heuristic only considers list of  codes as text if the codes
   81are all from the  set  of  7-bit   ASCII  without  most  of  the control
   82characters. A code is classified as text   by text_code/1, which in turn
   83calls is_text_code/1. Define portray_text:is_text_code/1   to succeed on
   84additional codes for  more  flexibility   (by  default,  that  predicate
   85succeeds nowhere). For example:
   86
   87```
   88?- maplist([C,R]>>(portray_text:text_code(C)->R=y;R=n),
   89           `G\u00e9n\u00e9rateur`,Results).
   90Results = [y,n,y,n,y,y,y,y,y,y].
   91```
   92
   93Now make is_text_code/1 accept anything:
   94
   95```
   96?- [user].
   97|: portray_text:is_text_code(_).
   98|: ^D
   99% user://3 compiled 0.00 sec, 1 clauses
  100true.
  101```
  102
  103Then:
  104
  105```
  106?- maplist([C,R]>>(portray_text:text_code(C)->R=y;R=n),
  107           `G\u00e9n\u00e9rateur`,Results).
  108Results = [y,y,y,y,y,y,y,y,y,y].
  109```
  110*/
  111
  112:- dynamic
  113    portray_text_option/2.  114
  115portray_text_option(enabled, true).
  116portray_text_option(min_length, 3).
  117portray_text_option(ellipsis,  30).
  118
  119pt_option(enabled,    boolean).
  120pt_option(min_length, nonneg).
  121pt_option(ellipsis,   nonneg).
  122
  123%!  portray_text(+OnOff:boolean) is det.
  124%
  125%   Switch portraying on or off. If   `true`, consider lists of integers
  126%   as list of Unicode code points and  print them as corresponding text
  127%   inside quotes: =|`text`|= or  =|"text"|=.   Quoting  depends  on the
  128%   value of current_prolog_flag/2 `back_quotes`.  Same as
  129%
  130%       ?- set_portray_text(enabled, true).
  131
  132portray_text(OnOff) :-
  133    set_portray_text(enabled, OnOff).
  134
  135%!  set_portray_text(+Key, +Value) is det.
  136%!  set_portray_text(+Key, ?Old, +New) is det.
  137%
  138%   Set options for portraying.  Defined Keys are:
  139%
  140%     - enabled
  141%       Enable/disable portray text
  142%     - min_length
  143%       Only consider for conversion lists of integers
  144%       that have a length of at least Value. Default is 3.
  145%     - ellipsis
  146%       When converting a list that is longer than Value, elide the
  147%       output at the start using ellipsis, leaving only Value number of
  148%       non-elided characters: =|`...end`|=
  149
  150set_portray_text(Key, New) :-
  151    set_portray_text(Key, _, New).
  152set_portray_text(Key, Old, New) :-
  153    nonvar(Key),
  154    pt_option(Key, Type),
  155    !,
  156    portray_text_option(Key, Old),
  157    (   Old == New
  158    ->  true
  159    ;   must_be(Type, New),
  160        retractall(portray_text_option(Key, _)),
  161        assert(portray_text_option(Key, New))
  162    ).
  163set_portray_text(Key, _, _) :-
  164    domain_error(portray_text_option, Key).
  165
  166
  167:- multifile
  168    user:portray/1.  169:- dynamic
  170    user:portray/1.  171
  172user:portray(Codes) :-
  173    portray_text_option(enabled, true),
  174    '$skip_list'(Length, Codes, _Tail),
  175    portray_text_option(min_length, MinLen),
  176    Length >= MinLen,
  177    all_codes(Codes),
  178    portray_text_option(ellipsis, IfLonger),
  179    quote(C),
  180    put_code(C),
  181    (   Length > IfLonger
  182    ->  First is IfLonger - 5,
  183        Skip is Length - 5,
  184        skip_first(Skip, Codes, Rest),
  185        put_n_codes(First, Codes, C),
  186        format('...', [])
  187    ;   Rest = Codes
  188    ),
  189    put_var_codes(Rest, C),
  190    put_code(C).
  191
  192quote(0'`) :-
  193    current_prolog_flag(back_quotes, codes),
  194    !.
  195quote(0'").
  196
  197put_n_codes(N, [H|T], C) :-
  198    N > 0,
  199    !,
  200    emit_code(H, C),
  201    N2 is N - 1,
  202    put_n_codes(N2, T, C).
  203put_n_codes(_, _, _).
  204
  205skip_first(N, [_|T0], T) :-
  206    succ(N2, N),
  207    !,
  208    skip_first(N2, T0, T).
  209skip_first(_, L, L).
  210
  211put_var_codes(Var, _) :-
  212    var_or_numbered(Var),
  213    !,
  214    format('|~p', [Var]).
  215put_var_codes([], _).
  216put_var_codes([H|T], C) :-
  217    emit_code(H, C),
  218    put_var_codes(T, C).
  219
  220emit_code(Q, Q)    :- !, format('\\~c', [Q]).
  221emit_code(0'\b, _) :- !, format('\\b').
  222emit_code(0'\r, _) :- !, format('\\r').
  223emit_code(0'\n, _) :- !, format('\\n').
  224emit_code(0'\t, _) :- !, format('\\t').
  225emit_code(C, _) :- put_code(C).
  226
  227all_codes(Var) :-
  228    var_or_numbered(Var),
  229    !.
  230all_codes([]).
  231all_codes([H|T]) :-
  232    is_code(H),
  233    all_codes(T).
  234
  235is_code(Term) :-
  236    integer(Term),
  237    Term >= 0,
  238    text_code(Term),
  239    !.
  240
  241% Idea: Maybe accept anything and hex-escape anything non-printable?
  242%       In particular, I could imaging 0 and ESC appearing in text of interest.
  243%       Currently we really accept only 7-bit ASCII so even latin-1 text
  244%       precludes recognition.
  245% Bug?: emit_code/2 can emit backspace but backspace (8) is not accepted below
  246
  247text_code(Code) :-
  248    is_text_code(Code),
  249    !.
  250text_code(9).      % horizontal tab, \t
  251text_code(10).     % newline \n
  252text_code(13).     % carriage return \r
  253text_code(C) :-    % space to tilde (127 is DEL)
  254    between(32, 126, C).
  255
  256var_or_numbered(Var) :-
  257    var(Var),
  258    !.
  259var_or_numbered('$VAR'(_)).
  260
  261%!  is_text_code(+Code:nonneg) is semidet.
  262%
  263%   Multifile hook that can be used to extend the set of character codes
  264%   that is recognised as likely text.  By default, is_text_code/1 fails
  265%   everywhere  and  internally,  only    non-control  ASCII  characters
  266%   (32-126) and the the control codes (9,10,13) are accepted.
  267%
  268%   @tbd we might be able  to  use   the  current  locale to include the
  269%   appropriate code page. (Does that really make sense?)
  270
  271
  272%   '$portray_text_enabled'(-Val)
  273%
  274%   Ask the current status of  text   portraying.  Used by the graphical
  275%   debugger.
  276%
  277%   @deprecated.  Use set_portray_text(enabled, Val, Val).
  278
  279'$portray_text_enabled'(Val) :-
  280    portray_text_option(enabled, Val)