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