summaryrefslogtreecommitdiffstats
path: root/stdlib/printexc.ml
diff options
context:
space:
mode:
authorAlain Frisch <alain@frisch.fr>2013-10-23 15:17:05 +0000
committerAlain Frisch <alain@frisch.fr>2013-10-23 15:17:05 +0000
commit5ef2ee909f2219afa5dbd6b91e6e8de7a3d9df69 (patch)
treeed33841bbf41a0ab6e633e5eb701b85d9e9b8a80 /stdlib/printexc.ml
parentfc87ceee897d9181ff582c42076b0270da9975ee (diff)
Support for exception values allocated in the static area (e.g. out of bound exception in native code).
git-svn-id: http://caml.inria.fr/svn/ocaml/branches/raise_variants@14242 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'stdlib/printexc.ml')
-rw-r--r--stdlib/printexc.ml4
1 files changed, 2 insertions, 2 deletions
diff --git a/stdlib/printexc.ml b/stdlib/printexc.ml
index 9f20c7b46..6560ef270 100644
--- a/stdlib/printexc.ml
+++ b/stdlib/printexc.ml
@@ -58,7 +58,7 @@ let to_string x =
sprintf locfmt file line char (char+6) "Undefined recursive module"
| _ ->
let x = Obj.repr x in
- if Obj.tag x <> 0 then
+ if Obj.raw_tag x <> 0 then
(Obj.magic (Obj.field x 0) : string)
else
let constructor =
@@ -175,7 +175,7 @@ external get_callstack: int -> raw_backtrace = "caml_get_current_callstack"
let exn_slot x =
let x = Obj.repr x in
- if Obj.tag x = 0 then Obj.field x 0 else x
+ if Obj.raw_tag x = 0 then Obj.field x 0 else x
let exn_slot_id x =
let slot = exn_slot x in