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