* src/vm/jit/alpha/asmpart.S (REPLACEMENT_ROOM): Fixed deleted characters.
[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                 Edwin Steiner
33
34    $Id: asmpart.S 4665 2006-03-21 07:42:34Z edwin $
35
36 */
37
38
39 #include "config.h"
40
41 #include "vm/jit/alpha/md-abi.h"
42 #include "vm/jit/alpha/md-asm.h"
43 #include "vm/jit/alpha/offsets.h"
44
45 #include "vm/jit/abi.h"
46 #include "vm/jit/methodheader.h"
47
48
49         .text
50         .set    noat
51         .set    noreorder
52
53
54 /* export functions ***********************************************************/
55
56         .globl asm_vm_call_method
57         .globl asm_vm_call_method_int
58         .globl asm_vm_call_method_long
59         .globl asm_vm_call_method_float
60         .globl asm_vm_call_method_double
61
62         .globl asm_call_jit_compiler
63         .globl asm_handle_exception
64         .globl asm_handle_nat_exception
65
66         .globl asm_wrapper_patcher
67
68         .globl asm_replacement_out
69         .globl asm_replacement_in
70
71         .globl asm_perform_threadswitch
72         .globl asm_initialize_thread_stack
73         .globl asm_switchstackandcall
74         .globl asm_criticalsections
75         .globl asm_getclassvalues_atomic
76
77         .globl asm_md_init
78         .globl asm_cacheflush
79
80
81 /* asm_vm_call_method **********************************************************
82 *                                                                              *
83 *   This function calls a Java-method (which possibly needs compilation)       *
84 *   with up to 4 address parameters.                                           *
85 *                                                                              *
86 *   This functions calls the JIT-compiler which eventually translates the      *
87 *   method into machine code.                                                  *
88 *                                                                              *
89 *   C-prototype:                                                               *
90 *    javaobject_header *asm_calljavafunction (methodinfo *m,                   *
91 *         void *arg1, void *arg2, void *arg3, void *arg4);                     *
92 *                                                                              *
93 *******************************************************************************/
94
95         .ent    asm_vm_call_method
96
97         .align  3
98
99         .quad   0                           /* catch type all                     */
100         .quad   calljava_xhandler2          /* handler pc                         */
101         .quad   calljava_xhandler2          /* end pc                             */
102         .quad   asm_vm_call_method          /* start pc                           */
103         .long   1                           /* extable size                       */
104         .long   0                           /* ALIGNMENT PADDING                  */
105         .quad   0                           /* line number table start            */
106         .quad   0                           /* line number table size             */
107         .long   0                           /* ALIGNMENT PADDING                  */
108         .long   0                           /* fltsave                            */
109         .long   1                           /* intsave                            */
110         .long   0                           /* isleaf                             */
111         .long   0                           /* IsSync                             */
112         .long   0                           /* frame size                         */
113         .quad   0                           /* method pointer (pointer to name)   */
114
115 asm_vm_call_method:
116 asm_vm_call_method_int:
117 asm_vm_call_method_long:
118 asm_vm_call_method_float:
119 asm_vm_call_method_double:
120         ldgp    gp,0(pv)
121         lda     sp,-5*8(sp)               /* allocate stack space                 */
122         stq     ra,0*8(sp)                /* save return address                  */
123         stq     gp,1*8(sp)                /* save global pointer                  */
124         stq     s6,3*8(sp)
125
126         stq     a0,4*8(sp)                /* save method pointer for compiler     */
127
128         mov     a2,t0                     /* pointer to arg block                 */
129         mov     a1,s6                     /* arg count                            */
130
131         ble     s6,calljava_argsloaded
132         lda     s6,-1(s6)
133         ldq     a0,offvmargdata(t0)
134         ldt     $f16,offvmargdata(t0)
135         ble     s6,calljava_argsloaded
136
137         lda     s6,-1(s6)
138         ldq     a1,offvmargdata+sizevmarg*1(t0)
139         ldt     $f17,offvmargdata+sizevmarg*1(t0)
140         ble     s6,calljava_argsloaded
141
142         lda     s6,-1(s6)
143         ldq     a2,offvmargdata+sizevmarg*2(t0)
144         ldt     $f18,offvmargdata+sizevmarg*2(t0)
145         ble     s6,calljava_argsloaded
146
147         lda     s6,-1(s6)
148         ldq     a3,offvmargdata+sizevmarg*3(t0)
149         ldt     $f19,offvmargdata+sizevmarg*3(t0)
150         ble     s6,calljava_argsloaded
151
152         lda     s6,-1(s6)
153         ldq     a4,offvmargdata+sizevmarg*4(t0)
154         ldt     $f20,offvmargdata+sizevmarg*4(t0)
155         ble     s6,calljava_argsloaded
156
157         lda     s6,-1(s6)
158         ldq     a5,offvmargdata+sizevmarg*5(t0)
159         ldt     $f21,offvmargdata+sizevmarg*5(t0)
160 calljava_argsloaded:
161         mov     sp,t4
162         ble     s6,calljava_nocopy
163         negq    s6,t1
164         s8addq  t1,sp,sp
165         s8addq  t1,t4,t2
166
167 calljava_copyloop:
168         ldq     t3,offvmargdata+sizevmarg*6(t0)
169         stq     t3,0(t2)
170         lda     t1,1(t1)
171         lda     t0,sizevmarg(t0)
172         lda     t2,8(t2)
173         bne     t1,calljava_copyloop
174
175 calljava_nocopy:
176         ldq     itmp1,4*8(t4)             /* pass method pointer via itmp1        */
177
178         lda     mptr,asm_call_jit_compiler/* fake virtual function call (2 instr) */
179         stq     mptr,2*8(t4)              /* store function address               */
180         lda     mptr,1*8(t4)              /* set method pointer                   */
181
182         ldq     pv,1*8(mptr)              /* method call as in Java               */
183         jmp     ra,(pv)                   /* call JIT compiler                    */
184 calljava_jit2:
185         lda     pv,(asm_vm_call_method - calljava_jit2)(ra)
186
187         s8addq  s6,sp,sp
188 calljava_return2:
189         ldq     ra,0*8(sp)                /* restore return address               */
190         ldq     gp,1*8(sp)                /* restore global pointer               */
191         ldq     s6,3*8(sp)
192         lda     sp,5*8(sp)                /* free stack space                     */
193
194 calljava_ret2:
195         jmp     zero,(ra)
196
197 calljava_xhandler2:
198         s8addq  s6,sp,sp
199         ldq     gp,1*8(sp)                /* restore global pointer               */
200         mov     itmp1,a0
201         jsr     ra,builtin_throw_exception
202         ldq     ra,0*8(sp)                /* restore return address               */
203         ldq     s6,3*8(sp)
204         lda     sp,5*8(sp)                /* free stack space                     */
205         mov     zero,v0                   /* return NULL                          */
206         jmp     zero,(ra)
207
208         .end    asm_vm_call_method
209
210
211 /****************** function asm_call_jit_compiler *****************************
212 *                                                                              *
213 *   invokes the compiler for untranslated JavaVM methods.                      *
214 *                                                                              *
215 *   Register R0 contains a pointer to the method info structure (prepared      *
216 *   by createcompilerstub). Using the return address in R26 and the            *
217 *   offset in the LDA instruction or using the value in methodptr R28 the      *
218 *   patching address for storing the method address can be computed:           *
219 *                                                                              *
220 *   method address was either loaded using                                     *
221 *   M_LDQ (REG_PV, REG_PV, a)        ; invokestatic/special    ($27)           *
222 *   M_LDA (REG_PV, REG_RA, low)                                                *
223 *   M_LDAH(REG_PV, REG_RA, high)     ; optional                                *
224 *   or                                                                         *
225 *   M_LDQ (REG_PV, REG_METHODPTR, m) ; invokevirtual/interface ($28)           *
226 *   in the static case the method pointer can be computed using the            *
227 *   return address and the lda function following the jmp instruction          *
228 *                                                                              *
229 *******************************************************************************/
230
231         .ent    asm_call_jit_compiler
232
233 asm_call_jit_compiler:
234         ldgp    gp,0(pv)
235         lda     sp,-(15*8+sizestackframeinfo)(sp) /* reserve stack space          */
236
237         SAVE_ARGUMENT_REGISTERS(0)    /* save 6 int/6 float argument registers    */
238
239         stq     mptr,12*8(sp)         /* save method pointer                      */
240         stq     ra,13*8(sp)           /* save return address                      */
241         stq     itmp1,14*8(sp)        /* save methodinfo pointer                  */
242
243         lda     a0,15*8(sp)           /* create stackframe info                   */
244         mov     zero,a1               /* we don't have pv handy                   */
245         lda     a2,15*8+sizestackframeinfo(sp) /* pass java sp                    */
246         mov     ra,a3                 /* pass Java ra                             */
247         mov     a3,a4                 /* xpc is equal to ra                       */
248         jsr     ra,stacktrace_create_extern_stackframeinfo
249         ldgp    gp,0(ra)
250
251         ldq     a0,14*8(sp)           /* pass methodinfo pointer                  */
252         jsr     ra,jit_compile        /* call jit compiler                        */
253         ldgp    gp,0(ra)
254         stq     v0,14*8(sp)           /* save return value                        */
255
256         ldq     a0,13*8(sp)           /* pass return address                      */
257         lda     a1,15*8(sp)           /* pass stackframeinfo (for PV)             */
258         ldq     a2,12*8(sp)           /* pass method pointer                      */
259         jsr     ra,md_assembler_get_patch_address /* get address of patch position*/
260         ldgp    gp,0(ra)
261         stq     v0,12*8(sp)           /* store patch address for later use        */
262
263         lda     a0,15*8(sp)           /* remove stackframe info                   */
264         jsr     ra,stacktrace_remove_stackframeinfo
265         ldgp    gp,0(ra)
266
267         RESTORE_ARGUMENT_REGISTERS(0) /* restore 6 int/6 float argument registers */
268
269         ldq     t0,12*8(sp)           /* load patch address                       */
270         ldq     ra,13*8(sp)           /* load return address                      */
271         ldq     pv,14*8(sp)           /* restore method entry point               */
272         lda     sp,15*8+sizestackframeinfo(sp) /* deallocate stack area           */
273
274         beq     pv,L_asm_call_jit_compiler_exception
275
276         stq     pv,0(t0)              /* patch method entry point                 */
277
278         call_pal PAL_imb              /* synchronise instruction cache            */
279
280         jmp     zero,(pv)             /* and call method, the method returns      */
281                                       /* directly to the caller (ra).             */
282
283 L_asm_call_jit_compiler_exception:
284 #if defined(USE_THREADS) && defined(NATIVE_THREADS)
285         subq    sp,1*8,sp
286         stq     ra,0*8(sp)            /* save return address (xpc)                */
287         jsr     ra,builtin_asm_get_exceptionptrptr
288         ldq     ra,0*8(sp)           /* restore return address (xpc)             */
289         addq    sp,1*8,sp
290 #else
291         lda     v0,_exceptionptr
292 #endif
293         ldq     xptr,0(v0)            /* get the exception pointer                */
294         stq     zero,0(v0)            /* clear the exception pointer              */
295
296         subq    ra,4,xpc
297         br      L_asm_handle_nat_exception
298
299         .end    asm_call_jit_compiler
300
301
302 /* asm_handle_exception ********************************************************
303
304    This function handles an exception. It does not use the usual calling
305    conventions. The exception pointer is passed in REG_ITMP1 and the
306    pc from the exception raising position is passed in REG_ITMP2. It searches
307    the local exception table for a handler. If no one is found, it unwinds
308    stacks and continues searching the callers.
309
310    ATTENTION: itmp3 == gp!
311
312 *******************************************************************************/
313
314         .ent    asm_handle_nat_exception
315
316 asm_handle_nat_exception:
317 L_asm_handle_nat_exception:       /* required for PIC code                    */
318         ldl     t0,0(ra)              /* load instruction LDA PV,xxx(RA)          */
319         sll     t0,48,t0
320         sra     t0,48,t0              /* isolate offset                           */
321         addq    t0,ra,pv              /* compute update address                   */
322         ldl     t0,4(ra)              /* load instruction LDAH PV,xxx(PV)         */
323         srl     t0,16,t0              /* isolate instruction code                 */
324         lda     t0,-0x177b(t0)        /* test for LDAH                            */
325         bne     t0,L_asm_handle_exception
326         ldl     t0,4(ra)              /* load instruction LDAH PV,xxx(PV)         */
327         sll     t0,16,t0              /* compute high offset                      */
328         addl    t0,0,t0               /* sign extend high offset                  */
329         addq    t0,pv,pv              /* compute update address                   */
330
331         .aent    asm_handle_exception
332
333 asm_handle_exception:
334 L_asm_handle_exception:                 /* required for PIC code              */
335         lda     sp,-(ARG_CNT+TMP_CNT)*8(sp) /* create maybe-leaf stackframe       */
336
337         SAVE_ARGUMENT_REGISTERS(0)          /* we save arg and temp registers in  */
338         SAVE_TEMPORARY_REGISTERS(ARG_CNT)   /* case this is a leaf method         */
339
340         lda     a3,(ARG_CNT+TMP_CNT)*8(zero)/* prepare a3 for handle_exception */
341         lda     a4,1(zero)                  /* set maybe-leaf flag                */
342
343 L_asm_handle_exception_stack_loop:
344         lda     sp,-5*8(sp)                 /* allocate stack                     */
345         stq     xptr,0*8(sp)                /* save exception pointer             */
346         stq     xpc,1*8(sp)                 /* save exception pc                  */
347         stq     pv,2*8(sp)                  /* save data segment pointer          */
348         stq     ra,3*8(sp)                  /* save return address                */
349         addq    a3,sp,a3                    /* calculate Java sp into a3...       */
350         addq    a3,5*8,a3
351         stq     a4,4*8(sp)                  /* save maybe-leaf flag               */
352
353         br      ra,L_asm_handle_exception_load_gp /* set ra for gp loading        */
354 L_asm_handle_exception_load_gp:
355         ldgp    gp,0(ra)                    /* load gp                            */
356
357         mov     xptr,a0                     /* pass exception pointer             */
358         mov     xpc,a1                      /* pass exception pc                  */
359         mov     pv,a2                       /* pass data segment pointer          */
360                                             /* a3 is still set                    */
361         jsr     ra,exceptions_handle_exception
362
363         beq     v0,L_asm_handle_exception_not_catched
364
365         mov     v0,xpc                      /* move handlerpc into xpc            */
366         ldq     xptr,0*8(sp)                /* restore exception pointer          */
367         ldq     pv,2*8(sp)                  /* restore data segment pointer       */
368         ldq     ra,3*8(sp)                  /* restore return address             */
369         ldq     a4,4*8(sp)                  /* get maybe-leaf flag                */
370         lda     sp,5*8(sp)                  /* free stack frame                   */
371
372         beq     a4,L_asm_handle_exception_no_leaf
373
374         RESTORE_ARGUMENT_REGISTERS(0)       /* if this is a leaf method, we have  */
375         RESTORE_TEMPORARY_REGISTERS(ARG_CNT)/* to restore arg and temp registers  */
376         
377         lda     sp,(ARG_CNT+TMP_CNT)*8(sp)  /* remove maybe-leaf stackframe       */
378
379 L_asm_handle_exception_no_leaf:
380         jmp     zero,(xpc)                  /* jump to the handler                */
381
382 L_asm_handle_exception_not_catched:
383         ldq     xptr,0*8(sp)                /* restore exception pointer          */
384         ldq     pv,2*8(sp)                  /* restore data segment pointer       */
385         ldq     ra,3*8(sp)                  /* restore return address             */
386         ldq     a4,4*8(sp)                  /* get maybe-leaf flag                */
387         lda     sp,5*8(sp)
388
389         beq     a4,L_asm_handle_exception_no_leaf_stack
390
391         lda     sp,(ARG_CNT+TMP_CNT)*8(sp)  /* remove maybe-leaf stackframe       */
392         mov     zero,a4                     /* clear the maybe-leaf flag          */
393
394 L_asm_handle_exception_no_leaf_stack:
395         ldl     t0,FrameSize(pv)            /* get frame size                     */
396         addq    t0,sp,t0                    /* pointer to save area               */
397
398         ldl     t1,IsLeaf(pv)               /* is leaf procedure                  */
399         bne     t1,L_asm_handle_exception_no_ra_restore
400
401         ldq     ra,-1*8(t0)                 /* restore ra                         */
402         subq    t0,8,t0                     /* t0--                               */
403
404 L_asm_handle_exception_no_ra_restore:
405         mov     ra,xpc                      /* the new xpc is ra                  */
406         ldl     t1,IntSave(pv)              /* t1 = saved int register count      */
407         br      t2,ex_int1                  /* t2 = current pc                    */
408 ex_int1:
409         lda     t2,(ex_int2-ex_int1)(t2)
410         negl    t1,t1                       /* negate register count              */
411         s4addq  t1,t2,t2                    /* t2 = IntSave - register count * 4  */
412         jmp     zero,(t2)                   /* jump to save position              */
413
414         ldq     s0,-7*8(t0)
415         ldq     s1,-6*8(t0)
416         ldq     s2,-5*8(t0)
417         ldq     s3,-4*8(t0)
418         ldq     s4,-3*8(t0)
419         ldq     s5,-2*8(t0)
420         ldq     s6,-1*8(t0)
421
422 ex_int2:
423         s8addq  t1,t0,t0                    /* t0 = t0 - 8 * register count       */
424
425         ldl     t1,FltSave(pv)              /* t1 = saved flt register count      */
426         br      t2,ex_flt1                  /* t2 = current pc                    */
427 ex_flt1:
428         lda     t2,(ex_flt2-ex_flt1)(t2)
429         negl    t1,t1                       /* negate register count              */
430         s4addq  t1,t2,t2                    /* t2 = FltSave - 4 * register count  */
431         jmp     zero,(t2)                   /* jump to save position              */
432
433         ldt     fs0,-8*8(t0)
434         ldt     fs1,-7*8(t0)
435         ldt     fs2,-6*8(t0)
436         ldt     fs3,-5*8(t0)
437         ldt     fs4,-4*8(t0)
438         ldt     fs5,-3*8(t0)
439         ldt     fs6,-2*8(t0)
440         ldt     fs7,-1*8(t0)
441
442 ex_flt2:
443         ldl     t0,FrameSize(pv)            /* get frame size                     */
444         addq    sp,t0,sp                    /* unwind stack                       */
445         mov     zero,a3                     /* prepare a3 for handle_exception    */
446
447         ldl     t0,0(ra)              /* load instruction LDA PV,xxx(RA)          */
448         sll     t0,48,t0
449         sra     t0,48,t0              /* isolate offset                           */
450         addq    t0,ra,pv              /* compute update address                   */
451         ldl     t0,4(ra)              /* load instruction LDAH PV,xxx(PV)         */
452         srl     t0,16,t0              /* isolate instruction code                 */
453         lda     t0,-0x177b(t0)        /* test for LDAH                            */
454         bne     t0,L_asm_handle_exception_stack_loop
455         ldl     t0,4(ra)              /* load instruction LDAH PV,xxx(RA)         */
456         sll     t0,16,t0              /* compute high offset                      */
457         addl    t0,0,t0               /* sign extend high offset                  */
458         addq    t0,pv,pv              /* compute update address                   */
459
460         br      L_asm_handle_exception_stack_loop
461
462         .end    asm_handle_nat_exception
463
464
465 /* asm_wrapper_patcher *********************************************************
466
467    XXX
468
469    Stack layout:
470      40   return address into JIT code (patch position)
471      32   pointer to virtual java_objectheader
472      24   machine code (which is patched back later)
473      16   unresolved class/method/field reference
474       8   data segment displacement from load instructions
475       0   patcher function pointer to call (pv afterwards)
476
477    ATTENTION: itmp3 == gp! But we don't need gp do call the patcher function.
478
479 *******************************************************************************/
480                 
481         .ent    asm_wrapper_patcher
482
483 asm_wrapper_patcher:
484         lda     sp,-((2+12+27+4)*8+sizestackframeinfo)(sp) /* create stack frame  */
485
486         SAVE_RETURN_REGISTERS(0)      /* save 1 int/1 float return registers      */
487         SAVE_ARGUMENT_REGISTERS(2)    /* save 6 int/6 float argument registers    */
488         SAVE_TEMPORARY_REGISTERS(14)  /* save 11 int/16 float temporary registers */
489
490         stq     itmp1,(2+12+27+0)*8(sp) /* save itmp1                             */
491         stq     itmp2,(2+12+27+1)*8(sp) /* save itmp2                             */
492         stq     ra,(2+12+27+2)*8(sp)  /* save method return address (for leafs)   */
493         stq     pv,(2+12+27+3)*8(sp)  /* save pv of calling java function         */
494
495         br      ra,L_asm_wrapper_patcher_load_gp
496 L_asm_wrapper_patcher_load_gp:
497         ldgp    gp,0(ra)              /* load gp (it's not set correctly in jit)  */
498
499         lda     a0,(2+12+27+4)*8(sp)  /* create stackframe info                   */
500         mov     pv,a1                 /* pass java pv                             */
501         lda     a2,((6+2+12+27+4)*8+sizestackframeinfo)(sp) /* pass java sp       */
502         ldq     a3,(2+12+27+2)*8(sp)  /* this is correct for leafs                */
503         ldq     a4,((5+2+12+27+4)*8+sizestackframeinfo)(sp) /* pass xpc           */
504         jsr     ra,stacktrace_create_extern_stackframeinfo
505         ldgp    gp,0(ra)
506
507         lda     a0,((0+2+12+27+4)*8+sizestackframeinfo)(sp) /* pass sp            */
508         ldq     pv,((0+2+12+27+4)*8+sizestackframeinfo)(sp) /* get function       */
509         ldq     itmp1,(2+12+27+3)*8(sp) /* save pv to the position of fp          */
510         stq     itmp1,((0+2+12+27+4)*8+sizestackframeinfo)(sp)
511         jmp     ra,(pv)               /* call the patcher function                */
512         ldgp    gp,0(ra)
513         stq     v0,((0+2+12+27+4)*8+sizestackframeinfo)(sp) /* save return value  */
514
515         lda     a0,(2+12+27+4)*8(sp)  /* remove stackframe info                   */
516         jsr     ra,stacktrace_remove_stackframeinfo
517         ldgp    gp,0(ra)
518
519         RESTORE_RETURN_REGISTERS(0)   /* restore 1 int/1 float return registers   */
520         RESTORE_ARGUMENT_REGISTERS(2) /* restore 6 int/6 float argument registers */
521         RESTORE_TEMPORARY_REGISTERS(14) /* restore 11 integer temporary registers */
522
523         ldq     itmp1,(2+12+27+0)*8(sp) /* restore itmp1                          */
524         ldq     itmp2,(2+12+27+1)*8(sp) /* restore itmp2                          */
525         ldq     ra,(2+12+27+2)*8(sp)  /* restore method return address (for leafs)*/
526         ldq     pv,(2+12+27+3)*8(sp)  /* restore pv of calling java function      */
527
528         ldq     itmp3,((0+2+12+27+4)*8+sizestackframeinfo)(sp) /* get return value*/
529         beq     itmp3,L_asm_wrapper_patcher_exception
530
531         ldq     itmp3,((5+2+12+27+4)*8+sizestackframeinfo)(sp)/* get RA to JIT    */
532         lda     sp,((6+2+12+27+4)*8+sizestackframeinfo)(sp) /* remove stack frame */
533
534         jmp     zero,(itmp3)          /* jump to new patched code                 */
535
536 L_asm_wrapper_patcher_exception:
537         ldq     xpc,((5+2+12+27+4)*8+sizestackframeinfo)(sp) /* RA is xpc         */
538         lda     sp,((6+2+12+27+4)*8+sizestackframeinfo)(sp) /* remove stack frame */
539
540         br      itmp1,L_asm_wrapper_patcher_exception_load_gp
541 L_asm_wrapper_patcher_exception_load_gp:
542         ldgp    gp,0(itmp1)           /* itmp3 == gp, load the current gp         */
543
544 #if defined(USE_THREADS) && defined(NATIVE_THREADS)
545         subq    sp,3*8,sp
546         stq     xpc,0*8(sp)           /* save return address (xpc)                */
547         stq     ra,1*8(sp)
548         stq     pv,2*8(sp)
549         jsr     ra,builtin_asm_get_exceptionptrptr
550         ldq     xpc,0*8(sp)           /* restore return address (xpc)             */
551         ldq     ra,1*8(sp)
552         ldq     pv,2*8(sp)
553         addq    sp,3*8,sp
554 #else
555         lda     v0,_exceptionptr
556 #endif
557         ldq     xptr,0(v0)            /* get the exception pointer                */
558         stq     zero,0(v0)            /* clear the exception pointer              */
559         br      L_asm_handle_exception/* we have the pv of the calling java func. */
560
561         .end    asm_wrapper_patcher
562
563                 
564 /* asm_replacement_out *********************************************************
565
566    This code is jumped to from the replacement-out stubs that are executed
567    when a thread reaches an activated replacement point.
568
569    The purpose of asm_replacement_out is to read out the parts of the
570    execution state that cannot be accessed from C code, store this state,
571    and then call the C function replace_me.
572
573    Stack layout:
574       8                 start of stack inside method to replace
575       0   rplpoint *    info on the replacement point that was reached
576
577    NOTE: itmp3 has been clobbered by the replacement-out stub!
578
579 *******************************************************************************/
580
581 /* some room to accomodate changes of the stack frame size during replacement */
582         /* XXX we should find a cleaner solution here */
583 #define REPLACEMENT_ROOM  512
584
585 #define REPLACEMENT_STACK_OFFSET ((sizeexecutionstate + REPLACEMENT_ROOM + 0xf) & ~0xf)
586
587         .ent asm_replacement_out
588
589 asm_replacement_out:
590     /* create stack frame */
591         lda     sp,-(REPLACEMENT_STACK_OFFSET)(sp)
592
593         /* save registers in execution state */
594         stq     $0 ,( 0*8+offes_intregs)(sp)
595         stq     $1 ,( 1*8+offes_intregs)(sp)
596         stq     $2 ,( 2*8+offes_intregs)(sp)
597         stq     $3 ,( 3*8+offes_intregs)(sp)
598         stq     $4 ,( 4*8+offes_intregs)(sp)
599         stq     $5 ,( 5*8+offes_intregs)(sp)
600         stq     $6 ,( 6*8+offes_intregs)(sp)
601         stq     $7 ,( 7*8+offes_intregs)(sp)
602         stq     $8 ,( 8*8+offes_intregs)(sp)
603         stq     $9 ,( 9*8+offes_intregs)(sp)
604         stq     $10,(10*8+offes_intregs)(sp)
605         stq     $11,(11*8+offes_intregs)(sp)
606         stq     $12,(12*8+offes_intregs)(sp)
607         stq     $13,(13*8+offes_intregs)(sp)
608         stq     $14,(14*8+offes_intregs)(sp)
609         stq     $15,(15*8+offes_intregs)(sp)
610         stq     $16,(16*8+offes_intregs)(sp)
611         stq     $17,(17*8+offes_intregs)(sp)
612         stq     $18,(18*8+offes_intregs)(sp)
613         stq     $19,(19*8+offes_intregs)(sp)
614         stq     $20,(20*8+offes_intregs)(sp)
615         stq     $21,(21*8+offes_intregs)(sp)
616         stq     $22,(22*8+offes_intregs)(sp)
617         stq     $23,(23*8+offes_intregs)(sp)
618         stq     $24,(24*8+offes_intregs)(sp)
619         stq     $25,(25*8+offes_intregs)(sp)
620         stq     $26,(26*8+offes_intregs)(sp)
621         stq     $27,(27*8+offes_intregs)(sp)
622         stq     $28,(28*8+offes_intregs)(sp)
623         stq     $29,(29*8+offes_intregs)(sp)
624         stq     $30,(30*8+offes_intregs)(sp)
625         stq     $31,(31*8+offes_intregs)(sp)
626         
627         stt     $f0 ,( 0*8+offes_fltregs)(sp)
628         stt     $f1 ,( 1*8+offes_fltregs)(sp)
629         stt     $f2 ,( 2*8+offes_fltregs)(sp)
630         stt     $f3 ,( 3*8+offes_fltregs)(sp)
631         stt     $f4 ,( 4*8+offes_fltregs)(sp)
632         stt     $f5 ,( 5*8+offes_fltregs)(sp)
633         stt     $f6 ,( 6*8+offes_fltregs)(sp)
634         stt     $f7 ,( 7*8+offes_fltregs)(sp)
635         stt     $f8 ,( 8*8+offes_fltregs)(sp)
636         stt     $f9 ,( 9*8+offes_fltregs)(sp)
637         stt     $f10,(10*8+offes_fltregs)(sp)
638         stt     $f11,(11*8+offes_fltregs)(sp)
639         stt     $f12,(12*8+offes_fltregs)(sp)
640         stt     $f13,(13*8+offes_fltregs)(sp)
641         stt     $f14,(14*8+offes_fltregs)(sp)
642         stt     $f15,(15*8+offes_fltregs)(sp)
643         stt     $f16,(16*8+offes_fltregs)(sp)
644         stt     $f17,(17*8+offes_fltregs)(sp)
645         stt     $f18,(18*8+offes_fltregs)(sp)
646         stt     $f19,(19*8+offes_fltregs)(sp)
647         stt     $f20,(20*8+offes_fltregs)(sp)
648         stt     $f21,(21*8+offes_fltregs)(sp)
649         stt     $f22,(22*8+offes_fltregs)(sp)
650         stt     $f23,(23*8+offes_fltregs)(sp)
651         stt     $f24,(24*8+offes_fltregs)(sp)
652         stt     $f25,(25*8+offes_fltregs)(sp)
653         stt     $f26,(26*8+offes_fltregs)(sp)
654         stt     $f27,(27*8+offes_fltregs)(sp)
655         stt     $f28,(28*8+offes_fltregs)(sp)
656         stt     $f29,(29*8+offes_fltregs)(sp)
657         stt     $f30,(30*8+offes_fltregs)(sp)
658         stt     $f31,(31*8+offes_fltregs)(sp)
659         
660         /* calculate sp of method */
661         lda     itmp1,(REPLACEMENT_STACK_OFFSET + 2*8)(sp)
662         stq     itmp1,(offes_sp)(sp)
663
664         br      ra,L_asm_replacement_out_load_gp
665 L_asm_replacement_out_load_gp:
666         ldgp    gp,0(ra)                    /* load gp                            */
667
668         /* store pv */
669         stq     pv,(offes_pv)(sp)
670
671         /* call replace_me */
672         ldq     a0,-(2*8)(itmp1)            /* arg0: rplpoint *                   */
673     mov     sp,a1                       /* arg1: execution state              */
674     jmp     zero,replace_me             /* call C function replace_me         */
675     jmp     zero,abort                  /* NEVER REACHED                      */
676
677         .end asm_replacement_out
678
679 /* asm_replacement_in **********************************************************
680
681    This code writes the given execution state and jumps to the replacement
682    code.
683
684    This function never returns!
685
686    NOTE: itmp3 is not restored!
687
688    C prototype:
689       void asm_replacement_in(executionstate *es);
690
691 *******************************************************************************/
692
693         .ent asm_replacement_in
694         
695 asm_replacement_in:
696         /* a0 == executionstate *es */
697
698         /* set new sp and pv */
699         ldq     sp,(offes_sp)(a0)
700         ldq     pv,(offes_pv)(a0)
701         
702         /* copy registers from execution state */
703         ldq     $0 ,( 0*8+offes_intregs)(a0)
704         ldq     $1 ,( 1*8+offes_intregs)(a0)
705         ldq     $2 ,( 2*8+offes_intregs)(a0)
706         ldq     $3 ,( 3*8+offes_intregs)(a0)
707         ldq     $4 ,( 4*8+offes_intregs)(a0)
708         ldq     $5 ,( 5*8+offes_intregs)(a0)
709         ldq     $6 ,( 6*8+offes_intregs)(a0)
710         ldq     $7 ,( 7*8+offes_intregs)(a0)
711         ldq     $8 ,( 8*8+offes_intregs)(a0)
712         ldq     $9 ,( 9*8+offes_intregs)(a0)
713         ldq     $10,(10*8+offes_intregs)(a0)
714         ldq     $11,(11*8+offes_intregs)(a0)
715         ldq     $12,(12*8+offes_intregs)(a0)
716         ldq     $13,(13*8+offes_intregs)(a0)
717         ldq     $14,(14*8+offes_intregs)(a0)
718         ldq     $15,(15*8+offes_intregs)(a0)
719         /* a0 is loaded below             */
720         ldq     $17,(17*8+offes_intregs)(a0)
721         ldq     $18,(18*8+offes_intregs)(a0)
722         ldq     $19,(19*8+offes_intregs)(a0)
723         ldq     $20,(20*8+offes_intregs)(a0)
724         ldq     $21,(21*8+offes_intregs)(a0)
725         ldq     $22,(22*8+offes_intregs)(a0)
726         ldq     $23,(23*8+offes_intregs)(a0)
727         ldq     $24,(24*8+offes_intregs)(a0)
728         ldq     $25,(25*8+offes_intregs)(a0)
729         ldq     $26,(26*8+offes_intregs)(a0)
730         /* $27 is pv                      */
731         ldq     $28,(28*8+offes_intregs)(a0)
732         ldq     $29,(29*8+offes_intregs)(a0)
733         /* $30 is sp                      */
734         /* $31 is zero                    */
735         
736         ldt     $f0 ,( 0*8+offes_fltregs)(a0)
737         ldt     $f1 ,( 1*8+offes_fltregs)(a0)
738         ldt     $f2 ,( 2*8+offes_fltregs)(a0)
739         ldt     $f3 ,( 3*8+offes_fltregs)(a0)
740         ldt     $f4 ,( 4*8+offes_fltregs)(a0)
741         ldt     $f5 ,( 5*8+offes_fltregs)(a0)
742         ldt     $f6 ,( 6*8+offes_fltregs)(a0)
743         ldt     $f7 ,( 7*8+offes_fltregs)(a0)
744         ldt     $f8 ,( 8*8+offes_fltregs)(a0)
745         ldt     $f9 ,( 9*8+offes_fltregs)(a0)
746         ldt     $f10,(10*8+offes_fltregs)(a0)
747         ldt     $f11,(11*8+offes_fltregs)(a0)
748         ldt     $f12,(12*8+offes_fltregs)(a0)
749         ldt     $f13,(13*8+offes_fltregs)(a0)
750         ldt     $f14,(14*8+offes_fltregs)(a0)
751         ldt     $f15,(15*8+offes_fltregs)(a0)
752         ldt     $f16,(16*8+offes_fltregs)(a0)
753         ldt     $f17,(17*8+offes_fltregs)(a0)
754         ldt     $f18,(18*8+offes_fltregs)(a0)
755         ldt     $f19,(19*8+offes_fltregs)(a0)
756         ldt     $f20,(20*8+offes_fltregs)(a0)
757         ldt     $f21,(21*8+offes_fltregs)(a0)
758         ldt     $f22,(22*8+offes_fltregs)(a0)
759         ldt     $f23,(23*8+offes_fltregs)(a0)
760         ldt     $f24,(24*8+offes_fltregs)(a0)
761         ldt     $f25,(25*8+offes_fltregs)(a0)
762         ldt     $f26,(26*8+offes_fltregs)(a0)
763         ldt     $f27,(27*8+offes_fltregs)(a0)
764         ldt     $f28,(28*8+offes_fltregs)(a0)
765         ldt     $f29,(29*8+offes_fltregs)(a0)
766         ldt     $f30,(30*8+offes_fltregs)(a0)
767         ldt     $f31,(31*8+offes_fltregs)(a0)
768
769         /* load new pc */
770
771         ldq     itmp3,offes_pc(a0)
772
773         /* load a0 */
774         
775         ldq     a0,(16*8+offes_intregs)(a0)
776         
777         /* jump to new code */
778
779         jmp     zero,(itmp3)
780
781         .end asm_replacement_in
782
783 /******************* function asm_initialize_thread_stack **********************
784 *                                                                              *
785 *   initialized a thread stack                                                 *
786 *                                                                              *
787 *******************************************************************************/
788
789         .ent    asm_initialize_thread_stack
790
791 asm_initialize_thread_stack:
792         lda     a1,-128(a1)
793         stq     zero, 0(a1)
794         stq     zero, 8(a1)
795         stq     zero, 16(a1)
796         stq     zero, 24(a1)
797         stq     zero, 32(a1)
798         stq     zero, 40(a1)
799         stq     zero, 48(a1)
800         stt     fzero, 56(a1)
801         stt     fzero, 64(a1)
802         stt     fzero, 72(a1)
803         stt     fzero, 80(a1)
804         stt     fzero, 88(a1)
805         stt     fzero, 96(a1)
806         stt     fzero, 104(a1)
807         stt     fzero, 112(a1)
808         stq     a0, 120(a1)
809         mov     a1, v0
810         jmp     zero,(ra)
811
812         .end    asm_initialize_thread_stack
813
814
815 /******************* function asm_perform_threadswitch *************************
816 *                                                                              *
817 *   void asm_perform_threadswitch (u1 **from, u1 **to, u1 **stackTop);         *
818 *                                                                              *
819 *   performs a threadswitch                                                    *
820 *                                                                              *
821 *******************************************************************************/
822
823         .ent    asm_perform_threadswitch
824
825 asm_perform_threadswitch:
826         subq    sp,128,sp
827         stq     s0, 0(sp)
828         stq     s1, 8(sp)
829         stq     s2, 16(sp)
830         stq     s3, 24(sp)
831         stq     s4, 32(sp)
832         stq     s5, 40(sp)
833         stq     s6, 48(sp)
834         stt     fs0, 56(sp)
835         stt     fs1, 64(sp)
836         stt     fs2, 72(sp)
837         stt     fs3, 80(sp)
838         stt     fs4, 88(sp)
839         stt     fs5, 96(sp)
840         stt     fs6, 104(sp)
841         stt     fs7, 112(sp)
842         stq     ra, 120(sp)
843         stq     sp, 0(a0)
844         stq     sp, 0(a2)
845         ldq     sp, 0(a1)
846         ldq     s0, 0(sp)
847         ldq     s1, 8(sp)
848         ldq     s2, 16(sp)
849         ldq     s3, 24(sp)
850         ldq     s4, 32(sp)
851         ldq     s5, 40(sp)
852         ldq     s6, 48(sp)
853         ldt     fs0, 56(sp)
854         ldt     fs1, 64(sp)
855         ldt     fs2, 72(sp)
856         ldt     fs3, 80(sp)
857         ldt     fs4, 88(sp)
858         ldt     fs5, 96(sp)
859         ldt     fs6, 104(sp)
860         ldt     fs7, 112(sp)
861         ldq     ra, 120(sp)
862         mov     ra, pv
863         addq    sp, 128, sp
864         jmp     zero,(ra)
865
866         .end    asm_perform_threadswitch
867
868
869 /********************* function asm_switchstackandcall *************************
870 *                                                                              *
871 *  void *asm_switchstackandcall (void *stack, void *func, void **stacktopsave, *
872 *                               void *p);                                      *
873 *                                                                              *
874 *   Switches to a new stack, calls a function and switches back.               *
875 *       a0      new stack pointer                                              *
876 *       a1      function pointer                                               *
877 *               a2              pointer to variable where stack top should be stored           *
878 *               a3      pointer to user data, is passed to the function                *
879 *                                                                              *
880 *******************************************************************************/
881
882
883         .ent    asm_switchstackandcall
884
885 asm_switchstackandcall:
886         lda     a0,-2*8(a0)     /* allocate new stack                                 */
887         stq     ra,0(a0)        /* save return address on new stack                   */
888         stq     sp,1*8(a0)      /* save old stack pointer on new stack                */
889         stq sp,0(a2)        /* save old stack pointer to variable                 */
890         mov     a0,sp           /* switch to new stack                                */
891         
892         mov     a1,pv           /* load function pointer                              */
893         mov a3,a0           /* pass pointer */
894         jmp     ra,(pv)         /* and call function                                  */
895
896         ldq     ra,0(sp)        /* load return address                                */
897         ldq     sp,1*8(sp)      /* switch to old stack                                */
898
899         jmp     zero,(ra)       /* return                                             */
900
901         .end    asm_switchstackandcall
902
903
904         .ent    asm_getclassvalues_atomic
905
906 asm_getclassvalues_atomic:
907 _crit_restart:
908 _crit_begin:
909         ldl     t0,offbaseval(a0)
910         ldl     t1,offdiffval(a0)
911         ldl     t2,offbaseval(a1)
912 _crit_end:
913         stl     t0,offcast_super_baseval(a2)
914         stl     t1,offcast_super_diffval(a2)
915         stl     t2,offcast_sub_baseval(a2)
916         jmp     zero,(ra)
917
918         .end    asm_getclassvalues_atomic
919
920
921     .data
922
923 asm_criticalsections:
924 #if defined(USE_THREADS) && defined(NATIVE_THREADS)
925     .quad   _crit_begin
926     .quad   _crit_end
927     .quad   _crit_restart
928 #endif
929     .quad   0
930
931
932 /* asm_md_init *****************************************************************
933
934    Initialize machine dependent stuff.
935
936    Determines if the byte support instruction set (21164a and higher)
937    is available.
938
939 *******************************************************************************/
940
941         .ent    asm_md_init
942
943 asm_md_init:
944         .long   0x47e03c20                  /* amask   1,v0                       */
945         jmp     zero,(ra)                   /* return                             */
946
947         .end    asm_md_init
948
949
950 /* asm_cacheflush **************************************************************
951
952    XXX
953
954 *******************************************************************************/
955
956         .ent    asm_cacheflush
957
958 asm_cacheflush:
959         call_pal PAL_imb              /* synchronize instruction cache            */
960         jmp     zero,(ra)
961
962         .end    asm_cacheflush
963
964
965 /* Disable exec-stacks, required for Gentoo ***********************************/
966
967 #if defined(__GCC__) && defined(__ELF__)
968         .section .note.GNU-stack,"",@progbits
969 #endif
970
971
972 /*
973  * These are local overrides for various environment variables in Emacs.
974  * Please do not remove this and leave it at the end of the file, where
975  * Emacs will automagically detect them.
976  * ---------------------------------------------------------------------
977  * Local variables:
978  * mode: asm
979  * indent-tabs-mode: t
980  * c-basic-offset: 4
981  * tab-width: 4
982  * End:
983  * vim:noexpandtab:sw=4:ts=4:
984  */