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