]> rtime.felk.cvut.cz Git - l4.git/blob - l4/pkg/ocaml/ocaml/contrib/asmrun/signals_asm.c
Update
[l4.git] / l4 / pkg / ocaml / ocaml / contrib / asmrun / signals_asm.c
1 /***********************************************************************/
2 /*                                                                     */
3 /*                           Objective Caml                            */
4 /*                                                                     */
5 /*            Xavier Leroy, projet Gallium, INRIA Rocquencourt         */
6 /*                                                                     */
7 /*  Copyright 2007 Institut National de Recherche en Informatique et   */
8 /*  en Automatique.  All rights reserved.  This file is distributed    */
9 /*  under the terms of the GNU Library General Public License, with    */
10 /*  the special exception on linking described in file ../LICENSE.     */
11 /*                                                                     */
12 /***********************************************************************/
13
14 /* $Id: signals_asm.c 8768 2008-01-11 16:13:18Z doligez $ */
15
16 /* Signal handling, code specific to the native-code compiler */
17
18 #if defined(TARGET_amd64) && defined (SYS_linux)
19 #define _GNU_SOURCE
20 #endif
21 #include <signal.h>
22 #include <stdio.h>
23 #include "fail.h"
24 #include "memory.h"
25 #include "osdeps.h"
26 #include "signals.h"
27 #include "signals_machdep.h"
28 #include "signals_osdep.h"
29 #include "stack.h"
30
31 #ifdef HAS_STACK_OVERFLOW_DETECTION
32 #include <sys/time.h>
33 #include <sys/resource.h>
34 #endif
35
36 #ifndef NSIG
37 #define NSIG 64
38 #endif
39
40 typedef void (*signal_handler)(int signo);
41
42 #ifdef _WIN32
43 extern signal_handler caml_win32_signal(int sig, signal_handler action);
44 #define signal(sig,act) caml_win32_signal(sig,act)
45 extern void caml_win32_overflow_detection();
46 #endif
47
48 extern char * caml_code_area_start, * caml_code_area_end;
49
50 #define Is_in_code_area(pc) \
51  ( ((char *)(pc) >= caml_code_area_start && \
52     (char *)(pc) <= caml_code_area_end)     \
53    || (Classify_addr(pc) & In_code_area) )
54
55 /* This routine is the common entry point for garbage collection
56    and signal handling.  It can trigger a callback to Caml code.
57    With system threads, this callback can cause a context switch.
58    Hence [caml_garbage_collection] must not be called from regular C code
59    (e.g. the [caml_alloc] function) because the context of the call
60    (e.g. [intern_val]) may not allow context switching.
61    Only generated assembly code can call [caml_garbage_collection],
62    via the caml_call_gc assembly stubs.  */
63
64 void caml_garbage_collection(void)
65 {
66   caml_young_limit = caml_young_start;
67   if (caml_young_ptr < caml_young_start || caml_force_major_slice) {
68     caml_minor_collection();
69   }
70   caml_process_pending_signals();
71 }
72
73 DECLARE_SIGNAL_HANDLER(handle_signal)
74 {
75 #if !defined(POSIX_SIGNALS) && !defined(BSD_SIGNALS)
76   signal(sig, handle_signal);
77 #endif
78   if (sig < 0 || sig >= NSIG) return;
79   if (caml_try_leave_blocking_section_hook ()) {
80     caml_execute_signal(sig, 1);
81     caml_enter_blocking_section_hook();
82   } else {
83     caml_record_signal(sig);
84   /* Some ports cache [caml_young_limit] in a register.
85      Use the signal context to modify that register too, but only if
86      we are inside Caml code (not inside C code). */
87 #if defined(CONTEXT_PC) && defined(CONTEXT_YOUNG_LIMIT)
88     if (Is_in_code_area(CONTEXT_PC))
89       CONTEXT_YOUNG_LIMIT = (context_reg) caml_young_limit;
90 #endif
91   }
92 }
93
94 int caml_set_signal_action(int signo, int action)
95 {
96   signal_handler oldact;
97 #ifdef POSIX_SIGNALS
98   struct sigaction sigact, oldsigact;
99 #else
100   signal_handler act;
101 #endif
102
103 #ifdef POSIX_SIGNALS
104   switch(action) {
105   case 0:
106     sigact.sa_handler = SIG_DFL;
107     sigact.sa_flags = 0;
108     break;
109   case 1:
110     sigact.sa_handler = SIG_IGN;
111     sigact.sa_flags = 0;
112     break;
113   default:
114     SET_SIGACT(sigact, handle_signal);
115     break;
116   }
117   sigemptyset(&sigact.sa_mask);
118   if (sigaction(signo, &sigact, &oldsigact) == -1) return -1;
119   oldact = oldsigact.sa_handler;
120 #else
121   switch(action) {
122   case 0:  act = SIG_DFL; break;
123   case 1:  act = SIG_IGN; break;
124   default: act = handle_signal; break;
125   }
126   oldact = signal(signo, act);
127   if (oldact == SIG_ERR) return -1;
128 #endif
129   if (oldact == (signal_handler) handle_signal)
130     return 2;
131   else if (oldact == SIG_IGN)
132     return 1;
133   else
134     return 0;
135 }
136
137 /* Machine- and OS-dependent handling of bound check trap */
138
139 #if defined(TARGET_power) || (defined(TARGET_sparc) && defined(SYS_solaris))
140 DECLARE_SIGNAL_HANDLER(trap_handler)
141 {
142 #if defined(SYS_solaris)
143   if (info->si_code != ILL_ILLTRP) {
144     /* Deactivate our exception handler and return. */
145     struct sigaction act;
146     act.sa_handler = SIG_DFL;
147     act.sa_flags = 0;
148     sigemptyset(&act.sa_mask);
149     sigaction(sig, &act, NULL);
150     return;
151   }
152 #endif
153 #if defined(SYS_rhapsody)
154   /* Unblock SIGTRAP */
155   { sigset_t mask;
156     sigemptyset(&mask);
157     sigaddset(&mask, SIGTRAP);
158     sigprocmask(SIG_UNBLOCK, &mask, NULL);
159   }
160 #endif
161   caml_exception_pointer = (char *) CONTEXT_EXCEPTION_POINTER;
162   caml_young_ptr = (char *) CONTEXT_YOUNG_PTR;
163 #if defined(SYS_rhapsody)
164   caml_bottom_of_stack = (char *) CONTEXT_SP;
165   caml_last_return_address = (uintnat) CONTEXT_PC;
166 #endif
167   caml_array_bound_error();
168 }
169 #endif
170
171 /* Machine- and OS-dependent handling of stack overflow */
172
173 #ifdef HAS_STACK_OVERFLOW_DETECTION
174
175 static char * system_stack_top;
176 static char sig_alt_stack[SIGSTKSZ];
177
178 DECLARE_SIGNAL_HANDLER(segv_handler)
179 {
180   struct rlimit limit;
181   struct sigaction act;
182   char * fault_addr;
183
184   /* Sanity checks:
185      - faulting address is word-aligned
186      - faulting address is within the stack
187      - we are in Caml code */
188   fault_addr = CONTEXT_FAULTING_ADDRESS;
189   if (((uintnat) fault_addr & (sizeof(intnat) - 1)) == 0
190       && getrlimit(RLIMIT_STACK, &limit) == 0
191       && fault_addr < system_stack_top
192       && fault_addr >= system_stack_top - limit.rlim_cur - 0x2000
193 #ifdef CONTEXT_PC
194       && Is_in_code_area(CONTEXT_PC)
195 #endif
196       ) {
197     /* Turn this into a Stack_overflow exception */
198 #if defined(CONTEXT_YOUNG_PTR) && defined(CONTEXT_EXCEPTION_POINTER)
199     caml_exception_pointer = (char *) CONTEXT_EXCEPTION_POINTER;
200     caml_young_ptr = (char *) CONTEXT_YOUNG_PTR;
201 #endif
202     caml_raise_stack_overflow();
203   }
204   /* Otherwise, deactivate our exception handler and return,
205      causing fatal signal to be generated at point of error. */
206   act.sa_handler = SIG_DFL;
207   act.sa_flags = 0;
208   sigemptyset(&act.sa_mask);
209   sigaction(SIGSEGV, &act, NULL);
210 }
211
212 #endif
213
214 /* Initialization of signal stuff */
215
216 void caml_init_signals(void)
217 {
218   /* Bound-check trap handling */
219 #if defined(TARGET_sparc) && defined(SYS_solaris)
220   { struct sigaction act;
221     sigemptyset(&act.sa_mask);
222     SET_SIGACT(act, trap_handler);
223     act.sa_flags |= SA_NODEFER;
224     sigaction(SIGILL, &act, NULL);
225   }
226 #endif
227
228 #if defined(TARGET_power)
229   { struct sigaction act;
230     sigemptyset(&act.sa_mask);
231     SET_SIGACT(act, trap_handler);
232 #if !defined(SYS_rhapsody)
233     act.sa_flags |= SA_NODEFER;
234 #endif
235     sigaction(SIGTRAP, &act, NULL);
236   }
237 #endif
238
239   /* Stack overflow handling */
240 #ifdef HAS_STACK_OVERFLOW_DETECTION
241   {
242     stack_t stk;
243     struct sigaction act;
244     stk.ss_sp = sig_alt_stack;
245     stk.ss_size = SIGSTKSZ;
246     stk.ss_flags = 0;
247     SET_SIGACT(act, segv_handler);
248     act.sa_flags |= SA_ONSTACK | SA_NODEFER;
249     sigemptyset(&act.sa_mask);
250     system_stack_top = (char *) &act;
251     if (sigaltstack(&stk, NULL) == 0) { sigaction(SIGSEGV, &act, NULL); }
252   }
253 #endif
254 #if defined(_WIN32) && !defined(_WIN64)
255   caml_win32_overflow_detection();
256 #endif
257 }