2007-01-29 04:11:18 -08:00
|
|
|
/***********************************************************************/
|
|
|
|
/* */
|
2011-07-27 07:17:02 -07:00
|
|
|
/* OCaml */
|
2007-01-29 04:11:18 -08:00
|
|
|
/* */
|
|
|
|
/* Xavier Leroy, projet Gallium, INRIA Rocquencourt */
|
|
|
|
/* */
|
|
|
|
/* Copyright 2006 Institut National de Recherche en Informatique et */
|
|
|
|
/* en Automatique. All rights reserved. This file is distributed */
|
|
|
|
/* under the terms of the GNU Library General Public License, with */
|
|
|
|
/* the special exception on linking described in file ../LICENSE. */
|
|
|
|
/* */
|
|
|
|
/***********************************************************************/
|
|
|
|
|
|
|
|
/* Stack backtrace for uncaught exceptions */
|
|
|
|
|
|
|
|
#include <stdio.h>
|
2013-03-11 12:04:12 -07:00
|
|
|
#include <stdlib.h>
|
2013-03-22 11:36:22 -07:00
|
|
|
#include <string.h>
|
|
|
|
|
2008-03-14 06:47:24 -07:00
|
|
|
#include "alloc.h"
|
2007-01-29 04:11:18 -08:00
|
|
|
#include "backtrace.h"
|
|
|
|
#include "memory.h"
|
|
|
|
#include "misc.h"
|
|
|
|
#include "mlvalues.h"
|
|
|
|
#include "stack.h"
|
|
|
|
|
|
|
|
int caml_backtrace_active = 0;
|
|
|
|
int caml_backtrace_pos = 0;
|
2012-07-22 08:15:55 -07:00
|
|
|
code_t * caml_backtrace_buffer = NULL;
|
2007-01-29 04:11:18 -08:00
|
|
|
value caml_backtrace_last_exn = Val_unit;
|
|
|
|
#define BACKTRACE_BUFFER_SIZE 1024
|
|
|
|
|
2014-05-10 12:19:52 -07:00
|
|
|
/* In order to prevent the GC from walking through the debug information
|
|
|
|
(which have no headers), we transform frame_descr pointers into
|
|
|
|
31/63 bits ocaml integers by shifting them by 1 to the right. We do
|
|
|
|
not lose information as descr pointers are aligned.
|
|
|
|
|
|
|
|
In particular, we do not need to use [caml_initialize] when setting
|
|
|
|
an array element with such a value.
|
|
|
|
*/
|
|
|
|
#define Val_Descrptr(descr) Val_long((uintnat)descr>>1)
|
|
|
|
#define Descrptr_Val(v) ((frame_descr *) (Long_val(v)<<1))
|
|
|
|
|
2008-03-14 06:47:24 -07:00
|
|
|
/* Start or stop the backtrace machinery */
|
2007-01-29 04:11:18 -08:00
|
|
|
|
2008-03-14 06:47:24 -07:00
|
|
|
CAMLprim value caml_record_backtrace(value vflag)
|
2007-01-29 04:11:18 -08:00
|
|
|
{
|
2008-03-14 06:47:24 -07:00
|
|
|
int flag = Int_val(vflag);
|
|
|
|
|
|
|
|
if (flag != caml_backtrace_active) {
|
|
|
|
caml_backtrace_active = flag;
|
|
|
|
caml_backtrace_pos = 0;
|
|
|
|
if (flag) {
|
|
|
|
caml_register_global_root(&caml_backtrace_last_exn);
|
|
|
|
} else {
|
|
|
|
caml_remove_global_root(&caml_backtrace_last_exn);
|
|
|
|
}
|
|
|
|
}
|
|
|
|
return Val_unit;
|
|
|
|
}
|
|
|
|
|
|
|
|
/* Return the status of the backtrace machinery */
|
|
|
|
|
|
|
|
CAMLprim value caml_backtrace_status(value vunit)
|
|
|
|
{
|
|
|
|
return Val_bool(caml_backtrace_active);
|
2007-01-29 04:11:18 -08:00
|
|
|
}
|
|
|
|
|
2013-06-19 07:12:02 -07:00
|
|
|
/* returns the next frame descriptor (or NULL if none is available),
|
|
|
|
and updates *pc and *sp to point to the following one. */
|
2007-01-29 04:11:18 -08:00
|
|
|
|
2013-06-19 07:12:02 -07:00
|
|
|
frame_descr * caml_next_frame_descriptor(uintnat * pc, char ** sp)
|
2007-01-29 04:11:18 -08:00
|
|
|
{
|
|
|
|
frame_descr * d;
|
|
|
|
uintnat h;
|
|
|
|
|
|
|
|
if (caml_frame_descriptors == NULL) caml_init_frame_descriptors();
|
|
|
|
|
|
|
|
while (1) {
|
2013-06-19 07:12:02 -07:00
|
|
|
h = Hash_retaddr(*pc);
|
|
|
|
while (1) {
|
2007-01-29 04:11:18 -08:00
|
|
|
d = caml_frame_descriptors[h];
|
2013-09-04 08:12:37 -07:00
|
|
|
if (d == 0) return NULL; /* can happen if some code compiled without -g */
|
2013-06-19 07:12:02 -07:00
|
|
|
if (d->retaddr == *pc) break;
|
2007-01-29 04:11:18 -08:00
|
|
|
h = (h+1) & caml_frame_descriptors_mask;
|
|
|
|
}
|
|
|
|
/* Skip to next frame */
|
|
|
|
if (d->frame_size != 0xFFFF) {
|
2013-06-19 07:12:02 -07:00
|
|
|
/* Regular frame, update sp/pc and return the frame descriptor */
|
2007-01-29 04:11:18 -08:00
|
|
|
#ifndef Stack_grows_upwards
|
2013-06-19 07:12:02 -07:00
|
|
|
*sp += (d->frame_size & 0xFFFC);
|
2007-01-29 04:11:18 -08:00
|
|
|
#else
|
2013-06-19 07:12:02 -07:00
|
|
|
*sp -= (d->frame_size & 0xFFFC);
|
2007-01-29 04:11:18 -08:00
|
|
|
#endif
|
2013-06-19 07:12:02 -07:00
|
|
|
*pc = Saved_return_address(*sp);
|
2007-01-29 04:11:18 -08:00
|
|
|
#ifdef Mask_already_scanned
|
2013-06-19 07:12:02 -07:00
|
|
|
*pc = Mask_already_scanned(*pc);
|
2007-01-29 04:11:18 -08:00
|
|
|
#endif
|
2013-06-19 07:12:02 -07:00
|
|
|
return d;
|
2007-01-29 04:11:18 -08:00
|
|
|
} else {
|
|
|
|
/* Special frame marking the top of a stack chunk for an ML callback.
|
|
|
|
Skip C portion of stack and continue with next ML stack chunk. */
|
2013-06-19 07:12:02 -07:00
|
|
|
struct caml_context * next_context = Callback_link(*sp);
|
|
|
|
*sp = next_context->bottom_of_stack;
|
|
|
|
*pc = next_context->last_retaddr;
|
2007-01-29 04:11:18 -08:00
|
|
|
/* A null sp means no more ML stack chunks; stop here. */
|
2013-06-19 07:12:02 -07:00
|
|
|
if (*sp == NULL) return NULL;
|
2007-01-29 04:11:18 -08:00
|
|
|
}
|
2013-06-19 07:12:02 -07:00
|
|
|
}
|
|
|
|
}
|
|
|
|
|
|
|
|
/* Stores the return addresses contained in the given stack fragment
|
|
|
|
into the backtrace array ; this version is performance-sensitive as
|
|
|
|
it is called at each [raise] in a program compiled with [-g], so we
|
|
|
|
preserved the global, statically bounded buffer of the old
|
|
|
|
implementation -- before the more flexible
|
|
|
|
[caml_get_current_callstack] was implemented. */
|
|
|
|
|
|
|
|
void caml_stash_backtrace(value exn, uintnat pc, char * sp, char * trapsp)
|
|
|
|
{
|
|
|
|
if (exn != caml_backtrace_last_exn) {
|
|
|
|
caml_backtrace_pos = 0;
|
|
|
|
caml_backtrace_last_exn = exn;
|
|
|
|
}
|
|
|
|
if (caml_backtrace_buffer == NULL) {
|
2014-05-10 12:19:53 -07:00
|
|
|
Assert(caml_backtrace_pos == 0);
|
2013-06-19 07:12:02 -07:00
|
|
|
caml_backtrace_buffer = malloc(BACKTRACE_BUFFER_SIZE * sizeof(code_t));
|
|
|
|
if (caml_backtrace_buffer == NULL) return;
|
|
|
|
}
|
|
|
|
|
|
|
|
/* iterate on each frame */
|
|
|
|
while (1) {
|
|
|
|
frame_descr * descr = caml_next_frame_descriptor(&pc, &sp);
|
|
|
|
if (descr == NULL) return;
|
|
|
|
/* store its descriptor in the backtrace buffer */
|
|
|
|
if (caml_backtrace_pos >= BACKTRACE_BUFFER_SIZE) return;
|
|
|
|
caml_backtrace_buffer[caml_backtrace_pos++] = (code_t) descr;
|
2013-09-04 08:12:37 -07:00
|
|
|
|
2007-01-29 04:11:18 -08:00
|
|
|
/* Stop when we reach the current exception handler */
|
|
|
|
#ifndef Stack_grows_upwards
|
2013-01-23 00:41:02 -08:00
|
|
|
if (sp > trapsp) return;
|
2007-01-29 04:11:18 -08:00
|
|
|
#else
|
2013-01-23 00:41:02 -08:00
|
|
|
if (sp < trapsp) return;
|
2007-01-29 04:11:18 -08:00
|
|
|
#endif
|
|
|
|
}
|
|
|
|
}
|
|
|
|
|
2013-06-19 07:12:02 -07:00
|
|
|
/* Stores upto [max_frames_value] frames of the current call stack to
|
|
|
|
return to the user. This is used not in an exception-raising
|
|
|
|
context, but only when the user requests to save the trace
|
|
|
|
(hopefully less often). Instead of using a bounded buffer as
|
|
|
|
[caml_stash_backtrace], we first traverse the stack to compute the
|
|
|
|
right size, then allocate space for the trace. */
|
|
|
|
|
|
|
|
CAMLprim value caml_get_current_callstack(value max_frames_value) {
|
|
|
|
CAMLparam1(max_frames_value);
|
|
|
|
CAMLlocal1(trace);
|
|
|
|
|
|
|
|
/* we use `intnat` here because, were it only `int`, passing `max_int`
|
|
|
|
from the OCaml side would overflow on 64bits machines. */
|
|
|
|
intnat max_frames = Long_val(max_frames_value);
|
|
|
|
intnat trace_size;
|
|
|
|
|
|
|
|
/* first compute the size of the trace */
|
|
|
|
{
|
|
|
|
uintnat pc = caml_last_return_address;
|
|
|
|
/* note that [caml_bottom_of_stack] always points to the most recent
|
|
|
|
* frame, independently of the [Stack_grows_upwards] setting */
|
|
|
|
char * sp = caml_bottom_of_stack;
|
|
|
|
char * limitsp = caml_top_of_stack;
|
|
|
|
|
|
|
|
trace_size = 0;
|
|
|
|
while (1) {
|
|
|
|
frame_descr * descr = caml_next_frame_descriptor(&pc, &sp);
|
2013-09-04 08:12:37 -07:00
|
|
|
if (descr == NULL) break;
|
2013-06-19 07:12:02 -07:00
|
|
|
if (trace_size >= max_frames) break;
|
|
|
|
++trace_size;
|
|
|
|
|
|
|
|
#ifndef Stack_grows_upwards
|
|
|
|
if (sp > limitsp) break;
|
|
|
|
#else
|
|
|
|
if (sp < limitsp) break;
|
|
|
|
#endif
|
|
|
|
}
|
|
|
|
}
|
|
|
|
|
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
|
|
|
trace = caml_alloc((mlsize_t) trace_size, 0);
|
2013-06-19 07:12:02 -07:00
|
|
|
|
|
|
|
/* then collect the trace */
|
|
|
|
{
|
|
|
|
uintnat pc = caml_last_return_address;
|
|
|
|
char * sp = caml_bottom_of_stack;
|
|
|
|
intnat trace_pos;
|
|
|
|
|
|
|
|
for (trace_pos = 0; trace_pos < trace_size; trace_pos++) {
|
|
|
|
frame_descr * descr = caml_next_frame_descriptor(&pc, &sp);
|
|
|
|
Assert(descr != NULL);
|
2014-05-10 12:19:52 -07:00
|
|
|
Field(trace, trace_pos) = Val_Descrptr(descr);
|
2013-06-19 07:12:02 -07:00
|
|
|
}
|
|
|
|
}
|
|
|
|
|
|
|
|
CAMLreturn(trace);
|
|
|
|
}
|
|
|
|
|
2008-03-14 06:47:24 -07:00
|
|
|
/* Extract location information for the given frame descriptor */
|
2007-01-29 04:11:18 -08:00
|
|
|
|
2008-03-14 06:47:24 -07:00
|
|
|
struct loc_info {
|
|
|
|
int loc_valid;
|
|
|
|
int loc_is_raise;
|
|
|
|
char * loc_filename;
|
|
|
|
int loc_lnum;
|
|
|
|
int loc_startchr;
|
|
|
|
int loc_endchr;
|
|
|
|
};
|
|
|
|
|
|
|
|
static void extract_location_info(frame_descr * d,
|
|
|
|
/*out*/ struct loc_info * li)
|
2007-01-29 04:11:18 -08:00
|
|
|
{
|
|
|
|
uintnat infoptr;
|
2014-08-27 02:58:33 -07:00
|
|
|
uint32_t info1, info2;
|
2007-01-29 04:11:18 -08:00
|
|
|
|
|
|
|
/* If no debugging information available, print nothing.
|
2010-01-22 04:48:24 -08:00
|
|
|
When everything is compiled with -g, this corresponds to
|
2007-01-29 04:11:18 -08:00
|
|
|
compiler-inserted re-raise operations. */
|
2008-03-14 06:47:24 -07:00
|
|
|
if ((d->frame_size & 1) == 0) {
|
|
|
|
li->loc_valid = 0;
|
|
|
|
li->loc_is_raise = 1;
|
|
|
|
return;
|
|
|
|
}
|
2007-01-29 04:11:18 -08:00
|
|
|
/* Recover debugging info */
|
|
|
|
infoptr = ((uintnat) d +
|
|
|
|
sizeof(char *) + sizeof(short) + sizeof(short) +
|
|
|
|
sizeof(short) * d->num_live + sizeof(frame_descr *) - 1)
|
|
|
|
& -sizeof(frame_descr *);
|
2014-08-27 02:58:33 -07:00
|
|
|
info1 = ((uint32_t *)infoptr)[0];
|
|
|
|
info2 = ((uint32_t *)infoptr)[1];
|
2007-01-29 04:11:18 -08:00
|
|
|
/* Format of the two info words:
|
|
|
|
llllllllllllllllllll aaaaaaaa bbbbbbbbbb nnnnnnnnnnnnnnnnnnnnnnnn kk
|
2010-01-22 04:48:24 -08:00
|
|
|
44 36 26 2 0
|
2007-01-29 04:11:18 -08:00
|
|
|
(32+12) (32+4)
|
|
|
|
k ( 2 bits): 0 if it's a call, 1 if it's a raise
|
|
|
|
n (24 bits): offset (in 4-byte words) of file name relative to infoptr
|
|
|
|
l (20 bits): line number
|
|
|
|
a ( 8 bits): beginning of character range
|
|
|
|
b (10 bits): end of character range */
|
2008-03-14 06:47:24 -07:00
|
|
|
li->loc_valid = 1;
|
|
|
|
li->loc_is_raise = (info1 & 3) != 0;
|
|
|
|
li->loc_filename = (char *) infoptr + (info1 & 0x3FFFFFC);
|
|
|
|
li->loc_lnum = info2 >> 12;
|
|
|
|
li->loc_startchr = (info2 >> 4) & 0xFF;
|
|
|
|
li->loc_endchr = ((info2 & 0xF) << 6) | (info1 >> 26);
|
|
|
|
}
|
|
|
|
|
2013-06-19 07:03:51 -07:00
|
|
|
/* Print location information -- same behavior as in Printexc
|
2013-09-04 08:12:37 -07:00
|
|
|
|
2013-06-19 07:03:51 -07:00
|
|
|
note that the test for compiler-inserted raises is slightly redundant:
|
|
|
|
(!li->loc_valid && li->loc_is_raise)
|
|
|
|
extract_location_info above guarantees that when li->loc_valid is
|
|
|
|
0, then li->loc_is_raise is always 1, so the latter test is
|
|
|
|
useless. We kept it to keep code identical to the byterun/
|
|
|
|
implementation. */
|
|
|
|
|
2012-07-22 08:15:55 -07:00
|
|
|
static void print_location(struct loc_info * li, int index)
|
2008-03-14 06:47:24 -07:00
|
|
|
{
|
|
|
|
char * info;
|
|
|
|
|
|
|
|
/* Ignore compiler-inserted raise */
|
2013-06-19 07:03:51 -07:00
|
|
|
if (!li->loc_valid && li->loc_is_raise) return;
|
|
|
|
|
|
|
|
if (li->loc_is_raise) {
|
|
|
|
/* Initial raise if index == 0, re-raise otherwise */
|
|
|
|
if (index == 0)
|
|
|
|
info = "Raised at";
|
|
|
|
else
|
|
|
|
info = "Re-raised at";
|
|
|
|
} else {
|
|
|
|
if (index == 0)
|
|
|
|
info = "Raised by primitive operation at";
|
|
|
|
else
|
|
|
|
info = "Called from";
|
|
|
|
}
|
|
|
|
if (! li->loc_valid) {
|
|
|
|
fprintf(stderr, "%s unknown location\n", info);
|
|
|
|
} else {
|
|
|
|
fprintf (stderr, "%s file \"%s\", line %d, characters %d-%d\n",
|
|
|
|
info, li->loc_filename, li->loc_lnum,
|
|
|
|
li->loc_startchr, li->loc_endchr);
|
|
|
|
}
|
2007-01-29 04:11:18 -08:00
|
|
|
}
|
|
|
|
|
2008-03-14 06:47:24 -07:00
|
|
|
/* Print a backtrace */
|
|
|
|
|
2007-01-29 04:11:18 -08:00
|
|
|
void caml_print_exception_backtrace(void)
|
|
|
|
{
|
|
|
|
int i;
|
2008-03-14 06:47:24 -07:00
|
|
|
struct loc_info li;
|
|
|
|
|
|
|
|
for (i = 0; i < caml_backtrace_pos; i++) {
|
2012-07-22 08:15:55 -07:00
|
|
|
extract_location_info((frame_descr *) (caml_backtrace_buffer[i]), &li);
|
|
|
|
print_location(&li, i);
|
2008-03-14 06:47:24 -07:00
|
|
|
}
|
|
|
|
}
|
2007-01-29 04:11:18 -08:00
|
|
|
|
2013-03-11 12:04:12 -07:00
|
|
|
/* Convert the raw backtrace to a data structure usable from OCaml */
|
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
|
|
|
CAMLprim value caml_convert_raw_backtrace_slot(value backtrace_slot) {
|
|
|
|
CAMLparam1(backtrace_slot);
|
|
|
|
CAMLlocal2(p, fname);
|
2008-03-14 06:47:24 -07:00
|
|
|
struct loc_info li;
|
|
|
|
|
2014-05-10 12:19:52 -07:00
|
|
|
extract_location_info(Descrptr_Val(backtrace_slot), &li);
|
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
|
|
|
|
|
|
|
if (li.loc_valid) {
|
|
|
|
fname = caml_copy_string(li.loc_filename);
|
|
|
|
p = caml_alloc_small(5, 0);
|
|
|
|
Field(p, 0) = Val_bool(li.loc_is_raise);
|
|
|
|
Field(p, 1) = fname;
|
|
|
|
Field(p, 2) = Val_int(li.loc_lnum);
|
|
|
|
Field(p, 3) = Val_int(li.loc_startchr);
|
|
|
|
Field(p, 4) = Val_int(li.loc_endchr);
|
|
|
|
} else {
|
|
|
|
p = caml_alloc_small(1, 1);
|
|
|
|
Field(p, 0) = Val_bool(li.loc_is_raise);
|
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
|
|
|
|
|
|
|
CAMLreturn(p);
|
2007-01-29 04:11:18 -08:00
|
|
|
}
|
2013-03-11 12:04:12 -07:00
|
|
|
|
|
|
|
/* Get a copy of the latest backtrace */
|
|
|
|
|
|
|
|
CAMLprim value caml_get_exception_raw_backtrace(value unit)
|
|
|
|
{
|
|
|
|
CAMLparam0();
|
|
|
|
CAMLlocal1(res);
|
|
|
|
|
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
|
|
|
res = caml_alloc(caml_backtrace_pos, 0);
|
|
|
|
if(caml_backtrace_buffer != NULL) {
|
|
|
|
intnat i;
|
|
|
|
for(i = 0; i < caml_backtrace_pos; i++)
|
2014-05-10 12:19:52 -07:00
|
|
|
Field(res, i) = Val_Descrptr(caml_backtrace_buffer[i]);
|
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
|
|
|
}
|
2013-03-11 12:04:12 -07:00
|
|
|
CAMLreturn(res);
|
|
|
|
}
|
2014-05-10 12:19:53 -07:00
|
|
|
|
|
|
|
/* the function below is deprecated: we previously returned directly
|
|
|
|
the OCaml-usable representation, instead of the raw backtrace as an
|
|
|
|
abstract type, but this has a large performance overhead if you
|
|
|
|
store a lot of backtraces and print only some of them.
|
|
|
|
|
|
|
|
It is not used by the Printexc library anymore, or anywhere else in
|
|
|
|
the compiler, but we have kept it in case some user still depends
|
|
|
|
on it as an external.
|
|
|
|
*/
|
|
|
|
|
|
|
|
CAMLprim value caml_get_exception_backtrace(value unit)
|
|
|
|
{
|
|
|
|
CAMLparam0();
|
|
|
|
CAMLlocal4(arr, raw_slot, slot, res);
|
|
|
|
|
|
|
|
arr = caml_alloc(caml_backtrace_pos, 0);
|
|
|
|
if (caml_backtrace_buffer == NULL) {
|
|
|
|
Assert(caml_backtrace_pos == 0);
|
|
|
|
} else {
|
|
|
|
intnat i;
|
|
|
|
for(i = 0; i < caml_backtrace_pos; i++) {
|
|
|
|
raw_slot = Val_Descrptr(caml_backtrace_buffer[i]);
|
|
|
|
slot = caml_convert_raw_backtrace_slot(raw_slot);
|
|
|
|
caml_modify(&Field(arr, i), slot);
|
|
|
|
}
|
|
|
|
}
|
|
|
|
res = caml_alloc_small(1, 0); Field(res, 0) = arr; /* Some */
|
|
|
|
CAMLreturn(res);
|
|
|
|
}
|