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