]> rtime.felk.cvut.cz Git - l4.git/blob - l4/pkg/ocaml/contrib/byterun/signals_byt.c
update
[l4.git] / l4 / pkg / ocaml / contrib / byterun / signals_byt.c
1 /***********************************************************************/
2 /*                                                                     */
3 /*                           Objective Caml                            */
4 /*                                                                     */
5 /*         Xavier Leroy and Damien Doligez, 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_byt.c 7904 2007-02-23 09:29:45Z xleroy $ */
15
16 /* Signal handling, code specific to the bytecode interpreter */
17
18 #include <signal.h>
19 #include "config.h"
20 #include "memory.h"
21 #include "osdeps.h"
22 #include "signals.h"
23 #include "signals_machdep.h"
24
25 #ifndef NSIG
26 #define NSIG 64
27 #endif
28
29 #ifdef _WIN32
30 typedef void (*sighandler)(int sig);
31 extern sighandler caml_win32_signal(int sig, sighandler action);
32 #define signal(sig,act) caml_win32_signal(sig,act)
33 #endif
34
35 CAMLexport int volatile caml_something_to_do = 0;
36 CAMLexport void (* volatile caml_async_action_hook)(void) = NULL;
37
38 void caml_process_event(void)
39 {
40   void (*async_action)(void);
41
42   if (caml_force_major_slice) caml_minor_collection ();
43                              /* FIXME should be [caml_check_urgent_gc] */
44   caml_process_pending_signals();
45   async_action = caml_async_action_hook;
46   if (async_action != NULL) {
47     caml_async_action_hook = NULL;
48     (*async_action)();
49   }
50 }
51
52 static void handle_signal(int signal_number)
53 {
54 #if !defined(POSIX_SIGNALS) && !defined(BSD_SIGNALS)
55   signal(signal_number, handle_signal);
56 #endif
57   if (signal_number < 0 || signal_number >= NSIG) return;
58   if (caml_try_leave_blocking_section_hook()) {
59     caml_execute_signal(signal_number, 1);
60     caml_enter_blocking_section_hook();
61   }else{
62     caml_record_signal(signal_number);
63  }
64 }
65
66 int caml_set_signal_action(int signo, int action)
67 {
68   void (*act)(int signo), (*oldact)(int signo);
69 #ifdef POSIX_SIGNALS
70   struct sigaction sigact, oldsigact;
71 #endif
72
73   switch (action) {
74   case 0:  act = SIG_DFL; break;
75   case 1:  act = SIG_IGN; break;
76   default: act = handle_signal; break;
77   }
78
79 #ifdef POSIX_SIGNALS
80   sigact.sa_handler = act;
81   sigemptyset(&sigact.sa_mask);
82   sigact.sa_flags = 0;
83   if (sigaction(signo, &sigact, &oldsigact) == -1) return -1;
84   oldact = oldsigact.sa_handler;
85 #else
86   oldact = signal(signo, act);
87   if (oldact == SIG_ERR) return -1;
88 #endif
89   if (oldact == handle_signal)
90     return 2;
91   else if (oldact == SIG_IGN)
92     return 1;
93   else
94     return 0;
95 }