1 | | % (c) 2009-2024 Lehrstuhl fuer Softwaretechnik und Programmiersprachen, |
2 | | % Heinrich Heine Universitaet Duesseldorf |
3 | | % This software is licenced under EPL 1.0 (http://www.eclipse.org/org/documents/epl-v10.html) |
4 | | |
5 | | :- module(tools_printing,[ |
6 | | print_term_summary/1, print_term_summary_hash/1, |
7 | | print_term_summary_wo_nl/1, |
8 | | print_value_summary/1, |
9 | | print_functor/1, |
10 | | print_var/1, print_vars/1, |
11 | | watch/3, |
12 | | trace_unify/2, trace_print/1, trace_print/2, |
13 | | print_error/1, |
14 | | print_message_on_stream/3, |
15 | | format_error/2, format_error_with_nl/2, |
16 | | no_color/0, |
17 | | set_no_color/1, reset_no_color_to_default/0, |
18 | | print_red/2, print_red/1, print_green/1, |
19 | | format_with_colour/4, format_with_colour_nl/4, |
20 | | start_terminal_colour/2, |
21 | | reset_terminal_colour/1, |
22 | | get_terminal_colour_code/2, |
23 | | print_time_stamp/1, |
24 | | print_dynamic_pred/3, print_dynamic_pred/4, |
25 | | print_dynamic_fact/2, |
26 | | print_goal/1, |
27 | | nested_print_term/2, nested_print_term/1, |
28 | | nested_write_term_to_codes/2, |
29 | | tcltk_nested_read_prolog_file_as_codes/2 |
30 | | ]). |
31 | | |
32 | | |
33 | | :- use_module(module_information). |
34 | | :- module_info(group,infrastructure). |
35 | | :- module_info(description,'This module contains printing/debug helper predicates.'). |
36 | | |
37 | | |
38 | | :- use_module(library(terms),[term_hash/2]). |
39 | | print_term_summary_hash(T) :- print_term_summary(T), |
40 | | term_hash(T,H), %% (H=179896960 -> trace ; true), %% |
41 | | format('Hash = ~w~n',H). |
42 | | |
43 | | %:- use_module(library(terms),[term_size/2]). |
44 | | print_term_summary(T) :- print_term_summary_wo_nl(T), |
45 | | %term_size(T,Sz), format(' term_size: ~w',[Sz]), |
46 | | nl. |
47 | | |
48 | | % a special version for user friendly B Value information |
49 | | print_value_summary(BValue) :- print_arg(BValue),nl. |
50 | | |
51 | | print_term_summary_wo_nl(N) :- var(N),!,write('VARIABLE: '),write(N). |
52 | | print_term_summary_wo_nl((A,B)) :- write('('), print_term_summary_wo_nl(A), |
53 | | write(','), print_term_summary_wo_nl(B),write(')'). |
54 | | print_term_summary_wo_nl(clpfd:Call) :- !, write(clpfd:Call). |
55 | | print_term_summary_wo_nl(Module:Call) :- !, |
56 | | write(Module), write(':'),print_term_summary_wo_nl(Call). |
57 | | print_term_summary_wo_nl(bind(Var,Val)) :- !,print_arg(bind(Var,Val)). |
58 | | print_term_summary_wo_nl(N) :- functor(N,F,Arity), write(F), write('/'),write(Arity), |
59 | | N=..[F|Args], l_print_arg(Args). |
60 | | |
61 | | l_print_arg(V) :- var(V),!, write('...'). |
62 | | l_print_arg([]). |
63 | | l_print_arg([H|T]) :- write(': '), print_arg(H), l_print_arg(T). |
64 | | |
65 | | % print nested args: avoid nesting any further to avoid blowup |
66 | | l_print_nested_arg(V) :- var(V),!, write('...'). |
67 | | l_print_nested_arg([]). |
68 | | l_print_nested_arg([H|T]) :- write(': '), print_nested_arg(H), l_print_nested_arg(T). |
69 | | |
70 | | print_nested_arg(N) :- var(N),!,print_var(N). |
71 | | print_nested_arg([H|T]) :- list_skeleton_size([H|T],Sz,Type), !, |
72 | | write(Type), |
73 | | (Type=closed,ground([H|T]) -> write('&ground') ; true), write(' LIST.size='), write(Sz). |
74 | | print_nested_arg(avl_set(A)) :- ground(A), avl_size(A,Sz),!, write('AVL.size='),write(Sz). |
75 | | print_nested_arg(A) :- print_arg(A). |
76 | | |
77 | | :- use_module(library(avl)). |
78 | | % USE MODULE NOT PERFORMED TO AVOID LOADING translate and all dependent modules |
79 | | %:- use_module(translate,[print_bexpr_with_limit/2, print_bstate/1]). |
80 | | |
81 | | print_arg(N) :- var(N),!,print_var(N). |
82 | | print_arg(int(N)) :- !, (var(N) -> print_var_integer(N) ; write(int(N))). |
83 | | print_arg(term(F)) :- nonvar(F), F=floating(N),!, (var(N) -> write(F) ; write(N)). |
84 | | print_arg(float(N)) :- !, write(float(N)). |
85 | | print_arg(freeval(ID,Case,Value)) :- !, format('freeval ~w.~w : ',[ID,Case]), print_arg(Value). |
86 | | print_arg(fd(N,GS)) :- !, |
87 | | (number(N),b_global_sets:is_b_global_constant(GS,N,Res) -> write(Res) |
88 | | ; write('fd('),print_integer(N),format(',~w)',GS)). |
89 | | print_arg(rec(Fields)) :- !, write('rec('), print_arg(Fields),write(')'). |
90 | | print_arg(bind(Var,Val)) :- atomic(Var), !, write(Var),write('/'),print_arg(Val). |
91 | | print_arg(field(Var,Val)) :- atomic(Var), !, write('field('),write(Var),write('/'),print_arg(Val),write(')'). |
92 | | print_arg(typedvalc(Val,Type,VarID,EnumWarningInfos,Card)) :- |
93 | | atomic(VarID), !, format('typedvalc for ~w :(',[VarID]),print_arg(Val), |
94 | | format(',~w,~w,~w) ',[Type,EnumWarningInfos,Card]). |
95 | | print_arg(wfx(WF0,_Store,WFE,_Infos)) :- !, write(wfx(WF0,'...',WFE,'...')). % do not print store and Infos: TODO we could show call_stack summary |
96 | | print_arg(Module:Call) :- atomic(Module),!, |
97 | | write(Module), write(':'),print_arg(Call). |
98 | | print_arg(A) :- atomic(A),!, write(A). |
99 | | print_arg(A) :- A=node(_,_,_,_,_),ground(A), !, write('AVLnode.size='),avl_size(A,Sz), write(Sz). |
100 | | print_arg(avl_set(A)) :- ground(A), !, |
101 | | (custom_explicit_sets:singleton_set(avl_set(A),El) -> write('AVL{'),print_arg(El),write('}') |
102 | | ; avl_size(A,Sz), |
103 | | (Sz>3 -> write('AVL.size='),write(Sz) |
104 | | ; custom_explicit_sets:expand_custom_set_to_list(avl_set(A),ESet,_,print_arg), |
105 | | write('AVL{'), l_print_nested_arg(ESet), write('}') |
106 | | ) |
107 | | ). |
108 | | print_arg((A,B)) :- !, write('('),print_arg(A), write(','), print_arg(B), write(')'). |
109 | | print_arg(string(A)) :- !, write('string('),print_arg(A), write(')'). |
110 | | print_arg([]) :- !, write('[]'). |
111 | | print_arg([H|T]) :- T==[], !, write('['),print_arg(H),write(']'). |
112 | | print_arg([H|T]) :- nonvar(T),T=[H2|T2],T2==[], !, |
113 | | write('['),print_arg(H),write(','),print_arg(H2),write(']'). |
114 | | print_arg([H|T]) :- nonvar(H), H=bind(_,_),!, get_list_up_to([H|T],10,S,ALL), |
115 | | translate:print_bstate(S), |
116 | | (ALL=all -> true ; write(', ... ')). |
117 | | print_arg([H|T]) :- list_skeleton_size([H|T],Sz,Type), !, |
118 | | write(Type), |
119 | | (Type=closed,ground([H|T]) -> write('&ground') ; true), |
120 | | write(' LIST.size='), write(Sz), |
121 | | (Sz<35 -> write(' ['), l_print_nested_arg([H|T]), write(']') ; true). |
122 | | print_arg(closure(P,T,B)) :- !, |
123 | | (custom_explicit_sets:is_interval_closure(P,T,B,Low,Up) |
124 | | -> write('SYMBOLIC-INTERVAL ['), |
125 | | print_integer_with_var(Low), write('..'), |
126 | | print_integer_with_var(Up), write(']') |
127 | | ; B=b(_,_,INFO), |
128 | | findall(Ann,member(prob_annotation(Ann),INFO),Anns), |
129 | | (closures:is_symbolic_closure(P,T,B) -> INF='ANNOTATED-' |
130 | | ; custom_explicit_sets:is_infinite_or_very_large_closure(P,T,B,200000) -> INF='INF_OR_LARGE-' |
131 | | ; INF=''), |
132 | | format('SYMBOLIC-~wSET(~w) ~w ',[INF,Anns,P]) |
133 | | ). %, write(' | '), write(_B). |
134 | | print_arg(mnf(Call)) :- !, write('mnf('),print_term_summary_wo_nl(Call), write(')'). |
135 | | print_arg(pp_mnf(Call)) :- !, write('mnf('),print_term_summary_wo_nl(Call), write(')'). |
136 | | print_arg(pp_cll(Call)) :- !, write('mnf('),print_term_summary_wo_nl(Call), write(')'). |
137 | | print_arg(b(Expr,T,I)) :- !, |
138 | | (T==pred -> write('PRED(') ; write('BEXPR(')), |
139 | | print_functor(Expr), write(','), |
140 | | translate:print_bexpr_with_limit(b(Expr,T,I),200), |
141 | | (error_manager:extract_line_col(b(Expr,T,I),Srow,Scol,_,_) -> format(', lne:col=~w:~w)',[Srow,Scol]) |
142 | | ; write(')')). |
143 | | print_arg(span_predicate(A,B,C)) :- |
144 | | error_manager:extract_line_col(span_predicate(A,B,C),Srow,Scol,Erow,Ecol), !, |
145 | | format('span_predicate(~w:~w-~w:~w)',[Srow,Scol,Erow,Ecol]). |
146 | | print_arg(N) :- print_functor(N). |
147 | | |
148 | | :- use_module(library(clpfd),[fd_dom/2, fd_degree/2, fd_size/2]). |
149 | | print_var(V) :- fd_dom(V,D), D \= inf..sup, fd_size(V,Sz), fd_degree(V,Dg),!, |
150 | | format('INT VAR: ~w:~w [sz:~w,dg:~w] ',[V,D,Sz,Dg]). |
151 | | %write(':('),frozen(V,Goal),write_term(Goal,[max_depth(3)]),write(')'). |
152 | | print_var(V) :- write('VARIABLE: '),write(V), print_frozen_var_info(V). |
153 | | print_var_integer(X) :- write('int(?:'),fd_dom(X,Dom),write(Dom), |
154 | | %write(':('),frozen(X,Goal),write(Goal),write(')') |
155 | | write(')'). |
156 | | |
157 | | % try determine variable type from frozen info |
158 | ? | print_frozen_var_info(V) :- frozen(V,G), (print_frozen_var_info2(G,V) -> true ; true). |
159 | | print_frozen_var_info2((A,B),V) :- !,(print_frozen_var_info2(A,V) -> true ; print_frozen_var_info2(B,V) -> true). |
160 | | print_frozen_var_info2(true,_) :- !,fail. |
161 | | print_frozen_var_info2(b_interpreter_check:imply_true(_,_,_),_) :- write(' : BOOL'). |
162 | | print_frozen_var_info2(bool_pred:blocking_force_eq(V,_,_),Var) :- Var==V, write(' : BOOL'). |
163 | | print_frozen_var_info2(kernel_equality:eq_empty_set(V,_),Var) :- Var==V, write(' : SET'). |
164 | | print_frozen_var_info2(kernel_equality:eq_empty_set_wf(V,_,_),Var) :- Var==V, write(' : SET'). |
165 | | print_frozen_var_info2(_:non_free(V),Var) :- Var==V, write(' : NON-FREE'). % kernel_objects |
166 | | print_frozen_var_info2(_:ground_value_check(V,_),Var) :- Var==V, write(' : GRVAL-CHECK'). |
167 | | print_frozen_var_info2(_:Call,_Var) :- functor(Call,Functor,Arity),format(' : ~w/~w',[Functor,Arity]). |
168 | | print_frozen_var_info2(Call,_Var) :- functor(Call,Functor,Arity),format(' : ~w/~w',[Functor,Arity]). |
169 | | % TO DO: add other co-routines for boolean values,... |
170 | | |
171 | | :- use_module(library(lists),[maplist/2]). |
172 | | print_vars(V) :- maplist(tools_printing:print_var,V),nl. |
173 | | |
174 | | print_integer(I) :- (var(I) -> fd_dom(I,Dom), write('?:'),write(Dom) ; write(I)). |
175 | | print_integer_with_var(I) :- (var(I) -> print_var(I) ; write(I)). |
176 | | |
177 | | get_list_up_to([],_,[],all). |
178 | | get_list_up_to([H|T],N,R,ALL) :- |
179 | | (N<1 -> R=[],ALL=no ; N1 is N-1, R=[H|TR], get_list_up_to(T,N1,TR,ALL)). |
180 | | |
181 | | list_skeleton_size(X,Sz,Type) :- var(X),!,Sz=0,Type=open. |
182 | | list_skeleton_size([],0,closed). |
183 | | list_skeleton_size([_|T],N,Type) :- list_skeleton_size(T,NT,Type), N is NT+1. |
184 | | |
185 | | |
186 | | print_functor(N) :- var(N),!,write('VARIABLE: '),write(N). |
187 | | print_functor(N) :- functor(N,F,Arity), write(F), write('/'),write(Arity). |
188 | | |
189 | | % --------------- |
190 | | |
191 | | :- block watch(-,?,?). |
192 | | watch([],N,Pos) :- !,print_data([],N,Pos). |
193 | | watch([H|T],N,Pos) :- !,print_data(H,N,Pos), P1 is Pos+1, watch(H,N,Pos), watch(T,N,P1). |
194 | | watch((P1,P2),N,Pos) :- print_data((P1,P2),N,Pos), watch(P2,N,Pos). |
195 | | watch(Other,N,Pos) :- print_data(Other,N,Pos). |
196 | | print_data(Data,N,Pos) :- write(N), write(' @ '), write(Pos),write(' : '), write(Data),nl. |
197 | | |
198 | | % --------------- |
199 | | |
200 | | :- use_module(library(lists),[maplist/3]). |
201 | | trace_unify(A,B) :- trace_unify_aux(A,B,0). |
202 | | trace_unify_aux(A,B,Lvl) :- (var(A);var(B)),!,indent(Lvl),write(A),write(' <-> '), write(B), |
203 | | if(A=B,true,(write(' FAILS'),nl,fail)),nl. |
204 | | trace_unify_aux(A,B,Lvl) :- functor(A,FA,FAN), functor(B,FB,FBN), |
205 | | indent(Lvl),write(FA/FAN), |
206 | | A=..[_|As], B=..[_|Bs], |
207 | | ((FA,FAN)=(FB,FBN) |
208 | | -> (As=[] -> nl ; write('('),nl,l_trace_unify(As,Bs,Lvl)) |
209 | | ; format(' FUNCTOR MISMATCH : ~w/~w <-> ~w/~w~n',[FA,FAN,FB,FBN]), |
210 | | maplist(abstract_top_level,As,AAs), AA =..[FA|AAs], |
211 | | maplist(abstract_top_level,Bs,ABs), AB =..[FB|ABs], |
212 | | indent(Lvl), |
213 | | format(' TOP: ~w <-> ~w~n',[AA,AB]), |
214 | | fail |
215 | | ). |
216 | | indent(0) :- !. |
217 | | indent(X) :- X>800, !, write('*800*-'), X1 is X-800, indent(X1). |
218 | | indent(X) :- X>80, !, write('*80*-'), X1 is X-80, indent(X1). |
219 | | indent(X) :- X>0, write('+-'), X1 is X-1, indent(X1). |
220 | | |
221 | | abstract_top_level(X,R) :- \+ compound(X),!,R=X. |
222 | | abstract_top_level(X,AX) :- functor(X,F,N), functor(AX,F,N). |
223 | | |
224 | | |
225 | | l_trace_unify([],[],L) :- indent(L), write(')'),nl. |
226 | | l_trace_unify([A|TA],[B|TB],Lvl) :- L1 is Lvl+1, trace_unify_aux(A,B,L1), |
227 | | l_trace_unify(TA,TB,Lvl). |
228 | | |
229 | | % --------------- |
230 | | |
231 | | trace_print(A) :- trace_print(A,0,4). |
232 | | trace_print(A,Max) :- trace_print(A,0,Max). |
233 | | |
234 | | trace_print(A,Lvl,MaxLvl) :- Lvl >= MaxLvl,!, indent(Lvl), print(A),nl. |
235 | | trace_print(A,Lvl,_MaxLvl) :- treat_as_atomic(A),!, indent(Lvl), print(A),nl. |
236 | | trace_print([H|T],Lvl,MaxLvl) :- !, indent(Lvl), print('['),nl, |
237 | | l_trace_print([H|T],Lvl,MaxLvl), |
238 | | indent(Lvl), print(']'),nl. |
239 | | %trace_print(A,Lvl,_MaxLvl) :- functor(A,_,1), arg(1,A,AN), atomic(AN),!, indent(Lvl), print(A),nl. |
240 | | trace_print(A,Lvl,_MaxLvl) :- A=..[_|Args], maplist(atomic,Args),!, |
241 | | indent(Lvl), print(A),nl. |
242 | | trace_print(A,Lvl,MaxLvl) :- functor(A,FA,FAN), |
243 | | indent(Lvl),print(FA/FAN),print('('),nl, |
244 | | A=..[_|As], l_trace_print(As,Lvl,MaxLvl). |
245 | | |
246 | | :- use_module(tools_positions, [is_position/1]). |
247 | | treat_as_atomic(A) :- var(A). |
248 | | treat_as_atomic(A) :- atomic(A). |
249 | | treat_as_atomic(nodeid(Pos)) :- is_position(Pos). |
250 | | treat_as_atomic(sharing(_,_,_,_)). |
251 | | treat_as_atomic(ID/V) :- treat_as_atomic(ID),treat_as_atomic(V). |
252 | | treat_as_atomic([H|T]) :- T==[], treat_as_atomic(H). |
253 | | |
254 | | l_trace_print([],L,_MaxLvl) :- indent(L), print(')'),nl. |
255 | | l_trace_print([A|TA],Lvl,MaxLvl) :- L1 is Lvl+1, trace_print(A,L1,MaxLvl), |
256 | | l_trace_print(TA,Lvl,MaxLvl). |
257 | | |
258 | | % ----------------------------------- |
259 | | |
260 | | % print on error stream |
261 | | print_error(Error) :- |
262 | | stream_is_interactive(user_error),!, |
263 | | start_terminal_colour([red,bold],user_error), |
264 | | call_cleanup(print_no_col(user_error,Error),reset_terminal_colour_and_nl(user_error)). |
265 | | %% flush_output(user_error), %%. |
266 | | print_error(Error) :- print_no_col(user_error,Error), nl(user_error). |
267 | | |
268 | | print_no_col(Stream,ErrorTerm) :- |
269 | | write(Stream,'! '), |
270 | | (var(ErrorTerm) -> write(Stream,'_') |
271 | | ; write_term(Stream,ErrorTerm,[max_depth(20),numbervars(true)])). |
272 | | |
273 | | reset_terminal_colour_and_nl(Stream) :- |
274 | | reset_terminal_colour(Stream), |
275 | | nl(Stream). % for SICS prompt it is important to have nl after code to reset colour |
276 | | |
277 | | print_message_on_stream(Stream,Color,Message) :- |
278 | | stream_is_interactive(Stream),!, |
279 | | start_terminal_colour(Color,Stream), |
280 | | call_cleanup(print_no_col(Stream,Message),reset_terminal_colour_and_nl(Stream)). |
281 | | print_message_on_stream(Stream,_Color,Message) :- |
282 | | print_no_col(Stream,Message), |
283 | | nl(Stream). |
284 | | |
285 | | format_error_with_nl(Str,Args) :- format_with_colour_nl(user_error,[red,bold],Str,Args). |
286 | | format_error(Str,Args) :- format_with_colour(user_error,[red,bold],Str,Args). |
287 | | |
288 | | format_with_colour_nl(Stream,Colour,Str,Args) :- |
289 | | format_with_colour(Stream,Colour,Str,Args), |
290 | | nl(Stream). % followed by a newline *after* resetting the colours; important for SICStus prompt |
291 | | |
292 | | format_with_colour(Stream,Colour,Str,Args) :- |
293 | | stream_is_interactive(Stream),!, |
294 | | start_terminal_colour(Colour,Stream), |
295 | | call_cleanup(format(Stream,Str,Args), |
296 | | reset_terminal_colour(Stream)). |
297 | | format_with_colour(Stream,_Colour,Str,Args) :- format(Stream,Str,Args). |
298 | | |
299 | | % we could provide a preference to override this; in case we do want to see the colour escape codes in a file |
300 | | stream_is_interactive(S) :- |
301 | | intelligent_get_stream(S,RealStream), stream_property(RealStream,interactive). |
302 | | |
303 | | intelligent_get_stream(user_output,S) :- !, current_output(S). |
304 | | intelligent_get_stream(user_intput,S) :- !, current_input(S). |
305 | | intelligent_get_stream(user_error,S) :- !, prolog_flag(user_error,S). |
306 | | intelligent_get_stream(S,S). |
307 | | |
308 | | :- load_files(library(system), [when(compile_time), imports([environ/2])]). |
309 | | :- if(environ(no_terminal_colors,true)). |
310 | | no_color. |
311 | | set_no_color(_). |
312 | | reset_no_color_to_default. |
313 | | print_red(X) :- write(X). |
314 | | print_red(Stream,T) :- write(Stream,T). |
315 | | print_green(X) :- write(X). |
316 | | reset_terminal_colour(_). |
317 | | start_terminal_colour(_,_). |
318 | | :- else. |
319 | | :- use_module(library(system),[environ/2]). |
320 | | :- dynamic colours_disabled/0. |
321 | | no_color :- colours_disabled. |
322 | | set_no_color(false) :- retractall(colours_disabled). |
323 | | set_no_color(true) :- % useful e.g. for --no-color cli flag |
324 | | (colours_disabled -> true ; assertz(colours_disabled)). |
325 | | reset_no_color_to_default :- |
326 | | (no_col_env -> set_no_color(true) ; retractall(colours_disabled)). |
327 | | %TODO: we could try and detect Windows 8 or earlier where no terminal colours are supported |
328 | | no_col_env :- environ('NO_COLOR',_),!. % see http://no-color.org |
329 | | no_col_env :- environ('NOCOLOR',_),!. |
330 | | no_col_env :- environ('CLICOLOR',V), (V=0 ; V='NO' ; V='FALSE'),!. |
331 | | no_col_env :- environ('TERM',dumb). |
332 | | % | ?- environ('TERM',X). |
333 | | % X = 'xterm-256color' |
334 | | |
335 | | print_red(Stream,Term) :- no_color,!, |
336 | | format(Stream,'~w',[Term]). |
337 | | print_red(Stream,Term) :- |
338 | | format(Stream,'\e[31m~w\e[0m',[Term]). |
339 | | |
340 | | print_red(Term) :- no_color,!, |
341 | | format('~w',[Term]). |
342 | | print_red(Term) :- |
343 | | format('\e[31m~w\e[0m',[Term]). |
344 | | |
345 | | print_green(Term) :- no_color,!, |
346 | | format('~w',[Term]). |
347 | | print_green(Term) :- |
348 | | format('\e[32m~w\e[0m',[Term]). |
349 | | |
350 | | reset_terminal_colour(_) :- no_color,!. |
351 | | reset_terminal_colour(Stream) :- write(Stream,'\e[0m'). |
352 | | |
353 | | % see https://misc.flogisoft.com/bash/tip_colors_and_formatting |
354 | | start_terminal_colour(_,_) :- no_color,!. |
355 | | start_terminal_colour(black,Stream) :- !, write(Stream,'\e[30m'). |
356 | | start_terminal_colour(red,Stream) :- !, write(Stream,'\e[31m'). |
357 | | start_terminal_colour(green,Stream) :- !, write(Stream,'\e[32m'). |
358 | | start_terminal_colour(yellow,Stream) :- !, write(Stream,'\e[33m'). |
359 | | start_terminal_colour(blue,Stream) :- !, write(Stream,'\e[34m'). |
360 | | start_terminal_colour(magenta,Stream) :- !, write(Stream,'\e[35m'). |
361 | | start_terminal_colour(cyan,Stream) :- !, write(Stream,'\e[36m'). |
362 | | start_terminal_colour(light_gray,Stream) :- !, write(Stream,'\e[37m'). |
363 | | start_terminal_colour(dark_gray,Stream) :- !, write(Stream,'\e[90m'). |
364 | | start_terminal_colour(light_red,Stream) :- !, write(Stream,'\e[91m'). |
365 | | start_terminal_colour(light_green,Stream) :- !, write(Stream,'\e[92m'). |
366 | | start_terminal_colour(white,Stream) :- !, write(Stream,'\e[97m'). |
367 | | start_terminal_colour(bold,Stream) :- !, write(Stream,'\e[1m'). |
368 | | start_terminal_colour(underline,Stream) :- !, write(Stream,'\e[4m'). |
369 | | start_terminal_colour(dim,Stream) :- !, write(Stream,'\e[2m'). |
370 | | start_terminal_colour(black_background,Stream) :- !, write(Stream,'\e[49m'). |
371 | | start_terminal_colour(red_background,Stream) :- !, write(Stream,'\e[41m'). |
372 | | start_terminal_colour(green_background,Stream) :- !, write(Stream,'\e[42m'). |
373 | | start_terminal_colour(yellow_background,Stream) :- !, write(Stream,'\e[43m'). |
374 | | start_terminal_colour(white_background,Stream) :- !, write(Stream,'\e[107m'). |
375 | | start_terminal_colour(blink,Stream) :- !, write(Stream,'\e[5m'). |
376 | | start_terminal_colour(reverse,Stream) :- !, write(Stream,'\e[7m'). % reversed |
377 | | start_terminal_colour(hidden,Stream) :- !, write(Stream,'\e[8m'). |
378 | | start_terminal_colour(reset,Stream) :- !, write(Stream,'\e[0m'). |
379 | | % cursor nagivation: |
380 | | start_terminal_colour(go_left,Stream) :- !, write(Stream,'\e[1000Dm'). % go to left of terminal |
381 | | start_terminal_colour(go_up(Nr),Stream) :- number(Nr),!, format(Stream,'\e[~wA',[Nr]). |
382 | | start_terminal_colour(go_down(Nr),Stream) :- number(Nr),!, format(Stream,'\e[~wB',[Nr]). |
383 | | start_terminal_colour(go_right(Nr),Stream) :- number(Nr),!, format(Stream,'\e[~wC',[Nr]). |
384 | | start_terminal_colour(go_left(Nr),Stream) :- number(Nr),!, format(Stream,'\e[~wD',[Nr]). |
385 | | start_terminal_colour(clear_screen,Stream) :- write(Stream,'\e[2J'). |
386 | | start_terminal_colour(clear_screen_to_start,Stream) :- write(Stream,'\e[1J'). |
387 | | start_terminal_colour(clear_screen_to_end,Stream) :- write(Stream,'\e[0J'). |
388 | | start_terminal_colour(clear_line,Stream) :- write(Stream,'\e[2K'). |
389 | | start_terminal_colour(clear_line_to_start,Stream) :- write(Stream,'\e[1K'). |
390 | | start_terminal_colour(clear_line_to_end,Stream) :- write(Stream,'\e[0K'). |
391 | | start_terminal_colour(set_column(Nr),Stream) :- number(Nr),!, format(Stream,'\e[~wG',[Nr]). |
392 | | start_terminal_colour(set_position(Row,Col),Stream) :- number(Row), number(Col),!, |
393 | | format(Stream,'\e[~w;~wHm',[Row,Col]). |
394 | | start_terminal_colour(next_line(Nr),Stream) :- number(Nr),!, format(Stream,'\e[~wE',[Nr]). |
395 | | start_terminal_colour(prev_line(Nr),Stream) :- number(Nr),!, format(Stream,'\e[~wF',[Nr]). |
396 | | start_terminal_colour(save_position,Stream) :- !, write(Stream,'\e[s'). |
397 | | start_terminal_colour(restore_position,Stream) :- !, write(Stream,'\e[u'). |
398 | | % more colors, not supported by all terminals: |
399 | | start_terminal_colour(bright_red,Stream) :- !, write(Stream,'\e[31;1m'). % also 91m ? |
400 | | start_terminal_colour(bright_green,Stream) :- !, write(Stream,'\e[32;1m'). |
401 | | start_terminal_colour(orange,Stream) :- !, write(Stream,'\e[38;5;202m'). |
402 | | start_terminal_colour(grey,Stream) :- !, write(Stream,'\e[38;5;241m'). |
403 | | start_terminal_colour(dark_red,Stream) :- !, write(Stream,'\e[38;5;52m'). |
404 | | start_terminal_colour(col256(Nr),Stream) :- number(Nr), Nr>=0, Nr=<255,!, format(Stream,'\e[38;5;~wm',[Nr]). |
405 | | start_terminal_colour([],_Stream) :- !. |
406 | | start_terminal_colour([H|T],Stream) :- !, start_terminal_colour(H,Stream),start_terminal_colour(T,Stream). |
407 | | start_terminal_colour(C,_Stream) :- format(user_error,'*** UNKNOWN COLOUR: ~w~n',[C]). |
408 | | :- endif. |
409 | | |
410 | | get_terminal_colour_code(black,'\e[30m'). |
411 | | get_terminal_colour_code(red,'\e[31m'). |
412 | | get_terminal_colour_code(green,'\e[32m'). |
413 | | get_terminal_colour_code(yellow,'\e[33m'). |
414 | | get_terminal_colour_code(blue,'\e[34m'). |
415 | | get_terminal_colour_code(magenta,'\e[35m'). |
416 | | get_terminal_colour_code(cyan,'\e[36m'). |
417 | | get_terminal_colour_code(light_gray,'\e[37m'). |
418 | | get_terminal_colour_code(reset,'\e[0m'). |
419 | | get_terminal_colour_code(light_red,'\e[91m'). |
420 | | get_terminal_colour_code(light_green,'\e[92m'). |
421 | | get_terminal_colour_code(light_yellow,'\e[93m'). |
422 | | get_terminal_colour_code(light_blue,'\e[94m'). |
423 | | get_terminal_colour_code(light_magenta,'\e[95m'). |
424 | | get_terminal_colour_code(light_cyan,'\e[96m'). |
425 | | get_terminal_colour_code(white,'\e[97m'). |
426 | | % TODO: extend and use above |
427 | | |
428 | | % To print out colors: between:between(0,255,Nr),format(user_output,'\e[38;5;~wm Number=~w~n',[Nr,Nr]),fail. |
429 | | % See: https://www.lihaoyi.com/post/BuildyourownCommandLinewithANSIescapecodes.html |
430 | | |
431 | | % ----------------------------------- |
432 | | |
433 | | :- use_module(library(system),[datime/1]). |
434 | | |
435 | | print_time_stamp(Stream) :- |
436 | | datime(datime(Year,Month,Day,Hour,Min,Sec)), |
437 | | (Min<10 |
438 | | -> format(Stream,'~w/~w/~w - ~wh0~w ~ws',[Day,Month,Year,Hour,Min,Sec]) |
439 | | ; format(Stream,'~w/~w/~w - ~wh~w ~ws',[Day,Month,Year,Hour,Min,Sec]) |
440 | | ). |
441 | | |
442 | | % ----------------------------------- |
443 | | print_dynamic_pred(InModule,Pred,N) :- print_dynamic_pred(user_output,InModule,Pred,N). |
444 | | |
445 | | print_dynamic_pred(Stream,InModule,Pred,N) :- nl(Stream), |
446 | | format(Stream,':- dynamic ~w/~w.~n',[Pred,N]), |
447 | | functor(Call,Pred,N), |
448 | ? | call(InModule:Call), |
449 | | write_term(Stream,Call,[quoted(true)]),write(Stream,'.'),nl(Stream),fail. |
450 | | print_dynamic_pred(Stream,InModule,Pred,N) :- |
451 | | functor(Call,Pred,N), |
452 | ? | (call(InModule:Call) -> true |
453 | | ; write_with_numbervars(Stream,Call), write(Stream,' :- fail.'),nl(Stream)), |
454 | | nl(Stream). |
455 | | |
456 | | write_with_numbervars(Stream,Term) :- copy_term(Term,T), numbervars(T,0,_), |
457 | | write_term(Stream,T,[quoted(true),numbervars(true)]). |
458 | | |
459 | | print_dynamic_fact(Stream,Fact) :- |
460 | | functor(Fact,Pred,N), |
461 | | format(Stream,':- dynamic ~w/~w.~n',[Pred,N]), |
462 | | write_term(Stream,Fact,[quoted(true)]),write(Stream,'.'),nl(Stream). |
463 | | |
464 | | % ----------------------------------- |
465 | | |
466 | | % typically used for printing call residues: |
467 | | print_goal(V) :- var(V),!, format(' ~p~n',[V]). |
468 | | print_goal([A|B]) :- !,print_goal(A), print_goal(B). |
469 | | print_goal((A,B)) :- !,print_goal(A), print_goal(B). |
470 | | print_goal(Module:(A,B)) :- !, format(' ~p:~n',[Module]), print_goal((A,B)). |
471 | | print_goal(when(C,G)) :- !, write(' when('), |
472 | | write_term(C,[max_depth(6)]), write(','), |
473 | | write_term(G,[max_depth(5)]), write(')'),nl. |
474 | | print_goal(A) :- write(' '), write_term(A,[max_depth(5)]), nl. % avoid printing huge terms |
475 | | %print_goal(A) :- format(' ~p~n',[A]). |
476 | | |
477 | | |
478 | | % ----------------------------------- |
479 | | |
480 | | % possible applicaton: inspect size of terms transmitted to ProB2: |
481 | | % prob2_interface:get_machine_formulas(Formulas), tell('formulasnest.pl'), nested_print_term(Formulas,6),told. |
482 | | |
483 | | nested_print_term(Term) :- nested_print_term(Term,10). |
484 | | nested_print_term(Term,MaxNest) :- nested_print_term(0,MaxNest,Term). |
485 | | |
486 | | indentws(0) :- !. |
487 | | indentws(X) :- X>0, write(' '), X1 is X-1, indentws(X1). |
488 | | |
489 | | :- use_module(library(terms),[term_size/2]). |
490 | | nested_print_term(CurNesting,_Max,T) :- var(T),!, indent(CurNesting),write(T),nl. |
491 | | nested_print_term(CurNesting,_,T) :- atom(T), !, atom_length(T,Len), |
492 | | indent(CurNesting), |
493 | | (Len > 100 |
494 | | -> atom_codes(T,Codes), length(Prefix,50), append(Prefix,_,Codes), |
495 | | format('atom: len(~w): ~s...~n',[Len,Prefix]) |
496 | | ; format('~w~n',[T])). |
497 | | nested_print_term(CurNesting,_,T) :- number(T),!, indent(CurNesting), format('~w~n',[T]). |
498 | | nested_print_term(CurNesting,MaxNesting,T) :- CurNesting >= MaxNesting,!, |
499 | | term_size(T,Sz), functor(T,F,N), |
500 | | indentws(CurNesting), |
501 | | (Sz>25000 -> Msg='****' ; Msg=''), format('~w/~w :: sz(~w)~w~n',[F,N,Sz,Msg]). |
502 | | nested_print_term(CurNesting,MaxNesting,T) :- |
503 | | list_skeleton_size(T,Len,closed), term_size(T,Sz),!, |
504 | | indentws(CurNesting),format('[ list_len_sz(~w,~w)~n',[Len,Sz]), |
505 | | C1 is CurNesting+1, |
506 | | maplist(nested_print_term(C1,MaxNesting),T), |
507 | | indentws(CurNesting),format('] list_len(~w)~n',[Len]). |
508 | | nested_print_term(CurNesting,MaxNesting,T) :- |
509 | | term_size(T,Sz), functor(T,F,N), |
510 | | indentws(CurNesting),format('~w/~w( sz(~w)~n',[F,N,Sz]), |
511 | | T =.. [_|Args], C1 is CurNesting+1, |
512 | | maplist(nested_print_term(C1,MaxNesting),Args), |
513 | | indentws(CurNesting),format('~w/~w)~n',[F,N]). |
514 | | |
515 | | |
516 | | % a version of write_term_to_codes that nests the Prolog term |
517 | | nested_write_term_to_codes(Term,Codes) :- |
518 | | nested_write(Term,0,Codes,[]). |
519 | | |
520 | | :- use_module(library(codesio)). |
521 | | % Note: write_term_to_codes(+Term, -Codes, +Options) with option indented(true) only indents clauses |
522 | | |
523 | | nested_write(Atom,Level) --> {simple(Atom)},!, indent(Level), format_to_codes('~q',[Atom]). |
524 | | nested_write(Term,Level) --> {Level>40},!, indent(Level), format_to_codes('~q',[Term]). |
525 | | nested_write([H|T],Level) --> !, |
526 | | indent(Level), "[\n", |
527 | | {L1 is Level+1}, |
528 | | l_nested_write([H|T],L1), |
529 | | indent(Level), "]". |
530 | | nested_write(Compound,Level) --> {decompose_compound(Compound,F,Args)}, |
531 | | indent(Level), |
532 | | ({maplist(simple,Args)} |
533 | | -> format_to_codes('~q',[Compound]) |
534 | | ; write_to_codes(F), "(\n", |
535 | | {L1 is Level+1}, |
536 | | l_nested_write(Args,L1), |
537 | | indent(Level), ")" |
538 | | ). |
539 | | |
540 | | decompose_compound(Module:Compound,Functor,Args) :- nonvar(Compound), !, |
541 | | Compound =.. [F|Args], Functor = Module:F. |
542 | | decompose_compound(Compound,F,Args) :- Compound =.. [F|Args]. |
543 | | |
544 | | indent(0) --> !, "". |
545 | | indent(L) --> {L>0, L1 is L-1}, " ", indent(L1). |
546 | | |
547 | | l_nested_write([],_) --> "". |
548 | | l_nested_write([H],Level) --> !, |
549 | | nested_write(H,Level), "\n". |
550 | | l_nested_write([H|T],Level) --> |
551 | | nested_write(H,Level), ",\n", |
552 | | l_nested_write(T,Level). |
553 | | |
554 | | % use_module(probsrc(tools_printing)), nested_write_term_to_codes(f(a,[0,s(X)]),C), format('~s~n',[C]). |
555 | | |
556 | | tcltk_nested_read_prolog_file_as_codes(File,list(Codes)) :- |
557 | | open(File, read, Stream, [encoding(utf8)]), |
558 | | call_cleanup(nested_read_terms(Stream, Codes, []), close(Stream)). |
559 | | |
560 | | nested_read_terms(Stream) --> {safe_read_stream(Stream,Term)}, |
561 | | ({Term=end_of_file} -> "\n" |
562 | | ; nested_write(Term,0), ".\n", |
563 | | nested_read_terms(Stream) |
564 | | ). |
565 | | |
566 | | safe_read_stream(Stream,T) :- |
567 | | catch(read(Stream,T), E, ( |
568 | | error_manager:add_error(nested_read_prolog_file_as_codes,'Exception reading term from file:',E), |
569 | | T=end_of_file)). |
570 | | |