36
37:- module(ansi_term,
38 [ ansi_format/3, 39 ansi_get_color/2, 40 ansi_hyperlink/2, 41 ansi_hyperlink/3 42 ]). 43:- autoload(library(error), [domain_error/2, must_be/2, instantiation_error/1]). 44:- autoload(library(lists), [append/3]). 45:- autoload(library(uri), [uri_file_name/2]). 46:- if(exists_source(library(time))). 47:- autoload(library(time), [call_with_time_limit/2]). 48:- endif. 49
50
73
74:- multifile
75 prolog:console_color/2, 76 supports_get_color/0,
77 hyperlink/2. 78
79
80color_term_flag_default(true) :-
81 stream_property(user_input, tty(true)),
82 stream_property(user_error, tty(true)),
83 stream_property(user_output, tty(true)),
84 \+ getenv('TERM', dumb),
85 !.
86color_term_flag_default(false).
87
88init_color_term_flag :-
89 color_term_flag_default(Default),
90 create_prolog_flag(color_term, Default,
91 [ type(boolean),
92 keep(true)
93 ]),
94 create_prolog_flag(hyperlink_term, false,
95 [ type(boolean),
96 keep(true)
97 ]).
98
99:- init_color_term_flag. 100
101
102:- meta_predicate
103 keep_line_pos(+, 0). 104
105:- multifile
106 user:message_property/2. 107
147
148ansi_format(Attr, Format, Args) :-
149 ansi_format(current_output, Attr, Format, Args).
150
151ansi_format(Stream, Class, Format, Args) :-
152 stream_property(Stream, tty(true)),
153 current_prolog_flag(color_term, true),
154 !,
155 class_attrs(Class, Attr),
156 phrase(sgr_codes_ex(Attr), Codes),
157 atomic_list_concat(Codes, ;, Code),
158 with_output_to(
159 Stream,
160 ( keep_line_pos(current_output, format('\e[~wm', [Code])),
161 format(Format, Args),
162 keep_line_pos(current_output, format('\e[0m'))
163 )
164 ),
165 flush_output.
166ansi_format(Stream, _Attr, Format, Args) :-
167 format(Stream, Format, Args).
168
169sgr_codes_ex(X) -->
170 { var(X),
171 !,
172 instantiation_error(X)
173 }.
174sgr_codes_ex([]) -->
175 !.
176sgr_codes_ex([H|T]) -->
177 !,
178 sgr_codes_ex(H),
179 sgr_codes_ex(T).
180sgr_codes_ex(Attr) -->
181 ( { sgr_code(Attr, Code) }
182 -> ( { is_list(Code) }
183 -> list(Code)
184 ; [Code]
185 )
186 ; { domain_error(sgr_code, Attr) }
187 ).
188
189list([]) --> [].
190list([H|T]) --> [H], list(T).
191
192
231
232sgr_code(reset, 0).
233sgr_code(bold, 1).
234sgr_code(faint, 2).
235sgr_code(italic, 3).
236sgr_code(underline, 4).
237sgr_code(blink(slow), 5).
238sgr_code(blink(rapid), 6).
239sgr_code(negative, 7).
240sgr_code(conceal, 8).
241sgr_code(crossed_out, 9).
242sgr_code(font(primary), 10) :- !.
243sgr_code(font(N), C) :-
244 C is 10+N.
245sgr_code(fraktur, 20).
246sgr_code(underline(double), 21).
247sgr_code(intensity(normal), 22).
248sgr_code(fg(Name), C) :-
249 ( ansi_color(Name, N)
250 -> C is N+30
251 ; rgb(Name, R, G, B)
252 -> sgr_code(fg(R,G,B), C)
253 ).
254sgr_code(bg(Name), C) :-
255 !,
256 ( ansi_color(Name, N)
257 -> C is N+40
258 ; rgb(Name, R, G, B)
259 -> sgr_code(bg(R,G,B), C)
260 ).
261sgr_code(framed, 51).
262sgr_code(encircled, 52).
263sgr_code(overlined, 53).
264sgr_code(ideogram(underline), 60).
265sgr_code(right_side_line, 60).
266sgr_code(ideogram(underline(double)), 61).
267sgr_code(right_side_line(double), 61).
268sgr_code(ideogram(overlined), 62).
269sgr_code(left_side_line, 62).
270sgr_code(ideogram(stress_marking), 64).
271sgr_code(-X, Code) :-
272 off_code(X, Code).
273sgr_code(hfg(Name), C) :-
274 ansi_color(Name, N),
275 C is N+90.
276sgr_code(hbg(Name), C) :-
277 !,
278 ansi_color(Name, N),
279 C is N+100.
280sgr_code(fg8(Name), [38,5,N]) :-
281 ansi_color8(Name, N).
282sgr_code(bg8(Name), [48,5,N]) :-
283 ansi_color8(Name, N).
284sgr_code(fg(R,G,B), [38,2,R,G,B]) :-
285 between(0, 255, R),
286 between(0, 255, G),
287 between(0, 255, B).
288sgr_code(bg(R,G,B), [48,2,R,G,B]) :-
289 between(0, 255, R),
290 between(0, 255, G),
291 between(0, 255, B).
292
293off_code(italic_and_franktur, 23).
294off_code(underline, 24).
295off_code(blink, 25).
296off_code(negative, 27).
297off_code(conceal, 28).
298off_code(crossed_out, 29).
299off_code(framed, 54).
300off_code(overlined, 55).
301
302ansi_color8(h(Name), N) :-
303 !,
304 ansi_color(Name, N0),
305 N is N0+8.
306ansi_color8(Name, N) :-
307 atom(Name),
308 !,
309 ansi_color(Name, N).
310ansi_color8(N, N) :-
311 between(0, 255, N).
312
313ansi_color(black, 0).
314ansi_color(red, 1).
315ansi_color(green, 2).
316ansi_color(yellow, 3).
317ansi_color(blue, 4).
318ansi_color(magenta, 5).
319ansi_color(cyan, 6).
320ansi_color(white, 7).
321ansi_color(default, 9).
322
323rgb(Name, R, G, B) :-
324 atom_codes(Name, [0'#,R1,R2,G1,G2,B1,B2]),
325 hex_color(R1,R2,R),
326 hex_color(G1,G2,G),
327 hex_color(B1,B2,B).
328rgb(Name, R, G, B) :-
329 atom_codes(Name, [0'#,R1,G1,B1]),
330 hex_color(R1,R),
331 hex_color(G1,G),
332 hex_color(B1,B).
333
334hex_color(D1,D2,V) :-
335 code_type(D1, xdigit(V1)),
336 code_type(D2, xdigit(V2)),
337 V is 16*V1+V2.
338
339hex_color(D1,V) :-
340 code_type(D1, xdigit(V1)),
341 V is 16*V1+V1.
342
352
353
354 357
362
363prolog:message_line_element(S, ansi(Class, Fmt, Args)) :-
364 class_attrs(Class, Attr),
365 ansi_format(S, Attr, Fmt, Args).
366prolog:message_line_element(S, ansi(Class, Fmt, Args, Ctx)) :-
367 class_attrs(Class, Attr),
368 ansi_format(S, Attr, Fmt, Args),
369 ( nonvar(Ctx),
370 Ctx = ansi(_, RI-RA)
371 -> keep_line_pos(S, format(S, RI, RA))
372 ; true
373 ).
374prolog:message_line_element(S, url(Location)) :-
375 ansi_hyperlink(S, Location).
376prolog:message_line_element(S, url(URL, Label)) :-
377 ansi_hyperlink(S, URL, Label).
378prolog:message_line_element(S, begin(Level, Ctx)) :-
379 level_attrs(Level, Attr),
380 stream_property(S, tty(true)),
381 current_prolog_flag(color_term, true),
382 !,
383 ( is_list(Attr)
384 -> sgr_codes(Attr, Codes),
385 atomic_list_concat(Codes, ;, Code)
386 ; sgr_code(Attr, Code)
387 ),
388 keep_line_pos(S, format(S, '\e[~wm', [Code])),
389 Ctx = ansi('\e[0m', '\e[0m\e[~wm'-[Code]).
390prolog:message_line_element(S, end(Ctx)) :-
391 nonvar(Ctx),
392 Ctx = ansi(Reset, _),
393 keep_line_pos(S, write(S, Reset)).
394
395sgr_codes([], []).
396sgr_codes([H0|T0], [H|T]) :-
397 sgr_code(H0, H),
398 sgr_codes(T0, T).
399
400level_attrs(Level, Attrs) :-
401 user:message_property(Level, color(Attrs)),
402 !.
403level_attrs(Level, Attrs) :-
404 class_attrs(message(Level), Attrs).
405
406class_attrs(Class, Attrs) :-
407 user:message_property(Class, color(Attrs)),
408 !.
409class_attrs(Class, Attrs) :-
410 prolog:console_color(Class, Attrs),
411 !.
412class_attrs(Class, Attrs) :-
413 '$messages':default_theme(Class, Attrs),
414 !.
415class_attrs(Attrs, Attrs).
416
428
429ansi_hyperlink(Stream, Location) :-
430 hyperlink(Stream, url(Location)),
431 !.
432ansi_hyperlink(Stream, File:Line:Column) :-
433 !,
434 ( url_file_name(URI, File)
435 -> format(Stream, '\e]8;;~w#~d:~d\e\\~w:~d:~d\e]8;;\e\\',
436 [ URI, Line, Column, File, Line, Column ])
437 ; format(Stream, '~w:~w:~w', [File, Line, Column])
438 ).
439ansi_hyperlink(Stream, File:Line) :-
440 !,
441 ( url_file_name(URI, File)
442 -> format(Stream, '\e]8;;~w#~w\e\\~w:~d\e]8;;\e\\',
443 [ URI, Line, File, Line ])
444 ; format(Stream, '~w:~w', [File, Line])
445 ).
446ansi_hyperlink(Stream, File) :-
447 ( url_file_name(URI, File)
448 -> format(Stream, '\e]8;;~w\e\\~w\e]8;;\e\\',
449 [ URI, File ])
450 ; format(Stream, '~w', [File])
451 ).
452
453ansi_hyperlink(Stream, URL, Label) :-
454 hyperlink(Stream, url(URL, Label)),
455 !.
456ansi_hyperlink(Stream, URL, Label) :-
457 ( current_prolog_flag(hyperlink_term, true)
458 -> format(Stream, '\e]8;;~w\e\\~w\e]8;;\e\\',
459 [ URL, Label ])
460 ; format(Stream, '~w', [Label])
461 ).
462
471
472:- dynamic has_lib_uri/1 as volatile. 473
474url_file_name(URL, File) :-
475 current_prolog_flag(hyperlink_term, true),
476 ( has_lib_uri(true)
477 -> uri_file_name(URL, File)
478 ; exists_source(library(uri))
479 -> use_module(library(uri), [uri_file_name/2]),
480 uri_file_name(URL, File),
481 asserta(has_lib_uri(true))
482 ; asserta(has_lib_uri(false)),
483 fail
484 ).
485
491
492keep_line_pos(S, G) :-
493 stream_property(S, position(Pos)),
494 !,
495 setup_call_cleanup(
496 stream_position_data(line_position, Pos, LPos),
497 G,
498 set_stream(S, line_position(LPos))).
499keep_line_pos(_, G) :-
500 call(G).
501
512
513
514:- if(current_predicate(call_with_time_limit/2)). 515ansi_get_color(Which0, RGB) :-
516 stream_property(user_input, tty(true)),
517 stream_property(user_output, tty(true)),
518 stream_property(user_error, tty(true)),
519 supports_get_color,
520 ( color_alias(Which0, Which)
521 -> true
522 ; must_be(between(0,15),Which0)
523 -> Which = Which0
524 ),
525 catch(keep_line_pos(user_output,
526 ansi_get_color_(Which, RGB)),
527 time_limit_exceeded,
528 no_xterm).
529
530supports_get_color :-
531 getenv('TERM', Term),
532 sub_atom(Term, 0, _, _, xterm),
533 \+ getenv('TERM_PROGRAM', 'Apple_Terminal').
534
535color_alias(foreground, 10).
536color_alias(background, 11).
537
538ansi_get_color_(Which, rgb(R,G,B)) :-
539 format(codes(Id), '~w', [Which]),
540 hex4(RH),
541 hex4(GH),
542 hex4(BH),
543 phrase(("\e]", Id, ";rgb:", RH, "/", GH, "/", BH, "\a"), Pattern),
544 call_with_time_limit(0.05,
545 with_tty_raw(exchange_pattern(Which, Pattern))),
546 !,
547 hex_val(RH, R),
548 hex_val(GH, G),
549 hex_val(BH, B).
550
551no_xterm :-
552 print_message(warning, ansi(no_xterm_get_colour)),
553 fail.
554
555hex4([_,_,_,_]).
556
557hex_val([D1,D2,D3,D4], V) :-
558 code_type(D1, xdigit(V1)),
559 code_type(D2, xdigit(V2)),
560 code_type(D3, xdigit(V3)),
561 code_type(D4, xdigit(V4)),
562 V is (V1<<12)+(V2<<8)+(V3<<4)+V4.
563
564exchange_pattern(Which, Pattern) :-
565 format(user_output, '\e]~w;?\a', [Which]),
566 flush_output(user_output),
567 read_pattern(user_input, Pattern, []).
568
569read_pattern(From, Pattern, NotMatched0) :-
570 copy_term(Pattern, TryPattern),
571 append(Skip, Rest, NotMatched0),
572 append(Rest, RestPattern, TryPattern),
573 !,
574 echo(Skip),
575 try_read_pattern(From, RestPattern, NotMatched, Done),
576 ( Done == true
577 -> Pattern = TryPattern
578 ; read_pattern(From, Pattern, NotMatched)
579 ).
580
582
583try_read_pattern(_, [], [], true) :-
584 !.
585try_read_pattern(From, [H|T], [C|RT], Done) :-
586 get_code(C),
587 ( C = H
588 -> try_read_pattern(From, T, RT, Done)
589 ; RT = [],
590 Done = false
591 ).
592
593echo([]).
594echo([H|T]) :-
595 put_code(user_output, H),
596 echo(T).
597
598:- else. 599ansi_get_color(_Which0, _RGB) :-
600 fail.
601:- endif. 602
603
604
605:- multifile prolog:message//1. 606
607prolog:message(ansi(no_xterm_get_colour)) -->
608 [ 'Terminal claims to be xterm compatible,'-[], nl,
609 'but does not report colour info'-[]
610 ]