Skip to content

Commit

Permalink
Assume that module names that are not in Env.t are persistent (#2235)
Browse files Browse the repository at this point in the history
Fix bug introduced by #2041

The environment used to lookup global identifiers coming from loaded
cmi files was incomplete, leading to identifiers that could not be
resolved.

This patch fixes the issue by assuming that module names that are not
found in the environment are always external.

Signed-off-by: Jeremie Dimino <jeremie@dimino.org>
  • Loading branch information
jeremiedimino authored and trefis committed Feb 6, 2019
1 parent b955ac9 commit 5c828b5
Show file tree
Hide file tree
Showing 8 changed files with 52 additions and 21 deletions.
4 changes: 2 additions & 2 deletions Changes
Original file line number Diff line number Diff line change
Expand Up @@ -60,8 +60,8 @@ OCaml 4.08.0
(Alban Reynaud and Gabriel Scherer,
review by Jeremy Yallop and Armaël Guéneau)

* MPR#7814, GPR#2041: allow modules from include directories to shadow
other ones, even in the toplevel
* MPR#7814, GPR#2041, GPR#2235: allow modules from include directories
to shadow other ones, even in the toplevel
(Jérémie Dimino, review by Alain Frisch and David Allsopp)

### Standard library:
Expand Down
1 change: 1 addition & 0 deletions testsuite/tests/no-alias-deps/a2235.ml
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
let x = 42
21 changes: 21 additions & 0 deletions testsuite/tests/no-alias-deps/gpr2235.ml
Original file line number Diff line number Diff line change
@@ -0,0 +1,21 @@
(* TEST
flags = "-no-alias-deps -w -49"
compile_only = "true"
files = "a2235.ml lib__2235.ml lib2235.ml user_of_lib2235.ml"
* setup-ocamlc.byte-build-env
** ocamlc.byte
module = "lib__2235.ml"
*** check-ocamlc.byte-output
**** ocamlc.byte
flags = "-no-alias-deps -w -49 -open Lib__2235 -o lib__A2235.cmo"
module = "a2235.ml"
***** check-ocamlc.byte-output
****** ocamlc.byte
flags = "-no-alias-deps -w -49 -open Lib__2235"
module = "lib2235.ml"
******* check-ocamlc.byte-output
******** ocamlc.byte
flags = "-no-alias-deps -w -49"
module = "user_of_lib2235.ml"
********* check-ocamlc.byte-output
*)
1 change: 1 addition & 0 deletions testsuite/tests/no-alias-deps/lib2235.ml
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
module A2235 = A2235
1 change: 1 addition & 0 deletions testsuite/tests/no-alias-deps/lib__2235.ml
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
module A2235 = Lib__A2235
1 change: 1 addition & 0 deletions testsuite/tests/no-alias-deps/ocamltests
Original file line number Diff line number Diff line change
@@ -1 +1,2 @@
aliases.ml
gpr2235.ml
3 changes: 3 additions & 0 deletions testsuite/tests/no-alias-deps/user_of_lib2235.ml
Original file line number Diff line number Diff line change
@@ -0,0 +1,3 @@
open Lib2235

let x = A2235.x
41 changes: 22 additions & 19 deletions typing/env.ml
Original file line number Diff line number Diff line change
Expand Up @@ -675,6 +675,13 @@ let rec print_address ppf = function

let current_unit = ref ""

let find_same_module id tbl =
match IdTbl.find_same id tbl with
| x -> x
| exception Not_found
when Ident.persistent id && not (Ident.name id = !current_unit) ->
Persistent

(* Persistent structure descriptions *)

type pers_struct =
Expand Down Expand Up @@ -771,15 +778,9 @@ let acknowledge_pers_struct check modname
let id = Ident.create_persistent name in
let path = Pident id in
let addr = EnvLazy.create_forced (Aident id) in
let env =
let add_imported_persistent env (name, _digest) =
add_persistent_structure (Ident.create_persistent name) env
in
List.fold_left add_imported_persistent empty crcs
in
let comps =
!components_of_module' ~alerts ~loc:Location.none
env Subst.identity path addr (Mty_signature sign)
empty Subst.identity path addr (Mty_signature sign)
in
let ps = { ps_name = name;
ps_sig = lazy (Subst.signature Subst.identity sign);
Expand Down Expand Up @@ -916,7 +917,7 @@ let get_unit_name () =
let rec find_module_descr path env =
match path with
Pident id ->
begin match IdTbl.find_same id env.components with
begin match find_same_module id env.components with
| Value x -> fst x
| Persistent -> (find_pers_struct (Ident.name id)).ps_comps
end
Expand Down Expand Up @@ -1019,7 +1020,7 @@ let find_module ~alias path env =
match path with
Pident id ->
begin
match IdTbl.find_same id env.modules with
match find_same_module id env.modules with
| Value (data, _) -> EnvLazy.force subst_modtype_maker data
| Persistent ->
let ps = find_pers_struct (Ident.name id) in
Expand Down Expand Up @@ -1061,12 +1062,9 @@ let rec find_module_address path env =
match path with
| Pident id ->
begin
match IdTbl.find_same id env.modules with
match find_same_module id env.modules with
| Value (_, addr) -> get_address addr
| Persistent ->
if not (Ident.name id = !current_unit) then
Aident id
else raise Not_found
| Persistent -> Aident id
end
| Pdot(p, s) -> begin
match get_components (find_module_descr p env) with
Expand Down Expand Up @@ -1263,11 +1261,16 @@ let mark_module_used name loc =
let rec lookup_module_descr_aux ?loc ~mark lid env =
match lid with
Lident s ->
let (p, data) = IdTbl.find_name ~mark s env.components in
(p,
match data with
| Value (comp, _) -> comp
| Persistent -> (find_pers_struct s).ps_comps)
begin match IdTbl.find_name ~mark s env.components with
| exception Not_found when s <> !current_unit ->
let p = Path.Pident (Ident.create_persistent s) in
(p, (find_pers_struct s).ps_comps)
| (p, data) ->
(p,
match data with
| Value (comp, _) -> comp
| Persistent -> (find_pers_struct s).ps_comps)
end
| Ldot(l, s) ->
let (p, descr) = lookup_module_descr ?loc ~mark l env in
begin match get_components descr with
Expand Down

0 comments on commit 5c828b5

Please sign in to comment.