Skip to content

Commit

Permalink
Add more new test cases for module inclusion errors
Browse files Browse the repository at this point in the history
These test cases will also have improved error messages in the next
non-test commit.  They come from the work done to address reviewer
comments for ocaml#10407.
  • Loading branch information
antalsz committed May 21, 2021
1 parent a251d85 commit aff5d6a
Show file tree
Hide file tree
Showing 4 changed files with 403 additions and 0 deletions.
36 changes: 36 additions & 0 deletions testsuite/tests/typing-gadts/return_type.ml
Original file line number Diff line number Diff line change
@@ -0,0 +1,36 @@
(* TEST
* expect
*)

type i = int

type 'a t = T : i
[%%expect{|
type i = int
Line 3, characters 16-17:
3 | type 'a t = T : i
^
Error: Constraints are not satisfied in this type.
Type i should be an instance of 'a t
|}]

type 'a t = T : i t
type 'a s = 'a t = T : i t
[%%expect{|
type 'a t = T : i t
Line 2, characters 23-26:
2 | type 'a s = 'a t = T : i t
^^^
Error: Constraints are not satisfied in this type.
Type i t should be an instance of 'a s
|}]

type 'a t = T : i s
and 'a s = 'a t
[%%expect{|
Line 1, characters 16-19:
1 | type 'a t = T : i s
^^^
Error: Constraints are not satisfied in this type.
Type i s should be an instance of 'a t
|}]
Original file line number Diff line number Diff line change
Expand Up @@ -42,3 +42,20 @@ Error: Signature mismatch:
type t += A
A private type would be revealed.
|}];;

module M2 : sig type t += A end = struct type t += private A | B end;;
[%%expect{|
Line 1, characters 34-68:
1 | module M2 : sig type t += A end = struct type t += private A | B end;;
^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Error: Signature mismatch:
Modules do not match:
sig type t += private A | B end
is not included in
sig type t += A end
Extension declarations do not match:
type t += private A
is not included in
type t += A
A private type would be revealed.
|}];;
329 changes: 329 additions & 0 deletions testsuite/tests/typing-modules/inclusion_errors.ml
Original file line number Diff line number Diff line change
Expand Up @@ -538,6 +538,27 @@ Error: Signature mismatch:
val f : s -> s
|}];;

module M : sig
val f : 'a -> float
end = struct
let f : 'b -> int = fun _ -> 0
end;;
[%%expect{|
Lines 3-5, characters 6-3:
3 | ......struct
4 | let f : 'b -> int = fun _ -> 0
5 | end..
Error: Signature mismatch:
Modules do not match:
sig val f : 'b -> int end
is not included in
sig val f : 'a -> float end
Values do not match:
val f : 'b -> int
is not included in
val f : 'a -> float
|}]

module M : sig
val x : 'a list ref
end = struct
Expand Down Expand Up @@ -1236,3 +1257,311 @@ Error: Signature mismatch:
is not included in
type t = private float
|}];;

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

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 = A of { x : int; y : bool }
end = struct
type t = private A of { x : int; y : bool }
end;;
[%%expect{|
Lines 3-5, characters 6-3:
3 | ......struct
4 | type t = private A of { x : int; y : bool }
5 | end..
Error: Signature mismatch:
Modules do not match:
sig type t = private A of { x : int; y : bool; } end
is not included in
sig type t = A of { x : int; y : bool; } end
Type declarations do not match:
type t = private A of { x : int; y : bool; }
is not included in
type t = A of { x : int; y : bool; }
A private type would be revealed.
|}];;

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

module M : sig
type t = A
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 end
Type declarations do not match:
type t = private A | B
is not included in
type t = A
A private type would be revealed.
|}];;

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

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

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

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

module M : sig
type t = { x : int; y : bool }
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 = { x : int; y : bool; } end
Type declarations do not match:
type t = private A | B
is not included in
type t = { x : int; y : bool; }
A private type would be revealed.
|}];;

module M : sig
type t = [`A]
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 ] end
Type declarations do not match:
type t = private [> `A | `B ]
is not included in
type t = [ `A ]
A private type would be revealed.
|}];;

module M : sig
type t = [`A]
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 ] end
Type declarations do not match:
type t = private [< `A | `B ]
is not included in
type t = [ `A ]
A private type would be revealed.
|}];;

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

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

0 comments on commit aff5d6a

Please sign in to comment.