0.9.9.36:
[sbcl.git] / src / runtime / alpha-arch.c
1 /*
2  * This software is part of the SBCL system. See the README file for
3  * more information.
4  *
5  * This software is derived from the CMU CL system, which was
6  * written at Carnegie Mellon University and released into the
7  * public domain. The software is in the public domain and is
8  * provided with absolutely no warranty. See the COPYING and CREDITS
9  * files for more information.
10  */
11
12 /* Note that although superficially it appears that we use
13  * os_context_t like we ought to, we actually just assume its a
14  * ucontext in places.  Naughty */
15
16 #include <stdio.h>
17 #include <string.h>
18
19 #include "sbcl.h"
20 #include "runtime.h"
21 #include "globals.h"
22 #include "validate.h"
23 #include "os.h"
24 #include "arch.h"
25 #include "lispregs.h"
26 #include "signal.h"
27 #include "alloc.h"
28 #include "interrupt.h"
29 #include "interr.h"
30 #include "breakpoint.h"
31 #include "monitor.h"
32
33 extern char call_into_lisp_LRA[], call_into_lisp_end[];
34
35 extern size_t os_vm_page_size;
36 #define BREAKPOINT_INST 0x80
37
38
39 void
40 arch_init(void)
41 {
42     /* This must be called _after_ os_init(), so that we know what the
43      * page size is. */
44
45     if (mmap((os_vm_address_t) call_into_lisp_LRA_page,os_vm_page_size,
46              OS_VM_PROT_ALL,MAP_PRIVATE|MAP_ANONYMOUS|MAP_FIXED,-1,0)
47         == (os_vm_address_t) -1)
48         perror("mmap");
49
50     /* call_into_lisp_LRA is a collection of trampolines written in asm -
51      * see alpha-assem.S.  We copy it to call_into_lisp_LRA_page where
52      * VOPs and things can find it. (I don't know why they can't find it
53      * where it was to start with.) */
54     bcopy(call_into_lisp_LRA,(void *)call_into_lisp_LRA_page,os_vm_page_size);
55
56     os_flush_icache((os_vm_address_t)call_into_lisp_LRA_page,
57                     os_vm_page_size);
58     return;
59 }
60
61 os_vm_address_t
62 arch_get_bad_addr (int sig, siginfo_t *code, os_context_t *context)
63 {
64     unsigned int badinst;
65
66     /* Instructions are 32 bit quantities. */
67     unsigned int *pc ;
68     /*  fprintf(stderr,"arch_get_bad_addr %d %p %p\n",
69         sig, code, context); */
70     pc= (unsigned int *)(*os_context_pc_addr(context));
71
72     if (((unsigned long)pc) & 3) {
73         return NULL;            /* In what case would pc be unaligned?? */
74     }
75
76     if ( (pc < READ_ONLY_SPACE_START ||
77           pc >= READ_ONLY_SPACE_START+READ_ONLY_SPACE_SIZE) &&
78          (pc < current_dynamic_space ||
79           pc >= current_dynamic_space + DYNAMIC_SPACE_SIZE))
80         return NULL;
81
82     return context->uc_mcontext.sc_traparg_a0;
83 }
84
85 void
86 arch_skip_instruction(os_context_t *context)
87 {
88     /* This may be complete rubbish, as (at least for traps) pc points
89      * _after_ the instruction that caused us to be here anyway.
90      */
91     ((char*)*os_context_pc_addr(context)) +=4; }
92
93 unsigned char *
94 arch_internal_error_arguments(os_context_t *context)
95 {
96     return (unsigned char *)(*os_context_pc_addr(context)+4);
97 }
98
99 boolean
100 arch_pseudo_atomic_atomic(os_context_t *context)
101 {
102     return ((*os_context_register_addr(context,reg_ALLOC)) & 1);
103 }
104
105 void arch_set_pseudo_atomic_interrupted(os_context_t *context)
106 {
107     /* On coming out of an atomic section, we subtract 1 from
108      * reg_Alloc, then try to store something at that address.  So,
109      * to signal that it was interrupted and a signal should be handled,
110      * we set bit 63 of reg_ALLOC here so that the end-of-atomic code
111      * will raise SIGSEGV (no ram mapped there).  We catch the signal
112      * (see the appropriate *-os.c) and call interrupt_handle_pending()
113      * for the saved signal instead */
114
115     *os_context_register_addr(context,reg_ALLOC) |=  (1L<<63);
116 }
117
118 void arch_clear_pseudo_atomic_interrupted(os_context_t *context)
119 {
120     *os_context_register_addr(context, reg_ALLOC) &= ~(1L<<63);
121 }
122
123 unsigned int arch_install_breakpoint(void *pc)
124 {
125     unsigned int *ptr = (unsigned int *)pc;
126     unsigned int result = *ptr;
127     *ptr = BREAKPOINT_INST;
128
129     os_flush_icache((os_vm_address_t)ptr, sizeof(unsigned int));
130
131     return result;
132 }
133
134 void arch_remove_breakpoint(void *pc, unsigned int orig_inst)
135 {
136     unsigned int *ptr = (unsigned int *)pc;
137     *ptr = orig_inst;
138     os_flush_icache((os_vm_address_t)pc, sizeof(unsigned int));
139 }
140
141 static unsigned int *skipped_break_addr, displaced_after_inst,
142      after_breakpoint;
143
144
145 /* This returns a PC value.  Lisp code is all in the 32-bit-addressable
146  * space, so we should be ok with an unsigned int. */
147 unsigned int
148 emulate_branch(os_context_t *context, unsigned int orig_inst)
149 {
150     int op = orig_inst >> 26;
151     int reg_a = (orig_inst >> 21) & 0x1f;
152     int reg_b = (orig_inst >> 16) & 0x1f;
153     int disp =
154         (orig_inst&(1<<20)) ?
155         orig_inst | (-1 << 21) :
156         orig_inst&0x1fffff;
157     int next_pc = *os_context_pc_addr(context);
158     int branch = 0; /* was NULL;               */
159
160     switch(op) {
161     case 0x1a: /* jmp, jsr, jsr_coroutine, ret */
162         *os_context_register_addr(context,reg_a) =
163             *os_context_pc_addr(context);
164         *os_context_pc_addr(context) =
165             *os_context_register_addr(context,reg_b)& ~3;
166         break;
167     case 0x30: /* br */
168         *os_context_register_addr(context,reg_a)=*os_context_pc_addr(context);
169         branch = 1;
170         break;
171     case 0x31: /* fbeq */
172         if (*(os_context_float_register_addr(context,reg_a))==0) branch = 1;
173         break;
174     case 0x32: /* fblt */
175         if (*os_context_float_register_addr(context,reg_a)<0) branch = 1;
176         break;
177     case 0x33: /* fble */
178         if (*os_context_float_register_addr(context,reg_a)<=0) branch = 1;
179         break;
180     case 0x34: /* bsr */
181         *os_context_register_addr(context,reg_a)=*os_context_pc_addr(context);
182         branch = 1;
183         break;
184     case 0x35: /* fbne */
185         if (*os_context_register_addr(context,reg_a)!=0) branch = 1;
186         break;
187     case 0x36: /* fbge */
188         if (*os_context_float_register_addr(context,reg_a)>=0) branch = 1;
189         break;
190     case 0x37: /* fbgt */
191         if (*os_context_float_register_addr(context,reg_a)>0) branch = 1;
192         break;
193     case 0x38: /* blbc */
194         if ((*os_context_register_addr(context,reg_a)&1) == 0) branch = 1;
195         break;
196     case 0x39: /* beq */
197         if (*os_context_register_addr(context,reg_a)==0) branch = 1;
198         break;
199     case 0x3a: /* blt */
200         if (*os_context_register_addr(context,reg_a)<0) branch = 1;
201         break;
202     case 0x3b: /* ble */
203         if (*os_context_register_addr(context,reg_a)<=0) branch = 1;
204         break;
205     case 0x3c: /* blbs */
206         if ((*os_context_register_addr(context,reg_a)&1)!=0) branch = 1;
207         break;
208     case 0x3d: /* bne */
209         if (*os_context_register_addr(context,reg_a)!=0) branch = 1;
210         break;
211     case 0x3e: /* bge */
212         if (*os_context_register_addr(context,reg_a)>=0) branch = 1;
213         break;
214     case 0x3f: /* bgt */
215         if (*os_context_register_addr(context,reg_a)>0) branch = 1;
216         break;
217     }
218     if (branch)
219         next_pc += disp*4;
220     return next_pc;
221 }
222
223 static sigset_t orig_sigmask;
224
225 /* Perform the instruction that we overwrote with a breakpoint.  As we
226  * don't have a single-step facility, this means we have to:
227  * - put the instruction back
228  * - put a second breakpoint at the following instruction,
229  *   set after_breakpoint and continue execution.
230  *
231  * When the second breakpoint is hit (very shortly thereafter, we hope)
232  * sigtrap_handler gets called again, but follows the AfterBreakpoint
233  * arm, which
234  * - puts a bpt back in the first breakpoint place (running across a
235  *   breakpoint shouldn't cause it to be uninstalled)
236  * - replaces the second bpt with the instruction it was meant to be
237  * - carries on
238  *
239  * Clear?
240  */
241
242 void arch_do_displaced_inst(os_context_t *context,unsigned int orig_inst)
243 {
244     /* Apparent off-by-one errors ahoy.  If you consult the Alpha ARM,
245      * it will tell you that after a BPT, the saved PC is the address
246      * of the instruction _after_ the instruction that caused the trap.
247      *
248      * However, we decremented PC by 4 before calling the Lisp-level
249      * handler that calls this routine (see alpha-arch.c line 322 and
250      * friends) so when we get to this point PC is actually pointing
251      * at the BPT instruction itself.  This is good, because this is
252      * where we want to restart execution when we do that */
253
254     unsigned int *pc=(unsigned int *)(*os_context_pc_addr(context));
255     unsigned int *next_pc;
256     int op = orig_inst >> 26;;
257
258     orig_sigmask = *os_context_sigmask_addr(context);
259     sigaddset_blockable(os_context_sigmask_addr(context));
260
261     /* Put the original instruction back. */
262     *pc = orig_inst;
263     os_flush_icache((os_vm_address_t)pc, sizeof(unsigned int));
264     skipped_break_addr = pc;
265
266     /* Figure out where we will end up after running the displaced
267      * instruction */
268     if (op == 0x1a || (op&0xf) == 0x30) /* a branch */
269         /* The cast to long is just to shut gcc up. */
270         next_pc = (unsigned int *)((long)emulate_branch(context,orig_inst));
271     else
272         next_pc = pc+1;
273
274     /* Set the after breakpoint. */
275     displaced_after_inst = *next_pc;
276     *next_pc = BREAKPOINT_INST;
277     after_breakpoint=1;
278     os_flush_icache((os_vm_address_t)next_pc, sizeof(unsigned int));
279 }
280
281 static void
282 sigtrap_handler(int signal, siginfo_t *siginfo, os_context_t *context)
283 {
284     unsigned int code;
285 #ifdef LISP_FEATURE_LINUX
286     os_restore_fp_control(context);
287 #endif
288
289     /* this is different from how CMUCL does it.  CMUCL used "call_pal
290      * PAL_gentrap", which doesn't do anything on Linux (unless NL0
291      * contains certain specific values).  We use "bugchk" instead.
292      * It's (for our purposes) just the same as bpt but has a
293      * different opcode so we can test whether we're dealing with a
294      * breakpoint or a "system service" */
295
296     if ((*(unsigned int*)(*os_context_pc_addr(context)-4))==BREAKPOINT_INST) {
297         if (after_breakpoint) {
298             /* see comments above arch_do_displaced_inst.  This is where
299              * we reinsert the breakpoint that we removed earlier */
300
301             *os_context_pc_addr(context) -=4;
302             *skipped_break_addr = BREAKPOINT_INST;
303             os_flush_icache((os_vm_address_t)skipped_break_addr,
304                             sizeof(unsigned int));
305             skipped_break_addr = NULL;
306             *(unsigned int *)*os_context_pc_addr(context) =
307                 displaced_after_inst;
308             os_flush_icache((os_vm_address_t)*os_context_pc_addr(context), sizeof(unsigned int));
309             *os_context_sigmask_addr(context)= orig_sigmask;
310             after_breakpoint=0; /* false */
311             return;
312         } else
313             code = trap_Breakpoint;
314     } else
315         /* a "system service" */
316     code=*((u32 *)(*os_context_pc_addr(context)));
317
318     switch (code) {
319       case trap_PendingInterrupt:
320         arch_skip_instruction(context);
321         interrupt_handle_pending(context);
322         break;
323
324       case trap_Halt:
325         fake_foreign_function_call(context);
326         lose("%%primitive halt called; the party is over.\n");
327
328       case trap_Error:
329       case trap_Cerror:
330         interrupt_internal_error(signal, siginfo, context, code==trap_Cerror);
331         break;
332
333     case trap_Breakpoint:        /* call lisp-level handler */
334         *os_context_pc_addr(context) -=4;
335         handle_breakpoint(signal, siginfo, context);
336         break;
337
338       case trap_FunEndBreakpoint:
339         *os_context_pc_addr(context) -=4;
340         *os_context_pc_addr(context) =
341             (int)handle_fun_end_breakpoint(signal, siginfo, context);
342         break;
343
344       default:
345         fprintf(stderr, "unidentified breakpoint/trap %d\n",code);
346         interrupt_handle_now(signal, siginfo, context);
347         break;
348     }
349 }
350
351 unsigned long
352 arch_get_fp_control()
353 {
354     return ieee_get_fp_control();
355 }
356
357 void
358 arch_set_fp_control(unsigned long fp)
359 {
360     ieee_set_fp_control(fp);
361 }
362
363
364 void arch_install_interrupt_handlers()
365 {
366     undoably_install_low_level_interrupt_handler(SIGTRAP, sigtrap_handler);
367 }
368
369 extern lispobj call_into_lisp(lispobj fun, lispobj *args, int nargs);
370
371 lispobj funcall0(lispobj function)
372 {
373     lispobj *args = current_control_stack_pointer;
374
375     return call_into_lisp(function, args, 0);
376 }
377
378 lispobj funcall1(lispobj function, lispobj arg0)
379 {
380     lispobj *args = current_control_stack_pointer;
381
382     current_control_stack_pointer += 1;
383     args[0] = arg0;
384
385     return call_into_lisp(function, args, 1);
386 }
387
388 lispobj funcall2(lispobj function, lispobj arg0, lispobj arg1)
389 {
390     lispobj *args = current_control_stack_pointer;
391
392     current_control_stack_pointer += 2;
393     args[0] = arg0;
394     args[1] = arg1;
395
396     return call_into_lisp(function, args, 2);
397 }
398
399 lispobj funcall3(lispobj function, lispobj arg0, lispobj arg1, lispobj arg2)
400 {
401     lispobj *args = current_control_stack_pointer;
402
403     current_control_stack_pointer += 3;
404     args[0] = arg0;
405     args[1] = arg1;
406     args[2] = arg2;
407
408     return call_into_lisp(function, args, 3);
409 }
410