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