8e9f02b2092805ee17568d781f827a96d93eb6db
[cacao.git] / src / vm / jit / alpha / asmpart.S
1 /* src/vm/jit/alpha/asmpart.S - Java-C interface functions for alpha
2
3    Copyright (C) 1996-2005, 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 8279 2007-08-09 09:36:57Z michi $
26
27 */
28
29
30 #include "config.h"
31
32 #include "vm/jit/alpha/md-abi.h"
33 #include "vm/jit/alpha/md-asm.h"
34
35 #include "vm/jit/abi-asm.h"
36 #include "vm/jit/methodheader.h"
37
38
39         .text
40         .set    noat
41         .set    noreorder
42
43
44 /* export functions ***********************************************************/
45
46         .globl asm_vm_call_method
47         .globl asm_vm_call_method_int
48         .globl asm_vm_call_method_long
49         .globl asm_vm_call_method_float
50         .globl asm_vm_call_method_double
51         .globl asm_vm_call_method_exception_handler
52         .globl asm_vm_call_method_end
53
54         .globl asm_call_jit_compiler
55
56         .globl asm_handle_exception
57         .globl asm_handle_nat_exception
58
59         .globl asm_abstractmethoderror
60
61         .globl asm_compare_and_swap
62         .globl asm_memory_barrier
63
64         .globl asm_md_init
65         .globl asm_cacheflush
66
67
68 /* asm_vm_call_method **********************************************************
69 *                                                                              *
70 *   This function calls a Java-method (which possibly needs compilation)       *
71 *   with up to 4 address parameters.                                           *
72 *                                                                              *
73 *   This functions calls the JIT-compiler which eventually translates the      *
74 *   method into machine code.                                                  *
75 *                                                                              *
76 *   C-prototype:                                                               *
77 *    javaobject_header *asm_calljavafunction (methodinfo *m,                   *
78 *         void *arg1, void *arg2, void *arg3, void *arg4);                     *
79 *                                                                              *
80 *******************************************************************************/
81
82         .ent    asm_vm_call_method
83
84         .align  3
85
86         .quad   0                           /* catch type all                     */
87         .quad   0                           /* handler pc                         */
88         .quad   0                           /* end pc                             */
89         .quad   0                           /* start pc                           */
90         .long   1                           /* extable size                       */
91         .long   0                           /* ALIGNMENT PADDING                  */
92         .quad   0                           /* line number table start            */
93         .quad   0                           /* line number table size             */
94         .long   0                           /* ALIGNMENT PADDING                  */
95         .long   0                           /* fltsave                            */
96         .long   1                           /* intsave                            */
97         .long   0                           /* isleaf                             */
98         .long   0                           /* IsSync                             */
99         .long   0                           /* frame size                         */
100         .quad   0                           /* codeinfo pointer                   */
101
102 asm_vm_call_method:
103 asm_vm_call_method_int:
104 asm_vm_call_method_long:
105 asm_vm_call_method_float:
106 asm_vm_call_method_double:
107         ldgp    gp,0(pv)
108         lda     sp,-5*8(sp)                 /* allocate stack space               */
109         stq     ra,0*8(sp)                  /* save return address                */
110         stq     gp,1*8(sp)                  /* save global pointer                */
111
112         stq     s0,3*8(sp)
113         stq     a0,4*8(sp)                  /* save method PV                     */
114
115         mov     a1,t0                       /* address of argument array          */
116         mov     a2,t1                       /* stack argument count               */
117         mov     sp,s0                       /* save stack pointer                 */
118
119         ldq     a0,0*8(t0)
120         ldq     a1,1*8(t0)
121         ldq     a2,2*8(t0)
122         ldq     a3,3*8(t0)
123         ldq     a4,4*8(t0)
124         ldq     a5,5*8(t0)
125
126         ldt     fa0,6*8(t0)
127         ldt     fa1,7*8(t0)
128         ldt     fa2,8*8(t0)
129         ldt     fa3,9*8(t0)
130         ldt     fa4,10*8(t0)
131         ldt     fa5,11*8(t0)
132
133         beq     t1,L_asm_vm_call_method_stack_copy_done
134
135         negq    t1,t2                       /* calculate stackframe size (* 8)    */
136         s8addq  t2,sp,sp                    /* create stackframe                  */
137         mov     sp,t2                       /* temporary stack pointer            */
138
139 L_asm_vm_call_method_stack_copy_loop:
140         ldq     t3,12*8(t0)                 /* load argument                      */
141         stq     t3,0(t2)                    /* store argument on stack            */
142
143         subq    t1,1,t1                     /* subtract 1 argument                */
144         addq    t0,8,t0                     /* load address of next argument      */
145         addq    t2,8,t2                     /* increase stack pointer             */
146
147         bgt     t1,L_asm_vm_call_method_stack_copy_loop
148
149 L_asm_vm_call_method_stack_copy_done:
150         lda     mptr,4*8(s0)                /* get address of PV                  */
151         ldq     pv,0*8(mptr)                /* load PV                            */
152         jmp     ra,(pv)
153 L_asm_vm_call_method_recompute_pv:
154         lda     pv,(asm_vm_call_method - L_asm_vm_call_method_recompute_pv)(ra)
155
156         mov     s0,sp                       /* restore stack pointer              */
157
158 L_asm_vm_call_method_recompute_return:
159         ldq     ra,0*8(sp)                  /* restore RA                         */
160         ldq     gp,1*8(sp)                  /* restore global pointer             */
161         ldq     s0,3*8(sp)
162
163         lda     sp,5*8(sp)                  /* free stack space                   */
164         jmp     zero,(ra)
165
166 asm_vm_call_method_exception_handler:
167         mov     s0,sp                       /* restore stack pointer              */
168         ldq     gp,1*8(sp)                  /* restore global pointer             */
169         mov     itmp1,a0
170         jsr     ra,builtin_throw_exception
171
172 asm_vm_call_method_end:                                 
173         br      L_asm_vm_call_method_recompute_return
174
175         .end    asm_vm_call_method
176
177
178 /* asm_call_jit_compiler *******************************************************
179
180    Invokes the compiler for untranslated Java methods.
181
182 *******************************************************************************/
183
184         .ent    asm_call_jit_compiler
185
186 asm_call_jit_compiler:
187         ldgp    gp,0(pv)
188         lda     sp,-(ARG_CNT+2)*8(sp) /* +2: keep stack 16-byte aligned           */
189
190         stq     ra,0*8(sp)            /* save return address                      */
191
192         SAVE_ARGUMENT_REGISTERS(1)    /* save 6 int/6 float argument registers    */
193
194         mov     itmp1,a0              /* pass methodinfo pointer                  */
195         mov     mptr,a1               /* pass method pointer                      */
196         lda     a2,(ARG_CNT+2)*8(sp)  /* pass java sp                             */
197         mov     ra,a3
198         jsr     ra,jit_asm_compile    /* call jit compiler                        */
199         mov     v0,pv
200
201         ldq     ra,0*8(sp)            /* load return address                      */
202
203         RESTORE_ARGUMENT_REGISTERS(1) /* restore 6 int/6 float argument registers */
204
205         lda     sp,(ARG_CNT+2)*8(sp)  /* remove stack frame                       */
206
207         beq     pv,L_asm_call_jit_compiler_exception
208
209         jmp     zero,(pv)             /* and call method, the method returns      */
210                                       /* directly to the caller (ra).             */
211
212 L_asm_call_jit_compiler_exception:
213         subq    sp,2*8,sp
214         stq     ra,0*8(sp)            /* save return address (xpc)                */
215         jsr     ra,exceptions_get_and_clear_exception
216         ldq     ra,0*8(sp)            /* restore return address (xpc)             */
217         addq    sp,2*8,sp
218
219         mov     v0,xptr               /* get exception                            */
220         subq    ra,4,xpc              /* exception address is ra - 4              */
221         br      L_asm_handle_nat_exception
222
223         .end    asm_call_jit_compiler
224
225
226 /* asm_handle_exception ********************************************************
227
228    This function handles an exception. It does not use the usual calling
229    conventions. The exception pointer is passed in REG_ITMP1 and the
230    pc from the exception raising position is passed in REG_ITMP2. It searches
231    the local exception table for a handler. If no one is found, it unwinds
232    stacks and continues searching the callers.
233
234    ATTENTION: itmp3 == gp!
235
236 *******************************************************************************/
237
238         .ent    asm_handle_nat_exception
239
240 asm_handle_nat_exception:
241 L_asm_handle_nat_exception:       /* required for PIC code                    */
242 L_asm_handle_exception_stack_loop:
243         lda     sp,-6*8(sp)                 /* keep stack 16-byte aligned         */
244         stq     xptr,0*8(sp)                /* save xptr                          */
245         stq     xpc,1*8(sp)                 /* save xpc                           */
246         stq     ra,3*8(sp)                  /* save RA                            */
247         stq     zero,4*8(sp)                /* save maybe-leaf flag (cleared)     */
248
249         mov     ra,a0                       /* pass RA                            */
250
251         br      ra,L_asm_handle_exception_load_gp
252 L_asm_handle_exception_load_gp:
253         ldgp    gp,0(ra)                    /* load gp                            */
254
255         jsr     ra,md_codegen_get_pv_from_pc/* get PV from RA                     */
256         stq     v0,2*8(sp)                  /* save PV                            */
257
258         ldq     a0,0*8(sp)                  /* pass xptr                          */
259         ldq     a1,1*8(sp)                  /* pass xpc                           */
260         mov     v0,a2                       /* pass PV                            */
261         addq    sp,6*8,a3                   /* pass Java SP                       */
262
263         br      L_asm_handle_exception_continue
264
265         .aent    asm_handle_exception
266
267 asm_handle_exception:
268 L_asm_handle_exception:                 /* required for PIC code              */
269         lda     sp,-(ARG_CNT+TMP_CNT)*8(sp) /* create maybe-leaf stackframe       */
270
271         SAVE_ARGUMENT_REGISTERS(0)          /* we save arg and temp registers in  */
272         SAVE_TEMPORARY_REGISTERS(ARG_CNT)   /* case this is a leaf method         */
273
274         lda     sp,-6*8(sp)                 /* keep stack 16-byte aligned         */
275         stq     xptr,0*8(sp)                /* save xptr                          */
276         stq     pv,2*8(sp)                  /* save PV                            */
277         stq     ra,3*8(sp)                  /* save RA                            */
278         lda     t0,1(zero)                  /* set maybe-leaf flag                */
279         stq     t0,4*8(sp)                  /* save maybe-leaf flag               */
280
281         br      ra,L_asm_handle_exception_load_gp_2
282 L_asm_handle_exception_load_gp_2:
283         ldgp    gp,0(ra)                    /* load gp                            */
284
285         mov     xptr,a0                     /* pass xptr                          */
286         mov     xpc,a1                      /* pass xpc                           */
287         mov     pv,a2                       /* pass PV                            */
288         lda     a3,(ARG_CNT+TMP_CNT+6)*8(sp)/* pass Java SP                       */
289
290 L_asm_handle_exception_continue:
291         jsr     ra,exceptions_handle_exception
292
293         beq     v0,L_asm_handle_exception_not_catched
294
295         mov     v0,xpc                      /* move handlerpc into xpc            */
296         ldq     xptr,0*8(sp)                /* restore xptr                       */
297         ldq     pv,2*8(sp)                  /* restore PV                         */
298         ldq     ra,3*8(sp)                  /* restore RA                         */
299         ldq     t0,4*8(sp)                  /* get maybe-leaf flag                */
300         lda     sp,6*8(sp)                  /* free stack frame                   */
301
302         beq     t0,L_asm_handle_exception_no_leaf
303
304         RESTORE_ARGUMENT_REGISTERS(0)       /* if this is a leaf method, we have  */
305         RESTORE_TEMPORARY_REGISTERS(ARG_CNT)/* to restore arg and temp registers  */
306         
307         lda     sp,(ARG_CNT+TMP_CNT)*8(sp)  /* remove maybe-leaf stackframe       */
308
309 L_asm_handle_exception_no_leaf:
310         jmp     zero,(xpc)                  /* jump to the handler                */
311
312 L_asm_handle_exception_not_catched:
313         ldq     xptr,0*8(sp)                /* restore xptr                       */
314         ldq     pv,2*8(sp)                  /* restore PV                         */
315         ldq     ra,3*8(sp)                  /* restore RA                         */
316         ldq     t0,4*8(sp)                  /* get maybe-leaf flag                */
317         lda     sp,6*8(sp)
318
319         beq     t0,L_asm_handle_exception_no_leaf_stack
320
321         lda     sp,(ARG_CNT+TMP_CNT)*8(sp)  /* remove maybe-leaf stackframe       */
322         mov     zero,t0                     /* clear the maybe-leaf flag          */
323
324 L_asm_handle_exception_no_leaf_stack:
325         ldl     t1,FrameSize(pv)            /* get frame size                     */
326         addq    t1,sp,t1                    /* pointer to save area               */
327
328         ldl     t2,IsLeaf(pv)               /* is leaf procedure                  */
329         bne     t2,L_asm_handle_exception_no_ra_restore
330
331         ldq     ra,-1*8(t1)                 /* restore ra                         */
332         subq    t1,8,t1                     /* t1--                               */
333
334 L_asm_handle_exception_no_ra_restore:
335         mov     ra,xpc                      /* the new xpc is ra                  */
336         ldl     t2,IntSave(pv)              /* t2 = saved int register count      */
337         br      t3,ex_int1                  /* t3 = current pc                    */
338 ex_int1:
339         lda     t3,(ex_int2 - ex_int1)(t3)
340         negl    t2,t2                       /* negate register count              */
341         s4addq  t2,t3,t3                    /* t2 = IntSave - register count * 4  */
342         jmp     zero,(t3)                   /* jump to save position              */
343
344         ldq     s0,-7*8(t1)
345         ldq     s1,-6*8(t1)
346         ldq     s2,-5*8(t1)
347         ldq     s3,-4*8(t1)
348         ldq     s4,-3*8(t1)
349         ldq     s5,-2*8(t1)
350         ldq     s6,-1*8(t1)
351
352 ex_int2:
353         s8addq  t2,t1,t1                    /* t1 = t1 - 8 * register count       */
354
355         ldl     t2,FltSave(pv)              /* t2 = saved flt register count      */
356         br      t3,ex_flt1                  /* t3 = current pc                    */
357 ex_flt1:
358         lda     t3,(ex_flt2 - ex_flt1)(t3)
359         negl    t2,t2                       /* negate register count              */
360         s4addq  t2,t3,t3                    /* t2 = FltSave - 4 * register count  */
361         jmp     zero,(t3)                   /* jump to save position              */
362
363         ldt     fs0,-8*8(t1)
364         ldt     fs1,-7*8(t1)
365         ldt     fs2,-6*8(t1)
366         ldt     fs3,-5*8(t1)
367         ldt     fs4,-4*8(t1)
368         ldt     fs5,-3*8(t1)
369         ldt     fs6,-2*8(t1)
370         ldt     fs7,-1*8(t1)
371
372 ex_flt2:
373         ldl     t1,FrameSize(pv)            /* get frame size                     */
374         addq    sp,t1,sp                    /* unwind stack                       */
375         br      L_asm_handle_exception_stack_loop
376
377         .end    asm_handle_nat_exception
378
379
380 /* asm_abstractmethoderror *****************************************************
381
382    Creates and throws an AbstractMethodError.
383
384 *******************************************************************************/
385
386         .ent    asm_abstractmethoderror
387
388 asm_abstractmethoderror:
389         subq    sp,2*8,sp                   /* create stackframe                  */
390         stq     ra,0*8(sp)                  /* save return address                */
391         addq    sp,2*8,a0                   /* pass java sp                       */
392         mov     ra,a1                       /* pass exception address             */
393         jsr     ra,exceptions_asm_new_abstractmethoderror
394         ldq     ra,0*8(sp)                  /* restore return address             */
395         addq    sp,2*8,sp                   /* remove stackframe                  */
396
397         mov     v0,xptr                     /* get exception pointer              */
398         subq    ra,4,xpc                    /* exception address is ra - 4        */
399         br      L_asm_handle_nat_exception
400
401         .end    asm_abstractmethoderror
402
403
404 /* asm_compare_and_swap ********************************************************
405
406    Does an atomic compare and swap.  Required for the lock
407    implementation.
408
409    Atomically do the following: Check if the location still contains
410    `oldval`. If so, replace it by `newval` and return `oldval`.
411
412    RETURN VALUE:
413        the old value at *p
414
415    long compare_and_swap(volatile long *p, long oldval, long newval);
416
417 *******************************************************************************/
418
419         .ent    asm_compare_and_swap
420
421 asm_compare_and_swap:
422 1:
423         ldq_l   v0,0(a0)
424         cmpeq   v0,a1,t0
425         beq     t0,2f
426         mov     a2,t0
427         stq_c   t0,0(a0)
428         beq     t0,1b
429 2:
430         jmp     zero,(ra)
431
432         .end    asm_compare_and_swap
433
434
435 /* asm_memory_barrier **********************************************************
436
437    A memory barrier for the Java Memory Model.
438
439 *******************************************************************************/
440
441         .ent    asm_memory_barrier
442
443 asm_memory_barrier:
444         mb
445         jmp     zero,(ra)
446
447         .end    asm_memory_barrier
448
449
450 /* asm_md_init *****************************************************************
451
452    Initialize machine dependent stuff.
453
454    Determines if the byte support instruction set (21164a and higher)
455    is available.
456
457 *******************************************************************************/
458
459         .ent    asm_md_init
460
461 asm_md_init:
462         .long   0x47e03c20                  /* amask   1,v0                       */
463         jmp     zero,(ra)                   /* return                             */
464
465         .end    asm_md_init
466
467
468 /* asm_cacheflush **************************************************************
469
470    XXX
471
472 *******************************************************************************/
473
474         .ent    asm_cacheflush
475
476 asm_cacheflush:
477         call_pal PAL_imb              /* synchronize instruction cache            */
478         jmp     zero,(ra)
479
480         .end    asm_cacheflush
481
482
483 /* disable exec-stacks ********************************************************/
484
485 #if defined(__linux__) && defined(__ELF__)
486         .section .note.GNU-stack,"",%progbits
487 #endif
488
489
490 /*
491  * These are local overrides for various environment variables in Emacs.
492  * Please do not remove this and leave it at the end of the file, where
493  * Emacs will automagically detect them.
494  * ---------------------------------------------------------------------
495  * Local variables:
496  * mode: asm
497  * indent-tabs-mode: t
498  * c-basic-offset: 4
499  * tab-width: 4
500  * End:
501  * vim:noexpandtab:sw=4:ts=4:
502  */