1995-08-09 08:06:35 -07:00
|
|
|
(***********************************************************************)
|
|
|
|
(* *)
|
2011-07-27 07:17:02 -07:00
|
|
|
(* OCaml *)
|
1995-08-09 08:06:35 -07:00
|
|
|
(* *)
|
|
|
|
(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
|
|
|
|
(* *)
|
1996-04-30 07:53:58 -07:00
|
|
|
(* Copyright 1996 Institut National de Recherche en Informatique et *)
|
1999-11-17 10:59:06 -08:00
|
|
|
(* en Automatique. All rights reserved. This file is distributed *)
|
2001-12-07 05:41:02 -08:00
|
|
|
(* under the terms of the GNU Library General Public License, with *)
|
|
|
|
(* the special exception on linking described in file ../LICENSE. *)
|
1995-08-09 08:06:35 -07:00
|
|
|
(* *)
|
|
|
|
(***********************************************************************)
|
|
|
|
|
1997-06-06 07:54:09 -07:00
|
|
|
open Printf;;
|
|
|
|
|
2010-01-20 08:26:46 -08:00
|
|
|
let printers = ref []
|
|
|
|
|
2004-01-16 07:24:03 -08:00
|
|
|
let locfmt = format_of_string "File \"%s\", line %d, characters %d-%d: %s";;
|
1997-05-13 11:27:27 -07:00
|
|
|
|
1997-06-12 08:29:01 -07:00
|
|
|
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 *)
|
1998-10-01 05:34:32 -07:00
|
|
|
else if Obj.tag f = Obj.string_tag then
|
2002-06-27 02:27:14 -07:00
|
|
|
sprintf "%S" (Obj.magic f : string)
|
1998-10-01 05:34:32 -07:00
|
|
|
else if Obj.tag f = Obj.double_tag then
|
1997-06-12 08:29:01 -07:00
|
|
|
string_of_float (Obj.magic f : float)
|
|
|
|
else
|
|
|
|
"_"
|
|
|
|
;;
|
|
|
|
let rec other_fields x i =
|
|
|
|
if i >= Obj.size x then ""
|
|
|
|
else sprintf ", %s%s" (field x i) (other_fields x (i+1))
|
|
|
|
;;
|
|
|
|
let fields x =
|
|
|
|
match Obj.size x with
|
|
|
|
| 0 -> ""
|
|
|
|
| 1 -> ""
|
|
|
|
| 2 -> sprintf "(%s)" (field x 1)
|
|
|
|
| n -> sprintf "(%s%s)" (field x 1) (other_fields x 2)
|
|
|
|
;;
|
|
|
|
|
2010-04-19 05:25:46 -07:00
|
|
|
let to_string x =
|
|
|
|
let rec conv = function
|
|
|
|
| hd :: tl ->
|
|
|
|
(match try hd x with _ -> None with
|
|
|
|
| Some s -> s
|
|
|
|
| None -> conv tl)
|
|
|
|
| [] ->
|
|
|
|
match x with
|
|
|
|
| Out_of_memory -> "Out of memory"
|
|
|
|
| Stack_overflow -> "Stack overflow"
|
|
|
|
| Match_failure(file, line, char) ->
|
|
|
|
sprintf locfmt file line char (char+5) "Pattern matching failed"
|
|
|
|
| Assert_failure(file, line, char) ->
|
|
|
|
sprintf locfmt file line char (char+6) "Assertion failed"
|
2011-09-08 01:34:43 -07:00
|
|
|
| Undefined_recursive_module(file, line, char) ->
|
|
|
|
sprintf locfmt file line char (char+6) "Undefined recursive module"
|
2010-04-19 05:25:46 -07:00
|
|
|
| _ ->
|
2010-01-20 08:26:46 -08:00
|
|
|
let x = Obj.repr x in
|
2013-11-06 02:57:20 -08:00
|
|
|
if Obj.tag x <> 0 then
|
2013-10-23 07:28:31 -07:00
|
|
|
(Obj.magic (Obj.field x 0) : string)
|
|
|
|
else
|
|
|
|
let constructor =
|
|
|
|
(Obj.magic (Obj.field (Obj.field x 0) 0) : string) in
|
|
|
|
constructor ^ (fields x) in
|
2010-04-19 05:25:46 -07:00
|
|
|
conv !printers
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
let print fct arg =
|
|
|
|
try
|
|
|
|
fct arg
|
|
|
|
with x ->
|
1997-06-12 08:29:01 -07:00
|
|
|
eprintf "Uncaught exception: %s\n" (to_string x);
|
1995-11-15 01:33:15 -08:00
|
|
|
flush stderr;
|
1995-05-04 03:15:53 -07:00
|
|
|
raise x
|
|
|
|
|
|
|
|
let catch fct arg =
|
|
|
|
try
|
|
|
|
fct arg
|
|
|
|
with x ->
|
|
|
|
flush stdout;
|
1997-06-12 08:29:01 -07:00
|
|
|
eprintf "Uncaught exception: %s\n" (to_string x);
|
1995-05-04 03:15:53 -07:00
|
|
|
exit 2
|
2008-03-14 06:47:24 -07:00
|
|
|
|
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
2014-05-10 12:19:47 -07:00
|
|
|
type raw_backtrace_slot
|
|
|
|
type raw_backtrace = raw_backtrace_slot array
|
2013-03-11 12:04:12 -07:00
|
|
|
|
|
|
|
external get_raw_backtrace:
|
|
|
|
unit -> raw_backtrace = "caml_get_exception_raw_backtrace"
|
|
|
|
|
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
2014-05-10 12:19:47 -07:00
|
|
|
type backtrace_slot =
|
2008-03-14 06:47:24 -07:00
|
|
|
| Known_location of bool (* is_raise *)
|
|
|
|
* string (* filename *)
|
|
|
|
* int (* line number *)
|
|
|
|
* int (* start char *)
|
|
|
|
* int (* end char *)
|
|
|
|
| Unknown_location of bool (*is_raise*)
|
|
|
|
|
2012-05-29 05:37:01 -07:00
|
|
|
(* to avoid warning *)
|
2012-05-29 04:47:28 -07:00
|
|
|
let _ = [Known_location (false, "", 0, 0, 0); Unknown_location false]
|
|
|
|
|
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
2014-05-10 12:19:47 -07:00
|
|
|
external convert_raw_backtrace_slot:
|
|
|
|
raw_backtrace_slot -> backtrace_slot = "caml_convert_raw_backtrace_slot"
|
2013-03-11 12:04:12 -07:00
|
|
|
|
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
2014-05-10 12:19:47 -07:00
|
|
|
let convert_raw_backtrace rbckt =
|
|
|
|
try Some (Array.map convert_raw_backtrace_slot rbckt)
|
|
|
|
with Failure _ -> None
|
2008-03-14 06:47:24 -07:00
|
|
|
|
2014-05-10 12:20:00 -07:00
|
|
|
let format_backtrace_slot pos slot =
|
|
|
|
let info is_raise =
|
2008-03-14 06:47:24 -07:00
|
|
|
if is_raise then
|
|
|
|
if pos = 0 then "Raised at" else "Re-raised at"
|
|
|
|
else
|
|
|
|
if pos = 0 then "Raised by primitive operation at" else "Called from"
|
|
|
|
in
|
2014-05-10 12:20:00 -07:00
|
|
|
match slot with
|
|
|
|
| Unknown_location true -> (* compiler-inserted re-raise, skipped *) None
|
|
|
|
| Unknown_location false ->
|
|
|
|
Some (sprintf "%s unknown location" (info false))
|
2008-03-14 06:47:24 -07:00
|
|
|
| Known_location(is_raise, filename, lineno, startchar, endchar) ->
|
2014-05-10 12:20:00 -07:00
|
|
|
Some (sprintf "%s file \"%s\", line %d, characters %d-%d"
|
|
|
|
(info is_raise) filename lineno startchar endchar)
|
2008-03-14 06:47:24 -07:00
|
|
|
|
2013-03-11 12:04:12 -07:00
|
|
|
let print_exception_backtrace outchan backtrace =
|
|
|
|
match backtrace with
|
2008-03-14 06:47:24 -07:00
|
|
|
| None ->
|
|
|
|
fprintf outchan
|
|
|
|
"(Program not linked with -g, cannot print stack backtrace)\n"
|
|
|
|
| Some a ->
|
|
|
|
for i = 0 to Array.length a - 1 do
|
2014-05-10 12:20:00 -07:00
|
|
|
match format_backtrace_slot i a.(i) with
|
|
|
|
| None -> ()
|
|
|
|
| Some str -> fprintf outchan "%s\n" str
|
2008-03-14 06:47:24 -07:00
|
|
|
done
|
|
|
|
|
2013-03-11 12:04:12 -07:00
|
|
|
let print_raw_backtrace outchan raw_backtrace =
|
|
|
|
print_exception_backtrace outchan (convert_raw_backtrace raw_backtrace)
|
|
|
|
|
|
|
|
(* confusingly named: prints the global current backtrace *)
|
|
|
|
let print_backtrace outchan =
|
|
|
|
print_raw_backtrace outchan (get_raw_backtrace ())
|
|
|
|
|
|
|
|
let backtrace_to_string backtrace =
|
|
|
|
match backtrace with
|
2008-03-14 06:47:24 -07:00
|
|
|
| None ->
|
|
|
|
"(Program not linked with -g, cannot print stack backtrace)\n"
|
|
|
|
| Some a ->
|
|
|
|
let b = Buffer.create 1024 in
|
|
|
|
for i = 0 to Array.length a - 1 do
|
2014-05-10 12:20:00 -07:00
|
|
|
match format_backtrace_slot i a.(i) with
|
|
|
|
| None -> ()
|
|
|
|
| Some str -> bprintf b "%s\n" str
|
2008-03-14 06:47:24 -07:00
|
|
|
done;
|
|
|
|
Buffer.contents b
|
|
|
|
|
2013-03-11 12:04:12 -07:00
|
|
|
let raw_backtrace_to_string raw_backtrace =
|
|
|
|
backtrace_to_string (convert_raw_backtrace raw_backtrace)
|
|
|
|
|
2014-05-10 12:20:00 -07:00
|
|
|
let backtrace_slot_is_raise = function
|
|
|
|
| Known_location(is_raise, _, _, _, _) -> is_raise
|
|
|
|
| Unknown_location(is_raise) -> is_raise
|
|
|
|
|
|
|
|
type location = {
|
|
|
|
filename : string;
|
|
|
|
line_number : int;
|
|
|
|
start_char : int;
|
|
|
|
end_char : int;
|
|
|
|
}
|
|
|
|
|
|
|
|
let backtrace_slot_location = function
|
|
|
|
| Unknown_location _ -> None
|
|
|
|
| Known_location(_is_raise, filename, line_number,
|
|
|
|
start_char, end_char) ->
|
|
|
|
Some {
|
|
|
|
filename;
|
|
|
|
line_number;
|
|
|
|
start_char;
|
|
|
|
end_char;
|
|
|
|
}
|
|
|
|
|
|
|
|
let backtrace_slots raw_backtrace =
|
|
|
|
(* The documentation of this function guarantees that Some is
|
|
|
|
returned only if a part of the trace is usable. This gives us
|
|
|
|
a bit more work than just convert_raw_backtrace, but it makes the
|
|
|
|
API more user-friendly -- otherwise most users would have to
|
|
|
|
reimplement the "Program not linked with -g, sorry" logic
|
|
|
|
themselves. *)
|
|
|
|
match convert_raw_backtrace raw_backtrace with
|
|
|
|
| None -> None
|
|
|
|
| Some backtrace ->
|
|
|
|
let usable_slot = function
|
|
|
|
| Unknown_location _ -> false
|
|
|
|
| Known_location _ -> true in
|
|
|
|
let rec exists_usable = function
|
|
|
|
| (-1) -> false
|
|
|
|
| i -> usable_slot backtrace.(i) || exists_usable (i - 1) in
|
|
|
|
if exists_usable (Array.length backtrace - 1)
|
|
|
|
then Some backtrace
|
|
|
|
else None
|
|
|
|
|
|
|
|
module Slot = struct
|
|
|
|
type t = backtrace_slot
|
|
|
|
let format = format_backtrace_slot
|
|
|
|
let is_raise = backtrace_slot_is_raise
|
|
|
|
let location = backtrace_slot_location
|
|
|
|
end
|
|
|
|
|
|
|
|
let raw_backtrace_length bckt = Array.length bckt
|
|
|
|
let get_raw_backtrace_slot bckt i = Array.get bckt i
|
|
|
|
|
2013-03-11 12:04:12 -07:00
|
|
|
(* confusingly named:
|
|
|
|
returns the *string* corresponding to the global current backtrace *)
|
|
|
|
let get_backtrace () =
|
|
|
|
backtrace_to_string (convert_raw_backtrace (get_raw_backtrace ()))
|
|
|
|
|
2008-03-14 06:47:24 -07:00
|
|
|
external record_backtrace: bool -> unit = "caml_record_backtrace"
|
|
|
|
external backtrace_status: unit -> bool = "caml_backtrace_status"
|
|
|
|
|
2010-01-20 08:26:46 -08:00
|
|
|
let register_printer fn =
|
|
|
|
printers := fn :: !printers
|
2013-07-11 05:37:10 -07:00
|
|
|
|
|
|
|
external get_callstack: int -> raw_backtrace = "caml_get_current_callstack"
|
2013-10-23 07:35:43 -07:00
|
|
|
|
|
|
|
let exn_slot x =
|
|
|
|
let x = Obj.repr x in
|
2013-11-06 02:57:20 -08:00
|
|
|
if Obj.tag x = 0 then Obj.field x 0 else x
|
2013-10-23 07:35:43 -07:00
|
|
|
|
|
|
|
let exn_slot_id x =
|
|
|
|
let slot = exn_slot x in
|
|
|
|
(Obj.obj (Obj.field slot 1) : int)
|
|
|
|
|
|
|
|
let exn_slot_name x =
|
|
|
|
let slot = exn_slot x in
|
|
|
|
(Obj.obj (Obj.field slot 0) : string)
|
2014-04-18 08:36:08 -07:00
|
|
|
|
|
|
|
|
|
|
|
let uncaught_exception_handler = ref None
|
|
|
|
|
|
|
|
let set_uncaught_exception_handler fn = uncaught_exception_handler := Some fn
|
|
|
|
|
|
|
|
let empty_backtrace : raw_backtrace = Obj.obj (Obj.new_block Obj.abstract_tag 0)
|
|
|
|
|
|
|
|
let try_get_raw_backtrace () =
|
|
|
|
try
|
|
|
|
get_raw_backtrace ()
|
|
|
|
with _ (* Out_of_memory? *) ->
|
|
|
|
empty_backtrace
|
|
|
|
|
|
|
|
let handle_uncaught_exception' exn debugger_in_use =
|
|
|
|
try
|
|
|
|
(* Get the backtrace now, in case one of the [at_exit] function
|
|
|
|
destroys it. *)
|
|
|
|
let raw_backtrace =
|
|
|
|
if debugger_in_use (* Same test as in [byterun/printexc.c] *) then
|
|
|
|
empty_backtrace
|
|
|
|
else
|
|
|
|
try_get_raw_backtrace ()
|
|
|
|
in
|
|
|
|
(try Pervasives.do_at_exit () with _ -> ());
|
|
|
|
match !uncaught_exception_handler with
|
|
|
|
| None ->
|
|
|
|
eprintf "Fatal error: exception %s\n" (to_string exn);
|
|
|
|
print_raw_backtrace stderr raw_backtrace;
|
|
|
|
flush stderr
|
|
|
|
| Some handler ->
|
|
|
|
try
|
|
|
|
handler exn raw_backtrace
|
|
|
|
with exn' ->
|
|
|
|
let raw_backtrace' = try_get_raw_backtrace () in
|
|
|
|
eprintf "Fatal error: exception %s\n" (to_string exn);
|
|
|
|
print_raw_backtrace stderr raw_backtrace;
|
|
|
|
eprintf "Fatal error in uncaught exception handler: exception %s\n"
|
|
|
|
(to_string exn');
|
|
|
|
print_raw_backtrace stderr raw_backtrace';
|
|
|
|
flush stderr
|
|
|
|
with
|
|
|
|
| Out_of_memory ->
|
|
|
|
prerr_endline
|
|
|
|
"Fatal error: out of memory in uncaught exception handler"
|
|
|
|
|
|
|
|
(* This function is called by [caml_fatal_uncaught_exception] in
|
|
|
|
[byterun/printexc.c] which expects no exception is raised. *)
|
|
|
|
let handle_uncaught_exception exn debugger_in_use =
|
|
|
|
try
|
|
|
|
handle_uncaught_exception' exn debugger_in_use
|
|
|
|
with _ ->
|
|
|
|
(* There is not much we can do at this point *)
|
|
|
|
()
|
|
|
|
|
|
|
|
external register_named_value : string -> 'a -> unit
|
|
|
|
= "caml_register_named_value"
|
|
|
|
|
|
|
|
let () =
|
|
|
|
register_named_value "Printexc.handle_uncaught_exception"
|
|
|
|
handle_uncaught_exception
|