Fix PR#6365

git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@14565 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
master
Jacques Garrigue 2014-04-09 04:01:26 +00:00
parent f309a7a05c
commit fb74ef5e51
3 changed files with 12 additions and 1 deletions

View File

@ -192,3 +192,9 @@ module M = struct
end
end;;
module type S = module type of M ;;
(* PR#6365 *)
module type S = sig module M : sig type t val x : t end end;;
module H = struct type t = A let x = A end;;
module H' = H;;
module type S' = S with module M = H';; (* shouldn't introduce an alias *)

View File

@ -347,4 +347,8 @@ Error: In this `with' constraint, the new definition of I
module Q :
sig type wrap' = wrap = W of (Set.Make(Int).t, Set.Make(N.I).t) eq end
end
# module type S = sig module M : sig type t val x : t end end
# module H : sig type t = A val x : t end
# module H' = H
# module type S' = sig module M : sig type t = H.t = A val x : t end end
#

View File

@ -198,7 +198,8 @@ let merge_constraint initial_env loc sg constr =
when Ident.name id = s ->
let path = Typetexp.find_module initial_env loc lid.txt in
let md' = Env.find_module path env in
let newmd = Mtype.strengthen_decl env md' path in
let md'' = {md' with md_type = Mtype.remove_aliases env md'.md_type} in
let newmd = Mtype.strengthen_decl env md'' path in
ignore(Includemod.modtypes env newmd.md_type md.md_type);
(Pident id, lid, Twith_module (path, lid)),
Sig_module(id, newmd, rs) :: rem