* src/vm/jit/powerpc/asmpart.S, src/vm/jit/alpha/asmpart.S,
[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 4440 2006-02-05 12:03:43Z 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 /*3*/
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         stq     a0,2*8(sp)                  /* save method pointer for compiler   */
157         lda     v0,2*8(sp)                  /* pass pointer to method pointer     */
158
159         mov     a1,a0                       /* pass the remaining parameters      */
160         mov     a2,a1
161         mov     a3,a2
162         mov     a4,a3
163
164         lda     itmp2,asm_call_jit_compiler /* fake virtual function call         */
165         stq     itmp2,3*8(sp)               /* store function address             */
166         mov     sp,itmp2                    /* set method pointer                 */
167
168         ldq     pv,3*8(itmp2)               /* method call as in Java             */
169         jmp     ra,(pv)                     /* call JIT compiler                  */
170 calljava_jit:
171         lda     pv,(asm_calljavafunction - calljava_jit)(ra)
172
173 L_asm_calljavafunction_return:
174         ldq     ra,0*8(sp)                  /* restore return address             */
175         ldq     gp,1*8(sp)                  /* restore global pointer             */
176         lda     sp,4*8(sp)                  /* free stack space                   */
177         jmp     zero,(ra)
178
179 calljava_xhandler:
180         ldq     gp,1*8(sp)                  /* restore global pointer             */
181         mov     xptr,a0
182         jsr     ra,builtin_throw_exception
183         mov     zero,v0                     /* return NULL                        */
184         br      L_asm_calljavafunction_return
185
186         .end    asm_calljavafunction
187
188
189
190
191         .ent    asm_calljavafunction2
192
193         .align  3
194
195         .quad   0                           /* catch type all                     */
196         .quad   calljava_xhandler2          /* handler pc                         */
197         .quad   calljava_xhandler2          /* end pc                             */
198         .quad   asm_calljavafunction2       /* start pc                           */
199         .long   1                           /* extable size                       */
200         .long   0                           /* ALIGNMENT PADDING                  */
201         .quad   0                           /* line number table start            */
202         .quad   0                           /* line number table size             */
203         .long   0                           /* ALIGNMENT PADDING                  */
204         .long   0                           /* fltsave                            */
205         .long   1                           /* intsave                            */
206         .long   0                           /* isleaf                             */
207         .long   0                           /* IsSync                             */
208         .long   0                           /* frame size                         */
209         .quad   0                           /* method pointer (pointer to name)   */
210
211 asm_calljavafunction2:
212 asm_calljavafunction2int:
213 asm_calljavafunction2long:
214 asm_calljavafunction2float:
215 asm_calljavafunction2double:
216         ldgp    gp,0(pv)
217         lda     sp,-5*8(sp)               /* allocate stack space                 */
218         stq     ra,0*8(sp)                /* save return address                  */
219         stq     gp,1*8(sp)                /* save global pointer                  */
220         stq     s6,3*8(sp)
221
222         stq     a0,4*8(sp)                /* save method pointer for compiler     */
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         lda     v0,4*8(t4)                /* pass pointer to method pointer via v0*/
272
273         lda     itmp2,asm_call_jit_compiler/* fake virtual function call (2 instr)*/
274         stq     itmp2,16(t4)              /* store function address               */
275         lda     itmp2,8(t4)               /* set method pointer                   */
276
277         ldq     pv,8(itmp2)               /* 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         ldl     t8,-8(ra)             /* load instruction LDQ PV,xxx($yy)         */
331         srl     t8,16,t8              /* shift right register number $yy          */
332         and     t8,31,t8              /* isolate register number                  */
333         subl    t8,28,t8              /* test for REG_METHODPTR                   */
334         beq     t8,noregchange       
335         ldl     t8,0(ra)              /* load instruction LDA PV,xxx(RA)          */
336         sll     t8,48,t8
337         sra     t8,48,t8              /* isolate offset                           */
338         addq    t8,ra,$28             /* compute update address                   */
339         ldl     t8,4(ra)              /* load instruction LDAH PV,xxx(PV)         */
340         srl     t8,16,t8              /* isolate instruction code                 */
341         lda     t8,-0x177b(t8)        /* test for LDAH                            */
342         bne     t8,noregchange       
343         ldl     t8,4(ra)              /* load instruction LDAH PV,xxx(PV)         */
344         sll     t8,16,t8              /* compute high offset                      */
345         addl    t8,0,t8               /* sign extend high offset                  */
346         addq    t8,$28,$28            /* compute update address                   */
347 noregchange:
348         lda     sp,-(15*8+sizestackframeinfo)(sp) /* reserve stack space          */
349
350         SAVE_ARGUMENT_REGISTERS(0)    /* save 6 int/6 float argument registers    */
351
352         stq     $28,12*8(sp)          /* save method pointer                      */
353         stq     ra,13*8(sp)           /* save return address                      */
354         stq     v0,14*8(sp)           /* save methodinfo pointer                  */
355
356         lda     a0,15*8(sp)           /* create stackframe info                   */
357         mov     zero,a1               /* we don't have pv handy                   */
358         lda     a2,15*8+sizestackframeinfo(sp) /* pass java sp                    */
359         mov     ra,a3                 /* pass Java ra                             */
360         mov     a3,a4                 /* xpc is equal to ra                       */
361         jsr     ra,stacktrace_create_extern_stackframeinfo
362         ldgp    gp,0(ra)
363
364         ldq     v0,14*8(sp)           /* restore methodinfo pointer               */
365         ldq     a0,0(v0)              /* pass methodinfo pointer                  */
366         jsr     ra,jit_compile        /* call jit compiler                        */
367         ldgp    gp,0(ra)
368         stq     v0,14*8(sp)           /* save return value                        */
369
370         lda     a0,15*8(sp)           /* remove stackframe info                   */
371         jsr     ra,stacktrace_remove_stackframeinfo
372         ldgp    gp,0(ra)
373
374         RESTORE_ARGUMENT_REGISTERS(0) /* restore 6 int/6 float argument registers */
375
376         ldq     $28,12*8(sp)          /* load method pointer                      */
377         ldq     ra,13*8(sp)           /* load return address                      */
378         ldq     v0,14*8(sp)           /* restore return value                     */
379         lda     sp,15*8+sizestackframeinfo(sp) /* deallocate stack area           */
380
381         beq     v0,L_asm_call_jit_compiler_exception
382
383         ldl     t8,-8(ra)             /* load instruction LDQ PV,xxx($yy)         */
384         sll     t8,48,t8
385         sra     t8,48,t8              /* isolate offset                           */
386
387         addq    t8,$28,t8             /* compute update address via method pointer*/
388         stq     v0,0(t8)              /* save new method address there            */
389
390         call_pal PAL_imb              /* synchronise instruction cache            */
391
392         mov     v0,pv                 /* load method address into pv              */
393         jmp     zero,(pv)             /* and call method. The method returns      */
394                                       /* directly to the caller (ra).             */
395
396 L_asm_call_jit_compiler_exception:
397 #if defined(USE_THREADS) && defined(NATIVE_THREADS)
398         subq    sp,1*8,sp
399         stq     ra,0*8(sp)            /* save return address (xpc)                */
400         jsr     ra,builtin_asm_get_exceptionptrptr
401         ldq     ra,0*8(sp)           /* restore return address (xpc)             */
402         addq    sp,1*8,sp
403 #else
404         lda     v0,_exceptionptr
405 #endif
406         ldq     xptr,0(v0)            /* get the exception pointer                */
407         stq     zero,0(v0)            /* clear the exception pointer              */
408
409         subq    ra,4,xpc
410         br      asm_handle_nat_exception
411
412         .end    asm_call_jit_compiler
413
414
415 /* asm_handle_exception ********************************************************
416
417    This function handles an exception. It does not use the usual calling
418    conventions. The exception pointer is passed in REG_ITMP1 and the
419    pc from the exception raising position is passed in REG_ITMP2. It searches
420    the local exception table for a handler. If no one is found, it unwinds
421    stacks and continues searching the callers.
422
423    ATTENTION: itmp3 == gp!
424
425 *******************************************************************************/
426
427         .ent    asm_handle_nat_exception
428
429 asm_handle_nat_exception:
430         ldl     t0,0(ra)              /* load instruction LDA PV,xxx(RA)          */
431         sll     t0,48,t0
432         sra     t0,48,t0              /* isolate offset                           */
433         addq    t0,ra,pv              /* compute update address                   */
434         ldl     t0,4(ra)              /* load instruction LDAH PV,xxx(PV)         */
435         srl     t0,16,t0              /* isolate instruction code                 */
436         lda     t0,-0x177b(t0)        /* test for LDAH                            */
437         bne     t0,asm_handle_exception
438         ldl     t0,4(ra)              /* load instruction LDAH PV,xxx(PV)         */
439         sll     t0,16,t0              /* compute high offset                      */
440         addl    t0,0,t0               /* sign extend high offset                  */
441         addq    t0,pv,pv              /* compute update address                   */
442
443         .aent    asm_handle_exception
444
445 asm_handle_exception:
446         lda     sp,-(ARG_CNT+TMP_CNT)*8(sp) /* create maybe-leaf stackframe       */
447
448         SAVE_ARGUMENT_REGISTERS(0)          /* we save arg and temp registers in  */
449         SAVE_TEMPORARY_REGISTERS(ARG_CNT)   /* case this is a leaf method         */
450
451         lda     a3,(ARG_CNT+TMP_CNT)*8(zero)/* prepare a3 for handle_exception */
452         lda     a4,1(zero)                  /* set maybe-leaf flag                */
453
454 L_asm_handle_exception_stack_loop:
455         lda     sp,-5*8(sp)                 /* allocate stack                     */
456         stq     xptr,0*8(sp)                /* save exception pointer             */
457         stq     xpc,1*8(sp)                 /* save exception pc                  */
458         stq     pv,2*8(sp)                  /* save data segment pointer          */
459         stq     ra,3*8(sp)                  /* save return address                */
460         addq    a3,sp,a3                    /* calculate Java sp into a3...       */
461         addq    a3,5*8,a3
462         stq     a4,4*8(sp)                  /* save maybe-leaf flag               */
463
464         br      ra,L_asm_handle_exception_load_gp /* set ra for gp loading        */
465 L_asm_handle_exception_load_gp:
466         ldgp    gp,0(ra)                    /* load gp                            */
467
468         mov     xptr,a0                     /* pass exception pointer             */
469         mov     xpc,a1                      /* pass exception pc                  */
470         mov     pv,a2                       /* pass data segment pointer          */
471                                             /* a3 is still set                    */
472         jsr     ra,exceptions_handle_exception
473
474         beq     v0,L_asm_handle_exception_not_catched
475
476         mov     v0,xpc                      /* move handlerpc into xpc            */
477         ldq     xptr,0*8(sp)                /* restore exception pointer          */
478         ldq     pv,2*8(sp)                  /* restore data segment pointer       */
479         ldq     ra,3*8(sp)                  /* restore return address             */
480         ldq     a4,4*8(sp)                  /* get maybe-leaf flag                */
481         lda     sp,5*8(sp)                  /* free stack frame                   */
482
483         beq     a4,L_asm_handle_exception_no_leaf
484
485         RESTORE_ARGUMENT_REGISTERS(0)       /* if this is a leaf method, we have  */
486         RESTORE_TEMPORARY_REGISTERS(ARG_CNT)/* to restore arg and temp registers  */
487         
488         lda     sp,(ARG_CNT+TMP_CNT)*8(sp)  /* remove maybe-leaf stackframe       */
489
490 L_asm_handle_exception_no_leaf:
491         jmp     zero,(xpc)                  /* jump to the handler                */
492
493 L_asm_handle_exception_not_catched:
494         ldq     xptr,0*8(sp)                /* restore exception pointer          */
495         ldq     pv,2*8(sp)                  /* restore data segment pointer       */
496         ldq     ra,3*8(sp)                  /* restore return address             */
497         ldq     a4,4*8(sp)                  /* get maybe-leaf flag                */
498         lda     sp,5*8(sp)
499
500         beq     a4,L_asm_handle_exception_no_leaf_stack
501
502         lda     sp,(ARG_CNT+TMP_CNT)*8(sp)  /* remove maybe-leaf stackframe       */
503         mov     zero,a4                     /* clear the maybe-leaf flag          */
504
505 L_asm_handle_exception_no_leaf_stack:
506         ldl     t0,FrameSize(pv)            /* get frame size                     */
507         addq    t0,sp,t0                    /* pointer to save area               */
508
509         ldl     t1,IsLeaf(pv)               /* is leaf procedure                  */
510         bne     t1,L_asm_handle_exception_no_ra_restore
511
512         ldq     ra,-1*8(t0)                 /* restore ra                         */
513         subq    t0,8,t0                     /* t0--                               */
514
515 L_asm_handle_exception_no_ra_restore:
516         mov     ra,xpc                      /* the new xpc is ra                  */
517         ldl     t1,IntSave(pv)              /* t1 = saved int register count      */
518         br      t2,ex_int1                  /* t2 = current pc                    */
519 ex_int1:
520         lda     t2,(ex_int2-ex_int1)(t2)
521         negl    t1,t1                       /* negate register count              */
522         s4addq  t1,t2,t2                    /* t2 = IntSave - register count * 4  */
523         jmp     zero,(t2)                   /* jump to save position              */
524
525         ldq     s0,-7*8(t0)
526         ldq     s1,-6*8(t0)
527         ldq     s2,-5*8(t0)
528         ldq     s3,-4*8(t0)
529         ldq     s4,-3*8(t0)
530         ldq     s5,-2*8(t0)
531         ldq     s6,-1*8(t0)
532
533 ex_int2:
534         s8addq  t1,t0,t0                    /* t0 = t0 - 8 * register count       */
535
536         ldl     t1,FltSave(pv)              /* t1 = saved flt register count      */
537         br      t2,ex_flt1                  /* t2 = current pc                    */
538 ex_flt1:
539         lda     t2,(ex_flt2-ex_flt1)(t2)
540         negl    t1,t1                       /* negate register count              */
541         s4addq  t1,t2,t2                    /* t2 = FltSave - 4 * register count  */
542         jmp     zero,(t2)                   /* jump to save position              */
543
544         ldt     fs0,-8*8(t0)
545         ldt     fs1,-7*8(t0)
546         ldt     fs2,-6*8(t0)
547         ldt     fs3,-5*8(t0)
548         ldt     fs4,-4*8(t0)
549         ldt     fs5,-3*8(t0)
550         ldt     fs6,-2*8(t0)
551         ldt     fs7,-1*8(t0)
552
553 ex_flt2:
554         ldl     t0,FrameSize(pv)            /* get frame size                     */
555         addq    sp,t0,sp                    /* unwind stack                       */
556         mov     zero,a3                     /* prepare a3 for handle_exception    */
557
558         ldl     t0,0(ra)              /* load instruction LDA PV,xxx(RA)          */
559         sll     t0,48,t0
560         sra     t0,48,t0              /* isolate offset                           */
561         addq    t0,ra,pv              /* compute update address                   */
562         ldl     t0,4(ra)              /* load instruction LDAH PV,xxx(PV)         */
563         srl     t0,16,t0              /* isolate instruction code                 */
564         lda     t0,-0x177b(t0)        /* test for LDAH                            */
565         bne     t0,L_asm_handle_exception_stack_loop
566         ldl     t0,4(ra)              /* load instruction LDAH PV,xxx(RA)         */
567         sll     t0,16,t0              /* compute high offset                      */
568         addl    t0,0,t0               /* sign extend high offset                  */
569         addq    t0,pv,pv              /* compute update address                   */
570
571         br      L_asm_handle_exception_stack_loop
572
573         .end    asm_handle_nat_exception
574
575
576 /* asm_wrapper_patcher *********************************************************
577
578    XXX
579
580    Stack layout:
581      40   return address into JIT code (patch position)
582      32   pointer to virtual java_objectheader
583      24   machine code (which is patched back later)
584      16   unresolved class/method/field reference
585       8   data segment displacement from load instructions
586       0   patcher function pointer to call (pv afterwards)
587
588    ATTENTION: itmp3 == gp! But we don't need gp do call the patcher function.
589
590 *******************************************************************************/
591                 
592         .ent    asm_wrapper_patcher
593
594 asm_wrapper_patcher:
595         lda     sp,-((2+12+27+4)*8+sizestackframeinfo)(sp) /* create stack frame  */
596
597         SAVE_RETURN_REGISTERS(0)      /* save 1 int/1 float return registers      */
598         SAVE_ARGUMENT_REGISTERS(2)    /* save 6 int/6 float argument registers    */
599         SAVE_TEMPORARY_REGISTERS(14)  /* save 11 int/16 float temporary registers */
600
601         stq     itmp1,(2+12+27+0)*8(sp) /* save itmp1                             */
602         stq     itmp2,(2+12+27+1)*8(sp) /* save itmp2                             */
603         stq     ra,(2+12+27+2)*8(sp)  /* save method return address (for leafs)   */
604         stq     pv,(2+12+27+3)*8(sp)  /* save pv of calling java function         */
605
606         br      ra,L_asm_wrapper_patcher_load_gp
607 L_asm_wrapper_patcher_load_gp:
608         ldgp    gp,0(ra)              /* load gp (it's not set correctly in jit)  */
609
610         lda     a0,(2+12+27+4)*8(sp)  /* create stackframe info                   */
611         mov     pv,a1                 /* pass java pv                             */
612         lda     a2,((6+2+12+27+4)*8+sizestackframeinfo)(sp) /* pass java sp       */
613         ldq     a3,(2+12+27+2)*8(sp)  /* this is correct for leafs                */
614         ldq     a4,((5+2+12+27+4)*8+sizestackframeinfo)(sp) /* pass xpc           */
615         jsr     ra,stacktrace_create_extern_stackframeinfo
616         ldgp    gp,0(ra)
617
618         lda     a0,((0+2+12+27+4)*8+sizestackframeinfo)(sp) /* pass sp            */
619         ldq     pv,((0+2+12+27+4)*8+sizestackframeinfo)(sp) /* get function       */
620         ldq     itmp1,(2+12+27+3)*8(sp) /* save pv to the position of fp          */
621         stq     itmp1,((0+2+12+27+4)*8+sizestackframeinfo)(sp)
622         jmp     ra,(pv)               /* call the patcher function                */
623         ldgp    gp,0(ra)
624         stq     v0,((0+2+12+27+4)*8+sizestackframeinfo)(sp) /* save return value  */
625
626         lda     a0,(2+12+27+4)*8(sp)  /* remove stackframe info                   */
627         jsr     ra,stacktrace_remove_stackframeinfo
628         ldgp    gp,0(ra)
629
630         RESTORE_RETURN_REGISTERS(0)   /* restore 1 int/1 float return registers   */
631         RESTORE_ARGUMENT_REGISTERS(2) /* restore 6 int/6 float argument registers */
632         RESTORE_TEMPORARY_REGISTERS(14) /* restore 11 integer temporary registers */
633
634         ldq     itmp1,(2+12+27+0)*8(sp) /* restore itmp1                          */
635         ldq     itmp2,(2+12+27+1)*8(sp) /* restore itmp2                          */
636         ldq     ra,(2+12+27+2)*8(sp)  /* restore method return address (for leafs)*/
637         ldq     pv,(2+12+27+3)*8(sp)  /* restore pv of calling java function      */
638
639         ldq     itmp3,((0+2+12+27+4)*8+sizestackframeinfo)(sp) /* get return value*/
640         beq     itmp3,L_asm_wrapper_patcher_exception
641
642         ldq     itmp3,((5+2+12+27+4)*8+sizestackframeinfo)(sp)/* get RA to JIT    */
643         lda     sp,((6+2+12+27+4)*8+sizestackframeinfo)(sp) /* remove stack frame */
644
645         jmp     zero,(itmp3)          /* jump to new patched code                 */
646
647 L_asm_wrapper_patcher_exception:
648         ldq     xpc,((5+2+12+27+4)*8+sizestackframeinfo)(sp) /* RA is xpc         */
649         lda     sp,((6+2+12+27+4)*8+sizestackframeinfo)(sp) /* remove stack frame */
650
651         br      itmp1,L_asm_wrapper_patcher_exception_load_gp
652 L_asm_wrapper_patcher_exception_load_gp:
653         ldgp    gp,0(itmp1)           /* itmp3 == gp, load the current gp         */
654
655 #if defined(USE_THREADS) && defined(NATIVE_THREADS)
656         subq    sp,3*8,sp
657         stq     xpc,0*8(sp)           /* save return address (xpc)                */
658         stq     ra,1*8(sp)
659         stq     pv,2*8(sp)
660         jsr     ra,builtin_asm_get_exceptionptrptr
661         ldq     xpc,0*8(sp)           /* restore return address (xpc)             */
662         ldq     ra,1*8(sp)
663         ldq     pv,2*8(sp)
664         addq    sp,3*8,sp
665 #else
666         lda     v0,_exceptionptr
667 #endif
668         ldq     xptr,0(v0)            /* get the exception pointer                */
669         stq     zero,0(v0)            /* clear the exception pointer              */
670         br      asm_handle_exception  /* we have the pv of the calling java func. */
671
672         .end    asm_wrapper_patcher
673
674                 
675 /******************* function asm_initialize_thread_stack **********************
676 *                                                                              *
677 *   initialized a thread stack                                                 *
678 *                                                                              *
679 *******************************************************************************/
680
681         .ent    asm_initialize_thread_stack
682
683 asm_initialize_thread_stack:
684         lda     a1,-128(a1)
685         stq     zero, 0(a1)
686         stq     zero, 8(a1)
687         stq     zero, 16(a1)
688         stq     zero, 24(a1)
689         stq     zero, 32(a1)
690         stq     zero, 40(a1)
691         stq     zero, 48(a1)
692         stt     fzero, 56(a1)
693         stt     fzero, 64(a1)
694         stt     fzero, 72(a1)
695         stt     fzero, 80(a1)
696         stt     fzero, 88(a1)
697         stt     fzero, 96(a1)
698         stt     fzero, 104(a1)
699         stt     fzero, 112(a1)
700         stq     a0, 120(a1)
701         mov     a1, v0
702         jmp     zero,(ra)
703
704         .end    asm_initialize_thread_stack
705
706
707 /******************* function asm_perform_threadswitch *************************
708 *                                                                              *
709 *   void asm_perform_threadswitch (u1 **from, u1 **to, u1 **stackTop);         *
710 *                                                                              *
711 *   performs a threadswitch                                                    *
712 *                                                                              *
713 *******************************************************************************/
714
715         .ent    asm_perform_threadswitch
716
717 asm_perform_threadswitch:
718         subq    sp,128,sp
719         stq     s0, 0(sp)
720         stq     s1, 8(sp)
721         stq     s2, 16(sp)
722         stq     s3, 24(sp)
723         stq     s4, 32(sp)
724         stq     s5, 40(sp)
725         stq     s6, 48(sp)
726         stt     fs0, 56(sp)
727         stt     fs1, 64(sp)
728         stt     fs2, 72(sp)
729         stt     fs3, 80(sp)
730         stt     fs4, 88(sp)
731         stt     fs5, 96(sp)
732         stt     fs6, 104(sp)
733         stt     fs7, 112(sp)
734         stq     ra, 120(sp)
735         stq     sp, 0(a0)
736         stq     sp, 0(a2)
737         ldq     sp, 0(a1)
738         ldq     s0, 0(sp)
739         ldq     s1, 8(sp)
740         ldq     s2, 16(sp)
741         ldq     s3, 24(sp)
742         ldq     s4, 32(sp)
743         ldq     s5, 40(sp)
744         ldq     s6, 48(sp)
745         ldt     fs0, 56(sp)
746         ldt     fs1, 64(sp)
747         ldt     fs2, 72(sp)
748         ldt     fs3, 80(sp)
749         ldt     fs4, 88(sp)
750         ldt     fs5, 96(sp)
751         ldt     fs6, 104(sp)
752         ldt     fs7, 112(sp)
753         ldq     ra, 120(sp)
754         mov     ra, pv
755         addq    sp, 128, sp
756         jmp     zero,(ra)
757
758         .end    asm_perform_threadswitch
759
760
761 /********************* function asm_switchstackandcall *************************
762 *                                                                              *
763 *  void *asm_switchstackandcall (void *stack, void *func, void **stacktopsave, *
764 *                               void *p);                                      *
765 *                                                                              *
766 *   Switches to a new stack, calls a function and switches back.               *
767 *       a0      new stack pointer                                              *
768 *       a1      function pointer                                               *
769 *               a2              pointer to variable where stack top should be stored           *
770 *               a3      pointer to user data, is passed to the function                *
771 *                                                                              *
772 *******************************************************************************/
773
774
775         .ent    asm_switchstackandcall
776
777 asm_switchstackandcall:
778         lda     a0,-2*8(a0)     /* allocate new stack                                 */
779         stq     ra,0(a0)        /* save return address on new stack                   */
780         stq     sp,1*8(a0)      /* save old stack pointer on new stack                */
781         stq sp,0(a2)        /* save old stack pointer to variable                 */
782         mov     a0,sp           /* switch to new stack                                */
783         
784         mov     a1,pv           /* load function pointer                              */
785         mov a3,a0           /* pass pointer */
786         jmp     ra,(pv)         /* and call function                                  */
787
788         ldq     ra,0(sp)        /* load return address                                */
789         ldq     sp,1*8(sp)      /* switch to old stack                                */
790
791         jmp     zero,(ra)       /* return                                             */
792
793         .end    asm_switchstackandcall
794
795
796         .ent    asm_getclassvalues_atomic
797
798 asm_getclassvalues_atomic:
799 _crit_restart:
800 _crit_begin:
801         ldl     t0,offbaseval(a0)
802         ldl     t1,offdiffval(a0)
803         ldl     t2,offbaseval(a1)
804 _crit_end:
805         stl     t0,offcast_super_baseval(a2)
806         stl     t1,offcast_super_diffval(a2)
807         stl     t2,offcast_sub_baseval(a2)
808         jmp     zero,(ra)
809
810         .end    asm_getclassvalues_atomic
811
812
813     .data
814
815 asm_criticalsections:
816 #if defined(USE_THREADS) && defined(NATIVE_THREADS)
817     .quad   _crit_begin
818     .quad   _crit_end
819     .quad   _crit_restart
820 #endif
821     .quad   0
822
823
824 /* Disable exec-stacks, required for Gentoo ***********************************/
825
826 #if defined(__GCC__) && defined(__ELF__)
827         .section .note.GNU-stack,"",@progbits
828 #endif
829
830
831 /*
832  * These are local overrides for various environment variables in Emacs.
833  * Please do not remove this and leave it at the end of the file, where
834  * Emacs will automagically detect them.
835  * ---------------------------------------------------------------------
836  * Local variables:
837  * mode: asm
838  * indent-tabs-mode: t
839  * c-basic-offset: 4
840  * tab-width: 4
841  * End:
842  */