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)  2009-2023, 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:- autoload(library(error), [must_be/2, domain_error/2]).   43
   44:- multifile
   45    is_text_code/1.                     % +Integer

Portray text

SWI-Prolog has the special string data type. However, in Prolog, text may be represented more traditionally as a list of character-codes, i.e. (small) integers (in SWI-Prolog specifically, those are Unicode code points). This results in output like the following (here using the backquote notation which maps text to a list of codes):

?- writeln(`hello`).
[104, 101, 108, 108, 111]

?- atom_codes("hello",X).
X = [104,101,108,108,111].

Unless you know the Unicode tables by heart, this is pretty unpleasant for debugging. Loading library(portray_text) makes the toplevel and debugger consider certain lists of integers as text and print them as text. This is called "portraying". Of course, interpretation is imperfect as there is no way to tell in general whether [65,66] should written as `AB` or as [65,66]. Therefore it is important that the user be aware of the fact that this conversion is enabled. This is why this library must be loaded explicitly.

To be able to copy the printed representation and paste it back, printed text is enclosed in back quotes if current_prolog_flag/2 for the flag back_quotes is codes (the default), and enclosed in double quotes otherwise. Certain control characters are printed out in backslash-escaped form.

The default heuristic only considers list of codes as text if the codes are all from the set of 7-bit ASCII without most of the control characters. A code is classified as text by text_code/1, which in turn calls is_text_code/1. Define portray_text:is_text_code/1 to succeed on additional codes for more flexibility (by default, that predicate succeeds nowhere). For example:

?- maplist([C,R]>>(portray_text:text_code(C)->R=y;R=n),
           `G\u00e9n\u00e9rateur`,Results).
Results = [y,n,y,n,y,y,y,y,y,y].

Now make is_text_code/1 accept anything:

?- [user].
|: portray_text:is_text_code(_).
|: ^D
% user://3 compiled 0.00 sec, 1 clauses
true.

Then:

?- maplist([C,R]>>(portray_text:text_code(C)->R=y;R=n),
           `G\u00e9n\u00e9rateur`,Results).
Results = [y,y,y,y,y,y,y,y,y,y].

*/

  110:- dynamic
  111    portray_text_option/2.  112
  113portray_text_option(enabled, true).
  114portray_text_option(min_length, 3).
  115portray_text_option(ellipsis,  30).
  116
  117pt_option(enabled,    boolean).
  118pt_option(min_length, nonneg).
  119pt_option(ellipsis,   nonneg).
 portray_text(+OnOff:boolean) is det
Switch portraying on or off. If true, consider lists of integers as list of Unicode code points and print them as corresponding text inside quotes: `text` or "text". Quoting depends on the value of current_prolog_flag/2 back_quotes. Same as
?- set_portray_text(enabled, true).
  130portray_text(OnOff) :-
  131    set_portray_text(enabled, OnOff).
 set_portray_text(+Key, +Value) is det
 set_portray_text(+Key, ?Old, +New) is det
Set options for portraying. Defined Keys are:
enabled
Enable/disable portray text
min_length
Only consider for conversion lists of integers that have a length of at least Value. Default is 3.
ellipsis
When converting a list that is longer than Value, display the output as start...end.
  147set_portray_text(Key, New) :-
  148    set_portray_text(Key, _, New).
  149set_portray_text(Key, Old, New) :-
  150    nonvar(Key),
  151    pt_option(Key, Type),
  152    !,
  153    portray_text_option(Key, Old),
  154    (   Old == New
  155    ->  true
  156    ;   must_be(Type, New),
  157        retractall(portray_text_option(Key, _)),
  158        assert(portray_text_option(Key, New))
  159    ).
  160set_portray_text(Key, _, _) :-
  161    domain_error(portray_text_option, Key).
  162
  163
  164:- multifile
  165    user:portray/1.  166:- dynamic
  167    user:portray/1.  168
  169user:portray(Codes) :-
  170    portray_text_option(enabled, true),
  171    '$skip_list'(Length, Codes, _Tail),
  172    portray_text_option(min_length, MinLen),
  173    Length >= MinLen,
  174    mostly_codes(Codes, 0.9),
  175    portray_text_option(ellipsis, IfLonger),
  176    quote(C),
  177    put_code(C),
  178    (   Length > IfLonger
  179    ->  First is IfLonger - 5,
  180        Skip is Length - 5,
  181        skip_first(Skip, Codes, Rest),
  182        put_n_codes(First, Codes, C),
  183        format('...', [])
  184    ;   Rest = Codes
  185    ),
  186    put_var_codes(Rest, C),
  187    put_code(C).
  188
  189quote(0'`) :-
  190    current_prolog_flag(back_quotes, codes),
  191    !.
  192quote(0'").
  193
  194put_n_codes(N, [H|T], C) :-
  195    N > 0,
  196    !,
  197    emit_code(H, C),
  198    N2 is N - 1,
  199    put_n_codes(N2, T, C).
  200put_n_codes(_, _, _).
  201
  202skip_first(N, [_|T0], T) :-
  203    succ(N2, N),
  204    !,
  205    skip_first(N2, T0, T).
  206skip_first(_, L, L).
  207
  208put_var_codes(Var, _) :-
  209    var_or_numbered(Var),
  210    !,
  211    format('|~p', [Var]).
  212put_var_codes([], _).
  213put_var_codes([H|T], C) :-
  214    emit_code(H, C),
  215    put_var_codes(T, C).
  216
  217emit_code(Q, Q)    :- !, format('\\~c', [Q]).
  218emit_code(0'\b, _) :- !, format('\\b').
  219emit_code(0'\r, _) :- !, format('\\r').
  220emit_code(0'\n, _) :- !, format('\\n').
  221emit_code(0'\t, _) :- !, format('\\t').
  222emit_code(C, _) :- put_code(C).
  223
  224mostly_codes(Codes, MinFactor) :-
  225    mostly_codes(Codes, 0, 0, MinFactor).
  226
  227mostly_codes(Var, _, _, _) :-
  228    var_or_numbered(Var),
  229    !.
  230mostly_codes([], Yes, No, MinFactor) :-
  231    Yes >= (Yes+No)*MinFactor.
  232mostly_codes([H|T], Yes, No, MinFactor) :-
  233    integer(H),
  234    H >= 0,
  235    H =< 0x1ffff,
  236    (   text_code(H)
  237    ->  Yes1 is Yes+1,
  238        mostly_codes(T, Yes1, No, MinFactor)
  239    ;   catch(code_type(H, print),error(_,_),fail),
  240        No1 is No+1,
  241        mostly_codes(T, Yes, No1, MinFactor),
  242        (   Yes+No1 > 100
  243        ->  Yes >= (Yes+No1)*MinFactor
  244        ;   true
  245        )
  246    ).
  247
  248% Idea: Maybe accept anything and hex-escape anything non-printable?
  249%       In particular, I could imaging 0 and ESC appearing in text of interest.
  250%       Currently we really accept only 7-bit ASCII so even latin-1 text
  251%       precludes recognition.
  252% Bug?: emit_code/2 can emit backspace but backspace (8) is not accepted below
  253
  254text_code(Code) :-
  255    is_text_code(Code),
  256    !.
  257text_code(9).      % horizontal tab, \t
  258text_code(10).     % newline \n
  259text_code(13).     % carriage return \r
  260text_code(C) :-    % space to tilde (127 is DEL)
  261    between(32, 126, C).
  262
  263var_or_numbered(Var) :-
  264    var(Var),
  265    !.
  266var_or_numbered('$VAR'(_)).
 is_text_code(+Code:nonneg) is semidet
Multifile hook that can be used to extend the set of character codes that is recognised as likely text. By default, is_text_code/1 fails everywhere and internally, only non-control ASCII characters (32-126) and the the control codes (9,10,13) are accepted.
To be done
- we might be able to use the current locale to include the appropriate code page. (Does that really make sense?)