Skip to content

Commit

Permalink
Dynamically allocate the alternate signal stack (ocaml#10266 and ocam…
Browse files Browse the repository at this point in the history
…l#10726)

In Glibc 2.34 and later, SIGSTKSZ may not be a compile-time constant.
It is no longer possible to statically allocate the alternate signal
stack for the main thread, as we've been doing for the last 25 years.

This commit implements dynamic allocation of the alternate signal stack
even for the main thread.  It reuses the code already in place to allocate
the alternate signal stack for other threads.

The alternate signal stack is freed when the main OCaml code / an OCaml thread
stops.

Fixes: ocaml#10250
  • Loading branch information
xavierleroy authored and dra27 committed Dec 10, 2021
1 parent 9844919 commit b5ad4de
Show file tree
Hide file tree
Showing 8 changed files with 89 additions and 19 deletions.
10 changes: 8 additions & 2 deletions manual/manual/cmds/intf-c.etex
Expand Up @@ -1699,8 +1699,8 @@ compilation of OCaml, as the variable "OC_LDFLAGS".
OCaml have been compiled with the "/MD" flag, and therefore
all other object files linked with it should also be compiled with
"/MD".
\item other systems: you may have to add one or more of "-lcurses",
"-lm", "-ldl", depending on your OS and C compiler.
\item other systems: you may have to add one or both of
"-lm" and "-ldl", depending on your OS and C compiler.
\end{itemize}

\paragraph{Stack backtraces.} When OCaml bytecode produced by
Expand Down Expand Up @@ -1749,6 +1749,12 @@ Once a runtime is unloaded, it cannot be started up again without reloading the
shared library and reinitializing its static data. Therefore, at the moment, the
facility is only useful for building reloadable shared libraries.

\paragraph{Unix signal handling.} Depending on the target platform and
operating system, the native-code runtime system may install signal
handlers for one or several of the "SIGSEGV", "SIGTRAP" and "SIGFPE"
signals when "caml_startup" is called, and reset these signals to
their default behaviors when "caml_shutdown" is called. The main
program written in~C should not try to handle these signals itself.

\section{s:c-advexample}{Advanced example with callbacks}

Expand Down
1 change: 1 addition & 0 deletions otherlibs/systhreads/st_stubs.c
Expand Up @@ -540,6 +540,7 @@ static ST_THREAD_FUNCTION caml_thread_start(void * arg)
#ifdef NATIVE_CODE
}
#endif
caml_stop_stack_overflow_detection();
/* The thread now stops running */
return 0;
}
Expand Down
6 changes: 4 additions & 2 deletions runtime/caml/signals.h
Expand Up @@ -87,8 +87,10 @@ value caml_do_pending_actions_exn (void);
value caml_process_pending_actions_with_root (value extra_root); // raises
value caml_process_pending_actions_with_root_exn (value extra_root);
int caml_set_signal_action(int signo, int action);
CAMLextern void caml_setup_stack_overflow_detection(void);

CAMLextern int caml_setup_stack_overflow_detection(void);
CAMLextern int caml_stop_stack_overflow_detection(void);
CAMLextern void caml_init_signals(void);
CAMLextern void caml_terminate_signals(void);
CAMLextern void (*caml_enter_blocking_section_hook)(void);
CAMLextern void (*caml_leave_blocking_section_hook)(void);
#ifdef POSIX_SIGNALS
Expand Down
6 changes: 5 additions & 1 deletion runtime/fail_nat.c
Expand Up @@ -31,6 +31,7 @@
#include "caml/stack.h"
#include "caml/roots.h"
#include "caml/callback.h"
#include "caml/signals.h"

/* The globals holding predefined exceptions */

Expand Down Expand Up @@ -70,7 +71,10 @@ void caml_raise(value v)
if (Is_exception_result(v))
v = Extract_exception(v);

if (Caml_state->exception_pointer == NULL) caml_fatal_uncaught_exception(v);
if (Caml_state->exception_pointer == NULL) {
caml_terminate_signals();
caml_fatal_uncaught_exception(v);
}

while (Caml_state->local_roots != NULL &&
(char *) Caml_state->local_roots < Caml_state->exception_pointer) {
Expand Down
5 changes: 4 additions & 1 deletion runtime/signals_byt.c
Expand Up @@ -81,4 +81,7 @@ int caml_set_signal_action(int signo, int action)
return 0;
}

CAMLexport void caml_setup_stack_overflow_detection(void) {}
CAMLexport int caml_setup_stack_overflow_detection(void) { return 0; }
CAMLexport int caml_stop_stack_overflow_detection(void) { return 0; }
CAMLexport void caml_init_signals(void) { }
CAMLexport void caml_terminate_signals(void) { }
71 changes: 60 additions & 11 deletions runtime/signals_nat.c
Expand Up @@ -181,8 +181,6 @@ DECLARE_SIGNAL_HANDLER(trap_handler)
#error "CONTEXT_SP is required if HAS_STACK_OVERFLOW_DETECTION is defined"
#endif

static char sig_alt_stack[SIGSTKSZ];

/* Code compiled with ocamlopt never accesses more than
EXTRA_STACK bytes below the stack pointer. */
#define EXTRA_STACK 256
Expand Down Expand Up @@ -276,28 +274,79 @@ void caml_init_signals(void)
#endif

#ifdef HAS_STACK_OVERFLOW_DETECTION
{
stack_t stk;
if (caml_setup_stack_overflow_detection() != -1) {
struct sigaction act;
stk.ss_sp = sig_alt_stack;
stk.ss_size = SIGSTKSZ;
stk.ss_flags = 0;
SET_SIGACT(act, segv_handler);
act.sa_flags |= SA_ONSTACK | SA_NODEFER;
sigemptyset(&act.sa_mask);
if (sigaltstack(&stk, NULL) == 0) { sigaction(SIGSEGV, &act, NULL); }
sigaction(SIGSEGV, &act, NULL);
}
#endif
}

CAMLexport void caml_setup_stack_overflow_detection(void)
/* Termination of signal stuff */

#if defined(TARGET_power) || defined(TARGET_s390x) \
|| defined(HAS_STACK_OVERFLOW_DETECTION)
static void set_signal_default(int signum)
{
struct sigaction act;
sigemptyset(&act.sa_mask);
act.sa_handler = SIG_DFL;
act.sa_flags = 0;
sigaction(signum, &act, NULL);
}
#endif

void caml_terminate_signals(void)
{
#if defined(TARGET_power)
set_signal_default(SIGTRAP);
#endif

#if defined(TARGET_s390x)
set_signal_default(SIGFPE);
#endif

#ifdef HAS_STACK_OVERFLOW_DETECTION
set_signal_default(SIGSEGV);
caml_stop_stack_overflow_detection();
#endif
}

/* Allocate and select an alternate stack for handling signals,
especially SIGSEGV signals.
Each thread needs its own alternate stack.
The alternate stack used to be statically-allocated for the main thread,
but this is incompatible with Glibc 2.34 and newer, where SIGSTKSZ
may not be a compile-time constant (issue #10250). */

CAMLexport int caml_setup_stack_overflow_detection(void)
{
#ifdef HAS_STACK_OVERFLOW_DETECTION
stack_t stk;
stk.ss_sp = malloc(SIGSTKSZ);
if (stk.ss_sp == NULL) return -1;
stk.ss_size = SIGSTKSZ;
stk.ss_flags = 0;
if (stk.ss_sp)
sigaltstack(&stk, NULL);
return sigaltstack(&stk, NULL);
#else
return 0;
#endif
}

CAMLexport int caml_stop_stack_overflow_detection(void)
{
#ifdef HAS_STACK_OVERFLOW_DETECTION
stack_t oldstk, stk;
stk.ss_flags = SS_DISABLE;
if (sigaltstack(&stk, &oldstk) == -1) return -1;
/* If caml_setup_stack_overflow_detection failed, we are not using
an alternate signal stack. SS_DISABLE will be set in oldstk,
and there is nothing to free in this case. */
if (! (oldstk.ss_flags & SS_DISABLE)) free(oldstk.ss_sp);
return 0;
#else
return 0;
#endif
}
8 changes: 6 additions & 2 deletions runtime/startup_nat.c
Expand Up @@ -36,6 +36,7 @@
#include "caml/mlvalues.h"
#include "caml/osdeps.h"
#include "caml/printexc.h"
#include "caml/signals.h"
#include "caml/stack.h"
#include "caml/startup_aux.h"
#include "caml/sys.h"
Expand Down Expand Up @@ -91,7 +92,6 @@ struct longjmp_buffer caml_termination_jmpbuf;
void (*caml_termination_hook)(void *) = NULL;

extern value caml_start_program (caml_domain_state*);
extern void caml_init_signals (void);
#ifdef _WIN32
extern void caml_win32_overflow_detection (void);
#endif
Expand All @@ -106,6 +106,7 @@ extern void caml_install_invalid_parameter_handler();
value caml_startup_common(char_os **argv, int pooling)
{
char_os * exe_name, * proc_self_exe;
value res;
char tos;

/* Initialize the domain */
Expand Down Expand Up @@ -152,10 +153,13 @@ value caml_startup_common(char_os **argv, int pooling)
exe_name = caml_search_exe_in_path(exe_name);
caml_sys_init(exe_name, argv);
if (sigsetjmp(caml_termination_jmpbuf.buf, 0)) {
caml_terminate_signals();
if (caml_termination_hook != NULL) caml_termination_hook(NULL);
return Val_unit;
}
return caml_start_program(Caml_state);
res = caml_start_program(Caml_state);
caml_terminate_signals();
return res;
}

value caml_startup_exn(char_os **argv)
Expand Down
1 change: 1 addition & 0 deletions runtime/sys.c
Expand Up @@ -160,6 +160,7 @@ CAMLprim value caml_sys_exit(value retcode_v)
#ifdef _WIN32
caml_restore_win32_terminal();
#endif
caml_terminate_signals();
exit(retcode);
}

Expand Down

0 comments on commit b5ad4de

Please sign in to comment.