Skip to content

Commit

Permalink
Merge pull request #10693 from lpw25/fix-includemod-ident-collision
Browse files Browse the repository at this point in the history
Fix ident collision in includemod
  • Loading branch information
gasche committed Oct 12, 2021
2 parents c937590 + 42aa963 commit 294e717
Show file tree
Hide file tree
Showing 4 changed files with 107 additions and 1 deletion.
3 changes: 3 additions & 0 deletions Changes
Original file line number Diff line number Diff line change
Expand Up @@ -278,6 +278,9 @@ Working version
rather than a basename.
(David Allsopp, report by Fabian @copy, review by Gabriel Scherer)

- #10693: Fix ident collision in includemod
(Leo White, review by Matthew Ryan)

OCaml 4.13 maintenance branch
-----------------------------

Expand Down
Original file line number Diff line number Diff line change
@@ -0,0 +1,55 @@
File "pr10693_bad.ml", line 27, characters 26-27:
27 | module Bad (A : S') : S = A
^
Error: Signature mismatch:
Modules do not match:
sig val x : 'a option module M : Dep -> S end
is not included in
S
In module M:
Modules do not match:
Dep -> S
is not included in
functor (X : Dep) ->
sig
val x : X.t option
module M : functor (Y : Dep) -> sig val x : X.t option end
end
In module M:
Modules do not match:
S
is not included in
sig
val x : X.t option
module M : functor (Y : Dep) -> sig val x : X.t option end
end
In module M.M:
Modules do not match:
functor (X : Dep) ->
sig
val x : X.t option
module M : functor (Y : Dep) -> sig val x : X.t option end
end
is not included in
functor (Y : Dep) -> sig val x : X.t option end
In module M.M:
Modules do not match:
sig
val x : X/2.t option
module M : functor (Y : Dep) -> sig val x : X/2.t option end
end
is not included in
sig val x : X.t option end
In module M.M:
Values do not match:
val x : X/1.t option
is not included in
val x : X/2.t option
The type X/1.t option is not compatible with the type X/2.t option
Type X/1.t is not compatible with type X/2.t
File "_none_", line 1:
Definition of module X/1
File "_none_", line 1:
Definition of module X/2
File "pr10693_bad.ml", line 17, characters 6-24: Expected declaration
File "pr10693_bad.ml", line 15, characters 4-22: Actual declaration
46 changes: 46 additions & 0 deletions testsuite/tests/typing-modules-bugs/pr10693_bad.ml
Original file line number Diff line number Diff line change
@@ -0,0 +1,46 @@
(* TEST
flags = "-no-app-funct"
ocamlc_byte_exit_status = "2"
* setup-ocamlc.byte-build-env
** ocamlc.byte
*** check-ocamlc.byte-output
*)
module type Dep = sig type t val x : t end
module String = struct type t = string let x = "Forty Two" end
module Int = struct type t = int let x = 42 end

module type S = sig
val x : 'a option
module M : functor (X : Dep) -> sig
val x : X.t option
module M : functor (Y : Dep) -> sig
val x : X.t option
end
end
end

module type S' = sig
val x : 'a option
module M : functor (_ : Dep) -> S
end

module Bad (A : S') : S = A

module M = struct
let x = None
module M (_ : Dep) = struct
let x = None
module M (X : Dep) = struct
let x = Some X.x
module M (Y : Dep) = struct
let x = Some X.x
end
end
end
end

module N = Bad(M)
module N' = N.M(String)
module N'' = N'.M(Int)

let () = print_endline (Option.get N''.x)
4 changes: 3 additions & 1 deletion typing/includemod.ml
Original file line number Diff line number Diff line change
Expand Up @@ -496,7 +496,9 @@ and functor_param ~in_eq ~loc env ~mark subst param1 param2 =
Env.add_module id1 Mp_present arg2' env,
Subst.add_module id2 (Path.Pident id1) subst
| None, Some id2 ->
Env.add_module id2 Mp_present arg2' env, subst
let id1 = Ident.rename id2 in
Env.add_module id1 Mp_present arg2' env,
Subst.add_module id2 (Path.Pident id1) subst
| Some id1, None ->
Env.add_module id1 Mp_present arg2' env, subst
| None, None ->
Expand Down

0 comments on commit 294e717

Please sign in to comment.