* jit/patcher.h: Added #error if included on s390.
[cacao.git] / src / vm / jit / s390 / asmpart.S
1 /* src/vm/jit/s390/asmpart.S - Java-C interface functions for s390
2
3    Copyright (C) 2006, 2007 R. Grafl, A. Krall, C. Kruegel,
4    C. Oates, R. Obermaisser, M. Platter, M. Probst, S. Ring,
5    E. Steiner, C. Thalinger, D. Thuernbeck, P. Tomsich, C. Ullrich,
6    J. Wenninger, Institut f. Computersprachen - TU Wien
7
8    This file is part of CACAO.
9
10    This program is free software; you can redistribute it and/or
11    modify it under the terms of the GNU General Public License as
12    published by the Free Software Foundation; either version 2, or (at
13    your option) any later version.
14
15    This program is distributed in the hope that it will be useful, but
16    WITHOUT ANY WARRANTY; without even the implied warranty of
17    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
18    General Public License for more details.
19
20    You should have received a copy of the GNU General Public License
21    along with this program; if not, write to the Free Software
22    Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
23    02110-1301, USA.
24
25    $Id: asmpart.S 8251 2007-08-01 15:26:59Z pm $
26
27 */
28
29
30 #include "config.h"
31
32 #include "vm/jit/s390/arch.h"
33 #include "vm/jit/s390/md-abi.h"
34 #include "vm/jit/s390/md-asm.h"
35 #include "vm/jit/s390/offsets.h"
36
37 #include "vm/jit/abi-asm.h"
38 #include "vm/jit/methodheader.h"
39
40         .text
41
42
43 /* export functions ***********************************************************/
44
45         .globl asm_vm_call_method
46         .globl asm_vm_call_method_int
47         .globl asm_vm_call_method_long
48         .globl asm_vm_call_method_float
49         .globl asm_vm_call_method_double
50         .globl asm_vm_call_method_exception_handler
51         .globl asm_vm_call_method_end
52
53         .globl asm_call_jit_compiler
54
55         .globl asm_handle_exception
56         .globl asm_handle_nat_exception
57
58         .globl asm_abstractmethoderror
59
60         .globl asm_replacement_out
61         .globl asm_replacement_in
62
63         .globl asm_builtin_f2i
64         .globl asm_builtin_f2l
65         .globl asm_builtin_d2i
66         .globl asm_builtin_d2l
67
68         .globl asm_criticalsections
69         .globl asm_getclassvalues_atomic
70
71
72 asm_abstractmethoderror:
73         .long 0
74 asm_replacement_out:
75         .long 0
76 asm_replacement_in:
77         .long 0
78 asm_builtin_f2i:
79         .long 0
80 asm_builtin_f2l:
81         .long 0
82 asm_builtin_d2i:
83         .long 0
84 asm_builtin_d2l:
85         .long 0
86
87 /********************* function asm_calljavafunction ***************************
88 *                                                                              *
89 *   This function calls a Java-method (which possibly needs compilation)       *
90 *   with up to 4 address parameters.                                           *
91 *                                                                              *
92 *   This functions calls the JIT-compiler which eventually translates the      *
93 *   method into machine code.                                                  *
94 *                                                                              *
95 *   C-prototype:                                                               *
96 *    javaobject_header *asm_calljavamethod (methodinfo *m,                     *
97 *         void *arg1, void *arg2, void *arg3, void *arg4);                     *
98 *                                                                              *
99 *******************************************************************************/
100
101         .long   0                         /* catch type all                       */
102         .long   0                         /* exception handler pc                 */
103         .long   0                         /* end pc                               */
104         .long   0                         /* start pc                             */
105         .long   1                         /* extable size                         */
106         .long   0                         /* line number table start              */
107         .long   0                         /* line number table size               */
108         .long   0                         /* fltsave                              */
109         .long   0                         /* intsave                              */
110         .long   0                         /* IsLeaf                               */
111         .long   0                         /* IsSync                               */
112         .long   0                         /* frame size                           */
113         .long   0                         /* codeinfo pointer                     */
114
115 asm_vm_call_method:
116 asm_vm_call_method_int:
117 asm_vm_call_method_long:
118 asm_vm_call_method_float:
119 asm_vm_call_method_double:
120
121 /*
122
123 a0:   methodinfo *m
124 a1:   s4 vmargscount   ---> v0: java_objectheader *
125 a2:   vm_arg *vmargs
126 r14:  return address
127
128 96 ...     on stack parameters (none)
129 0 - 96     register save area
130 -------------------------------------------------- <- SP on asm_vm_... entry
131            local variables
132                    saved return address (important to be at 0(sp) because of md_stacktrace_get_returnaddress)
133 ----------------------------------------- <- SP after stack frame allocation
134            arguments on stack
135 ---------------------------------------------------- <- SP on JIT code entry
136            saved return address (callee saved)
137
138 */
139
140
141 /*
142         Regiser usage:
143         itmp1: argument block pointer
144         itmp2: argument counter
145         s0: integer argument counter
146         s1: float argument counter
147         s2: integer register counter
148         s3: backup argument block pointer
149         s4: backup argument count
150 */
151
152         stm   %r6, %r15, 24(sp)               /* save callers regiters */
153         stm   a0, a2, 8(sp)                   /* save arguments */
154         ahi   sp, -8                          /* allocate stack space for local variables */
155         st    %r14, 0(sp)                     /* store RA once more at bottom of stack frame */
156
157         ltr   a1, a1                          /* maybe we have no args... */
158         je    L_no_args
159
160         lr    itmp2, a1                       /* load arg count */
161         lr    itmp1, a2                       /* load arg pointer */
162
163         ahi   itmp1, -sizevmarg               /* initialize arg pointer */
164         ahi   itmp2, 1                        /* initialize arg count */ 
165         lhi   s0, 0                           /* initialize integer arg counter */
166         lhi   s2, 0                           /* initialize integer register counter */
167         lhi   s1, 0                           /* initialize float arg counter */
168
169         lr    s4, a1                          /* backup arg count */
170         lr    s3, a2                          /* backup arg pointer */
171
172 L_register_copy:
173
174         ahi   itmp1, sizevmarg                /* forward arg pointer */
175         ahi   itmp2, -1                       /* decrement arg count */
176         je    L_register_copy_done            /* no arguments left */
177
178         tm    offvmargtype+7(itmp1), 0x02     /* is this a float/double type? */
179         jne   L_register_handle_float
180
181 L_register_handle_int:
182
183         chi   s2, INT_ARG_CNT                 /* are we out of integer arg registers ? */
184         je    L_register_copy                 /* yes, next loop */
185
186         tm    offvmargtype+7(itmp1), 0x01       /* is this a 2 word type ? */
187         jne   L_register_handle_long
188
189         ahi   s0, 1                           /* increment integer arg counter */
190         ahi   s2, 1                           /* increment integer register counter */
191
192         /* handle argument */
193
194         chi   s2, 1
195         je    L_handle_i0
196         chi   s2, 2
197         je    L_handle_i1
198         chi   s2, 3
199         je    L_handle_i2
200         chi   s2, 4
201         je    L_handle_i3
202         chi   s2, 5
203         je    L_handle_i4
204
205 L_register_handle_long:
206
207         chi   s2, (INT_ARG_CNT - 1)           /* are there 2 integer arg registers left ? */
208         jl    L_register_handle_long_continue /* yes */
209         lhi   s2, INT_ARG_CNT                 /* no, drop last register */
210         j     L_register_copy
211
212 L_register_handle_long_continue:
213
214         ahi   s0, 1                           /* increment integer arg counter */
215         ahi   s2, 2                           /* consume 2 integer arg registers */
216
217         /* handle argument */
218
219         chi   s2, 2
220         je    L_handle_l0
221         chi   s2, 3
222         je    L_handle_l1
223         chi   s2, 4
224         je    L_handle_l2
225         chi   s2, 5
226         je    L_handle_l3
227
228 L_register_handle_float:
229
230         chi   s1, FLT_ARG_CNT                 /* are we out of float arg registers */
231         je    L_register_copy                 /* no arg regisers left */
232
233         ahi   s1, 1                           /* increment float argument counter */
234
235         tm    offvmargtype+7(itmp1), 0x01     /* is this a 2 word type ? */
236         jne   L_register_handle_double
237
238         /* handle argument */
239
240         chi   s1, 1
241         je    L_handle_f0
242         chi   s1, 2
243         je    L_handle_f1
244
245 L_register_handle_double:
246
247         /* handle argument */
248
249         chi   s1, 1
250         je    L_handle_d0
251         chi   s1, 2
252         je    L_handle_d1
253
254 L_register_copy_done:
255
256 /*
257         Regiser usage:
258         itmp1: argument block pointer
259         itmp2: argument counter
260         s0: integer argument counter (initialized by previous code) 
261         s1: float argument counter (initialized by previous code)
262         s2: pointer to current argument on stack
263         s3: backup argument block pointer (used to initialize itmp1)
264             after used as backup of original stack pointer
265         s4: backup argument count (used to initialize itmp2)
266             after used as size of parameters on stack
267 */
268
269         lr    itmp2, s4                     /* restore argument counter */
270         lr    itmp1, s3                     /* restore argument block pointer */
271
272                                             /* calculate remaining arguments */
273         sr    s4, s0                        /* - integer arguments in registers */
274         sr    s4, s1                        /* - float arguments in registers */
275
276         lr    s3, sp                        /* backup stack pointer (does not alter CC) */
277
278         je    L_copy_done                   /* no arguments left for stack */
279
280         sll   s4, 3                         /* allocate 8 bytes per parameter on stack */       
281         sr    sp, s4                        /* allocate stack space for arguments */ 
282
283         lr    s2, sp                        /* points now to current argument on stack */
284
285         ahi   itmp1, -sizevmarg             /* initialize argument block pointer */
286         ahi   itmp2, 1                      /* initialize argument counter */
287
288 L_stack_copy_loop:
289
290         ahi   itmp1, sizevmarg              /* forward argument block pointer */
291         ahi   itmp2, -1                     /* decrement argument counter */
292         je    L_copy_done                   /* all arguments done */
293
294         tm    offvmargtype+7(itmp1), 0x02   /* is this a float/double type? */
295         jne   L_stack_handle_float
296
297 L_stack_handle_int:
298
299         ahi   s0, -1                         /* decrement number of integer arguments in regs */
300         jhe   L_stack_copy_loop              /* argument is in register */
301
302         tm    offvmargtype+7(itmp1), 0x01    /* is this a 2 word type ? */
303         jne   L_stack_handle_long
304
305         mvc   0(4, s2), offvmargdata+4(itmp1)/* copy integer value */
306         ahi   s2, 4
307         j     L_stack_copy_loop
308
309 L_stack_handle_long:
310
311         mvc   0(8, s2), offvmargdata(itmp1)  /* copy long value */
312         ahi   s2, 8
313         j     L_stack_copy_loop
314
315 L_stack_handle_float:
316
317         ahi   s1, -1                         /* decrement number of float arguments in regs */
318         jhe   L_stack_copy_loop              /* argument is in register */
319
320         tm    offvmargtype+7(itmp1), 0x01    /* is this a 2 word type ? */
321         jne   L_stack_handle_double
322
323         mvc   0(4, s2), offvmargdata(itmp1)  /* copy float value */
324         ahi   s2, 4
325         j     L_stack_copy_loop
326
327 L_stack_handle_double:
328
329         mvc   0(8, s2), offvmargdata(itmp1)  /* copy double value */
330         ahi   s2, 8
331         j     L_stack_copy_loop
332
333 L_copy_done:
334
335         /* Now we call the compiler in a rather questionable way i needed
336          * some days to understand:
337          *
338          * We can't simply call asm_call_jit_compiler, but we have to call an 
339          * address loaded from memory like it is done in JIT code.
340          *
341          * This is because the compiler will intercept the instruction before 
342          * the call instruction, extract the address where the function pointer
343          * has been loaded from and overwrite it with the code entry.
344          *
345          * Arguments are passed in temporary registers.
346          */
347
348         /* load address of L_asm_call_jit_compiler into memory */
349
350         basr  mptr, 0                         /* store PC */
351 L_basr:
352         la    mptr, L_asm_call_jit_compiler-L_basr(mptr) /* add offset to PC */
353         st    mptr, 4(s3)                     /* store on stack */
354
355         l     itmp1, 8+8(s3)                  /* load methodinfo for compiler */
356         la    mptr, 4(s3)                     /* store **function in mptr for compiler */
357
358         /* call L_asm_call_jit_compiler like JIT code would do */
359
360         l     itmp3, 0(mptr)                  /* load address of target from memory */
361         basr  %r14, itmp3                     /* jump to target */
362
363         /* todo will s4 survive the call? */
364         ar    sp, s4                          /* remove stack space for arguments */
365
366 L_asm_vm_call_method_return:
367
368         ahi   sp, 8                           /* remove stack space for local variables */
369         lm    %r6, %r15, 24(sp)               /* restore callers registers */
370         br    %r14                            /* return */
371
372 asm_vm_call_method_exception_handler:
373         lr    a0, xptr
374
375         bras  %r14, L_avcmeh_bras
376         .long builtin_throw_exception
377 L_avcmeh_bras:
378         l     %r14, 0(%r14)
379         ahi   sp, -96
380         basr  %r14, %r14
381         ahi   sp, 96
382
383         j     L_asm_vm_call_method_return
384
385 /* .... */
386
387 L_no_args:
388         lr    s3, sp
389         lhi   s4, 0
390         j     L_copy_done
391
392 L_handle_i0:
393         l     a0, offvmargdata+4(itmp1)
394         j     L_register_copy
395 L_handle_i1:
396         l     a1, offvmargdata+4(itmp1)
397         j     L_register_copy
398 L_handle_i2:
399         l     a2, offvmargdata+4(itmp1)
400         j     L_register_copy
401 L_handle_i3:
402         l     a3, offvmargdata+4(itmp1)
403         j     L_register_copy
404 L_handle_i4:
405         l     a4, offvmargdata+4(itmp1)
406         j     L_register_copy
407
408 L_handle_l0:
409         lm    a0, a1, offvmargdata(itmp1)
410         j     L_register_copy
411 L_handle_l1:
412         lm    a1, a2, offvmargdata(itmp1)
413         j     L_register_copy
414 L_handle_l2:
415         lm    a2, a3, offvmargdata(itmp1)
416         j     L_register_copy
417 L_handle_l3:
418         lm    a3, a4, offvmargdata(itmp1)
419         j     L_register_copy
420
421 L_handle_f0:
422         le    fa0, offvmargdata(itmp1)
423         j     L_register_copy
424 L_handle_f1:
425         le    fa1, offvmargdata(itmp1)
426         j     L_register_copy
427
428 L_handle_d0:
429         ld    fa0, offvmargdata(itmp1)
430         j     L_register_copy
431 L_handle_d1:
432         ld    fa1, offvmargdata(itmp1)
433         j     L_register_copy
434
435 asm_vm_call_method_end:
436         brc   0,0       
437
438 /****************** function asm_call_jit_compiler *****************************
439 *                                                                              *
440 *   invokes the compiler for untranslated JavaVM methods.                      *
441 *                                                                              *
442 *   itmp1: methodinfo pointer                                                  *
443 *   itmp2: method pointer                                                      *
444 *                                                                              *
445 *******************************************************************************/
446
447 /*
448
449 argument registers: arguments (like in JIT)
450
451         arguments on stack (like in JIT)
452 ------------------------------------------------------------- <- SP on entry
453
454         saved return address                                           \
455         stored volatile (in terms of C ABI) floag argument registers   | 
456 96      stored volatile (in terms of C ABI) integer argument registers | ACJC_STACKFRAME
457 0 - 96  register save area (C ABI)                                     /
458 -------------------------------------------------- <- SP for jit_asm_compile
459 */
460
461 /* This is called from a compiler stub.
462  * Arguments are already in registers and the stack is setup like in CACAO.
463  */
464
465 asm_call_jit_compiler:
466 L_asm_call_jit_compiler:
467
468 #       define ACJC_STACKFRAME (4 + (4 * 4) + (2 * 8) + 96)
469
470         ahi     sp,-ACJC_STACKFRAME        /* allocate stack space */
471
472         stm         %r2,%r5,96(sp)             /* store volatile int arg regs */
473         std     %f0,96+16(sp)              /* store volatile float arg regs */
474         std     %f2,96+24(sp)              
475         st      %r14,96+32(sp)             /* store return address */
476
477         /* load arguments */
478
479         lr      a0,itmp1                   /* pass methodinfo pointer            */
480         lr      a1,itmp2                   /* pass method pointer                */
481         la      a2,ACJC_STACKFRAME(sp)     /* pass java sp                       */
482         la      a3,0(%r14)                 /* pass return address, make sure bit 32 is 0 */
483
484         /* call jit_asm_compile in a PIC way */
485
486         bras    itmp2, L_bras_jac
487         .long   jit_asm_compile
488 L_bras_jac:
489         l       itmp2, 0(itmp2)
490         basr    %r14, itmp2
491
492         lr      pv, v0                     /* save return value */
493
494         lm      %r2,%r5,96(sp)             /* restore volatile int arg regs */
495         ld      %f0,96+16(sp)              /* restore volatile float arg regs */
496         ld      %f2,96+24(sp)              /* restore volatile float arg regs */
497
498         ltr     pv,pv
499         je      L_asm_call_jit_compiler_exception
500
501         l       %r14,96+32(sp)             /* restore return address */
502         ahi     sp, ACJC_STACKFRAME        /* remove stack frame */
503
504 jit_code_entry:                        /* label to set breakpoint on */
505         br      pv                         /* call the method, it will return to the caller */
506
507
508 L_asm_call_jit_compiler_exception:
509         bras    itmp2, L_bras_acjce
510         .long exceptions_get_and_clear_exception
511 L_bras_acjce:
512         l       itmp2, 0(itmp2)
513         basr    %r14, itmp2
514         lr      xptr, %r2
515         l       xpc,96+32(sp)              /* restore return address */
516         ahi     sp, ACJC_STACKFRAME        /* remove stack frame */
517         j       L_asm_handle_nat_exception
518
519
520 #if 0
521 /* asm_handle_exception ********************************************************
522 *                                                                              *
523 *   This function handles an exception. It does not use the usual calling      *
524 *   conventions. The exception pointer is passed in REG_ITMP1 and the          *
525 *   pc from the exception raising position is passed in REG_ITMP2. It searches *
526 *   the local exception table for a handler. If no one is found, it unwinds    *
527 *   stacks and continues searching the callers.                                *
528 *                                                                              *
529 *******************************************************************************/
530
531 #endif
532
533 asm_handle_nat_exception:
534 L_asm_handle_nat_exception:
535         /* TODO really nothing here ? */
536 asm_handle_exception:
537 L_asm_handle_exception:                 /* required for PIC code              */
538
539         ahi     sp, -(ARGUMENT_REGISTERS_SIZE + TEMPORARY_REGISTERS_SIZE) /* create maybe-leaf stackframe */
540         STORE_ARGUMENT_REGISTERS(0)
541         STORE_TEMPORARY_REGISTERS(ARGUMENT_REGISTERS_SIZE)      
542         lhi     a3, (ARGUMENT_REGISTERS_SIZE + TEMPORARY_REGISTERS_SIZE) /* prepare a3 for handle_exception */
543
544         lhi     %r0, 1                      /* set maybe-leaf flag */
545
546 L_asm_handle_exception_stack_loop:
547         ahi     sp,-(6*4)
548         st      xptr,0*4(sp)                /* save exception pointer             */
549         st      xpc,1*4(sp)                 /* save exception pc                  */
550         la      a3,(6*4)(a3,sp)             /* calculate Java sp into a3...       */
551         st      a3,3*4(sp)                  /* ...and save it                     */
552         st      %r0,4*4(sp)                 /* save maybe-leaf flag               */
553
554         lr      a0,xpc                      /* exception pc                       */
555
556         ahi     sp,-96                      /* add register save area for C code */
557
558         bras    %r14,L_ahe_bras             /* call codegen_get_pv_from_pc */
559         .long   codegen_get_pv_from_pc
560 L_ahe_bras:
561         l       %r14,0(%r14)
562         basr    %r14,%r14
563         st      v0,2*4+96(sp)               /* save data segment pointer          */
564     
565         lr      a2,v0                       /* pass data segment pointer          */
566         l       a0,0*4+96(sp)               /* pass exception pointer             */
567         l       a1,1*4+96(sp)               /* pass exception pc                  */
568         l       a3,3*4+96(sp)               /* pass Java stack pointer            */
569
570         bras    %r14,L_ahe_bras2            /* call exceptions_handle_exception */
571         .long   exceptions_handle_exception
572 L_ahe_bras2:
573         l       %r14,0(%r14)
574         basr    %r14,%r14
575
576         ahi     sp,96                       /* remove regiser save area for C code */
577
578         ltr     v0,v0
579         jz      L_asm_handle_exception_not_catched
580
581         lr      xpc,v0                      /* move handlerpc into xpc            */
582         l       xptr,0*4(sp)                /* restore exception pointer          */
583         l       pv,2*4(sp)                  /* restore PV                         */
584         ahi     pv,-0xffc                   /* offset PV */
585         l       %r0,4*4(sp)                 /* get maybe-leaf flag                */
586         ahi     sp,(6*4)                    /* free stack frame                   */
587
588         ltr     %r0, %r0
589         jz      L_asm_handle_exception_no_leaf
590
591         LOAD_ARGUMENT_REGISTERS(0)
592         LOAD_TEMPORARY_REGISTERS(ARGUMENT_REGISTERS_SIZE)       
593
594         ahi     sp, (ARGUMENT_REGISTERS_SIZE + TEMPORARY_REGISTERS_SIZE) /* Remove maybe-leaf stackframe */
595
596 L_asm_handle_exception_no_leaf:
597         br      xpc                         /* jump to the handler */
598
599 L_asm_handle_exception_not_catched:
600         l       xptr,0*4(sp)                /* restore exception pointer          */
601         l       itmp3,2*4(sp)               /* restore data segment pointer       */
602         ahi     itmp3,-0xfff                /* for negative displacements */
603         l       %r0,4*4(sp)                 /* get maybe-leaf flag                */
604         ahi     sp,(6*4)
605
606         ltr     %r0,%r0
607         jz      L_asm_handle_exception_no_leaf_stack
608
609         ahi     sp, (ARGUMENT_REGISTERS_SIZE + TEMPORARY_REGISTERS_SIZE) /* Remove maybe-leaf stackframe */
610         lhi     %r0,0                       /* clear the isleaf flag              */
611
612         /*
613         +-----------------+-----------+---------+----+
614         | Memuse          | Float Sav | Int Sav | RA |
615         |                 | 0 ... n   | 0 ... n |    |
616         +-----------------+-----------+---------+----+
617         ^                 ^           ^
618         SP                F           I
619
620                                       ^         ^    ^
621                                   p3        p2   p1     
622         */
623
624 L_asm_handle_exception_no_leaf_stack:
625
626         l       itmp2,0xfff+FrameSize(itmp3)/* get frame size                     */
627         la      itmp2,0(itmp2,sp)           /* pointer to save area (p1) */
628         ahi     itmp2,-4                    /* skip RA (p2) */
629         ahi     itmp2,-0xfff                /* for negative displacements */
630
631         l       a0,0xfff+IntSave(itmp3)     /* a0 = saved int register count  */
632
633         ltr     a0,a0
634         je      noint
635
636         chi     a0,1
637         je      int1
638         chi     a0,2
639         je      int2
640         chi     a0,3
641         je      int3
642         chi     a0,4
643         je      int4
644         
645 int5:
646         l       s0,0xfff-5*4(itmp2)
647 int4:   
648         l       s1,0xfff-4*4(itmp2)
649 int3:   
650         l       s2,0xfff-3*4(itmp2)
651 int2:   
652         l       s3,0xfff-2*4(itmp2)
653 int1:   
654         l       s4,0xfff-1*4(itmp2)
655
656 noint:
657
658         sll     a0,2                        /* a0 = saved int register count * 4 */
659         sr      itmp2, a0                   /* skip Int Sav (p3) */
660
661         l       a0,0xfff+FltSave(itmp3)
662         ltr         a0,a0                       /* Number of saved floating point registers */
663         je      noflt
664
665         chi     a0,1
666         je      flt1
667
668 flt2:   
669         ld    %f4,0xfff-2*8(itmp2)
670 flt1:   
671         ld    %f6,0xfff-1*8(itmp2)
672                 
673 noflt:
674
675         l       itmp3,0xfff+FrameSize(itmp3)/* get frame size (at least 4 - RA)   */
676         ahi     itmp3,-4                    /* substract 4 */
677         l       xpc,0(itmp3,sp)             /* load the new xpc -  return address */
678         la      sp, 4(itmp3,sp)             /* unwind stack                       */
679
680                                             /* exception pointer is still set     */
681 #if 0
682         sub     $3,xpc                      /* subtract 3 bytes for call          */
683 #endif
684
685         lhi     a3,0                        /* prepare a3 for handle_exception    */
686         
687         j               L_asm_handle_exception_stack_loop
688
689
690 #if 0
691
692 /* asm_abstractmethoderror *****************************************************
693
694    Creates and throws an AbstractMethodError.
695
696 *******************************************************************************/
697
698 asm_abstractmethoderror:
699         mov     sp,a0                       /* pass java sp                       */
700         add     $1*8,a0
701         mov     0*8(sp),a1                  /* pass exception address             */
702         sub     $3,a1
703         call    exceptions_asm_new_abstractmethoderror@PLT
704                                             /* exception pointer is return value  */
705         pop     xpc                         /* get exception address              */
706         sub     $3,xpc                      /* exception address is ra - 3        */
707         jmp     L_asm_handle_exception
708
709 #endif
710
711 #if 0
712
713 /* asm_replacement_out *********************************************************
714
715    This code is jumped to from the replacement-out stubs that are executed
716    when a thread reaches an activated replacement point.
717
718    The purpose of asm_replacement_out is to read out the parts of the
719    execution state that cannot be accessed from C code, store this state,
720    and then call the C function replace_me.
721
722    Stack layout:
723       8                 start of stack inside method to replace
724       0   rplpoint *    info on the replacement point that was reached
725
726 *******************************************************************************/
727
728 /* some room to accomodate changes of the stack frame size during replacement */
729         /* XXX we should find a cleaner solution here */
730 #define REPLACEMENT_ROOM  512
731
732 asm_replacement_out:
733     /* create stack frame */
734         sub     $(sizeexecutionstate + REPLACEMENT_ROOM),sp
735
736         /* save registers in execution state */
737         mov     %rax,(RAX*8+offes_intregs)(sp)
738         mov     %rbx,(RBX*8+offes_intregs)(sp)
739         mov     %rcx,(RCX*8+offes_intregs)(sp)
740         mov     %rdx,(RDX*8+offes_intregs)(sp)
741         mov     %rsi,(RSI*8+offes_intregs)(sp)
742         mov     %rdi,(RDI*8+offes_intregs)(sp)
743         mov     %rbp,(RBP*8+offes_intregs)(sp)
744         movq    $0  ,(RSP*8+offes_intregs)(sp) /* not used */
745         mov     %r8 ,(R8 *8+offes_intregs)(sp)
746         mov     %r9 ,(R9 *8+offes_intregs)(sp)
747         mov     %r10,(R10*8+offes_intregs)(sp)
748         mov     %r11,(R11*8+offes_intregs)(sp)
749         mov     %r12,(R12*8+offes_intregs)(sp)
750         mov     %r13,(R13*8+offes_intregs)(sp)
751         mov     %r14,(R14*8+offes_intregs)(sp)
752         mov     %r15,(R15*8+offes_intregs)(sp)
753
754         movq    %xmm0 ,(XMM0 *8+offes_fltregs)(sp)
755         movq    %xmm1 ,(XMM1 *8+offes_fltregs)(sp)
756         movq    %xmm2 ,(XMM2 *8+offes_fltregs)(sp)
757         movq    %xmm3 ,(XMM3 *8+offes_fltregs)(sp)
758         movq    %xmm4 ,(XMM4 *8+offes_fltregs)(sp)
759         movq    %xmm5 ,(XMM5 *8+offes_fltregs)(sp)
760         movq    %xmm6 ,(XMM6 *8+offes_fltregs)(sp)
761         movq    %xmm7 ,(XMM7 *8+offes_fltregs)(sp)
762         movq    %xmm8 ,(XMM8 *8+offes_fltregs)(sp)
763         movq    %xmm9 ,(XMM9 *8+offes_fltregs)(sp)
764         movq    %xmm10,(XMM10*8+offes_fltregs)(sp)
765         movq    %xmm11,(XMM11*8+offes_fltregs)(sp)
766         movq    %xmm12,(XMM12*8+offes_fltregs)(sp)
767         movq    %xmm13,(XMM13*8+offes_fltregs)(sp)
768         movq    %xmm14,(XMM14*8+offes_fltregs)(sp)
769         movq    %xmm15,(XMM15*8+offes_fltregs)(sp)
770
771         /* calculate sp of method */
772         mov     sp,itmp1
773         add     $(sizeexecutionstate + REPLACEMENT_ROOM + 8),itmp1
774         mov     itmp1,(offes_sp)(sp)
775
776         /* pv must be looked up via AVL tree */
777         movq    $0,(offes_pv)(sp)
778
779         /* call replace_me */
780         mov     -8(itmp1),a0                /* rplpoint *                         */
781     mov     sp,a1                       /* arg1: execution state              */
782     call    replace_me@PLT              /* call C function replace_me         */
783     call    abort@PLT                   /* NEVER REACHED                      */
784
785 /* asm_replacement_in **********************************************************
786
787    This code writes the given execution state and jumps to the replacement
788    code.
789
790    This function never returns!
791
792    C prototype:
793       void asm_replacement_in(executionstate *es);
794
795 *******************************************************************************/
796
797 asm_replacement_in:
798         mov     a0,%rbp                     /* executionstate *es                 */
799
800         /* set new sp */
801         mov     (offes_sp)(%rbp),%rsp
802         
803         /* store address of new code */
804         push    (offes_pc)(%rbp)
805         
806         /* copy registers from execution state */
807         movq    (XMM0 *8+offes_fltregs)(%rbp),%xmm0
808         movq    (XMM1 *8+offes_fltregs)(%rbp),%xmm1
809         movq    (XMM2 *8+offes_fltregs)(%rbp),%xmm2
810         movq    (XMM3 *8+offes_fltregs)(%rbp),%xmm3
811         movq    (XMM4 *8+offes_fltregs)(%rbp),%xmm4
812         movq    (XMM5 *8+offes_fltregs)(%rbp),%xmm5
813         movq    (XMM6 *8+offes_fltregs)(%rbp),%xmm6
814         movq    (XMM7 *8+offes_fltregs)(%rbp),%xmm7
815         movq    (XMM8 *8+offes_fltregs)(%rbp),%xmm8
816         movq    (XMM9 *8+offes_fltregs)(%rbp),%xmm9
817         movq    (XMM10*8+offes_fltregs)(%rbp),%xmm10
818         movq    (XMM11*8+offes_fltregs)(%rbp),%xmm11
819         movq    (XMM12*8+offes_fltregs)(%rbp),%xmm12
820         movq    (XMM13*8+offes_fltregs)(%rbp),%xmm13
821         movq    (XMM14*8+offes_fltregs)(%rbp),%xmm14
822         movq    (XMM15*8+offes_fltregs)(%rbp),%xmm15
823
824         mov     (RAX*8+offes_intregs)(%rbp),%rax
825         mov     (RBX*8+offes_intregs)(%rbp),%rbx
826         mov     (RCX*8+offes_intregs)(%rbp),%rcx
827         mov     (RDX*8+offes_intregs)(%rbp),%rdx
828         mov     (RSI*8+offes_intregs)(%rbp),%rsi
829         mov     (RDI*8+offes_intregs)(%rbp),%rdi
830         mov     (R8 *8+offes_intregs)(%rbp),%r8
831         mov     (R9 *8+offes_intregs)(%rbp),%r9
832         mov     (R10*8+offes_intregs)(%rbp),%r10
833         mov     (R11*8+offes_intregs)(%rbp),%r11
834         mov     (R12*8+offes_intregs)(%rbp),%r12
835         mov     (R13*8+offes_intregs)(%rbp),%r13
836         mov     (R14*8+offes_intregs)(%rbp),%r14
837         mov     (R15*8+offes_intregs)(%rbp),%r15
838
839         mov     (RBP*8+offes_intregs)(%rbp),%rbp
840
841         /* jump to new code */
842         ret
843 #endif
844
845 /* TODO use move here ? */
846
847 asm_getclassvalues_atomic:
848 _crit_restart:
849 _crit_begin:
850         l       %r0,offbaseval(a0)
851         l       %r1,offdiffval(a0)
852         l       a3,offbaseval(a1)
853 _crit_end:
854         st      %r0,offcast_super_baseval(a2)
855         st      %r1,offcast_super_diffval(a2)
856         st      a3,offcast_sub_baseval(a2)
857         br      %r14
858
859         .data
860                 
861 asm_criticalsections:
862 #if defined(ENABLE_THREADS)
863         .long   _crit_begin
864         .long   _crit_end
865         .long   _crit_restart
866 #endif
867         .long 0
868
869
870 /*
871  * These are local overrides for various environment variables in Emacs.
872  * Please do not remove this and leave it at the end of the file, where
873  * Emacs will automagically detect them.
874  * ---------------------------------------------------------------------
875  * Local variables:
876  * mode: asm
877  * indent-tabs-mode: t
878  * c-basic-offset: 4
879  * tab-width: 4
880  * End:
881  * vim:noexpandtab:sw=4:ts=4:
882  */