35
36:- module(pldoc_latex,
37 [ doc_latex/3, 38 latex_for_file/3, 39 latex_for_wiki_file/3, 40 latex_for_predicates/3 41 ]). 42:- use_module(library(pldoc)). 43:- use_module(library(readutil)). 44:- use_module(library(error)). 45:- use_module(library(apply)). 46:- use_module(library(option)). 47:- use_module(library(lists)). 48:- use_module(library(debug)). 49:- use_module(pldoc(doc_wiki)). 50:- use_module(pldoc(doc_process)). 51:- use_module(pldoc(doc_modes)). 52:- use_module(library(pairs), [pairs_values/2]). 53:- use_module(library(prolog_source), [file_name_on_path/2]). 54:- use_module(library(prolog_xref), [xref_hook/1]). 55:- use_module(pldoc(doc_html), 56 [ doc_file_objects/5, 57 unquote_filespec/2,
58 doc_tag_title/2,
59 existing_linked_file/2,
60 pred_anchor_name/3,
61 private/2,
62 (multifile)/2,
63 is_pi/1,
64 is_op_type/2
65 ]). 66
87
88:- predicate_options(doc_latex/3, 3,
89 [ stand_alone(boolean),
90 public_only(boolean),
91 section_level(oneof([section,subsection,subsubsection])),
92 summary(atom)
93 ]). 94:- predicate_options(latex_for_file/3, 3,
95 [ stand_alone(boolean),
96 public_only(boolean),
97 section_level(oneof([section,subsection,subsubsection]))
98 ]). 99:- predicate_options(latex_for_predicates/3, 3,
100 [ 101 ]). 102:- predicate_options(latex_for_wiki_file/3, 3,
103 [ stand_alone(boolean),
104 public_only(boolean),
105 section_level(oneof([section,subsection,subsubsection]))
106 ]). 107
108
109:- thread_local
110 options/1,
111 documented/1. 112
113current_options(Options) :-
114 options(Current),
115 !,
116 Options = Current.
117current_options([]).
118
154
155doc_latex(Spec, OutFile, Options) :-
156 load_urldefs,
157 merge_options(Options,
158 [ include_reexported(true)
159 ],
160 Options1),
161 retractall(documented(_)),
162 setup_call_cleanup(
163 asserta(options(Options), Ref),
164 phrase(process_items(Spec, [body], Options1), Tokens),
165 erase(Ref)),
166 setup_call_cleanup(
167 open(OutFile, write, Out),
168 print_latex(Out, Tokens, Options1),
169 close(Out)),
170 latex_summary(Options).
171
172process_items([], Mode, _) -->
173 !,
174 pop_mode(body, Mode, _).
175process_items([H|T], Mode, Options) -->
176 process_items(H, Mode, Mode1, Options),
177 process_items(T, Mode1, Options).
178process_items(Spec, Mode, Options) -->
179 {Mode = [Mode0|_]},
180 process_items(Spec, Mode, Mode1, Options),
181 pop_mode(Mode0, Mode1, _).
182
183process_items(PI, Mode0, Mode, Options) -->
184 { is_pi(PI) },
185 !,
186 need_mode(description, Mode0, Mode),
187 latex_tokens_for_predicates(PI, Options).
188process_items(FileSpec, Mode0, Mode, Options) -->
189 { ( absolute_file_name(FileSpec,
190 [ file_type(prolog),
191 access(read),
192 file_errors(fail)
193 ],
194 File)
195 -> true
196 ; absolute_file_name(FileSpec,
197 [ access(read)
198 ],
199 File)
200 ),
201 file_name_extension(_Base, Ext, File)
202 },
203 need_mode(body, Mode0, Mode),
204 ( { user:prolog_file_type(Ext, prolog) }
205 -> latex_tokens_for_file(File, Options)
206 ; latex_tokens_for_wiki_file(File, Options)
207 ).
208
209
216
217latex_for_file(FileSpec, Out, Options) :-
218 load_urldefs,
219 phrase(latex_tokens_for_file(FileSpec, Options), Tokens),
220 print_latex(Out, Tokens, Options).
221
222
224
225latex_tokens_for_file(FileSpec, Options, Tokens, Tail) :-
226 absolute_file_name(FileSpec,
227 [ file_type(prolog),
228 access(read)
229 ],
230 File),
231 doc_file_objects(FileSpec, File, Objects, FileOptions, Options),
232 asserta(options(Options), Ref),
233 call_cleanup(phrase(latex([ \file_header(File, FileOptions)
234 | \objects(Objects, FileOptions)
235 ]),
236 Tokens, Tail),
237 erase(Ref)).
238
239
246
247latex_for_wiki_file(FileSpec, Out, Options) :-
248 load_urldefs,
249 phrase(latex_tokens_for_wiki_file(FileSpec, Options), Tokens),
250 print_latex(Out, Tokens, Options).
251
252latex_tokens_for_wiki_file(FileSpec, Options, Tokens, Tail) :-
253 absolute_file_name(FileSpec, File,
254 [ access(read)
255 ]),
256 read_file_to_codes(File, String, []),
257 b_setval(pldoc_file, File),
258 asserta(options(Options), Ref),
259 call_cleanup((wiki_codes_to_dom(String, [], DOM),
260 phrase(latex(DOM), Tokens, Tail)
261 ),
262 (nb_delete(pldoc_file),
263 erase(Ref))).
264
265
272
273latex_for_predicates(Spec, Out, Options) :-
274 load_urldefs,
275 phrase(latex_tokens_for_predicates(Spec, Options), Tokens),
276 print_latex(Out, [nl_exact(0)|Tokens], Options).
277
278latex_tokens_for_predicates([], _Options) --> !.
279latex_tokens_for_predicates([H|T], Options) -->
280 !,
281 latex_tokens_for_predicates(H, Options),
282 latex_tokens_for_predicates(T, Options).
283latex_tokens_for_predicates(PI, Options) -->
284 { generic_pi(PI),
285 !,
286 ( doc_comment(PI, Pos, _Summary, Comment)
287 -> true
288 ; Comment = ''
289 )
290 },
291 object(PI, Pos, Comment, [description], _, Options).
292latex_tokens_for_predicates(Spec, Options) -->
293 { findall(PI, documented_pi(Spec, PI, Options), List),
294 ( List == []
295 -> print_message(warning, pldoc(no_predicates_from(Spec)))
296 ; true
297 )
298 },
299 latex_tokens_for_predicates(List, Options).
300
301documented_pi(Spec, PI, Options) :-
302 option(modules(List), Options),
303 member(M, List),
304 generalise_spec(Spec, PI, M),
305 doc_comment(PI, _Pos, _Summary, _Comment),
306 !.
307documented_pi(Spec, PI, Options) :-
308 option(module(M), Options),
309 generalise_spec(Spec, PI, M),
310 doc_comment(PI, _Pos, _Summary, _Comment),
311 !.
312documented_pi(Spec, PI, _Options) :-
313 generalise_spec(Spec, PI, _),
314 doc_comment(PI, _Pos, _Summary, _Comment).
315
316generic_pi(Module:Name/Arity) :-
317 atom(Module), atom(Name), integer(Arity),
318 !.
319generic_pi(Module:Name//Arity) :-
320 atom(Module), atom(Name), integer(Arity).
321
322generalise_spec(Name/Arity, M:Name/Arity, M).
323generalise_spec(Name//Arity, M:Name//Arity, M).
324
325
326 329
330:- thread_local
331 fragile/0. 332
333latex([]) -->
334 !,
335 [].
336latex(Atomic) -->
337 { string(Atomic),
338 atom_string(Atom, Atomic),
339 sub_atom(Atom, 0, _, 0, 'LaTeX')
340 },
341 !,
342 [ latex('\\LaTeX{}') ].
343latex(Atomic) --> 344 { atomic(Atomic),
345 !,
346 atom_string(Atom, Atomic),
347 findall(x, sub_atom(Atom, _, _, _, '\n'), Xs),
348 length(Xs, Lines)
349 },
350 ( {Lines == 0}
351 -> [ Atomic ]
352 ; [ nl(Lines) ]
353 ).
354latex(List) -->
355 latex_special(List, Rest),
356 !,
357 latex(Rest).
358latex(w(Word)) -->
359 [ Word ].
360latex([H|T]) -->
361 !,
362 ( latex(H)
363 -> latex(T)
364 ; { print_message(error, latex(failed(H))) },
365 latex(T)
366 ).
367
369latex(h1(Attrs, Content)) -->
370 latex_section(0, Attrs, Content).
371latex(h2(Attrs, Content)) -->
372 latex_section(1, Attrs, Content).
373latex(h3(Attrs, Content)) -->
374 latex_section(2, Attrs, Content).
375latex(h4(Attrs, Content)) -->
376 latex_section(3, Attrs, Content).
377latex(p(Content)) -->
378 [ nl_exact(2) ],
379 latex(Content).
380latex(blockquote(Content)) -->
381 latex(cmd(begin(quote))),
382 latex(Content),
383 latex(cmd(end(quote))).
384latex(center(Content)) -->
385 latex(cmd(begin(center))),
386 latex(Content),
387 latex(cmd(end(center))).
388latex(a(Attrs, Content)) -->
389 { attribute(href(HREF), Attrs) },
390 ( {HREF == Content}
391 -> latex(cmd(url(no_escape(HREF))))
392 ; { atom_concat(#,Sec,HREF) }
393 -> latex([Content, ' (', cmd(secref(Sec)), ')'])
394 ; latex(cmd(href(no_escape(HREF), Content)))
395 ).
396latex(br(_)) -->
397 latex(latex(\\)).
398latex(hr(_)) -->
399 latex(cmd(hrule)).
400latex(code(CodeList)) -->
401 { is_list(CodeList),
402 !,
403 atomic_list_concat(CodeList, Atom)
404 },
405 ( {fragile}
406 -> latex(cmd(const(Atom)))
407 ; [ verb(Atom) ]
408 ).
409latex(code(Code)) -->
410 { identifier(Code) },
411 !,
412 latex(cmd(const(Code))).
413latex(code(Code)) -->
414 ( {fragile}
415 -> latex(cmd(const(Code)))
416 ; [ verb(Code) ]
417 ).
418latex(b(Code)) -->
419 latex(cmd(textbf(Code))).
420latex(strong(Code)) -->
421 latex(cmd(textbf(Code))).
422latex(i(Code)) -->
423 latex(cmd(textit(Code))).
424latex(var(Var)) -->
425 latex(cmd(arg(Var))).
426latex(pre(_Class, Code)) -->
427 [ nl_exact(2), code(Code), nl_exact(2) ].
428latex(ul(Content)) -->
429 { if_short_list(Content, shortlist, itemize, Env) },
430 latex(cmd(begin(Env))),
431 latex(Content),
432 latex(cmd(end(Env))).
433latex(ol(Content)) -->
434 latex(cmd(begin(enumerate))),
435 latex(Content),
436 latex(cmd(end(enumerate))).
437latex(li(Content)) -->
438 latex(cmd(item)),
439 latex(Content).
440latex(dl(_, Content)) -->
441 latex(cmd(begin(description))),
442 latex(Content),
443 latex(cmd(end(description))).
444latex(dd(_, Content)) -->
445 latex(Content).
446latex(dd(Content)) -->
447 latex(Content).
448latex(dt(class=term, \term(Text, Term, Bindings))) -->
449 termitem(Text, Term, Bindings).
450latex(dt(Content)) -->
451 latex(cmd(item(opt(Content)))).
452latex(table(Attrs, Content)) -->
453 latex_table(Attrs, Content).
454latex(\Cmd, List, Tail) :-
455 call(Cmd, List, Tail).
456
458latex(latex(Text)) -->
459 [ latex(Text) ].
460latex(cmd(Term)) -->
461 { Term =.. [Cmd|Args] },
462 indent(Cmd),
463 [ cmd(Cmd) ],
464 latex_arguments(Args),
465 outdent(Cmd).
466
467indent(begin) --> !, [ nl(2) ].
468indent(end) --> !, [ nl_exact(1) ].
469indent(section) --> !, [ nl(2) ].
470indent(subsection) --> !, [ nl(2) ].
471indent(subsubsection) --> !, [ nl(2) ].
472indent(item) --> !, [ nl(1), indent(4) ].
473indent(definition) --> !, [ nl(1), indent(4) ].
474indent(tag) --> !, [ nl(1), indent(4) ].
475indent(termitem) --> !, [ nl(1), indent(4) ].
476indent(prefixtermitem) --> !, [ nl(1), indent(4) ].
477indent(infixtermitem) --> !, [ nl(1), indent(4) ].
478indent(postfixtermitem) --> !, [ nl(1), indent(4) ].
479indent(predicate) --> !, [ nl(1), indent(4) ].
480indent(dcg) --> !, [ nl(1), indent(4) ].
481indent(infixop) --> !, [ nl(1), indent(4) ].
482indent(prefixop) --> !, [ nl(1), indent(4) ].
483indent(postfixop) --> !, [ nl(1), indent(4) ].
484indent(predicatesummary) --> !,[ nl(1) ].
485indent(dcgsummary) --> !, [ nl(1) ].
486indent(oppredsummary) --> !, [ nl(1) ].
487indent(hline) --> !, [ nl(1) ].
488indent(_) --> [].
489
490outdent(begin) --> !, [ nl_exact(1) ].
491outdent(end) --> !, [ nl(2) ].
492outdent(item) --> !, [ ' ' ].
493outdent(tag) --> !, [ nl(1) ].
494outdent(termitem) --> !, [ nl(1) ].
495outdent(prefixtermitem) --> !, [ nl(1) ].
496outdent(infixtermitem) --> !, [ nl(1) ].
497outdent(postfixtermitem) --> !, [ nl(1) ].
498outdent(definition) --> !, [ nl(1) ].
499outdent(section) --> !, [ nl(2) ].
500outdent(subsection) --> !, [ nl(2) ].
501outdent(subsubsection) --> !, [ nl(2) ].
502outdent(predicate) --> !, [ nl(1) ].
503outdent(dcg) --> !, [ nl(1) ].
504outdent(infixop) --> !, [ nl(1) ].
505outdent(prefixop) --> !, [ nl(1) ].
506outdent(postfixop) --> !, [ nl(1) ].
507outdent(predicatesummary) --> !,[ nl(1) ].
508outdent(dcgsummary) --> !, [ nl(1) ].
509outdent(oppredsummary) --> !, [ nl(1) ].
510outdent(hline) --> !, [ nl(1) ].
511outdent(_) --> [].
512
516
517latex_special(In, Rest) -->
518 { url_chars(In, Chars, Rest),
519 special(Chars),
520 atom_chars(Atom, Chars),
521 urldef_name(Atom, Name)
522 },
523 !,
524 latex([cmd(Name), latex('{}')]).
525
526special(Chars) :-
527 memberchk(\, Chars),
528 !.
529special(Chars) :-
530 length(Chars, Len),
531 Len > 1.
532
533url_chars([H|T0], [H|T], Rest) :-
534 urlchar(H),
535 !,
536 url_chars(T0, T, Rest).
537url_chars(L, [], L).
538
539
550
551latex_arguments(List, Out, Tail) :-
552 asserta(fragile, Ref),
553 call_cleanup(fragile_list(List, Out, Tail),
554 erase(Ref)).
555
556fragile_list([]) --> [].
557fragile_list([opt([])|T]) -->
558 !,
559 fragile_list(T).
560fragile_list([opt(H)|T]) -->
561 !,
562 [ '[' ],
563 latex_arg(H),
564 [ ']' ],
565 fragile_list(T).
566fragile_list([H|T]) -->
567 [ curl(open) ],
568 latex_arg(H),
569 [ curl(close) ],
570 fragile_list(T).
571
576
577latex_arg(H) -->
578 { atomic(H),
579 atom_string(Atom, H),
580 urldef_name(Atom, Name)
581 },
582 !,
583 latex(cmd(Name)).
584latex_arg(H) -->
585 { maplist(atom, H),
586 atomic_list_concat(H, Atom),
587 urldef_name(Atom, Name)
588 },
589 !,
590 latex(cmd(Name)).
591latex_arg(no_escape(Text)) -->
592 !,
593 [no_escape(Text)].
594latex_arg(H) -->
595 latex(H).
596
597attribute(Att, Attrs) :-
598 is_list(Attrs),
599 !,
600 option(Att, Attrs).
601attribute(Att, One) :-
602 option(Att, [One]).
603
604if_short_list(Content, If, Else, Env) :-
605 ( short_list(Content)
606 -> Env = If
607 ; Env = Else
608 ).
609
614
615short_list([]).
616short_list([_,dd(Content)|T]) :-
617 !,
618 short_content(Content),
619 short_list(T).
620short_list([_,dd(_, Content)|T]) :-
621 !,
622 short_content(Content),
623 short_list(T).
624short_list([li(Content)|T]) :-
625 short_content(Content),
626 short_list(T).
627
628short_content(Content) :-
629 phrase(latex(Content), Tokens),
630 summed_string_len(Tokens, 0, Len),
631 Len < 50.
632
633summed_string_len([], Len, Len).
634summed_string_len([H|T], L0, L) :-
635 atomic(H),
636 !,
637 atom_length(H, AL),
638 L1 is L0 + AL,
639 summed_string_len(T, L1, L).
640summed_string_len([_|T], L0, L) :-
641 summed_string_len(T, L0, L).
642
643
651
652latex_section(Level, Attrs, Content) -->
653 { current_options(Options),
654 option(section_level(LaTexSection), Options, section),
655 latex_section_level(LaTexSection, BaseLevel),
656 FinalLevel is BaseLevel+Level,
657 ( latex_section_level(SectionCommand, FinalLevel)
658 -> Term =.. [SectionCommand, Content]
659 ; domain_error(latex_section_level, FinalLevel)
660 )
661 },
662 latex(cmd(Term)),
663 section_label(Attrs).
664
665section_label(Attrs) -->
666 { is_list(Attrs),
667 memberchk(id(Name), Attrs),
668 !,
669 delete_unsafe_label_chars(Name, SafeName),
670 atom_concat('sec:', SafeName, Label)
671 },
672 latex(cmd(label(Label))).
673section_label(_) -->
674 [].
675
676latex_section_level(chapter, 0).
677latex_section_level(section, 1).
678latex_section_level(subsection, 2).
679latex_section_level(subsubsection, 3).
680latex_section_level(paragraph, 4).
681
682deepen_section_level(Level0, Level1) :-
683 latex_section_level(Level0, N),
684 N1 is N + 1,
685 latex_section_level(Level1, N1).
686
692
693delete_unsafe_label_chars(LabelIn, LabelOut) :-
694 atom_chars(LabelIn, Chars),
695 delete(Chars, '_', CharsOut),
696 atom_chars(LabelOut, CharsOut).
697
698
699 702
706
707include(PI, predicate, _) -->
708 !,
709 ( { options(Options)
710 -> true
711 ; Options = []
712 },
713 latex_tokens_for_predicates(PI, Options)
714 -> []
715 ; latex(cmd(item(['[[', \predref(PI), ']]'])))
716 ).
717include(File, Type, Options) -->
718 { existing_linked_file(File, Path) },
719 !,
720 include_file(Path, Type, Options).
721include(File, _, _) -->
722 latex(code(['[[', File, ']]'])).
723
724include_file(Path, image, Options) -->
725 { option(caption(Caption), Options) },
726 !,
727 latex(cmd(begin(figure, [no_escape(htbp)]))),
728 latex(cmd(begin(center))),
729 latex(cmd(includegraphics(Path))),
730 latex(cmd(end(center))),
731 latex(cmd(caption(Caption))),
732 latex(cmd(end(figure))).
733include_file(Path, image, _) -->
734 !,
735 latex(cmd(includegraphics(Path))).
736include_file(Path, Type, _) -->
737 { assertion(memberchk(Type, [prolog,wiki])),
738 current_options(Options0),
739 select_option(stand_alone(_), Options0, Options1, _),
740 select_option(section_level(Level0), Options1, Options2, section),
741 deepen_section_level(Level0, Level),
742 Options = [stand_alone(false), section_level(Level)|Options2]
743 },
744 ( {Type == prolog}
745 -> latex_tokens_for_file(Path, Options)
746 ; latex_tokens_for_wiki_file(Path, Options)
747 ).
748
753
754file(File, _Options) -->
755 { fragile },
756 !,
757 latex(cmd(texttt(File))).
758file(File, _Options) -->
759 latex(cmd(file(File))).
760
765
766predref(Module:Name/Arity) -->
767 !,
768 latex(cmd(qpredref(Module, Name, Arity))).
769predref(Module:Name//Arity) -->
770 latex(cmd(qdcgref(Module, Name, Arity))).
771predref(Name/Arity) -->
772 latex(cmd(predref(Name, Arity))).
773predref(Name//Arity) -->
774 latex(cmd(dcgref(Name, Arity))).
775
779
780nopredref(Name/Arity) -->
781 latex(cmd(nopredref(Name, Arity))).
782
786
787flagref(Flag) -->
788 latex(cmd(prologflag(Flag))).
789
793
794cite(Citations) -->
795 { atomic_list_concat(Citations, ',', Atom) },
796 latex(cmd(cite(Atom))).
797
802
803tags([\args(Params)|Rest]) -->
804 !,
805 args(Params),
806 tags_list(Rest).
807tags(List) -->
808 tags_list(List).
809
810tags_list([]) -->
811 [].
812tags_list(List) -->
813 [ nl(2) ],
814 latex(cmd(begin(tags))),
815 latex(List),
816 latex(cmd(end(tags))),
817 [ nl(2) ].
818
822
823tag(Tag, [One]) -->
824 !,
825 { doc_tag_title(Tag, Title) },
826 latex([ cmd(tag(Title))
827 | One
828 ]).
829tag(Tag, More) -->
830 { doc_tag_title(Tag, Title) },
831 latex([ cmd(mtag(Title)),
832 \tag_value_list(More)
833 ]).
834
835tag_value_list([H|T]) -->
836 latex(['- '|H]),
837 ( { T \== [] }
838 -> [latex(' \\\\')],
839 tag_value_list(T)
840 ; []
841 ).
842
847
848args(Params) -->
849 latex([ cmd(begin(arguments)),
850 \arg_list(Params),
851 cmd(end(arguments))
852 ]).
853
854arg_list([]) -->
855 [].
856arg_list([H|T]) -->
857 argument(H),
858 arg_list(T).
859
860argument(arg(Name,Descr)) -->
861 [ nl(1) ],
862 latex(cmd(arg(Name))), [ latex(' & ') ],
863 latex(Descr), [latex(' \\\\')].
864
868
(File, Options) -->
870 { memberchk(file(Title, Comment), Options),
871 !,
872 file_synopsis(File, Synopsis)
873 },
874 file_title([Synopsis, ': ', Title], File, Options),
875 { is_structured_comment(Comment, Prefixes),
876 string_codes(Comment, Codes),
877 indented_lines(Codes, Prefixes, Lines),
878 section_comment_header(Lines, _Header, Lines1),
879 wiki_lines_to_dom(Lines1, [], DOM0),
880 tags_to_front(DOM0, DOM)
881 },
882 latex(DOM),
883 latex(cmd(vspace('0.7cm'))).
884file_header(File, Options) -->
885 { file_synopsis(File, Synopsis)
886 },
887 file_title([Synopsis], File, Options).
888
889tags_to_front(DOM0, DOM) :-
890 append(Content, [\tags(Tags)], DOM0),
891 !,
892 DOM = [\tags(Tags)|Content].
893tags_to_front(DOM, DOM).
894
895file_synopsis(File, Synopsis) :-
896 file_name_on_path(File, Term),
897 unquote_filespec(Term, Unquoted),
898 format(atom(Synopsis), '~w', [Unquoted]).
899
900
904
905file_title(Title, File, Options) -->
906 { option(section_level(Level), Options, section),
907 Section =.. [Level,Title],
908 file_base_name(File, BaseExt),
909 file_name_extension(Base, _, BaseExt),
910 delete_unsafe_label_chars(Base, SafeBase),
911 atom_concat('sec:', SafeBase, Label)
912 },
913 latex(cmd(Section)),
914 latex(cmd(label(Label))).
915
916
920
921objects(Objects, Options) -->
922 objects(Objects, [body], Options).
923
924objects([], Mode, _) -->
925 pop_mode(body, Mode, _).
926objects([Obj|T], Mode, Options) -->
927 object(Obj, Mode, Mode1, Options),
928 objects(T, Mode1, Options).
929
930object(doc(Obj,Pos,Comment), Mode0, Mode, Options) -->
931 !,
932 object(Obj, Pos, Comment, Mode0, Mode, Options).
933object(Obj, Mode0, Mode, Options) -->
934 { doc_comment(Obj, Pos, _Summary, Comment)
935 },
936 !,
937 object(Obj, Pos, Comment, Mode0, Mode, Options).
938
939object(Obj, Pos, Comment, Mode0, Mode, Options) -->
940 { is_pi(Obj),
941 !,
942 is_structured_comment(Comment, Prefixes),
943 string_codes(Comment, Codes),
944 indented_lines(Codes, Prefixes, Lines),
945 strip_module(user:Obj, Module, _),
946 process_modes(Lines, Module, Pos, Modes, Args, Lines1),
947 ( private(Obj, Options)
948 -> Class = privdef 949 ; multifile(Obj, Options)
950 -> Class = multidef
951 ; Class = pubdef 952 ),
953 ( Obj = Module:_
954 -> POptions = [module(Module)|Options]
955 ; POptions = Options
956 ),
957 DOM = [\pred_dt(Modes, Class, POptions), dd(class=defbody, DOM1)],
958 wiki_lines_to_dom(Lines1, Args, DOM0),
959 strip_leading_par(DOM0, DOM1),
960 assert_documented(Obj)
961 },
962 need_mode(description, Mode0, Mode),
963 latex(DOM).
964object([Obj|Same], Pos, Comment, Mode0, Mode, Options) -->
965 !,
966 object(Obj, Pos, Comment, Mode0, Mode, Options),
967 { maplist(assert_documented, Same) }.
968object(Obj, _Pos, _Comment, Mode, Mode, _Options) -->
969 { debug(pldoc, 'Skipped ~p', [Obj]) },
970 [].
971
972assert_documented(Obj) :-
973 assert(documented(Obj)).
974
975
982
983need_mode(Mode, Stack, Stack) -->
984 { Stack = [Mode|_] },
985 !,
986 [].
987need_mode(Mode, Stack, Rest) -->
988 { memberchk(Mode, Stack)
989 },
990 !,
991 pop_mode(Mode, Stack, Rest).
992need_mode(Mode, Stack, [Mode|Stack]) -->
993 !,
994 latex(cmd(begin(Mode))).
995
996pop_mode(Mode, Stack, Stack) -->
997 { Stack = [Mode|_] },
998 !,
999 [].
1000pop_mode(Mode, [H|Rest0], Rest) -->
1001 latex(cmd(end(H))),
1002 pop_mode(Mode, Rest0, Rest).
1003
1004
1013
1014pred_dt(Modes, Class, Options) -->
1015 [nl(2)],
1016 pred_dt(Modes, [], _Done, [class(Class)|Options]).
1017
1018pred_dt([], Done, Done, _) -->
1019 [].
1020pred_dt([H|T], Done0, Done, Options) -->
1021 pred_mode(H, Done0, Done1, Options),
1022 ( {T == []}
1023 -> []
1024 ; latex(cmd(nodescription)),
1025 pred_dt(T, Done1, Done, Options)
1026 ).
1027
1028pred_mode(mode(Head,Vars), Done0, Done, Options) -->
1029 !,
1030 { bind_vars(Head, Vars) },
1031 pred_mode(Head, Done0, Done, Options).
1032pred_mode(Head is Det, Done0, Done, Options) -->
1033 !,
1034 anchored_pred_head(Head, Done0, Done, [det(Det)|Options]).
1035pred_mode(Head, Done0, Done, Options) -->
1036 anchored_pred_head(Head, Done0, Done, Options).
1037
1038bind_vars(Term, Bindings) :-
1039 bind_vars(Bindings),
1040 anon_vars(Term).
1041
1042bind_vars([]).
1043bind_vars([Name=Var|T]) :-
1044 Var = '$VAR'(Name),
1045 bind_vars(T).
1046
1051
1052anon_vars(Var) :-
1053 var(Var),
1054 !,
1055 Var = '$VAR'('_').
1056anon_vars(Term) :-
1057 compound(Term),
1058 !,
1059 Term =.. [_|Args],
1060 maplist(anon_vars, Args).
1061anon_vars(_).
1062
1063
1064anchored_pred_head(Head, Done0, Done, Options) -->
1065 { pred_anchor_name(Head, PI, _Name) },
1066 ( { memberchk(PI, Done0) }
1067 -> { Done = Done0 }
1068 ; { Done = [PI|Done0] }
1069 ),
1070 pred_head(Head, Options).
1071
1072
1079
1080pred_head(//(Head), Options) -->
1081 !,
1082 { pred_attributes(Options, Atts),
1083 Head =.. [Functor|Args],
1084 length(Args, Arity)
1085 },
1086 latex(cmd(dcg(opt(Atts), Functor, Arity, \pred_args(Args, 1)))).
1087pred_head(Head, _Options) --> 1088 { Head =.. [Functor,Left,Right],
1089 Functor \== (:),
1090 is_op_type(Functor, infix), !
1091 },
1092 latex(cmd(infixop(Functor, \pred_arg(Left, 1), \pred_arg(Right, 2)))).
1093pred_head(Head, _Options) --> 1094 { Head =.. [Functor,Arg],
1095 is_op_type(Functor, prefix), !
1096 },
1097 latex(cmd(prefixop(Functor, \pred_arg(Arg, 1)))).
1098pred_head(Head, _Options) --> 1099 { Head =.. [Functor,Arg],
1100 is_op_type(Functor, postfix), !
1101 },
1102 latex(cmd(postfixop(Functor, \pred_arg(Arg, 1)))).
1103pred_head(M:Head, Options) --> 1104 !,
1105 { pred_attributes(Options, Atts),
1106 Head =.. [Functor|Args],
1107 length(Args, Arity)
1108 },
1109 latex(cmd(qpredicate(opt(Atts),
1110 M,
1111 Functor, Arity, \pred_args(Args, 1)))).
1112pred_head(Head, Options) --> 1113 { pred_attributes(Options, Atts),
1114 Head =.. [Functor|Args],
1115 length(Args, Arity)
1116 },
1117 latex(cmd(predicate(opt(Atts),
1118 Functor, Arity, \pred_args(Args, 1)))).
1119
1124
1125pred_attributes(Options, Attrs) :-
1126 findall(A, pred_att(Options, A), As),
1127 insert_comma(As, Attrs).
1128
1129pred_att(Options, Det) :-
1130 option(det(Det), Options).
1131pred_att(Options, private) :-
1132 option(class(privdef), Options).
1133pred_att(Options, multifile) :-
1134 option(class(multidef), Options).
1135
1136insert_comma([H1,H2|T0], [H1, ','|T]) :-
1137 !,
1138 insert_comma([H2|T0], T).
1139insert_comma(L, L).
1140
1141
1142:- if(current_predicate(is_dict/1)). 1143dict_kv_pairs([]) --> [].
1144dict_kv_pairs([H|T]) -->
1145 dict_kv(H),
1146 ( { T == [] }
1147 -> []
1148 ; latex(', '),
1149 dict_kv_pairs(T)
1150 ).
1151
1152dict_kv(Key-Value) -->
1153 latex(cmd(key(Key))),
1154 latex(':'),
1155 term(Value).
1156:- endif. 1157
1158pred_args([], _) -->
1159 [].
1160pred_args([H|T], I) -->
1161 pred_arg(H, I),
1162 ( {T==[]}
1163 -> []
1164 ; latex(', '),
1165 { I2 is I + 1 },
1166 pred_args(T, I2)
1167 ).
1168
1169pred_arg(Var, I) -->
1170 { var(Var) },
1171 !,
1172 latex(['Arg', I]).
1173pred_arg(...(Term), I) -->
1174 !,
1175 pred_arg(Term, I),
1176 latex(cmd(ldots)).
1177pred_arg(Term, I) -->
1178 { Term =.. [Ind,Arg],
1179 mode_indicator(Ind)
1180 },
1181 !,
1182 latex([Ind, \pred_arg(Arg, I)]).
1183pred_arg(Arg:Type, _) -->
1184 !,
1185 latex([\argname(Arg), :, \argtype(Type)]).
1186pred_arg(Arg, _) -->
1187 { atom(Arg) },
1188 !,
1189 argname(Arg).
1190pred_arg(Arg, _) -->
1191 argtype(Arg). 1192
1193argname('$VAR'(Name)) -->
1194 !,
1195 latex(Name).
1196argname(Name) -->
1197 !,
1198 latex(Name).
1199
1200argtype(Term) -->
1201 { format(string(S), '~W',
1202 [ Term,
1203 [ quoted(true),
1204 numbervars(true)
1205 ]
1206 ]) },
1207 latex(S).
1208
1214
1215term(_, Term, Bindings) -->
1216 { bind_vars(Bindings) },
1217 term(Term).
1218
1219term('$VAR'(Name)) -->
1220 !,
1221 latex(cmd(arg(Name))).
1222term(Compound) -->
1223 { callable(Compound),
1224 !,
1225 Compound =.. [Functor|Args]
1226 },
1227 !,
1228 term_with_args(Functor, Args).
1229term(Rest) -->
1230 latex(Rest).
1231
1232term_with_args(Functor, [Left, Right]) -->
1233 { is_op_type(Functor, infix) },
1234 !,
1235 latex(cmd(infixterm(Functor, \term(Left), \term(Right)))).
1236term_with_args(Functor, [Arg]) -->
1237 { is_op_type(Functor, prefix) },
1238 !,
1239 latex(cmd(prefixterm(Functor, \term(Arg)))).
1240term_with_args(Functor, [Arg]) -->
1241 { is_op_type(Functor, postfix) },
1242 !,
1243 latex(cmd(postfixterm(Functor, \term(Arg)))).
1244term_with_args(Functor, Args) -->
1245 latex(cmd(term(Functor, \pred_args(Args, 1)))).
1246
1247
1251
1252termitem(_Text, Term, Bindings) -->
1253 { bind_vars(Bindings) },
1254 termitem(Term).
1255
1256termitem('$VAR'(Name)) -->
1257 !,
1258 latex(cmd(termitem(var(Name), ''))).
1259:- if(current_predicate(is_dict/1)). 1260termitem(Dict) -->
1261 { is_dict(Dict),
1262 !,
1263 dict_pairs(Dict, Tag, Pairs)
1264 },
1265 latex(cmd(dictitem(Tag, \dict_kv_pairs(Pairs)))).
1266:- endif. 1267termitem(Compound) -->
1268 { callable(Compound),
1269 !,
1270 Compound =.. [Functor|Args]
1271 },
1272 !,
1273 termitem_with_args(Functor, Args).
1274termitem(Rest) -->
1275 latex(cmd(termitem(Rest, ''))).
1276
1277termitem_with_args(Functor, [Left, Right]) -->
1278 { is_op_type(Functor, infix) },
1279 !,
1280 latex(cmd(infixtermitem(Functor, \term(Left), \term(Right)))).
1281termitem_with_args(Functor, [Arg]) -->
1282 { is_op_type(Functor, prefix) },
1283 !,
1284 latex(cmd(prefixtermitem(Functor, \term(Arg)))).
1285termitem_with_args(Functor, [Arg]) -->
1286 { is_op_type(Functor, postfix) },
1287 !,
1288 latex(cmd(postfixtermitem(Functor, \term(Arg)))).
1289termitem_with_args({}, [Arg]) -->
1290 !,
1291 latex(cmd(curltermitem(\argtype(Arg)))).
1292termitem_with_args(Functor, Args) -->
1293 latex(cmd(termitem(Functor, \pred_args(Args, 1)))).
1294
1295
1299
1300latex_table(_Attrs, Content) -->
1301 { max_columns(Content, 0, _, -, Wittness),
1302 col_align(Wittness, 1, Content, Align),
1303 atomics_to_string(Align, '|', S0),
1304 atomic_list_concat(['|',S0,'|'], Format)
1305 },
1307 latex(cmd(begin(quote))),
1308 latex(cmd(begin(tabulary,
1309 no_escape('0.9\\textwidth'),
1310 no_escape(Format)))),
1311 latex(cmd(hline)),
1312 rows(Content),
1313 latex(cmd(hline)),
1314 latex(cmd(end(tabulary))),
1315 latex(cmd(end(quote))).
1317
1318max_columns([], C, C, W, W).
1319max_columns([tr(List)|T], C0, C, _, W) :-
1320 length(List, C1),
1321 C1 >= C0, 1322 !,
1323 max_columns(T, C1, C, List, W).
1324max_columns([_|T], C0, C, W0, W) :-
1325 max_columns(T, C0, C, W0, W).
1326
1327col_align([], _, _, []).
1328col_align([CH|CT], Col, Rows, [AH|AT]) :-
1329 ( member(tr(Cells), Rows),
1330 nth1(Col, Cells, Cell),
1331 auto_par(Cell)
1332 -> Wrap = auto
1333 ; Wrap = false
1334 ),
1335 col_align(CH, Wrap, AH),
1336 Col1 is Col+1,
1337 col_align(CT, Col1, Rows, AT).
1338
1339col_align(td(class=Class,_), Wrap, Align) :-
1340 align_class(Class, Wrap, Align),
1341 !.
1342col_align(_, auto, 'L') :- !.
1343col_align(_, false, 'l').
1344
1345align_class(left, auto, 'L').
1346align_class(center, auto, 'C').
1347align_class(right, auto, 'R').
1348align_class(left, false, 'l').
1349align_class(center, false, 'c').
1350align_class(right, false, 'r').
1351
1352rows([]) -->
1353 [].
1354rows([tr(Content)|T]) -->
1355 row(Content),
1356 rows(T).
1357
1358row([]) -->
1359 [ latex(' \\\\'), nl(1) ].
1360row([td(_Attrs, Content)|T]) -->
1361 !,
1362 row([td(Content)|T]).
1363row([td(Content)|T]) -->
1364 latex(Content),
1365 ( {T == []}
1366 -> []
1367 ; [ latex(' & ') ]
1368 ),
1369 row(T).
1370row([th(Content)|T]) -->
1371 latex(cmd(textbf(Content))),
1372 ( {T == []}
1373 -> []
1374 ; [ latex(' & ') ]
1375 ),
1376 row(T).
1377
1381
1382auto_par(Content) :-
1383 phrase(html_text(Content), Words),
1384 length(Words, WC),
1385 WC > 1,
1386 atomics_to_string(Words, Text),
1387 string_length(Text, Width),
1388 Width > 15.
1389
1390html_text([]) -->
1391 !.
1392html_text([H|T]) -->
1393 !,
1394 html_text(H),
1395 html_text(T).
1396html_text(\predref(Name/Arity)) -->
1397 !,
1398 { format(string(S), '~q/~q', [Name, Arity]) },
1399 [S].
1400html_text(Compound) -->
1401 { compound(Compound),
1402 !,
1403 functor(Compound, _Name, Arity),
1404 arg(Arity, Compound, Content)
1405 },
1406 html_text(Content).
1407html_text(Word) -->
1408 [Word].
1409
1410
1411
1412
1413 1416
1421
1422latex_summary(Options) :-
1423 option(summary(File), Options),
1424 !,
1425 findall(Obj, summary_obj(Obj), Objs),
1426 maplist(pi_sort_key, Objs, Keyed),
1427 keysort(Keyed, KSorted),
1428 pairs_values(KSorted, SortedObj),
1429 phrase(summarylist(SortedObj, Options), Tokens),
1430 open(File, write, Out),
1431 call_cleanup(print_latex(Out, Tokens, Options),
1432 close(Out)).
1433latex_summary(_) :-
1434 retractall(documented(_)).
1435
1436summary_obj(Obj) :-
1437 documented(Obj),
1438 pi_head(Obj, Head),
1439 \+ xref_hook(Head).
1440
1441pi_head(M:PI, M:Head) :-
1442 !,
1443 pi_head(PI, Head).
1444pi_head(Name/Arity, Head) :-
1445 functor(Head, Name, Arity).
1446pi_head(Name//DCGArity, Head) :-
1447 Arity is DCGArity+2,
1448 functor(Head, Name, Arity).
1449
1450
1451pi_sort_key(M:PI, PI-(M:PI)) :- !.
1452pi_sort_key(PI, PI-PI).
1453
1454object_name_arity(_:Term, Type, Name, Arity) :-
1455 nonvar(Term),
1456 !,
1457 object_name_arity(Term, Type, Name, Arity).
1458object_name_arity(Name/Arity, pred, Name, Arity).
1459object_name_arity(Name//Arity, dcg, Name, Arity).
1460
1461summarylist(Objs, Options) -->
1462 latex(cmd(begin(summarylist, ll))),
1463 summary(Objs, Options),
1464 latex(cmd(end(summarylist))).
1465
1466summary([], _) -->
1467 [].
1468summary([H|T], Options) -->
1469 summary_line(H, Options),
1470 summary(T, Options).
1471
1472summary_line(Obj, _Options) -->
1473 { doc_comment(Obj, _Pos, Summary, _Comment),
1474 !,
1475 atom_codes(Summary, Codes),
1476 phrase(pldoc_wiki:line_tokens(Tokens), Codes), 1477 object_name_arity(Obj, Type, Name, Arity)
1478 },
1479 ( {Type == dcg}
1480 -> latex(cmd(dcgsummary(Name, Arity, Tokens)))
1481 ; { strip_module(Obj, M, _),
1482 current_op(Pri, Ass, M:Name)
1483 }
1484 -> latex(cmd(oppredsummary(Name, Arity, Ass, Pri, Tokens)))
1485 ; latex(cmd(predicatesummary(Name, Arity, Tokens)))
1486 ).
1487summary_line(Obj, _Options) -->
1488 { print_message(warning, pldoc(no_summary_for(Obj)))
1489 }.
1490
1491 1494
1495print_latex(Out, Tokens, Options) :-
1496 latex_header(Out, Options),
1497 print_latex_tokens(Tokens, Out),
1498 latex_footer(Out, Options).
1499
1500
1504
1505print_latex_tokens([], _).
1506print_latex_tokens([nl(N)|T0], Out) :-
1507 !,
1508 max_nl(T0, T, N, NL),
1509 nl(Out, NL),
1510 print_latex_tokens(T, Out).
1511print_latex_tokens([nl_exact(N)|T0], Out) :-
1512 !,
1513 nl_exact(T0, T,N, NL),
1514 nl(Out, NL),
1515 print_latex_tokens(T, Out).
1516print_latex_tokens([H|T], Out) :-
1517 print_latex_token(H, Out),
1518 print_latex_tokens(T, Out).
1519
1520print_latex_token(cmd(Cmd), Out) :-
1521 !,
1522 format(Out, '\\~w', [Cmd]).
1523print_latex_token(curl(open), Out) :-
1524 !,
1525 format(Out, '{', []).
1526print_latex_token(curl(close), Out) :-
1527 !,
1528 format(Out, '}', []).
1529print_latex_token(indent(N), Out) :-
1530 !,
1531 format(Out, '~t~*|', [N]).
1532print_latex_token(nl(N), Out) :-
1533 !,
1534 format(Out, '~N', []),
1535 forall(between(2,N,_), nl(Out)).
1536print_latex_token(verb(Verb), Out) :-
1537 is_list(Verb), Verb \== [],
1538 !,
1539 atomic_list_concat(Verb, Atom),
1540 print_latex_token(verb(Atom), Out).
1541print_latex_token(verb(Verb), Out) :-
1542 !,
1543 ( member(C, [$,'|',@,=,'"',^,!]),
1544 \+ sub_atom(Verb, _, _, _, C)
1545 -> atom_replace_char(Verb, '\n', ' ', Verb2),
1546 format(Out, '\\verb~w~w~w', [C,Verb2,C])
1547 ; assertion(fail)
1548 ).
1549print_latex_token(code(Code), Out) :-
1550 !,
1551 format(Out, '~N\\begin{code}~n', []),
1552 format(Out, '~w', [Code]),
1553 format(Out, '~N\\end{code}', []).
1554print_latex_token(latex(Code), Out) :-
1555 !,
1556 write(Out, Code).
1557print_latex_token(w(Word), Out) :-
1558 !,
1559 print_latex(Out, Word).
1560print_latex_token(no_escape(Text), Out) :-
1561 !,
1562 write(Out, Text).
1563print_latex_token(Rest, Out) :-
1564 ( atomic(Rest)
1565 -> print_latex(Out, Rest)
1566 ; 1567 write(Out, Rest)
1568 ).
1569
1570atom_replace_char(In, From, To, Out) :-
1571 sub_atom(In, _, _, _, From),
1572 !,
1573 atom_chars(In, CharsIn),
1574 replace(CharsIn, From, To, CharsOut),
1575 atom_chars(Out, CharsOut).
1576atom_replace_char(In, _, _, In).
1577
1578replace([], _, _, []).
1579replace([H|T0], H, N, [N|T]) :-
1580 !,
1581 replace(T0, H, N, T).
1582replace([H|T0], F, N, [H|T]) :-
1583 replace(T0, F, N, T).
1584
1585
1589
1590print_latex(Out, String) :-
1591 atom_string(Atom, String),
1592 atom_chars(Atom, Chars),
1593 print_chars(Chars, Out).
1594
1595print_chars([], _).
1596print_chars([H|T], Out) :-
1597 print_char(H, Out),
1598 print_chars(T, Out).
1599
1600
1604
1605max_nl([nl(M1)|T0], T, M0, M) :-
1606 !,
1607 M2 is max(M1, M0),
1608 max_nl(T0, T, M2, M).
1609max_nl([nl_exact(M1)|T0], T, _, M) :-
1610 !,
1611 nl_exact(T0, T, M1, M).
1612max_nl(T, T, M, M).
1613
1614nl_exact([nl(_)|T0], T, M0, M) :-
1615 !,
1616 max_nl(T0, T, M0, M).
1617nl_exact([nl_exact(M1)|T0], T, M0, M) :-
1618 !,
1619 M2 is max(M1, M0),
1620 max_nl(T0, T, M2, M).
1621nl_exact(T, T, M, M).
1622
1623
1624nl(Out, N) :-
1625 forall(between(1, N, _), nl(Out)).
1626
1627
1628print_char('<', Out) :- !, write(Out, '$<$').
1629print_char('>', Out) :- !, write(Out, '$>$').
1630print_char('{', Out) :- !, write(Out, '\\{').
1631print_char('}', Out) :- !, write(Out, '\\}').
1632print_char('$', Out) :- !, write(Out, '\\$').
1633print_char('&', Out) :- !, write(Out, '\\&').
1634print_char('#', Out) :- !, write(Out, '\\#').
1635print_char('%', Out) :- !, write(Out, '\\%').
1636print_char('~', Out) :- !, write(Out, '\\Stilde{}').
1637print_char('\\',Out) :- !, write(Out, '\\bsl{}').
1638print_char('^', Out) :- !, write(Out, '\\Shat{}').
1639print_char('|', Out) :- !, write(Out, '\\Sbar{}').
1640print_char(C, Out) :- put_char(Out, C).
1641
1642
1646
1647identifier(Atom) :-
1648 atom_chars(Atom, [C0|Chars]),
1649 char_type(C0, lower),
1650 all_chartype(Chars, alnum).
1651
1652all_chartype([], _).
1653all_chartype([H|T], Type) :-
1654 char_type(H, Type),
1655 all_chartype(T, Type).
1656
1657
1658 1661
1669
1670:- dynamic
1671 urldef_name/2,
1672 urlchar/1, 1673 urldefs_loaded/1. 1674
1680
1681load_urldefs :-
1682 urldefs_loaded(_),
1683 !.
1684load_urldefs :-
1685 absolute_file_name(library('pldoc/pldoc.sty'), File,
1686 [ access(read) ]),
1687 load_urldefs(File).
1688
1689load_urldefs(File) :-
1690 urldefs_loaded(File),
1691 !.
1692load_urldefs(File) :-
1693 open(File, read, In),
1694 call_cleanup(( read_line_to_codes(In, L0),
1695 process_urldefs(L0, In)),
1696 close(In)),
1697 assert(urldefs_loaded(File)).
1698
1699process_urldefs(end_of_file, _) :- !.
1700process_urldefs(Line, In) :-
1701 ( phrase(urldef(Name, String), Line)
1702 -> assert(urldef_name(String, Name)),
1703 assert_chars(String)
1704 ; true
1705 ),
1706 read_line_to_codes(In, L2),
1707 process_urldefs(L2, In).
1708
1709assert_chars(String) :-
1710 atom_chars(String, Chars),
1711 ( member(C, Chars),
1712 \+ urlchar(C),
1713 assert(urlchar(C)),
1714 fail
1715 ; true
1716 ).
1717
1718urldef(Name, String) -->
1719 "\\urldef{\\", string(NameS), "}\\satom{", string(StringS), "}",
1720 ws,
1721 ( "%"
1722 -> string(_)
1723 ; []
1724 ),
1725 eol,
1726 !,
1727 { atom_codes(Name, NameS),
1728 atom_codes(String, StringS)
1729 }.
1730
1731ws --> [C], { C =< 32 }, !, ws.
1732ws --> [].
1733
1734string([]) --> [].
1735string([H|T]) --> [H], string(T).
1736
1737eol([],[]).
1738
1739
1740 1743
(Out, Options) :-
1745 ( option(stand_alone(true), Options, true)
1746 -> forall(header(Line), format(Out, '~w~n', [Line]))
1747 ; true
1748 ),
1749 forall(generated(Line), format(Out, '~w~n', [Line])).
1750
(Out, Options) :-
1752 ( option(stand_alone(true), Options, true)
1753 -> forall(footer(Line), format(Out, '~w~n', [Line]))
1754 ; true
1755 ).
1756
('\\documentclass[11pt]{article}').
1758header('\\usepackage{times}').
1759header('\\usepackage{pldoc}').
1760header('\\sloppy').
1761header('\\makeindex').
1762header('').
1763header('\\begin{document}').
1764
('').
1766footer('\\printindex').
1767footer('\\end{document}').
1768
1769generated('% This LaTeX document was generated using the LaTeX backend of PlDoc,').
1770generated('% The SWI-Prolog documentation system').
1771generated('').
1772
1773
1774 1777
1778:- multifile
1779 prolog:message//1. 1780
1781prolog:message(pldoc(no_summary_for(Obj))) -->
1782 [ 'No summary documentation for ~p'-[Obj] ]