summaryrefslogtreecommitdiffstats
path: root/stdlib
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib')
-rw-r--r--stdlib/obj.ml10
-rw-r--r--stdlib/obj.mli11
-rw-r--r--stdlib/printexc.ml4
3 files changed, 23 insertions, 2 deletions
diff --git a/stdlib/obj.ml b/stdlib/obj.ml
index 7d01cc766..b6fd215b9 100644
--- a/stdlib/obj.ml
+++ b/stdlib/obj.ml
@@ -31,3 +31,13 @@ let marshal (obj: t) =
Marshal.to_string obj []
let unmarshal str pos =
(Marshal.from_string str pos, pos + Marshal.total_size str pos)
+
+let no_scan_tag = 251
+let closure_tag = 250
+let infix_tag = 249
+let object_tag = 248
+let abstract_tag = 251
+let string_tag = 252
+let double_tag = 253
+let double_array_tag = 254
+let final_tag = 255
diff --git a/stdlib/obj.mli b/stdlib/obj.mli
index dc24531b4..e93394677 100644
--- a/stdlib/obj.mli
+++ b/stdlib/obj.mli
@@ -29,8 +29,19 @@ external new_block : int -> int -> t = "obj_block"
external dup : t -> t = "obj_dup"
external truncate : t -> int -> unit = "obj_truncate"
+val no_scan_tag : int
+val closure_tag : int
+val infix_tag : int
+val object_tag : int
+val abstract_tag : int
+val string_tag : int
+val double_tag : int
+val double_array_tag : int
+val final_tag : int
+
(* The following two functions are deprecated. Use module [Marshal]
instead. *)
val marshal : t -> string
val unmarshal : string -> int -> t * int
+
diff --git a/stdlib/printexc.ml b/stdlib/printexc.ml
index 1d825d60b..a8a52eb7f 100644
--- a/stdlib/printexc.ml
+++ b/stdlib/printexc.ml
@@ -24,9 +24,9 @@ let field x i =
let f = Obj.field x i in
if not (Obj.is_block f) then
sprintf "%d" (Obj.magic f : int) (* can also be a char *)
- else if Obj.tag f = 252 then
+ else if Obj.tag f = Obj.string_tag then
sprintf "\"%s\"" (String.escaped (Obj.magic f : string))
- else if Obj.tag f = 253 then
+ else if Obj.tag f = Obj.double_tag then
string_of_float (Obj.magic f : float)
else
"_"