Skip to content

Commit d74d713

Browse files
committed
Driver: generate external pages
Generate pages that are external of a package: landing pages for package, library, library list and package list. There is a problem currently with empty parent id. Currently using a "`a`" container directory for the package list.
1 parent d6fea07 commit d74d713

File tree

5 files changed

+286
-10
lines changed

5 files changed

+286
-10
lines changed

src/driver/compile.ml

Lines changed: 15 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -22,7 +22,11 @@ let init_stats (units : Odoc_unit.t list) =
2222
let assets =
2323
match unit.kind with `Asset -> assets + 1 | _ -> assets
2424
in
25-
let indexes = Fpath.Set.add unit.index.output_file indexes in
25+
let indexes =
26+
match unit.index with
27+
| None -> indexes
28+
| Some index -> Fpath.Set.add index.output_file indexes
29+
in
2630
let non_hidden =
2731
match unit.kind with
2832
| `Intf { hidden = false; _ } -> non_hidden + 1
@@ -256,10 +260,16 @@ let html_generate output_dir linked =
256260
Odoc.html_generate_asset ~output_dir ~input_file:l.odoc_file
257261
~asset_path:l.input_file ()
258262
| _ ->
259-
let db_path = compile_index l.index in
260-
let search_uris = [ db_path; Sherlodoc.js_file ] in
261-
let index = l.index.output_file in
262-
Odoc.html_generate ~search_uris ~index ~output_dir ~input_file ();
263+
let search_uris, index =
264+
match l.index with
265+
| None -> (None, None)
266+
| Some index ->
267+
let db_path = compile_index index in
268+
let search_uris = [ db_path; Sherlodoc.js_file ] in
269+
let index = index.output_file in
270+
(Some search_uris, Some index)
271+
in
272+
Odoc.html_generate ?search_uris ?index ~output_dir ~input_file ();
263273
Atomic.incr Stats.stats.generated_units
264274
in
265275
Fiber.List.iter html_generate linked

src/driver/landing_pages.ml

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

src/driver/odoc_driver.ml

Lines changed: 16 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -558,8 +558,17 @@ let run libs verbose packages_dir odoc_dir odocl_dir html_dir stats nb_workers
558558
(fun () ->
559559
let all =
560560
let all = Util.StringMap.bindings all |> List.map snd in
561-
Odoc_unit.of_packages ~output_dir:odoc_dir ~linked_dir:odocl_dir
562-
~index_dir:None all
561+
let internal =
562+
Odoc_unit.of_packages ~output_dir:odoc_dir ~linked_dir:odocl_dir
563+
~index_dir:None all
564+
in
565+
let external_ =
566+
let mld_dir = odoc_dir in
567+
let odocl_dir = Option.value odocl_dir ~default:odoc_dir in
568+
Landing_pages.of_packages ~mld_dir ~odoc_dir ~odocl_dir
569+
~output_dir:odoc_dir all
570+
in
571+
internal @ external_
563572
in
564573
Compile.init_stats all;
565574
let compiled =
@@ -573,6 +582,11 @@ let run libs verbose packages_dir odoc_dir odocl_dir html_dir stats nb_workers
573582
(fun () -> render_stats env nb_workers)
574583
in
575584

585+
(* List.iter *)
586+
(* (fun l -> *)
587+
(* if Astring.String.is_infix ~affix:"index.mld" l then *)
588+
(* Format.printf "%s\n" l) *)
589+
(* !Cmd_outputs.compile_output; *)
576590
Format.eprintf "Final stats: %a@.%!" Stats.pp_stats Stats.stats;
577591
Format.eprintf "Total time: %f@.%!" (Stats.total_time ());
578592
if stats then Stats.bench_results html_dir

src/driver/odoc_unit.ml

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -20,7 +20,7 @@ type 'a unit = {
2020
pkg_args : pkg_args;
2121
pkgname : string;
2222
include_dirs : Fpath.t list;
23-
index : index;
23+
index : index option;
2424
kind : 'a;
2525
}
2626

@@ -110,7 +110,7 @@ let of_packages ~output_dir ~linked_dir ~index_dir (pkgs : Packages.t list) :
110110
odocl_file;
111111
include_dirs;
112112
kind;
113-
index = index_of pkg;
113+
index = Some (index_of pkg);
114114
}
115115
in
116116
let rec build_deps deps =

src/driver/odoc_unit.mli

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -20,7 +20,7 @@ type 'a unit = {
2020
pkg_args : pkg_args;
2121
pkgname : string;
2222
include_dirs : Fpath.t list;
23-
index : index;
23+
index : index option;
2424
kind : 'a;
2525
}
2626

0 commit comments

Comments
 (0)