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
|
|
|
(* *)
|
|
|
|
(***********************************************************************)
|
|
|
|
|
2013-07-11 05:37:10 -07:00
|
|
|
(** Facilities for printing exceptions and inspecting current call stack. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
|
2010-04-19 05:25:46 -07:00
|
|
|
val to_string: exn -> string
|
2001-10-26 15:38:48 -07:00
|
|
|
(** [Printexc.to_string e] returns a string representation of
|
|
|
|
the exception [e]. *)
|
1995-05-04 03:15:53 -07:00
|
|
|
|
2010-04-19 05:25:46 -07:00
|
|
|
val print: ('a -> 'b) -> 'a -> 'b
|
2001-10-26 15:38:48 -07:00
|
|
|
(** [Printexc.print fn x] applies [fn] to [x] and returns the result.
|
|
|
|
If the evaluation of [fn x] raises any exception, the
|
|
|
|
name of the exception is printed on standard error output,
|
|
|
|
and the exception is raised again.
|
|
|
|
The typical use is to catch and report exceptions that
|
|
|
|
escape a function application. *)
|
1997-06-06 07:54:09 -07:00
|
|
|
|
2010-04-19 05:25:46 -07:00
|
|
|
val catch: ('a -> 'b) -> 'a -> 'b
|
2001-10-26 15:38:48 -07:00
|
|
|
(** [Printexc.catch fn x] is similar to {!Printexc.print}, but
|
|
|
|
aborts the program with exit code 2 after printing the
|
|
|
|
uncaught exception. This function is deprecated: the runtime
|
|
|
|
system is now able to print uncaught exceptions as precisely
|
|
|
|
as [Printexc.catch] does. Moreover, calling [Printexc.catch]
|
|
|
|
makes it harder to track the location of the exception
|
|
|
|
using the debugger or the stack backtrace facility.
|
|
|
|
So, do not use [Printexc.catch] in new code. *)
|
2008-03-14 06:47:24 -07:00
|
|
|
|
|
|
|
val print_backtrace: out_channel -> unit
|
|
|
|
(** [Printexc.print_backtrace oc] prints an exception backtrace
|
|
|
|
on the output channel [oc]. The backtrace lists the program
|
|
|
|
locations where the most-recently raised exception was raised
|
2010-05-21 11:30:12 -07:00
|
|
|
and where it was propagated through function calls.
|
|
|
|
@since 3.11.0
|
|
|
|
*)
|
2008-03-14 06:47:24 -07:00
|
|
|
|
|
|
|
val get_backtrace: unit -> string
|
|
|
|
(** [Printexc.get_backtrace ()] returns a string containing the
|
|
|
|
same exception backtrace that [Printexc.print_backtrace] would
|
2010-05-21 11:30:12 -07:00
|
|
|
print.
|
|
|
|
@since 3.11.0
|
|
|
|
*)
|
2008-03-14 06:47:24 -07:00
|
|
|
|
|
|
|
val record_backtrace: bool -> unit
|
|
|
|
(** [Printexc.record_backtrace b] turns recording of exception backtraces
|
|
|
|
on (if [b = true]) or off (if [b = false]). Initially, backtraces
|
|
|
|
are not recorded, unless the [b] flag is given to the program
|
2010-05-21 11:30:12 -07:00
|
|
|
through the [OCAMLRUNPARAM] variable.
|
|
|
|
@since 3.11.0
|
|
|
|
*)
|
2008-03-14 06:47:24 -07:00
|
|
|
|
|
|
|
val backtrace_status: unit -> bool
|
|
|
|
(** [Printexc.backtrace_status()] returns [true] if exception
|
2010-05-21 11:30:12 -07:00
|
|
|
backtraces are currently recorded, [false] if not.
|
|
|
|
@since 3.11.0
|
|
|
|
*)
|
2010-01-20 08:26:46 -08:00
|
|
|
|
2010-04-19 05:25:46 -07:00
|
|
|
val register_printer: (exn -> string option) -> unit
|
|
|
|
(** [Printexc.register_printer fn] registers [fn] as an exception
|
|
|
|
printer. The printer should return [None] or raise an exception
|
|
|
|
if it does not know how to convert the passed exception, and [Some
|
|
|
|
s] with [s] the resulting string if it can convert the passed
|
|
|
|
exception. Exceptions raised by the printer are ignored.
|
|
|
|
|
2010-01-20 08:26:46 -08:00
|
|
|
When converting an exception into a string, the printers will be invoked
|
|
|
|
in the reverse order of their registrations, until a printer returns
|
|
|
|
a [Some s] value (if no such printer exists, the runtime will use a
|
2010-05-21 11:30:12 -07:00
|
|
|
generic printer).
|
2011-06-14 04:08:07 -07:00
|
|
|
|
|
|
|
When using this mechanism, one should be aware that an exception backtrace
|
|
|
|
is attached to the thread that saw it raised, rather than to the exception
|
|
|
|
itself. Practically, it means that the code related to [fn] should not use
|
|
|
|
the backtrace if it has itself raised an exception before.
|
2010-05-21 11:30:12 -07:00
|
|
|
@since 3.11.2
|
|
|
|
*)
|
2013-03-11 12:04:12 -07:00
|
|
|
|
|
|
|
(** {6 Raw backtraces} *)
|
|
|
|
|
|
|
|
type raw_backtrace
|
|
|
|
|
|
|
|
(** The abstract type [backtrace] stores exception backtraces in
|
|
|
|
a low-level format, instead of directly exposing them as string as
|
|
|
|
the [get_backtrace()] function does.
|
|
|
|
|
2013-11-08 07:36:36 -08:00
|
|
|
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.
|
2013-03-11 12:04:12 -07:00
|
|
|
*)
|
|
|
|
|
|
|
|
val get_raw_backtrace: unit -> raw_backtrace
|
|
|
|
val print_raw_backtrace: out_channel -> raw_backtrace -> unit
|
|
|
|
val raw_backtrace_to_string: raw_backtrace -> string
|
2013-07-11 05:37:10 -07:00
|
|
|
|
2014-04-18 08:36:08 -07:00
|
|
|
(** {6 Uncaught exceptions} *)
|
|
|
|
|
|
|
|
val set_uncaught_exception_handler: (exn -> raw_backtrace -> unit) -> unit
|
|
|
|
(** [Printexc.set_uncaught_exception_handler fn] registers [fn] as the handler
|
|
|
|
for uncaught exceptions. The default handler prints the exception and
|
|
|
|
backtrace on standard error output.
|
|
|
|
|
|
|
|
Note that when [fn] is called all the functions registered with
|
|
|
|
{!Pervasives.at_exit} have already been called. Because of this you must
|
|
|
|
make sure any output channel [fn] writes on is flushed.
|
|
|
|
|
|
|
|
If [fn] raises an exception, it is ignored.
|
|
|
|
|
|
|
|
@since 4.02.0
|
|
|
|
*)
|
2013-07-11 05:37:10 -07:00
|
|
|
|
|
|
|
(** {6 Current call stack} *)
|
|
|
|
|
|
|
|
val get_callstack: int -> raw_backtrace
|
|
|
|
|
|
|
|
(** [Printexc.get_callstack n] returns a description of the top of the
|
|
|
|
call stack on the current program point (for the current thread),
|
|
|
|
with at most [n] entries. (Note: this function is not related to
|
|
|
|
exceptions at all, despite being part of the [Printexc] module.)
|
|
|
|
|
|
|
|
@since 4.01.0
|
|
|
|
*)
|
2013-10-23 07:35:43 -07:00
|
|
|
|
|
|
|
|
|
|
|
(** {6 Exception slots} *)
|
|
|
|
|
|
|
|
val exn_slot_id: exn -> int
|
|
|
|
(** [Printexc.exn_slot_id] returns an integer which uniquely identifies
|
|
|
|
the constructor used to create the exception value [exn]
|
|
|
|
(in the current runtime).
|
|
|
|
|
|
|
|
@since 4.02.0
|
|
|
|
*)
|
|
|
|
|
|
|
|
val exn_slot_name: exn -> string
|
|
|
|
(** [Printexc.exn_slot_id exn] returns the internal name of the constructor
|
|
|
|
used to create the exception value [exn].
|
|
|
|
|
|
|
|
@since 4.02.0
|
|
|
|
*)
|