Fix PR#7414 for local modules

master
Leo White 2018-05-09 14:14:49 +01:00
parent dd01cab508
commit 7c63ec8e98
4 changed files with 70 additions and 0 deletions

View File

@ -30,6 +30,7 @@ pr7182_ok.ml
pr7305_principal.ml
pr7321_ok.ml
pr7414_bad.ml
pr7414_2_bad.ml
pr7519_ok.ml
pr7601_ok.ml
pr7601a_ok.ml

View File

@ -0,0 +1,18 @@
File "pr7414_2_bad.ml", line 46, characters 28-34:
Error: Signature mismatch:
Modules do not match:
functor () -> sig module Choice : T val r : '_weak1 list ref ref end
is not included in
functor () -> S
At position functor () -> <here>
Modules do not match:
sig module Choice : T val r : '_weak1 list ref ref end
is not included in
S
At position functor () -> <here>
Values do not match:
val r : '_weak1 list ref ref
is not included in
val r : Choice.t list ref ref
File "pr7414_2_bad.ml", line 29, characters 2-31: Expected declaration
File "pr7414_2_bad.ml", line 40, characters 8-9: Actual declaration

View File

@ -0,0 +1,50 @@
(* TEST
flags = " -w a "
ocamlc_byte_exit_status = "2"
* setup-ocamlc.byte-build-env
** ocamlc.byte
*** check-ocamlc.byte-output
*)
module type T = sig
type t
val x : t
val show : t -> string
end
module Int = struct
type t = int
let x = 0
let show x = string_of_int x
end
module String = struct
type t = string
let x = "Hello"
let show x = x
end
module type S = sig
module Choice : T
val r : Choice.t list ref ref
end
module Force (X : functor () -> S) = struct end
let () =
let switch = ref true in
let module Choose () = struct
module Choice =
(val if !switch then (module Int : T)
else (module String : T))
let r = ref (ref [])
end in
let module M = Choose () in
let () = switch := false in
let module N = Choose () in
let () = N.r := !M.r in
let module Ignore = Force(Choose) in
let module M' = (M : S) in
let () = (!M'.r) := [M'.Choice.x] in
let module N' = (N : S) in
List.iter (fun x -> print_string (N'.Choice.show x)) !(!N'.r)

View File

@ -3652,6 +3652,7 @@ and type_expect_
Ident.set_current_time ty.level;
let context = Typetexp.narrow () in
let modl = !type_module env smodl in
Mtype.lower_nongen ty.level modl.mod_type;
let (id, new_env) = Env.enter_module name.txt modl.mod_type env in
Ctype.init_def(Ident.current_time());
Typetexp.widen context;