Skip to content

Commit a161f9a

Browse files
committed
More fixes for monorepo mode
- library dependencies need transitive deps too - added the ability to specify extra pkgs/libs (like odoc-config.sexp) - minor improvements to landing pages - pick up jpgs as assets
1 parent 270aeea commit a161f9a

File tree

7 files changed

+101
-38
lines changed

7 files changed

+101
-38
lines changed

src/driver/bin/odoc_driver_monorepo.ml

Lines changed: 14 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -6,7 +6,7 @@
66

77
open Odoc_driver_lib
88

9-
let run path
9+
let run path extra_pkgs extra_libs
1010
{
1111
Common_args.verbose;
1212
html_dir;
@@ -35,7 +35,9 @@ let run path
3535
let () = Worker_pool.start_workers env sw nb_workers in
3636

3737
let all, extra_paths, generate_json =
38-
(Monorepo_style.of_dune_build path, Voodoo.empty_extra_paths, generate_json)
38+
( Monorepo_style.of_dune_build path ~extra_pkgs ~extra_libs,
39+
Voodoo.empty_extra_paths,
40+
generate_json )
3941
in
4042

4143
let all = Packages.remap_virtual all in
@@ -93,9 +95,18 @@ let path =
9395
& pos 0 Common_args.fpath_arg (Fpath.v ".")
9496
& info ~doc ~docv:"PATH" [])
9597

98+
let extra_pkgs =
99+
let doc = "Extra packages to link with" in
100+
Arg.(value & opt_all string [] & info [ "P" ] ~doc)
101+
102+
let extra_libs =
103+
let doc = "Extra libraries to link with" in
104+
Arg.(value & opt_all string [] & info [ "L" ] ~doc)
105+
96106
let cmd =
97107
let doc = "Generate documentation from a dune monorepo" in
98108
let info = Cmd.info "odoc_driver_monorepo" ~doc in
99-
Cmd.v info Term.(const run $ path $ Common_args.term)
109+
Cmd.v info
110+
Term.(const run $ path $ extra_pkgs $ extra_libs $ Common_args.term)
100111

101112
let _ = exit (Cmd.eval cmd)

src/driver/landing_pages.ml

Lines changed: 5 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -132,11 +132,11 @@ let content dir _pkg libs _src subdirs all_libs pfp =
132132
fpf pfp "{1 Subdirectories}\n";
133133
Fpath.Set.iter
134134
(fun subdir ->
135-
fpf pfp "- {{!/pkg/%apage-index}%s}\n%!" Fpath.pp subdir
136-
(Fpath.basename subdir))
135+
fpf pfp "- {{!/%s/%apage-index}%s}\n%!" Monorepo_style.monorepo_pkg_name
136+
Fpath.pp subdir (Fpath.basename subdir))
137137
subdirs);
138138

139-
if List.length libs > 0 then
139+
if (not is_root) && List.length libs > 0 then
140140
List.iter
141141
(fun (_, lib) ->
142142
fpf pfp "{1 Library %s}" lib.Packages.lib_name;
@@ -248,8 +248,9 @@ let make_custom dirs index_of (pkg : Packages.t) :
248248
acc)
249249
else
250250
let libs =
251+
let is_root = Fpath.to_string p = "./" in
251252
Fpath.Map.fold
252-
(fun p' lib libs -> if p = p' then lib :: libs else libs)
253+
(fun p' lib libs -> if p = p' || is_root then lib :: libs else libs)
253254
lib_dirs []
254255
in
255256
let src = Fpath.Map.find_opt p src_dirs in

src/driver/monorepo_style.ml

Lines changed: 63 additions & 22 deletions
Original file line numberDiff line numberDiff line change
@@ -68,7 +68,7 @@ let dune_describe dir =
6868
let out = Worker_pool.submit "dune describe" cmd None in
6969
match out with Error _ -> [] | Ok out -> of_dune_describe out.Run.output
7070

71-
let of_dune_build dir =
71+
let of_dune_build dir ~extra_pkgs ~extra_libs =
7272
let root = Fpath.(dir / "_build" / "default") in
7373
let contents =
7474
Bos.OS.Dir.fold_contents ~dotfiles:true (fun p acc -> p :: acc) [] root
@@ -78,16 +78,11 @@ let of_dune_build dir =
7878
| Ok c ->
7979
let cset = Fpath.Set.of_list c in
8080
let libs = dune_describe dir in
81-
let local_libs =
82-
List.filter_map
83-
(function Library l -> if l.local then Some l else None)
84-
libs
85-
in
8681

87-
let global_libs =
88-
List.filter_map
89-
(function Library l -> if l.local then None else Some l)
90-
libs
82+
let local_libs, global_libs =
83+
List.partition
84+
(function l -> l.local)
85+
(List.filter_map (function Library l -> Some l) libs)
9186
in
9287

9388
List.iter
@@ -97,11 +92,13 @@ let of_dune_build dir =
9792
Fmt.(option (pair string Fpath.pp))
9893
(internal_name_of_library lib)))
9994
local_libs;
95+
10096
let uid_to_libname =
10197
List.fold_left
10298
(fun acc l -> Util.StringMap.add l.uid l.name acc)
103-
Util.StringMap.empty local_libs
99+
Util.StringMap.empty (local_libs @ global_libs)
104100
in
101+
105102
let all_lib_deps =
106103
List.fold_left
107104
(fun acc (l : library) ->
@@ -112,8 +109,35 @@ let of_dune_build dir =
112109
l.requires
113110
|> Util.StringSet.of_list)
114111
acc)
115-
Util.StringMap.empty local_libs
112+
Util.StringMap.empty (local_libs @ global_libs)
113+
in
114+
115+
let rec with_trans_deps =
116+
let cache = Hashtbl.create (List.length libs) in
117+
fun lib_name ->
118+
try Hashtbl.find cache lib_name
119+
with Not_found ->
120+
let libs =
121+
try Util.StringMap.find lib_name all_lib_deps
122+
with Not_found ->
123+
Logs.debug (fun m -> m "No lib deps for library %s" lib_name);
124+
Util.StringSet.empty
125+
in
126+
let result =
127+
Util.StringSet.fold
128+
(fun l acc -> Util.StringSet.union (with_trans_deps l) acc)
129+
libs libs
130+
in
131+
Hashtbl.add cache lib_name result;
132+
result
116133
in
134+
135+
let all_lib_deps =
136+
Util.StringMap.mapi
137+
(fun lib_name _ -> with_trans_deps lib_name)
138+
all_lib_deps
139+
in
140+
117141
let colon = Fmt.any ":" in
118142
Format.eprintf "all_lib_deps: %a@."
119143
Fmt.(list ~sep:comma (pair ~sep:colon string (list ~sep:semi string)))
@@ -141,29 +165,31 @@ let of_dune_build dir =
141165
in
142166
let libs =
143167
List.filter_map
144-
(fun (Library lib) ->
168+
(fun lib ->
145169
match internal_name_of_library lib with
146170
| None -> None
147-
| Some (_, cmtidir) ->
171+
| Some (libname, cmtidir) ->
148172
let cmtidir = Fpath.(append dir cmtidir) in
149173
let id_override =
150174
Fpath.relativize
151175
~root:Fpath.(v "_build/default")
152176
Fpath.(v lib.source_dir)
153177
|> Option.map Fpath.to_string
154178
in
155-
Logs.debug (fun m ->
156-
m "this should never be 'None': %a"
157-
Fmt.Dump.(option string)
158-
id_override);
179+
(match id_override with
180+
| None ->
181+
Logs.warn (fun m ->
182+
m "Could not determine id_override for library '%s'"
183+
libname)
184+
| _ -> ());
159185
if Fpath.Set.mem cmtidir cset then
160186
Some
161187
(Packages.Lib.v ~libname_of_archive ~pkg_name:lib.name
162188
~dir:(Fpath.append dir (Fpath.v lib.source_dir))
163189
~cmtidir:(Some cmtidir) ~all_lib_deps ~cmi_only_libs:[]
164190
~id_override)
165191
else None)
166-
libs
192+
local_libs
167193
in
168194
let find_docs ext =
169195
List.filter_map
@@ -182,22 +208,37 @@ let of_dune_build dir =
182208
find_docs ".mld"
183209
|> List.map (fun (p, r) -> { Packages.mld_path = p; mld_rel_path = r })
184210
in
185-
211+
let assets =
212+
find_docs ".jpg"
213+
|> List.map (fun (p, r) ->
214+
{ Packages.asset_path = p; asset_rel_path = r })
215+
in
186216
let libs = List.flatten libs in
217+
let global_config =
218+
{
219+
Global_config.deps =
220+
{
221+
packages = extra_pkgs;
222+
libraries =
223+
extra_libs
224+
@ List.map (fun (lib : Packages.libty) -> lib.lib_name) libs;
225+
};
226+
}
227+
in
187228
let local =
188229
[
189230
{
190231
Packages.name = monorepo_pkg_name;
191232
version = "1.0";
192233
libraries = libs;
193234
mlds;
194-
assets = [];
235+
assets;
195236
selected = true;
196237
remaps = [];
197238
pkg_dir = Fpath.v ".";
198239
doc_dir = Fpath.v ".";
199240
other_docs;
200-
config = Global_config.empty;
241+
config = global_config;
201242
};
202243
]
203244
in

src/driver/monorepo_style.mli

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,4 @@
11
val monorepo_pkg_name : string
22

3-
val of_dune_build : Fpath.t -> Packages.t list
3+
val of_dune_build :
4+
Fpath.t -> extra_pkgs:string list -> extra_libs:string list -> Packages.t list

src/driver/odoc.ml

Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -44,6 +44,7 @@ let compile ~output_dir ~input_file:file ~includes ~suppress_warnings ~parent_id
4444
(fun path acc -> Cmd.(acc % "-I" % p path))
4545
includes Cmd.empty
4646
in
47+
4748
let output_file =
4849
let _, f = Fpath.split_base file in
4950
Some Fpath.(output_dir // Id.to_fpath parent_id // set_ext "odoc" f)
@@ -54,6 +55,11 @@ let compile ~output_dir ~input_file:file ~includes ~suppress_warnings ~parent_id
5455
in
5556
let cmd = cmd % "--parent-id" % Id.to_string parent_id in
5657
let cmd = if suppress_warnings then cmd % "--suppress-warnings" else cmd in
58+
let dirname = Id.to_fpath parent_id |> Fpath.filename in
59+
let cmd =
60+
if Fpath.filename file = "index.mld" then cmd % "--short-title" % dirname
61+
else cmd
62+
in
5763
let desc = Printf.sprintf "Compiling %s" (Fpath.to_string file) in
5864
ignore
5965
@@ Cmd_outputs.submit

src/driver/odoc_units_of.ml

Lines changed: 9 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -1,9 +1,6 @@
11
open Odoc_unit
22

3-
type indices_style =
4-
| Voodoo
5-
| Normal
6-
| Automatic
3+
type indices_style = Voodoo | Normal | Automatic
74

85
let packages ~dirs ~extra_paths ~remap ~indices_style (pkgs : Packages.t list) :
96
t list =
@@ -279,11 +276,15 @@ let packages ~dirs ~extra_paths ~remap ~indices_style (pkgs : Packages.t list) :
279276
let std_units = mld_units @ asset_units @ md_units @ lib_units in
280277
match indices_style with
281278
| Automatic when pkg.name = Monorepo_style.monorepo_pkg_name ->
282-
let others :> t list = Landing_pages.make_custom dirs index_of (List.find (fun p -> p.Packages.name = Monorepo_style.monorepo_pkg_name) pkgs) in
283-
others @ List.concat std_units
279+
let others :> t list =
280+
Landing_pages.make_custom dirs index_of
281+
(List.find
282+
(fun p -> p.Packages.name = Monorepo_style.monorepo_pkg_name)
283+
pkgs)
284+
in
285+
others @ List.concat std_units
284286
| Normal | Voodoo | Automatic ->
285-
List.concat
286-
(pkg_index () :: src_index () :: std_units)
287+
List.concat (pkg_index () :: src_index () :: std_units)
287288
in
288289
if indices_style = Normal then
289290
let gen_indices :> t = Landing_pages.package_list ~dirs ~remap pkgs in

src/driver/packages.mli

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -89,6 +89,8 @@ type t = {
8989

9090
val pp : Format.formatter -> t -> unit
9191

92+
val fix_missing_deps : t list -> t list
93+
9294
val mk_mlds : Opam.doc_file list -> mld list * asset list * md list
9395

9496
val of_libs : packages_dir:Fpath.t option -> Util.StringSet.t -> t list

0 commit comments

Comments
 (0)