36
37:- module(portray_text,
38 [ portray_text/1, 39 set_portray_text/2, 40 set_portray_text/3, 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.
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).
132portray_text(OnOff) :-
133 set_portray_text(enabled, OnOff).
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
246
247text_code(Code) :-
248 is_text_code(Code),
249 !.
250text_code(9). 251text_code(10). 252text_code(13). 253text_code(C) :- 254 between(32, 126, C).
255
256var_or_numbered(Var) :-
257 var(Var),
258 !.
259var_or_numbered('$VAR'(_)).
278
279'$portray_text_enabled'(Val) :-
280 portray_text_option(enabled, Val)
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):
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
iscodes
(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:
Now make is_text_code/1 accept anything:
Then:
*/