Skip to content

Commit

Permalink
Accept test results
Browse files Browse the repository at this point in the history
  • Loading branch information
nojb committed Aug 24, 2021
1 parent 974a56a commit 55dd374
Show file tree
Hide file tree
Showing 3 changed files with 93 additions and 93 deletions.
168 changes: 84 additions & 84 deletions testsuite/tests/basic/patmatch_for_multiple.ml
Original file line number Diff line number Diff line change
Expand Up @@ -26,15 +26,15 @@ match (3, 2, 1) with
| _ -> false
;;
[%%expect{|
(let (*match*/88 = 3 *match*/89 = 2 *match*/90 = 1)
(let (*match*/90 = 3 *match*/91 = 2 *match*/92 = 1)
(catch
(catch
(catch (if (!= *match*/89 3) (exit 3) (exit 1)) with (3)
(if (!= *match*/88 1) (exit 2) (exit 1)))
(catch (if (!= *match*/91 3) (exit 3) (exit 1)) with (3)
(if (!= *match*/90 1) (exit 2) (exit 1)))
with (2) 0)
with (1) 1))
(let (*match*/88 = 3 *match*/89 = 2 *match*/90 = 1)
(catch (if (!= *match*/89 3) (if (!= *match*/88 1) 0 (exit 1)) (exit 1))
(let (*match*/90 = 3 *match*/91 = 2 *match*/92 = 1)
(catch (if (!= *match*/91 3) (if (!= *match*/90 1) 0 (exit 1)) (exit 1))
with (1) 1))
- : bool = false
|}];;
Expand All @@ -47,26 +47,26 @@ match (3, 2, 1) with
| _ -> false
;;
[%%expect{|
(let (*match*/93 = 3 *match*/94 = 2 *match*/95 = 1)
(let (*match*/95 = 3 *match*/96 = 2 *match*/97 = 1)
(catch
(catch
(catch
(if (!= *match*/94 3) (exit 6)
(let (x/97 =a (makeblock 0 *match*/93 *match*/94 *match*/95))
(exit 4 x/97)))
(if (!= *match*/96 3) (exit 6)
(let (x/99 =a (makeblock 0 *match*/95 *match*/96 *match*/97))
(exit 4 x/99)))
with (6)
(if (!= *match*/93 1) (exit 5)
(let (x/96 =a (makeblock 0 *match*/93 *match*/94 *match*/95))
(exit 4 x/96))))
(if (!= *match*/95 1) (exit 5)
(let (x/98 =a (makeblock 0 *match*/95 *match*/96 *match*/97))
(exit 4 x/98))))
with (5) 0)
with (4 x/91) (seq (ignore x/91) 1)))
(let (*match*/93 = 3 *match*/94 = 2 *match*/95 = 1)
with (4 x/93) (seq (ignore x/93) 1)))
(let (*match*/95 = 3 *match*/96 = 2 *match*/97 = 1)
(catch
(if (!= *match*/94 3)
(if (!= *match*/93 1) 0
(exit 4 (makeblock 0 *match*/93 *match*/94 *match*/95)))
(exit 4 (makeblock 0 *match*/93 *match*/94 *match*/95)))
with (4 x/91) (seq (ignore x/91) 1)))
(if (!= *match*/96 3)
(if (!= *match*/95 1) 0
(exit 4 (makeblock 0 *match*/95 *match*/96 *match*/97)))
(exit 4 (makeblock 0 *match*/95 *match*/96 *match*/97)))
with (4 x/93) (seq (ignore x/93) 1)))
- : bool = false
|}];;
Expand All @@ -76,8 +76,8 @@ let _ = fun a b ->
| ((true, _) as _g)
| ((false, _) as _g) -> ()
[%%expect{|
(function a/98[int] b/99 : int 0)
(function a/98[int] b/99 : int 0)
(function a/100[int] b/101 : int 0)
(function a/100[int] b/101 : int 0)
- : bool -> 'a -> unit = <fun>
|}];;
Expand All @@ -96,8 +96,8 @@ let _ = fun a b -> match a, b with
| (false, _) as p -> p
(* outside, trivial *)
[%%expect {|
(function a/102[int] b/103 (let (p/104 =a (makeblock 0 a/102 b/103)) p/104))
(function a/102[int] b/103 (makeblock 0 a/102 b/103))
(function a/104[int] b/105 (let (p/106 =a (makeblock 0 a/104 b/105)) p/106))
(function a/104[int] b/105 (makeblock 0 a/104 b/105))
- : bool -> 'a -> bool * 'a = <fun>
|}]
Expand All @@ -106,8 +106,8 @@ let _ = fun a b -> match a, b with
| ((false, _) as p) -> p
(* inside, trivial *)
[%%expect{|
(function a/106[int] b/107 (let (p/108 =a (makeblock 0 a/106 b/107)) p/108))
(function a/106[int] b/107 (makeblock 0 a/106 b/107))
(function a/108[int] b/109 (let (p/110 =a (makeblock 0 a/108 b/109)) p/110))
(function a/108[int] b/109 (makeblock 0 a/108 b/109))
- : bool -> 'a -> bool * 'a = <fun>
|}];;
Expand All @@ -116,11 +116,11 @@ let _ = fun a b -> match a, b with
| (false as x, _) as p -> x, p
(* outside, simple *)
[%%expect {|
(function a/112[int] b/113
(let (x/114 =a[int] a/112 p/115 =a (makeblock 0 a/112 b/113))
(makeblock 0 (int,*) x/114 p/115)))
(function a/112[int] b/113
(makeblock 0 (int,*) a/112 (makeblock 0 a/112 b/113)))
(function a/114[int] b/115
(let (x/116 =a[int] a/114 p/117 =a (makeblock 0 a/114 b/115))
(makeblock 0 (int,*) x/116 p/117)))
(function a/114[int] b/115
(makeblock 0 (int,*) a/114 (makeblock 0 a/114 b/115)))
- : bool -> 'a -> bool * (bool * 'a) = <fun>
|}]
Expand All @@ -129,11 +129,11 @@ let _ = fun a b -> match a, b with
| ((false as x, _) as p) -> x, p
(* inside, simple *)
[%%expect {|
(function a/118[int] b/119
(let (x/120 =a[int] a/118 p/121 =a (makeblock 0 a/118 b/119))
(makeblock 0 (int,*) x/120 p/121)))
(function a/118[int] b/119
(makeblock 0 (int,*) a/118 (makeblock 0 a/118 b/119)))
(function a/120[int] b/121
(let (x/122 =a[int] a/120 p/123 =a (makeblock 0 a/120 b/121))
(makeblock 0 (int,*) x/122 p/123)))
(function a/120[int] b/121
(makeblock 0 (int,*) a/120 (makeblock 0 a/120 b/121)))
- : bool -> 'a -> bool * (bool * 'a) = <fun>
|}]

Expand All @@ -142,15 +142,15 @@ let _ = fun a b -> match a, b with
| (false, x) as p -> x, p
(* outside, complex *)
[%%expect{|
(function a/128[int] b/129[int]
(if a/128
(let (x/130 =a[int] a/128 p/131 =a (makeblock 0 a/128 b/129))
(makeblock 0 (int,*) x/130 p/131))
(let (x/132 =a b/129 p/133 =a (makeblock 0 a/128 b/129))
(makeblock 0 (int,*) x/132 p/133))))
(function a/128[int] b/129[int]
(if a/128 (makeblock 0 (int,*) a/128 (makeblock 0 a/128 b/129))
(makeblock 0 (int,*) b/129 (makeblock 0 a/128 b/129))))
(function a/130[int] b/131[int]
(if a/130
(let (x/132 =a[int] a/130 p/133 =a (makeblock 0 a/130 b/131))
(makeblock 0 (int,*) x/132 p/133))
(let (x/134 =a b/131 p/135 =a (makeblock 0 a/130 b/131))
(makeblock 0 (int,*) x/134 p/135))))
(function a/130[int] b/131[int]
(if a/130 (makeblock 0 (int,*) a/130 (makeblock 0 a/130 b/131))
(makeblock 0 (int,*) b/131 (makeblock 0 a/130 b/131))))
- : bool -> bool -> bool * (bool * bool) = <fun>
|}]

Expand All @@ -160,19 +160,19 @@ let _ = fun a b -> match a, b with
-> x, p
(* inside, complex *)
[%%expect{|
(function a/134[int] b/135[int]
(function a/136[int] b/137[int]
(catch
(if a/134
(let (x/142 =a[int] a/134 p/143 =a (makeblock 0 a/134 b/135))
(exit 10 x/142 p/143))
(let (x/140 =a b/135 p/141 =a (makeblock 0 a/134 b/135))
(exit 10 x/140 p/141)))
with (10 x/136[int] p/137) (makeblock 0 (int,*) x/136 p/137)))
(function a/134[int] b/135[int]
(if a/136
(let (x/144 =a[int] a/136 p/145 =a (makeblock 0 a/136 b/137))
(exit 10 x/144 p/145))
(let (x/142 =a b/137 p/143 =a (makeblock 0 a/136 b/137))
(exit 10 x/142 p/143)))
with (10 x/138[int] p/139) (makeblock 0 (int,*) x/138 p/139)))
(function a/136[int] b/137[int]
(catch
(if a/134 (exit 10 a/134 (makeblock 0 a/134 b/135))
(exit 10 b/135 (makeblock 0 a/134 b/135)))
with (10 x/136[int] p/137) (makeblock 0 (int,*) x/136 p/137)))
(if a/136 (exit 10 a/136 (makeblock 0 a/136 b/137))
(exit 10 b/137 (makeblock 0 a/136 b/137)))
with (10 x/138[int] p/139) (makeblock 0 (int,*) x/138 p/139)))
- : bool -> bool -> bool * (bool * bool) = <fun>
|}]

Expand All @@ -185,15 +185,15 @@ let _ = fun a b -> match a, b with
| (false as x, _) as p -> x, p
(* outside, onecase *)
[%%expect {|
(function a/144[int] b/145[int]
(if a/144
(let (x/146 =a[int] a/144 _p/147 =a (makeblock 0 a/144 b/145))
(makeblock 0 (int,*) x/146 [0: 1 1]))
(let (x/148 =a[int] a/144 p/149 =a (makeblock 0 a/144 b/145))
(makeblock 0 (int,*) x/148 p/149))))
(function a/144[int] b/145[int]
(if a/144 (makeblock 0 (int,*) a/144 [0: 1 1])
(makeblock 0 (int,*) a/144 (makeblock 0 a/144 b/145))))
(function a/146[int] b/147[int]
(if a/146
(let (x/148 =a[int] a/146 _p/149 =a (makeblock 0 a/146 b/147))
(makeblock 0 (int,*) x/148 [0: 1 1]))
(let (x/150 =a[int] a/146 p/151 =a (makeblock 0 a/146 b/147))
(makeblock 0 (int,*) x/150 p/151))))
(function a/146[int] b/147[int]
(if a/146 (makeblock 0 (int,*) a/146 [0: 1 1])
(makeblock 0 (int,*) a/146 (makeblock 0 a/146 b/147))))
- : bool -> bool -> bool * (bool * bool) = <fun>
|}]

Expand All @@ -202,11 +202,11 @@ let _ = fun a b -> match a, b with
| ((false as x, _) as p) -> x, p
(* inside, onecase *)
[%%expect{|
(function a/150[int] b/151
(let (x/152 =a[int] a/150 p/153 =a (makeblock 0 a/150 b/151))
(makeblock 0 (int,*) x/152 p/153)))
(function a/150[int] b/151
(makeblock 0 (int,*) a/150 (makeblock 0 a/150 b/151)))
(function a/152[int] b/153
(let (x/154 =a[int] a/152 p/155 =a (makeblock 0 a/152 b/153))
(makeblock 0 (int,*) x/154 p/155)))
(function a/152[int] b/153
(makeblock 0 (int,*) a/152 (makeblock 0 a/152 b/153)))
- : bool -> 'a -> bool * (bool * 'a) = <fun>
|}]

Expand All @@ -223,14 +223,14 @@ let _ =fun a b -> match a, b with
| (_, _) as p -> p
(* outside, tuplist *)
[%%expect {|
(function a/163[int] b/164
(function a/165[int] b/166
(catch
(if a/163 (if b/164 (let (p/165 =a (field 0 b/164)) p/165) (exit 12))
(if a/165 (if b/166 (let (p/167 =a (field 0 b/166)) p/167) (exit 12))
(exit 12))
with (12) (let (p/166 =a (makeblock 0 a/163 b/164)) p/166)))
(function a/163[int] b/164
(catch (if a/163 (if b/164 (field 0 b/164) (exit 12)) (exit 12)) with (12)
(makeblock 0 a/163 b/164)))
with (12) (let (p/168 =a (makeblock 0 a/165 b/166)) p/168)))
(function a/165[int] b/166
(catch (if a/165 (if b/166 (field 0 b/166) (exit 12)) (exit 12)) with (12)
(makeblock 0 a/165 b/166)))
- : bool -> bool tuplist -> bool * bool tuplist = <fun>
|}]

Expand All @@ -239,19 +239,19 @@ let _ = fun a b -> match a, b with
| ((_, _) as p) -> p
(* inside, tuplist *)
[%%expect{|
(function a/167[int] b/168
(function a/169[int] b/170
(catch
(catch
(if a/167
(if b/168 (let (p/172 =a (field 0 b/168)) (exit 13 p/172)) (exit 14))
(if a/169
(if b/170 (let (p/174 =a (field 0 b/170)) (exit 13 p/174)) (exit 14))
(exit 14))
with (14) (let (p/171 =a (makeblock 0 a/167 b/168)) (exit 13 p/171)))
with (13 p/169) p/169))
(function a/167[int] b/168
with (14) (let (p/173 =a (makeblock 0 a/169 b/170)) (exit 13 p/173)))
with (13 p/171) p/171))
(function a/169[int] b/170
(catch
(catch
(if a/167 (if b/168 (exit 13 (field 0 b/168)) (exit 14)) (exit 14))
with (14) (exit 13 (makeblock 0 a/167 b/168)))
with (13 p/169) p/169))
(if a/169 (if b/170 (exit 13 (field 0 b/170)) (exit 14)) (exit 14))
with (14) (exit 13 (makeblock 0 a/169 b/170)))
with (13 p/171) p/171))
- : bool -> bool tuplist -> bool * bool tuplist = <fun>
|}]
12 changes: 6 additions & 6 deletions testsuite/tests/generalized-open/gpr1506.ml
Original file line number Diff line number Diff line change
Expand Up @@ -103,9 +103,9 @@ include struct open struct type t = T end let x = T end
Line 1, characters 15-41:
1 | include struct open struct type t = T end let x = T end
^^^^^^^^^^^^^^^^^^^^^^^^^^
Error: The type t/150 introduced by this open appears in the signature
Error: The type t/152 introduced by this open appears in the signature
Line 1, characters 46-47:
The value x has no valid type if t/150 is hidden
The value x has no valid type if t/152 is hidden
|}];;

module A = struct
Expand All @@ -123,9 +123,9 @@ Lines 3-6, characters 4-7:
4 | type t = T
5 | let x = T
6 | end
Error: The type t/155 introduced by this open appears in the signature
Error: The type t/157 introduced by this open appears in the signature
Line 7, characters 8-9:
The value y has no valid type if t/155 is hidden
The value y has no valid type if t/157 is hidden
|}];;

module A = struct
Expand All @@ -142,9 +142,9 @@ Lines 3-5, characters 4-7:
3 | ....open struct
4 | type t = T
5 | end
Error: The type t/160 introduced by this open appears in the signature
Error: The type t/162 introduced by this open appears in the signature
Line 6, characters 8-9:
The value y has no valid type if t/160 is hidden
The value y has no valid type if t/162 is hidden
|}]

(* It was decided to not allow this anymore. *)
Expand Down
6 changes: 3 additions & 3 deletions testsuite/tests/typing-sigsubst/sigsubst.ml
Original file line number Diff line number Diff line change
Expand Up @@ -24,11 +24,11 @@ end
Line 3, characters 2-36:
3 | include Comparable with type t = t
^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Error: Illegal shadowing of included type t/98 by t/102
Error: Illegal shadowing of included type t/100 by t/104
Line 2, characters 2-19:
Type t/98 came from this include
Type t/100 came from this include
Line 3, characters 2-23:
The value print has no valid type if t/98 is shadowed
The value print has no valid type if t/100 is shadowed
|}]

module type Sunderscore = sig
Expand Down

0 comments on commit 55dd374

Please sign in to comment.