* src/vm/jit/alpha/asmpart.S (asm_calljavafunction): Removed.
[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 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    Contact: cacao@cacaojvm.org
26
27    Authors: Andreas Krall
28             Reinhard Grafl
29
30    Changes: Joseph Wenninger
31             Christian Thalinger
32
33    $Id: asmpart.S 4561 2006-03-05 23:53:19Z twisti $
34
35 */
36
37
38 #include "config.h"
39
40 #include "vm/jit/alpha/md-abi.h"
41 #include "vm/jit/alpha/md-asm.h"
42 #include "vm/jit/alpha/offsets.h"
43
44 #include "vm/jit/abi.h"
45 #include "vm/jit/methodheader.h"
46
47
48         .text
49         .set    noat
50         .set    noreorder
51
52
53 /********************* exported functions and variables ***********************/
54
55         .globl asm_md_init
56
57         .globl asm_sync_instruction_cache
58
59         .globl asm_vm_call_method
60         .globl asm_vm_call_method_int
61         .globl asm_vm_call_method_long
62         .globl asm_vm_call_method_float
63         .globl asm_vm_call_method_double
64
65         .globl asm_call_jit_compiler
66         .globl asm_handle_exception
67         .globl asm_handle_nat_exception
68
69         .globl asm_wrapper_patcher
70
71         .globl asm_perform_threadswitch
72         .globl asm_initialize_thread_stack
73         .globl asm_switchstackandcall
74         .globl asm_criticalsections
75         .globl asm_getclassvalues_atomic
76
77
78 /* asm_sync_instruction_cache **************************************************
79
80    XXX
81
82 *******************************************************************************/
83
84         .ent    asm_sync_instruction_cache
85
86 asm_sync_instruction_cache:
87         call_pal PAL_imb              /* synchronize instruction cache            */
88         jmp     zero,(ra)
89
90         .end    asm_sync_instruction_cache
91
92
93 /* asm_md_init *****************************************************************
94
95    Initialize machine dependent stuff.
96
97    Determines if the byte support instruction set (21164a and higher)
98    is available.
99
100 *******************************************************************************/
101
102         .ent    asm_md_init
103
104 asm_md_init:
105
106         .long   0x47e03c20                  /* amask   1,v0                       */
107         jmp     zero,(ra)                   /* return                             */
108
109         .end    asm_md_init
110
111
112 /* asm_vm_call_method **********************************************************
113 *                                                                              *
114 *   This function calls a Java-method (which possibly needs compilation)       *
115 *   with up to 4 address parameters.                                           *
116 *                                                                              *
117 *   This functions calls the JIT-compiler which eventually translates the      *
118 *   method into machine code.                                                  *
119 *                                                                              *
120 *   C-prototype:                                                               *
121 *    javaobject_header *asm_calljavafunction (methodinfo *m,                   *
122 *         void *arg1, void *arg2, void *arg3, void *arg4);                     *
123 *                                                                              *
124 *******************************************************************************/
125
126         .ent    asm_vm_call_method
127
128         .align  3
129
130         .quad   0                           /* catch type all                     */
131         .quad   calljava_xhandler2          /* handler pc                         */
132         .quad   calljava_xhandler2          /* end pc                             */
133         .quad   asm_vm_call_method          /* start pc                           */
134         .long   1                           /* extable size                       */
135         .long   0                           /* ALIGNMENT PADDING                  */
136         .quad   0                           /* line number table start            */
137         .quad   0                           /* line number table size             */
138         .long   0                           /* ALIGNMENT PADDING                  */
139         .long   0                           /* fltsave                            */
140         .long   1                           /* intsave                            */
141         .long   0                           /* isleaf                             */
142         .long   0                           /* IsSync                             */
143         .long   0                           /* frame size                         */
144         .quad   0                           /* method pointer (pointer to name)   */
145
146 asm_vm_call_method:
147 asm_vm_call_method_int:
148 asm_vm_call_method_long:
149 asm_vm_call_method_float:
150 asm_vm_call_method_double:
151         ldgp    gp,0(pv)
152         lda     sp,-5*8(sp)               /* allocate stack space                 */
153         stq     ra,0*8(sp)                /* save return address                  */
154         stq     gp,1*8(sp)                /* save global pointer                  */
155         stq     s6,3*8(sp)
156
157         stq     a0,4*8(sp)                /* save method pointer for compiler     */
158
159         mov     a2,t0                     /* pointer to arg block                 */
160         mov     a1,s6                     /* arg count                            */
161
162         ble     s6,calljava_argsloaded
163         lda     s6,-1(s6)
164         ldq     a0,offvmargdata(t0)
165         ldt     $f16,offvmargdata(t0)
166         ble     s6,calljava_argsloaded
167
168         lda     s6,-1(s6)
169         ldq     a1,offvmargdata+sizevmarg*1(t0)
170         ldt     $f17,offvmargdata+sizevmarg*1(t0)
171         ble     s6,calljava_argsloaded
172
173         lda     s6,-1(s6)
174         ldq     a2,offvmargdata+sizevmarg*2(t0)
175         ldt     $f18,offvmargdata+sizevmarg*2(t0)
176         ble     s6,calljava_argsloaded
177
178         lda     s6,-1(s6)
179         ldq     a3,offvmargdata+sizevmarg*3(t0)
180         ldt     $f19,offvmargdata+sizevmarg*3(t0)
181         ble     s6,calljava_argsloaded
182
183         lda     s6,-1(s6)
184         ldq     a4,offvmargdata+sizevmarg*4(t0)
185         ldt     $f20,offvmargdata+sizevmarg*4(t0)
186         ble     s6,calljava_argsloaded
187
188         lda     s6,-1(s6)
189         ldq     a5,offvmargdata+sizevmarg*5(t0)
190         ldt     $f21,offvmargdata+sizevmarg*5(t0)
191 calljava_argsloaded:
192         mov     sp,t4
193         ble     s6,calljava_nocopy
194         negq    s6,t1
195         s8addq  t1,sp,sp
196         s8addq  t1,t4,t2
197
198 calljava_copyloop:
199         ldq     t3,offvmargdata+sizevmarg*6(t0)
200         stq     t3,0(t2)
201         lda     t1,1(t1)
202         lda     t0,sizevmarg(t0)
203         lda     t2,8(t2)
204         bne     t1,calljava_copyloop
205
206 calljava_nocopy:
207         ldq     itmp1,4*8(t4)             /* pass method pointer via itmp1        */
208
209         lda     mptr,asm_call_jit_compiler/* fake virtual function call (2 instr) */
210         stq     mptr,2*8(t4)              /* store function address               */
211         lda     mptr,1*8(t4)              /* set method pointer                   */
212
213         ldq     pv,1*8(mptr)              /* method call as in Java               */
214         jmp     ra,(pv)                   /* call JIT compiler                    */
215 calljava_jit2:
216         lda     pv,(asm_vm_call_method - calljava_jit2)(ra)
217
218         s8addq  s6,sp,sp
219 calljava_return2:
220         ldq     ra,0*8(sp)                /* restore return address               */
221         ldq     gp,1*8(sp)                /* restore global pointer               */
222         ldq     s6,3*8(sp)
223         lda     sp,5*8(sp)                /* free stack space                     */
224
225 calljava_ret2:
226         jmp     zero,(ra)
227
228 calljava_xhandler2:
229         s8addq  s6,sp,sp
230         ldq     gp,1*8(sp)                /* restore global pointer               */
231         mov     itmp1,a0
232         jsr     ra,builtin_throw_exception
233         ldq     ra,0*8(sp)                /* restore return address               */
234         ldq     s6,3*8(sp)
235         lda     sp,5*8(sp)                /* free stack space                     */
236         mov     zero,v0                   /* return NULL                          */
237         jmp     zero,(ra)
238
239         .end    asm_vm_call_method
240
241
242 /****************** function asm_call_jit_compiler *****************************
243 *                                                                              *
244 *   invokes the compiler for untranslated JavaVM methods.                      *
245 *                                                                              *
246 *   Register R0 contains a pointer to the method info structure (prepared      *
247 *   by createcompilerstub). Using the return address in R26 and the            *
248 *   offset in the LDA instruction or using the value in methodptr R28 the      *
249 *   patching address for storing the method address can be computed:           *
250 *                                                                              *
251 *   method address was either loaded using                                     *
252 *   M_LDQ (REG_PV, REG_PV, a)        ; invokestatic/special    ($27)           *
253 *   M_LDA (REG_PV, REG_RA, low)                                                *
254 *   M_LDAH(REG_PV, REG_RA, high)     ; optional                                *
255 *   or                                                                         *
256 *   M_LDQ (REG_PV, REG_METHODPTR, m) ; invokevirtual/interface ($28)           *
257 *   in the static case the method pointer can be computed using the            *
258 *   return address and the lda function following the jmp instruction          *
259 *                                                                              *
260 *******************************************************************************/
261
262         .ent    asm_call_jit_compiler
263
264 asm_call_jit_compiler:
265         ldgp    gp,0(pv)
266         lda     sp,-(15*8+sizestackframeinfo)(sp) /* reserve stack space          */
267
268         SAVE_ARGUMENT_REGISTERS(0)    /* save 6 int/6 float argument registers    */
269
270         stq     mptr,12*8(sp)         /* save method pointer                      */
271         stq     ra,13*8(sp)           /* save return address                      */
272         stq     itmp1,14*8(sp)        /* save methodinfo pointer                  */
273
274         lda     a0,15*8(sp)           /* create stackframe info                   */
275         mov     zero,a1               /* we don't have pv handy                   */
276         lda     a2,15*8+sizestackframeinfo(sp) /* pass java sp                    */
277         mov     ra,a3                 /* pass Java ra                             */
278         mov     a3,a4                 /* xpc is equal to ra                       */
279         jsr     ra,stacktrace_create_extern_stackframeinfo
280         ldgp    gp,0(ra)
281
282         ldq     a0,14*8(sp)           /* pass methodinfo pointer                  */
283         jsr     ra,jit_compile        /* call jit compiler                        */
284         ldgp    gp,0(ra)
285         stq     v0,14*8(sp)           /* save return value                        */
286
287         ldq     a0,13*8(sp)           /* pass return address                      */
288         lda     a1,15*8(sp)           /* pass stackframeinfo (for PV)             */
289         ldq     a2,12*8(sp)           /* pass method pointer                      */
290         jsr     ra,md_assembler_get_patch_address /* get address of patch position*/
291         ldgp    gp,0(ra)
292         stq     v0,12*8(sp)           /* store patch address for later use        */
293
294         lda     a0,15*8(sp)           /* remove stackframe info                   */
295         jsr     ra,stacktrace_remove_stackframeinfo
296         ldgp    gp,0(ra)
297
298         RESTORE_ARGUMENT_REGISTERS(0) /* restore 6 int/6 float argument registers */
299
300         ldq     t0,12*8(sp)           /* load patch address                       */
301         ldq     ra,13*8(sp)           /* load return address                      */
302         ldq     pv,14*8(sp)           /* restore method entry point               */
303         lda     sp,15*8+sizestackframeinfo(sp) /* deallocate stack area           */
304
305         beq     pv,L_asm_call_jit_compiler_exception
306
307         stq     pv,0(t0)              /* patch method entry point                 */
308
309         call_pal PAL_imb              /* synchronise instruction cache            */
310
311         jmp     zero,(pv)             /* and call method, the method returns      */
312                                       /* directly to the caller (ra).             */
313
314 L_asm_call_jit_compiler_exception:
315 #if defined(USE_THREADS) && defined(NATIVE_THREADS)
316         subq    sp,1*8,sp
317         stq     ra,0*8(sp)            /* save return address (xpc)                */
318         jsr     ra,builtin_asm_get_exceptionptrptr
319         ldq     ra,0*8(sp)           /* restore return address (xpc)             */
320         addq    sp,1*8,sp
321 #else
322         lda     v0,_exceptionptr
323 #endif
324         ldq     xptr,0(v0)            /* get the exception pointer                */
325         stq     zero,0(v0)            /* clear the exception pointer              */
326
327         subq    ra,4,xpc
328         br      L_asm_handle_nat_exception
329
330         .end    asm_call_jit_compiler
331
332
333 /* asm_handle_exception ********************************************************
334
335    This function handles an exception. It does not use the usual calling
336    conventions. The exception pointer is passed in REG_ITMP1 and the
337    pc from the exception raising position is passed in REG_ITMP2. It searches
338    the local exception table for a handler. If no one is found, it unwinds
339    stacks and continues searching the callers.
340
341    ATTENTION: itmp3 == gp!
342
343 *******************************************************************************/
344
345         .ent    asm_handle_nat_exception
346
347 asm_handle_nat_exception:
348 L_asm_handle_nat_exception:       /* required for PIC code                    */
349         ldl     t0,0(ra)              /* load instruction LDA PV,xxx(RA)          */
350         sll     t0,48,t0
351         sra     t0,48,t0              /* isolate offset                           */
352         addq    t0,ra,pv              /* compute update address                   */
353         ldl     t0,4(ra)              /* load instruction LDAH PV,xxx(PV)         */
354         srl     t0,16,t0              /* isolate instruction code                 */
355         lda     t0,-0x177b(t0)        /* test for LDAH                            */
356         bne     t0,L_asm_handle_exception
357         ldl     t0,4(ra)              /* load instruction LDAH PV,xxx(PV)         */
358         sll     t0,16,t0              /* compute high offset                      */
359         addl    t0,0,t0               /* sign extend high offset                  */
360         addq    t0,pv,pv              /* compute update address                   */
361
362         .aent    asm_handle_exception
363
364 asm_handle_exception:
365 L_asm_handle_exception:                 /* required for PIC code              */
366         lda     sp,-(ARG_CNT+TMP_CNT)*8(sp) /* create maybe-leaf stackframe       */
367
368         SAVE_ARGUMENT_REGISTERS(0)          /* we save arg and temp registers in  */
369         SAVE_TEMPORARY_REGISTERS(ARG_CNT)   /* case this is a leaf method         */
370
371         lda     a3,(ARG_CNT+TMP_CNT)*8(zero)/* prepare a3 for handle_exception */
372         lda     a4,1(zero)                  /* set maybe-leaf flag                */
373
374 L_asm_handle_exception_stack_loop:
375         lda     sp,-5*8(sp)                 /* allocate stack                     */
376         stq     xptr,0*8(sp)                /* save exception pointer             */
377         stq     xpc,1*8(sp)                 /* save exception pc                  */
378         stq     pv,2*8(sp)                  /* save data segment pointer          */
379         stq     ra,3*8(sp)                  /* save return address                */
380         addq    a3,sp,a3                    /* calculate Java sp into a3...       */
381         addq    a3,5*8,a3
382         stq     a4,4*8(sp)                  /* save maybe-leaf flag               */
383
384         br      ra,L_asm_handle_exception_load_gp /* set ra for gp loading        */
385 L_asm_handle_exception_load_gp:
386         ldgp    gp,0(ra)                    /* load gp                            */
387
388         mov     xptr,a0                     /* pass exception pointer             */
389         mov     xpc,a1                      /* pass exception pc                  */
390         mov     pv,a2                       /* pass data segment pointer          */
391                                             /* a3 is still set                    */
392         jsr     ra,exceptions_handle_exception
393
394         beq     v0,L_asm_handle_exception_not_catched
395
396         mov     v0,xpc                      /* move handlerpc into xpc            */
397         ldq     xptr,0*8(sp)                /* restore exception pointer          */
398         ldq     pv,2*8(sp)                  /* restore data segment pointer       */
399         ldq     ra,3*8(sp)                  /* restore return address             */
400         ldq     a4,4*8(sp)                  /* get maybe-leaf flag                */
401         lda     sp,5*8(sp)                  /* free stack frame                   */
402
403         beq     a4,L_asm_handle_exception_no_leaf
404
405         RESTORE_ARGUMENT_REGISTERS(0)       /* if this is a leaf method, we have  */
406         RESTORE_TEMPORARY_REGISTERS(ARG_CNT)/* to restore arg and temp registers  */
407         
408         lda     sp,(ARG_CNT+TMP_CNT)*8(sp)  /* remove maybe-leaf stackframe       */
409
410 L_asm_handle_exception_no_leaf:
411         jmp     zero,(xpc)                  /* jump to the handler                */
412
413 L_asm_handle_exception_not_catched:
414         ldq     xptr,0*8(sp)                /* restore exception pointer          */
415         ldq     pv,2*8(sp)                  /* restore data segment pointer       */
416         ldq     ra,3*8(sp)                  /* restore return address             */
417         ldq     a4,4*8(sp)                  /* get maybe-leaf flag                */
418         lda     sp,5*8(sp)
419
420         beq     a4,L_asm_handle_exception_no_leaf_stack
421
422         lda     sp,(ARG_CNT+TMP_CNT)*8(sp)  /* remove maybe-leaf stackframe       */
423         mov     zero,a4                     /* clear the maybe-leaf flag          */
424
425 L_asm_handle_exception_no_leaf_stack:
426         ldl     t0,FrameSize(pv)            /* get frame size                     */
427         addq    t0,sp,t0                    /* pointer to save area               */
428
429         ldl     t1,IsLeaf(pv)               /* is leaf procedure                  */
430         bne     t1,L_asm_handle_exception_no_ra_restore
431
432         ldq     ra,-1*8(t0)                 /* restore ra                         */
433         subq    t0,8,t0                     /* t0--                               */
434
435 L_asm_handle_exception_no_ra_restore:
436         mov     ra,xpc                      /* the new xpc is ra                  */
437         ldl     t1,IntSave(pv)              /* t1 = saved int register count      */
438         br      t2,ex_int1                  /* t2 = current pc                    */
439 ex_int1:
440         lda     t2,(ex_int2-ex_int1)(t2)
441         negl    t1,t1                       /* negate register count              */
442         s4addq  t1,t2,t2                    /* t2 = IntSave - register count * 4  */
443         jmp     zero,(t2)                   /* jump to save position              */
444
445         ldq     s0,-7*8(t0)
446         ldq     s1,-6*8(t0)
447         ldq     s2,-5*8(t0)
448         ldq     s3,-4*8(t0)
449         ldq     s4,-3*8(t0)
450         ldq     s5,-2*8(t0)
451         ldq     s6,-1*8(t0)
452
453 ex_int2:
454         s8addq  t1,t0,t0                    /* t0 = t0 - 8 * register count       */
455
456         ldl     t1,FltSave(pv)              /* t1 = saved flt register count      */
457         br      t2,ex_flt1                  /* t2 = current pc                    */
458 ex_flt1:
459         lda     t2,(ex_flt2-ex_flt1)(t2)
460         negl    t1,t1                       /* negate register count              */
461         s4addq  t1,t2,t2                    /* t2 = FltSave - 4 * register count  */
462         jmp     zero,(t2)                   /* jump to save position              */
463
464         ldt     fs0,-8*8(t0)
465         ldt     fs1,-7*8(t0)
466         ldt     fs2,-6*8(t0)
467         ldt     fs3,-5*8(t0)
468         ldt     fs4,-4*8(t0)
469         ldt     fs5,-3*8(t0)
470         ldt     fs6,-2*8(t0)
471         ldt     fs7,-1*8(t0)
472
473 ex_flt2:
474         ldl     t0,FrameSize(pv)            /* get frame size                     */
475         addq    sp,t0,sp                    /* unwind stack                       */
476         mov     zero,a3                     /* prepare a3 for handle_exception    */
477
478         ldl     t0,0(ra)              /* load instruction LDA PV,xxx(RA)          */
479         sll     t0,48,t0
480         sra     t0,48,t0              /* isolate offset                           */
481         addq    t0,ra,pv              /* compute update address                   */
482         ldl     t0,4(ra)              /* load instruction LDAH PV,xxx(PV)         */
483         srl     t0,16,t0              /* isolate instruction code                 */
484         lda     t0,-0x177b(t0)        /* test for LDAH                            */
485         bne     t0,L_asm_handle_exception_stack_loop
486         ldl     t0,4(ra)              /* load instruction LDAH PV,xxx(RA)         */
487         sll     t0,16,t0              /* compute high offset                      */
488         addl    t0,0,t0               /* sign extend high offset                  */
489         addq    t0,pv,pv              /* compute update address                   */
490
491         br      L_asm_handle_exception_stack_loop
492
493         .end    asm_handle_nat_exception
494
495
496 /* asm_wrapper_patcher *********************************************************
497
498    XXX
499
500    Stack layout:
501      40   return address into JIT code (patch position)
502      32   pointer to virtual java_objectheader
503      24   machine code (which is patched back later)
504      16   unresolved class/method/field reference
505       8   data segment displacement from load instructions
506       0   patcher function pointer to call (pv afterwards)
507
508    ATTENTION: itmp3 == gp! But we don't need gp do call the patcher function.
509
510 *******************************************************************************/
511                 
512         .ent    asm_wrapper_patcher
513
514 asm_wrapper_patcher:
515         lda     sp,-((2+12+27+4)*8+sizestackframeinfo)(sp) /* create stack frame  */
516
517         SAVE_RETURN_REGISTERS(0)      /* save 1 int/1 float return registers      */
518         SAVE_ARGUMENT_REGISTERS(2)    /* save 6 int/6 float argument registers    */
519         SAVE_TEMPORARY_REGISTERS(14)  /* save 11 int/16 float temporary registers */
520
521         stq     itmp1,(2+12+27+0)*8(sp) /* save itmp1                             */
522         stq     itmp2,(2+12+27+1)*8(sp) /* save itmp2                             */
523         stq     ra,(2+12+27+2)*8(sp)  /* save method return address (for leafs)   */
524         stq     pv,(2+12+27+3)*8(sp)  /* save pv of calling java function         */
525
526         br      ra,L_asm_wrapper_patcher_load_gp
527 L_asm_wrapper_patcher_load_gp:
528         ldgp    gp,0(ra)              /* load gp (it's not set correctly in jit)  */
529
530         lda     a0,(2+12+27+4)*8(sp)  /* create stackframe info                   */
531         mov     pv,a1                 /* pass java pv                             */
532         lda     a2,((6+2+12+27+4)*8+sizestackframeinfo)(sp) /* pass java sp       */
533         ldq     a3,(2+12+27+2)*8(sp)  /* this is correct for leafs                */
534         ldq     a4,((5+2+12+27+4)*8+sizestackframeinfo)(sp) /* pass xpc           */
535         jsr     ra,stacktrace_create_extern_stackframeinfo
536         ldgp    gp,0(ra)
537
538         lda     a0,((0+2+12+27+4)*8+sizestackframeinfo)(sp) /* pass sp            */
539         ldq     pv,((0+2+12+27+4)*8+sizestackframeinfo)(sp) /* get function       */
540         ldq     itmp1,(2+12+27+3)*8(sp) /* save pv to the position of fp          */
541         stq     itmp1,((0+2+12+27+4)*8+sizestackframeinfo)(sp)
542         jmp     ra,(pv)               /* call the patcher function                */
543         ldgp    gp,0(ra)
544         stq     v0,((0+2+12+27+4)*8+sizestackframeinfo)(sp) /* save return value  */
545
546         lda     a0,(2+12+27+4)*8(sp)  /* remove stackframe info                   */
547         jsr     ra,stacktrace_remove_stackframeinfo
548         ldgp    gp,0(ra)
549
550         RESTORE_RETURN_REGISTERS(0)   /* restore 1 int/1 float return registers   */
551         RESTORE_ARGUMENT_REGISTERS(2) /* restore 6 int/6 float argument registers */
552         RESTORE_TEMPORARY_REGISTERS(14) /* restore 11 integer temporary registers */
553
554         ldq     itmp1,(2+12+27+0)*8(sp) /* restore itmp1                          */
555         ldq     itmp2,(2+12+27+1)*8(sp) /* restore itmp2                          */
556         ldq     ra,(2+12+27+2)*8(sp)  /* restore method return address (for leafs)*/
557         ldq     pv,(2+12+27+3)*8(sp)  /* restore pv of calling java function      */
558
559         ldq     itmp3,((0+2+12+27+4)*8+sizestackframeinfo)(sp) /* get return value*/
560         beq     itmp3,L_asm_wrapper_patcher_exception
561
562         ldq     itmp3,((5+2+12+27+4)*8+sizestackframeinfo)(sp)/* get RA to JIT    */
563         lda     sp,((6+2+12+27+4)*8+sizestackframeinfo)(sp) /* remove stack frame */
564
565         jmp     zero,(itmp3)          /* jump to new patched code                 */
566
567 L_asm_wrapper_patcher_exception:
568         ldq     xpc,((5+2+12+27+4)*8+sizestackframeinfo)(sp) /* RA is xpc         */
569         lda     sp,((6+2+12+27+4)*8+sizestackframeinfo)(sp) /* remove stack frame */
570
571         br      itmp1,L_asm_wrapper_patcher_exception_load_gp
572 L_asm_wrapper_patcher_exception_load_gp:
573         ldgp    gp,0(itmp1)           /* itmp3 == gp, load the current gp         */
574
575 #if defined(USE_THREADS) && defined(NATIVE_THREADS)
576         subq    sp,3*8,sp
577         stq     xpc,0*8(sp)           /* save return address (xpc)                */
578         stq     ra,1*8(sp)
579         stq     pv,2*8(sp)
580         jsr     ra,builtin_asm_get_exceptionptrptr
581         ldq     xpc,0*8(sp)           /* restore return address (xpc)             */
582         ldq     ra,1*8(sp)
583         ldq     pv,2*8(sp)
584         addq    sp,3*8,sp
585 #else
586         lda     v0,_exceptionptr
587 #endif
588         ldq     xptr,0(v0)            /* get the exception pointer                */
589         stq     zero,0(v0)            /* clear the exception pointer              */
590         br      L_asm_handle_exception/* we have the pv of the calling java func. */
591
592         .end    asm_wrapper_patcher
593
594                 
595 /******************* function asm_initialize_thread_stack **********************
596 *                                                                              *
597 *   initialized a thread stack                                                 *
598 *                                                                              *
599 *******************************************************************************/
600
601         .ent    asm_initialize_thread_stack
602
603 asm_initialize_thread_stack:
604         lda     a1,-128(a1)
605         stq     zero, 0(a1)
606         stq     zero, 8(a1)
607         stq     zero, 16(a1)
608         stq     zero, 24(a1)
609         stq     zero, 32(a1)
610         stq     zero, 40(a1)
611         stq     zero, 48(a1)
612         stt     fzero, 56(a1)
613         stt     fzero, 64(a1)
614         stt     fzero, 72(a1)
615         stt     fzero, 80(a1)
616         stt     fzero, 88(a1)
617         stt     fzero, 96(a1)
618         stt     fzero, 104(a1)
619         stt     fzero, 112(a1)
620         stq     a0, 120(a1)
621         mov     a1, v0
622         jmp     zero,(ra)
623
624         .end    asm_initialize_thread_stack
625
626
627 /******************* function asm_perform_threadswitch *************************
628 *                                                                              *
629 *   void asm_perform_threadswitch (u1 **from, u1 **to, u1 **stackTop);         *
630 *                                                                              *
631 *   performs a threadswitch                                                    *
632 *                                                                              *
633 *******************************************************************************/
634
635         .ent    asm_perform_threadswitch
636
637 asm_perform_threadswitch:
638         subq    sp,128,sp
639         stq     s0, 0(sp)
640         stq     s1, 8(sp)
641         stq     s2, 16(sp)
642         stq     s3, 24(sp)
643         stq     s4, 32(sp)
644         stq     s5, 40(sp)
645         stq     s6, 48(sp)
646         stt     fs0, 56(sp)
647         stt     fs1, 64(sp)
648         stt     fs2, 72(sp)
649         stt     fs3, 80(sp)
650         stt     fs4, 88(sp)
651         stt     fs5, 96(sp)
652         stt     fs6, 104(sp)
653         stt     fs7, 112(sp)
654         stq     ra, 120(sp)
655         stq     sp, 0(a0)
656         stq     sp, 0(a2)
657         ldq     sp, 0(a1)
658         ldq     s0, 0(sp)
659         ldq     s1, 8(sp)
660         ldq     s2, 16(sp)
661         ldq     s3, 24(sp)
662         ldq     s4, 32(sp)
663         ldq     s5, 40(sp)
664         ldq     s6, 48(sp)
665         ldt     fs0, 56(sp)
666         ldt     fs1, 64(sp)
667         ldt     fs2, 72(sp)
668         ldt     fs3, 80(sp)
669         ldt     fs4, 88(sp)
670         ldt     fs5, 96(sp)
671         ldt     fs6, 104(sp)
672         ldt     fs7, 112(sp)
673         ldq     ra, 120(sp)
674         mov     ra, pv
675         addq    sp, 128, sp
676         jmp     zero,(ra)
677
678         .end    asm_perform_threadswitch
679
680
681 /********************* function asm_switchstackandcall *************************
682 *                                                                              *
683 *  void *asm_switchstackandcall (void *stack, void *func, void **stacktopsave, *
684 *                               void *p);                                      *
685 *                                                                              *
686 *   Switches to a new stack, calls a function and switches back.               *
687 *       a0      new stack pointer                                              *
688 *       a1      function pointer                                               *
689 *               a2              pointer to variable where stack top should be stored           *
690 *               a3      pointer to user data, is passed to the function                *
691 *                                                                              *
692 *******************************************************************************/
693
694
695         .ent    asm_switchstackandcall
696
697 asm_switchstackandcall:
698         lda     a0,-2*8(a0)     /* allocate new stack                                 */
699         stq     ra,0(a0)        /* save return address on new stack                   */
700         stq     sp,1*8(a0)      /* save old stack pointer on new stack                */
701         stq sp,0(a2)        /* save old stack pointer to variable                 */
702         mov     a0,sp           /* switch to new stack                                */
703         
704         mov     a1,pv           /* load function pointer                              */
705         mov a3,a0           /* pass pointer */
706         jmp     ra,(pv)         /* and call function                                  */
707
708         ldq     ra,0(sp)        /* load return address                                */
709         ldq     sp,1*8(sp)      /* switch to old stack                                */
710
711         jmp     zero,(ra)       /* return                                             */
712
713         .end    asm_switchstackandcall
714
715
716         .ent    asm_getclassvalues_atomic
717
718 asm_getclassvalues_atomic:
719 _crit_restart:
720 _crit_begin:
721         ldl     t0,offbaseval(a0)
722         ldl     t1,offdiffval(a0)
723         ldl     t2,offbaseval(a1)
724 _crit_end:
725         stl     t0,offcast_super_baseval(a2)
726         stl     t1,offcast_super_diffval(a2)
727         stl     t2,offcast_sub_baseval(a2)
728         jmp     zero,(ra)
729
730         .end    asm_getclassvalues_atomic
731
732
733     .data
734
735 asm_criticalsections:
736 #if defined(USE_THREADS) && defined(NATIVE_THREADS)
737     .quad   _crit_begin
738     .quad   _crit_end
739     .quad   _crit_restart
740 #endif
741     .quad   0
742
743
744 /* Disable exec-stacks, required for Gentoo ***********************************/
745
746 #if defined(__GCC__) && defined(__ELF__)
747         .section .note.GNU-stack,"",@progbits
748 #endif
749
750
751 /*
752  * These are local overrides for various environment variables in Emacs.
753  * Please do not remove this and leave it at the end of the file, where
754  * Emacs will automagically detect them.
755  * ---------------------------------------------------------------------
756  * Local variables:
757  * mode: asm
758  * indent-tabs-mode: t
759  * c-basic-offset: 4
760  * tab-width: 4
761  * End:
762  */