37
38:- module(prolog_pretty_print,
39 [ print_term/2 40 ]). 41:- autoload(library(option),
42 [merge_options/3, select_option/3, select_option/4,
43 option/2, option/3]).
62:- predicate_options(print_term/2, 2,
63 [ output(stream),
64 right_margin(integer),
65 left_margin(integer),
66 tab_width(integer),
67 indent_arguments(integer),
68 auto_indent_arguments(integer),
69 operators(boolean),
70 write_options(list),
71 fullstop(boolean),
72 nl(boolean)
73 ]).
129print_term(Term, Options) :-
130 defaults(Defs0),
131 select_option(write_options(WrtDefs), Defs0, Defs),
132 select_option(write_options(WrtUser), Options, Options1, []),
133 merge_options(WrtUser, WrtDefs, WrtOpts),
134 merge_options(Options1, Defs, Options2),
135 Options3 = [write_options(WrtOpts)|Options2],
136 default_margin(Options3, Options4),
137 \+ \+ print_term_2(Term, Options4).
138
139print_term_2(Term, Options) :-
140 prepare_term(Term, Template, Cycles, Constraints),
141 option(write_options(WrtOpts), Options),
142 option(max_depth(MaxDepth), WrtOpts, infinite),
143
144 dict_create(Context, #, [max_depth(MaxDepth)|Options]),
145 pp(Template, Context, Options),
146 print_extra(Cycles, Context, 'where', Options),
147 print_extra(Constraints, Context, 'with constraints', Options),
148 ( option(fullstop(true), Options)
149 -> option(output(Out), Options),
150 put_char(Out, '.')
151 ; true
152 ),
153 ( option(nl(true), Options)
154 -> option(output(Out2), Options),
155 nl(Out2)
156 ; true
157 ).
158
([], _, _, _) :- !.
160print_extra(List, Context, Comment, Options) :-
161 option(output(Out), Options),
162 format(Out, ', % ~w', [Comment]),
163 context(Context, indent, Indent),
164 NewIndent is Indent+4,
165 modify_context(Context, [indent=NewIndent], Context1),
166 print_extra_2(List, Context1, Options).
167
([H|T], Context, Options) :-
169 option(output(Out), Options),
170 context(Context, indent, Indent),
171 indent(Out, Indent, Options),
172 pp(H, Context, Options),
173 ( T == []
174 -> true
175 ; format(Out, ',', []),
176 print_extra_2(T, Context, Options)
177 ).
185prepare_term(Term, Template, Cycles, Constraints) :-
186 term_attvars(Term, []),
187 !,
188 Constraints = [],
189 '$factorize_term'(Term, Template, Factors),
190 bind_non_cycles(Factors, 1, Cycles),
191 numbervars(Template+Cycles+Constraints, 0, _,
192 [singletons(true)]).
193prepare_term(Term, Template, Cycles, Constraints) :-
194 copy_term(Term, Copy, Constraints),
195 '$factorize_term'(Copy, Template, Factors),
196 bind_non_cycles(Factors, 1, Cycles),
197 numbervars(Template+Cycles+Constraints, 0, _,
198 [singletons(true)]).
199
200
201bind_non_cycles([], _, []).
202bind_non_cycles([V=Term|T], I, L) :-
203 unify_with_occurs_check(V, Term),
204 !,
205 bind_non_cycles(T, I, L).
206bind_non_cycles([H|T0], I, [H|T]) :-
207 H = ('$VAR'(Name)=_),
208 atom_concat('_S', I, Name),
209 I2 is I + 1,
210 bind_non_cycles(T0, I2, T).
211
212
213defaults([ output(user_output),
214 depth(0),
215 indent_arguments(auto),
216 auto_indent_arguments(4),
217 operators(true),
218 write_options([ quoted(true),
219 numbervars(true),
220 portray(true),
221 attributes(portray)
222 ]),
223 priority(1200)
224 ]).
225
226default_margin(Options0, Options) :-
227 default_right_margin(Options0, Options1),
228 default_indent(Options1, Options).
229
230default_right_margin(Options0, Options) :-
231 option(right_margin(Margin), Options0),
232 !,
233 ( var(Margin)
234 -> tty_right_margin(Options0, Margin)
235 ; true
236 ),
237 Options = Options0.
238default_right_margin(Options0, [right_margin(Margin)|Options0]) :-
239 tty_right_margin(Options0, Margin).
240
241tty_right_margin(Options, Margin) :-
242 option(output(Output), Options),
243 stream_property(Output, tty(true)),
244 catch(tty_size(_Rows, Columns), error(_,_), fail),
245 !,
246 Margin is Columns - 8.
247tty_right_margin(_, 72).
248
249default_indent(Options0, Options) :-
250 option(output(Output), Options0),
251 ( stream_property(Output, position(Pos))
252 -> stream_position_data(line_position, Pos, Column)
253 ; Column = 0
254 ),
255 option(left_margin(LM), Options0, Column),
256 Options = [indent(LM)|Options0].
257
258
259 262
263context(Ctx, Name, Value) :-
264 get_dict(Name, Ctx, Value).
265
266modify_context(Ctx0, Mapping, Ctx) :-
267 Ctx = Ctx0.put(Mapping).
268
269dec_depth(Ctx, Ctx) :-
270 context(Ctx, max_depth, infinite),
271 !.
272dec_depth(Ctx0, Ctx) :-
273 ND is Ctx0.max_depth - 1,
274 Ctx = Ctx0.put(max_depth, ND).
275
276
277 280
281pp(Primitive, Ctx, Options) :-
282 ( atomic(Primitive)
283 ; var(Primitive)
284 ; Primitive = '$VAR'(Var),
285 ( integer(Var)
286 ; atom(Var)
287 )
288 ),
289 !,
290 pprint(Primitive, Ctx, Options).
291pp(Portray, _Ctx, Options) :-
292 option(write_options(WriteOptions), Options),
293 option(portray(true), WriteOptions),
294 option(output(Out), Options),
295 with_output_to(Out, user:portray(Portray)),
296 !.
297pp(List, Ctx, Options) :-
298 List = [_|_],
299 !,
300 context(Ctx, indent, Indent),
301 context(Ctx, depth, Depth),
302 option(output(Out), Options),
303 option(indent_arguments(IndentStyle), Options),
304 ( ( IndentStyle == false
305 -> true
306 ; IndentStyle == auto,
307 print_width(List, Width, Options),
308 option(right_margin(RM), Options),
309 Indent + Width < RM
310 )
311 -> pprint(List, Ctx, Options)
312 ; format(Out, '[ ', []),
313 Nindent is Indent + 2,
314 NDepth is Depth + 1,
315 modify_context(Ctx, [indent=Nindent, depth=NDepth, priority=999], NCtx),
316 pp_list_elements(List, NCtx, Options),
317 indent(Out, Indent, Options),
318 format(Out, ']', [])
319 ).
320pp(Dict, Ctx, Options) :-
321 is_dict(Dict),
322 !,
323 dict_pairs(Dict, Tag, Pairs),
324 option(output(Out), Options),
325 option(indent_arguments(IndentStyle), Options),
326 context(Ctx, indent, Indent),
327 ( IndentStyle == false ; Pairs == []
328 -> pprint(Dict, Ctx, Options)
329 ; IndentStyle == auto,
330 print_width(Dict, Width, Options),
331 option(right_margin(RM), Options),
332 Indent + Width < RM 333 -> pprint(Dict, Ctx, Options)
334 ; compound_indent(Out, '~q{ ', Tag, Indent, Nindent, Options),
335 context(Ctx, depth, Depth),
336 NDepth is Depth + 1,
337 modify_context(Ctx, [indent=Nindent, depth=NDepth], NCtx0),
338 dec_depth(NCtx0, NCtx),
339 pp_dict_args(Pairs, NCtx, Options),
340 BraceIndent is Nindent - 2, 341 indent(Out, BraceIndent, Options),
342 write(Out, '}')
343 ).
344pp(Term, Ctx, Options) :- 345 compound(Term),
346 compound_name_arity(Term, Name, Arity),
347 current_op(Prec, Type, Name),
348 match_op(Type, Arity, Kind, Prec, Left, Right),
349 option(operators(true), Options),
350 !,
351 quoted_op(Name, QName),
352 option(output(Out), Options),
353 context(Ctx, indent, Indent),
354 context(Ctx, depth, Depth),
355 context(Ctx, priority, CPrec),
356 NDepth is Depth + 1,
357 modify_context(Ctx, [depth=NDepth], Ctx1),
358 dec_depth(Ctx1, Ctx2),
359 LeftOptions = Ctx2.put(priority, Left),
360 FuncOptions = Ctx2.put(embrace, never),
361 RightOptions = Ctx2.put(priority, Right),
362 ( Kind == prefix
363 -> arg(1, Term, Arg),
364 ( ( space_op(Name)
365 ; need_space(Name, Arg, FuncOptions, RightOptions)
366 )
367 -> Space = ' '
368 ; Space = ''
369 ),
370 ( CPrec >= Prec
371 -> format(atom(Buf), '~w~w', [QName, Space]),
372 atom_length(Buf, AL),
373 NIndent is Indent + AL,
374 write(Out, Buf),
375 modify_context(Ctx2, [indent=NIndent, priority=Right], Ctx3),
376 pp(Arg, Ctx3, Options)
377 ; format(atom(Buf), '(~w~w', [QName,Space]),
378 atom_length(Buf, AL),
379 NIndent is Indent + AL,
380 write(Out, Buf),
381 modify_context(Ctx2, [indent=NIndent, priority=Right], Ctx3),
382 pp(Arg, Ctx3, Options),
383 format(Out, ')', [])
384 )
385 ; Kind == postfix
386 -> arg(1, Term, Arg),
387 ( ( space_op(Name)
388 ; need_space(Name, Arg, FuncOptions, LeftOptions)
389 )
390 -> Space = ' '
391 ; Space = ''
392 ),
393 ( CPrec >= Prec
394 -> modify_context(Ctx2, [priority=Left], Ctx3),
395 pp(Arg, Ctx3, Options),
396 format(Out, '~w~w', [Space,QName])
397 ; format(Out, '(', []),
398 NIndent is Indent + 1,
399 modify_context(Ctx2, [indent=NIndent, priority=Left], Ctx3),
400 pp(Arg, Ctx3, Options),
401 format(Out, '~w~w)', [Space,QName])
402 )
403 ; arg(1, Term, Arg1), 404 arg(2, Term, Arg2),
405 ( print_width(Term, Width, Options),
406 option(right_margin(RM), Options),
407 Indent + Width < RM
408 -> ToWide = false,
409 ( ( space_op(Name)
410 ; need_space(Arg1, Name, LeftOptions, FuncOptions)
411 ; need_space(Name, Arg2, FuncOptions, RightOptions)
412 )
413 -> Space = ' '
414 ; Space = ''
415 )
416 ; ToWide = true,
417 ( ( is_solo(Name)
418 ; space_op(Name)
419 )
420 -> Space = ''
421 ; Space = ' '
422 )
423 ),
424 ( CPrec >= Prec
425 -> ( ToWide == true,
426 infix_list(Term, Name, List),
427 List == [_,_|_]
428 -> Pri is min(Left,Right),
429 modify_context(Ctx2, [space=Space, priority=Pri], Ctx3),
430 pp_infix_list(List, QName, 2, Ctx3, Options)
431 ; modify_context(Ctx2, [priority=Left], Ctx3),
432 pp(Arg1, Ctx3, Options),
433 format(Out, '~w~w~w', [Space,QName,Space]),
434 line_position(Out, NIndent),
435 modify_context(Ctx2, [priority=Right, indent=NIndent], Ctx4),
436 pp(Arg2, Ctx4, Options)
437 )
438 ; ( ToWide == true,
439 infix_list(Term, Name, List),
440 List = [_,_|_]
441 -> Pri is min(Left,Right),
442 format(Out, '( ', []),
443 NIndent is Indent + 2,
444 modify_context(Ctx2,
445 [space=Space, indent=NIndent, priority=Pri],
446 Ctx3),
447 pp_infix_list(List, QName, 0, Ctx3, Options),
448 indent(Out, Indent, Options),
449 format(Out, ')', [])
450 ; format(Out, '(', []),
451 NIndent is Indent + 1,
452 modify_context(Ctx2, [indent=NIndent, priority=Left], Ctx3),
453 pp(Arg1, Ctx3, Options),
454 format(Out, '~w~w~w', [Space,QName,Space]),
455 modify_context(Ctx2, [priority=Right], Ctx4),
456 pp(Arg2, Ctx4, Options),
457 format(Out, ')', [])
458 )
459 )
460 ).
461pp(Term, Ctx, Options) :- 462 option(output(Out), Options),
463 option(indent_arguments(IndentStyle), Options),
464 context(Ctx, indent, Indent),
465 ( IndentStyle == false
466 -> pprint(Term, Ctx, Options)
467 ; IndentStyle == auto,
468 print_width(Term, Width, Options),
469 option(right_margin(RM), Options),
470 Indent + Width < RM 471 -> pprint(Term, Ctx, Options)
472 ; compound_name_arguments(Term, Name, Args),
473 compound_indent(Out, '~q(', Name, Indent, Nindent, Options),
474 context(Ctx, depth, Depth),
475 NDepth is Depth + 1,
476 modify_context(Ctx,
477 [indent=Nindent, depth=NDepth, priority=999],
478 NCtx0),
479 dec_depth(NCtx0, NCtx),
480 pp_compound_args(Args, NCtx, Options),
481 write(Out, ')')
482 ).
483
484compound_indent(Out, Format, Functor, Indent, Nindent, Options) :-
485 option(indent_arguments(IndentStyle), Options),
486 format(string(Buf2), Format, [Functor]),
487 write(Out, Buf2),
488 atom_length(Buf2, FunctorIndent),
489 ( IndentStyle == auto,
490 option(auto_indent_arguments(IndentArgs), Options),
491 IndentArgs > 0,
492 FunctorIndent > IndentArgs*2
493 -> true
494 ; IndentArgs = IndentStyle
495 ),
496 ( integer(IndentArgs)
497 -> Nindent is Indent + IndentArgs,
498 ( FunctorIndent > IndentArgs
499 -> indent(Out, Nindent, Options)
500 ; true
501 )
502 ; Nindent is Indent + FunctorIndent
503 ).
504
505
506quoted_op(Op, Atom) :-
507 is_solo(Op),
508 !,
509 Atom = Op.
510quoted_op(Op, Q) :-
511 format(atom(Q), '~q', [Op]).
519infix_list(Term, Op, List) :-
520 phrase(infix_list(Term, Op), List).
521
522infix_list(Term, Op) -->
523 { compound(Term),
524 compound_name_arity(Term, Op, 2)
525 },
526 ( {current_op(_Pri, xfy, Op)}
527 -> { arg(1, Term, H),
528 arg(2, Term, Term2)
529 },
530 [H],
531 infix_list(Term2, Op)
532 ; {current_op(_Pri, yfx, Op)}
533 -> { arg(1, Term, Term2),
534 arg(2, Term, T)
535 },
536 infix_list(Term2, Op),
537 [T]
538 ).
539infix_list(Term, Op) -->
540 {atom(Op)}, 541 [Term].
542
543pp_infix_list([H|T], QName, IncrIndent, Ctx, Options) =>
544 pp(H, Ctx, Options),
545 context(Ctx, space, Space),
546 ( T == []
547 -> true
548 ; option(output(Out), Options),
549 format(Out, '~w~w', [Space,QName]),
550 context(Ctx, indent, Indent),
551 NIndent is Indent+IncrIndent,
552 indent(Out, NIndent, Options),
553 modify_context(Ctx, [indent=NIndent], Ctx2),
554 pp_infix_list(T, QName, 0, Ctx2, Options)
555 ).
562pp_list_elements(_, Ctx, Options) :-
563 context(Ctx, max_depth, 0),
564 !,
565 option(output(Out), Options),
566 write(Out, '...').
567pp_list_elements([H|T], Ctx0, Options) :-
568 dec_depth(Ctx0, Ctx),
569 pp(H, Ctx, Options),
570 ( T == []
571 -> true
572 ; nonvar(T),
573 T = [_|_]
574 -> option(output(Out), Options),
575 write(Out, ','),
576 context(Ctx, indent, Indent),
577 indent(Out, Indent, Options),
578 pp_list_elements(T, Ctx, Options)
579 ; option(output(Out), Options),
580 context(Ctx, indent, Indent),
581 indent(Out, Indent-2, Options),
582 write(Out, '| '),
583 pp(T, Ctx, Options)
584 ).
585
586
587pp_compound_args([], _, _).
588pp_compound_args([H|T], Ctx, Options) :-
589 pp(H, Ctx, Options),
590 ( T == []
591 -> true
592 ; T = [_|_]
593 -> option(output(Out), Options),
594 write(Out, ','),
595 context(Ctx, indent, Indent),
596 indent(Out, Indent, Options),
597 pp_compound_args(T, Ctx, Options)
598 ; option(output(Out), Options),
599 context(Ctx, indent, Indent),
600 indent(Out, Indent-2, Options),
601 write(Out, '| '),
602 pp(T, Ctx, Options)
603 ).
604
605
606:- if(current_predicate(is_dict/1)). 607pp_dict_args([Name-Value|T], Ctx, Options) :-
608 option(output(Out), Options),
609 line_position(Out, Pos0),
610 pp(Name, Ctx, Options),
611 write(Out, ': '),
612 line_position(Out, Pos1),
613 context(Ctx, indent, Indent),
614 Indent2 is Indent + Pos1-Pos0,
615 modify_context(Ctx, [indent=Indent2], Ctx2),
616 pp(Value, Ctx2, Options),
617 ( T == []
618 -> true
619 ; option(output(Out), Options),
620 write(Out, ','),
621 indent(Out, Indent, Options),
622 pp_dict_args(T, Ctx, Options)
623 ).
624:- endif. 625
627
628match_op(fx, 1, prefix, P, _, R) :- R is P - 1.
629match_op(fy, 1, prefix, P, _, P).
630match_op(xf, 1, postfix, P, L, _) :- L is P - 1.
631match_op(yf, 1, postfix, P, P, _).
632match_op(xfx, 2, infix, P, A, A) :- A is P - 1.
633match_op(xfy, 2, infix, P, L, P) :- L is P - 1.
634match_op(yfx, 2, infix, P, P, R) :- R is P - 1.
643indent(Out, Indent, Options) :-
644 option(tab_width(TW), Options, 8),
645 nl(Out),
646 ( TW =:= 0
647 -> tab(Out, Indent)
648 ; Tabs is Indent // TW,
649 Spaces is Indent mod TW,
650 forall(between(1, Tabs, _), put(Out, 9)),
651 tab(Out, Spaces)
652 ).
658print_width(Term, W, Options) :-
659 option(right_margin(RM), Options),
660 option(write_options(WOpts), Options),
661 ( catch(write_length(Term, W, [max_length(RM)|WOpts]),
662 error(_,_), fail) 663 -> true 664 ; W = RM
665 ).
671pprint(Term, Ctx, Options) :-
672 option(output(Out), Options),
673 pprint(Out, Term, Ctx, Options).
674
675pprint(Out, Term, Ctx, Options) :-
676 option(write_options(WriteOptions), Options),
677 context(Ctx, max_depth, MaxDepth),
678 ( MaxDepth == infinite
679 -> write_term(Out, Term, WriteOptions)
680 ; MaxDepth =< 0
681 -> format(Out, '...', [])
682 ; write_term(Out, Term, [max_depth(MaxDepth)|WriteOptions])
683 ).
684
685
686
695is_op1(Name, Type, Pri, ArgPri, Options) :-
696 operator_module(Module, Options),
697 current_op(Pri, OpType, Module:Name),
698 argpri(OpType, Type, Pri, ArgPri),
699 !.
700
701argpri(fx, prefix, Pri0, Pri) :- Pri is Pri0 - 1.
702argpri(fy, prefix, Pri, Pri).
703argpri(xf, postfix, Pri0, Pri) :- Pri is Pri0 - 1.
704argpri(yf, postfix, Pri, Pri).
710is_op2(Name, LeftPri, Pri, RightPri, Options) :-
711 operator_module(Module, Options),
712 current_op(Pri, Type, Module:Name),
713 infix_argpri(Type, LeftPri, Pri, RightPri),
714 !.
715
716infix_argpri(xfx, ArgPri, Pri, ArgPri) :- ArgPri is Pri - 1.
717infix_argpri(yfx, Pri, Pri, ArgPri) :- ArgPri is Pri - 1.
718infix_argpri(xfy, ArgPri, Pri, Pri) :- ArgPri is Pri - 1.
726need_space(T1, T2, _, _) :-
727 ( is_solo(T1)
728 ; is_solo(T2)
729 ),
730 !,
731 fail.
732need_space(T1, T2, LeftOptions, RightOptions) :-
733 end_code_type(T1, TypeR, LeftOptions.put(side, right)),
734 end_code_type(T2, TypeL, RightOptions.put(side, left)),
735 \+ no_space(TypeR, TypeL).
736
737no_space(punct, _).
738no_space(_, punct).
739no_space(quote(R), quote(L)) :-
740 !,
741 R \== L.
742no_space(alnum, symbol).
743no_space(symbol, alnum).
750end_code_type(_, Type, Options) :-
751 MaxDepth = Options.max_depth,
752 integer(MaxDepth),
753 Options.depth >= MaxDepth,
754 !,
755 Type = symbol.
756end_code_type(Term, Type, Options) :-
757 primitive(Term, _),
758 !,
759 quote_atomic(Term, S, Options),
760 end_type(S, Type, Options).
761end_code_type(Dict, Type, Options) :-
762 is_dict(Dict, Tag),
763 !,
764 ( Options.side == left
765 -> end_code_type(Tag, Type, Options)
766 ; Type = punct
767 ).
768end_code_type('$VAR'(Var), Type, Options) :-
769 Options.get(numbervars) == true,
770 !,
771 format(string(S), '~W', ['$VAR'(Var), [numbervars(true)]]),
772 end_type(S, Type, Options).
773end_code_type(List, Type, _) :-
774 ( List == []
775 ; List = [_|_]
776 ),
777 !,
778 Type = punct.
779end_code_type(OpTerm, Type, Options) :-
780 compound_name_arity(OpTerm, Name, 1),
781 is_op1(Name, OpType, Pri, ArgPri, Options),
782 \+ Options.get(ignore_ops) == true,
783 !,
784 ( Pri > Options.priority
785 -> Type = punct
786 ; op_or_arg(OpType, Options.side, OpArg),
787 ( OpArg == op
788 -> end_code_type(Name, Type, Options)
789 ; arg(1, OpTerm, Arg),
790 arg_options(Options, ArgOptions),
791 end_code_type(Arg, Type, ArgOptions.put(priority, ArgPri))
792 )
793 ).
794end_code_type(OpTerm, Type, Options) :-
795 compound_name_arity(OpTerm, Name, 2),
796 is_op2(Name, LeftPri, Pri, _RightPri, Options),
797 \+ Options.get(ignore_ops) == true,
798 !,
799 ( Pri > Options.priority
800 -> Type = punct
801 ; arg(1, OpTerm, Arg),
802 arg_options(Options, ArgOptions),
803 end_code_type(Arg, Type, ArgOptions.put(priority, LeftPri))
804 ).
805end_code_type(Compound, Type, Options) :-
806 compound_name_arity(Compound, Name, _),
807 end_code_type(Name, Type, Options).
808
809op_or_arg(prefix, left, op).
810op_or_arg(prefix, right, arg).
811op_or_arg(postfix, left, arg).
812op_or_arg(postfix, right, op).
813
814
815
816end_type(S, Type, Options) :-
817 number(S),
818 !,
819 ( (S < 0 ; S == -0.0),
820 Options.side == left
821 -> Type = symbol
822 ; Type = alnum
823 ).
824end_type(S, Type, Options) :-
825 Options.side == left,
826 !,
827 left_type(S, Type).
828end_type(S, Type, _) :-
829 right_type(S, Type).
830
831left_type(S, Type), atom(S) =>
832 sub_atom(S, 0, 1, _, Start),
833 syntax_type(Start, Type).
834left_type(S, Type), string(S) =>
835 sub_string(S, 0, 1, _, Start),
836 syntax_type(Start, Type).
837left_type(S, Type), blob(S, _) =>
838 syntax_type("<", Type).
839
840right_type(S, Type), atom(S) =>
841 sub_atom(S, _, 1, 0, End),
842 syntax_type(End, Type).
843right_type(S, Type), string(S) =>
844 sub_string(S, _, 1, 0, End),
845 syntax_type(End, Type).
846right_type(S, Type), blob(S, _) =>
847 syntax_type(")", Type).
848
849syntax_type("\"", quote(double)) :- !.
850syntax_type("\'", quote(single)) :- !.
851syntax_type("\`", quote(back)) :- !.
852syntax_type(S, Type) :-
853 string_code(1, S, C),
854 ( code_type(C, prolog_identifier_continue)
855 -> Type = alnum
856 ; code_type(C, prolog_symbol)
857 -> Type = symbol
858 ; code_type(C, space)
859 -> Type = layout
860 ; Type = punct
861 ).
862
863is_solo(Var) :-
864 var(Var), !, fail.
865is_solo(',').
866is_solo(';').
867is_solo('!').
874primitive(Term, Type) :- var(Term), !, Type = 'pl-avar'.
875primitive(Term, Type) :- atom(Term), !, Type = 'pl-atom'.
876primitive(Term, Type) :- blob(Term,_), !, Type = 'pl-blob'.
877primitive(Term, Type) :- string(Term), !, Type = 'pl-string'.
878primitive(Term, Type) :- integer(Term), !, Type = 'pl-int'.
879primitive(Term, Type) :- rational(Term), !, Type = 'pl-rational'.
880primitive(Term, Type) :- float(Term), !, Type = 'pl-float'.
886operator_module(Module, Options) :-
887 Module = Options.get(module),
888 !.
889operator_module(TypeIn, _) :-
890 '$current_typein_module'(TypeIn).
896arg_options(Options, Options.put(depth, NewDepth)) :-
897 NewDepth is Options.depth+1.
898
899quote_atomic(Float, String, Options) :-
900 float(Float),
901 Format = Options.get(float_format),
902 !,
903 format(string(String), Format, [Float]).
904quote_atomic(Plain, Plain, _) :-
905 number(Plain),
906 !.
907quote_atomic(Plain, String, Options) :-
908 Options.get(quoted) == true,
909 !,
910 ( Options.get(embrace) == never
911 -> format(string(String), '~q', [Plain])
912 ; format(string(String), '~W', [Plain, Options])
913 ).
914quote_atomic(Var, String, Options) :-
915 var(Var),
916 !,
917 format(string(String), '~W', [Var, Options]).
918quote_atomic(Plain, Plain, _).
919
920space_op(:-)
Pretty Print Prolog terms
This module is a first start of what should become a full-featured pretty printer for Prolog terms with many options and parameters. Eventually, it should replace portray_clause/1 and various other special-purpose predicates.