]> rtime.felk.cvut.cz Git - l4.git/blob - l4/pkg/ocaml/ocaml/contrib/asmrun/signals_osdep.h
Update
[l4.git] / l4 / pkg / ocaml / ocaml / contrib / asmrun / signals_osdep.h
1 /***********************************************************************/
2 /*                                                                     */
3 /*                           Objective Caml                            */
4 /*                                                                     */
5 /*            Xavier Leroy, projet Cristal, INRIA Rocquencourt         */
6 /*                                                                     */
7 /*  Copyright 2004 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_osdep.h 9194 2009-03-28 15:18:31Z xleroy $ */
15
16 /* Processor- and OS-dependent signal interface */
17
18 /****************** Alpha, all OS */
19
20 #if defined(TARGET_alpha)
21
22   #define DECLARE_SIGNAL_HANDLER(name) \
23     static void name(int sig, int code, struct sigcontext * context)
24
25   #define SET_SIGACT(sigact,name) \
26      sigact.sa_handler = (void (*)(int)) (name); \
27      sigact.sa_flags = 0
28
29   typedef long context_reg;
30   #define CONTEXT_PC (context->sc_pc)
31   #define CONTEXT_EXCEPTION_POINTER (context->sc_regs[15])
32   #define CONTEXT_YOUNG_LIMIT (context->sc_regs[13])
33   #define CONTEXT_YOUNG_PTR (context->sc_regs[14])
34
35 /****************** AMD64, Linux */
36
37 #elif defined(TARGET_amd64) && defined (SYS_linux)
38
39   #define DECLARE_SIGNAL_HANDLER(name) \
40     static void name(int sig, siginfo_t * info, ucontext_t * context)
41
42   #define SET_SIGACT(sigact,name) \
43      sigact.sa_sigaction = (void (*)(int,siginfo_t *,void *)) (name); \
44      sigact.sa_flags = SA_SIGINFO
45
46   typedef greg_t context_reg;
47   #define CONTEXT_PC (context->uc_mcontext.gregs[REG_RIP])
48   #define CONTEXT_EXCEPTION_POINTER (context->uc_mcontext.gregs[REG_R14])
49   #define CONTEXT_YOUNG_PTR (context->uc_mcontext.gregs[REG_R15])
50   #define CONTEXT_FAULTING_ADDRESS ((char *) context->uc_mcontext.gregs[REG_CR2])
51
52 /****************** AMD64, MacOSX */
53
54 #elif defined(TARGET_amd64) && defined (SYS_macosx)
55
56   #define DECLARE_SIGNAL_HANDLER(name) \
57     static void name(int sig, siginfo_t * info, void * context)
58
59   #define SET_SIGACT(sigact,name) \
60      sigact.sa_sigaction = (name); \
61      sigact.sa_flags = SA_SIGINFO | SA_64REGSET
62
63   #include <sys/ucontext.h>
64   #include <AvailabilityMacros.h>
65
66 #if !defined(MAC_OS_X_VERSION_10_5) || MAC_OS_X_VERSION_MIN_REQUIRED < MAC_OS_X_VERSION_10_5
67     #define CONTEXT_REG(r) r
68   #else
69     #define CONTEXT_REG(r) __##r
70   #endif
71
72   #define CONTEXT_STATE (((ucontext_t *)context)->uc_mcontext->CONTEXT_REG(ss))
73   #define CONTEXT_PC (CONTEXT_STATE.CONTEXT_REG(rip))
74   #define CONTEXT_EXCEPTION_POINTER (CONTEXT_STATE.CONTEXT_REG(r14))
75   #define CONTEXT_YOUNG_PTR (CONTEXT_STATE.CONTEXT_REG(r15))
76   #define CONTEXT_SP (CONTEXT_STATE.CONTEXT_REG(rsp))
77   #define CONTEXT_FAULTING_ADDRESS ((char *) info->si_addr)
78
79 /****************** AMD64, Solaris x86 */
80
81 #elif defined(TARGET_amd64) && defined (SYS_solaris)
82
83   #include <ucontext.h>
84
85   #define DECLARE_SIGNAL_HANDLER(name) \
86     static void name(int sig, siginfo_t * info, ucontext_t * context)
87
88   #define SET_SIGACT(sigact,name) \
89     sigact.sa_sigaction = (void (*)(int,siginfo_t *,void *)) (name); \
90     sigact.sa_flags = SA_SIGINFO
91
92   typedef greg_t context_reg;
93   #define CONTEXT_PC (context->uc_mcontext.gregs[REG_RIP])
94   #define CONTEXT_EXCEPTION_POINTER (context->uc_mcontext.gregs[REG_R14])
95   #define CONTEXT_YOUNG_PTR (context->uc_mcontext.gregs[REG_R15])
96   #define CONTEXT_FAULTING_ADDRESS ((char *) info->si_addr)
97
98 /****************** I386, Linux */
99
100 #elif defined(TARGET_i386) && defined(SYS_linux_elf)
101
102   #define DECLARE_SIGNAL_HANDLER(name) \
103     static void name(int sig, struct sigcontext context)
104
105   #define SET_SIGACT(sigact,name) \
106      sigact.sa_handler = (void (*)(int)) (name); \
107      sigact.sa_flags = 0
108
109   #define CONTEXT_FAULTING_ADDRESS ((char *) context.cr2)
110
111 /****************** I386, BSD */
112
113 #elif defined(TARGET_i386) && defined(SYS_bsd)
114
115   #define DECLARE_SIGNAL_HANDLER(name) \
116     static void name(int sig, siginfo_t * info, void * context)
117
118   #define SET_SIGACT(sigact,name) \
119      sigact.sa_sigaction = (name); \
120      sigact.sa_flags = SA_SIGINFO
121
122   #define CONTEXT_FAULTING_ADDRESS ((char *) info->si_addr)
123
124 /****************** I386, MacOS X */
125
126 #elif defined(TARGET_i386) && defined(SYS_macosx)
127
128   #define DECLARE_SIGNAL_HANDLER(name) \
129     static void name(int sig, siginfo_t * info, void * context)
130
131   #define SET_SIGACT(sigact,name) \
132      sigact.sa_sigaction = (name); \
133      sigact.sa_flags = SA_SIGINFO
134
135   #include <sys/ucontext.h>
136   #include <AvailabilityMacros.h>
137
138 #if !defined(MAC_OS_X_VERSION_10_5) || MAC_OS_X_VERSION_MIN_REQUIRED < MAC_OS_X_VERSION_10_5
139     #define CONTEXT_REG(r) r
140   #else
141     #define CONTEXT_REG(r) __##r
142   #endif
143
144   #define CONTEXT_STATE (((ucontext_t *)context)->uc_mcontext->CONTEXT_REG(ss))
145   #define CONTEXT_PC (CONTEXT_STATE.CONTEXT_REG(eip))
146   #define CONTEXT_FAULTING_ADDRESS ((char *) info->si_addr)
147
148 /****************** I386, Solaris x86 */
149
150 #elif defined(TARGET_i386) && defined(SYS_solaris)
151
152   #define DECLARE_SIGNAL_HANDLER(name) \
153     static void name(int sig, siginfo_t * info, void * context)
154
155   #define SET_SIGACT(sigact,name) \
156     sigact.sa_sigaction = (name); \
157     sigact.sa_flags = SA_SIGINFO
158
159   #define CONTEXT_FAULTING_ADDRESS ((char *) info->si_addr)
160
161 /****************** MIPS, all OS */
162
163 #elif defined(TARGET_mips)
164
165   #define DECLARE_SIGNAL_HANDLER(name) \
166     static void name(int sig, int code, struct sigcontext * context)
167
168   #define SET_SIGACT(sigact,name) \
169      sigact.sa_handler = (void (*)(int)) (name); \
170      sigact.sa_flags = 0
171
172   typedef int context_reg;
173   #define CONTEXT_PC (context->sc_pc)
174   #define CONTEXT_EXCEPTION_POINTER (context->sc_regs[30])
175   #define CONTEXT_YOUNG_LIMIT (context->sc_regs[22])
176   #define CONTEXT_YOUNG_PTR (context->sc_regs[23])
177
178 /****************** PowerPC, MacOS X */
179
180 #elif defined(TARGET_power) && defined(SYS_rhapsody)
181
182   #define DECLARE_SIGNAL_HANDLER(name) \
183      static void name(int sig, siginfo_t * info, void * context)
184
185   #include <sys/ucontext.h>
186   #include <AvailabilityMacros.h>
187
188   #ifdef __LP64__
189     #define SET_SIGACT(sigact,name) \
190        sigact.sa_sigaction = (name); \
191        sigact.sa_flags = SA_SIGINFO | SA_64REGSET
192
193     typedef unsigned long long context_reg;
194
195     #define CONTEXT_MCONTEXT (((ucontext64_t *)context)->uc_mcontext64)
196   #else
197     #define SET_SIGACT(sigact,name) \
198        sigact.sa_sigaction = (name); \
199        sigact.sa_flags = SA_SIGINFO
200
201     typedef unsigned long context_reg;
202
203     #define CONTEXT_MCONTEXT (((ucontext_t *)context)->uc_mcontext)
204   #endif
205
206 #if !defined(MAC_OS_X_VERSION_10_5) || MAC_OS_X_VERSION_MIN_REQUIRED < MAC_OS_X_VERSION_10_5
207     #define CONTEXT_REG(r) r
208   #else
209     #define CONTEXT_REG(r) __##r
210   #endif
211
212   #define CONTEXT_STATE (CONTEXT_MCONTEXT->CONTEXT_REG(ss))
213   #define CONTEXT_PC (CONTEXT_STATE.CONTEXT_REG(srr0))
214   #define CONTEXT_EXCEPTION_POINTER (CONTEXT_STATE.CONTEXT_REG(r29))
215   #define CONTEXT_YOUNG_LIMIT (CONTEXT_STATE.CONTEXT_REG(r30))
216   #define CONTEXT_YOUNG_PTR (CONTEXT_STATE.CONTEXT_REG(r31))
217   #define CONTEXT_SP (CONTEXT_STATE.CONTEXT_REG(r1))
218   #define CONTEXT_FAULTING_ADDRESS ((char *) info->si_addr)
219
220 /****************** PowerPC, ELF (Linux) */
221
222 #elif defined(TARGET_power) && defined(SYS_elf)
223
224   #define DECLARE_SIGNAL_HANDLER(name) \
225     static void name(int sig, struct sigcontext * context)
226
227   #define SET_SIGACT(sigact,name) \
228      sigact.sa_handler = (void (*)(int)) (name); \
229      sigact.sa_flags = 0
230
231   typedef unsigned long context_reg;
232   #define CONTEXT_PC (context->regs->nip)
233   #define CONTEXT_EXCEPTION_POINTER (context->regs->gpr[29])
234   #define CONTEXT_YOUNG_LIMIT (context->regs->gpr[30])
235   #define CONTEXT_YOUNG_PTR (context->regs->gpr[31])
236
237 /****************** PowerPC, BSD */
238
239 #elif defined(TARGET_power) && defined(SYS_bsd)
240
241   #define DECLARE_SIGNAL_HANDLER(name) \
242     static void name(int sig, int code, struct sigcontext * context)
243
244   #define SET_SIGACT(sigact,name) \
245      sigact.sa_handler = (void (*)(int)) (name); \
246      sigact.sa_flags = 0
247
248   typedef unsigned long context_reg;
249   #define CONTEXT_EXCEPTION_POINTER (context->sc_frame.fixreg[29])
250   #define CONTEXT_YOUNG_LIMIT (context->sc_frame.fixreg[30])
251   #define CONTEXT_YOUNG_PTR (context->sc_frame.fixreg[31])
252
253 /****************** SPARC, Solaris */
254
255 #elif defined(TARGET_sparc) && defined(SYS_solaris)
256
257   #include <ucontext.h>
258
259   #define DECLARE_SIGNAL_HANDLER(name) \
260     static void name(int sig, siginfo_t * info, ucontext_t * context)
261
262   #define SET_SIGACT(sigact,name) \
263      sigact.sa_sigaction = (void (*)(int,siginfo_t *,void *)) (name); \
264      sigact.sa_flags = SA_SIGINFO
265
266   typedef long context_reg;
267   #define CONTEXT_PC (context->uc_mcontext.gregs[REG_PC])
268     /* Local register number N is saved on the stack N words
269        after the stack pointer */
270   #define SPARC_L_REG(n) ((long *)(context->uc_mcontext.gregs[REG_SP]))[n]
271   #define CONTEXT_EXCEPTION_POINTER (SPARC_L_REG(5))
272   #define CONTEXT_YOUNG_LIMIT (SPARC_L_REG(7))
273   #define CONTEXT_YOUNG_PTR (SPARC_L_REG(6))
274
275 /******************** Default */
276
277 #else
278
279   #define DECLARE_SIGNAL_HANDLER(name) \
280     static void name(int sig)
281
282   #define SET_SIGACT(sigact,name) \
283      sigact.sa_handler = (name); \
284      sigact.sa_flags = 0
285
286 #endif