summaryrefslogtreecommitdiffstats
path: root/stdlib/obj.ml
diff options
context:
space:
mode:
authorXavier Leroy <xavier.leroy@inria.fr>1995-07-27 17:44:04 +0000
committerXavier Leroy <xavier.leroy@inria.fr>1995-07-27 17:44:04 +0000
commit3843b0cddbc532d33a42f0d04378f9ccdec5f907 (patch)
tree39821009262f70b6073a855e61f2644dc06156ca /stdlib/obj.ml
parent863984ea8ba4be4fc317680c3c457aa8f89c2c72 (diff)
Declarations des primitives flottantes.
Declaration des primitives sur les objets. git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@154 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'stdlib/obj.ml')
-rw-r--r--stdlib/obj.ml6
1 files changed, 3 insertions, 3 deletions
diff --git a/stdlib/obj.ml b/stdlib/obj.ml
index 247f4cdf5..8fe21c7f6 100644
--- a/stdlib/obj.ml
+++ b/stdlib/obj.ml
@@ -6,7 +6,7 @@ external repr : 'a -> t = "%identity"
external magic : 'a -> 'b = "%identity"
external is_block : t -> bool = "obj_is_block"
external tag : t -> int = "obj_tag"
-external size : t -> int = "%array_length"
-external field : t -> int -> t = "%array_unsafe_get"
-external set_field : t -> int -> t -> unit = "%array_unsafe_set"
+external size : t -> int = "%obj_size"
+external field : t -> int -> t = "%obj_field"
+external set_field : t -> int -> t -> unit = "%obj_set_field"
external new_block : int -> int -> t = "obj_block"