Skip to content

Commit

Permalink
Add tests
Browse files Browse the repository at this point in the history
  • Loading branch information
Nicolas Chataing committed Jun 29, 2021
1 parent 10779fd commit af30889
Show file tree
Hide file tree
Showing 2 changed files with 96 additions and 0 deletions.
68 changes: 68 additions & 0 deletions testsuite/tests/typing-unboxed-types/test_unboxed_constr.ml
Original file line number Diff line number Diff line change
@@ -0,0 +1,68 @@
(* TEST
flags = "-dheadshape"
* expect
*)

(* Check the unboxing of constructors *)
type t = A of int | B;;
[%%expect{|
SHAPE(t/88[1]) {head_imm = Shape_set [0]; head_blocks = Shape_set [0]}
type t = A of int | B
|}];;

type t = A of int | B of float | C | D;;
[%%expect{|
SHAPE(t/91[2]) {head_imm = Shape_set [0; 1]; head_blocks = Shape_set [0; 1]}
type t = A of int | B of float | C | D
|}];;

type t = A of int [@unboxed] | B;;
[%%expect{|
SHAPE(t/96[3]) CONFLICT
type t = A of int | B
|}];;

type t = A of float [@unboxed] | B;;
[%%expect{|
SHAPE(t/99[4]) {head_imm = Shape_set [0]; head_blocks = Shape_set [253]}
type t = A of float | B
|}];;

type t = A of float [@unboxed] | B of string [@unboxed] | C | D of int;;
[%%expect{|
SHAPE(t/102[5]) {head_imm = Shape_set [0]; head_blocks = Shape_set [0; 252; 253]}
type t = A of float | B of string | C | D of int
|}];;

type t = K of int u u [@unboxed]
and 'a u = 'a id
and 'a id = Id of 'a [@unboxed];;
[%%expect{|
SHAPE(t/107[6]) {head_imm = Shape_any; head_blocks = Shape_set []}
SHAPE(id/109[6]) {head_imm = Shape_any; head_blocks = Shape_any}
type t = K of int u u
and 'a u = 'a id
and 'a id = Id of 'a
|}];;

type t = { a : int } [@@unboxed]
and tt = A of t [@unboxed];;
[%%expect{|
SHAPE(tt/113[7]) {head_imm = Shape_any; head_blocks = Shape_set []}
type t = { a : int; } [@@unboxed]
and tt = A of t
|}];;

type t = A of { a : int } [@unboxed];;
[%%expect{|
SHAPE(t/116[8]) {head_imm = Shape_any; head_blocks = Shape_set []}
type t = A of { a : int; }
|}];;

type ('a, 'r) u = 'r
and 'a t = A of { body : 'r. ('a, 'r) u } [@unboxed];;
[%%expect{|
SHAPE(t/120[9]) {head_imm = Shape_any; head_blocks = Shape_any}
type ('a, 'r) u = 'r
and 'a t = A of { body : 'r. ('a, 'r) u; }
|}];;
Original file line number Diff line number Diff line change
@@ -0,0 +1,28 @@
(* TEST
*)

module A = struct
type t = A of int | B of float [@unboxed]

let f = function A _ -> 0 | B _ -> 1

let test () =
assert (f (A 0) = 0);
assert (f (B 0.) = 1)
end

let () = A.test ()

module B = struct
type t = A of int | B of float
type tt = A' of t [@unboxed] | B'

let f = function A' _ -> 0 | B' -> 1

let test () =
assert (f (A' (A 0)) = 0);
assert (f (A' (B 0.)) = 0);
assert (f B' = 1)
end

let () = B.test ()

0 comments on commit af30889

Please sign in to comment.