Skip to content

Commit

Permalink
Merge pull request #2221 from nojb/fix_ocamldep_shadowing
Browse files Browse the repository at this point in the history
ocamldep: .ml in earlier include dirs should shadow .mli in later include dir
  • Loading branch information
nojb committed Apr 10, 2019
2 parents b29e897 + aebc58a commit 3fac824
Show file tree
Hide file tree
Showing 8 changed files with 66 additions and 43 deletions.
5 changes: 5 additions & 0 deletions Changes
Original file line number Diff line number Diff line change
Expand Up @@ -655,6 +655,11 @@ OCaml 4.08.0
on a new line, for more readable diffs of versioned dependencies.
(Gabriel Scherer, review by Nicolás Ojeda Bär)

- #2221: ocamldep will now correctly allow a .ml file in an include directory
that appears first in the search order to shadow a .mli appearing in a later
include directory.
(Nicolás Ojeda Bär, review by Florian Angeletti)

- #2223: ocamltest: fix the "bsd" and "not-bsd" built-in actions to
recognize all BSD variants
(Damien Doligez, review by Sébastien Hinderer and David Allsopp)
Expand Down
84 changes: 41 additions & 43 deletions driver/makedepend.ml
Original file line number Diff line number Diff line change
Expand Up @@ -87,12 +87,19 @@ let add_to_synonym_list synonyms suffix =
end

(* Find file 'name' (capitalized) in search path *)
let find_file name =
let uname = String.uncapitalize_ascii name in
let find_module_in_load_path name =
let names = List.map (fun ext -> name ^ ext) (!mli_synonyms @ !ml_synonyms) in
let unames =
let uname = String.uncapitalize_ascii name in
List.map (fun ext -> uname ^ ext) (!mli_synonyms @ !ml_synonyms)
in
let rec find_in_array a pos =
if pos >= Array.length a then None else begin
let s = a.(pos) in
if s = name || s = uname then Some s else find_in_array a (pos + 1)
if List.mem s names || List.mem s unames then
Some s
else
find_in_array a (pos + 1)
end in
let rec find_in_path = function
[] -> raise Not_found
Expand All @@ -103,58 +110,49 @@ let find_file name =
| None -> find_in_path rem in
find_in_path !load_path

let rec find_file_in_list = function
[] -> raise Not_found
| x :: rem -> try find_file x with Not_found -> find_file_in_list rem


let find_dependency target_kind modname (byt_deps, opt_deps) =
try
let candidates = List.map ((^) modname) !mli_synonyms in
let filename = find_file_in_list candidates in
let filename = find_module_in_load_path modname in
let basename = Filename.chop_extension filename in
let cmi_file = basename ^ ".cmi" in
let cmx_file = basename ^ ".cmx" in
let mli_exists =
List.exists (fun ext -> Sys.file_exists (basename ^ ext)) !mli_synonyms in
let ml_exists =
List.exists (fun ext -> Sys.file_exists (basename ^ ext)) !ml_synonyms in
let new_opt_dep =
if !all_dependencies then
match target_kind with
| MLI -> [ cmi_file ]
| ML ->
cmi_file :: (if ml_exists then [ cmx_file ] else [])
else
if mli_exists then
let new_opt_dep =
if !all_dependencies then
match target_kind with
| MLI -> [ cmi_file ]
| ML ->
cmi_file :: (if ml_exists then [ cmx_file ] else [])
else
(* this is a make-specific hack that makes .cmx to be a 'proxy'
target that would force the dependency on .cmi via transitivity *)
if ml_exists
then [ cmx_file ]
else [ cmi_file ]
in
( cmi_file :: byt_deps, new_opt_dep @ opt_deps)
with Not_found ->
try
(* "just .ml" case *)
let candidates = List.map ((^) modname) !ml_synonyms in
let filename = find_file_in_list candidates in
let basename = Filename.chop_extension filename in
let cmi_file = basename ^ ".cmi" in
let cmx_file = basename ^ ".cmx" in
let bytenames =
if !all_dependencies then
match target_kind with
| MLI -> [ cmi_file ]
| ML -> [ cmi_file ]
else
(* again, make-specific hack *)
[basename ^ (if !native_only then ".cmx" else ".cmo")] in
let optnames =
if !all_dependencies
then match target_kind with
| MLI -> [ cmi_file ]
| ML -> [ cmi_file; cmx_file ]
else [ cmx_file ]
in
(bytenames @ byt_deps, optnames @ opt_deps)
in
( cmi_file :: byt_deps, new_opt_dep @ opt_deps)
else
(* "just .ml" case *)
let bytenames =
if !all_dependencies then
match target_kind with
| MLI -> [ cmi_file ]
| ML -> [ cmi_file ]
else
(* again, make-specific hack *)
[basename ^ (if !native_only then ".cmx" else ".cmo")] in
let optnames =
if !all_dependencies
then match target_kind with
| MLI -> [ cmi_file ]
| ML -> [ cmi_file; cmx_file ]
else [ cmx_file ]
in
(bytenames @ byt_deps, optnames @ opt_deps)
with Not_found ->
(byt_deps, opt_deps)

Expand Down
13 changes: 13 additions & 0 deletions testsuite/tests/tool-ocamldep-shadowing/a.ml
Original file line number Diff line number Diff line change
@@ -0,0 +1,13 @@
(* TEST
* setup-ocamlc.byte-build-env
** script
script = "cp -R ${test_source_directory}/dir1 ${test_source_directory}/dir2 ."
*** ocamlc.byte
commandline = "-depend -slash -I dir1 -I dir2 a.ml"
**** check-ocamlc.byte-output
compiler_reference = "${test_source_directory}/a.reference"
*)

include B
include C
6 changes: 6 additions & 0 deletions testsuite/tests/tool-ocamldep-shadowing/a.reference
Original file line number Diff line number Diff line change
@@ -0,0 +1,6 @@
a.cmo : \
dir2/c.cmi \
dir1/b.cmo
a.cmx : \
dir2/c.cmi \
dir1/b.cmx
Empty file.
Empty file.
Empty file.
1 change: 1 addition & 0 deletions testsuite/tests/tool-ocamldep-shadowing/ocamltests
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
a.ml

0 comments on commit 3fac824

Please sign in to comment.