1 /*
2  * %CopyrightBegin%
3  *
4  * Copyright Ericsson AB 2001-2020. All Rights Reserved.
5  *
6  * Licensed under the Apache License, Version 2.0 (the "License");
7  * you may not use this file except in compliance with the License.
8  * You may obtain a copy of the License at
9  *
10  *     http://www.apache.org/licenses/LICENSE-2.0
11  *
12  * Unless required by applicable law or agreed to in writing, software
13  * distributed under the License is distributed on an "AS IS" BASIS,
14  * WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
15  * See the License for the specific language governing permissions and
16  * limitations under the License.
17  *
18  * %CopyrightEnd%
19  */
20 
21 /*
22  * Erlang code compiled to x86 native code uses RSP as its stack pointer. This
23  * improves performance in several ways:
24  *
25  * - It permits the use of the x86 call and ret instructions, which
26  *   reduces code volume and improves branch prediction.
27  * - It avoids stealing a gp register to act as a stack pointer.
28  *
29  * Unix signal handlers are by default delivered onto the current stack, i.e.
30  * RSP. This is a problem since our native-code stacks are small and may not
31  * have room for the Unix signal handler.
32  *
33  * There is a way to redirect signal handlers to an "alternate" signal stack by
34  * using the SA_ONSTACK flag with the sigaction() library call. Unfortunately,
35  * this has to be specified explicitly for each signal, and it is difficult to
36  * enforce given the presence of libraries.
37  *
38  * Our solution is to override the C library's signal handler setup procedure
39  * with our own which enforces the SA_ONSTACK flag.
40  */
41 
42 #ifdef HAVE_CONFIG_H
43 #include "config.h"
44 #endif
45 
46 #include <signal.h>
47 #include <stdio.h>
48 #include <stdlib.h>
49 
50 #include "sys.h"
51 #include "erl_alloc.h"
52 #include "erl_vm.h"
53 
54 #if (defined(BEAMASM) && defined(NATIVE_ERLANG_STACK))
55 
56 #if defined(__GLIBC__) && __GLIBC__ == 2 && (__GLIBC_MINOR__ >= 3)
57 /*
58  * __libc_sigaction() is the core routine.
59  * Without libpthread, sigaction() and __sigaction() are both aliases
60  * for __libc_sigaction().
61  * libpthread redefines __sigaction() as a non-trivial wrapper around
62  * __libc_sigaction(), and makes sigaction() an alias for __sigaction().
63  * glibc has internal calls to both sigaction() and __sigaction().
64  *
65  * Overriding __libc_sigaction() would be ideal, but doing so breaks
66  * libpthread (threads hang).
67  *
68  * Overriding __sigaction(), using dlsym RTLD_NEXT to find glibc's
69  * version of __sigaction(), works with glibc-2.2.4 and 2.2.5.
70  * Unfortunately, this solution doesn't work with earlier versions,
71  * including glibc-2.2.2 and glibc-2.1.92 (2.2 despite its name):
72  * 2.2.2 SIGSEGVs in dlsym RTLD_NEXT (known glibc bug), and 2.1.92
73  * SIGSEGVs inexplicably in two test cases in the HiPE test suite.
74  *
75  * Instead we only override sigaction() and call __sigaction()
76  * directly. This should work for HiPE/x86 as long as only the Posix
77  * signal interface is used, i.e. there are no calls to simulated
78  * old BSD or SysV interfaces.
79  * glibc's internal calls to __sigaction() appear to be mostly safe.
80  * sys_init_signal_stack() fixes some unsafe ones, e.g. the SIGPROF handler.
81  */
82 #ifndef __USE_GNU
83 #    define __USE_GNU /* to un-hide RTLD_NEXT */
84 #endif
85 #define NEXT_SIGACTION "__sigaction"
86 #define LIBC_SIGACTION __sigaction
87 #define OVERRIDE_SIGACTION
88 #endif /* glibc >= 2.3 */
89 
90 /* Is there no standard identifier for Darwin/MacOSX ? */
91 #if defined(__APPLE__) && defined(__MACH__) && !defined(__DARWIN__)
92 #define __DARWIN__ 1
93 #endif
94 
95 #if defined(__DARWIN__)
96 /*
97  * Assumes Mac OS X >= 10.3 (dlsym operations not available in 10.2 and
98  * earlier).
99  *
100  * The code below assumes that is is part of the main image (earlier
101  * in the load order than libSystem and certainly before any dylib
102  * that might use sigaction) -- a standard RTLD_NEXT caveat.
103  *
104  * _sigaction lives in /usr/lib/libSystem.B.dylib and can be found
105  * with the standard dlsym(RTLD_NEXT) call. The proviso on Mac OS X
106  * being that the symbol for dlsym doesn't include a leading '_'.
107  *
108  * The other _sigaction, _sigaction_no_bind I don't understand the purpose
109  * of and don't modify.
110  */
111 #define NEXT_SIGACTION "sigaction"
112 #define LIBC_SIGACTION _sigaction
113 #undef OVERRIDE_SIGACTION
114 #define _NSIG NSIG
115 #endif /* __DARWIN__ */
116 
117 #if defined(__sun__)
118 /*
119  * Assume Solaris/x86 2.8.
120  * There is a number of sigaction() procedures in libc:
121  * * sigaction(): weak reference to _sigaction().
122  * * _sigaction(): apparently a simple wrapper around __sigaction().
123  * * __sigaction(): apparently the procedure doing the actual system call.
124  * * _libc_sigaction(): apparently some thread-related wrapper, which ends
125  *   up calling __sigaction().
126  * The threads library redefines sigaction() and _sigaction() to its
127  * own wrapper, which checks for and restricts access to threads-related
128  * signals. The wrapper appears to eventually call libc's __sigaction().
129  *
130  * We catch and override _sigaction() since overriding __sigaction()
131  * causes fatal errors in some cases.
132  *
133  * When linked with thread support, there are calls to sigaction() before
134  * our init routine has had a chance to find _sigaction()'s address.
135  * This forces us to initialise at the first call.
136  */
137 #define NEXT_SIGACTION "_sigaction"
138 #define LIBC_SIGACTION _sigaction
139 #define OVERRIDE_SIGACTION
140 #define _NSIG NSIG
141 #endif /* __sun__ */
142 
143 #if defined(__FreeBSD__)
144 /*
145  * This is a copy of Darwin code for FreeBSD.
146  * CAVEAT: detailed semantics are not verified yet.
147  */
148 #define NEXT_SIGACTION "sigaction"
149 #define LIBC_SIGACTION _sigaction
150 #undef OVERRIDE_SIGACTION
151 #define _NSIG NSIG
152 #endif /* __FreeBSD__ */
153 
154 #if defined(__NetBSD__)
155 /*
156  * Note: This is only stub code to allow the build to succeed.
157  * Whether this actually provides the needed overrides for safe
158  * signal delivery or not is unknown.
159  */
160 #undef NEXT_SIGACTION
161 #undef OVERRIDE_SIGACTION
162 #endif /* __NetBSD__ */
163 
164 #if !(defined(__GLIBC__) || defined(__DARWIN__) || defined(__NetBSD__) ||  \
165           defined(__FreeBSD__) || defined(__sun__))
166 /*
167  * Unknown libc -- assume musl, which does not allow safe signals
168  */
169 #error "beamasm requires a libc that can guarantee that sigaltstack works"
170 #endif /* !(__GLIBC__ || __DARWIN__ || __NetBSD__ || __FreeBSD__ ||        \
171             * __sun__)                                                         \
172             */
173 
174 #if defined(NEXT_SIGACTION)
175 /*
176  * Initialize a function pointer to the libc core sigaction routine,
177  * to be used by our wrappers.
178  */
179 #include <dlfcn.h>
180 
181 static int (*next_sigaction)(int, const struct sigaction *, struct sigaction *);
182 
do_init(void)183 static void do_init(void) {
184     next_sigaction = dlsym(RTLD_NEXT, NEXT_SIGACTION);
185 
186     if (next_sigaction != 0) {
187         return;
188     }
189 
190     perror("dlsym");
191     abort();
192 }
193 
194 #define INIT()                                                         \
195             do {                                                               \
196                 if (!next_sigaction)                                           \
197                     do_init();                                                 \
198             } while (0)
199 #else /* !defined(NEXT_SIGACTION) */
200 #define INIT()                                                         \
201             do {                                                               \
202             } while (0)
203 #endif /* !defined(NEXT_SIGACTION) */
204 
205 #if defined(NEXT_SIGACTION)
206 /*
207  * This is our wrapper for sigaction(). sigaction() can be called before
208  * sys_init_signal_stack() has been executed, especially when threads support
209  * has been linked with the executable. Therefore, we must initialise
210  * next_sigaction() dynamically, the first time it's needed.
211  */
my_sigaction(int signum,const struct sigaction * act,struct sigaction * oldact)212 static int my_sigaction(int signum,
213                         const struct sigaction *act,
214                         struct sigaction *oldact) {
215     struct sigaction newact;
216 
217     INIT();
218 
219     if (act && act->sa_handler != SIG_DFL && act->sa_handler != SIG_IGN &&
220         !(act->sa_flags & SA_ONSTACK)) {
221         newact = *act;
222         newact.sa_flags |= SA_ONSTACK;
223         act = &newact;
224     }
225     return next_sigaction(signum, act, oldact);
226 }
227 #endif
228 
229 #if defined(LIBC_SIGACTION)
230 
231 /*
232  * This overrides the C library's core sigaction() procedure, catching
233  * all its internal calls.
234  */
235 extern int LIBC_SIGACTION(int, const struct sigaction *, struct sigaction *);
236 
LIBC_SIGACTION(int signum,const struct sigaction * act,struct sigaction * oldact)237 int LIBC_SIGACTION(int signum,
238                    const struct sigaction *act,
239                    struct sigaction *oldact) {
240     return my_sigaction(signum, act, oldact);
241 }
242 
243 #endif
244 
245 #if defined(OVERRIDE_SIGACTION)
246 
247 /*
248  * This catches the application's own sigaction() calls.
249  */
sigaction(int signum,const struct sigaction * act,struct sigaction * oldact)250 int sigaction(int signum,
251               const struct sigaction *act,
252               struct sigaction *oldact) {
253     return my_sigaction(signum, act, oldact);
254 }
255 
256 #endif
257 
258 /*
259  * Set alternate signal stack for the invoking thread.
260  */
sys_sigaltstack(void * ss_sp)261 static void sys_sigaltstack(void *ss_sp) {
262     stack_t ss;
263 
264     ss.ss_sp = ss_sp;
265     ss.ss_flags = 0;
266     ss.ss_size = SIGSTKSZ;
267 
268     if (sigaltstack(&ss, NULL) < 0) {
269         ERTS_INTERNAL_ERROR("Failed to set alternate signal stack");
270     }
271 }
272 
273 /*
274  * Set up alternate signal stack for an Erlang process scheduler thread.
275  */
sys_thread_init_signal_stack(void)276 void sys_thread_init_signal_stack(void) {
277     /* This will never be freed. */
278     char *stack = malloc(SIGSTKSZ);
279     sys_sigaltstack(stack);
280 }
281 
282 /*
283  * 1. Set up alternate signal stack for the main thread.
284  * 2. Add SA_ONSTACK to existing user-defined signal handlers.
285  */
sys_init_signal_stack(void)286 void sys_init_signal_stack(void) {
287     struct sigaction sa;
288     int i;
289 
290     INIT();
291 
292     sys_thread_init_signal_stack();
293 
294     for (i = 1; i < _NSIG; ++i) {
295         if (sigaction(i, NULL, &sa)) {
296             /* This will fail with EINVAL on Solaris if 'i' is one of the
297                thread library's private signals. We DO catch the initial
298                setup of these signals, so things MAY be OK anyway. */
299             continue;
300         }
301 
302         if (sa.sa_handler == SIG_DFL || sa.sa_handler == SIG_IGN ||
303             (sa.sa_flags & SA_ONSTACK)) {
304             continue;
305         }
306 
307         sa.sa_flags |= SA_ONSTACK;
308 
309         if (sigaction(i, &sa, NULL)) {
310 #ifdef SIGCANCEL
311             /* Solaris 9 x86 refuses to let us modify SIGCANCEL. */
312             if (i == SIGCANCEL)
313                 continue;
314 #endif
315             ERTS_INTERNAL_ERROR("Failed to use alternate signal stack");
316         }
317     }
318 }
319 
320 #else
321 
sys_init_signal_stack(void)322 void sys_init_signal_stack(void) {
323     /* Not required for this configuration. */
324 }
325 
sys_thread_init_signal_stack(void)326 void sys_thread_init_signal_stack(void) {
327     /* Not required for this configuration. */
328 }
329 
330 #endif
331