Skip to content

Commit 86de835

Browse files
committed
Driver: review comments
1 parent 218d177 commit 86de835

File tree

2 files changed

+64
-91
lines changed

2 files changed

+64
-91
lines changed

src/driver/compile.ml

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -149,15 +149,15 @@ let compile ?partial ~partial_dir ?linked_dir:_ (all : Odoc_unit.t list) =
149149
~includes ~parent_id:unit.parent_id;
150150
Atomic.incr Stats.stats.compiled_mlds
151151
in
152-
let _compiled_mlds = Fiber.List.map compile_mld mld_units in
152+
let () = Fiber.List.iter compile_mld mld_units in
153153
let compile_impl (unit : Odoc_unit.impl Odoc_unit.unit) =
154154
let includes = Fpath.Set.of_list unit.include_dirs in
155155
let source_id = match unit.kind with `Impl src -> src.src_id in
156156
Odoc.compile_impl ~output_dir:unit.output_dir ~input_file:unit.input_file
157157
~includes ~parent_id:unit.parent_id ~source_id;
158158
Atomic.incr Stats.stats.compiled_impls
159159
in
160-
let _compiled_impls = Fiber.List.map compile_impl impl_units in
160+
let () = Fiber.List.iter compile_impl impl_units in
161161
let zipped_res =
162162
List.map2
163163
(fun Odoc_unit.{ kind = `Intf { hash; _ }; _ } b -> (hash, b))

src/driver/odoc_unit.ml

Lines changed: 62 additions & 89 deletions
Original file line numberDiff line numberDiff line change
@@ -90,90 +90,78 @@ let of_packages ~output_dir ~linked_dir ~index_dir (pkgs : Packages.t list) :
9090
let output_file = Fpath.(index_dir / pkg.name / Odoc.index_filename) in
9191
{ pkg_args; output_file; json = false; search_dir = pkg.pkg_dir }
9292
in
93-
let rec of_intf hidden pkg libname (intf : Packages.intf) : intf unit =
93+
let rec build_deps deps =
94+
List.filter_map
95+
(fun (_name, hash) ->
96+
match Util.StringMap.find_opt hash hashtable with
97+
| None -> None
98+
| Some (pkg, lib, mod_) ->
99+
let result = of_intf mod_.m_hidden pkg lib mod_.m_intf in
100+
Hashtbl.add cache mod_.m_intf.mif_hash result;
101+
Some result)
102+
deps
103+
and make_unit ~rel_dir ~input_file ~prefix ~pkg ~include_dirs : _ unit =
104+
let ( // ) = Fpath.( // ) in
105+
let ( / ) = Fpath.( / ) in
106+
let filename = input_file |> Fpath.rem_ext |> Fpath.basename in
107+
let odoc_dir = output_dir // rel_dir in
108+
let parent_id = rel_dir |> Odoc.id_of_fpath in
109+
let odoc_file = odoc_dir / (prefix ^ filename ^ ".odoc") in
110+
let odocl_file = linked_dir // rel_dir / (prefix ^ filename ^ ".odocl") in
111+
{
112+
output_dir;
113+
pkgname = pkg.Packages.name;
114+
pkg_args;
115+
parent_id;
116+
odoc_dir;
117+
input_file;
118+
odoc_file;
119+
odocl_file;
120+
include_dirs;
121+
kind = ();
122+
index = index_of pkg;
123+
}
124+
and of_intf hidden pkg libname (intf : Packages.intf) : intf unit =
94125
match Hashtbl.find_opt cache intf.mif_hash with
95126
| Some unit -> unit
96127
| None ->
97128
let open Fpath in
98129
let rel_dir = pkg.Packages.pkg_dir / "lib" / libname in
99-
let odoc_dir = output_dir // rel_dir in
100-
let parent_id = rel_dir |> Odoc.id_of_fpath in
101-
let filename = intf.mif_path |> Fpath.rem_ext |> Fpath.basename in
102-
let odoc_file = odoc_dir / (filename ^ ".odoc") in
103-
let odocl_file = linked_dir // rel_dir / (filename ^ ".odocl") in
104-
let input_file = intf.mif_path in
105-
let deps =
106-
List.filter_map
107-
(fun (_name, hash) ->
108-
match Util.StringMap.find_opt hash hashtable with
109-
| None -> None
110-
| Some (pkg, lib, mod_) ->
111-
let result = of_intf mod_.m_hidden pkg lib mod_.m_intf in
112-
Hashtbl.add cache mod_.m_intf.mif_hash result;
113-
Some result)
114-
intf.mif_deps
130+
let include_dirs, kind =
131+
let deps = build_deps intf.mif_deps in
132+
let include_dirs = List.map (fun u -> u.odoc_dir) deps in
133+
let kind = `Intf { hidden; hash = intf.mif_hash; deps } in
134+
(include_dirs, kind)
135+
in
136+
let unit =
137+
make_unit ~rel_dir ~prefix:"" ~input_file:intf.mif_path ~pkg
138+
~include_dirs
115139
in
116-
let include_dirs = List.map (fun u -> u.odoc_dir) deps in
117-
let kind = `Intf { hidden; hash = intf.mif_hash; deps } in
118-
{
119-
output_dir;
120-
pkgname = pkg.name;
121-
pkg_args;
122-
parent_id;
123-
odoc_dir;
124-
input_file;
125-
odoc_file;
126-
odocl_file;
127-
include_dirs;
128-
kind;
129-
index = index_of pkg;
130-
}
140+
{ unit with kind }
131141
in
132142
let of_impl pkg libname (impl : Packages.impl) : impl unit option =
133143
let open Fpath in
134144
match impl.mip_src_info with
135145
| None -> None
136146
| Some { src_path } ->
137147
let rel_dir = pkg.Packages.pkg_dir / "lib" / libname in
138-
let odoc_dir = output_dir // rel_dir in
139-
let parent_id = rel_dir |> Odoc.id_of_fpath in
140-
let filename = impl.mip_path |> Fpath.rem_ext |> Fpath.basename in
141-
let odoc_file = odoc_dir / ("impl-" ^ filename ^ ".odoc") in
142-
let odocl_file =
143-
linked_dir // rel_dir / ("impl-" ^ filename ^ ".odocl")
148+
let include_dirs =
149+
let deps = build_deps impl.mip_deps in
150+
List.map (fun u -> u.odoc_dir) deps
144151
in
145-
let input_file = impl.mip_path in
146-
let src_name = Fpath.filename src_path in
147-
let src_id =
148-
Fpath.(pkg.pkg_dir / "src" / libname / src_name) |> Odoc.id_of_fpath
152+
let kind =
153+
let src_name = Fpath.filename src_path in
154+
let src_id =
155+
Fpath.(pkg.pkg_dir / "src" / libname / src_name) |> Odoc.id_of_fpath
156+
in
157+
`Impl { src_id; src_path }
149158
in
150-
let deps =
151-
List.filter_map
152-
(fun (_name, hash) ->
153-
match Util.StringMap.find_opt hash hashtable with
154-
| None -> None
155-
| Some (pkg, lib, mod_) ->
156-
let result = of_intf mod_.m_hidden pkg lib mod_.m_intf in
157-
Hashtbl.add cache mod_.m_intf.mif_hash result;
158-
Some result)
159-
impl.mip_deps
159+
let unit =
160+
make_unit ~rel_dir ~input_file:impl.mip_path ~pkg ~include_dirs
161+
~prefix:"impl-"
160162
in
161-
let include_dirs = List.map (fun u -> u.odoc_dir) deps in
162-
let kind = `Impl { src_id; src_path } in
163-
Some
164-
{
165-
output_dir;
166-
pkgname = pkg.name;
167-
parent_id;
168-
odoc_dir;
169-
input_file;
170-
odoc_file;
171-
odocl_file;
172-
pkg_args;
173-
include_dirs;
174-
kind;
175-
index = index_of pkg;
176-
}
163+
let unit = { unit with kind } in
164+
Some unit
177165
in
178166

179167
let of_module pkg libname (m : Packages.modulety) : [ impl | intf ] unit list
@@ -194,34 +182,19 @@ let of_packages ~output_dir ~linked_dir ~index_dir (pkgs : Packages.t list) :
194182
pkg.Packages.pkg_dir / "doc" // Fpath.parent mld_rel_path
195183
|> Fpath.normalize
196184
in
197-
let odoc_dir = output_dir // rel_dir in
198-
let filename = mld_path |> Fpath.rem_ext |> Fpath.basename in
199-
let odoc_file = odoc_dir / ("page-" ^ filename ^ ".odoc") in
200-
let odocl_file = linked_dir // rel_dir / ("page-" ^ filename ^ ".odocl") in
201-
let parent_id = rel_dir |> Odoc.id_of_fpath in
202185
let include_dirs =
203186
List.map
204187
(fun (lib : Packages.libty) ->
205188
Fpath.(output_dir // pkg.pkg_dir / "lib" / lib.lib_name))
206189
pkg.libraries
207190
in
208-
let include_dirs = odoc_dir :: include_dirs in
191+
let include_dirs = (output_dir // rel_dir) :: include_dirs in
209192
let kind = `Mld in
210-
[
211-
{
212-
output_dir;
213-
pkgname = pkg.name;
214-
parent_id;
215-
odoc_dir;
216-
input_file = mld_path;
217-
odoc_file;
218-
odocl_file;
219-
kind;
220-
pkg_args;
221-
include_dirs;
222-
index = index_of pkg;
223-
};
224-
]
193+
let unit =
194+
make_unit ~rel_dir ~input_file:mld_path ~pkg ~include_dirs ~prefix:"page-"
195+
in
196+
let unit = { unit with kind } in
197+
[ unit ]
225198
in
226199
let of_package (pkg : Packages.t) : t list =
227200
let lib_units :> t list list = List.map (of_lib pkg) pkg.libraries in

0 commit comments

Comments
 (0)