Skip to content

Commit

Permalink
swaps and moves
Browse files Browse the repository at this point in the history
  • Loading branch information
Octachron committed May 31, 2021
1 parent 8268edb commit 0d26ea1
Show file tree
Hide file tree
Showing 14 changed files with 648 additions and 112 deletions.
17 changes: 16 additions & 1 deletion .depend
Original file line number Diff line number Diff line change
Expand Up @@ -66,6 +66,16 @@ utils/diffing.cmx : \
utils/diffing.cmi
utils/diffing.cmi : \
utils/misc.cmi
utils/diffing_with_keys.cmo : \
utils/misc.cmi \
utils/diffing.cmi \
utils/diffing_with_keys.cmi
utils/diffing_with_keys.cmx : \
utils/misc.cmx \
utils/diffing.cmx \
utils/diffing_with_keys.cmi
utils/diffing_with_keys.cmi : \
utils/diffing.cmi
utils/domainstate.cmo : \
utils/domainstate.cmi
utils/domainstate.cmx : \
Expand Down Expand Up @@ -695,6 +705,8 @@ typing/includecore.cmo : \
typing/ident.cmi \
typing/errortrace.cmi \
typing/env.cmi \
utils/diffing_with_keys.cmi \
utils/diffing.cmi \
typing/ctype.cmi \
parsing/builtin_attributes.cmi \
typing/btype.cmi \
Expand All @@ -710,6 +722,8 @@ typing/includecore.cmx : \
typing/ident.cmx \
typing/errortrace.cmx \
typing/env.cmx \
utils/diffing_with_keys.cmx \
utils/diffing.cmx \
typing/ctype.cmx \
parsing/builtin_attributes.cmx \
typing/btype.cmx \
Expand All @@ -723,7 +737,8 @@ typing/includecore.cmi : \
parsing/location.cmi \
typing/ident.cmi \
typing/errortrace.cmi \
typing/env.cmi
typing/env.cmi \
utils/diffing_with_keys.cmi
typing/includemod.cmo : \
typing/types.cmi \
typing/typedtree.cmi \
Expand Down
3 changes: 2 additions & 1 deletion compilerlibs/Makefile.compilerlibs
Original file line number Diff line number Diff line change
Expand Up @@ -45,7 +45,8 @@ UTILS = \
utils/domainstate.cmo \
utils/binutils.cmo \
utils/lazy_backtrack.cmo \
utils/diffing.cmo
utils/diffing.cmo \
utils/diffing_with_keys.cmo
UTILS_CMI =

PARSING = \
Expand Down
2 changes: 1 addition & 1 deletion dune
Original file line number Diff line number Diff line change
Expand Up @@ -45,7 +45,7 @@
config build_path_prefix_map misc identifiable numbers arg_helper clflags
profile terminfo ccomp warnings consistbl strongly_connected_components
targetint load_path int_replace_polymorphic_compare binutils local_store
lazy_backtrack diffing
lazy_backtrack diffing diffing_with_keys

;; PARSING
location longident docstrings syntaxerr ast_helper camlinternalMenhirLib
Expand Down
3 changes: 1 addition & 2 deletions testsuite/tests/typing-misc/records.ml
Original file line number Diff line number Diff line change
Expand Up @@ -267,6 +267,5 @@ Line 1, characters 0-30:
1 | type perm = d = {y:int; x:int}
^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Error: This variant or record definition does not match that of type d
1. Fields have different names, x and y.
2. Fields have different names, y and x.
Fields x and y have been swapped.
|}]
3 changes: 1 addition & 2 deletions testsuite/tests/typing-misc/variant.ml
Original file line number Diff line number Diff line change
Expand Up @@ -122,8 +122,7 @@ Line 1, characters 0-35:
1 | type perm = d = Y of int | X of int
^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Error: This variant or record definition does not match that of type d
1. Constructors have different names, X and Y.
2. Constructors have different names, Y and X.
Constructors X and Y have been swapped.
|}]

module M : sig
Expand Down
216 changes: 214 additions & 2 deletions testsuite/tests/typing-modules/records_errors_test.ml
Original file line number Diff line number Diff line change
Expand Up @@ -281,6 +281,218 @@ Error: Signature mismatch:
g : unit;
}
3. An extra field, beta, is provided in the first declaration.
6. A field, e, is missing in the first declaration.
9. An extra field, phi, is provided in the first declaration.
5. A field, e, is missing in the first declaration.
8. An extra field, phi, is provided in the first declaration.
|}]


(** Multiple errors *)

module M : sig
type t = { a:int; e:int; c:int; d:int; b:int }
end = struct
type t = { alpha:int; b:int; c:int; d:int; e:int }
end
[%%expect {|
Lines 5-7, characters 6-3:
5 | ......struct
6 | type t = { alpha:int; b:int; c:int; d:int; e:int }
7 | end
Error: Signature mismatch:
Modules do not match:
sig
type t = { alpha : int; b : int; c : int; d : int; e : int; }
end
is not included in
sig type t = { a : int; e : int; c : int; d : int; b : int; } end
Type declarations do not match:
type t = { alpha : int; b : int; c : int; d : int; e : int; }
is not included in
type t = { a : int; e : int; c : int; d : int; b : int; }
1. Fields have different names, alpha and a.
2<->5. Fields b and e have been swapped.
|}]


module M: sig
type t = { a:int; b:int; c:int; d:int; e:int; f:float }
end =
struct
type t = { b:int; c:int; d:int; e:int; a:int; f:int }
end
[%%expect {|
Lines 4-6, characters 0-3:
4 | struct
5 | type t = { b:int; c:int; d:int; e:int; a:int; f:int }
6 | end
Error: Signature mismatch:
Modules do not match:
sig
type t = { b : int; c : int; d : int; e : int; a : int; f : int; }
end
is not included in
sig
type t = {
a : int;
b : int;
c : int;
d : int;
e : int;
f : float;
}
end
Type declarations do not match:
type t = { b : int; c : int; d : int; e : int; a : int; f : int; }
is not included in
type t = { a : int; b : int; c : int; d : int; e : int; f : float; }
1->5. Field a has been moved from position 1 to 5.
6. Fields do not match:
f : int;
is not compatible with:
f : float;
The types are not equal.
|}]

(** Existential types introduce equations that must be taken in account
when diffing
*)


module Eq : sig
type t = A: { a:'a; b:'b; x:'a } -> t
end = struct
type t = A: { a:'a; b:'b; x:'x } -> t
end
[%%expect {|
Lines 8-10, characters 6-3:
8 | ......struct
9 | type t = A: { a:'a; b:'b; x:'x } -> t
10 | end
Error: Signature mismatch:
Modules do not match:
sig type t = A : { a : 'a; b : 'b; x : 'x; } -> t end
is not included in
sig type t = A : { a : 'a; b : 'b; x : 'a; } -> t end
Type declarations do not match:
type t = A : { a : 'a; b : 'b; x : 'x; } -> t
is not included in
type t = A : { a : 'a; b : 'b; x : 'a; } -> t
Constructors do not match:
A : { a : 'a; b : 'b; x : 'x; } -> t
is not compatible with:
A : { a : 'a; b : 'b; x : 'a; } -> t
Fields do not match:
x : 'x;
is not compatible with:
x : 'a;
The types are not equal.
|}]


module Not_a_swap: sig
type t = A: { x:'a; a:'a; b:'b; y:'b} -> t
end = struct
type t = A: { y:'a; a:'a; b:'b; x:'b} -> t
end
[%%expect {|
Lines 3-5, characters 6-3:
3 | ......struct
4 | type t = A: { y:'a; a:'a; b:'b; x:'b} -> t
5 | end
Error: Signature mismatch:
Modules do not match:
sig type t = A : { y : 'a; a : 'a; b : 'b; x : 'b; } -> t end
is not included in
sig type t = A : { x : 'a; a : 'a; b : 'b; y : 'b; } -> t end
Type declarations do not match:
type t = A : { y : 'a; a : 'a; b : 'b; x : 'b; } -> t
is not included in
type t = A : { x : 'a; a : 'a; b : 'b; y : 'b; } -> t
Constructors do not match:
A : { y : 'a; a : 'a; b : 'b; x : 'b; } -> t
is not compatible with:
A : { x : 'a; a : 'a; b : 'b; y : 'b; } -> t
1. Fields have different names, y and x.
4. Fields have different names, x and y.
|}]

module Swap: sig
type t = A: { x:'a; a:'a; b:'b; y:'b} -> t
end = struct
type t = A: { y:'b; a:'a; b:'b; x:'a} -> t
end
[%%expect {|
Lines 3-5, characters 6-3:
3 | ......struct
4 | type t = A: { y:'b; a:'a; b:'b; x:'a} -> t
5 | end
Error: Signature mismatch:
Modules do not match:
sig type t = A : { y : 'b; a : 'a; b : 'b; x : 'a; } -> t end
is not included in
sig type t = A : { x : 'a; a : 'a; b : 'b; y : 'b; } -> t end
Type declarations do not match:
type t = A : { y : 'b; a : 'a; b : 'b; x : 'a; } -> t
is not included in
type t = A : { x : 'a; a : 'a; b : 'b; y : 'b; } -> t
Constructors do not match:
A : { y : 'b; a : 'a; b : 'b; x : 'a; } -> t
is not compatible with:
A : { x : 'a; a : 'a; b : 'b; y : 'b; } -> t
Fields x and y have been swapped.
|}]


module Not_a_move: sig
type t = A: { a:'a; b:'b; x:'b} -> t
end = struct
type t = A: { x:'a; a:'a; b:'b} -> t
end
[%%expect {|
Lines 3-5, characters 6-3:
3 | ......struct
4 | type t = A: { x:'a; a:'a; b:'b} -> t
5 | end
Error: Signature mismatch:
Modules do not match:
sig type t = A : { x : 'a; a : 'a; b : 'b; } -> t end
is not included in
sig type t = A : { a : 'a; b : 'b; x : 'b; } -> t end
Type declarations do not match:
type t = A : { x : 'a; a : 'a; b : 'b; } -> t
is not included in
type t = A : { a : 'a; b : 'b; x : 'b; } -> t
Constructors do not match:
A : { x : 'a; a : 'a; b : 'b; } -> t
is not compatible with:
A : { a : 'a; b : 'b; x : 'b; } -> t
1. An extra field, x, is provided in the first declaration.
3. A field, x, is missing in the first declaration.
|}]


module Move: sig
type t = A: { a:'a; b:'b; x:'b} -> t
end = struct
type t = A: { x:'b; a:'a; b:'b} -> t
end
[%%expect {|
Lines 3-5, characters 6-3:
3 | ......struct
4 | type t = A: { x:'b; a:'a; b:'b} -> t
5 | end
Error: Signature mismatch:
Modules do not match:
sig type t = A : { x : 'b; a : 'a; b : 'b; } -> t end
is not included in
sig type t = A : { a : 'a; b : 'b; x : 'b; } -> t end
Type declarations do not match:
type t = A : { x : 'b; a : 'a; b : 'b; } -> t
is not included in
type t = A : { a : 'a; b : 'b; x : 'b; } -> t
Constructors do not match:
A : { x : 'b; a : 'a; b : 'b; } -> t
is not compatible with:
A : { a : 'a; b : 'b; x : 'b; } -> t
Field x has been moved from position 3 to 1.
|}]
91 changes: 89 additions & 2 deletions testsuite/tests/typing-modules/variants_errors_test.ml
Original file line number Diff line number Diff line change
Expand Up @@ -320,6 +320,93 @@ Error: Signature mismatch:
is not included in
type t = A | B | C | D | E | F | G
3. An extra constructor, Beta, is provided in the first declaration.
6. A constructor, E, is missing in the first declaration.
9. An extra constructor, Phi, is provided in the first declaration.
5. A constructor, E, is missing in the first declaration.
8. An extra constructor, Phi, is provided in the first declaration.
|}]


(** Swaps and moves *)

module Swap : sig
type t =
| A
| E
| C
| D
| B
end = struct
type t =
| Alpha
| B
| C
| D
| E
end
[%%expect {|
Lines 10-17, characters 6-3:
10 | ......struct
11 | type t =
12 | | Alpha
13 | | B
14 | | C
15 | | D
16 | | E
17 | end
Error: Signature mismatch:
Modules do not match:
sig type t = Alpha | B | C | D | E end
is not included in
sig type t = A | E | C | D | B end
Type declarations do not match:
type t = Alpha | B | C | D | E
is not included in
type t = A | E | C | D | B
1. Constructors have different names, Alpha and A.
2<->5. Constructors B and E have been swapped.
|}]


module Move: sig
type t =
| A of int
| B
| C
| D
| E
| F
end = struct
type t =
| A of float
| B
| D
| E
| F
| C
end
[%%expect {|
Lines 9-17, characters 6-3:
9 | ......struct
10 | type t =
11 | | A of float
12 | | B
13 | | D
14 | | E
15 | | F
16 | | C
17 | end
Error: Signature mismatch:
Modules do not match:
sig type t = A of float | B | D | E | F | C end
is not included in
sig type t = A of int | B | C | D | E | F end
Type declarations do not match:
type t = A of float | B | D | E | F | C
is not included in
type t = A of int | B | C | D | E | F
1. Constructors do not match:
A of float
is not compatible with:
A of int
The types are not equal.
3->6. Constructor C has been moved from position 3 to 6.
|}]

0 comments on commit 0d26ea1

Please sign in to comment.