Skip to content

Commit

Permalink
Add new test cases for module inclusion errors
Browse files Browse the repository at this point in the history
These test cases will have improved error messages in the next commit
  • Loading branch information
antalsz committed May 10, 2021
1 parent 49528a6 commit 40c4bd0
Show file tree
Hide file tree
Showing 4 changed files with 521 additions and 6 deletions.
88 changes: 88 additions & 0 deletions testsuite/tests/typing-misc/deep.ml
Original file line number Diff line number Diff line change
@@ -0,0 +1,88 @@
(* TEST
* expect
*)

module M : sig
val x : bool * int
end = struct
let x = false , "not an int"
end
[%%expect{|
Lines 3-5, characters 6-3:
3 | ......struct
4 | let x = false , "not an int"
5 | end
Error: Signature mismatch:
Modules do not match:
sig val x : bool * string end
is not included in
sig val x : bool * int end
Values do not match:
val x : bool * string
is not included in
val x : bool * int
|}]

module T : sig
val f : int -> (float * string ref) list
end = struct
let f x = x + List.length [0.0, ref true]
end
[%%expect{|
Lines 3-5, characters 6-3:
3 | ......struct
4 | let f x = x + List.length [0.0, ref true]
5 | end
Error: Signature mismatch:
Modules do not match:
sig val f : int -> int end
is not included in
sig val f : int -> (float * string ref) list end
Values do not match:
val f : int -> int
is not included in
val f : int -> (float * string ref) list
|}]

(* Alpha-equivalence *)
module T : sig
val f : ('a list * 'b list -> int)
end = struct
let f : ('c list * 'd ref -> int) = assert false
end
[%%expect{|
Lines 3-5, characters 6-3:
3 | ......struct
4 | let f : ('c list * 'd ref -> int) = assert false
5 | end
Error: Signature mismatch:
Modules do not match:
sig val f : 'c list * 'd ref -> int end
is not included in
sig val f : 'a list * 'b list -> int end
Values do not match:
val f : 'c list * 'd ref -> int
is not included in
val f : 'a list * 'b list -> int
|}]

module T : sig
type t = int * float
end = struct
type t = bool * float
end
[%%expect{|
Lines 3-5, characters 6-3:
3 | ......struct
4 | type t = bool * float
5 | end
Error: Signature mismatch:
Modules do not match:
sig type t = bool * float end
is not included in
sig type t = int * float end
Type declarations do not match:
type t = bool * float
is not included in
type t = int * float
|}]
64 changes: 64 additions & 0 deletions testsuite/tests/typing-modules/inclusion_errors.ml
Original file line number Diff line number Diff line change
Expand Up @@ -1053,6 +1053,70 @@ Error: Signature mismatch:
type t = private [> `A of int ]
|}];;

module M : sig
type t = private [< `A | `B]
end = struct
type t = private [`A | `B]
end;;
[%%expect{|
Lines 3-5, characters 6-3:
3 | ......struct
4 | type t = private [`A | `B]
5 | end..
Error: Signature mismatch:
Modules do not match:
sig type t = private [ `A | `B ] end
is not included in
sig type t = private [< `A | `B ] end
Type declarations do not match:
type t = private [ `A | `B ]
is not included in
type t = private [< `A | `B ]
|}];;

module M : sig
type t = [`A | `B]
end = struct
type t = private [`A | `B]
end;;
[%%expect{|
Lines 3-5, characters 6-3:
3 | ......struct
4 | type t = private [`A | `B]
5 | end..
Error: Signature mismatch:
Modules do not match:
sig type t = private [ `A | `B ] end
is not included in
sig type t = [ `A | `B ] end
Type declarations do not match:
type t = private [ `A | `B ]
is not included in
type t = [ `A | `B ]
A private type would be revealed.
|}];;

module M : sig
type t = private [< `A | `B > `B]
end = struct
type t = private [< `A | `B]
end;;
[%%expect{|
Lines 3-5, characters 6-3:
3 | ......struct
4 | type t = private [< `A | `B]
5 | end..
Error: Signature mismatch:
Modules do not match:
sig type t = private [< `A | `B ] end
is not included in
sig type t = private [< `A | `B > `B ] end
Type declarations do not match:
type t = private [< `A | `B ]
is not included in
type t = private [< `A | `B > `B ]
|}];;

module M : sig
type t = private <a : int; ..>
end = struct
Expand Down
44 changes: 44 additions & 0 deletions testsuite/tests/typing-modules/pr10399.ml
Original file line number Diff line number Diff line change
@@ -0,0 +1,44 @@
(* TEST
* expect
*)

(* From jctis: <https://github.com/ocaml/ocaml/issues/10399> *)

module PR10399 : sig
type t = < x : int >

class c : object method x : int method y : bool end

val o : t
end = struct
type t = < x : int >

class c = object method x = 3 method y = true end

let o = new c
end

[%%expect{|
Lines 7-13, characters 6-3:
7 | ......struct
8 | type t = < x : int >
9 |
10 | class c = object method x = 3 method y = true end
11 |
12 | let o = new c
13 | end
Error: Signature mismatch:
Modules do not match:
sig
type t = < x : int >
class c : object method x : int method y : bool end
val o : c
end
is not included in
sig
type t = < x : int >
class c : object method x : int method y : bool end
val o : t
end
Values do not match: val o : c is not included in val o : t
|}]
Loading

0 comments on commit 40c4bd0

Please sign in to comment.