37
38:- module(pldoc_html,
39 [ doc_for_file/2, 40 doc_write_html/3, 41 doc_for_wiki_file/2, 42 43 doc_page_dom/3, 44 print_html_head/1, 45 predref//1, 46 predref//2, 47 nopredref//1, 48 module_info/3, 49 doc_hide_private/3, 50 edit_button//2, 51 source_button//2, 52 zoom_button//2, 53 pred_edit_button//2, 54 object_edit_button//2, 55 object_source_button//2, 56 doc_resources//1, 57 ensure_doc_objects/1, 58 59 doc_file_objects/5, 60 existing_linked_file/2, 61 unquote_filespec/2, 62 doc_tag_title/2, 63 mode_anchor_name/2, 64 pred_anchor_name/3, 65 private/2, 66 (multifile)/2, 67 is_pi/1, 68 is_op_type/2, 69 70 file//1, 71 file//2, 72 include//3, 73 tags//1, 74 term//3, 75 file_header//2, 76 flagref//1, 77 objects//2, 78 object_ref//2, 79 object_name//2, 80 object_href/2, 81 object_tree//3, 82 object_page//2, 83 object_page_header//2, 84 object_synopsis//2, 85 object_footer//2, 86 object_page_footer//2, 87 cite//1 88 ]). 90:- if(exists_source(library(http/http_dispatch))). 91:- use_module(library(http/http_dispatch)). 92:- use_module(library(http/http_wrapper)). 93:- use_module(library(http/jquery)). 94
95pldoc_server(true).
96:- else. 97
98:- multifile
99 http:location/3. 100
101http:location(pldoc_resource, '/pldoc/res', []).
102
103pldoc_server(false).
104:- endif. 105
106:- use_module(library(lists)). 107:- use_module(library(option)). 108:- use_module(library(uri)). 109:- use_module(library(readutil)). 110:- use_module(library(http/html_write)). 111:- use_module(library(http/http_path)). 112:- use_module(library(http/html_head)). 113:- use_module(library(http/term_html)). 114:- use_module(library(debug)). 115:- use_module(library(apply)). 116:- use_module(library(pairs)). 117:- use_module(library(filesex)). 118:- use_module(doc_process). 119:- use_module(doc_man). 120:- use_module(doc_modes). 121:- use_module(doc_wiki). 122:- use_module(doc_search). 123:- use_module(doc_index). 124:- use_module(doc_util). 125:- use_module(library(solution_sequences)). 126:- use_module(library(error)). 127:- use_module(library(occurs)). 128:- use_module(library(prolog_source)). 129:- use_module(library(prolog_xref)). 130
131:- include(hooks). 132
133
142
143:- public
144 args//1, 145 pred_dt//3, 146 section//2,
147 tag//2. 148
149
150:- predicate_options(doc_for_wiki_file/2, 2,
151 [ edit(boolean)
152 ]). 153:- predicate_options(doc_hide_private/3, 3,
154 [module(atom), public(list), public_only(boolean)]). 155:- predicate_options(edit_button//2, 2,
156 [ edit(boolean)
157 ]). 158:- predicate_options(file//2, 2,
159 [ label(any),
160 absolute_path(atom),
161 href(atom),
162 map_extension(list),
163 files(list),
164 edit_handler(atom)
165 ]). 166:- predicate_options(file_header//2, 2,
167 [ edit(boolean),
168 files(list),
169 public_only(boolean)
170 ]). 171:- predicate_options(include//3, 3,
172 [ absolute_path(atom),
173 class(atom),
174 files(list),
175 href(atom),
176 label(any),
177 map_extension(list)
178 ]). 179:- predicate_options(object_edit_button//2, 2,
180 [ edit(boolean),
181 pass_to(pred_edit_button//2, 2)
182 ]). 183:- predicate_options(object_page//2, 2,
184 [ for(any),
185 header(boolean),
186 links(boolean),
187 no_manual(boolean),
188 try_manual(boolean),
189 search_in(oneof([all,app,man])),
190 search_match(oneof([name,summary])),
191 search_options(boolean)
192 ]). 193:- predicate_options(object_ref//2, 2,
194 [ files(list),
195 qualify(boolean),
196 style(oneof([number,title,number_title])),
197 secref_style(oneof([number,title,number_title]))
198 ]). 199:- predicate_options(object_synopsis//2, 2,
200 [ href(atom)
201 ]). 202:- predicate_options(pred_dt//3, 3,
203 [ edit(boolean)
204 ]). 205:- predicate_options(pred_edit_button//2, 2,
206 [ edit(boolean)
207 ]). 208:- predicate_options(predref//2, 2,
209 [ files(list),
210 prefer(oneof([manual,app])),
211 pass_to(object_ref/4, 2)
212 ]). 213:- predicate_options(private/2, 2,
214 [ module(atom),
215 public(list)
216 ]). 217:- predicate_options(source_button//2, 2,
218 [ files(list)
219 ]). 220
221
222 225
226:- if(pldoc_server(true)). 227:- html_resource(pldoc_css,
228 [ virtual(true),
229 requires([ pldoc_resource('pldoc.css')
230 ])
231 ]). 232:- html_resource(pldoc_resource('pldoc.js'),
233 [ requires([ jquery
234 ])
235 ]). 236:- html_resource(pldoc_js,
237 [ virtual(true),
238 requires([ pldoc_resource('pldoc.js')
239 ])
240 ]). 241:- html_resource(pldoc,
242 [ virtual(true),
243 requires([ pldoc_css,
244 pldoc_js
245 ])
246 ]). 247:- else. 248:- html_resource(pldoc_css, [virtual(true)]). 249:- html_resource(pldoc_resource('pldoc.js'), [virtual(true)]). 250:- html_resource(pldoc_js, [virtual(true)]). 251:- html_resource(pldoc, [virtual(true)]). 252:- endif. 253
254
255 258
277
278doc_for_file(FileSpec, Options) :-
279 doc_file_objects(FileSpec, File, Objects, FileOptions, Options),
280 doc_file_title(File, Title, FileOptions, Options),
281 doc_write_page(
282 pldoc(file(File, Title)),
283 title(Title),
284 \prolog_file(File, Objects, FileOptions, Options),
285 Options).
286
287doc_file_title(_, Title, _, Options) :-
288 option(title(Title), Options),
289 !.
290doc_file_title(File, Title, FileOptions, _) :-
291 memberchk(file(Title0, _Comment), FileOptions),
292 !,
293 file_base_name(File, Base),
294 atomic_list_concat([Base, ' -- ', Title0], Title).
295doc_file_title(File, Title, _, _) :-
296 file_base_name(File, Title).
297
298:- html_meta doc_write_page(+, html, html, +). 299
300doc_write_page(Style, Head, Body, Options) :-
301 option(files(_), Options),
302 !,
303 phrase(page(Style, Head, Body), HTML),
304 print_html(HTML).
305doc_write_page(Style, Head, Body, _) :-
306 reply_html_page(Style, Head, Body).
307
308
309prolog_file(File, Objects, FileOptions, Options) -->
310 { b_setval(pldoc_file, File), 311 file_directory_name(File, Dir)
312 },
313 html([ \doc_resources(Options),
314 \doc_links(Dir, FileOptions),
315 \file_header(File, FileOptions)
316 | \objects(Objects, FileOptions)
317 ]),
318 undocumented(File, Objects, FileOptions).
319
324
325doc_resources(Options) -->
326 { option(resource_directory(ResDir), Options),
327 nb_current(pldoc_output, OutputFile),
328 !,
329 directory_file_path(ResDir, 'pldoc.css', Res),
330 relative_file_name(Res, OutputFile, Ref)
331 },
332 html_requires(Ref).
333doc_resources(Options) -->
334 { option(html_resources(Resoures), Options, pldoc)
335 },
336 html_requires(Resoures).
337
338
364
365doc_file_objects(FileSpec, File, Objects, FileOptions, Options) :-
366 xref_current_source(FileSpec),
367 xref_option(FileSpec, comments(collect)),
368 !,
369 File = FileSpec,
370 findall(Object, xref_doc_object(File, Object), Objects0),
371 reply_file_objects(File, Objects0, Objects, FileOptions, Options).
372doc_file_objects(FileSpec, File, Objects, FileOptions, Options) :-
373 absolute_file_name(FileSpec, File,
374 [ file_type(prolog),
375 access(read)
376 ]),
377 source_file(File),
378 !,
379 ensure_doc_objects(File),
380 Pos = File:Line,
381 findall(Line-doc(Obj,Pos,Comment),
382 doc_comment(Obj, Pos, _, Comment), Pairs),
383 sort(Pairs, Pairs1), 384 keysort(Pairs1, ByLine),
385 pairs_values(ByLine, Objs0),
386 reply_file_objects(File, Objs0, Objects, FileOptions, Options).
387doc_file_objects(FileSpec, File, Objects, FileOptions, Options) :-
388 absolute_file_name(FileSpec, File,
389 [ file_type(prolog),
390 access(read)
391 ]),
392 xref_source(File, [silent(true)]),
393 findall(Object, xref_doc_object(File, Object), Objects0),
394 reply_file_objects(File, Objects0, Objects, FileOptions, Options).
395
396
397reply_file_objects(File, Objs0, Objects, FileOptions, Options) :-
398 module_info(File, ModuleOptions, Options),
399 file_info(Objs0, Objs1, FileOptions, ModuleOptions),
400 doc_hide_private(Objs1, ObjectsSelf, ModuleOptions),
401 include_reexported(ObjectsSelf, Objects1, File, FileOptions),
402 remove_doc_duplicates(Objects1, Objects, []).
403
404remove_doc_duplicates([], [], _).
405remove_doc_duplicates([H|T0], [H|T], Seen) :-
406 H = doc(_, _, Comment),
407 \+ memberchk(Comment, Seen),
408 !,
409 remove_doc_duplicates(T0, T, [Comment|Seen]).
410remove_doc_duplicates([_|T0], T, Seen) :-
411 remove_doc_duplicates(T0, T, Seen).
412
413include_reexported(SelfObjects, Objects, File, Options) :-
414 option(include_reexported(true), Options),
415 option(module(Module), Options),
416 option(public(Exports), Options),
417 select_undocumented(Exports, Module, SelfObjects, Undoc),
418 re_exported_doc(Undoc, File, Module, REObjs, _),
419 REObjs \== [],
420 !,
421 append(SelfObjects, REObjs, Objects).
422include_reexported(Objects, Objects, _, _).
423
424
426
427xref_doc_object(File, doc(M:module(Title),File:0,Comment)) :-
428 xref_comment(File, Title, Comment),
429 xref_module(File, M).
430xref_doc_object(File, doc(M:Name/Arity,File:0,Comment)) :-
431 xref_comment(File, Head, _Summary, Comment),
432 xref_module(File, Module),
433 strip_module(Module:Head, M, Plain),
434 functor(Plain, Name, Arity).
435
444
445:- dynamic
446 no_comments/2. 447
448ensure_doc_objects(File) :-
449 source_file(File),
450 !,
451 ( doc_file_has_comments(File)
452 -> true
453 ; no_comments(File, TimeChecked),
454 time_file(File, TimeChecked)
455 -> true
456 ; xref_source(File, [silent(true), comments(store)]),
457 retractall(no_comments(File, _)),
458 ( doc_file_has_comments(File)
459 -> true
460 ; time_file(File, TimeChecked),
461 assertz(no_comments(File, TimeChecked))
462 )
463 ).
464ensure_doc_objects(File) :-
465 xref_source(File, [silent(true)]).
466
471
472module_info(File, [module(Module), public(Exports)|Options], Options) :-
473 module_property(Module, file(File)),
474 !,
475 module_property(Module, exports(Exports)).
476module_info(File, [module(Module), public(Exports)|Options], Options) :-
477 xref_module(File, Module),
478 !,
479 findall(PI, xref_exported_pi(File, PI), Exports).
480module_info(_, Options, Options).
481
482xref_exported_pi(Src, Name/Arity) :-
483 xref_exported(Src, Head),
484 functor(Head, Name, Arity).
485
489
490doc_hide_private(Objs, Objs, Options) :-
491 option(public_only(false), Options, true),
492 !.
493doc_hide_private(Objs0, Objs, Options) :-
494 hide_private(Objs0, Objs, Options).
495
496hide_private([], [], _).
497hide_private([H|T0], T, Options) :-
498 obj(H, Obj),
499 private(Obj, Options),
500 !,
501 hide_private(T0, T, Options).
502hide_private([H|T0], [H|T], Options) :-
503 hide_private(T0, T, Options).
504
510
511obj(doc(Obj0, _Pos, _Summary), Obj) :-
512 !,
513 ( Obj0 = [Obj|_]
514 -> true
515 ; Obj = Obj0
516 ).
517obj(Obj0, Obj) :-
518 ( Obj0 = [Obj|_]
519 -> true
520 ; Obj = Obj0
521 ).
522
523
529
530:- multifile
531 prolog:doc_is_public_object/1. 532
533private(Object, _Options) :-
534 prolog:doc_is_public_object(Object), !, fail.
535private(Module:PI, Options) :-
536 multifile(Module:PI, Options), !, fail.
537private(Module:PI, Options) :-
538 public(Module:PI, Options), !, fail.
539private(Module:PI, Options) :-
540 option(module(Module), Options),
541 option(public(Public), Options),
542 !,
543 \+ ( member(PI2, Public),
544 eq_pi(PI, PI2)
545 ).
546private(Module:PI, _Options) :-
547 module_property(Module, file(_)), 548 !,
549 module_property(Module, exports(Exports)),
550 \+ ( member(PI2, Exports),
551 eq_pi(PI, PI2)
552 ).
553private(Module:PI, _Options) :-
554 \+ (pi_to_head(PI, Head),
555 xref_exported(Source, Head),
556 xref_module(Source, Module)).
557
562
566
567multifile(Obj, _Options) :-
568 strip_module(user:Obj, Module, PI),
569 pi_to_head(PI, Head),
570 ( predicate_property(Module:Head, multifile)
571 ; xref_module(Source, Module),
572 xref_defined(Source, Head, multifile(_Line))
573 ),
574 !.
575
579
580public(Obj, _Options) :-
581 strip_module(user:Obj, Module, PI),
582 pi_to_head(PI, Head),
583 ( predicate_property(Module:Head, public)
584 ; xref_module(Source, Module),
585 xref_defined(Source, Head, public(_Line))
586 ),
587 !.
588
589pi_to_head(Var, _) :-
590 var(Var), !, fail.
591pi_to_head(Name/Arity, Term) :-
592 functor(Term, Name, Arity).
593pi_to_head(Name//DCGArity, Term) :-
594 Arity is DCGArity+2,
595 functor(Term, Name, Arity).
596
600
601file_info(Comments, RestComments, [file(Title, Comment)|Opts], Opts) :-
602 select(doc(_:module(Title),_,Comment), Comments, RestComments),
603 !.
604file_info(Comments, Comments, Opts, Opts).
605
606
610
(File, Options) -->
612 { memberchk(file(Title, Comment), Options),
613 !,
614 file_base_name(File, Base)
615 },
616 file_title([Base, ' -- ', Title], File, Options),
617 { is_structured_comment(Comment, Prefixes),
618 string_codes(Comment, Codes),
619 indented_lines(Codes, Prefixes, Lines),
620 section_comment_header(Lines, _Header, Lines1),
621 wiki_lines_to_dom(Lines1, [], DOM)
622 },
623 html(DOM).
624file_header(File, Options) -->
625 { file_base_name(File, Base)
626 },
627 file_title([Base], File, Options).
628
629
633
634file_title(Title, File, Options) -->
635 prolog:doc_file_title(Title, File, Options),
636 !.
637file_title(Title, File, Options) -->
638 { file_base_name(File, Base)
639 },
640 html(h1(class(file),
641 [ span(style('float:right'),
642 [ \reload_button(File, Base, Options),
643 \zoom_button(Base, Options),
644 \source_button(Base, Options),
645 \edit_button(File, Options)
646 ])
647 | Title
648 ])).
649
650
657
658reload_button(File, _Base, Options) -->
659 { \+ source_file(File),
660 \+ option(files(_), Options)
661 },
662 !,
663 html(span(class(file_anot), '[not loaded]')).
664reload_button(_File, Base, Options) -->
665 { option(edit(true), Options),
666 !,
667 option(public_only(Public), Options, true)
668 },
669 html(a(href(Base+[reload(true), public_only(Public)]),
670 img([ class(action),
671 alt('Reload'),
672 title('Make & Reload'),
673 src(location_by_id(pldoc_resource)+'reload.png')
674 ]))).
675reload_button(_, _, _) --> [].
676
682
683edit_button(File, Options) -->
684 { option(edit(true), Options)
685 },
686 !,
687 html(a([ onClick('HTTPrequest(\'' +
688 location_by_id(pldoc_edit) + [file(File)] +
689 '\')')
690 ],
691 img([ class(action),
692 alt(edit),
693 title('Edit file'),
694 src(location_by_id(pldoc_resource)+'edit.png')
695 ]))).
696edit_button(_, _) -->
697 [].
698
699
703
704zoom_button(_, Options) -->
705 { option(files(_Map), Options) },
706 !. 707zoom_button(Base, Options) -->
708 { ( option(public_only(true), Options, true)
709 -> Zoom = 'public.png',
710 Alt = 'Public',
711 Title = 'Click to include private',
712 PublicOnly = false
713 ; Zoom = 'private.png',
714 Alt = 'All predicates',
715 Title = 'Click to show exports only',
716 PublicOnly = true
717 )
718 },
719 html(a(href(Base+[public_only(PublicOnly)]),
720 img([ class(action),
721 alt(Alt),
722 title(Title),
723 src(location_by_id(pldoc_resource)+Zoom)
724 ]))).
725
726
730
731source_button(_File, Options) -->
732 { option(files(_Map), Options) },
733 !. 734source_button(File, _Options) -->
735 { ( is_absolute_file_name(File)
736 -> doc_file_href(File, HREF0)
737 ; HREF0 = File
738 )
739 },
740 html(a(href(HREF0+[show(src)]),
741 img([ class(action),
742 alt('Show source'),
743 title('Show source'),
744 src(location_by_id(pldoc_resource)+'source.png')
745 ]))).
746
747
754
755objects(Objects, Options) -->
756 { option(navtree(true), Options),
757 !,
758 objects_nav_tree(Objects, Tree)
759 },
760 html([ div(class(navtree),
761 div(class(navwindow),
762 \nav_tree(Tree, Objects, Options))),
763 div(class(navcontent),
764 \objects_nt(Objects, Options))
765 ]).
766objects(Objects, Options) -->
767 objects_nt(Objects, Options).
768
769objects_nt(Objects, Options) -->
770 objects(Objects, [body], Options).
771
772objects([], Mode, _) -->
773 pop_mode(body, Mode, _).
774objects([Obj|T], Mode, Options) -->
775 object(Obj, Mode, Mode1, Options),
776 objects(T, Mode1, Options).
777
786
787object(doc(Obj,Pos,Comment), Mode0, Mode, Options) -->
788 !,
789 object(Obj, [Pos-Comment], Mode0, Mode, [scope(file)|Options]).
790object(Obj, Mode0, Mode, Options) -->
791 { findall(Pos-Comment,
792 doc_comment(Obj, Pos, _Summary, Comment),
793 Pairs)
794 },
795 !,
796 { b_setval(pldoc_object, Obj) },
797 object(Obj, Pairs, Mode0, Mode, Options).
798
799object(Obj, Pairs, Mode0, Mode, Options) -->
800 { is_pi(Obj),
801 !,
802 maplist(pred_dom(Obj, Options), Pairs, DOMS),
803 append(DOMS, DOM)
804 },
805 need_mode(dl, Mode0, Mode),
806 html(DOM).
807object([Obj|_Same], Pairs, Mode0, Mode, Options) -->
808 !,
809 object(Obj, Pairs, Mode0, Mode, Options).
810object(Obj, _Pairs, Mode, Mode, _Options) -->
811 { debug(pldoc, 'Skipped ~p', [Obj]) },
812 [].
813
814pred_dom(Obj, Options, Pos-Comment, DOM) :-
815 is_structured_comment(Comment, Prefixes),
816 string_codes(Comment, Codes),
817 indented_lines(Codes, Prefixes, Lines),
818 strip_module(user:Obj, Module, _),
819 process_modes(Lines, Module, Pos, Modes, Args, Lines1),
820 ( private(Obj, Options)
821 -> Class = privdef 822 ; multifile(Obj, Options)
823 -> ( option(scope(file), Options)
824 -> ( more_doc(Obj, Pos)
825 -> Class = multidef(object(Obj))
826 ; Class = multidef
827 )
828 ; Class = multidef(file((Pos)))
829 )
830 ; public(Obj, Options)
831 -> Class = publicdef 832 ; Class = pubdef 833 ),
834 ( Obj = Module:_
835 -> POptions = [module(Module)|Options]
836 ; POptions = Options
837 ),
838 Pos = File:Line,
839 DTOptions = [file(File),line(Line)|POptions],
840 DOM = [\pred_dt(Modes, Class, DTOptions), dd(class=defbody, DOM1)],
841 wiki_lines_to_dom(Lines1, Args, DOM0),
842 strip_leading_par(DOM0, DOM1).
843
844more_doc(Obj, File:_) :-
845 doc_comment(Obj, File2:_, _, _),
846 File2 \== File,
847 !.
848
855
856need_mode(Mode, Stack, Stack) -->
857 { Stack = [Mode|_] },
858 !,
859 [].
860need_mode(Mode, Stack, Rest) -->
861 { memberchk(Mode, Stack)
862 },
863 !,
864 pop_mode(Mode, Stack, Rest).
865need_mode(Mode, Stack, [Mode|Stack]) -->
866 !,
867 html_begin(Mode).
868
869pop_mode(Mode, Stack, Stack) -->
870 { Stack = [Mode|_] },
871 !,
872 [].
873pop_mode(Mode, [H|Rest0], Rest) -->
874 html_end(H),
875 pop_mode(Mode, Rest0, Rest).
876
880
881undocumented(File, Objs, Options) -->
882 { memberchk(module(Module), Options),
883 memberchk(public(Exports), Options),
884 select_undocumented(Exports, Module, Objs, Undoc),
885 re_exported_doc(Undoc, File, Module, UREObjs, ReallyUnDoc),
886 sort(2, @=<, UREObjs, REObjs) 887 888 },
889 !,
890 re_exported_doc(REObjs, Options),
891 undocumented(ReallyUnDoc, Options).
892undocumented(_, _, _) -->
893 [].
894
895re_exported_doc([], _) --> !.
896re_exported_doc(Objs, Options) -->
897 reexport_header(Objs, Options),
898 objects(Objs, Options).
899
(_, Options) -->
901 { option(reexport_header(true), Options, true)
902 },
903 !,
904 html([ h2(class(wiki), 'Re-exported predicates'),
905 p([ "The following predicates are exported from this file \c
906 while their implementation is defined in imported modules \c
907 or non-module files loaded by this module."
908 ])
909 ]).
910reexport_header(_, _) -->
911 [].
912
913undocumented([], _) --> !.
914undocumented(UnDoc, Options) -->
915 html([ h2(class(undoc), 'Undocumented predicates'),
916 p(['The following predicates are exported, but not ',
917 'or incorrectly documented.'
918 ]),
919 dl(class(undoc),
920 \undocumented_predicates(UnDoc, Options))
921 ]).
922
923
924undocumented_predicates([], _) -->
925 [].
926undocumented_predicates([H|T], Options) -->
927 undocumented_pred(H, Options),
928 undocumented_predicates(T, Options).
929
930undocumented_pred(Name/Arity, Options) -->
931 { functor(Head, Name, Arity) },
932 html(dt(class=undoc, \pred_mode(Head, [], _, Options))).
933
934select_undocumented([], _, _, []).
935select_undocumented([PI|T0], M, Objs, [PI|T]) :-
936 is_pi(PI),
937 \+ in_doc(M:PI, Objs),
938 !,
939 select_undocumented(T0, M, Objs, T).
940select_undocumented([_|T0], M, Objs, T) :-
941 select_undocumented(T0, M, Objs, T).
942
943in_doc(PI, Objs) :-
944 member(doc(O,_,_), Objs),
945 ( is_list(O)
946 -> member(O2, O),
947 eq_pi(PI, O2)
948 ; eq_pi(PI, O)
949 ).
950
951
955
956eq_pi(PI, PI) :- !.
957eq_pi(M:PI1, M:PI2) :-
958 atom(M),
959 !,
960 eq_pi(PI1, PI2).
961eq_pi(Name/A, Name//DCGA) :-
962 A =:= DCGA+2,
963 !.
964eq_pi(Name//DCGA, Name/A) :-
965 A =:= DCGA+2.
966
970
971is_pi(Var) :-
972 var(Var),
973 !,
974 fail.
975is_pi(_:PI) :-
976 !,
977 is_pi(PI).
978is_pi(_/_).
979is_pi(_//_).
980
981
984
985re_exported_doc([], _, _, [], []).
986re_exported_doc([PI|T0], File, Module, [doc(Orig:PI,Pos,Comment)|ObjT], UnDoc) :-
987 pi_to_head(PI, Head),
988 ( predicate_property(Module:Head, imported_from(Orig))
989 -> true
990 ; predicate_property(Module:Head, exported)
991 -> Orig = Module
992 ; xref_defined(File, Head, imported(File2)),
993 ensure_doc_objects(File2),
994 xref_module(File2, Orig)
995 ),
996 doc_comment(Orig:PI, Pos, _, Comment),
997 !,
998 re_exported_doc(T0, File, Module, ObjT, UnDoc).
999re_exported_doc([PI|T0], File, Module, REObj, [PI|UnDoc]) :-
1000 re_exported_doc(T0, File, Module, REObj, UnDoc).
1001
1002
1003 1006
1014
1015object_page(Obj, Options) -->
1016 prolog:doc_object_page(Obj, Options),
1017 !,
1018 object_page_footer(Obj, Options).
1019object_page(Obj, Options) -->
1020 { doc_comment(Obj, File:_Line, _Summary, _Comment)
1021 },
1022 !,
1023 ( { \+ ( doc_comment(Obj, File2:_, _, _),
1024 File2 \== File )
1025 }
1026 -> html([ \html_requires(pldoc),
1027 \object_page_header(File, Options),
1028 \object_synopsis(Obj, []),
1029 \objects([Obj], Options)
1030 ])
1031 ; html([ \html_requires(pldoc),
1032 \object_page_header(-, Options),
1033 \objects([Obj], [synopsis(true)|Options])
1034 ])
1035 ),
1036 object_page_footer(Obj, Options).
1037object_page(M:Name/Arity, Options) --> 1038 { functor(Head, Name, Arity),
1039 ( predicate_property(M:Head, exported)
1040 -> module_property(M, class(library))
1041 ; \+ predicate_property(M:Head, defined)
1042 )
1043 },
1044 prolog:doc_object_page(Name/Arity, Options),
1045 !,
1046 object_page_footer(Name/Arity, Options).
1047
(File, Options) -->
1049 prolog:doc_page_header(file(File), Options),
1050 !.
1051object_page_header(File, Options) -->
1052 { option(header(true), Options, true) },
1053 !,
1054 html(div(class(navhdr),
1055 [ div(class(jump), \file_link(File)),
1056 div(class(search), \search_form(Options)),
1057 br(clear(right))
1058 ])).
1059object_page_header(_, _) --> [].
1060
1061file_link(-) -->
1062 !,
1063 places_menu(-).
1064file_link(File) -->
1065 { file_directory_name(File, Dir)
1066 },
1067 places_menu(Dir),
1068 html([ div(a(href(location_by_id(pldoc_doc)+File), File))
1069 ]).
1070
1075
(Obj, Options) -->
1077 prolog:doc_object_footer(Obj, Options),
1078 !.
1079object_footer(_, _) --> [].
1080
1081
1086
(Obj, Options) -->
1088 prolog:doc_object_page_footer(Obj, Options),
1089 !.
1090object_page_footer(_, _) --> [].
1091
1092
1103
1104object_synopsis(Name/Arity, _) -->
1105 { functor(Head, Name, Arity),
1106 predicate_property(system:Head, built_in)
1107 },
1108 synopsis([span(class(builtin), 'built-in')]).
1109object_synopsis(Name/Arity, Options) -->
1110 !,
1111 object_synopsis(_:Name/Arity, Options).
1112object_synopsis(M:Name/Arity, Options) -->
1113 { functor(Head, Name, Arity),
1114 ( option(source(Spec), Options)
1115 -> absolute_file_name(Spec, File,
1116 [ access(read),
1117 file_type(prolog),
1118 file_errors(fail)
1119 ])
1120 ; predicate_property(M:Head, exported),
1121 \+ predicate_property(M:Head, imported_from(_)),
1122 module_property(M, file(File)),
1123 file_name_on_path(File, Spec)
1124 ),
1125 !,
1126 unquote_filespec(Spec, Unquoted)
1127 },
1128 use_module_synopsis(Head, File, Unquoted, Options).
1129object_synopsis(Name//Arity, Options) -->
1130 !,
1131 { DCGArity is Arity+2 },
1132 object_synopsis(Name/DCGArity, Options).
1133object_synopsis(Module:Name//Arity, Options) -->
1134 !,
1135 { DCGArity is Arity+2 },
1136 object_synopsis(Module:Name/DCGArity, Options).
1137object_synopsis(f(_/_), _) -->
1138 synopsis(span(class(function),
1139 [ 'Arithmetic function (see ',
1140 \object_ref(is/2, []),
1141 ')'
1142 ])).
1143object_synopsis(c(Func), _) -->
1144 { sub_atom(Func, 0, _, _, 'PL_')
1145 ; sub_atom(Func, 0, _, _, 'S')
1146 },
1147 !,
1148 synopsis([span(class(cfunc), 'C-language interface function')]).
1149object_synopsis(_, _) --> [].
1150
1151:- html_meta(synopsis(html,?,?)). 1152
1153use_module_synopsis(Head, File, Unquoted, Options) -->
1154 { Args = [class(copy), title('Click to copy')] },
1155 ( { option(href(HREF), Options) }
1156 -> synopsis([ code(Args, [':- use_module(',a(href(HREF), '~q'-[Unquoted]),').'])
1157 | \can_autoload(Head, File)
1158 ])
1159 ; synopsis([ code(Args, ':- use_module(~q).'-[Unquoted])
1160 | \can_autoload(Head, File)
1161 ])
1162 ).
1163
1164synopsis(HTML) -->
1165 html(div(class(synopsis),
1166 [ span(class('synopsis-hdr'), 'Availability:')
1167 | HTML
1168 ])).
1169
1170can_autoload(Head, File) -->
1171 { predicate_property(Head, autoload(FileBase)),
1172 file_name_extension(FileBase, _Ext, File)
1173 },
1174 !,
1175 html(span(class(autoload), \can_be_autoloaded)).
1176can_autoload(_, _) -->
1177 [].
1178
1179can_be_autoloaded -->
1180 { catch(http_link_to_id(pldoc_man, [section(autoload)], HREF),
1181 error(_,_), fail)
1182 },
1183 html(['(can be ', a(href(HREF), autoloaded), ')']).
1184can_be_autoloaded -->
1185 html('(can be autoloaded)').
1186
1187
1192
1193unquote_filespec(Spec, Unquoted) :-
1194 compound(Spec),
1195 Spec =.. [Alias,Path],
1196 atom(Path),
1197 atomic_list_concat(Parts, /, Path),
1198 maplist(need_no_quotes, Parts),
1199 !,
1200 parts_to_path(Parts, UnquotedPath),
1201 Unquoted =.. [Alias, UnquotedPath].
1202unquote_filespec(Spec, Spec).
1203
1204need_no_quotes(Atom) :-
1205 format(atom(A), '~q', [Atom]),
1206 \+ sub_atom(A, 0, _, _, '\'').
1207
1208parts_to_path([One], One) :- !.
1209parts_to_path(List, More/T) :-
1210 ( append(H, [T], List)
1211 -> parts_to_path(H, More)
1212 ).
1213
1214
1215 1218
1222
1223doc_write_html(Out, Title, Doc) :-
1224 doc_page_dom(Title, Doc, DOM),
1225 phrase(html(DOM), Tokens),
1226 print_html_head(Out),
1227 print_html(Out, Tokens).
1228
1233
1234doc_page_dom(Title, Body, DOM) :-
1235 DOM = html([ head([ title(Title),
1236 link([ rel(stylesheet),
1237 type('text/css'),
1238 href(location_by_id(pldoc_resource)+'pldoc.css')
1239 ]),
1240 script([ src(location_by_id(pldoc_resource)+'pldoc.js'),
1241 type('text/javascript')
1242 ], [])
1243 ]),
1244 body(Body)
1245 ]).
1246
1250
1251print_html_head(Out) :-
1252 format(Out,
1253 '<!DOCTYPE HTML PUBLIC "-//W3C//DTD HTML 4.01//EN" \c
1254 "http://www.w3.org/TR/html4/strict.dtd">~n', []).
1255
1259
1265
1266tags(Tags) -->
1267 html(dl(class=tags, Tags)).
1268
1272
1273tag(Tag, Values) -->
1274 { doc_tag_title(Tag, Title),
1275 atom_concat('keyword-', Tag, Class)
1276 },
1277 html([ dt(class=Class, Title),
1278 \tag_values(Values, Class)
1279 ]).
1280
1281tag_values([], _) -->
1282 [].
1283tag_values([H|T], Class) -->
1284 html(dd(class=Class, ['- '|H])),
1285 tag_values(T, Class).
1286
1287
1291
1292doc_tag_title(Tag, Title) :-
1293 tag_title(Tag, Title),
1294 !.
1295doc_tag_title(Tag, Tag).
1296
1297tag_title(compat, 'Compatibility').
1298tag_title(tbd, 'To be done').
1299tag_title(see, 'See also').
1300tag_title(error, 'Errors').
1301tag_title(since, 'Since').
1302
1307
1308args(Params) -->
1309 html([ dt(class=tag, 'Arguments:'),
1310 dd(table(class=arglist,
1311 \arg_list(Params)))
1312 ]).
1313
1314arg_list([]) -->
1315 [].
1316arg_list([H|T]) -->
1317 argument(H),
1318 arg_list(T).
1319
1320argument(arg(Name,Descr)) -->
1321 html(tr([td(var(Name)), td(class=argdescr, ['- '|Descr])])).
1322
1323
1324 1327
1332
1333objects_nav_tree(Objects, Tree) :-
1334 maplist(object_nav_tree, Objects, Trees),
1335 union_trees(Trees, Tree0),
1336 remove_unique_root(Tree0, Tree).
1337
1338object_nav_tree(Obj, Tree) :-
1339 Node = node(directory(Dir), FileNodes),
1340 FileNode = node(file(File), Siblings),
1341 doc_comment(Obj, File:_Line, _Summary, _Comment),
1342 !,
1343 file_directory_name(File, Dir),
1344 sibling_file_nodes(Dir, FileNodes0),
1345 selectchk(node(file(File),[]), FileNodes0, FileNode, FileNodes),
1346 findall(Sibling, doc_comment(Sibling, File:_, _, _), Siblings0),
1347 delete(Siblings0, _:module(_), Siblings1),
1348 doc_hide_private(Siblings1, Siblings2, []),
1349 flatten(Siblings2, Siblings), 1350 embed_directories(Node, Tree).
1351
1352sibling_file_nodes(Dir, Nodes) :-
1353 findall(node(file(File), []),
1354 ( source_file(File),
1355 file_directory_name(File, Dir)
1356 ),
1357 Nodes).
1358
1359embed_directories(Node, Tree) :-
1360 Node = node(file(File), _),
1361 !,
1362 file_directory_name(File, Dir),
1363 Super = node(directory(Dir), [Node]),
1364 embed_directories(Super, Tree).
1365embed_directories(Node, Tree) :-
1366 Node = node(directory(Dir), _),
1367 file_directory_name(Dir, SuperDir),
1368 SuperDir \== Dir,
1369 !,
1370 Super = node(directory(SuperDir), [Node]),
1371 embed_directories(Super, Tree).
1372embed_directories(Tree, Tree).
1373
1374
1375union_trees([Tree], Tree) :- !.
1376union_trees([T1,T2|Trees], Tree) :-
1377 merge_trees(T1, T2, M1),
1378 union_trees([M1|Trees], Tree).
1379
1380merge_trees(node(R, Ch1), node(R, Ch2), node(R, Ch)) :-
1381 merge_nodes(Ch1, Ch2, Ch).
1382
1383merge_nodes([], Ch, Ch) :- !.
1384merge_nodes(Ch, [], Ch) :- !.
1385merge_nodes([node(Root, Ch1)|T1], N1, [T1|Nodes]) :-
1386 selectchk(node(Root, Ch2), N1, N2),
1387 !,
1388 merge_trees(node(Root, Ch1), node(Root, Ch2), T1),
1389 merge_nodes(T1, N2, Nodes).
1390merge_nodes([Node|T1], N1, [Node|Nodes]) :-
1391 merge_nodes(T1, N1, Nodes).
1392
1396
1397remove_unique_root(node(_, [node(R1, [R2])]), Tree) :-
1398 !,
1399 remove_unique_root(node(R1, [R2]), Tree).
1400remove_unique_root(Tree, Tree).
1401
1405
1406nav_tree(Tree, Current, Options) -->
1407 html(ul(class(nav),
1408 \object_tree(Tree, Current, Options))).
1409
1413
1414object_tree(node(Id, []), Target, Options) -->
1415 !,
1416 { node_class(Id, Target, Class) },
1417 html(li(class(Class),
1418 \node(Id, Options))).
1419object_tree(node(Id, Children), Target, Options) -->
1420 !,
1421 { node_class(Id, Target, Class) },
1422 html(li(class(Class),
1423 [ \node(Id, Options),
1424 ul(class(nav),
1425 \object_trees(Children, Target, Options))
1426 ])).
1427object_tree(Id, Target, Options) -->
1428 !,
1429 { node_class(Id, Target, Class) },
1430 html(li(class([obj|Class]), \node(Id, Options))).
1431
1432object_trees([], _, _) --> [].
1433object_trees([H|T], Target, Options) -->
1434 object_tree(H, Target, Options),
1435 object_trees(T, Target, Options).
1436
1437node_class(Ids, Current, Class) :-
1438 is_list(Ids),
1439 !,
1440 ( member(Id, Ids), memberchk(Id, Current)
1441 -> Class = [nav,current]
1442 ; Class = [nav]
1443 ).
1444node_class(Id, Current, Class) :-
1445 ( memberchk(Id, Current)
1446 -> Class = [nav,current]
1447 ; Class = [nav]
1448 ).
1449
1450node(file(File), Options) -->
1451 !,
1452 object_ref(file(File), [style(title)|Options]).
1453node(Id, Options) -->
1454 object_ref(Id, Options).
1455
1456
1457 1460
1461section(Type, Title) -->
1462 { string_codes(Title, Codes),
1463 wiki_codes_to_dom(Codes, [], Content0),
1464 strip_leading_par(Content0, Content),
1465 make_section(Type, Content, HTML)
1466 },
1467 html(HTML).
1468
1469make_section(module, Title, h1(class=module, Title)).
1470make_section(section, Title, h1(class=section, Title)).
1471
1472
1473 1476
1482
1483pred_dt(Modes, Class, Options) -->
1484 pred_dt(Modes, Class, [], _Done, Options).
1485
1486pred_dt([], _, Done, Done, _) -->
1487 [].
1488pred_dt([H|T], Class, Done0, Done, Options) -->
1489 { functor(Class, CSSClass, _) },
1490 html(dt(class=CSSClass,
1491 [ \pred_mode(H, Done0, Done1, Options),
1492 \mode_anot(Class)
1493 ])),
1494 pred_dt(T, Class, Done1, Done, Options).
1495
1496mode_anot(privdef) -->
1497 !,
1498 html(span([class(anot), style('float:right')],
1499 '[private]')).
1500mode_anot(multidef(object(Obj))) -->
1501 !,
1502 { object_href(Obj, HREF) },
1503 html(span([class(anot), style('float:right')],
1504 ['[', a(href(HREF), multifile), ']'
1505 ])).
1506mode_anot(multidef(file(File:_))) -->
1507 !,
1508 { file_name_on_path(File, Spec),
1509 unquote_filespec(Spec, Unquoted),
1510 doc_file_href(File, HREF)
1511 },
1512 html(span([class(anot), style('float:right')],
1513 ['[multifile, ', a(href(HREF), '~q'-[Unquoted]), ']'
1514 ])).
1515mode_anot(multidef) -->
1516 !,
1517 html(span([class(anot), style('float:right')],
1518 '[multifile]')).
1519mode_anot(_) -->
1520 [].
1521
1522pred_mode(mode(Head,Vars), Done0, Done, Options) -->
1523 !,
1524 { bind_vars(Head, Vars) },
1525 pred_mode(Head, Done0, Done, Options).
1526pred_mode(Head is Det, Done0, Done, Options) -->
1527 !,
1528 anchored_pred_head(Head, Done0, Done, Options),
1529 pred_det(Det).
1530pred_mode(Head, Done0, Done, Options) -->
1531 anchored_pred_head(Head, Done0, Done, Options).
1532
1533bind_vars(Term, Bindings) :-
1534 bind_vars(Bindings),
1535 anon_vars(Term).
1536
1537bind_vars([]).
1538bind_vars([Name=Var|T]) :-
1539 Var = '$VAR'(Name),
1540 bind_vars(T).
1541
1546
1547anon_vars(Var) :-
1548 var(Var),
1549 !,
1550 Var = '$VAR'('_').
1551anon_vars(Term) :-
1552 compound(Term),
1553 !,
1554 Term =.. [_|Args],
1555 maplist(anon_vars, Args).
1556anon_vars(_).
1557
1558
1559anchored_pred_head(Head, Done0, Done, Options) -->
1560 { pred_anchor_name(Head, PI, Name) },
1561 ( { memberchk(PI, Done0) }
1562 -> { Done = Done0 },
1563 pred_head(Head)
1564 ; html([ span(style('float:right'),
1565 [ \pred_edit_or_source_button(Head, Options),
1566 &(nbsp)
1567 ]),
1568 a(name=Name, \pred_head(Head))
1569 ]),
1570 { Done = [PI|Done0] }
1571 ).
1572
1573
1574pred_edit_or_source_button(Head, Options) -->
1575 { option(edit(true), Options) },
1576 !,
1577 pred_edit_button(Head, Options).
1578pred_edit_or_source_button(Head, Options) -->
1579 { option(source_link(true), Options) },
1580 !,
1581 pred_source_button(Head, Options).
1582pred_edit_or_source_button(_, _) --> [].
1583
1595
1596pred_edit_button(_, Options) -->
1597 { \+ option(edit(true), Options) },
1598 !.
1599pred_edit_button(PI0, Options0) -->
1600 { canonicalise_predref(PI0, PI, Options0, Options) },
1601 pred_edit_button2(PI, Options).
1602
1603pred_edit_button2(Name/Arity, Options) -->
1604 { \+ ( memberchk(file(_), Options), 1605 memberchk(line(_), Options) 1606 ),
1607 functor(Head, Name, Arity),
1608 option(module(M), Options, _),
1609 \+ ( current_module(M),
1610 source_file(M:Head, _File)
1611 )
1612 },
1613 !.
1614pred_edit_button2(Name/Arity, Options) -->
1615 { include(edit_param, Options, Extra),
1616 http_link_to_id(pldoc_edit,
1617 [name(Name),arity(Arity)|Extra],
1618 EditHREF)
1619 },
1620 html(a(onClick('HTTPrequest(\'' + EditHREF + '\')'),
1621 img([ class(action),
1622 alt('Edit predicate'),
1623 title('Edit predicate'),
1624 src(location_by_id(pldoc_resource)+'editpred.png')
1625 ]))).
1626pred_edit_button2(_, _) -->
1627 !,
1628 [].
1629
1630edit_param(module(_)).
1631edit_param(file(_)).
1632edit_param(line(_)).
1633
1634
1638
1639object_edit_button(_, Options) -->
1640 { \+ option(edit(true), Options) },
1641 !.
1642object_edit_button(PI, Options) -->
1643 { is_pi(PI) },
1644 !,
1645 pred_edit_button(PI, Options).
1646object_edit_button(_, _) -->
1647 [].
1648
1649
1653
1654pred_source_button(PI0, Options0) -->
1655 { canonicalise_predref(PI0, PI, Options0, Options),
1656 option(module(M), Options, _),
1657 pred_source_href(PI, M, HREF), !
1658 },
1659 html(a([ href(HREF),
1660 class(source)
1661 ],
1662 img([ class(action),
1663 alt('Source'),
1664 title('Show source'),
1665 src(location_by_id(pldoc_resource)+'source.png')
1666 ]))).
1667pred_source_button(_, _) -->
1668 [].
1669
1670
1674
1675object_source_button(PI, Options) -->
1676 { is_pi(PI),
1677 option(source_link(true), Options, true)
1678 },
1679 !,
1680 pred_source_button(PI, Options).
1681object_source_button(_, _) -->
1682 [].
1683
1684
1689
1690canonicalise_predref(M:PI0, PI, Options0, [module(M)|Options]) :-
1691 !,
1692 canonicalise_predref(PI0, PI, Options0, Options).
1693canonicalise_predref(//(Head), PI, Options0, Options) :-
1694 !,
1695 functor(Head, Name, Arity),
1696 PredArity is Arity + 2,
1697 canonicalise_predref(Name/PredArity, PI, Options0, Options).
1698canonicalise_predref(Name//Arity, PI, Options0, Options) :-
1699 integer(Arity), Arity >= 0,
1700 !,
1701 PredArity is Arity + 2,
1702 canonicalise_predref(Name/PredArity, PI, Options0, Options).
1703canonicalise_predref(PI, PI, Options, Options) :-
1704 PI = Name/Arity,
1705 atom(Name), integer(Arity), Arity >= 0,
1706 !.
1707canonicalise_predref(Head, PI, Options0, Options) :-
1708 functor(Head, Name, Arity),
1709 canonicalise_predref(Name/Arity, PI, Options0, Options).
1710
1711
1716
1717pred_head(Var) -->
1718 { var(Var),
1719 !,
1720 instantiation_error(Var)
1721 }.
1722pred_head(//(Head)) -->
1723 !,
1724 pred_head(Head),
1725 html(//).
1726pred_head(M:Head) -->
1727 html([span(class=module, M), :]),
1728 pred_head(Head).
1729pred_head(Head) -->
1730 { atom(Head) },
1731 !,
1732 html(b(class=pred, Head)).
1733pred_head(Head) --> 1734 { Head =.. [Functor,Left,Right],
1735 is_op_type(Functor, infix)
1736 },
1737 !,
1738 html([ var(class=arglist, \pred_arg(Left, 1)),
1739 ' ', b(class=pred, Functor), ' ',
1740 var(class=arglist, \pred_arg(Right, 2))
1741 ]).
1742pred_head(Head) --> 1743 { Head =.. [Functor,Arg],
1744 is_op_type(Functor, prefix)
1745 },
1746 !,
1747 html([ b(class=pred, Functor), ' ',
1748 var(class=arglist, \pred_arg(Arg, 1))
1749 ]).
1750pred_head(Head) --> 1751 { Head =.. [Functor,Arg],
1752 is_op_type(Functor, postfix)
1753 },
1754 !,
1755 html([ var(class=arglist, \pred_arg(Arg, 1)),
1756 ' ', b(class=pred, Functor)
1757 ]).
1758pred_head({Head}) -->
1759 !,
1760 html([ b(class=pred, '{'),
1761 var(class=arglist,
1762 \pred_args([Head], 1)),
1763 b(class=pred, '}')
1764 ]).
1765pred_head(Head) --> 1766 { Head =.. [Functor|Args] },
1767 html([ b(class=pred, Functor),
1768 var(class=arglist,
1769 [ '(', \pred_args(Args, 1), ')' ])
1770 ]).
1771
1776
1777is_op_type(Functor, Type) :-
1778 current_op(_Pri, F, Functor),
1779 op_type(F, Type).
1780
1781op_type(fx, prefix).
1782op_type(fy, prefix).
1783op_type(xf, postfix).
1784op_type(yf, postfix).
1785op_type(xfx, infix).
1786op_type(xfy, infix).
1787op_type(yfx, infix).
1788op_type(yfy, infix).
1789
1790
1791pred_args([], _) -->
1792 [].
1793pred_args([H|T], I) -->
1794 pred_arg(H, I),
1795 ( {T==[]}
1796 -> []
1797 ; html(', '),
1798 { I2 is I + 1 },
1799 pred_args(T, I2)
1800 ).
1801
1802pred_arg(Var, I) -->
1803 { var(Var) },
1804 !,
1805 html(['Arg', I]).
1806pred_arg(...(Term), I) -->
1807 !,
1808 pred_arg(Term, I),
1809 html('...').
1810pred_arg(Term, I) -->
1811 { Term =.. [Ind,Arg],
1812 mode_indicator(Ind)
1813 },
1814 !,
1815 html([Ind, \pred_arg(Arg, I)]).
1816pred_arg(Arg:Type, _) -->
1817 !,
1818 html([\argname(Arg), :, \argtype(Type)]).
1819pred_arg(Arg, _) -->
1820 argname(Arg).
1821
1822argname('$VAR'(Name)) -->
1823 !,
1824 html(Name).
1825argname(Name) -->
1826 !,
1827 html(Name).
1828
1829argtype(Term) -->
1830 { format(string(S), '~W',
1831 [ Term,
1832 [ quoted(true),
1833 numbervars(true)
1834 ]
1835 ]) },
1836 html(S).
1837
1838pred_det(unknown) -->
1839 [].
1840pred_det(Det) -->
1841 html([' is ', b(class=det, Det)]).
1842
1843
1849
1850term(_, Atom, []) -->
1851 { atomic(Atom),
1852 !,
1853 format(string(S), '~W', [Atom,[quoted(true)]])
1854 },
1855 html(span(class=functor, S)).
1856term(_, Key:Type, [TypeName=Type]) -->
1857 { atomic(Key)
1858 },
1859 !,
1860 html([span(class='pl-key', Key), :, span(class('pl-var'), TypeName)]).
1861term(_, Term, Bindings) -->
1862 { is_mode(Term is det), 1863 bind_vars(Bindings)
1864 },
1865 !,
1866 pred_head(Term).
1867term(_, Term, Bindings) -->
1868 term(Term,
1869 [ variable_names(Bindings),
1870 quoued(true)
1871 ]).
1872
1873
1874 1877
1888
1889predref(Term) -->
1890 { catch(nb_getval(pldoc_options, Options), _, Options = []) },
1891 predref(Term, Options).
1892
1893predref(Obj, Options) -->
1894 { Obj = _:_,
1895 doc_comment(Obj, File:_Line, _, _),
1896 ( ( option(files(Map), Options)
1897 -> memberchk(file(File,_), Map)
1898 ; true
1899 )
1900 -> object_href(Obj, HREF, Options)
1901 ; manref(Obj, HREF, Options)
1902 )
1903 },
1904 !,
1905 html(a(href(HREF), \object_name(Obj, [qualify(true)|Options]))).
1906predref(M:Term, Options) -->
1907 !,
1908 predref(Term, M, Options).
1909predref(Term, Options) -->
1910 predref(Term, _, Options).
1911
1912predref(Name/Arity, _, Options) --> 1913 { prolog:doc_object_summary(Name/Arity, manual, _, _),
1914 !,
1915 manref(Name/Arity, HREF, Options)
1916 },
1917 html(a([class=builtin, href=HREF], [Name, /, Arity])).
1918predref(Name/Arity, _, Options) --> 1919 { option(prefer(manual), Options),
1920 prolog:doc_object_summary(Name/Arity, Category, _, _),
1921 !,
1922 manref(Name/Arity, HREF, Options)
1923 },
1924 html(a([class=Category, href=HREF], [Name, /, Arity])).
1925predref(Obj, Module, Options) --> 1926 { doc_comment(Module:Obj, File:_Line, _, _),
1927 ( option(files(Map), Options)
1928 -> memberchk(file(File,_), Map)
1929 ; true
1930 )
1931 },
1932 !,
1933 object_ref(Module:Obj, Options).
1934predref(Name/Arity, Module, Options) -->
1935 { \+ option(files(_), Options),
1936 pred_href(Name/Arity, Module, HREF)
1937 },
1938 !,
1939 html(a(href=HREF, [Name, /, Arity])).
1940predref(Name//Arity, Module, Options) -->
1941 { \+ option(files(_), Options),
1942 PredArity is Arity + 2,
1943 pred_href(Name/PredArity, Module, HREF)
1944 },
1945 !,
1946 html(a(href=HREF, [Name, //, Arity])).
1947predref(PI, _, Options) --> 1948 { canonical_pi(PI, CPI, HTML),
1949 ( option(files(_), Options)
1950 -> Category = extmanual
1951 ; prolog:doc_object_summary(CPI, Category, _, _)
1952 ),
1953 manref(CPI, HREF, Options)
1954 },
1955 html(a([class=Category, href=HREF], HTML)).
1956predref(PI, _, _Options) -->
1957 { canonical_pi(PI, _CPI, HTML)
1958 },
1959 !,
1960 html(span(class=undef, HTML)).
1961predref(Callable, Module, Options) -->
1962 { callable(Callable),
1963 functor(Callable, Name, Arity)
1964 },
1965 predref(Name/Arity, Module, Options).
1966
1967canonical_pi(Name/Arity, Name/Arity, [Name, /, Arity]) :-
1968 atom(Name), integer(Arity),
1969 !.
1970canonical_pi(Name//Arity, Name/Arity2, [Name, //, Arity]) :-
1971 atom(Name), integer(Arity),
1972 !,
1973 Arity2 is Arity+2.
1974
1978
1979nopredref(PI) -->
1980 { canonical_pi(PI, _CPI, HTML)
1981 },
1982 !,
1983 html(span(class=nopredref, HTML)).
1984
1990
1991flagref(Flag) -->
1992 html(code(Flag)).
1993
1998
1999cite(Citations) -->
2000 html('['), citations(Citations), html(']').
2001
2002citations([]) --> [].
2003citations([H|T]) -->
2004 citation(H),
2005 ( {T==[]}
2006 -> []
2007 ; [';'],
2008 citations(T)
2009 ).
2010
2011citation(H) -->
2012 html([@,H]).
2013
2014
2019
2020manref(PI, HREF, Options) :-
2021 predname(PI, PredName),
2022 ( option(files(_Map), Options)
2023 -> option(man_server(Server), Options,
2024 'http://www.swi-prolog.org/pldoc'),
2025 uri_components(Server, Comp0),
2026 uri_data(path, Comp0, Path0),
2027 directory_file_path(Path0, man, Path),
2028 uri_data(path, Comp0, Path, Components),
2029 uri_query_components(Query, [predicate=PredName]),
2030 uri_data(search, Components, Query),
2031 uri_components(HREF, Components)
2032 ; http_link_to_id(pldoc_man, [predicate=PredName], HREF)
2033 ).
2034
2035predname(Name/Arity, PredName) :-
2036 !,
2037 format(atom(PredName), '~w/~d', [Name, Arity]).
2038predname(Module:Name/Arity, PredName) :-
2039 !,
2040 format(atom(PredName), '~w:~w/~d', [Module, Name, Arity]).
2041
2042
2053
2054pred_href(Name/Arity, Module, HREF) :-
2055 format(string(FragmentId), '~w/~d', [Name, Arity]),
2056 uri_data(fragment, Components, FragmentId),
2057 functor(Head, Name, Arity),
2058 ( catch(relative_file(Module:Head, File), _, fail)
2059 -> uri_data(path, Components, File),
2060 uri_components(HREF, Components)
2061 ; in_file(Module:Head, File)
2062 -> ( current_prolog_flag(home, SWI),
2063 sub_atom(File, 0, _, _, SWI),
2064 prolog:doc_object_summary(Name/Arity, packages, _, _)
2065 -> http_link_to_id(pldoc_man, [predicate=FragmentId], HREF)
2066 ; http_location_by_id(pldoc_doc, DocHandler),
2067 atom_concat(DocHandler, File, Path),
2068 uri_data(path, Components, Path),
2069 uri_components(HREF, Components)
2070 )
2071 ).
2072
2073relative_file(Head, '') :-
2074 b_getval(pldoc_file, CurrentFile), CurrentFile \== [],
2075 in_file(Head, CurrentFile),
2076 !.
2077relative_file(Head, RelFile) :-
2078 b_getval(pldoc_file, CurrentFile), CurrentFile \== [],
2079 in_file(Head, DefFile),
2080 relative_file_name(DefFile, CurrentFile, RelFile).
2081
2085
2086pred_source_href(Name/Arity, Module, HREF) :-
2087 format(string(FragmentId), '~w/~d', [Name, Arity]),
2088 uri_data(fragment, Components, FragmentId),
2089 uri_query_components(Query, [show=src]),
2090 uri_data(search, Components, Query),
2091 functor(Head, Name, Arity),
2092 ( catch(relative_file(Module:Head, File), _, fail)
2093 -> uri_data(path, Components, File),
2094 uri_components(HREF, Components)
2095 ; in_file(Module:Head, File0)
2096 -> insert_alias(File0, File),
2097 http_location_by_id(pldoc_doc, DocHandler),
2098 atom_concat(DocHandler, File, Path),
2099 uri_data(path, Components, Path),
2100 uri_components(HREF, Components)
2101 ).
2102
2103
2109
2110object_ref([], _) -->
2111 !,
2112 [].
2113object_ref([H|T], Options) -->
2114 !,
2115 object_ref(H, Options),
2116 ( {T == []}
2117 -> html(', '),
2118 object_ref(T, Options)
2119 ; []
2120 ).
2121object_ref(Obj, Options) -->
2122 { object_href(Obj, HREF, Options)
2123 },
2124 html(a(href(HREF), \object_name(Obj, Options))).
2125
2130
2131object_href(Obj, HREF) :-
2132 object_href(Obj, HREF, []).
2133
2134object_href(M:PI0, HREF, Options) :-
2135 option(files(Map), Options),
2136 ( module_property(M, file(File))
2137 -> true
2138 ; xref_module(File, M)
2139 ),
2140 memberchk(file(File, DocFile), Map),
2141 !,
2142 file_base_name(DocFile, LocalFile), 2143 expand_pi(PI0, PI),
2144 term_to_string(PI, PIS),
2145 uri_data(path, Components, LocalFile),
2146 uri_data(fragment, Components, PIS),
2147 uri_components(HREF, Components).
2148object_href(file(File), HREF, _Options) :-
2149 doc_file_href(File, HREF),
2150 !.
2151object_href(directory(Dir), HREF, _Options) :-
2152 directory_file_path(Dir, 'index.html', Index),
2153 doc_file_href(Index, HREF),
2154 !.
2155object_href(Obj, HREF, _Options) :-
2156 prolog:doc_object_href(Obj, HREF),
2157 !.
2158object_href(Obj0, HREF, _Options) :-
2159 localise_object(Obj0, Obj),
2160 term_to_string(Obj, String),
2161 http_link_to_id(pldoc_object, [object=String], HREF).
2162
2163expand_pi(Name//Arity0, Name/Arity) :-
2164 !,
2165 Arity is Arity0+2.
2166expand_pi(PI, PI).
2167
2168
2173
2174localise_object(Obj0, Obj) :-
2175 prolog:doc_canonical_object(Obj0, Obj),
2176 !.
2177localise_object(Obj, Obj).
2178
2179
2184
2185term_to_string(Term, String) :-
2186 State = state(-),
2187 ( numbervars(Term, 0, _, [singletons(true)]),
2188 with_output_to(string(String),
2189 write_term(Term,
2190 [ numbervars(true),
2191 quoted(true)
2192 ])),
2193 nb_setarg(1, State, String),
2194 fail
2195 ; arg(1, State, String)
2196 ).
2197
2209
2210object_name(Obj, Options) -->
2211 { option(style(Style), Options, inline)
2212 },
2213 object_name(Style, Obj, Options).
2214
2215object_name(title, Obj, Options) -->
2216 { merge_options(Options, [secref_style(title)], Options1) },
2217 prolog:doc_object_link(Obj, Options1),
2218 !.
2219object_name(inline, Obj, Options) -->
2220 prolog:doc_object_link(Obj, Options),
2221 !.
2222object_name(title, f(Name/Arity), _Options) -->
2223 !,
2224 html(['Function ', Name, /, Arity]).
2225object_name(inline, f(Name/Arity), _Options) -->
2226 !,
2227 html([Name, /, Arity]).
2228object_name(Style, PI, Options) -->
2229 { is_pi(PI) },
2230 !,
2231 pi(Style, PI, Options).
2232object_name(inline, Module:module(_Title), _) -->
2233 !,
2234 { module_property(Module, file(File)),
2235 file_base_name(File, Base)
2236 },
2237 !,
2238 html(Base).
2239object_name(title, Module:module(Title), _) -->
2240 { module_property(Module, file(File)),
2241 file_base_name(File, Base)
2242 },
2243 !,
2244 html([Base, ' -- ', Title]).
2245object_name(title, file(File), _) -->
2246 { module_property(Module, file(File)),
2247 doc_comment(Module:module(Title), _, _, _),
2248 !,
2249 file_base_name(File, Base)
2250 },
2251 html([Base, ' -- ', Title]).
2252object_name(_, file(File), _) -->
2253 { file_base_name(File, Base) },
2254 html(Base).
2255object_name(_, directory(Dir), _) -->
2256 { file_base_name(Dir, Base) },
2257 html(Base).
2258object_name(_, module(Title), _Options) -->
2259 { print_message(warning,
2260 pldoc(module_comment_outside_module(Title)))
2261 }.
2262
2263pi(title, PI, Options) -->
2264 pi_type(PI),
2265 pi(PI, Options).
2266pi(inline, PI, Options) -->
2267 pi(PI, Options).
2268
2269pi(M:PI, Options) -->
2270 !,
2271 ( { option(qualify(true), Options) }
2272 -> html([span(class(module), M), :])
2273 ; []
2274 ),
2275 pi(PI, Options).
2276pi(Name/Arity, _) -->
2277 !,
2278 html([Name, /, \arity(Arity)]).
2279pi(Name//Arity, _) -->
2280 html([Name, //, \arity(Arity)]).
2281
2282arity(Arity) -->
2283 { var(Arity) },
2284 !,
2285 html('_').
2286arity(Arity) -->
2287 html(Arity).
2288
2289pi_type(_:PI) -->
2290 !,
2291 pi_type(PI).
2292pi_type(_/_) -->
2293 html(['Predicate ']).
2294pi_type(_//_) -->
2295 html(['Grammar rule ']).
2296
2297
2298
2306
2307in_file(Module:Head, File) :-
2308 !,
2309 distinct(File, in_file(Module, Head, File)).
2310in_file(Head, File) :-
2311 distinct(File, in_file(_, Head, File)).
2312
2313in_file(Module, Head, File) :-
2314 var(Module),
2315 ( predicate_property(system:Head, foreign)
2316 -> !,
2317 fail
2318 ; predicate_property(system:Head, file(File)),
2319 \+ system_arithmetic_function(Head)
2320 -> !
2321 ; predicate_property(Head, autoload(File0))
2322 -> !,
2323 file_name_extension(File0, pl, File)
2324 ; exported_from(Module, Head, File),
2325 module_property(Module, class(library))
2326 ).
2327in_file(Module, Head, File) :-
2328 nonvar(Module),
2329 predicate_property(Module:Head, file(File)),
2330 \+ predicate_property(Module:Head, imported_from(_)).
2331in_file(Module, Head, File) :-
2332 xref_defined(File, Head, How),
2333 xref_current_source(File),
2334 atom(File), 2335 xref_module(File, Module),
2336 How \= imported(_From).
2337in_file(Module, Head, File) :-
2338 exported_from(Module, Head, File).
2339in_file(Module, Head, File) :-
2340 predicate_property(Module:Head, file(File)),
2341 \+ predicate_property(Module:Head, imported_from(_)).
2342in_file(Module, Head, File) :-
2343 current_module(Module),
2344 source_file(Module:Head, File).
2345
2346exported_from(Module, Head, File) :-
2347 distinct(Primary,
2348 ( predicate_property(Module:Head, exported),
2349 ( predicate_property(Module:Head, imported_from(Primary))
2350 -> true
2351 ; Primary = Module
2352 ))),
2353 module_property(Primary, file(File)).
2354
2355:- multifile
2356 arithmetic:evaluable/2. 2357
2358system_arithmetic_function(Head) :-
2359 functor(Head, Name, Arity),
2360 FArith is Arity-1,
2361 FArith >= 0,
2362 functor(FHead, Name, FArith),
2363 arithmetic:evaluable(FHead, system).
2364
2393
2394file(File) -->
2395 file(File, []).
2396
2397file(File, Options) -->
2398 { catch(nb_getval(pldoc_options, GenOptions), _, GenOptions = []),
2399 merge_options(Options, GenOptions, FinalOptions)
2400 },
2401 link_file(File, FinalOptions),
2402 !.
2403file(File, Options) -->
2404 { option(edit_handler(Handler), Options),
2405 http_current_request(Request),
2406 memberchk(path(Path), Request),
2407 absolute_file_name(File, Location,
2408 [ relative_to(Path)
2409 ]),
2410 http_link_to_id(Handler, [location(Location)], HREF),
2411 format(atom(Title), 'Click to create ~w', [File])
2412 },
2413 html(a([href(HREF), class(nofile), title(Title)], File)).
2414file(File, _) -->
2415 html(code(class(nofile), File)).
2416
2417link_file(File, Options) -->
2418 { file_href(File, HREF, Options),
2419 option(label(Label), Options, File),
2420 option(class(Class), Options, file)
2421 },
2422 html(a([class(Class), href(HREF)], Label)).
2423
2427
2428file_href(_, HREF, Options) :-
2429 option(href(HREF), Options),
2430 !.
2431file_href(File, HREF, Options) :-
2432 file_href_real(File, HREF0, Options),
2433 map_extension(HREF0, HREF, Options).
2434
2440
2441map_extension(HREF0, HREF, Options) :-
2442 option(map_extension(Map), Options),
2443 file_name_extension(Base, Old, HREF0),
2444 memberchk(Old-New, Map),
2445 !,
2446 file_name_extension(Base, New, HREF).
2447map_extension(HREF, HREF, _).
2448
2449
2450file_href_real(File, HREF, Options) :-
2451 ( option(absolute_path(Path), Options)
2452 ; existing_linked_file(File, Path)
2453 ),
2454 !,
2455 ( option(files(Map), Options),
2456 memberchk(file(Path, LinkFile), Map)
2457 -> true
2458 ; LinkFile = Path
2459 ),
2460 file_href(LinkFile, HREF).
2461file_href_real(File, HREF, _) :-
2462 directory_alias(Alias),
2463 Term =.. [Alias,File],
2464 absolute_file_name(Term, _,
2465 [ access(read),
2466 file_errors(fail)
2467 ]),
2468 !,
2469 http_absolute_location(Term, HREF, []).
2470
2471directory_alias(icons).
2472directory_alias(css).
2473
2474
2481
2482file_href(Path, HREF) :- 2483 source_file(Path),
2484 !,
2485 doc_file_href(Path, HREF).
2486file_href(Path, HREF) :-
2487 ( nb_current(pldoc_output, CFile)
2488 ; nb_current(pldoc_file, CFile)
2489 ),
2490 CFile \== [],
2491 !,
2492 relative_file_name(Path, CFile, HREF).
2493file_href(Path, Path).
2494
2495
2500
2501existing_linked_file(File, Path) :-
2502 catch(b_getval(pldoc_file, CurrentFile), _, fail),
2503 CurrentFile \== [],
2504 absolute_file_name(File, Path,
2505 [ relative_to(CurrentFile),
2506 access(read),
2507 file_errors(fail)
2508 ]).
2509
2510
2517
2518include(PI, predicate, _) -->
2519 !,
2520 ( html_tokens_for_predicates(PI, [])
2521 -> []
2522 ; html(['[[', \predref(PI), ']]'])
2523 ).
2524include(File, image, Options) -->
2525 { file_name_extension(_, svg, File),
2526 file_href(File, HREF, Options),
2527 !,
2528 include(image_attribute, Options, Attrs0),
2529 merge_options(Attrs0,
2530 [ alt(File),
2531 data(HREF),
2532 type('image/svg+xml')
2533 ], Attrs)
2534 },
2535 ( { option(caption(Caption), Options) }
2536 -> html(div(class(figure),
2537 [ div(class(image), object(Attrs, [])),
2538 div(class(caption), Caption)
2539 ]))
2540 ; html(object(Attrs, []))
2541 ).
2542include(File, image, Options) -->
2543 { file_href(File, HREF, Options),
2544 !,
2545 include(image_attribute, Options, Attrs0),
2546 merge_options(Attrs0,
2547 [ alt(File),
2548 border(0),
2549 src(HREF)
2550 ], Attrs)
2551 },
2552 ( { option(caption(Caption), Options) }
2553 -> html(div(class(figure),
2554 [ div(class(image), img(Attrs)),
2555 div(class(caption), Caption)
2556 ]))
2557 ; html(img(Attrs))
2558 ).
2559include(File, wiki, _Options) --> 2560 { access_file(File, read),
2561 !,
2562 read_file_to_codes(File, String, []),
2563 wiki_codes_to_dom(String, [], DOM)
2564 },
2565 html(DOM).
2566include(File, _Type, Options) -->
2567 link_file(File, Options),
2568 !.
2569include(File, _, _) -->
2570 html(code(class(nofile), ['[[',File,']]'])).
2571
2572image_attribute(src(_)).
2573image_attribute(alt(_)).
2574image_attribute(title(_)).
2575image_attribute(align(_)).
2576image_attribute(width(_)).
2577image_attribute(height(_)).
2578image_attribute(border(_)).
2579image_attribute(class(_)).
2580image_attribute(style(_)).
2581
2582
2592
2593html_tokens_for_predicates([], _Options) -->
2594 [].
2595html_tokens_for_predicates([H|T], Options) -->
2596 !,
2597 html_tokens_for_predicates(H, Options),
2598 html_tokens_for_predicates(T, Options).
2599html_tokens_for_predicates(PI, Options) -->
2600 { PI = _:_/_,
2601 !,
2602 ( doc_comment(PI, Pos, _Summary, Comment)
2603 -> true
2604 ; Comment = ''
2605 )
2606 },
2607 object(PI, [Pos-Comment], [dl], _, Options).
2608html_tokens_for_predicates(Spec, Options) -->
2609 { findall(PI, documented_pi(Spec, PI), List),
2610 List \== [], !
2611 },
2612 html_tokens_for_predicates(List, Options).
2613html_tokens_for_predicates(Spec, Options) -->
2614 man_page(Spec,
2615 [ links(false), 2616 navtree(false), 2617 footer(false), 2618 synopsis(false) 2619 | Options
2620 ]).
2621
2622
2623documented_pi(Spec, PI) :-
2624 generalise_spec(Spec, PI),
2625 doc_comment(PI, _Pos, _Summary, _Comment).
2626
2627generalise_spec(Name/Arity, _M:Name/Arity).
2628generalise_spec(Name//Arity, _M:Name//Arity).
2629
2630
2631 2634
2635
2639
2640doc_for_wiki_file(FileSpec, Options) :-
2641 absolute_file_name(FileSpec, File,
2642 [ access(read)
2643 ]),
2644 read_file_to_codes(File, String, []),
2645 b_setval(pldoc_file, File),
2646 call_cleanup(reply_wiki_page(File, String, Options),
2647 nb_delete(pldoc_file)).
2648
2649reply_wiki_page(File, String, Options) :-
2650 wiki_codes_to_dom(String, [], DOM0),
2651 title(DOM0, File, Title),
2652 insert_edit_button(DOM0, File, DOM, Options),
2653 reply_html_page(pldoc(wiki),
2654 title(Title),
2655 [ \html_requires(pldoc)
2656 | DOM
2657 ]).
2658
2659title(DOM, _, Title) :-
2660 sub_term(h1(_,Title), DOM),
2661 !.
2662title(_, File, Title) :-
2663 file_base_name(File, Title).
2664
2665insert_edit_button(DOM, _, DOM, Options) :-
2666 option(edit(false), Options, false),
2667 !.
2668insert_edit_button([h1(Attrs,Title)|DOM], File,
2669 [h1(Attrs,[ span(style('float:right'),
2670 \edit_button(File, [edit(true)]))
2671 | Title
2672 ])|DOM], _) :- !.
2673insert_edit_button(DOM, File,
2674 [ h1(class(wiki),
2675 [ span(style('float:right'),
2676 \edit_button(File, [edit(true)]))
2677 ])
2678 | DOM
2679 ], _).
2680
2681
2682 2685
2689
2690mode_anchor_name(Var, _) :-
2691 var(Var),
2692 !,
2693 instantiation_error(Var).
2694mode_anchor_name(mode(Head, _), Anchor) :-
2695 !,
2696 mode_anchor_name(Head, Anchor).
2697mode_anchor_name(Head is _Det, Anchor) :-
2698 !,
2699 mode_anchor_name(Head, Anchor).
2700mode_anchor_name(Head, Anchor) :-
2701 pred_anchor_name(Head, _, Anchor).
2702
2703
2707
2708pred_anchor_name(//(Head), Name/Arity, Anchor) :-
2709 !,
2710 functor(Head, Name, DCGArity),
2711 Arity is DCGArity+2,
2712 format(atom(Anchor), '~w/~d', [Name, Arity]).
2713pred_anchor_name(Head, Name/Arity, Anchor) :-
2714 functor(Head, Name, Arity),
2715 format(atom(Anchor), '~w/~d', [Name, Arity]).
2716
2717:- multifile prolog:message//1. 2718
2719prolog:message(pldoc(module_comment_outside_module(Title))) -->
2720 [ 'PlDoc comment <module> ~w does not appear in a module'-[Title] ]