summaryrefslogtreecommitdiffstats
path: root/stdlib/printexc.ml
diff options
context:
space:
mode:
authorXavier Leroy <xavier.leroy@inria.fr>1998-10-01 12:34:32 +0000
committerXavier Leroy <xavier.leroy@inria.fr>1998-10-01 12:34:32 +0000
commit67971438eea22040f18045b765bcc60fe41f1955 (patch)
treee6b6c43025c9c4971f7e2ece4f8998f46fb7323b /stdlib/printexc.ml
parent497f50b8bab07e5efee4df344511151ac05c2083 (diff)
Noms symboliques pour les tags speciaux
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@2107 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 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
"_"