Skip to content

Commit

Permalink
Driver: Check for missing/unknown opam packages
Browse files Browse the repository at this point in the history
Closes #1302, closes #1296
  • Loading branch information
jonludlam committed Feb 20, 2025
1 parent a5ac62b commit 005b2ca
Show file tree
Hide file tree
Showing 3 changed files with 38 additions and 0 deletions.
14 changes: 14 additions & 0 deletions src/driver/bin/odoc_driver.ml
Original file line number Diff line number Diff line change
@@ -1,6 +1,19 @@
(* Odoc driver *)
open Odoc_driver_lib

let check_packages packages =
match packages with
| [] -> ()
| _ -> (
match Opam.check packages with
| Ok () -> ()
| Error missing ->
Logs.err (fun m ->
m "Error: Unknown/uninstalled packages: %a"
Fmt.Dump.(list string)
(Util.StringSet.elements missing));
exit 1)

let run_inner ~odoc_dir ~odocl_dir ~index_dir ~mld_dir ~compile_grep ~link_grep
~generate_grep ~index_grep ~remap ~index_mld packages
{
Expand All @@ -20,6 +33,7 @@ let run_inner ~odoc_dir ~odocl_dir ~index_dir ~mld_dir ~compile_grep ~link_grep

if verbose then Logs.set_level (Some Logs.Debug);
Logs.set_reporter (Logs_fmt.reporter ());
check_packages packages;
Stats.init_nprocs nb_workers;

let index_mld_content =
Expand Down
23 changes: 23 additions & 0 deletions src/driver/opam.ml
Original file line number Diff line number Diff line change
Expand Up @@ -281,6 +281,29 @@ let dune_overrides () =
[])
| _ -> [])

let check pkgs =
let cmd =
Cmd.(
opam % "list" % "-i" % "--columns" % "package" % "--color" % "never"
% "-s")
in
let cmd = List.fold_left (fun cmd pkg -> Cmd.(cmd % pkg)) cmd pkgs in
let out = Util.lines_of_process cmd in
let res =
List.filter_map
(fun x ->
match Astring.String.cut ~sep:"." x with
| Some (name, _version) -> Some name
| None -> None)
out
in
let missing = Util.StringSet.(diff (of_list pkgs) (of_list res)) in
let dune_pkgnames =
Util.StringSet.of_list (List.map (fun (p, _) -> p.name) (dune_overrides ()))
in
let missing = Util.StringSet.(diff missing dune_pkgnames) in
if Util.StringSet.cardinal missing = 0 then Ok () else Error missing

let pkg_to_dir_map () =
let dune_overrides = dune_overrides () in
let pkgs = all_opam_packages () in
Expand Down
1 change: 1 addition & 0 deletions src/driver/opam.mli
Original file line number Diff line number Diff line change
Expand Up @@ -20,6 +20,7 @@ val all_opam_packages : unit -> package list

val classify_docs : Fpath.t -> string option -> Fpath.t list -> doc_file list

val check : string list -> (unit, Util.StringSet.t) Result.t
val deps : string list -> package list
val pkg_to_dir_map : unit -> fpaths_of_package * package_of_fpath
val pp : Format.formatter -> package -> unit
Expand Down

0 comments on commit 005b2ca

Please sign in to comment.