1995-08-09 08:06:35 -07:00
|
|
|
(***********************************************************************)
|
|
|
|
(* *)
|
2011-07-27 07:17:02 -07:00
|
|
|
(* OCaml *)
|
1995-08-09 08:06:35 -07:00
|
|
|
(* *)
|
|
|
|
(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
|
|
|
|
(* *)
|
1996-04-30 07:53:58 -07:00
|
|
|
(* Copyright 1996 Institut National de Recherche en Informatique et *)
|
1999-11-17 10:59:06 -08:00
|
|
|
(* en Automatique. All rights reserved. This file is distributed *)
|
|
|
|
(* under the terms of the Q Public License version 1.0. *)
|
1995-08-09 08:06:35 -07:00
|
|
|
(* *)
|
|
|
|
(***********************************************************************)
|
|
|
|
|
1995-07-27 10:47:52 -07:00
|
|
|
(* Description of primitive functions *)
|
|
|
|
|
1997-05-13 07:07:00 -07:00
|
|
|
open Misc
|
2015-08-25 09:18:46 -07:00
|
|
|
open Parsetree
|
|
|
|
|
|
|
|
type boxed_integer = Pnativeint | Pint32 | Pint64
|
|
|
|
|
|
|
|
type native_repr =
|
|
|
|
| Same_as_ocaml_repr
|
|
|
|
| Unboxed_float
|
|
|
|
| Unboxed_integer of boxed_integer
|
|
|
|
| Untagged_int
|
1995-07-27 10:47:52 -07:00
|
|
|
|
|
|
|
type description =
|
|
|
|
{ prim_name: string; (* Name of primitive or C function *)
|
|
|
|
prim_arity: int; (* Number of arguments *)
|
|
|
|
prim_alloc: bool; (* Does it allocates or raise? *)
|
|
|
|
prim_native_name: string; (* Name of C function for the nat. code gen. *)
|
2015-08-25 09:18:46 -07:00
|
|
|
prim_native_repr_args: native_repr list;
|
|
|
|
prim_native_repr_res: native_repr }
|
|
|
|
|
|
|
|
type error =
|
2015-10-06 03:58:28 -07:00
|
|
|
| Old_style_float_with_native_repr_attribute
|
|
|
|
| Old_style_noalloc_with_noalloc_attribute
|
2015-08-25 09:18:46 -07:00
|
|
|
|
|
|
|
exception Error of Location.t * error
|
|
|
|
|
2015-10-06 03:58:27 -07:00
|
|
|
let is_ocaml_repr = function
|
2015-08-25 09:18:46 -07:00
|
|
|
| Same_as_ocaml_repr -> true
|
|
|
|
| Unboxed_float
|
|
|
|
| Unboxed_integer _
|
|
|
|
| Untagged_int -> false
|
|
|
|
|
2015-10-06 03:58:25 -07:00
|
|
|
let is_unboxed = function
|
|
|
|
| Same_as_ocaml_repr
|
|
|
|
| Untagged_int -> false
|
|
|
|
| Unboxed_float
|
|
|
|
| Unboxed_integer _ -> true
|
|
|
|
|
|
|
|
let is_untagged = function
|
|
|
|
| Untagged_int -> true
|
|
|
|
| Same_as_ocaml_repr
|
|
|
|
| Unboxed_float
|
|
|
|
| Unboxed_integer _ -> false
|
|
|
|
|
2015-08-25 09:18:46 -07:00
|
|
|
let rec make_native_repr_args arity x =
|
|
|
|
if arity = 0 then
|
|
|
|
[]
|
|
|
|
else
|
|
|
|
x :: make_native_repr_args (arity - 1) x
|
|
|
|
|
|
|
|
let simple ~name ~arity ~alloc =
|
|
|
|
{prim_name = name;
|
|
|
|
prim_arity = arity;
|
|
|
|
prim_alloc = alloc;
|
|
|
|
prim_native_name = "";
|
|
|
|
prim_native_repr_args = make_native_repr_args arity Same_as_ocaml_repr;
|
|
|
|
prim_native_repr_res = Same_as_ocaml_repr}
|
|
|
|
|
2015-10-31 04:41:16 -07:00
|
|
|
let make ~name ~alloc ~native_name ~native_repr_args ~native_repr_res =
|
|
|
|
{prim_name = name;
|
|
|
|
prim_arity = List.length native_repr_args;
|
|
|
|
prim_alloc = alloc;
|
|
|
|
prim_native_name = native_name;
|
|
|
|
prim_native_repr_args = native_repr_args;
|
|
|
|
prim_native_repr_res = native_repr_res}
|
|
|
|
|
2015-08-25 09:18:46 -07:00
|
|
|
let parse_declaration valdecl ~native_repr_args ~native_repr_res =
|
|
|
|
let arity = List.length native_repr_args in
|
2015-10-06 03:58:27 -07:00
|
|
|
let name, native_name, old_style_noalloc, old_style_float =
|
2015-08-25 09:18:46 -07:00
|
|
|
match valdecl.pval_prim with
|
|
|
|
| name :: "noalloc" :: name2 :: "float" :: _ -> (name, name2, true, true)
|
|
|
|
| name :: "noalloc" :: name2 :: _ -> (name, name2, true, false)
|
|
|
|
| name :: name2 :: "float" :: _ -> (name, name2, false, true)
|
|
|
|
| name :: "noalloc" :: _ -> (name, "", true, false)
|
|
|
|
| name :: name2 :: _ -> (name, name2, false, false)
|
|
|
|
| name :: _ -> (name, "", false, false)
|
|
|
|
| [] ->
|
|
|
|
fatal_error "Primitive.parse_declaration"
|
|
|
|
in
|
2015-10-06 03:58:28 -07:00
|
|
|
let noalloc_attribute =
|
|
|
|
Attr_helper.has_no_payload_attribute ["noalloc"; "ocaml.noalloc"]
|
|
|
|
valdecl.pval_attributes
|
|
|
|
in
|
|
|
|
if old_style_float &&
|
|
|
|
not (List.for_all is_ocaml_repr native_repr_args &&
|
|
|
|
is_ocaml_repr native_repr_res) then
|
|
|
|
raise (Error (valdecl.pval_loc,
|
|
|
|
Old_style_float_with_native_repr_attribute));
|
|
|
|
if old_style_noalloc && noalloc_attribute then
|
|
|
|
raise (Error (valdecl.pval_loc,
|
|
|
|
Old_style_noalloc_with_noalloc_attribute));
|
2015-10-06 03:58:27 -07:00
|
|
|
(* The compiler used to assume "noalloc" with "float", we just make this
|
|
|
|
explicit now (GPR#167): *)
|
|
|
|
let old_style_noalloc = old_style_noalloc || old_style_float in
|
|
|
|
if old_style_float then
|
|
|
|
Location.prerr_warning valdecl.pval_loc
|
|
|
|
(Warnings.Deprecated "[@@unboxed] + [@@noalloc] should be used instead \
|
|
|
|
of \"float\"")
|
|
|
|
else if old_style_noalloc then
|
|
|
|
Location.prerr_warning valdecl.pval_loc
|
|
|
|
(Warnings.Deprecated "[@@noalloc] should be used instead of \
|
|
|
|
\"noalloc\"");
|
2015-10-06 03:58:28 -07:00
|
|
|
let noalloc = old_style_noalloc || noalloc_attribute in
|
2015-08-25 09:18:46 -07:00
|
|
|
let native_repr_args, native_repr_res =
|
2015-10-06 03:58:27 -07:00
|
|
|
if old_style_float then
|
2015-08-25 09:18:46 -07:00
|
|
|
(make_native_repr_args arity Unboxed_float, Unboxed_float)
|
|
|
|
else
|
|
|
|
(native_repr_args, native_repr_res)
|
|
|
|
in
|
|
|
|
{prim_name = name;
|
|
|
|
prim_arity = arity;
|
|
|
|
prim_alloc = not noalloc;
|
|
|
|
prim_native_name = native_name;
|
|
|
|
prim_native_repr_args = native_repr_args;
|
|
|
|
prim_native_repr_res = native_repr_res}
|
1995-07-27 10:47:52 -07:00
|
|
|
|
2015-10-06 03:58:25 -07:00
|
|
|
open Outcometree
|
|
|
|
|
|
|
|
let rec add_native_repr_attributes ty attrs =
|
|
|
|
match ty, attrs with
|
|
|
|
| Otyp_arrow (label, a, b), attr_opt :: rest ->
|
|
|
|
let b = add_native_repr_attributes b rest in
|
|
|
|
let a =
|
|
|
|
match attr_opt with
|
|
|
|
| None -> a
|
|
|
|
| Some attr -> Otyp_attribute (a, attr)
|
|
|
|
in
|
|
|
|
Otyp_arrow (label, a, b)
|
|
|
|
| _, [Some attr] -> Otyp_attribute (ty, attr)
|
|
|
|
| _ ->
|
|
|
|
assert (List.for_all (fun x -> x = None) attrs);
|
|
|
|
ty
|
|
|
|
|
|
|
|
let oattr_unboxed = { oattr_name = "unboxed" }
|
|
|
|
let oattr_untagged = { oattr_name = "untagged" }
|
|
|
|
let oattr_noalloc = { oattr_name = "noalloc" }
|
|
|
|
|
|
|
|
let print p osig_val_decl =
|
|
|
|
let prims =
|
|
|
|
if p.prim_native_name <> "" then
|
|
|
|
[p.prim_name; p.prim_native_name]
|
|
|
|
else
|
|
|
|
[p.prim_name]
|
2001-08-06 05:28:50 -07:00
|
|
|
in
|
2015-10-06 03:58:25 -07:00
|
|
|
let for_all f =
|
|
|
|
List.for_all f p.prim_native_repr_args && f p.prim_native_repr_res
|
2015-08-25 09:18:48 -07:00
|
|
|
in
|
2015-10-06 03:58:25 -07:00
|
|
|
let all_unboxed = for_all is_unboxed in
|
|
|
|
let all_untagged = for_all is_untagged in
|
|
|
|
let attrs = if p.prim_alloc then [] else [oattr_noalloc] in
|
|
|
|
let attrs =
|
|
|
|
if all_unboxed then
|
|
|
|
oattr_unboxed :: attrs
|
|
|
|
else if all_untagged then
|
|
|
|
oattr_untagged :: attrs
|
2015-08-25 09:18:46 -07:00
|
|
|
else
|
2015-10-06 03:58:25 -07:00
|
|
|
attrs
|
2015-08-25 09:18:46 -07:00
|
|
|
in
|
2015-08-25 09:18:48 -07:00
|
|
|
let attr_of_native_repr = function
|
|
|
|
| Same_as_ocaml_repr -> None
|
2015-10-06 03:58:25 -07:00
|
|
|
| Unboxed_float
|
|
|
|
| Unboxed_integer _ -> if all_unboxed then None else Some oattr_unboxed
|
|
|
|
| Untagged_int -> if all_untagged then None else Some oattr_untagged
|
2015-08-25 09:18:48 -07:00
|
|
|
in
|
2015-10-06 03:58:25 -07:00
|
|
|
let type_attrs =
|
2015-08-25 09:18:48 -07:00
|
|
|
List.map attr_of_native_repr p.prim_native_repr_args @
|
|
|
|
[attr_of_native_repr p.prim_native_repr_res]
|
|
|
|
in
|
2015-10-06 03:58:25 -07:00
|
|
|
{ osig_val_decl with
|
|
|
|
oval_prims = prims;
|
|
|
|
oval_type = add_native_repr_attributes osig_val_decl.oval_type type_attrs;
|
|
|
|
oval_attributes = attrs }
|
2008-07-23 22:35:22 -07:00
|
|
|
|
|
|
|
let native_name p =
|
|
|
|
if p.prim_native_name <> ""
|
|
|
|
then p.prim_native_name
|
|
|
|
else p.prim_name
|
|
|
|
|
|
|
|
let byte_name p =
|
|
|
|
p.prim_name
|
2015-08-25 09:18:46 -07:00
|
|
|
|
|
|
|
let report_error ppf err =
|
|
|
|
match err with
|
2015-10-06 03:58:28 -07:00
|
|
|
| Old_style_float_with_native_repr_attribute ->
|
2015-09-24 11:30:01 -07:00
|
|
|
Format.fprintf ppf "Cannot use \"float\" in conjunction with \
|
2015-10-06 03:58:28 -07:00
|
|
|
[%@unboxed]/[%@untagged]"
|
|
|
|
| Old_style_noalloc_with_noalloc_attribute ->
|
|
|
|
Format.fprintf ppf "Cannot use \"noalloc\" in conjunction with \
|
|
|
|
[%@%@noalloc]"
|
2015-08-25 09:18:46 -07:00
|
|
|
|
|
|
|
let () =
|
|
|
|
Location.register_error_of_exn
|
|
|
|
(function
|
|
|
|
| Error (loc, err) ->
|
|
|
|
Some (Location.error_of_printer loc report_error err)
|
|
|
|
| _ ->
|
|
|
|
None
|
|
|
|
)
|