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
61
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 operators(boolean),
69 write_options(list)
70 ]). 71
119
120print_term(Term, Options) :-
121 defaults(Defs0),
122 select_option(write_options(WrtDefs), Defs0, Defs),
123 select_option(write_options(WrtUser), Options, Options1, []),
124 merge_options(WrtUser, WrtDefs, WrtOpts),
125 merge_options(Options1, Defs, Options2),
126 Options3 = [write_options(WrtOpts)|Options2],
127 default_margin(Options3, Options4),
128 \+ \+ print_term_2(Term, Options4).
129
130print_term_2(Term, Options) :-
131 prepare_term(Term, Template, Cycles, Constraints),
132 option(write_options(WrtOpts), Options),
133 option(max_depth(MaxDepth), WrtOpts, infinite),
134
135 dict_create(Context, #, [max_depth(MaxDepth)|Options]),
136 pp(Template, Context, Options),
137 print_extra(Cycles, Context, 'where', Options),
138 print_extra(Constraints, Context, 'with constraints', Options),
139 ( option(fullstop(true), Options)
140 -> option(output(Out), Options),
141 put_char(Out, '.')
142 ; true
143 ),
144 ( option(nl(true), Options)
145 -> option(output(Out2), Options),
146 nl(Out2)
147 ; true
148 ).
149
([], _, _, _) :- !.
151print_extra(List, Context, Comment, Options) :-
152 option(output(Out), Options),
153 format(Out, ', % ~w', [Comment]),
154 context(Context, indent, Indent),
155 NewIndent is Indent+4,
156 modify_context(Context, [indent=NewIndent], Context1),
157 print_extra_2(List, Context1, Options).
158
([H|T], Context, Options) :-
160 option(output(Out), Options),
161 context(Context, indent, Indent),
162 indent(Out, Indent, Options),
163 pp(H, Context, Options),
164 ( T == []
165 -> true
166 ; format(Out, ',', []),
167 print_extra_2(T, Context, Options)
168 ).
169
170
175
176prepare_term(Term, Template, Cycles, Constraints) :-
177 term_attvars(Term, []),
178 !,
179 Constraints = [],
180 '$factorize_term'(Term, Template, Factors),
181 bind_non_cycles(Factors, 1, Cycles),
182 numbervars(Template+Cycles+Constraints, 0, _,
183 [singletons(true)]).
184prepare_term(Term, Template, Cycles, Constraints) :-
185 copy_term(Term, Copy, Constraints),
186 '$factorize_term'(Copy, Template, Factors),
187 bind_non_cycles(Factors, 1, Cycles),
188 numbervars(Template+Cycles+Constraints, 0, _,
189 [singletons(true)]).
190
191
192bind_non_cycles([], _, []).
193bind_non_cycles([V=Term|T], I, L) :-
194 unify_with_occurs_check(V, Term),
195 !,
196 bind_non_cycles(T, I, L).
197bind_non_cycles([H|T0], I, [H|T]) :-
198 H = ('$VAR'(Name)=_),
199 atom_concat('_S', I, Name),
200 I2 is I + 1,
201 bind_non_cycles(T0, I2, T).
202
203
204defaults([ output(user_output),
205 depth(0),
206 indent_arguments(auto),
207 operators(true),
208 write_options([ quoted(true),
209 numbervars(true),
210 portray(true),
211 attributes(portray)
212 ]),
213 priority(1200)
214 ]).
215
216default_margin(Options0, Options) :-
217 default_right_margin(Options0, Options1),
218 default_indent(Options1, Options).
219
220default_right_margin(Options0, Options) :-
221 option(right_margin(Margin), Options0),
222 !,
223 ( var(Margin)
224 -> tty_right_margin(Options0, Margin)
225 ; true
226 ),
227 Options = Options0.
228default_right_margin(Options0, [right_margin(Margin)|Options0]) :-
229 tty_right_margin(Options0, Margin).
230
231tty_right_margin(Options, Margin) :-
232 option(output(Output), Options),
233 stream_property(Output, tty(true)),
234 catch(tty_size(_Rows, Columns), error(_,_), fail),
235 !,
236 Margin is Columns - 8.
237tty_right_margin(_, 72).
238
239default_indent(Options0, Options) :-
240 option(output(Output), Options0),
241 ( stream_property(Output, position(Pos))
242 -> stream_position_data(line_position, Pos, Column)
243 ; Column = 0
244 ),
245 option(left_margin(LM), Options0, Column),
246 Options = [indent(LM)|Options0].
247
248
249 252
253context(Ctx, Name, Value) :-
254 get_dict(Name, Ctx, Value).
255
256modify_context(Ctx0, Mapping, Ctx) :-
257 Ctx = Ctx0.put(Mapping).
258
259dec_depth(Ctx, Ctx) :-
260 context(Ctx, max_depth, infinite),
261 !.
262dec_depth(Ctx0, Ctx) :-
263 ND is Ctx0.max_depth - 1,
264 Ctx = Ctx0.put(max_depth, ND).
265
266
267 270
271pp(Primitive, Ctx, Options) :-
272 ( atomic(Primitive)
273 ; var(Primitive)
274 ; Primitive = '$VAR'(Var),
275 ( integer(Var)
276 ; atom(Var)
277 )
278 ),
279 !,
280 pprint(Primitive, Ctx, Options).
281pp(Portray, _Ctx, Options) :-
282 option(write_options(WriteOptions), Options),
283 option(portray(true), WriteOptions),
284 option(output(Out), Options),
285 with_output_to(Out, user:portray(Portray)),
286 !.
287pp(List, Ctx, Options) :-
288 List = [_|_],
289 !,
290 context(Ctx, indent, Indent),
291 context(Ctx, depth, Depth),
292 option(output(Out), Options),
293 option(indent_arguments(IndentStyle), Options),
294 ( ( IndentStyle == false
295 -> true
296 ; IndentStyle == auto,
297 print_width(List, Width, Options),
298 option(right_margin(RM), Options),
299 Indent + Width < RM
300 )
301 -> pprint(List, Ctx, Options)
302 ; format(Out, '[ ', []),
303 Nindent is Indent + 2,
304 NDepth is Depth + 1,
305 modify_context(Ctx, [indent=Nindent, depth=NDepth, priority=999], NCtx),
306 pp_list_elements(List, NCtx, Options),
307 indent(Out, Indent, Options),
308 format(Out, ']', [])
309 ).
310pp(Dict, Ctx, Options) :-
311 is_dict(Dict),
312 !,
313 dict_pairs(Dict, Tag, Pairs),
314 option(output(Out), Options),
315 option(indent_arguments(IndentStyle), Options),
316 context(Ctx, indent, Indent),
317 ( IndentStyle == false ; Pairs == []
318 -> pprint(Dict, Ctx, Options)
319 ; IndentStyle == auto,
320 print_width(Dict, Width, Options),
321 option(right_margin(RM), Options),
322 Indent + Width < RM 323 -> pprint(Dict, Ctx, Options)
324 ; format(atom(Buf2), '~q{ ', [Tag]),
325 write(Out, Buf2),
326 atom_length(Buf2, FunctorIndent),
327 ( integer(IndentStyle)
328 -> Nindent is Indent + IndentStyle,
329 ( FunctorIndent > IndentStyle
330 -> indent(Out, Nindent, Options)
331 ; true
332 )
333 ; Nindent is Indent + FunctorIndent
334 ),
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 modify_context(Ctx2, [priority=Right], Ctx4),
435 pp(Arg2, Ctx4, Options)
436 )
437 ; ( ToWide == true,
438 infix_list(Term, Name, List),
439 List = [_,_|_]
440 -> Pri is min(Left,Right),
441 format(Out, '( ', []),
442 NIndent is Indent + 2,
443 modify_context(Ctx2,
444 [space=Space, indent=NIndent, priority=Pri],
445 Ctx3),
446 pp_infix_list(List, QName, 0, Ctx3, Options),
447 indent(Out, Indent, Options),
448 format(Out, ')', [])
449 ; format(Out, '(', []),
450 NIndent is Indent + 1,
451 modify_context(Ctx2, [indent=NIndent, priority=Left], Ctx3),
452 pp(Arg1, Ctx3, Options),
453 format(Out, '~w~w~w', [Space,QName,Space]),
454 modify_context(Ctx2, [priority=Right], Ctx4),
455 pp(Arg2, Ctx4, Options),
456 format(Out, ')', [])
457 )
458 )
459 ).
460pp(Term, Ctx, Options) :- 461 option(output(Out), Options),
462 option(indent_arguments(IndentStyle), Options),
463 context(Ctx, indent, Indent),
464 ( IndentStyle == false
465 -> pprint(Term, Ctx, Options)
466 ; IndentStyle == auto,
467 print_width(Term, Width, Options),
468 option(right_margin(RM), Options),
469 Indent + Width < RM 470 -> pprint(Term, Ctx, Options)
471 ; compound_name_arguments(Term, Name, Args),
472 format(atom(Buf2), '~q(', [Name]),
473 write(Out, Buf2),
474 atom_length(Buf2, FunctorIndent),
475 ( integer(IndentStyle)
476 -> Nindent is Indent + IndentStyle,
477 ( FunctorIndent > IndentStyle
478 -> indent(Out, Nindent, Options)
479 ; true
480 )
481 ; Nindent is Indent + FunctorIndent
482 ),
483 context(Ctx, depth, Depth),
484 NDepth is Depth + 1,
485 modify_context(Ctx,
486 [indent=Nindent, depth=NDepth, priority=999],
487 NCtx0),
488 dec_depth(NCtx0, NCtx),
489 pp_compound_args(Args, NCtx, Options),
490 write(Out, ')')
491 ).
492
493
494quoted_op(Op, Atom) :-
495 is_solo(Op),
496 !,
497 Atom = Op.
498quoted_op(Op, Q) :-
499 format(atom(Q), '~q', [Op]).
500
506
507infix_list(Term, Op, List) :-
508 phrase(infix_list(Term, Op), List).
509
510infix_list(Term, Op) -->
511 { compound(Term),
512 compound_name_arity(Term, Op, 2)
513 },
514 ( {current_op(_Pri, xfy, Op)}
515 -> { arg(1, Term, H),
516 arg(2, Term, Term2)
517 },
518 [H],
519 infix_list(Term2, Op)
520 ; {current_op(_Pri, yfx, Op)}
521 -> { arg(1, Term, Term2),
522 arg(2, Term, T)
523 },
524 infix_list(Term2, Op),
525 [T]
526 ).
527infix_list(Term, Op) -->
528 {atom(Op)}, 529 [Term].
530
531pp_infix_list([H|T], QName, IncrIndent, Ctx, Options) =>
532 pp(H, Ctx, Options),
533 context(Ctx, space, Space),
534 ( T == []
535 -> true
536 ; option(output(Out), Options),
537 format(Out, '~w~w', [Space,QName]),
538 context(Ctx, indent, Indent),
539 NIndent is Indent+IncrIndent,
540 indent(Out, NIndent, Options),
541 modify_context(Ctx, [indent=NIndent], Ctx2),
542 pp_infix_list(T, QName, 0, Ctx2, Options)
543 ).
544
545
549
550pp_list_elements(_, Ctx, Options) :-
551 context(Ctx, max_depth, 0),
552 !,
553 option(output(Out), Options),
554 write(Out, '...').
555pp_list_elements([H|T], Ctx0, Options) :-
556 dec_depth(Ctx0, Ctx),
557 pp(H, Ctx, Options),
558 ( T == []
559 -> true
560 ; nonvar(T),
561 T = [_|_]
562 -> option(output(Out), Options),
563 write(Out, ','),
564 context(Ctx, indent, Indent),
565 indent(Out, Indent, Options),
566 pp_list_elements(T, Ctx, Options)
567 ; option(output(Out), Options),
568 context(Ctx, indent, Indent),
569 indent(Out, Indent-2, Options),
570 write(Out, '| '),
571 pp(T, Ctx, Options)
572 ).
573
574
575pp_compound_args([], _, _).
576pp_compound_args([H|T], Ctx, Options) :-
577 pp(H, Ctx, Options),
578 ( T == []
579 -> true
580 ; T = [_|_]
581 -> option(output(Out), Options),
582 write(Out, ','),
583 context(Ctx, indent, Indent),
584 indent(Out, Indent, Options),
585 pp_compound_args(T, Ctx, Options)
586 ; option(output(Out), Options),
587 context(Ctx, indent, Indent),
588 indent(Out, Indent-2, Options),
589 write(Out, '| '),
590 pp(T, Ctx, Options)
591 ).
592
593
594:- if(current_predicate(is_dict/1)). 595pp_dict_args([Name-Value|T], Ctx, Options) :-
596 option(output(Out), Options),
597 line_position(Out, Pos0),
598 pp(Name, Ctx, Options),
599 write(Out, ':'),
600 line_position(Out, Pos1),
601 context(Ctx, indent, Indent),
602 Indent2 is Indent + Pos1-Pos0,
603 modify_context(Ctx, [indent=Indent2], Ctx2),
604 pp(Value, Ctx2, Options),
605 ( T == []
606 -> true
607 ; option(output(Out), Options),
608 write(Out, ','),
609 indent(Out, Indent, Options),
610 pp_dict_args(T, Ctx, Options)
611 ).
612:- endif. 613
615
616match_op(fx, 1, prefix, P, _, R) :- R is P - 1.
617match_op(fy, 1, prefix, P, _, P).
618match_op(xf, 1, postfix, P, L, _) :- L is P - 1.
619match_op(yf, 1, postfix, P, P, _).
620match_op(xfx, 2, infix, P, A, A) :- A is P - 1.
621match_op(xfy, 2, infix, P, L, P) :- L is P - 1.
622match_op(yfx, 2, infix, P, P, R) :- R is P - 1.
623
624
630
631indent(Out, Indent, Options) :-
632 option(tab_width(TW), Options, 8),
633 nl(Out),
634 ( TW =:= 0
635 -> tab(Out, Indent)
636 ; Tabs is Indent // TW,
637 Spaces is Indent mod TW,
638 forall(between(1, Tabs, _), put(Out, 9)),
639 tab(Out, Spaces)
640 ).
641
645
646print_width(Term, W, Options) :-
647 option(right_margin(RM), Options),
648 option(write_options(WOpts), Options),
649 ( catch(write_length(Term, W, [max_length(RM)|WOpts]),
650 error(_,_), fail) 651 -> true 652 ; W = RM
653 ).
654
658
659pprint(Term, Ctx, Options) :-
660 option(output(Out), Options),
661 pprint(Out, Term, Ctx, Options).
662
663pprint(Out, Term, Ctx, Options) :-
664 option(write_options(WriteOptions), Options),
665 context(Ctx, max_depth, MaxDepth),
666 ( MaxDepth == infinite
667 -> write_term(Out, Term, WriteOptions)
668 ; MaxDepth =< 0
669 -> format(Out, '...', [])
670 ; write_term(Out, Term, [max_depth(MaxDepth)|WriteOptions])
671 ).
672
673
674 677
678
682
683is_op1(Name, Type, Pri, ArgPri, Options) :-
684 operator_module(Module, Options),
685 current_op(Pri, OpType, Module:Name),
686 argpri(OpType, Type, Pri, ArgPri),
687 !.
688
689argpri(fx, prefix, Pri0, Pri) :- Pri is Pri0 - 1.
690argpri(fy, prefix, Pri, Pri).
691argpri(xf, postfix, Pri0, Pri) :- Pri is Pri0 - 1.
692argpri(yf, postfix, Pri, Pri).
693
697
698is_op2(Name, LeftPri, Pri, RightPri, Options) :-
699 operator_module(Module, Options),
700 current_op(Pri, Type, Module:Name),
701 infix_argpri(Type, LeftPri, Pri, RightPri),
702 !.
703
704infix_argpri(xfx, ArgPri, Pri, ArgPri) :- ArgPri is Pri - 1.
705infix_argpri(yfx, Pri, Pri, ArgPri) :- ArgPri is Pri - 1.
706infix_argpri(xfy, ArgPri, Pri, Pri) :- ArgPri is Pri - 1.
707
708
713
714need_space(T1, T2, _, _) :-
715 ( is_solo(T1)
716 ; is_solo(T2)
717 ),
718 !,
719 fail.
720need_space(T1, T2, LeftOptions, RightOptions) :-
721 end_code_type(T1, TypeR, LeftOptions.put(side, right)),
722 end_code_type(T2, TypeL, RightOptions.put(side, left)),
723 \+ no_space(TypeR, TypeL).
724
725no_space(punct, _).
726no_space(_, punct).
727no_space(quote(R), quote(L)) :-
728 !,
729 R \== L.
730no_space(alnum, symbol).
731no_space(symbol, alnum).
732
737
738end_code_type(_, Type, Options) :-
739 MaxDepth = Options.max_depth,
740 integer(MaxDepth),
741 Options.depth >= MaxDepth,
742 !,
743 Type = symbol.
744end_code_type(Term, Type, Options) :-
745 primitive(Term, _),
746 !,
747 quote_atomic(Term, S, Options),
748 end_type(S, Type, Options).
749end_code_type(Dict, Type, Options) :-
750 is_dict(Dict, Tag),
751 !,
752 ( Options.side == left
753 -> end_code_type(Tag, Type, Options)
754 ; Type = punct
755 ).
756end_code_type('$VAR'(Var), Type, Options) :-
757 Options.get(numbervars) == true,
758 !,
759 format(string(S), '~W', ['$VAR'(Var), [numbervars(true)]]),
760 end_type(S, Type, Options).
761end_code_type(List, Type, _) :-
762 ( List == []
763 ; List = [_|_]
764 ),
765 !,
766 Type = punct.
767end_code_type(OpTerm, Type, Options) :-
768 compound_name_arity(OpTerm, Name, 1),
769 is_op1(Name, OpType, Pri, ArgPri, Options),
770 \+ Options.get(ignore_ops) == true,
771 !,
772 ( Pri > Options.priority
773 -> Type = punct
774 ; op_or_arg(OpType, Options.side, OpArg),
775 ( OpArg == op
776 -> end_code_type(Name, Type, Options)
777 ; arg(1, OpTerm, Arg),
778 arg_options(Options, ArgOptions),
779 end_code_type(Arg, Type, ArgOptions.put(priority, ArgPri))
780 )
781 ).
782end_code_type(OpTerm, Type, Options) :-
783 compound_name_arity(OpTerm, Name, 2),
784 is_op2(Name, LeftPri, Pri, _RightPri, Options),
785 \+ Options.get(ignore_ops) == true,
786 !,
787 ( Pri > Options.priority
788 -> Type = punct
789 ; arg(1, OpTerm, Arg),
790 arg_options(Options, ArgOptions),
791 end_code_type(Arg, Type, ArgOptions.put(priority, LeftPri))
792 ).
793end_code_type(Compound, Type, Options) :-
794 compound_name_arity(Compound, Name, _),
795 end_code_type(Name, Type, Options).
796
797op_or_arg(prefix, left, op).
798op_or_arg(prefix, right, arg).
799op_or_arg(postfix, left, arg).
800op_or_arg(postfix, right, op).
801
802
803
804end_type(S, Type, Options) :-
805 number(S),
806 !,
807 ( (S < 0 ; S == -0.0),
808 Options.side == left
809 -> Type = symbol
810 ; Type = alnum
811 ).
812end_type(S, Type, Options) :-
813 Options.side == left,
814 !,
815 sub_string(S, 0, 1, _, Start),
816 syntax_type(Start, Type).
817end_type(S, Type, _) :-
818 sub_string(S, _, 1, 0, End),
819 syntax_type(End, Type).
820
821syntax_type("\"", quote(double)) :- !.
822syntax_type("\'", quote(single)) :- !.
823syntax_type("\`", quote(back)) :- !.
824syntax_type(S, Type) :-
825 string_code(1, S, C),
826 ( code_type(C, prolog_identifier_continue)
827 -> Type = alnum
828 ; code_type(C, prolog_symbol)
829 -> Type = symbol
830 ; code_type(C, space)
831 -> Type = layout
832 ; Type = punct
833 ).
834
835is_solo(Var) :-
836 var(Var), !, fail.
837is_solo(',').
838is_solo(';').
839is_solo('!').
840
845
846primitive(Term, Type) :- var(Term), !, Type = 'pl-avar'.
847primitive(Term, Type) :- atom(Term), !, Type = 'pl-atom'.
848primitive(Term, Type) :- string(Term), !, Type = 'pl-string'.
849primitive(Term, Type) :- integer(Term), !, Type = 'pl-int'.
850primitive(Term, Type) :- rational(Term), !, Type = 'pl-rational'.
851primitive(Term, Type) :- float(Term), !, Type = 'pl-float'.
852
856
857operator_module(Module, Options) :-
858 Module = Options.get(module),
859 !.
860operator_module(TypeIn, _) :-
861 '$current_typein_module'(TypeIn).
862
866
867arg_options(Options, Options.put(depth, NewDepth)) :-
868 NewDepth is Options.depth+1.
869
870quote_atomic(Float, String, Options) :-
871 float(Float),
872 Format = Options.get(float_format),
873 !,
874 format(string(String), Format, [Float]).
875quote_atomic(Plain, Plain, _) :-
876 number(Plain),
877 !.
878quote_atomic(Plain, String, Options) :-
879 Options.get(quoted) == true,
880 !,
881 ( Options.get(embrace) == never
882 -> format(string(String), '~q', [Plain])
883 ; format(string(String), '~W', [Plain, Options])
884 ).
885quote_atomic(Var, String, Options) :-
886 var(Var),
887 !,
888 format(string(String), '~W', [Var, Options]).
889quote_atomic(Plain, Plain, _).
890
891space_op(:-)