1(**************************************************************************)
2(*                                                                        *)
3(*                                 OCaml                                  *)
4(*                                                                        *)
5(*             Xavier Leroy, projet Cristal, INRIA Rocquencourt           *)
6(*                                                                        *)
7(*   Copyright 1996 Institut National de Recherche en Informatique et     *)
8(*     en Automatique.                                                    *)
9(*                                                                        *)
10(*   All rights reserved.  This file is distributed under the terms of    *)
11(*   the GNU Lesser General Public License version 2.1, with the          *)
12(*   special exception on linking described in the file LICENSE.          *)
13(*                                                                        *)
14(**************************************************************************)
15
16(** Operations on internal representations of values.
17
18   Not for the casual user.
19*)
20
21type t
22
23external repr : 'a -> t = "%identity"
24external obj : t -> 'a = "%identity"
25external magic : 'a -> 'b = "%identity"
26val [@inline always] is_block : t -> bool
27external is_int : t -> bool = "%obj_is_int"
28external tag : t -> int = "caml_obj_tag"
29external size : t -> int = "%obj_size"
30external reachable_words : t -> int = "caml_obj_reachable_words"
31  (**
32     Computes the total size (in words, including the headers) of all
33     heap blocks accessible from the argument.  Statically
34     allocated blocks are excluded.
35
36     @Since 4.04
37  *)
38
39external field : t -> int -> t = "%obj_field"
40
41(** When using flambda:
42
43    [set_field] MUST NOT be called on immutable blocks.  (Blocks allocated
44    in C stubs, or with [new_block] below, are always considered mutable.)
45
46    The same goes for [set_double_field] and [set_tag].  However, for
47    [set_tag], in the case of immutable blocks where the middle-end optimizers
48    never see code that discriminates on their tag (for example records), the
49    operation should be safe.  Such uses are nonetheless discouraged.
50
51    For experts only:
52    [set_field] et al can be made safe by first wrapping the block in
53    {!Sys.opaque_identity}, so any information about its contents will not
54    be propagated.
55*)
56external set_field : t -> int -> t -> unit = "%obj_set_field"
57external set_tag : t -> int -> unit = "caml_obj_set_tag"
58
59val [@inline always] double_field : t -> int -> float  (* @since 3.11.2 *)
60val [@inline always] set_double_field : t -> int -> float -> unit
61  (* @since 3.11.2 *)
62external new_block : int -> int -> t = "caml_obj_block"
63external dup : t -> t = "caml_obj_dup"
64external truncate : t -> int -> unit = "caml_obj_truncate"
65external add_offset : t -> Int32.t -> t = "caml_obj_add_offset"
66         (* @since 3.12.0 *)
67
68val first_non_constant_constructor_tag : int
69val last_non_constant_constructor_tag : int
70
71val lazy_tag : int
72val closure_tag : int
73val object_tag : int
74val infix_tag : int
75val forward_tag : int
76val no_scan_tag : int
77val abstract_tag : int
78val string_tag : int   (* both [string] and [bytes] *)
79val double_tag : int
80val double_array_tag : int
81val custom_tag : int
82val final_tag : int
83  [@@ocaml.deprecated "Replaced by custom_tag."]
84
85val int_tag : int
86val out_of_heap_tag : int
87val unaligned_tag : int   (* should never happen @since 3.11.0 *)
88
89val extension_constructor : 'a -> extension_constructor
90val [@inline always] extension_name : extension_constructor -> string
91val [@inline always] extension_id : extension_constructor -> int
92
93(** The following two functions are deprecated.  Use module {!Marshal}
94    instead. *)
95
96val marshal : t -> bytes
97  [@@ocaml.deprecated "Use Marshal.to_bytes instead."]
98val unmarshal : bytes -> int -> t * int
99  [@@ocaml.deprecated "Use Marshal.from_bytes and Marshal.total_size instead."]
100
101module Ephemeron: sig
102  (** Ephemeron with arbitrary arity and untyped *)
103
104  type obj_t = t
105  (** alias for {!Obj.t} *)
106
107  type t
108  (** an ephemeron cf {!Ephemeron} *)
109
110  val create: int -> t
111  (** [create n] returns an ephemeron with [n] keys.
112      All the keys and the data are initially empty *)
113
114  val length: t -> int
115  (** return the number of keys *)
116
117  val get_key: t -> int -> obj_t option
118  (** Same as {!Ephemeron.K1.get_key} *)
119
120  val get_key_copy: t -> int -> obj_t option
121  (** Same as {!Ephemeron.K1.get_key_copy} *)
122
123  val set_key: t -> int -> obj_t -> unit
124  (** Same as {!Ephemeron.K1.set_key} *)
125
126  val unset_key: t -> int -> unit
127  (** Same as {!Ephemeron.K1.unset_key} *)
128
129  val check_key: t -> int -> bool
130  (** Same as {!Ephemeron.K1.check_key} *)
131
132  val blit_key : t -> int -> t -> int -> int -> unit
133  (** Same as {!Ephemeron.K1.blit_key} *)
134
135  val get_data: t -> obj_t option
136  (** Same as {!Ephemeron.K1.get_data} *)
137
138  val get_data_copy: t -> obj_t option
139  (** Same as {!Ephemeron.K1.get_data_copy} *)
140
141  val set_data: t -> obj_t -> unit
142  (** Same as {!Ephemeron.K1.set_data} *)
143
144  val unset_data: t -> unit
145  (** Same as {!Ephemeron.K1.unset_data} *)
146
147  val check_data: t -> bool
148  (** Same as {!Ephemeron.K1.check_data} *)
149
150  val blit_data : t -> t -> unit
151  (** Same as {!Ephemeron.K1.blit_data} *)
152end
153