Skip to content

Commit

Permalink
Introduce caml_record_backtraces
Browse files Browse the repository at this point in the history
The manual suggests calling caml_record_backtrace (which is the
primitive), but this symbol is not declared publicly in the headers. All
occurrences in C, and the use-case detailed in the manual, are for
turning backtraces on, so introduce an actual C function to do this and
remove the declaration of the primitive.
  • Loading branch information
dra27 committed Mar 1, 2021
1 parent 98c16b3 commit 6fe74ec
Show file tree
Hide file tree
Showing 6 changed files with 28 additions and 19 deletions.
4 changes: 4 additions & 0 deletions Changes
Original file line number Diff line number Diff line change
Expand Up @@ -42,6 +42,10 @@ Working version
Leroy and Damien Doligez, benchmarking by Shubham Kumar and KC
Sivaramakrishnan)

- #9919: Introduce caml_record_backtraces and update Interfacing with C to
refer to it (previous instruction to use caml_record_backtrace primitive was
not possible without defining CAML_INTERNALS)

- #10102: Ignore PROFINFO_WIDTH if WITH_PROFINFO is not defined (technically
a breaking change if the configuration system was being abused before).
(David Allsopp, review by Xavier Leroy)
Expand Down
3 changes: 2 additions & 1 deletion manual/src/cmds/intf-c.etex
Original file line number Diff line number Diff line change
Expand Up @@ -1740,7 +1740,8 @@ information is available, but the backtrace mechanism needs to be
turned on programmatically. This can be achieved from the OCaml side
by calling "Printexc.record_backtrace true" in the initialization of
one of the OCaml modules. This can also be achieved from the C side
by calling "caml_record_backtrace(Val_int(1));" in the OCaml-C glue code.
by calling "caml_record_backtraces(1);" in the OCaml-C glue code.
("caml_record_backtraces" is declared in "backtrace.h")

\paragraph{Unloading the runtime.}

Expand Down
10 changes: 7 additions & 3 deletions runtime/backtrace.c
Original file line number Diff line number Diff line change
Expand Up @@ -35,10 +35,8 @@ void caml_init_backtrace(void)
}

/* Start or stop the backtrace machinery */
CAMLprim value caml_record_backtrace(value vflag)
CAMLexport void caml_record_backtraces(int flag)
{
int flag = Int_val(vflag);

if (flag != Caml_state->backtrace_active) {
Caml_state->backtrace_active = flag;
Caml_state->backtrace_pos = 0;
Expand All @@ -49,6 +47,12 @@ CAMLprim value caml_record_backtrace(value vflag)
Caml_state->backtrace_buffer). So we don't have to allocate it here.
*/
}
return;
}

CAMLprim value caml_record_backtrace(value flag)
{
caml_record_backtraces(Int_val(flag));
return Val_unit;
}

Expand Down
25 changes: 13 additions & 12 deletions runtime/caml/backtrace.h
Original file line number Diff line number Diff line change
Expand Up @@ -16,9 +16,19 @@
#ifndef CAML_BACKTRACE_H
#define CAML_BACKTRACE_H

#include "mlvalues.h"

/* [caml_record_backtraces] controls backtrace recording.
* This function can be called at runtime by user-code, or during
* initialization if backtraces were requested.
*
* It might be called before GC initialization, so it shouldn't do OCaml
* allocation.
*/
CAMLextern void caml_record_backtraces(int);

#ifdef CAML_INTERNALS

#include "mlvalues.h"
#include "exec.h"

/* Runtime support for backtrace generation.
Expand Down Expand Up @@ -52,7 +62,8 @@
* OCaml values of algebraic data-type [Printexc.backtrace_slot]
*/
/* [Caml_state->backtrace_active] is non zero iff backtraces are recorded.
* This variable must be changed with [caml_record_backtrace].
* This variable must be changed with [caml_record_backtrace] in OCaml or
* [caml_record_backtraces] in C.
*/
#define caml_backtrace_active (Caml_state_field(backtrace_active))
/* The [Caml_state->backtrace_buffer] and [Caml_state->backtrace_last_exn]
Expand Down Expand Up @@ -89,16 +100,6 @@
runtimes for raise.
*/

/* [caml_record_backtrace] toggle backtrace recording on and off.
* This function can be called at runtime by user-code, or during
* initialization if backtraces were requested.
*
* It might be called before GC initialization, so it shouldn't do OCaml
* allocation.
*/
CAMLextern value caml_record_backtrace(value vflag);


#ifndef NATIVE_CODE

/* Path to the file containing debug information, if any, or NULL. */
Expand Down
3 changes: 1 addition & 2 deletions runtime/startup_aux.c
Original file line number Diff line number Diff line change
Expand Up @@ -111,8 +111,7 @@ void caml_parse_ocamlrunparam(void)
switch (*opt++){
case 'a': scanmult (opt, &p); caml_set_allocation_policy ((intnat) p);
break;
case 'b': scanmult (opt, &p); caml_record_backtrace(Val_int (p));
break;
case 'b': scanmult (opt, &p); caml_record_backtraces(p); break;
case 'c': scanmult (opt, &p); caml_cleanup_on_exit = (p != 0); break;
case 'h': scanmult (opt, &caml_init_heap_wsz); break;
case 'H': scanmult (opt, &caml_use_huge_pages); break;
Expand Down
2 changes: 1 addition & 1 deletion runtime/startup_byt.c
Original file line number Diff line number Diff line change
Expand Up @@ -321,7 +321,7 @@ static int parse_command_line(char_os **argv)
exit(0);
break;
case 'b':
caml_record_backtrace(Val_true);
caml_record_backtraces(1);
break;
case 'I':
if (argv[i + 1] != NULL) {
Expand Down

0 comments on commit 6fe74ec

Please sign in to comment.