Skip to content

Commit

Permalink
Source: Removes the auto-detection of cmt files
Browse files Browse the repository at this point in the history
Signed-off-by: Paul-Elliot <[email protected]>
  • Loading branch information
panglesd authored and jonludlam committed Sep 13, 2023
1 parent fd2e7ff commit 1a36a10
Show file tree
Hide file tree
Showing 9 changed files with 56 additions and 72 deletions.
49 changes: 33 additions & 16 deletions src/odoc/bin/main.ml
Original file line number Diff line number Diff line change
Expand Up @@ -174,7 +174,12 @@ end = struct
Resolver.create ~important_digests:(not resolve_fwd_refs) ~directories
~open_modules
in
let input = Fs.File.of_string input in
let input = Fs.File.of_string input
and source_cmt =
match source_cmt with
| None -> None
| Some cmt -> Some (Fs.File.of_string cmt)
in
let output = output_file ~dst ~input in
let parent_cli_spec =
match (parent_name_opt, package_opt) with
Expand All @@ -187,14 +192,34 @@ end = struct
"Either --package or --parent should be specified, not both")
in
let source =
match (source_parent_file, source_name) with
| Some parent, Some name -> Ok (Some (parent, name, source_cmt))
| Some _, None | None, Some _ ->
match
(source_parent_file, source_name, source_cmt, Fs.File.get_ext input)
with
| Some parent, Some name, None, ".cmt" -> Ok (Some (parent, name, input))
| Some parent, Some name, Some cmt, ".cmt" ->
if Fpath.equal cmt input then Ok (Some (parent, name, input))
else
Error
(`Cli_error
"--cmt has to be equal to the input file when this one has \
.cmt extension.")
| Some parent, Some name, Some cmt, _ -> Ok (Some (parent, name, cmt))
| Some _, Some _, None, _ ->
Error
(`Cli_error
"--cmt has to be passed when --source-parent-file and \
--source-name are passed and the input file is not a cmt file.")
| Some _, None, _, _ | None, Some _, _, _ ->
Error
(`Cli_error
"--source-parent-file and --source-name must be passed at the \
same time.")
| None, None -> Ok None
| None, None, Some _, _ ->
Error
(`Cli_error
"--cmt should only be passed when --source-parent-file and \
--source-name are passed.")
| None, None, _, _ -> Ok None
in
parent_cli_spec >>= fun parent_cli_spec ->
source >>= fun source ->
Expand Down Expand Up @@ -840,10 +865,9 @@ end)

module Depends = struct
module Compile = struct
let list_dependencies has_src input_file =
let list_dependencies input_files =
let deps =
Depends.for_compile_step ~has_src
(List.map ~f:Fs.File.of_string input_file)
Depends.for_compile_step (List.map ~f:Fs.File.of_string input_files)
in
List.iter
~f:(fun t ->
Expand All @@ -857,14 +881,7 @@ module Depends = struct
let doc = "Input files" in
Arg.(non_empty & pos_all file [] & info ~doc ~docv:"file.cm{i,t,ti}" [])
in
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)
Term.(const list_dependencies $ input)

let info ~docs =
Term.info "compile-deps" ~docs
Expand Down
28 changes: 4 additions & 24 deletions src/odoc/compile.ml
Original file line number Diff line number Diff line change
Expand Up @@ -32,24 +32,6 @@ 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)

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 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 Expand Up @@ -118,8 +100,6 @@ let resolve_imports resolver imports =
let resolve_and_substitute ~resolver ~make_root ~source ~hidden
(parent : Paths.Identifier.ContainerPage.t option) input_file input_type =
let filename = Fs.File.to_string input_file in
(* [impl_shape] is used to lookup locations in the implementation. It is
useless if no source code is given on command line. *)
let unit, cmt_infos =
match input_type with
| `Cmti ->
Expand All @@ -129,9 +109,8 @@ let resolve_and_substitute ~resolver ~make_root ~source ~hidden
and cmt_infos =
match source with
| None -> None
| Some (_, None) -> lookup_implementation_of_cmti input_file
| Some (_, Some filename) ->
Odoc_loader.read_cmt_infos ~filename
| Some (_, filename) ->
Odoc_loader.read_cmt_infos ~filename:(Fs.File.to_string filename)
|> Error.raise_errors_and_warnings
in
(unit, cmt_infos)
Expand Down Expand Up @@ -289,7 +268,8 @@ let mld ~parent_spec ~output ~children ~warnings_options input =
| `Stop -> resolve [] (* TODO: Error? *)
| `Docs content -> resolve content

let handle_file_ext = function
let handle_file_ext ext =
match ext with
| ".cmti" -> Ok `Cmti
| ".cmt" -> Ok `Cmt
| ".cmi" -> Ok `Cmi
Expand Down
6 changes: 1 addition & 5 deletions src/odoc/compile.mli
Original file line number Diff line number Diff line change
Expand Up @@ -23,10 +23,6 @@ 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 All @@ -45,7 +41,7 @@ val compile :
children:string list ->
output:Fs.File.t ->
warnings_options:Odoc_model.Error.warnings_options ->
source:(Fpath.t * string list * string option) option ->
source:(Fpath.t * string list * Fpath.t) option ->
Fs.File.t ->
(unit, [> msg ]) result
(** Produces .odoc files out of [.cm{i,t,ti}] or .mld files. *)
13 changes: 3 additions & 10 deletions src/odoc/depends.ml
Original file line number Diff line number Diff line change
Expand Up @@ -42,23 +42,16 @@ let for_compile_step_cmt acc file =
let cmt_infos = Cmt_format.read_cmt (Fs.File.to_string file) in
List.fold_left ~f:add_dep ~init:acc cmt_infos.Cmt_format.cmt_imports

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

let for_compile_step ~has_src files =
let for_compile_step files =
let set =
List.fold_left
~f:(fun acc file ->
if Fs.File.has_ext "cmt" file then for_compile_step_cmt acc file
else for_compile_step_cmi_or_cmti ~has_src acc file)
else for_compile_step_cmi_or_cmti acc file)
~init:Compile_set.empty files
in
set |> Compile_set.to_seq |> List.of_seq
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 : has_src:bool -> Fs.File.t list -> Compile.t list
val for_compile_step : Fs.File.t list -> Compile.t list
(** Takes a [.cm{i,t,ti}] file and returns the list of its dependencies. *)

val for_rendering_step :
Expand Down
7 changes: 3 additions & 4 deletions test/sources/compile_deps.t/run.t
Original file line number Diff line number Diff line change
@@ -1,8 +1,7 @@
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
code rendering is enabled.

$ ocamlc -c b.ml -bin-annot
$ ocamlc -c a.mli -I . -bin-annot
Expand All @@ -20,8 +19,8 @@ compile-deps
CamlinternalFormatBasics 8f8f634558798ee408df3c50a5539b15
Stdlib 6d7bf11af14ea68354925f3a37387930

Must contain B:
$ odoc compile-deps --has-src a.cmti
Must be the merge of both dependencies:
$ odoc compile-deps a.cmti a.cmt
A 21e6137bd9b3aaa3c66960387b5f32c0
B 903ddd9b7c0fa4ee6d34b4af6358d1e1
CamlinternalFormatBasics 8f8f634558798ee408df3c50a5539b15
Expand Down
2 changes: 1 addition & 1 deletion test/sources/lookup_def.t/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,7 @@ Compile the modules:
$ odoc source-tree -I . --parent page-root -o src-source.odoc source_tree.map

$ ocamlc -c a.mli a.ml -bin-annot
$ odoc compile --source-name a.ml --source-parent-file src-source.odoc -I . a.cmti
$ odoc compile --cmt a.cmt --source-name a.ml --source-parent-file src-source.odoc -I . a.cmti
$ odoc link a.odoc

Show the locations:
Expand Down
2 changes: 1 addition & 1 deletion test/sources/single_mli.t/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -10,7 +10,7 @@ Similar to Astring library.
$ ocamlc -c a.ml -bin-annot -I .

$ odoc compile --hidden --source-name a_x.ml --source-parent-file src-source.odoc -I . a_x.cmt
$ odoc compile --source-name a.ml --source-parent-file src-source.odoc -I . a.cmti
$ odoc compile --cmt a.cmt --source-name a.ml --source-parent-file src-source.odoc -I . a.cmti

$ odoc link -I . a_x.odoc
$ odoc link -I . a.odoc
Expand Down
19 changes: 9 additions & 10 deletions test/sources/source.t/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -163,18 +163,17 @@ Another example, with a cmti file:
$ ocamlc -bin-annot b.ml

When giving a .cmti with the source-name and source-parent option, the cmt file
is looked up automatically:
has to be given explicitely with the --cmt argument:

$ odoc compile -I . --source-name b.ml --source-parent-file src-source2.odoc b.cmti
$ odoc link -I . b.odoc
--cmt has to be passed when --source-parent-file and --source-name are passed and the input file is not a cmt file.
[2]

The --cmt option can be used to explicitely give the cmt:
$ odoc compile -I . --cmt b.cmt --source-name b.ml --source-parent-file src-source2.odoc b.cmti

$ mv b.cmt new_b.cmt

$ odoc compile -I . --source-name b.ml --source-parent-file src-source2.odoc b.cmti
File "b.cmti":
Warning: No implementation file found for the given interface
$ odoc compile -I . --cmt new_b.cmt --source-name b.ml --source-parent-file src-source2.odoc b.cmti
$ odoc link -I . b.odoc
The --cmt argument has to be compatible with a cmt file given as input:

$ cp b.cmt other.cmt
$ odoc compile -I . --cmt other.cmt --source-name b.ml --source-parent-file src-source2.odoc b.cmt
--cmt has to be equal to the input file when this one has .cmt extension.
[2]

0 comments on commit 1a36a10

Please sign in to comment.