summaryrefslogtreecommitdiffstats
path: root/stdlib/callback.ml
diff options
context:
space:
mode:
authorAlain Frisch <alain@frisch.fr>2013-10-18 13:00:58 +0000
committerAlain Frisch <alain@frisch.fr>2013-10-18 13:00:58 +0000
commitd802a51be69feb3ec0df2456386e205e336f1517 (patch)
treebf4cb5dfa5a16a8d93522fa0f32fb1b90d670f41 /stdlib/callback.ml
parent804007bfc513122d045f5d41c0f6b10a1a87fa45 (diff)
#6203: change representation of exception values created with a constant constructor: the value is now equal to the exception slot. This avoids some allocation when the constructor is called and an extra indirection on matching against the constructor.
git-svn-id: http://caml.inria.fr/svn/ocaml/branches/raise_variants@14235 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'stdlib/callback.ml')
-rw-r--r--stdlib/callback.ml4
1 files changed, 3 insertions, 1 deletions
diff --git a/stdlib/callback.ml b/stdlib/callback.ml
index 34e7304f7..c9cf062bf 100644
--- a/stdlib/callback.ml
+++ b/stdlib/callback.ml
@@ -20,4 +20,6 @@ let register name v =
register_named_value name (Obj.repr v)
let register_exception name (exn : exn) =
- register_named_value name (Obj.field (Obj.repr exn) 0)
+ let exn = Obj.repr exn in
+ let slot = if Obj.size exn = 1 then exn else Obj.field exn 1 in
+ register_named_value name slot