summaryrefslogtreecommitdiffstats
path: root/stdlib/printexc.ml
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib/printexc.ml')
-rw-r--r--stdlib/printexc.ml16
1 files changed, 8 insertions, 8 deletions
diff --git a/stdlib/printexc.ml b/stdlib/printexc.ml
index 285308b79..b983e3693 100644
--- a/stdlib/printexc.ml
+++ b/stdlib/printexc.ml
@@ -82,12 +82,13 @@ let catch fct arg =
eprintf "Uncaught exception: %s\n" (to_string x);
exit 2
-type raw_backtrace
+type raw_backtrace_slot
+type raw_backtrace = raw_backtrace_slot array
external get_raw_backtrace:
unit -> raw_backtrace = "caml_get_exception_raw_backtrace"
-type loc_info =
+type backtrace_slot =
| Known_location of bool (* is_raise *)
* string (* filename *)
* int (* line number *)
@@ -98,10 +99,12 @@ type loc_info =
(* to avoid warning *)
let _ = [Known_location (false, "", 0, 0, 0); Unknown_location false]
-type backtrace = loc_info array
+external convert_raw_backtrace_slot:
+ raw_backtrace_slot -> backtrace_slot = "caml_convert_raw_backtrace_slot"
-external convert_raw_backtrace:
- raw_backtrace -> backtrace option = "caml_convert_raw_backtrace"
+let convert_raw_backtrace rbckt =
+ try Some (Array.map convert_raw_backtrace_slot rbckt)
+ with Failure _ -> None
let format_loc_info pos li =
let is_raise =
@@ -158,9 +161,6 @@ let raw_backtrace_to_string raw_backtrace =
(* confusingly named:
returns the *string* corresponding to the global current backtrace *)
let get_backtrace () =
- (* we could use the caml_get_exception_backtrace primitive here, but
- we hope to deprecate it so it's better to just compose the
- raw stuff *)
backtrace_to_string (convert_raw_backtrace (get_raw_backtrace ()))
external record_backtrace: bool -> unit = "caml_record_backtrace"