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-03-09 14:38:52 -08:00
|
|
|
let constructor =
|
|
|
|
(Obj.magic (Obj.field (Obj.field x 0) 0) : string) in
|
2010-01-20 08:26:46 -08:00
|
|
|
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
|
|
|
|
2013-03-11 12:04:12 -07:00
|
|
|
type raw_backtrace
|
|
|
|
|
|
|
|
external get_raw_backtrace:
|
|
|
|
unit -> raw_backtrace = "caml_get_exception_raw_backtrace"
|
|
|
|
|
2008-03-14 06:47:24 -07:00
|
|
|
type loc_info =
|
|
|
|
| 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]
|
|
|
|
|
2013-03-11 12:04:12 -07:00
|
|
|
type backtrace = loc_info array
|
|
|
|
|
|
|
|
external convert_raw_backtrace:
|
|
|
|
raw_backtrace -> backtrace option = "caml_convert_raw_backtrace"
|
2008-03-14 06:47:24 -07:00
|
|
|
|
|
|
|
let format_loc_info pos li =
|
|
|
|
let is_raise =
|
|
|
|
match li with
|
|
|
|
| Known_location(is_raise, _, _, _, _) -> is_raise
|
|
|
|
| Unknown_location(is_raise) -> is_raise in
|
|
|
|
let info =
|
|
|
|
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
|
|
|
|
match li with
|
|
|
|
| Known_location(is_raise, filename, lineno, startchar, endchar) ->
|
|
|
|
sprintf "%s file \"%s\", line %d, characters %d-%d"
|
|
|
|
info filename lineno startchar endchar
|
|
|
|
| Unknown_location(is_raise) ->
|
|
|
|
sprintf "%s unknown location"
|
|
|
|
info
|
|
|
|
|
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
|
|
|
|
if a.(i) <> Unknown_location true then
|
|
|
|
fprintf outchan "%s\n" (format_loc_info i a.(i))
|
|
|
|
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
|
|
|
|
if a.(i) <> Unknown_location true then
|
|
|
|
bprintf b "%s\n" (format_loc_info i a.(i))
|
|
|
|
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)
|
|
|
|
|
|
|
|
(* 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 ()))
|
|
|
|
|
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
|