summaryrefslogtreecommitdiffstats
path: root/stdlib
diff options
context:
space:
mode:
authorGabriel Scherer <gabriel.scherer@gmail.com>2014-05-10 19:19:47 +0000
committerGabriel Scherer <gabriel.scherer@gmail.com>2014-05-10 19:19:47 +0000
commit1fdea57c4c03c47ec48ecccc99d59211b4ec2c7c (patch)
treea860ad50726fd1e9712b1d6ff918386af9801cc5 /stdlib
parenteb2b1f64b17aab853ca16c531bf9c6b99c69503e (diff)
Printexc: OCaml-friendly access to individual backtrace slots
(Patch by Jacques-Henri Jourdan) There are several changes: - `raw_backtrace` is no longer an abstract type, but rather an `raw_backtrace_slot array`, where `raw_backtrace_slot` is a new abstract type. `raw_backtrace_slot` elements are hashable and comparable. At runtime, values of this type contain either a bytecode pointer or a frame_descr pointer. In order to prevent the GC from walking through this pointer, the low-order bit is set to 1 when stored in the array. - The old `loc_info` type is know public, renamed into `backtrace_slot`: type backtrace_slot = | Known_location of bool (* is_raise *) * string (* filename *) * int (* line number *) * int (* start char *) * int (* end char *) | Unknown_location of bool (*is_raise*) - new primitive : val convert_raw_backtrace_slot: raw_backtrace_slot -> backtrace_slot Rather than returning an option, it raises Failure when it is not possible to get the debugging information. It seems more idiomatic, especially because the exceptional case cannot appear only for a part of the executable. - the caml_convert_raw_backtrace primitive is removed; it is more difficult to implement in the C side because of the new exception interface described above. - In the bytecode runtime, the events are no longer deserialized once for each conversion, but once and for all at the first conversion, and stored in a global array (*outside* the OCaml heap), sorted by program counter value. I believe this information should not take much memory in practice (it uses the same order of magnitude memory as the bytecode executable). It also makes location lookup much more efficient, as a dichomoty is used instead of linear search as previously. git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@14776 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'stdlib')
-rw-r--r--stdlib/printexc.ml16
-rw-r--r--stdlib/printexc.mli27
2 files changed, 33 insertions, 10 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"
diff --git a/stdlib/printexc.mli b/stdlib/printexc.mli
index 2916bf143..53cf81566 100644
--- a/stdlib/printexc.mli
+++ b/stdlib/printexc.mli
@@ -85,15 +85,20 @@ val register_printer: (exn -> string option) -> unit
(** {6 Raw backtraces} *)
-type raw_backtrace
+type raw_backtrace_slot
+type raw_backtrace = raw_backtrace_slot array
-(** The abstract type [backtrace] stores exception backtraces in
+(** The abstract type [raw_backtrace_slot] stores a slot of a backtrace in
a low-level format, instead of directly exposing them as string as
the [get_backtrace()] function does.
This allows delaying the formatting of backtraces to when they are
actually printed, which might be useful if you record more
backtraces than you print.
+
+ Elements of type raw_backtrace_slot can be compared and hashed: when two
+ elements are equal, then they represent the same source location (the
+ converse is not necessarily true in presence of inlining, for example).
*)
val get_raw_backtrace: unit -> raw_backtrace
@@ -116,6 +121,24 @@ val set_uncaught_exception_handler: (exn -> raw_backtrace -> unit) -> unit
@since 4.02.0
*)
+(** {6 Backtrace slots processing} *)
+
+type backtrace_slot =
+ | Known_location of bool (* is_raise *)
+ * string (* filename *)
+ * int (* line number *)
+ * int (* start char *)
+ * int (* end char *)
+ | Unknown_location of bool (*is_raise*)
+
+(** [convert_raw_backtrace_slot] converts one slot of a raw backtrace
+ to an Ocaml algebraic datatype representing to location
+ information in the source file.
+
+ Raises [Failure] if not able to load debug information.
+*)
+val convert_raw_backtrace_slot: raw_backtrace_slot -> backtrace_slot
+
(** {6 Current call stack} *)
val get_callstack: int -> raw_backtrace