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