|
1 | 1 | open Packages
|
2 |
| - |
3 |
| -let pkg_landing_page_content pkg = |
4 |
| - let title = Format.sprintf "{0 %s}\n" pkg.name in |
5 |
| - let documentation = |
6 |
| - match pkg.mlds with |
7 |
| - | _ :: _ -> |
8 |
| - Format.sprintf |
9 |
| - "{1 Documentation pages}\n\n{{!/%s/doc/index}Documentation for %s}\n" |
10 |
| - pkg.name pkg.name |
11 |
| - | [] -> "" |
12 |
| - in |
13 |
| - let libraries = |
14 |
| - match pkg.libraries with |
15 |
| - | [] -> "" |
16 |
| - | _ :: _ -> |
17 |
| - Format.sprintf "{1 Libraries}\n\n{{!/%s/lib/index}Libraries for %s}\n" |
18 |
| - pkg.name pkg.name |
19 |
| - in |
20 |
| - title ^ documentation ^ libraries |
21 |
| - |
22 |
| -let library_landing_page_content lib = |
23 |
| - let title = Format.sprintf "{0 %s}\n" lib.lib_name in |
24 |
| - let s_of_module m = |
25 |
| - if m.m_hidden then None |
26 |
| - else Some (Format.sprintf "- {!%s}" m.Packages.m_name) |
27 |
| - in |
28 |
| - let modules = |
29 |
| - lib.modules |> List.filter_map s_of_module |> String.concat "\n" |
30 |
| - in |
31 |
| - title ^ modules |
32 |
| - |
33 |
| -let libraries_landing_page_content pkg = |
34 |
| - let title = Format.sprintf "{0 %s}\n" pkg.name in |
35 |
| - let s_of_lib (lib : Packages.libty) = |
36 |
| - Format.sprintf "- {{!/%s/%s/index}%s}" pkg.name lib.lib_name lib.lib_name |
37 |
| - in |
38 |
| - let libraries = pkg.libraries |> List.map s_of_lib |> String.concat "\n" in |
39 |
| - title ^ libraries |
40 |
| - |
41 |
| -let list_packages_content all = |
42 |
| - let sorted_packages = |
43 |
| - all |> List.sort (fun n1 n2 -> String.compare n1.name n2.name) |
44 |
| - in |
45 |
| - let title = "{0 List of all packages}\n" in |
46 |
| - let s_of_pkg pkg = |
47 |
| - Format.sprintf "- {{!/__driver/%s/index}%s}" pkg.name pkg.name |
48 |
| - in |
49 |
| - let pkg_ul = sorted_packages |> List.map s_of_pkg |> String.concat "\n" in |
50 |
| - title ^ pkg_ul |
51 |
| - |
| 2 | +open Odoc_unit |
52 | 3 | let write_file file content = Bos.OS.File.write file content |> Result.get_ok
|
53 | 4 |
|
54 |
| -let of_package ~mld_dir ~odoc_dir ~odocl_dir ~output_dir pkg = |
55 |
| - let make_unit rel_path ~content ?(include_dirs = []) ~pkgname ~pkg_args () = |
56 |
| - let input_file = Fpath.(mld_dir // rel_path / "index.mld") in |
57 |
| - let odoc_file = Fpath.(odoc_dir // rel_path / "page-index.odoc") in |
58 |
| - let odocl_file = Fpath.(odocl_dir // rel_path / "page-index.odocl") in |
59 |
| - let () = write_file input_file content in |
60 |
| - let parent_id = rel_path |> Odoc.Id.of_fpath in |
61 |
| - let open Odoc_unit in |
62 |
| - { |
63 |
| - parent_id; |
64 |
| - odoc_dir; |
65 |
| - input_file; |
66 |
| - output_dir; |
67 |
| - odoc_file; |
68 |
| - odocl_file; |
69 |
| - pkg_args; |
70 |
| - pkgname; |
71 |
| - include_dirs; |
72 |
| - index = None; |
73 |
| - kind = `Mld; |
74 |
| - } |
75 |
| - in |
76 |
| - let library_list_page = |
77 |
| - let open Odoc_unit in |
78 |
| - let content = libraries_landing_page_content pkg in |
79 |
| - let rel_path = Fpath.(v pkg.name / "lib") in |
80 |
| - let pkg_args = |
81 |
| - { pages = [ (pkg.name, Fpath.( // ) odoc_dir rel_path) ]; libs = [] } |
82 |
| - in |
83 |
| - make_unit rel_path ~content ~pkgname:pkg.name ~pkg_args () |
84 |
| - in |
85 |
| - let library_landing_pages = |
86 |
| - let do_ lib = |
87 |
| - let open Odoc_unit in |
88 |
| - let content = library_landing_page_content lib in |
89 |
| - let rel_path = Fpath.(v pkg.name / "lib" / lib.lib_name) in |
90 |
| - let pkg_args = |
91 |
| - { pages = [ (pkg.name, Fpath.( // ) odoc_dir rel_path) ]; libs = [] } |
92 |
| - in |
93 |
| - let include_dirs = [ Fpath.(odoc_dir // rel_path) ] in |
94 |
| - make_unit rel_path ~content ~pkgname:pkg.name ~include_dirs ~pkg_args () |
95 |
| - in |
96 |
| - List.map do_ pkg.libraries |
97 |
| - in |
98 |
| - let package_landing_page = |
99 |
| - let open Odoc_unit in |
100 |
| - let content = pkg_landing_page_content pkg in |
101 |
| - let rel_path = Fpath.v pkg.name in |
102 |
| - let pkg_args = |
103 |
| - { pages = [ (pkg.name, Fpath.( // ) odoc_dir rel_path) ]; libs = [] } |
104 |
| - in |
105 |
| - make_unit rel_path ~content ~pkgname:pkg.name ~pkg_args () |
106 |
| - in |
107 |
| - package_landing_page :: library_list_page :: library_landing_pages |
108 |
| - |
109 |
| -let of_packages ~mld_dir ~odoc_dir ~odocl_dir ~output_dir all = |
110 |
| - let content = list_packages_content all in |
111 |
| - let rel_path = Fpath.v "./" in |
| 5 | +let make_unit ~odoc_dir ~odocl_dir ~mld_dir ~output_dir rel_path ~content |
| 6 | + ?(include_dirs = []) ~pkgname ~pkg_args () = |
112 | 7 | let input_file = Fpath.(mld_dir // rel_path / "index.mld") in
|
| 8 | + let odoc_file = Fpath.(odoc_dir // rel_path / "page-index.odoc") in |
| 9 | + let odocl_file = Fpath.(odocl_dir // rel_path / "page-index.odocl") in |
113 | 10 | let () = write_file input_file content in
|
114 |
| - let open Odoc_unit in |
115 | 11 | let parent_id = rel_path |> Odoc.Id.of_fpath in
|
116 |
| - let pkgname = "__driver" in |
117 |
| - let pkg_args = |
118 |
| - { |
119 |
| - pages = |
120 |
| - (pkgname, Fpath.(odoc_dir // rel_path)) :: [] |
121 |
| - (* List.map (fun pkg -> (pkg.name, Fpath.(odoc_dir / pkg.name))) all *); |
122 |
| - libs = []; |
123 |
| - } |
124 |
| - in |
125 | 12 | {
|
126 | 13 | parent_id;
|
127 | 14 | odoc_dir;
|
128 | 15 | input_file;
|
129 | 16 | output_dir;
|
| 17 | + odoc_file; |
| 18 | + odocl_file; |
130 | 19 | pkg_args;
|
131 | 20 | pkgname;
|
132 |
| - odoc_file = Fpath.(odoc_dir // rel_path / "page-index.odoc"); |
133 |
| - odocl_file = Fpath.(odocl_dir // rel_path / "page-index.odocl"); |
134 |
| - include_dirs = []; |
| 21 | + include_dirs; |
135 | 22 | index = None;
|
136 | 23 | kind = `Mld;
|
137 | 24 | }
|
138 |
| - :: List.concat_map (of_package ~mld_dir ~odoc_dir ~odocl_dir ~output_dir) all |
139 | 25 |
|
140 |
| -(* let compile_list_packages odoc_dir all : compiled = *) |
141 |
| -(* let sorted_packages = *) |
142 |
| -(* all |> Util.StringMap.to_list *) |
143 |
| -(* |> List.sort (fun (n1, _) (n2, _) -> String.compare n1 n2) *) |
144 |
| -(* in *) |
145 |
| -(* let title = "{0 List of all packages}\n" in *) |
146 |
| -(* let s_of_pkg (name, _) = Format.sprintf "- {{!%s/index}%s}" name name in *) |
147 |
| -(* let pkg_ul = sorted_packages |> List.map s_of_pkg |> String.concat "\n" in *) |
148 |
| -(* let content = title ^ pkg_ul in *) |
149 |
| -(* let input_file = Fpath.( / ) odoc_dir "index.mld" in *) |
150 |
| -(* let () = Bos.OS.File.write input_file content |> Result.get_ok in *) |
151 |
| -(* Odoc.compile ~output_dir:odoc_dir ~input_file ~includes:Fpath.Set.empty *) |
152 |
| -(* ~parent_id:(Odoc.id_of_fpath (Fpath.v "./")); *) |
153 |
| -(* Atomic.incr Stats.stats.compiled_mlds; *) |
154 |
| -(* { *) |
155 |
| -(* m = Mld; *) |
156 |
| -(* odoc_output_dir = odoc_dir; *) |
157 |
| -(* odoc_file = Fpath.(odoc_dir / "page-index.odoc"); *) |
158 |
| -(* odocl_file = Fpath.(odoc_dir / "page-index.odocl"); *) |
159 |
| -(* include_dirs = Fpath.Set.empty; *) |
160 |
| -(* impl = None; *) |
161 |
| -(* pkg_args = { docs = [ ("_driver_pkg", odoc_dir) ]; libs = [] }; *) |
162 |
| -(* pkgname = { p_name = "_driver_pkg"; p_dir = Fpath.v "./" }; *) |
163 |
| -(* } *) |
| 26 | +module PackageLanding = struct |
| 27 | + let content pkg = |
| 28 | + let title = Format.sprintf "{0 %s}\n" pkg.name in |
| 29 | + let documentation = |
| 30 | + match pkg.mlds with |
| 31 | + | _ :: _ -> |
| 32 | + Format.sprintf |
| 33 | + "{1 Documentation pages}\n\n\ |
| 34 | + {{!/%s/doc/index}Documentation for %s}\n" |
| 35 | + pkg.name pkg.name |
| 36 | + | [] -> "" |
| 37 | + in |
| 38 | + let libraries = |
| 39 | + match pkg.libraries with |
| 40 | + | [] -> "" |
| 41 | + | _ :: _ -> |
| 42 | + Format.sprintf "{1 Libraries}\n\n{{!/%s/lib/index}Libraries for %s}\n" |
| 43 | + pkg.name pkg.name |
| 44 | + in |
| 45 | + title ^ documentation ^ libraries |
| 46 | + |
| 47 | + let page ~odoc_dir ~odocl_dir ~mld_dir ~output_dir ~pkg = |
| 48 | + let content = content pkg in |
| 49 | + let rel_path = Fpath.v pkg.name in |
| 50 | + let pkg_args = |
| 51 | + { pages = [ (pkg.name, Fpath.( // ) odoc_dir rel_path) ]; libs = [] } |
| 52 | + in |
| 53 | + make_unit ~odoc_dir ~odocl_dir ~mld_dir ~output_dir rel_path ~content |
| 54 | + ~pkgname:pkg.name ~pkg_args () |
| 55 | +end |
| 56 | + |
| 57 | +module PackageList = struct |
| 58 | + let content all = |
| 59 | + let sorted_packages = |
| 60 | + all |> List.sort (fun n1 n2 -> String.compare n1.name n2.name) |
| 61 | + in |
| 62 | + let title = "{0 List of all packages}\n" in |
| 63 | + let s_of_pkg pkg = |
| 64 | + Format.sprintf "- {{!/__driver/%s/index}%s}" pkg.name pkg.name |
| 65 | + in |
| 66 | + let pkg_ul = sorted_packages |> List.map s_of_pkg |> String.concat "\n" in |
| 67 | + title ^ pkg_ul |
| 68 | + |
| 69 | + let page ~mld_dir ~odoc_dir ~odocl_dir ~output_dir all = |
| 70 | + let content = content all in |
| 71 | + let rel_path = Fpath.v "./" in |
| 72 | + let pkgname = "__driver" in |
| 73 | + let pkg_args = |
| 74 | + { pages = [ (pkgname, Fpath.(odoc_dir // rel_path)) ]; libs = [] } |
| 75 | + in |
| 76 | + make_unit ~odoc_dir ~odocl_dir ~mld_dir ~output_dir ~content ~pkgname |
| 77 | + ~pkg_args rel_path () |
| 78 | +end |
| 79 | + |
| 80 | +module LibraryLanding = struct |
| 81 | + let content lib = |
| 82 | + let title = Format.sprintf "{0 %s}\n" lib.lib_name in |
| 83 | + let s_of_module m = |
| 84 | + if m.m_hidden then None |
| 85 | + else Some (Format.sprintf "- {!%s}" m.Packages.m_name) |
| 86 | + in |
| 87 | + let modules = |
| 88 | + lib.modules |> List.filter_map s_of_module |> String.concat "\n" |
| 89 | + in |
| 90 | + title ^ modules |
| 91 | + let page ~pkg ~odoc_dir ~odocl_dir ~mld_dir ~output_dir lib = |
| 92 | + let content = content lib in |
| 93 | + let rel_path = Fpath.(v pkg.name / "lib" / lib.lib_name) in |
| 94 | + let pkg_args = |
| 95 | + { pages = [ (pkg.name, Fpath.( // ) odoc_dir rel_path) ]; libs = [] } |
| 96 | + in |
| 97 | + let include_dirs = [ Fpath.(odoc_dir // rel_path) ] in |
| 98 | + make_unit ~odoc_dir ~odocl_dir ~mld_dir ~output_dir rel_path ~content |
| 99 | + ~pkgname:pkg.name ~include_dirs ~pkg_args () |
| 100 | +end |
164 | 101 |
|
165 |
| -(* let compile_landing_pages odoc_dir pkg : compiled list = *) |
166 |
| -(* let pkgname = pkg.Packages.pkgname in *) |
167 |
| -(* let driver_page ~odoc_file ~odocl_file ?(include_dirs = Fpath.Set.empty) () = *) |
168 |
| -(* let pkg_args = *) |
169 |
| -(* { *) |
170 |
| -(* docs = [ (pkgname.p_name, Fpath.( / ) odoc_dir pkgname.p_name) ]; *) |
171 |
| -(* libs = []; *) |
172 |
| -(* } *) |
173 |
| -(* in *) |
174 |
| -(* { *) |
175 |
| -(* m = Mld; *) |
176 |
| -(* odoc_output_dir = odoc_dir; *) |
177 |
| -(* odoc_file; *) |
178 |
| -(* odocl_file; *) |
179 |
| -(* include_dirs; *) |
180 |
| -(* impl = None; *) |
181 |
| -(* pkg_args; *) |
182 |
| -(* pkgname; *) |
183 |
| -(* } *) |
184 |
| -(* in *) |
185 |
| -(* let title = Format.sprintf "{0 %s}\n" in *) |
186 |
| -(* let compile ~content ~input_file ?(include_dirs = Fpath.Set.empty) ~parent_id *) |
187 |
| -(* () = *) |
188 |
| -(* let () = Bos.OS.File.write input_file content |> Result.get_ok in *) |
189 |
| -(* Odoc.compile ~output_dir:odoc_dir ~input_file ~includes:include_dirs *) |
190 |
| -(* ~parent_id; *) |
191 |
| -(* Atomic.incr Stats.stats.compiled_mlds; *) |
192 |
| -(* ( Fpath.(odoc_dir // Odoc.fpath_of_id parent_id / "page-index.odoc"), *) |
193 |
| -(* Fpath.(odoc_dir // Odoc.fpath_of_id parent_id / "page-index.odocl") ) *) |
194 |
| -(* in *) |
| 102 | +module PackageLibLanding = struct |
| 103 | + let content pkg = |
| 104 | + let title = Format.sprintf "{0 %s}\n" pkg.name in |
| 105 | + let s_of_lib (lib : Packages.libty) = |
| 106 | + Format.sprintf "- {{!/%s/%s/index}%s}" pkg.name lib.lib_name lib.lib_name |
| 107 | + in |
| 108 | + let libraries = pkg.libraries |> List.map s_of_lib |> String.concat "\n" in |
| 109 | + title ^ libraries |
195 | 110 |
|
196 |
| -(* let library_landing_page pkgname (lib : Packages.libty) : compiled = *) |
197 |
| -(* let libname = lib.lib_name in *) |
198 |
| -(* let parent_id = *) |
199 |
| -(* Fpath.(v pkgname.Packages.p_name / "lib" / libname) |> Odoc.id_of_fpath *) |
200 |
| -(* in *) |
201 |
| -(* let input_file = *) |
202 |
| -(* Fpath.(odoc_dir // Odoc.fpath_of_id parent_id / "index.mld") *) |
203 |
| -(* in *) |
204 |
| -(* let s_of_module m = Format.sprintf "- {!%s}" m.Packages.m_name in *) |
205 |
| -(* let modules = lib.modules |> List.map s_of_module |> String.concat "\n" in *) |
206 |
| -(* let content = title libname ^ modules in *) |
207 |
| -(* let include_dirs = *) |
208 |
| -(* Fpath.(Set.empty |> Set.add (odoc_dir // Odoc.fpath_of_id parent_id)) *) |
209 |
| -(* in *) |
210 |
| -(* let odoc_file, odocl_file = *) |
211 |
| -(* compile ~content ~input_file ~include_dirs ~parent_id () *) |
212 |
| -(* in *) |
213 |
| -(* driver_page ~odoc_file ~odocl_file ~include_dirs () *) |
214 |
| -(* in *) |
| 111 | + let page ~pkg ~odoc_dir ~odocl_dir ~mld_dir ~output_dir = |
| 112 | + let content = content pkg in |
| 113 | + let rel_path = Fpath.(v pkg.name / "lib") in |
| 114 | + let pkg_args = |
| 115 | + { pages = [ (pkg.name, Fpath.( // ) odoc_dir rel_path) ]; libs = [] } |
| 116 | + in |
| 117 | + make_unit ~odoc_dir ~odocl_dir ~mld_dir ~output_dir rel_path ~content |
| 118 | + ~pkgname:pkg.name ~pkg_args () |
| 119 | +end |
215 | 120 |
|
216 |
| -(* let libraries_landing_page pkg : compiled list = *) |
217 |
| -(* let pkgname = pkg.Packages.pkgname in *) |
218 |
| -(* let parent_id = Fpath.(v pkgname.p_name / "lib") |> Odoc.id_of_fpath in *) |
219 |
| -(* let input_file = *) |
220 |
| -(* Fpath.(odoc_dir // Odoc.fpath_of_id parent_id / "index.mld") *) |
221 |
| -(* in *) |
222 |
| -(* let s_of_lib (lib : Packages.libty) = *) |
223 |
| -(* Format.sprintf "- {{!%s/index}%s}" lib.lib_name lib.lib_name *) |
224 |
| -(* in *) |
225 |
| -(* let libraries = pkg.libraries |> List.map s_of_lib |> String.concat "\n" in *) |
226 |
| -(* let content = title pkgname.p_name ^ libraries in *) |
227 |
| -(* let odoc_file, odocl_file = compile ~content ~input_file ~parent_id () in *) |
228 |
| -(* driver_page ~odoc_file ~odocl_file () *) |
229 |
| -(* :: List.map (library_landing_page pkgname) pkg.libraries *) |
230 |
| -(* in *) |
| 121 | +let of_package ~mld_dir ~odoc_dir ~odocl_dir ~output_dir pkg = |
| 122 | + let library_pages = |
| 123 | + List.map |
| 124 | + (LibraryLanding.page ~pkg ~odoc_dir ~odocl_dir ~mld_dir ~output_dir) |
| 125 | + pkg.libraries |
| 126 | + in |
| 127 | + let package_landing_page = |
| 128 | + PackageLanding.page ~odoc_dir ~odocl_dir ~mld_dir ~output_dir ~pkg |
| 129 | + in |
| 130 | + let library_list_page = |
| 131 | + PackageLibLanding.page ~odoc_dir ~odocl_dir ~mld_dir ~output_dir ~pkg |
| 132 | + in |
| 133 | + package_landing_page :: library_list_page :: library_pages |
231 | 134 |
|
232 |
| -(* let package_landing_page = *) |
233 |
| -(* let input_file = Fpath.(odoc_dir // v pkgname.p_name / "index.mld") in *) |
234 |
| -(* let documentation = *) |
235 |
| -(* match pkg.mlds with *) |
236 |
| -(* | _ :: _ -> *) |
237 |
| -(* Format.sprintf *) |
238 |
| -(* "{1 Documentation pages}\n\n{{!doc/index}Documentation for %s}" *) |
239 |
| -(* pkgname.p_name *) |
240 |
| -(* | [] -> "" *) |
241 |
| -(* in *) |
242 |
| -(* let libraries = *) |
243 |
| -(* match pkg.libraries with *) |
244 |
| -(* | [] -> "" *) |
245 |
| -(* | _ :: _ -> *) |
246 |
| -(* Format.sprintf "{1 Libraries}\n\n{{!lib/index}Libraries for %s}" *) |
247 |
| -(* pkgname.p_name *) |
248 |
| -(* in *) |
249 |
| -(* let content = title pkgname.p_name ^ documentation ^ libraries in *) |
250 |
| -(* let parent_id = Odoc.id_of_fpath (Fpath.v pkgname.p_name) in *) |
251 |
| -(* let odoc_file, odocl_file = compile ~content ~input_file ~parent_id () in *) |
252 |
| -(* driver_page ~odoc_file ~odocl_file () *) |
253 |
| -(* in *) |
254 |
| -(* package_landing_page :: libraries_landing_page pkg *) |
| 135 | +let of_packages ~mld_dir ~odoc_dir ~odocl_dir ~output_dir all = |
| 136 | + PackageList.page ~mld_dir ~odoc_dir ~odocl_dir ~output_dir all |
| 137 | + :: List.concat_map (of_package ~mld_dir ~odoc_dir ~odocl_dir ~output_dir) all |
0 commit comments