1:- module(pls_index_docs, [
2 index_docs/4,
3 get_docs/2
4
5]). 6
7:- use_module(library(dcg/basics)). 8
9:- use_module(library(pldoc)). 10:- use_module(library(pldoc/doc_process)). 11:- use_module(library(pldoc/doc_wiki)). 12
13:- use_module(documents). 14
17index_docs(URI, PredicateOrKey, Range, CommentPos) :-
18 ( filter_for_docs(Range, CommentPos, DocLine, Docs)
19 -> add_document_item(URI, Range, docs(PredicateOrKey, DocLine, Docs))
20 ; true
21 ),
22 !.
30filter_for_docs(Range, CommentPos, DocLine, Docs) :-
31 findall(
32 Line-Comment,
33 (
34 member(Pos-Comment, CommentPos),
35 stream_position_data(line_count, Pos, LineNo),
36 Line is LineNo - 1,
37 string_lines(Comment, Lines),
38 length(Lines, LineCount),
39 Start = Range.start.line,
40 Start is Line + LineCount
41 ),
42 Comments
43 ),
44 Comments = [DocLine-Docs].
45
46get_docs(Predicate, Docs) :-
47 get_document_item(_URI, _Range, docs(Predicate, _DocLine, Comment)),
48 comment_markup(Predicate, Comment, Docs),
49 !.
50
51 get_docs(Predicate, Docs) :-
52 swritef(Docs, "### %w\n*No documentation available.*",[Predicate]).
53
(Predicate, Comment, Markup) :-
55 ( is_structured_comment(Comment, Prefixes)
56 -> true
57 ; Prefixes = []
58 ),
59 string_codes(Comment, Codes),
60 indented_lines(Codes, Prefixes, Lines),
61 findall(
62 String,
63 (
64 member(_Indent-Indented, Lines),
65 string_codes(Line, Indented),
66 format_doc_line(Line,String)
67 ),
68 Strings
69 ),
70 with_output_to(string(Markup),
71 (
72 writef("### %w\n",[Predicate]),
73 forall(member(String, Strings),writeln(String))
74 )
75 ).
76
77format_doc_line(Line, String) :-
78 79 mode(Line, Mode),
80 swritef(String, "*%w*\n",[Mode]),
81 !.
82
83format_doc_line(Line, String) :-
84 comment(Line, Comment),
85 swritef(String, "%w\n",[Comment]),
86 !.
87
88format_doc_line(Line, Line).
89
90mode(Line, Mode) :-
91 string_codes(Line, Codes),
92 phrase(mode(Mode),Codes).
93
94mode(Mode) -->
95 "!",
96 whites,
97 string(Codes),
98 {string_codes(Mode, Codes)}.
99
100mode(Mode) -->
101 "%%",
102 whites,
103 string(Codes),
104 {string_codes(Mode, Codes)}.
105
(Line, Comment) :-
107 string_codes(Line, Codes),
108 phrase(comment(Comment), Codes).
109
(Comment) -->
111 "%",
112 whites,
113 string(Codes),
114 {string_codes(Comment, Codes)}