1995-08-09 08:06:35 -07:00
|
|
|
/***********************************************************************/
|
|
|
|
/* */
|
1996-04-30 07:53:58 -07:00
|
|
|
/* Objective Caml */
|
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
|
|
|
/* */
|
|
|
|
/***********************************************************************/
|
|
|
|
|
|
|
|
/* $Id$ */
|
|
|
|
|
2004-08-13 06:38:27 -07:00
|
|
|
#if defined(TARGET_amd64) && defined (SYS_linux)
|
|
|
|
#define _GNU_SOURCE
|
|
|
|
#endif
|
1995-12-21 03:01:45 -08:00
|
|
|
#include <signal.h>
|
2003-03-26 06:54:45 -08:00
|
|
|
#include <stdio.h>
|
1995-12-21 03:01:45 -08:00
|
|
|
#include "alloc.h"
|
1996-11-15 07:24:14 -08:00
|
|
|
#include "callback.h"
|
1995-12-21 04:29:49 -08:00
|
|
|
#include "memory.h"
|
1995-12-21 03:01:45 -08:00
|
|
|
#include "minor_gc.h"
|
1995-07-10 02:48:27 -07:00
|
|
|
#include "misc.h"
|
|
|
|
#include "mlvalues.h"
|
1995-07-24 05:44:52 -07:00
|
|
|
#include "fail.h"
|
2005-07-28 09:28:41 -07:00
|
|
|
#include "osdeps.h"
|
1995-07-10 02:48:27 -07:00
|
|
|
#include "signals.h"
|
2005-07-29 05:11:01 -07:00
|
|
|
#include "signals_machdep.h"
|
|
|
|
#include "signals_osdep.h"
|
1997-11-25 06:33:21 -08:00
|
|
|
#include "stack.h"
|
1998-08-08 09:52:33 -07:00
|
|
|
#include "sys.h"
|
2001-08-08 01:30:26 -07:00
|
|
|
#ifdef HAS_STACK_OVERFLOW_DETECTION
|
2003-06-02 02:29:46 -07:00
|
|
|
#include <sys/time.h>
|
2001-08-08 01:30:26 -07:00
|
|
|
#include <sys/resource.h>
|
|
|
|
#endif
|
1995-07-10 02:48:27 -07:00
|
|
|
|
2005-07-29 05:11:01 -07:00
|
|
|
#ifndef NSIG
|
|
|
|
#define NSIG 64
|
|
|
|
#endif
|
|
|
|
|
|
|
|
#ifdef _WIN32
|
|
|
|
typedef void (*sighandler)(int sig);
|
|
|
|
extern sighandler caml_win32_signal(int sig, sighandler action);
|
|
|
|
#define signal(sig,act) caml_win32_signal(sig,act)
|
|
|
|
#endif
|
2004-08-12 06:32:11 -07:00
|
|
|
|
2004-01-02 11:23:29 -08:00
|
|
|
extern char * caml_code_area_start, * caml_code_area_end;
|
2002-11-07 03:51:39 -08:00
|
|
|
|
2002-11-25 04:50:20 -08:00
|
|
|
#define In_code_area(pc) \
|
2005-07-29 05:11:01 -07:00
|
|
|
((char *)(pc) >= caml_code_area_start && \
|
|
|
|
(char *)(pc) <= caml_code_area_end)
|
2002-11-25 04:50:20 -08:00
|
|
|
|
2005-09-22 07:21:50 -07:00
|
|
|
volatile intnat caml_pending_signals[NSIG];
|
2004-01-01 08:42:43 -08:00
|
|
|
volatile int caml_force_major_slice = 0;
|
|
|
|
value caml_signal_handlers = 0;
|
2005-07-29 05:11:01 -07:00
|
|
|
|
2005-07-31 05:31:03 -07:00
|
|
|
static void caml_process_pending_signals(void)
|
|
|
|
{
|
|
|
|
int signal_num;
|
2005-09-22 07:21:50 -07:00
|
|
|
intnat signal_state;
|
2005-07-31 05:31:03 -07:00
|
|
|
|
|
|
|
for (signal_num = 0; signal_num < NSIG; signal_num++) {
|
|
|
|
Read_and_clear(signal_state, caml_pending_signals[signal_num]);
|
|
|
|
if (signal_state) caml_execute_signal(signal_num, 0);
|
|
|
|
}
|
|
|
|
}
|
|
|
|
|
2005-09-22 07:21:50 -07:00
|
|
|
static intnat volatile caml_async_signal_mode = 0;
|
2005-07-29 05:11:01 -07:00
|
|
|
|
|
|
|
static void caml_enter_blocking_section_default(void)
|
|
|
|
{
|
|
|
|
Assert (caml_async_signal_mode == 0);
|
|
|
|
caml_async_signal_mode = 1;
|
|
|
|
}
|
|
|
|
|
|
|
|
static void caml_leave_blocking_section_default(void)
|
|
|
|
{
|
|
|
|
Assert (caml_async_signal_mode == 1);
|
|
|
|
caml_async_signal_mode = 0;
|
|
|
|
}
|
|
|
|
|
|
|
|
static int caml_try_leave_blocking_section_default(void)
|
|
|
|
{
|
2005-09-22 07:21:50 -07:00
|
|
|
intnat res;
|
2005-07-29 05:11:01 -07:00
|
|
|
Read_and_clear(res, caml_async_signal_mode);
|
|
|
|
return res;
|
|
|
|
}
|
|
|
|
|
|
|
|
CAMLexport void (*caml_enter_blocking_section_hook)(void) =
|
|
|
|
caml_enter_blocking_section_default;
|
|
|
|
CAMLexport void (*caml_leave_blocking_section_hook)(void) =
|
|
|
|
caml_leave_blocking_section_default;
|
|
|
|
CAMLexport int (*caml_try_leave_blocking_section_hook)(void) =
|
|
|
|
caml_try_leave_blocking_section_default;
|
1995-12-21 03:01:45 -08:00
|
|
|
|
2005-04-17 01:23:51 -07:00
|
|
|
int caml_rev_convert_signal_number(int signo);
|
2001-06-19 01:43:11 -07:00
|
|
|
|
1997-08-29 08:37:22 -07:00
|
|
|
/* Execute a signal handler immediately. */
|
1995-12-21 03:01:45 -08:00
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
void caml_execute_signal(int signal_number, int in_signal_handler)
|
1995-12-21 03:01:45 -08:00
|
|
|
{
|
1999-06-05 05:02:48 -07:00
|
|
|
value res;
|
2005-07-28 09:28:41 -07:00
|
|
|
#ifdef POSIX_SIGNALS
|
1999-06-05 05:02:48 -07:00
|
|
|
sigset_t sigs;
|
|
|
|
/* Block the signal before executing the handler, and record in sigs
|
|
|
|
the original signal mask */
|
|
|
|
sigemptyset(&sigs);
|
|
|
|
sigaddset(&sigs, signal_number);
|
|
|
|
sigprocmask(SIG_BLOCK, &sigs, &sigs);
|
2005-07-28 09:28:41 -07:00
|
|
|
#endif
|
2005-04-17 01:23:51 -07:00
|
|
|
res = caml_callback_exn(
|
|
|
|
Field(caml_signal_handlers, signal_number),
|
|
|
|
Val_int(caml_rev_convert_signal_number(signal_number)));
|
2005-07-28 09:28:41 -07:00
|
|
|
#ifdef POSIX_SIGNALS
|
1999-06-05 05:02:48 -07:00
|
|
|
if (! in_signal_handler) {
|
|
|
|
/* Restore the original signal mask */
|
|
|
|
sigprocmask(SIG_SETMASK, &sigs, NULL);
|
|
|
|
} else if (Is_exception_result(res)) {
|
|
|
|
/* Restore the original signal mask and unblock the signal itself */
|
|
|
|
sigdelset(&sigs, signal_number);
|
|
|
|
sigprocmask(SIG_SETMASK, &sigs, NULL);
|
|
|
|
}
|
2005-07-28 09:28:41 -07:00
|
|
|
#endif
|
2004-01-01 08:42:43 -08:00
|
|
|
if (Is_exception_result(res)) caml_raise(Extract_exception(res));
|
1995-12-21 03:01:45 -08:00
|
|
|
}
|
|
|
|
|
2005-10-12 05:33:47 -07:00
|
|
|
/* Record the delivery of a signal and play with the allocation limit
|
|
|
|
so that the next allocation will trigger a garbage collection. */
|
|
|
|
|
|
|
|
void caml_record_signal(int signal_number)
|
|
|
|
{
|
|
|
|
caml_pending_signals[signal_number] = 1;
|
|
|
|
caml_young_limit = caml_young_end;
|
|
|
|
/* Some ports cache [caml_young_limit] in a register.
|
|
|
|
Use the signal context to modify that register too, but only if
|
|
|
|
we are inside Caml code (not inside C code). */
|
|
|
|
#if defined(CONTEXT_PC) && defined(CONTEXT_YOUNG_LIMIT)
|
|
|
|
if (In_code_area(CONTEXT_PC))
|
|
|
|
CONTEXT_YOUNG_LIMIT = (context_reg) caml_young_limit;
|
|
|
|
#endif
|
|
|
|
}
|
|
|
|
|
1995-12-21 03:01:45 -08:00
|
|
|
/* This routine is the common entry point for garbage collection
|
2001-07-23 08:33:21 -07:00
|
|
|
and signal handling. It can trigger a callback to Caml code.
|
|
|
|
With system threads, this callback can cause a context switch.
|
2004-01-01 08:42:43 -08:00
|
|
|
Hence [caml_garbage_collection] must not be called from regular C code
|
|
|
|
(e.g. the [caml_alloc] function) because the context of the call
|
2001-07-23 08:33:21 -07:00
|
|
|
(e.g. [intern_val]) may not allow context switching.
|
2004-01-01 08:42:43 -08:00
|
|
|
Only generated assembly code can call [caml_garbage_collection],
|
2001-07-23 08:33:21 -07:00
|
|
|
via the caml_call_gc assembly stubs. */
|
1995-12-21 03:01:45 -08:00
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
void caml_garbage_collection(void)
|
1995-12-21 03:01:45 -08:00
|
|
|
{
|
2005-07-29 05:11:01 -07:00
|
|
|
int signal_number;
|
2005-09-22 07:21:50 -07:00
|
|
|
intnat signal_state;
|
1995-12-21 03:01:45 -08:00
|
|
|
|
2005-07-29 05:11:01 -07:00
|
|
|
caml_young_limit = caml_young_start;
|
|
|
|
if (caml_young_ptr < caml_young_start || caml_force_major_slice) {
|
2003-12-31 06:20:40 -08:00
|
|
|
caml_minor_collection();
|
|
|
|
}
|
2005-07-29 05:11:01 -07:00
|
|
|
for (signal_number = 0; signal_number < NSIG; signal_number++) {
|
|
|
|
Read_and_clear(signal_state, caml_pending_signals[signal_number]);
|
|
|
|
if (signal_state) caml_execute_signal(signal_number, 0);
|
|
|
|
}
|
1995-12-21 03:01:45 -08:00
|
|
|
}
|
|
|
|
|
1995-12-22 08:48:37 -08:00
|
|
|
/* Trigger a garbage collection as soon as possible */
|
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
void caml_urge_major_slice (void)
|
1995-12-22 08:48:37 -08:00
|
|
|
{
|
2004-01-01 08:42:43 -08:00
|
|
|
caml_force_major_slice = 1;
|
2003-12-31 06:20:40 -08:00
|
|
|
caml_young_limit = caml_young_end;
|
|
|
|
/* This is only moderately effective on ports that cache [caml_young_limit]
|
|
|
|
in a register, since [caml_modify] is called directly, not through
|
|
|
|
[caml_c_call], so it may take a while before the register is reloaded
|
|
|
|
from [caml_young_limit]. */
|
1995-12-22 08:48:37 -08:00
|
|
|
}
|
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
void caml_enter_blocking_section(void)
|
1995-07-10 02:48:27 -07:00
|
|
|
{
|
2005-07-31 05:31:03 -07:00
|
|
|
int i;
|
2005-09-22 07:21:50 -07:00
|
|
|
intnat pending;
|
1995-12-21 03:01:45 -08:00
|
|
|
|
|
|
|
while (1){
|
2005-07-29 05:11:01 -07:00
|
|
|
/* Process all pending signals now */
|
2005-07-31 05:31:03 -07:00
|
|
|
caml_process_pending_signals();
|
2005-07-29 05:11:01 -07:00
|
|
|
caml_enter_blocking_section_hook ();
|
|
|
|
/* Check again for pending signals. */
|
|
|
|
pending = 0;
|
2005-07-31 05:31:03 -07:00
|
|
|
for (i = 0; i < NSIG; i++) pending |= caml_pending_signals[i];
|
2005-07-29 05:11:01 -07:00
|
|
|
/* If none, done; otherwise, try again */
|
|
|
|
if (!pending) break;
|
|
|
|
caml_leave_blocking_section_hook ();
|
1995-12-21 03:01:45 -08:00
|
|
|
}
|
1995-07-10 02:48:27 -07:00
|
|
|
}
|
|
|
|
|
2005-07-31 05:31:03 -07:00
|
|
|
CAMLexport void caml_leave_blocking_section(void)
|
1995-07-10 02:48:27 -07:00
|
|
|
{
|
2005-07-29 05:11:01 -07:00
|
|
|
caml_leave_blocking_section_hook ();
|
2005-07-31 05:31:03 -07:00
|
|
|
caml_process_pending_signals();
|
1995-12-21 03:01:45 -08:00
|
|
|
}
|
|
|
|
|
2004-08-12 06:32:11 -07:00
|
|
|
DECLARE_SIGNAL_HANDLER(handle_signal)
|
1995-12-21 03:01:45 -08:00
|
|
|
{
|
2005-07-28 09:28:41 -07:00
|
|
|
#if !defined(POSIX_SIGNALS) && !defined(BSD_SIGNALS)
|
|
|
|
signal(sig, handle_signal);
|
|
|
|
#endif
|
2005-07-29 05:11:01 -07:00
|
|
|
if (sig < 0 || sig >= NSIG) return;
|
|
|
|
if (caml_try_leave_blocking_section_hook ()) {
|
2004-01-01 08:42:43 -08:00
|
|
|
caml_execute_signal(sig, 1);
|
2005-07-29 05:11:01 -07:00
|
|
|
caml_enter_blocking_section_hook();
|
1995-12-21 03:01:45 -08:00
|
|
|
} else {
|
2005-10-12 05:33:47 -07:00
|
|
|
caml_record_signal(sig);
|
1995-12-21 03:01:45 -08:00
|
|
|
}
|
1995-07-10 02:48:27 -07:00
|
|
|
}
|
|
|
|
|
1995-12-21 03:01:45 -08:00
|
|
|
#ifndef SIGABRT
|
|
|
|
#define SIGABRT -1
|
|
|
|
#endif
|
|
|
|
#ifndef SIGALRM
|
|
|
|
#define SIGALRM -1
|
|
|
|
#endif
|
|
|
|
#ifndef SIGFPE
|
|
|
|
#define SIGFPE -1
|
|
|
|
#endif
|
|
|
|
#ifndef SIGHUP
|
|
|
|
#define SIGHUP -1
|
|
|
|
#endif
|
|
|
|
#ifndef SIGILL
|
|
|
|
#define SIGILL -1
|
|
|
|
#endif
|
|
|
|
#ifndef SIGINT
|
|
|
|
#define SIGINT -1
|
|
|
|
#endif
|
|
|
|
#ifndef SIGKILL
|
|
|
|
#define SIGKILL -1
|
|
|
|
#endif
|
|
|
|
#ifndef SIGPIPE
|
|
|
|
#define SIGPIPE -1
|
|
|
|
#endif
|
|
|
|
#ifndef SIGQUIT
|
|
|
|
#define SIGQUIT -1
|
|
|
|
#endif
|
|
|
|
#ifndef SIGSEGV
|
|
|
|
#define SIGSEGV -1
|
|
|
|
#endif
|
|
|
|
#ifndef SIGTERM
|
|
|
|
#define SIGTERM -1
|
|
|
|
#endif
|
|
|
|
#ifndef SIGUSR1
|
|
|
|
#define SIGUSR1 -1
|
|
|
|
#endif
|
|
|
|
#ifndef SIGUSR2
|
|
|
|
#define SIGUSR2 -1
|
|
|
|
#endif
|
|
|
|
#ifndef SIGCHLD
|
|
|
|
#define SIGCHLD -1
|
|
|
|
#endif
|
|
|
|
#ifndef SIGCONT
|
|
|
|
#define SIGCONT -1
|
|
|
|
#endif
|
|
|
|
#ifndef SIGSTOP
|
|
|
|
#define SIGSTOP -1
|
|
|
|
#endif
|
|
|
|
#ifndef SIGTSTP
|
|
|
|
#define SIGTSTP -1
|
|
|
|
#endif
|
|
|
|
#ifndef SIGTTIN
|
|
|
|
#define SIGTTIN -1
|
|
|
|
#endif
|
|
|
|
#ifndef SIGTTOU
|
|
|
|
#define SIGTTOU -1
|
|
|
|
#endif
|
|
|
|
#ifndef SIGVTALRM
|
|
|
|
#define SIGVTALRM -1
|
|
|
|
#endif
|
1996-04-18 09:27:16 -07:00
|
|
|
#ifndef SIGPROF
|
|
|
|
#define SIGPROF -1
|
|
|
|
#endif
|
1995-12-21 03:01:45 -08:00
|
|
|
|
1998-08-13 08:58:08 -07:00
|
|
|
static int posix_signals[] = {
|
1995-12-21 03:01:45 -08:00
|
|
|
SIGABRT, SIGALRM, SIGFPE, SIGHUP, SIGILL, SIGINT, SIGKILL, SIGPIPE,
|
|
|
|
SIGQUIT, SIGSEGV, SIGTERM, SIGUSR1, SIGUSR2, SIGCHLD, SIGCONT,
|
1996-04-18 09:27:16 -07:00
|
|
|
SIGSTOP, SIGTSTP, SIGTTIN, SIGTTOU, SIGVTALRM, SIGPROF
|
1995-12-21 03:01:45 -08:00
|
|
|
};
|
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
int caml_convert_signal_number(int signo)
|
1998-08-13 08:58:08 -07:00
|
|
|
{
|
|
|
|
if (signo < 0 && signo >= -(sizeof(posix_signals) / sizeof(int)))
|
|
|
|
return posix_signals[-signo-1];
|
|
|
|
else
|
|
|
|
return signo;
|
|
|
|
}
|
|
|
|
|
2005-04-17 01:23:51 -07:00
|
|
|
int caml_rev_convert_signal_number(int signo)
|
2001-06-19 01:43:11 -07:00
|
|
|
{
|
|
|
|
int i;
|
|
|
|
for (i = 0; i < sizeof(posix_signals) / sizeof(int); i++)
|
|
|
|
if (signo == posix_signals[i]) return -i - 1;
|
|
|
|
return signo;
|
|
|
|
}
|
|
|
|
|
2005-07-28 09:28:41 -07:00
|
|
|
typedef void (*signal_handler)(int signo);
|
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
value caml_install_signal_handler(value signal_number, value action) /* ML */
|
1995-07-10 02:48:27 -07:00
|
|
|
{
|
2001-06-19 01:43:11 -07:00
|
|
|
CAMLparam2 (signal_number, action);
|
1995-12-21 03:01:45 -08:00
|
|
|
int sig;
|
2005-07-28 09:28:41 -07:00
|
|
|
signal_handler oldact;
|
|
|
|
#ifdef POSIX_SIGNALS
|
1998-08-08 09:52:33 -07:00
|
|
|
struct sigaction sigact, oldsigact;
|
2005-07-28 09:28:41 -07:00
|
|
|
#else
|
|
|
|
signal_handler act;
|
|
|
|
#endif
|
2001-06-19 01:43:11 -07:00
|
|
|
CAMLlocal1 (res);
|
1995-12-21 03:01:45 -08:00
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
sig = caml_convert_signal_number(Int_val(signal_number));
|
1995-12-21 03:01:45 -08:00
|
|
|
if (sig < 0 || sig >= NSIG)
|
2004-01-01 08:42:43 -08:00
|
|
|
caml_invalid_argument("Sys.signal: unavailable signal");
|
2005-07-28 09:28:41 -07:00
|
|
|
#ifdef POSIX_SIGNALS
|
1995-12-21 03:01:45 -08:00
|
|
|
switch(action) {
|
|
|
|
case Val_int(0): /* Signal_default */
|
2004-08-12 06:32:11 -07:00
|
|
|
sigact.sa_handler = SIG_DFL;
|
|
|
|
sigact.sa_flags = 0;
|
1995-12-21 03:01:45 -08:00
|
|
|
break;
|
|
|
|
case Val_int(1): /* Signal_ignore */
|
2004-08-12 06:32:11 -07:00
|
|
|
sigact.sa_handler = SIG_IGN;
|
|
|
|
sigact.sa_flags = 0;
|
1995-12-21 03:01:45 -08:00
|
|
|
break;
|
|
|
|
default: /* Signal_handle */
|
2004-08-12 06:32:11 -07:00
|
|
|
SET_SIGACT(sigact, handle_signal);
|
1995-12-21 03:01:45 -08:00
|
|
|
break;
|
|
|
|
}
|
|
|
|
sigemptyset(&sigact.sa_mask);
|
2003-12-29 14:15:02 -08:00
|
|
|
if (sigaction(sig, &sigact, &oldsigact) == -1) caml_sys_error(NO_ARG);
|
2005-07-28 09:28:41 -07:00
|
|
|
oldact = oldsigact.sa_handler;
|
|
|
|
#else
|
|
|
|
switch(action) {
|
|
|
|
case Val_int(0): /* Signal_default */
|
|
|
|
act = SIG_DFL;
|
|
|
|
break;
|
|
|
|
case Val_int(1): /* Signal_ignore */
|
|
|
|
act = SIG_IGN;
|
|
|
|
break;
|
|
|
|
default: /* Signal_handle */
|
|
|
|
act = handle_signal;
|
|
|
|
break;
|
|
|
|
}
|
|
|
|
oldact = signal(sig, act);
|
|
|
|
if (oldact == SIG_ERR) caml_sys_error(NO_ARG);
|
|
|
|
#endif
|
|
|
|
if (oldact == (signal_handler) handle_signal) {
|
2003-12-29 14:15:02 -08:00
|
|
|
res = caml_alloc_small(1, 0); /* Signal_handle */
|
2004-01-01 08:42:43 -08:00
|
|
|
Field(res, 0) = Field(caml_signal_handlers, sig);
|
1998-08-08 09:52:33 -07:00
|
|
|
}
|
2005-07-28 09:28:41 -07:00
|
|
|
else if (oldact == SIG_IGN)
|
1998-08-08 09:52:33 -07:00
|
|
|
res = Val_int(1); /* Signal_ignore */
|
|
|
|
else
|
|
|
|
res = Val_int(0); /* Signal_default */
|
2001-06-19 01:43:11 -07:00
|
|
|
if (Is_block(action)) {
|
2004-01-01 08:42:43 -08:00
|
|
|
if (caml_signal_handlers == 0) {
|
|
|
|
caml_signal_handlers = caml_alloc(NSIG, 0);
|
2004-01-02 11:23:29 -08:00
|
|
|
caml_register_global_root(&caml_signal_handlers);
|
2001-06-19 01:43:11 -07:00
|
|
|
}
|
2004-01-01 08:42:43 -08:00
|
|
|
caml_modify(&Field(caml_signal_handlers, sig), Field(action, 0));
|
2001-06-19 01:43:11 -07:00
|
|
|
}
|
2005-07-31 05:31:03 -07:00
|
|
|
caml_process_pending_signals();
|
2001-06-29 04:37:06 -07:00
|
|
|
CAMLreturn (res);
|
1995-07-10 02:48:27 -07:00
|
|
|
}
|
1995-12-05 05:07:49 -08:00
|
|
|
|
1995-12-21 03:01:45 -08:00
|
|
|
/* Machine- and OS-dependent handling of bound check trap */
|
1995-12-05 05:07:49 -08:00
|
|
|
|
2004-08-12 09:04:07 -07:00
|
|
|
#if defined(TARGET_power) || (defined(TARGET_sparc) && defined(SYS_solaris))
|
2004-08-12 06:32:11 -07:00
|
|
|
DECLARE_SIGNAL_HANDLER(trap_handler)
|
1995-12-05 05:07:49 -08:00
|
|
|
{
|
2004-08-12 06:32:11 -07:00
|
|
|
#if defined(SYS_solaris)
|
1998-11-11 07:35:48 -08:00
|
|
|
if (info->si_code != ILL_ILLTRP) {
|
2004-08-12 06:32:11 -07:00
|
|
|
/* Deactivate our exception handler and return. */
|
|
|
|
struct sigaction act;
|
|
|
|
act.sa_handler = SIG_DFL;
|
|
|
|
act.sa_flags = 0;
|
|
|
|
sigemptyset(&act.sa_mask);
|
|
|
|
sigaction(sig, &act, NULL);
|
|
|
|
return;
|
1995-12-05 05:07:49 -08:00
|
|
|
}
|
1996-01-07 08:58:44 -08:00
|
|
|
#endif
|
2004-08-12 06:32:11 -07:00
|
|
|
#if defined(SYS_rhapsody)
|
1999-11-15 12:04:30 -08:00
|
|
|
/* Unblock SIGTRAP */
|
2004-08-12 06:32:11 -07:00
|
|
|
{ sigset_t mask;
|
|
|
|
sigemptyset(&mask);
|
|
|
|
sigaddset(&mask, SIGTRAP);
|
|
|
|
sigprocmask(SIG_UNBLOCK, &mask, NULL);
|
|
|
|
}
|
1999-11-15 12:04:30 -08:00
|
|
|
#endif
|
2004-08-12 06:32:11 -07:00
|
|
|
caml_exception_pointer = (char *) CONTEXT_EXCEPTION_POINTER;
|
|
|
|
caml_young_ptr = (char *) CONTEXT_YOUNG_PTR;
|
2004-01-02 11:23:29 -08:00
|
|
|
caml_array_bound_error();
|
2003-07-17 08:11:03 -07:00
|
|
|
}
|
|
|
|
#endif
|
|
|
|
|
2001-08-08 01:30:26 -07:00
|
|
|
/* Machine- and OS-dependent handling of stack overflow */
|
|
|
|
|
|
|
|
#ifdef HAS_STACK_OVERFLOW_DETECTION
|
|
|
|
|
|
|
|
static char * system_stack_top;
|
|
|
|
static char sig_alt_stack[SIGSTKSZ];
|
|
|
|
|
2004-08-13 05:17:02 -07:00
|
|
|
DECLARE_SIGNAL_HANDLER(segv_handler)
|
2001-08-08 01:30:26 -07:00
|
|
|
{
|
|
|
|
struct rlimit limit;
|
|
|
|
struct sigaction act;
|
2004-08-13 05:17:02 -07:00
|
|
|
char * fault_addr;
|
2001-08-08 01:30:26 -07:00
|
|
|
|
|
|
|
/* Sanity checks:
|
|
|
|
- faulting address is word-aligned
|
2004-08-13 05:17:02 -07:00
|
|
|
- faulting address is within the stack
|
|
|
|
- we are in Caml code */
|
|
|
|
fault_addr = CONTEXT_FAULTING_ADDRESS;
|
2005-09-22 07:21:50 -07:00
|
|
|
if (((uintnat) fault_addr & (sizeof(intnat) - 1)) == 0
|
2004-08-13 05:17:02 -07:00
|
|
|
&& getrlimit(RLIMIT_STACK, &limit) == 0
|
|
|
|
&& fault_addr < system_stack_top
|
|
|
|
&& fault_addr >= system_stack_top - limit.rlim_cur - 0x2000
|
|
|
|
#ifdef CONTEXT_PC
|
|
|
|
&& In_code_area(CONTEXT_PC)
|
|
|
|
#endif
|
|
|
|
) {
|
|
|
|
/* Turn this into a Stack_overflow exception */
|
|
|
|
#if defined(CONTEXT_YOUNG_PTR) && defined(CONTEXT_EXCEPTION_POINTER)
|
|
|
|
caml_exception_pointer = (char *) CONTEXT_EXCEPTION_POINTER;
|
|
|
|
caml_young_ptr = (char *) CONTEXT_YOUNG_PTR;
|
2004-08-13 04:45:44 -07:00
|
|
|
#endif
|
2004-08-13 05:17:02 -07:00
|
|
|
caml_raise_stack_overflow();
|
2004-08-13 04:45:44 -07:00
|
|
|
}
|
2004-08-13 05:17:02 -07:00
|
|
|
/* Otherwise, deactivate our exception handler and return,
|
|
|
|
causing fatal signal to be generated at point of error. */
|
|
|
|
act.sa_handler = SIG_DFL;
|
|
|
|
act.sa_flags = 0;
|
|
|
|
sigemptyset(&act.sa_mask);
|
|
|
|
sigaction(SIGSEGV, &act, NULL);
|
2001-08-08 01:30:26 -07:00
|
|
|
}
|
|
|
|
|
|
|
|
#endif
|
|
|
|
|
1995-12-21 03:01:45 -08:00
|
|
|
/* Initialization of signal stuff */
|
1995-12-05 05:07:49 -08:00
|
|
|
|
2004-01-01 08:42:43 -08:00
|
|
|
void caml_init_signals(void)
|
1995-12-05 05:07:49 -08:00
|
|
|
{
|
2001-08-08 01:30:26 -07:00
|
|
|
/* Bound-check trap handling */
|
2004-08-12 09:04:07 -07:00
|
|
|
#if defined(TARGET_sparc) && defined(SYS_solaris)
|
2004-08-12 06:32:11 -07:00
|
|
|
{ struct sigaction act;
|
2001-08-08 01:30:26 -07:00
|
|
|
sigemptyset(&act.sa_mask);
|
2004-08-12 06:32:11 -07:00
|
|
|
SET_SIGACT(act, trap_handler);
|
|
|
|
act.sa_flags |= SA_NODEFER;
|
2001-08-08 01:30:26 -07:00
|
|
|
sigaction(SIGILL, &act, NULL);
|
|
|
|
}
|
1995-12-05 05:07:49 -08:00
|
|
|
#endif
|
2004-08-12 06:32:11 -07:00
|
|
|
|
1996-01-07 08:58:44 -08:00
|
|
|
#if defined(TARGET_power)
|
2004-08-12 06:32:11 -07:00
|
|
|
{ struct sigaction act;
|
2001-08-08 01:30:26 -07:00
|
|
|
sigemptyset(&act.sa_mask);
|
2004-08-12 06:32:11 -07:00
|
|
|
SET_SIGACT(act, trap_handler);
|
|
|
|
#if !defined(SYS_rhapsody)
|
|
|
|
act.sa_flags |= SA_NODEFER;
|
1999-11-15 12:04:30 -08:00
|
|
|
#endif
|
2001-08-08 01:30:26 -07:00
|
|
|
sigaction(SIGTRAP, &act, NULL);
|
|
|
|
}
|
|
|
|
#endif
|
2004-08-12 06:32:11 -07:00
|
|
|
|
2001-08-08 01:30:26 -07:00
|
|
|
/* Stack overflow handling */
|
|
|
|
#ifdef HAS_STACK_OVERFLOW_DETECTION
|
|
|
|
{
|
|
|
|
struct sigaltstack stk;
|
|
|
|
struct sigaction act;
|
|
|
|
stk.ss_sp = sig_alt_stack;
|
|
|
|
stk.ss_size = SIGSTKSZ;
|
|
|
|
stk.ss_flags = 0;
|
2004-08-12 06:32:11 -07:00
|
|
|
SET_SIGACT(act, segv_handler);
|
|
|
|
act.sa_flags |= SA_ONSTACK | SA_NODEFER;
|
2001-08-08 01:30:26 -07:00
|
|
|
sigemptyset(&act.sa_mask);
|
|
|
|
system_stack_top = (char *) &act;
|
|
|
|
if (sigaltstack(&stk, NULL) == 0) { sigaction(SIGSEGV, &act, NULL); }
|
|
|
|
}
|
1996-01-07 08:58:44 -08:00
|
|
|
#endif
|
1995-12-05 05:07:49 -08:00
|
|
|
}
|