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(url_escape(HREF))))
392 ; { atom_concat(#,Sec,HREF) }
393 -> latex([Content, ' (', cmd(secref(Sec)), ')'])
394 ; latex(cmd(href(url_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(url_escape(Text)) -->
595 !,
596 [url_escape(Text)].
597latex_arg(H) -->
598 latex(H).
599
600attribute(Att, Attrs) :-
601 is_list(Attrs),
602 !,
603 option(Att, Attrs).
604attribute(Att, One) :-
605 option(Att, [One]).
606
607if_short_list(Content, If, Else, Env) :-
608 ( short_list(Content)
609 -> Env = If
610 ; Env = Else
611 ).
612
617
618short_list([]).
619short_list([_,dd(Content)|T]) :-
620 !,
621 short_content(Content),
622 short_list(T).
623short_list([_,dd(_, Content)|T]) :-
624 !,
625 short_content(Content),
626 short_list(T).
627short_list([li(Content)|T]) :-
628 short_content(Content),
629 short_list(T).
630
631short_content(Content) :-
632 phrase(latex(Content), Tokens),
633 summed_string_len(Tokens, 0, Len),
634 Len < 50.
635
636summed_string_len([], Len, Len).
637summed_string_len([H|T], L0, L) :-
638 atomic(H),
639 !,
640 atom_length(H, AL),
641 L1 is L0 + AL,
642 summed_string_len(T, L1, L).
643summed_string_len([_|T], L0, L) :-
644 summed_string_len(T, L0, L).
645
646
654
655latex_section(Level, Attrs, Content) -->
656 { current_options(Options),
657 option(section_level(LaTexSection), Options, section),
658 latex_section_level(LaTexSection, BaseLevel),
659 FinalLevel is BaseLevel+Level,
660 ( latex_section_level(SectionCommand, FinalLevel)
661 -> Term =.. [SectionCommand, Content]
662 ; domain_error(latex_section_level, FinalLevel)
663 )
664 },
665 latex(cmd(Term)),
666 section_label(Attrs).
667
668section_label(Attrs) -->
669 { is_list(Attrs),
670 memberchk(id(Name), Attrs),
671 !,
672 delete_unsafe_label_chars(Name, SafeName),
673 atom_concat('sec:', SafeName, Label)
674 },
675 latex(cmd(label(Label))).
676section_label(_) -->
677 [].
678
679latex_section_level(chapter, 0).
680latex_section_level(section, 1).
681latex_section_level(subsection, 2).
682latex_section_level(subsubsection, 3).
683latex_section_level(paragraph, 4).
684
685deepen_section_level(Level0, Level1) :-
686 latex_section_level(Level0, N),
687 N1 is N + 1,
688 latex_section_level(Level1, N1).
689
695
696delete_unsafe_label_chars(LabelIn, LabelOut) :-
697 atom_chars(LabelIn, Chars),
698 delete(Chars, '_', CharsOut),
699 atom_chars(LabelOut, CharsOut).
700
701
702 705
709
710include(PI, predicate, _) -->
711 !,
712 ( { options(Options)
713 -> true
714 ; Options = []
715 },
716 latex_tokens_for_predicates(PI, Options)
717 -> []
718 ; latex(cmd(item(['[[', \predref(PI), ']]'])))
719 ).
720include(File, Type, Options) -->
721 { existing_linked_file(File, Path) },
722 !,
723 include_file(Path, Type, Options).
724include(File, _, _) -->
725 latex(code(['[[', File, ']]'])).
726
727include_file(Path, image, Options) -->
728 { option(caption(Caption), Options) },
729 !,
730 latex(cmd(begin(figure, [no_escape(htbp)]))),
731 latex(cmd(begin(center))),
732 latex(cmd(includegraphics(Path))),
733 latex(cmd(end(center))),
734 latex(cmd(caption(Caption))),
735 latex(cmd(end(figure))).
736include_file(Path, image, _) -->
737 !,
738 latex(cmd(includegraphics(Path))).
739include_file(Path, Type, _) -->
740 { assertion(memberchk(Type, [prolog,wiki])),
741 current_options(Options0),
742 select_option(stand_alone(_), Options0, Options1, _),
743 select_option(section_level(Level0), Options1, Options2, section),
744 deepen_section_level(Level0, Level),
745 Options = [stand_alone(false), section_level(Level)|Options2]
746 },
747 ( {Type == prolog}
748 -> latex_tokens_for_file(Path, Options)
749 ; latex_tokens_for_wiki_file(Path, Options)
750 ).
751
756
757file(File, _Options) -->
758 { fragile },
759 !,
760 latex(cmd(texttt(File))).
761file(File, _Options) -->
762 latex(cmd(file(File))).
763
768
769predref(Module:Name/Arity) -->
770 !,
771 latex(cmd(qpredref(Module, Name, Arity))).
772predref(Module:Name//Arity) -->
773 latex(cmd(qdcgref(Module, Name, Arity))).
774predref(Name/Arity) -->
775 latex(cmd(predref(Name, Arity))).
776predref(Name//Arity) -->
777 latex(cmd(dcgref(Name, Arity))).
778
782
783nopredref(Name/Arity) -->
784 latex(cmd(nopredref(Name, Arity))).
785
789
790flagref(Flag) -->
791 latex(cmd(prologflag(Flag))).
792
796
797cite(Citations) -->
798 { atomic_list_concat(Citations, ',', Atom) },
799 latex(cmd(cite(Atom))).
800
805
806tags([\args(Params)|Rest]) -->
807 !,
808 args(Params),
809 tags_list(Rest).
810tags(List) -->
811 tags_list(List).
812
813tags_list([]) -->
814 [].
815tags_list(List) -->
816 [ nl(2) ],
817 latex(cmd(begin(tags))),
818 latex(List),
819 latex(cmd(end(tags))),
820 [ nl(2) ].
821
825
826tag(Tag, [One]) -->
827 !,
828 { doc_tag_title(Tag, Title) },
829 latex([ cmd(tag(Title))
830 | One
831 ]).
832tag(Tag, More) -->
833 { doc_tag_title(Tag, Title) },
834 latex([ cmd(mtag(Title)),
835 \tag_value_list(More)
836 ]).
837
838tag_value_list([H|T]) -->
839 latex(['- '|H]),
840 ( { T \== [] }
841 -> [latex(' \\\\')],
842 tag_value_list(T)
843 ; []
844 ).
845
850
851args(Params) -->
852 latex([ cmd(begin(arguments)),
853 \arg_list(Params),
854 cmd(end(arguments))
855 ]).
856
857arg_list([]) -->
858 [].
859arg_list([H|T]) -->
860 argument(H),
861 arg_list(T).
862
863argument(arg(Name,Descr)) -->
864 [ nl(1) ],
865 latex(cmd(arg(Name))), [ latex(' & ') ],
866 latex(Descr), [latex(' \\\\')].
867
871
(File, Options) -->
873 { memberchk(file(Title, Comment), Options),
874 !,
875 file_synopsis(File, Synopsis)
876 },
877 file_title([Synopsis, ': ', Title], File, Options),
878 { is_structured_comment(Comment, Prefixes),
879 string_codes(Comment, Codes),
880 indented_lines(Codes, Prefixes, Lines),
881 section_comment_header(Lines, _Header, Lines1),
882 wiki_lines_to_dom(Lines1, [], DOM0),
883 tags_to_front(DOM0, DOM)
884 },
885 latex(DOM),
886 latex(cmd(vspace('0.7cm'))).
887file_header(File, Options) -->
888 { file_synopsis(File, Synopsis)
889 },
890 file_title([Synopsis], File, Options).
891
892tags_to_front(DOM0, DOM) :-
893 append(Content, [\tags(Tags)], DOM0),
894 !,
895 DOM = [\tags(Tags)|Content].
896tags_to_front(DOM, DOM).
897
898file_synopsis(File, Synopsis) :-
899 file_name_on_path(File, Term),
900 unquote_filespec(Term, Unquoted),
901 format(atom(Synopsis), '~w', [Unquoted]).
902
903
907
908file_title(Title, File, Options) -->
909 { option(section_level(Level), Options, section),
910 Section =.. [Level,Title],
911 file_base_name(File, BaseExt),
912 file_name_extension(Base, _, BaseExt),
913 delete_unsafe_label_chars(Base, SafeBase),
914 atom_concat('sec:', SafeBase, Label)
915 },
916 latex(cmd(Section)),
917 latex(cmd(label(Label))).
918
919
923
924objects(Objects, Options) -->
925 objects(Objects, [body], Options).
926
927objects([], Mode, _) -->
928 pop_mode(body, Mode, _).
929objects([Obj|T], Mode, Options) -->
930 object(Obj, Mode, Mode1, Options),
931 objects(T, Mode1, Options).
932
933object(doc(Obj,Pos,Comment), Mode0, Mode, Options) -->
934 !,
935 object(Obj, Pos, Comment, Mode0, Mode, Options).
936object(Obj, Mode0, Mode, Options) -->
937 { doc_comment(Obj, Pos, _Summary, Comment)
938 },
939 !,
940 object(Obj, Pos, Comment, Mode0, Mode, Options).
941
942object(Obj, Pos, Comment, Mode0, Mode, Options) -->
943 { is_pi(Obj),
944 !,
945 is_structured_comment(Comment, Prefixes),
946 string_codes(Comment, Codes),
947 indented_lines(Codes, Prefixes, Lines),
948 strip_module(user:Obj, Module, _),
949 process_modes(Lines, Module, Pos, Modes, Args, Lines1),
950 ( private(Obj, Options)
951 -> Class = privdef 952 ; multifile(Obj, Options)
953 -> Class = multidef
954 ; Class = pubdef 955 ),
956 ( Obj = Module:_
957 -> POptions = [module(Module)|Options]
958 ; POptions = Options
959 ),
960 DOM = [\pred_dt(Modes, Class, POptions), dd(class=defbody, DOM1)],
961 wiki_lines_to_dom(Lines1, Args, DOM0),
962 strip_leading_par(DOM0, DOM1),
963 assert_documented(Obj)
964 },
965 need_mode(description, Mode0, Mode),
966 latex(DOM).
967object([Obj|Same], Pos, Comment, Mode0, Mode, Options) -->
968 !,
969 object(Obj, Pos, Comment, Mode0, Mode, Options),
970 { maplist(assert_documented, Same) }.
971object(Obj, _Pos, _Comment, Mode, Mode, _Options) -->
972 { debug(pldoc, 'Skipped ~p', [Obj]) },
973 [].
974
975assert_documented(Obj) :-
976 assert(documented(Obj)).
977
978
985
986need_mode(Mode, Stack, Stack) -->
987 { Stack = [Mode|_] },
988 !,
989 [].
990need_mode(Mode, Stack, Rest) -->
991 { memberchk(Mode, Stack)
992 },
993 !,
994 pop_mode(Mode, Stack, Rest).
995need_mode(Mode, Stack, [Mode|Stack]) -->
996 !,
997 latex(cmd(begin(Mode))).
998
999pop_mode(Mode, Stack, Stack) -->
1000 { Stack = [Mode|_] },
1001 !,
1002 [].
1003pop_mode(Mode, [H|Rest0], Rest) -->
1004 latex(cmd(end(H))),
1005 pop_mode(Mode, Rest0, Rest).
1006
1007
1016
1017pred_dt(Modes, Class, Options) -->
1018 [nl(2)],
1019 pred_dt(Modes, [], _Done, [class(Class)|Options]).
1020
1021pred_dt([], Done, Done, _) -->
1022 [].
1023pred_dt([H|T], Done0, Done, Options) -->
1024 pred_mode(H, Done0, Done1, Options),
1025 ( {T == []}
1026 -> []
1027 ; latex(cmd(nodescription)),
1028 pred_dt(T, Done1, Done, Options)
1029 ).
1030
1031pred_mode(mode(Head,Vars), Done0, Done, Options) -->
1032 !,
1033 { bind_vars(Head, Vars) },
1034 pred_mode(Head, Done0, Done, Options).
1035pred_mode(Head is Det, Done0, Done, Options) -->
1036 !,
1037 anchored_pred_head(Head, Done0, Done, [det(Det)|Options]).
1038pred_mode(Head, Done0, Done, Options) -->
1039 anchored_pred_head(Head, Done0, Done, Options).
1040
1041bind_vars(Term, Bindings) :-
1042 bind_vars(Bindings),
1043 anon_vars(Term).
1044
1045bind_vars([]).
1046bind_vars([Name=Var|T]) :-
1047 Var = '$VAR'(Name),
1048 bind_vars(T).
1049
1054
1055anon_vars(Var) :-
1056 var(Var),
1057 !,
1058 Var = '$VAR'('_').
1059anon_vars(Term) :-
1060 compound(Term),
1061 !,
1062 Term =.. [_|Args],
1063 maplist(anon_vars, Args).
1064anon_vars(_).
1065
1066
1067anchored_pred_head(Head, Done0, Done, Options) -->
1068 { pred_anchor_name(Head, PI, _Name) },
1069 ( { memberchk(PI, Done0) }
1070 -> { Done = Done0 }
1071 ; { Done = [PI|Done0] }
1072 ),
1073 pred_head(Head, Options).
1074
1075
1082
1083pred_head(//(Head), Options) -->
1084 !,
1085 { pred_attributes(Options, Atts),
1086 Head =.. [Functor|Args],
1087 length(Args, Arity)
1088 },
1089 latex(cmd(dcg(opt(Atts), Functor, Arity, \pred_args(Args, 1)))).
1090pred_head(Head, _Options) --> 1091 { Head =.. [Functor,Left,Right],
1092 Functor \== (:),
1093 is_op_type(Functor, infix), !
1094 },
1095 latex(cmd(infixop(Functor, \pred_arg(Left, 1), \pred_arg(Right, 2)))).
1096pred_head(Head, _Options) --> 1097 { Head =.. [Functor,Arg],
1098 is_op_type(Functor, prefix), !
1099 },
1100 latex(cmd(prefixop(Functor, \pred_arg(Arg, 1)))).
1101pred_head(Head, _Options) --> 1102 { Head =.. [Functor,Arg],
1103 is_op_type(Functor, postfix), !
1104 },
1105 latex(cmd(postfixop(Functor, \pred_arg(Arg, 1)))).
1106pred_head(M:Head, Options) --> 1107 !,
1108 { pred_attributes(Options, Atts),
1109 Head =.. [Functor|Args],
1110 length(Args, Arity)
1111 },
1112 latex(cmd(qpredicate(opt(Atts),
1113 M,
1114 Functor, Arity, \pred_args(Args, 1)))).
1115pred_head(Head, Options) --> 1116 { pred_attributes(Options, Atts),
1117 Head =.. [Functor|Args],
1118 length(Args, Arity)
1119 },
1120 latex(cmd(predicate(opt(Atts),
1121 Functor, Arity, \pred_args(Args, 1)))).
1122
1127
1128pred_attributes(Options, Attrs) :-
1129 findall(A, pred_att(Options, A), As),
1130 insert_comma(As, Attrs).
1131
1132pred_att(Options, Det) :-
1133 option(det(Det), Options).
1134pred_att(Options, private) :-
1135 option(class(privdef), Options).
1136pred_att(Options, multifile) :-
1137 option(class(multidef), Options).
1138
1139insert_comma([H1,H2|T0], [H1, ','|T]) :-
1140 !,
1141 insert_comma([H2|T0], T).
1142insert_comma(L, L).
1143
1144
1145:- if(current_predicate(is_dict/1)). 1146dict_kv_pairs([]) --> [].
1147dict_kv_pairs([H|T]) -->
1148 dict_kv(H),
1149 ( { T == [] }
1150 -> []
1151 ; latex(', '),
1152 dict_kv_pairs(T)
1153 ).
1154
1155dict_kv(Key-Value) -->
1156 latex(cmd(key(Key))),
1157 latex(':'),
1158 term(Value).
1159:- endif. 1160
1161pred_args([], _) -->
1162 [].
1163pred_args([H|T], I) -->
1164 pred_arg(H, I),
1165 ( {T==[]}
1166 -> []
1167 ; latex(', '),
1168 { I2 is I + 1 },
1169 pred_args(T, I2)
1170 ).
1171
1172pred_arg(Var, I) -->
1173 { var(Var) },
1174 !,
1175 latex(['Arg', I]).
1176pred_arg(...(Term), I) -->
1177 !,
1178 pred_arg(Term, I),
1179 latex(cmd(ldots)).
1180pred_arg(Term, I) -->
1181 { Term =.. [Ind,Arg],
1182 mode_indicator(Ind)
1183 },
1184 !,
1185 latex([Ind, \pred_arg(Arg, I)]).
1186pred_arg(Arg:Type, _) -->
1187 !,
1188 latex([\argname(Arg), :, \argtype(Type)]).
1189pred_arg(Arg, _) -->
1190 { atom(Arg) },
1191 !,
1192 argname(Arg).
1193pred_arg(Arg, _) -->
1194 argtype(Arg). 1195
1196argname('$VAR'(Name)) -->
1197 !,
1198 latex(Name).
1199argname(Name) -->
1200 !,
1201 latex(Name).
1202
1203argtype(Term) -->
1204 { format(string(S), '~W',
1205 [ Term,
1206 [ quoted(true),
1207 numbervars(true)
1208 ]
1209 ]) },
1210 latex(S).
1211
1217
1218term(_, Term, Bindings) -->
1219 { bind_vars(Bindings) },
1220 term(Term).
1221
1222term('$VAR'(Name)) -->
1223 !,
1224 latex(cmd(arg(Name))).
1225term(Compound) -->
1226 { callable(Compound),
1227 !,
1228 Compound =.. [Functor|Args]
1229 },
1230 !,
1231 term_with_args(Functor, Args).
1232term(Rest) -->
1233 latex(Rest).
1234
1235term_with_args(Functor, [Left, Right]) -->
1236 { is_op_type(Functor, infix) },
1237 !,
1238 latex(cmd(infixterm(Functor, \term(Left), \term(Right)))).
1239term_with_args(Functor, [Arg]) -->
1240 { is_op_type(Functor, prefix) },
1241 !,
1242 latex(cmd(prefixterm(Functor, \term(Arg)))).
1243term_with_args(Functor, [Arg]) -->
1244 { is_op_type(Functor, postfix) },
1245 !,
1246 latex(cmd(postfixterm(Functor, \term(Arg)))).
1247term_with_args(Functor, Args) -->
1248 latex(cmd(term(Functor, \pred_args(Args, 1)))).
1249
1250
1254
1255termitem(_Text, Term, Bindings) -->
1256 { bind_vars(Bindings) },
1257 termitem(Term).
1258
1259termitem('$VAR'(Name)) -->
1260 !,
1261 latex(cmd(termitem(var(Name), ''))).
1262:- if(current_predicate(is_dict/1)). 1263termitem(Dict) -->
1264 { is_dict(Dict),
1265 !,
1266 dict_pairs(Dict, Tag, Pairs)
1267 },
1268 latex(cmd(dictitem(Tag, \dict_kv_pairs(Pairs)))).
1269:- endif. 1270termitem(Compound) -->
1271 { callable(Compound),
1272 !,
1273 Compound =.. [Functor|Args]
1274 },
1275 !,
1276 termitem_with_args(Functor, Args).
1277termitem(Rest) -->
1278 latex(cmd(termitem(Rest, ''))).
1279
1280termitem_with_args(Functor, [Left, Right]) -->
1281 { is_op_type(Functor, infix) },
1282 !,
1283 latex(cmd(infixtermitem(Functor, \term(Left), \term(Right)))).
1284termitem_with_args(Functor, [Arg]) -->
1285 { is_op_type(Functor, prefix) },
1286 !,
1287 latex(cmd(prefixtermitem(Functor, \term(Arg)))).
1288termitem_with_args(Functor, [Arg]) -->
1289 { is_op_type(Functor, postfix) },
1290 !,
1291 latex(cmd(postfixtermitem(Functor, \term(Arg)))).
1292termitem_with_args({}, [Arg]) -->
1293 !,
1294 latex(cmd(curltermitem(\argtype(Arg)))).
1295termitem_with_args(Functor, Args) -->
1296 latex(cmd(termitem(Functor, \pred_args(Args, 1)))).
1297
1298
1302
1303latex_table(_Attrs, Content) -->
1304 { max_columns(Content, 0, _, -, Wittness),
1305 col_align(Wittness, 1, Content, Align),
1306 atomics_to_string(Align, '|', S0),
1307 atomic_list_concat(['|',S0,'|'], Format)
1308 },
1310 latex(cmd(begin(quote))),
1311 latex(cmd(begin(tabulary,
1312 no_escape('0.9\\textwidth'),
1313 no_escape(Format)))),
1314 latex(cmd(hline)),
1315 rows(Content),
1316 latex(cmd(hline)),
1317 latex(cmd(end(tabulary))),
1318 latex(cmd(end(quote))).
1320
1321max_columns([], C, C, W, W).
1322max_columns([tr(List)|T], C0, C, _, W) :-
1323 length(List, C1),
1324 C1 >= C0, 1325 !,
1326 max_columns(T, C1, C, List, W).
1327max_columns([_|T], C0, C, W0, W) :-
1328 max_columns(T, C0, C, W0, W).
1329
1330col_align([], _, _, []).
1331col_align([CH|CT], Col, Rows, [AH|AT]) :-
1332 ( member(tr(Cells), Rows),
1333 nth1(Col, Cells, Cell),
1334 auto_par(Cell)
1335 -> Wrap = auto
1336 ; Wrap = false
1337 ),
1338 col_align(CH, Wrap, AH),
1339 Col1 is Col+1,
1340 col_align(CT, Col1, Rows, AT).
1341
1342col_align(td(class=Class,_), Wrap, Align) :-
1343 align_class(Class, Wrap, Align),
1344 !.
1345col_align(_, auto, 'L') :- !.
1346col_align(_, false, 'l').
1347
1348align_class(left, auto, 'L').
1349align_class(center, auto, 'C').
1350align_class(right, auto, 'R').
1351align_class(left, false, 'l').
1352align_class(center, false, 'c').
1353align_class(right, false, 'r').
1354
1355rows([]) -->
1356 [].
1357rows([tr(Content)|T]) -->
1358 row(Content),
1359 rows(T).
1360
1361row([]) -->
1362 [ latex(' \\\\'), nl(1) ].
1363row([td(_Attrs, Content)|T]) -->
1364 !,
1365 row([td(Content)|T]).
1366row([td(Content)|T]) -->
1367 latex(Content),
1368 ( {T == []}
1369 -> []
1370 ; [ latex(' & ') ]
1371 ),
1372 row(T).
1373row([th(Content)|T]) -->
1374 latex(cmd(textbf(Content))),
1375 ( {T == []}
1376 -> []
1377 ; [ latex(' & ') ]
1378 ),
1379 row(T).
1380
1384
1385auto_par(Content) :-
1386 phrase(html_text(Content), Words),
1387 length(Words, WC),
1388 WC > 1,
1389 atomics_to_string(Words, Text),
1390 string_length(Text, Width),
1391 Width > 15.
1392
1393html_text([]) -->
1394 !.
1395html_text([H|T]) -->
1396 !,
1397 html_text(H),
1398 html_text(T).
1399html_text(\predref(Name/Arity)) -->
1400 !,
1401 { format(string(S), '~q/~q', [Name, Arity]) },
1402 [S].
1403html_text(Compound) -->
1404 { compound(Compound),
1405 !,
1406 functor(Compound, _Name, Arity),
1407 arg(Arity, Compound, Content)
1408 },
1409 html_text(Content).
1410html_text(Word) -->
1411 [Word].
1412
1413
1414
1415
1416 1419
1424
1425latex_summary(Options) :-
1426 option(summary(File), Options),
1427 !,
1428 findall(Obj, summary_obj(Obj), Objs),
1429 maplist(pi_sort_key, Objs, Keyed),
1430 keysort(Keyed, KSorted),
1431 pairs_values(KSorted, SortedObj),
1432 phrase(summarylist(SortedObj, Options), Tokens),
1433 open(File, write, Out),
1434 call_cleanup(print_latex(Out, Tokens, Options),
1435 close(Out)).
1436latex_summary(_) :-
1437 retractall(documented(_)).
1438
1439summary_obj(Obj) :-
1440 documented(Obj),
1441 pi_head(Obj, Head),
1442 \+ xref_hook(Head).
1443
1444pi_head(M:PI, M:Head) :-
1445 !,
1446 pi_head(PI, Head).
1447pi_head(Name/Arity, Head) :-
1448 functor(Head, Name, Arity).
1449pi_head(Name//DCGArity, Head) :-
1450 Arity is DCGArity+2,
1451 functor(Head, Name, Arity).
1452
1453
1454pi_sort_key(M:PI, PI-(M:PI)) :- !.
1455pi_sort_key(PI, PI-PI).
1456
1457object_name_arity(_:Term, Type, Name, Arity) :-
1458 nonvar(Term),
1459 !,
1460 object_name_arity(Term, Type, Name, Arity).
1461object_name_arity(Name/Arity, pred, Name, Arity).
1462object_name_arity(Name//Arity, dcg, Name, Arity).
1463
1464summarylist(Objs, Options) -->
1465 latex(cmd(begin(summarylist, ll))),
1466 summary(Objs, Options),
1467 latex(cmd(end(summarylist))).
1468
1469summary([], _) -->
1470 [].
1471summary([H|T], Options) -->
1472 summary_line(H, Options),
1473 summary(T, Options).
1474
1475summary_line(Obj, _Options) -->
1476 { doc_comment(Obj, _Pos, Summary, _Comment),
1477 !,
1478 atom_codes(Summary, Codes),
1479 phrase(pldoc_wiki:line_tokens(Tokens), Codes), 1480 object_name_arity(Obj, Type, Name, Arity)
1481 },
1482 ( {Type == dcg}
1483 -> latex(cmd(dcgsummary(Name, Arity, Tokens)))
1484 ; { strip_module(Obj, M, _),
1485 current_op(Pri, Ass, M:Name)
1486 }
1487 -> latex(cmd(oppredsummary(Name, Arity, Ass, Pri, Tokens)))
1488 ; latex(cmd(predicatesummary(Name, Arity, Tokens)))
1489 ).
1490summary_line(Obj, _Options) -->
1491 { print_message(warning, pldoc(no_summary_for(Obj)))
1492 }.
1493
1494 1497
1498print_latex(Out, Tokens, Options) :-
1499 latex_header(Out, Options),
1500 print_latex_tokens(Tokens, Out),
1501 latex_footer(Out, Options).
1502
1503
1507
1508print_latex_tokens([], _).
1509print_latex_tokens([nl(N)|T0], Out) :-
1510 !,
1511 max_nl(T0, T, N, NL),
1512 nl(Out, NL),
1513 print_latex_tokens(T, Out).
1514print_latex_tokens([nl_exact(N)|T0], Out) :-
1515 !,
1516 nl_exact(T0, T,N, NL),
1517 nl(Out, NL),
1518 print_latex_tokens(T, Out).
1519print_latex_tokens([H|T], Out) :-
1520 print_latex_token(H, Out),
1521 print_latex_tokens(T, Out).
1522
1523print_latex_token(cmd(Cmd), Out) :-
1524 !,
1525 format(Out, '\\~w', [Cmd]).
1526print_latex_token(curl(open), Out) :-
1527 !,
1528 format(Out, '{', []).
1529print_latex_token(curl(close), Out) :-
1530 !,
1531 format(Out, '}', []).
1532print_latex_token(indent(N), Out) :-
1533 !,
1534 format(Out, '~t~*|', [N]).
1535print_latex_token(nl(N), Out) :-
1536 !,
1537 format(Out, '~N', []),
1538 forall(between(2,N,_), nl(Out)).
1539print_latex_token(verb(Verb), Out) :-
1540 is_list(Verb), Verb \== [],
1541 !,
1542 atomic_list_concat(Verb, Atom),
1543 print_latex_token(verb(Atom), Out).
1544print_latex_token(verb(Verb), Out) :-
1545 !,
1546 ( member(C, [$,'|',@,=,'"',^,!]),
1547 \+ sub_atom(Verb, _, _, _, C)
1548 -> atom_replace_char(Verb, '\n', ' ', Verb2),
1549 format(Out, '\\verb~w~w~w', [C,Verb2,C])
1550 ; assertion(fail)
1551 ).
1552print_latex_token(code(Code), Out) :-
1553 !,
1554 format(Out, '~N\\begin{code}~n', []),
1555 format(Out, '~w', [Code]),
1556 format(Out, '~N\\end{code}', []).
1557print_latex_token(latex(Code), Out) :-
1558 !,
1559 write(Out, Code).
1560print_latex_token(w(Word), Out) :-
1561 !,
1562 print_latex(Out, Word).
1563print_latex_token(no_escape(Text), Out) :-
1564 !,
1565 write(Out, Text).
1566print_latex_token(url_escape(Text), Out) :-
1567 !,
1568 print_url(Out, Text).
1569print_latex_token(Rest, Out) :-
1570 ( atomic(Rest)
1571 -> print_latex(Out, Rest)
1572 ; 1573 write(Out, Rest)
1574 ).
1575
1576atom_replace_char(In, From, To, Out) :-
1577 sub_atom(In, _, _, _, From),
1578 !,
1579 atom_chars(In, CharsIn),
1580 replace(CharsIn, From, To, CharsOut),
1581 atom_chars(Out, CharsOut).
1582atom_replace_char(In, _, _, In).
1583
1584replace([], _, _, []).
1585replace([H|T0], H, N, [N|T]) :-
1586 !,
1587 replace(T0, H, N, T).
1588replace([H|T0], F, N, [H|T]) :-
1589 replace(T0, F, N, T).
1590
1591
1595
1596print_latex(Out, String) :-
1597 atom_string(Atom, String),
1598 atom_chars(Atom, Chars),
1599 print_chars(Chars, Out).
1600
1601print_chars([], _).
1602print_chars([H|T], Out) :-
1603 print_char(H, Out),
1604 print_chars(T, Out).
1605
1606
1607print_url(Out, String) :-
1608 string_chars(String, Chars),
1609 print_url_chars(Chars, Out).
1610
1611print_url_chars([], _).
1612print_url_chars([H|T], Out) :-
1613 print_url_char(H, Out),
1614 print_url_chars(T, Out).
1615
1616print_url_char('#', Out) :- !, write(Out, '\\#').
1617print_url_char(C, Out) :- put_char(Out, C).
1618
1619
1623
1624max_nl([nl(M1)|T0], T, M0, M) :-
1625 !,
1626 M2 is max(M1, M0),
1627 max_nl(T0, T, M2, M).
1628max_nl([nl_exact(M1)|T0], T, _, M) :-
1629 !,
1630 nl_exact(T0, T, M1, M).
1631max_nl(T, T, M, M).
1632
1633nl_exact([nl(_)|T0], T, M0, M) :-
1634 !,
1635 max_nl(T0, T, M0, M).
1636nl_exact([nl_exact(M1)|T0], T, M0, M) :-
1637 !,
1638 M2 is max(M1, M0),
1639 max_nl(T0, T, M2, M).
1640nl_exact(T, T, M, M).
1641
1642
1643nl(Out, N) :-
1644 forall(between(1, N, _), nl(Out)).
1645
1646
1647print_char('<', Out) :- !, write(Out, '$<$').
1648print_char('>', Out) :- !, write(Out, '$>$').
1649print_char('{', Out) :- !, write(Out, '\\{').
1650print_char('}', Out) :- !, write(Out, '\\}').
1651print_char('$', Out) :- !, write(Out, '\\$').
1652print_char('&', Out) :- !, write(Out, '\\&').
1653print_char('#', Out) :- !, write(Out, '\\#').
1654print_char('%', Out) :- !, write(Out, '\\%').
1655print_char('~', Out) :- !, write(Out, '\\Stilde{}').
1656print_char('\\',Out) :- !, write(Out, '\\bsl{}').
1657print_char('^', Out) :- !, write(Out, '\\Shat{}').
1658print_char('|', Out) :- !, write(Out, '\\Sbar{}').
1659print_char(C, Out) :- put_char(Out, C).
1660
1661
1665
1666identifier(Atom) :-
1667 atom_chars(Atom, [C0|Chars]),
1668 char_type(C0, lower),
1669 all_chartype(Chars, alnum).
1670
1671all_chartype([], _).
1672all_chartype([H|T], Type) :-
1673 char_type(H, Type),
1674 all_chartype(T, Type).
1675
1676
1677 1680
1688
1689:- dynamic
1690 urldef_name/2,
1691 urlchar/1, 1692 urldefs_loaded/1. 1693
1699
1700load_urldefs :-
1701 urldefs_loaded(_),
1702 !.
1703load_urldefs :-
1704 absolute_file_name(library('pldoc/pldoc.sty'), File,
1705 [ access(read) ]),
1706 load_urldefs(File).
1707
1708load_urldefs(File) :-
1709 urldefs_loaded(File),
1710 !.
1711load_urldefs(File) :-
1712 open(File, read, In),
1713 call_cleanup(( read_line_to_codes(In, L0),
1714 process_urldefs(L0, In)),
1715 close(In)),
1716 assert(urldefs_loaded(File)).
1717
1718process_urldefs(end_of_file, _) :- !.
1719process_urldefs(Line, In) :-
1720 ( phrase(urldef(Name, String), Line)
1721 -> assert(urldef_name(String, Name)),
1722 assert_chars(String)
1723 ; true
1724 ),
1725 read_line_to_codes(In, L2),
1726 process_urldefs(L2, In).
1727
1728assert_chars(String) :-
1729 atom_chars(String, Chars),
1730 ( member(C, Chars),
1731 \+ urlchar(C),
1732 assert(urlchar(C)),
1733 fail
1734 ; true
1735 ).
1736
1737urldef(Name, String) -->
1738 "\\urldef{\\", string(NameS), "}\\satom{", string(StringS), "}",
1739 ws,
1740 ( "%"
1741 -> string(_)
1742 ; []
1743 ),
1744 eol,
1745 !,
1746 { atom_codes(Name, NameS),
1747 atom_codes(String, StringS)
1748 }.
1749
1750ws --> [C], { C =< 32 }, !, ws.
1751ws --> [].
1752
1753string([]) --> [].
1754string([H|T]) --> [H], string(T).
1755
1756eol([],[]).
1757
1758
1759 1762
(Out, Options) :-
1764 ( option(stand_alone(true), Options, true)
1765 -> forall(header(Line), format(Out, '~w~n', [Line]))
1766 ; true
1767 ),
1768 forall(generated(Line), format(Out, '~w~n', [Line])).
1769
(Out, Options) :-
1771 ( option(stand_alone(true), Options, true)
1772 -> forall(footer(Line), format(Out, '~w~n', [Line]))
1773 ; true
1774 ).
1775
('\\documentclass[11pt]{article}').
1777header('\\usepackage{times}').
1778header('\\usepackage{pldoc}').
1779header('\\sloppy').
1780header('\\makeindex').
1781header('').
1782header('\\begin{document}').
1783
('').
1785footer('\\printindex').
1786footer('\\end{document}').
1787
1788generated('% This LaTeX document was generated using the LaTeX backend of PlDoc,').
1789generated('% The SWI-Prolog documentation system').
1790generated('').
1791
1792
1793 1796
1797:- multifile
1798 prolog:message//1. 1799
1800prolog:message(pldoc(no_summary_for(Obj))) -->
1801 [ 'No summary documentation for ~p'-[Obj] ]