Make use of the [@@immediate] information when deciding if a type can be

[@@unboxed]
master
Damien Doligez 2017-11-08 13:55:35 +01:00 committed by Gabriel Scherer
parent 3882302fa6
commit 4e9c510270
5 changed files with 15 additions and 4 deletions

View File

@ -16,6 +16,10 @@ Working version
(Vincent Laviron, with help from Pierre Chambart,
reviews by Gabriel Scherer and Luc Maranget)
- GPR#1469: Use the information from [@@immediate] annotations when
computing whether a type can be [@@unboxed]
(Damien Doligez, report by Stephan Muenzel, review by ...)
- GPR#1516: Allow float array construction in recursive bindings
when configured with -no-flat-float-array
(Jeremy Yallop, report by Gabriel Scherer)

View File

@ -162,9 +162,11 @@ type ('a, 'p) t = private 'a s
type 'a packed = T : ('a, _) t -> 'a packed [@@unboxed]
;;
(* MPR#7682 *)
type f = {field: 'a. 'a list} [@@unboxed];;
let g = Array.make 10 { field=[] };;
let h = g.(5);;
(* Using [@@immediate] information (GPR#1469) *)
type 'a t [@@immediate];;
type u = U : 'a t -> u [@@unboxed];;

View File

@ -203,9 +203,11 @@ Error: This type cannot be unboxed because
# type 'a s
type ('a, 'p) t = private 'a s
type 'a packed = T : ('a, 'b) t -> 'a packed [@@unboxed]
# type f = { field : 'a. 'a list; } [@@unboxed]
# type f = { field : 'a. 'a list; } [@@unboxed]
# val g : f array =
[|{field = []}; {field = []}; {field = []}; {field = []}; {field = []};
{field = []}; {field = []}; {field = []}; {field = []}; {field = []}|]
# val h : f = {field = []}
# type 'a t [@@immediate]
# type u = U : 'a t -> u [@@unboxed]
#

View File

@ -169,9 +169,11 @@ and _ t = T : 'a -> 'a s t
# type 'a s
type ('a, 'p) t = private 'a s
type 'a packed = T : ('a, 'b) t -> 'a packed [@@unboxed]
# type f = { field : 'a. 'a list; } [@@unboxed]
# type f = { field : 'a. 'a list; } [@@unboxed]
# val g : f array =
[|{field = []}; {field = []}; {field = []}; {field = []}; {field = []};
{field = []}; {field = []}; {field = []}; {field = []}; {field = []}|]
# val h : f = {field = []}
# type 'a t [@@immediate]
# type u = U : 'a t -> u [@@unboxed]
#

View File

@ -132,6 +132,7 @@ let rec get_unboxed_type_representation env ty fuel =
| Tconstr (p, args, _) ->
begin match Env.find_type p env with
| exception Not_found -> Some ty
| {type_immediate = true; _} -> Some Predef.type_int
| {type_unboxed = {unboxed = false}} -> Some ty
| {type_params; type_kind =
Type_record ([{ld_type = ty2; _}], _)