Skip to content

Commit

Permalink
Add compile-deps --has-src
Browse files Browse the repository at this point in the history
Dependencies are not the same when source code rendering is enabled or not. The
`--has-src` flag specifies which behaviour to adopt.
The logic to lookup the cmt is factorized between `compile` and `compile-deps`.

Signed-off-by: Paul-Elliot <[email protected]>
Co-authored-by: Jules Aguillon <[email protected]>
  • Loading branch information
panglesd and Julow committed Jul 26, 2023
1 parent ae44182 commit ae5b86c
Show file tree
Hide file tree
Showing 9 changed files with 72 additions and 17 deletions.
15 changes: 12 additions & 3 deletions src/odoc/bin/main.ml
Original file line number Diff line number Diff line change
Expand Up @@ -833,8 +833,10 @@ end)

module Depends = struct
module Compile = struct
let list_dependencies input_file =
let deps = Depends.for_compile_step (Fs.File.of_string input_file) in
let list_dependencies has_src input_file =
let deps =
Depends.for_compile_step ~has_src (Fs.File.of_string input_file)
in
List.iter
~f:(fun t ->
Printf.printf "%s %s\n" (Depends.Compile.name t)
Expand All @@ -850,7 +852,14 @@ module Depends = struct
& pos 0 (some file) None
& info ~doc ~docv:"file.cm{i,t,ti}" [])
in
Term.(const list_dependencies $ input)
let has_src =
let doc =
"Include the dependencies needed when compiling with --source-name \
and --source-parent-file."
in
Arg.(value & flag & info ~doc [ "has-src" ])
in
Term.(const list_dependencies $ has_src $ input)

let info ~docs =
Term.info "compile-deps" ~docs
Expand Down
15 changes: 10 additions & 5 deletions src/odoc/compile.ml
Original file line number Diff line number Diff line change
Expand Up @@ -32,19 +32,24 @@ type parent_cli_spec =
let check_is_none msg = function None -> Ok () | Some _ -> Error (`Msg msg)
let check_is_empty msg = function [] -> Ok () | _ :: _ -> Error (`Msg msg)

(** Raises warnings and errors. *)
let lookup_implementation_of_cmti intf_file =
let lookup_cmt_of_cmti intf_file =
let input_file = Fs.File.set_ext ".cmt" intf_file in
if Fs.File.exists input_file then
let filename = Fs.File.to_string input_file in
Odoc_loader.read_cmt_infos ~filename |> Error.raise_errors_and_warnings
if Fs.File.exists input_file then Some input_file
else (
Error.raise_warning ~non_fatal:true
(Error.filename_only
"No implementation file found for the given interface"
(Fs.File.to_string intf_file));
None)

(** Raises warnings and errors. *)
let lookup_implementation_of_cmti intf_file =
match lookup_cmt_of_cmti intf_file with
| Some filename ->
let filename = Fs.File.to_string filename in
Odoc_loader.read_cmt_infos ~filename |> Error.raise_errors_and_warnings
| None -> None

(** Used to disambiguate child references. *)
let is_module_name n = String.length n > 0 && Char.Ascii.is_upper n.[0]

Expand Down
4 changes: 4 additions & 0 deletions src/odoc/compile.mli
Original file line number Diff line number Diff line change
Expand Up @@ -23,6 +23,10 @@ type parent_cli_spec =
| CliPackage of string
| CliNoparent

val lookup_cmt_of_cmti : Fs.File.t -> Fs.File.t option
(** From a cmti file, returns the cmt file if it exists. If it does not esists,
raise a warning. *)

val name_of_output : prefix:string -> Fs.File.t -> string
(** Compute the name of the page from the output file. Prefix is the prefix to
remove from the filename. *)
Expand Down
22 changes: 14 additions & 8 deletions src/odoc/depends.ml
Original file line number Diff line number Diff line change
Expand Up @@ -17,6 +17,8 @@
open StdLabels
open Or_error

module Odoc_compile = Compile

module Compile = struct
type t = { unit_name : string; digest : Digest.t }

Expand All @@ -33,14 +35,18 @@ let for_compile_step_cmt file =
let cmt_infos = Cmt_format.read_cmt (Fs.File.to_string file) in
List.fold_left ~f:add_dep ~init:[] cmt_infos.Cmt_format.cmt_imports

let for_compile_step_cmi_or_cmti file =
let cmi_infos = Cmi_format.read_cmi (Fs.File.to_string file) in
List.fold_left ~f:add_dep ~init:[] cmi_infos.Cmi_format.cmi_crcs

let for_compile_step file =
match Fs.File.has_ext "cmt" file with
| true -> for_compile_step_cmt file
| false -> for_compile_step_cmi_or_cmti file
let for_compile_step_cmi_or_cmti ~has_src file =
if has_src then
match Odoc_compile.lookup_cmt_of_cmti file with
| None -> []
| Some file -> for_compile_step_cmt file
else
let cmi_infos = Cmi_format.read_cmi (Fs.File.to_string file) in
List.fold_left ~f:add_dep ~init:[] cmi_infos.Cmi_format.cmi_crcs

let for_compile_step ~has_src file =
if Fs.File.has_ext "cmt" file then for_compile_step_cmt file
else for_compile_step_cmi_or_cmti ~has_src file

module Hash_set : sig
type t
Expand Down
2 changes: 1 addition & 1 deletion src/odoc/depends.mli
Original file line number Diff line number Diff line change
Expand Up @@ -27,7 +27,7 @@ module Compile : sig
val digest : t -> Digest.t
end

val for_compile_step : Fs.File.t -> Compile.t list
val for_compile_step : has_src:bool -> Fs.File.t -> Compile.t list
(** Takes a [.cm{i,t,ti}] file and returns the list of its dependencies. *)

val for_rendering_step :
Expand Down
1 change: 1 addition & 0 deletions test/sources/compile_deps.t/a.ml
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
include B
1 change: 1 addition & 0 deletions test/sources/compile_deps.t/a.mli
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
val a : int
1 change: 1 addition & 0 deletions test/sources/compile_deps.t/b.ml
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
let a = 5
28 changes: 28 additions & 0 deletions test/sources/compile_deps.t/run.t
Original file line number Diff line number Diff line change
@@ -0,0 +1,28 @@
Source code rendering needs the same compilation order as cmts.

As a consequence, the dependencies should be taken from the cmt, when source
code rendering is enabled. This must be specified using the --has-src flag for
compile-deps

$ ocamlc -c b.ml -bin-annot
$ ocamlc -c a.mli -I . -bin-annot
$ ocamlc -c a.ml -I . -bin-annot

[a.cmti] does not depend on B, while its implementation [a.cmt] depends on B.

$ odoc compile-deps a.cmti
CamlinternalFormatBasics 8f8f634558798ee408df3c50a5539b15
Stdlib 79b0e9d3b6f7fed07eb3cc2abb961b91
A 21e6137bd9b3aaa3c66960387b5f32c0
$ odoc compile-deps a.cmt
Stdlib 79b0e9d3b6f7fed07eb3cc2abb961b91
CamlinternalFormatBasics 8f8f634558798ee408df3c50a5539b15
B 903ddd9b7c0fa4ee6d34b4af6358d1e1
A 21e6137bd9b3aaa3c66960387b5f32c0

Must contain B:
$ odoc compile-deps --has-src a.cmti
Stdlib 79b0e9d3b6f7fed07eb3cc2abb961b91
CamlinternalFormatBasics 8f8f634558798ee408df3c50a5539b15
B 903ddd9b7c0fa4ee6d34b4af6358d1e1
A 21e6137bd9b3aaa3c66960387b5f32c0

0 comments on commit ae5b86c

Please sign in to comment.