summaryrefslogtreecommitdiffstats
path: root/stdlib/obj.mli
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib/obj.mli')
-rw-r--r--stdlib/obj.mli12
1 files changed, 8 insertions, 4 deletions
diff --git a/stdlib/obj.mli b/stdlib/obj.mli
index 9a5bd721d..08b8a4f64 100644
--- a/stdlib/obj.mli
+++ b/stdlib/obj.mli
@@ -43,18 +43,22 @@ val infix_tag : int
val forward_tag : int
val no_scan_tag : int
val abstract_tag : int
-val string_tag : int
+val string_tag : int (* both [string] and [bytes] *)
val double_tag : int
val double_array_tag : int
val custom_tag : int
-val final_tag : int (* DEPRECATED *)
+val final_tag : int [@@ocaml.deprecated]
val int_tag : int
val out_of_heap_tag : int
val unaligned_tag : int (* should never happen @since 3.11.0 *)
+val extension_name : 'a -> string
+val extension_id : 'a -> int
+val extension_slot : 'a -> t
+
(** The following two functions are deprecated. Use module {!Marshal}
instead. *)
-val marshal : t -> string
-val unmarshal : string -> int -> t * int
+val marshal : t -> bytes [@@ocaml.deprecated]
+val unmarshal : bytes -> int -> t * int [@@ocaml.deprecated]