d69e59c6287a1ea4c9509738101d7a3652c2f3ee
[cacao.git] / src / vm / jit / mips / asmpart.S
1 /* src/vm/jit/mips/asmpart.S - Java-C interface functions for MIPS
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 */
26
27
28 #include "config.h"
29
30 #include "vm/jit/mips/md-abi.h"
31 #include "vm/jit/mips/md-asm.h"
32
33 #include "vm/jit/abi-asm.h"
34 #include "vm/jit/methodheader.h"
35
36
37         .text
38         .set    noat
39
40
41 /* export functions ***********************************************************/
42
43         .globl asm_vm_call_method
44         .globl asm_vm_call_method_int
45         .globl asm_vm_call_method_long
46         .globl asm_vm_call_method_float
47         .globl asm_vm_call_method_double
48         .globl asm_vm_call_method_exception_handler
49         .globl asm_vm_call_method_end
50
51         .globl asm_call_jit_compiler
52
53         .globl asm_handle_exception
54         .globl asm_handle_nat_exception
55
56         .globl asm_abstractmethoderror
57
58         .globl compare_and_swap
59
60
61 /* asm_vm_call_method **********************************************************
62 *                                                                              *
63 *   This function calls a Java-method (which possibly needs compilation)       *
64 *   with up to 4 address parameters.                                           *
65 *                                                                              *
66 *   This functions calls the JIT-compiler which eventually translates the      *
67 *   method into machine code.                                                  *
68 *                                                                              *
69 *   A possibly throwed exception will be returned to the caller as function    *
70 *   return value, so the java method cannot return a fucntion value (this      *
71 *   function usually calls 'main' and '<clinit>' which do not return a         *
72 *   function value).                                                           *
73 *                                                                              *
74 *   C-prototype:                                                               *
75 *    javaobject_header *asm_calljavafunction (methodinfo *m,                   *
76 *         void *arg1, void *arg2, void *arg3, void *arg4);                     *
77 *                                                                              *
78 *******************************************************************************/
79
80         .ent    asm_vm_call_method
81
82         .align  3
83
84 #if SIZEOF_VOID_P == 8
85
86         .dword  0                           /* catch type all                     */
87         .dword  0                           /* handler pc                         */
88         .dword  0                           /* end pc                             */
89         .dword  0                           /* start pc                           */
90         .word   1                           /* extable size                       */
91         .word   0                           /* 4-byte ALIGNMENT PADDING           */
92         .dword  0                           /* line number table start            */
93         .dword  0                           /* line number table size             */
94         .word   0                           /* 4-byte ALIGNMENT PADDING           */
95         .word   0                           /* fltsave                            */
96         .word   0                           /* intsave                            */
97         .word   0                           /* isleaf                             */
98         .word   0                           /* IsSync                             */
99         .word   0                           /* frame size                         */
100         .dword  0                           /* codeinfo pointer                   */
101
102 #else /* SIZEOF_VOID_P == 8 */
103
104         .word   0                           /* catch type all                     */
105         .word   0                           /* handler pc                         */
106         .word   0                           /* end pc                             */
107         .word   0                           /* start pc                           */
108         .word   1                           /* extable size                       */
109         .word   0                           /* line number table start            */
110         .word   0                           /* line number table size             */
111         .word   0                           /* fltsave                            */
112         .word   0                           /* intsave                            */
113         .word   0                           /* isleaf                             */
114         .word   0                           /* IsSync                             */
115         .word   0                           /* frame size                         */
116         .word   0                           /* method pointer (pointer to name)   */
117
118 #endif /* SIZEOF_VOID_P == 8 */
119
120 asm_vm_call_method:
121 asm_vm_call_method_int:
122 asm_vm_call_method_long:
123 asm_vm_call_method_float:
124 asm_vm_call_method_double:
125         .set    noreorder                 /* XXX we need to recompute pv          */
126
127         aaddiu  sp,sp,-12*8               /* allocate stack space (only 11 needed)*/
128         ast     ra,0*8(sp)                /* save return address                  */
129
130         bal     L_asm_vm_call_method_compute_pv
131         ast     pv,1*8(sp)                /* procedure vector                     */
132 L_asm_vm_call_method_compute_pv:
133         aaddiu  pv,ra,-4*4
134
135         ast     s0,3*8(sp)                /* save callee saved register           */
136         ast     a0,4*8(sp)                /* save method PV                       */
137
138 #if SIZEOF_VOID_P == 8
139         sdc1    fss0,5*8(sp)              /* save non JavaABI saved flt registers */
140         sdc1    fss1,6*8(sp)
141         sdc1    fss2,7*8(sp)
142         sdc1    fss3,8*8(sp)
143         sdc1    fss4,9*8(sp)
144         sdc1    fss5,10*8(sp)
145 #endif
146
147         move    t0,a1                     /* address of data structure            */
148         move    t1,a2                     /* stack argument count                 */
149         move    s0,sp                     /* save stack pointer                   */
150
151 #if SIZEOF_VOID_P == 8
152
153         ld      a0,0*8(t0)
154         ld      a1,1*8(t0)
155         ld      a2,2*8(t0)
156         ld      a3,3*8(t0)
157         ld      a4,4*8(t0)
158         ld      a5,5*8(t0)
159         ld      a6,6*8(t0)
160         ld      a7,7*8(t0)
161
162         ldc1    fa0,8*8(t0)
163         ldc1    fa1,9*8(t0)
164         ldc1    fa2,10*8(t0)
165         ldc1    fa3,11*8(t0)
166         ldc1    fa4,12*8(t0)
167         ldc1    fa5,13*8(t0)
168         ldc1    fa6,14*8(t0)
169         ldc1    fa7,15*8(t0)
170
171 #else /* SIZEOF_VOID_P == 8 */
172
173 # if WORDS_BIGENDIAN == 1
174         lw      a0,0*8+4(t0)
175         lw      a1,1*8+4(t0)
176         lw      a2,2*8+4(t0)
177         lw      a3,3*8+4(t0)
178 # else
179         lw      a0,0*8(t0)
180         lw      a1,1*8(t0)
181         lw      a2,2*8(t0)
182         lw      a3,3*8(t0)
183 # endif
184
185 # if !defined(ENABLE_SOFT_FLOAT)
186         ldc1    fa0,4*8(t0)
187         ldc1    fa1,5*8(t0)
188 # endif
189
190 #endif /* SIZEOF_VOID_P == 8 */
191
192         beqz    t1,L_asm_vm_call_method_stack_copy_done
193         nop
194
195         sll     t2,t1,3                   /* calculate stackframe size (* 8)      */
196         asubu   sp,sp,t2                  /* create stackframe                    */
197         move    t2,sp                     /* temporary stack pointer              */
198
199 L_asm_vm_call_method_stack_copy_loop:
200 #if SIZEOF_VOID_P == 8
201         ld      t3,16*8(t0)               /* load argument                        */
202         sd      t3,0(t2)                  /* store argument on stack              */
203 #else
204 # if !defined(ENABLE_SOFT_FLOAT)
205         lw      t3,6*8+0(t0)              /* load argument                        */
206         lw      t4,6*8+4(t0)
207         sw      t3,0(t2)                  /* store argument on stack              */
208         sw      t4,4(t2)
209 # else
210 #  error implement me
211 # endif
212 #endif
213
214         aaddi   t1,t1,-1                  /* subtract 1 argument                  */
215         aaddi   t0,t0,8                   /* load address of next argument        */
216         aaddi   t2,t2,8                   /* increase stack pointer               */
217
218         bgtz    t1,L_asm_vm_call_method_stack_copy_loop
219         nop
220
221 L_asm_vm_call_method_stack_copy_done:
222         ala     mptr,4*8(s0)              /* get address of PV                    */
223         ald     pv,0*8(mptr)              /* load PV                              */
224         jalr    pv
225         nop
226 L_asm_vm_call_method_recompute_pv:
227 #if SIZEOF_VOID_P == 8
228         aaddiu  pv,ra,-76*4               /* recompute procedure vector           */
229 #else
230         aaddiu  pv,ra,(asm_vm_call_method - L_asm_vm_call_method_recompute_pv)
231 #endif
232
233         .set    reorder                   /* XXX we need to recompute pv          */
234
235         move    sp,s0                     /* restore stack pointer                */
236
237 calljava_return2:
238         ald     ra,0*8(sp)                /* restore return address               */
239         ald     pv,1*8(sp)                /* restore procedure vector             */
240         ald     s0,3*8(sp)
241
242 #if SIZEOF_VOID_P == 8
243         ldc1    fss0,5*8(sp)              /* restore non JavaABI saved flt regs   */
244         ldc1    fss1,6*8(sp)
245         ldc1    fss2,7*8(sp)
246         ldc1    fss3,8*8(sp)
247         ldc1    fss4,9*8(sp)
248         ldc1    fss5,10*8(sp)
249 #endif
250
251         aaddiu  sp,sp,12*8                /* free stack space                     */
252         j       ra                        /* return                               */
253
254 asm_vm_call_method_exception_handler:
255         move    sp,s0                     /* restore stack pointer                */
256 #if SIZEOF_VOID_P == 4
257         aaddiu  sp,sp,-4*4                /* reserve space for 1 argument         */
258 #endif
259
260         move    a0,itmp1                  
261         jal     builtin_throw_exception
262 #if SIZEOF_VOID_P == 4
263         aaddiu  sp,sp,4*4
264 #endif
265 asm_vm_call_method_end:
266         b       calljava_return2
267
268         .end    asm_vm_call_method
269
270
271 /****************** function asm_call_jit_compiler *****************************
272 *                                                                              *
273 *   invokes the compiler for untranslated JavaVM methods.                      *
274 *                                                                              *
275 *   Register REG_ITEMP1 contains a pointer to the method info structure        *
276 *   (prepared by createcompilerstub). Using the return address in R31 and the  *
277 *   offset in the LDA instruction or using the value in methodptr R25 the      *
278 *   patching address for storing the method address can be computed:           *
279 *                                                                              *
280 *   method address was either loaded using                                     *
281 *   M_ALD (REG_PV, REG_PV, a)        ; invokestatic/special    ($28)           *
282 *   M_JSR (REG_RA, REG_PV);                                                    *
283 *   M_NOP                                                                      *
284 *   M_LDA (REG_PV, REG_RA, val)                                                *
285 *   or                                                                         *
286 *   M_ALD (REG_PV, REG_METHODPTR, m) ; invokevirtual/interface ($25)           *
287 *   M_JSR (REG_RA, REG_PV);                                                    *
288 *   M_NOP                                                                      *
289 *   in the static case the method pointer can be computed using the            *
290 *   return address and the lda function following the jmp instruction          *
291 *                                                                              *
292 *******************************************************************************/
293
294         .ent    asm_call_jit_compiler
295
296 asm_call_jit_compiler:
297 #if SIZEOF_VOID_P == 8
298
299         aaddiu  sp,sp,-(ARG_CNT+2)*8  /* +2: keep stack 16-bytes aligned          */
300
301         ast     ra,0*8(sp)            /* save return address                      */
302
303         SAVE_ARGUMENT_REGISTERS(1)
304
305         move    a0,itmp1              /* pass methodinfo pointer                  */
306         move    a1,mptr               /* pass method pointer                      */
307         aaddiu  a2,sp,(ARG_CNT+2)*8   /* pass java sp                             */
308         move    a3,ra
309         jal     jit_asm_compile       /* call jit compiler                        */
310         move    pv,v0
311
312         ald     ra,0*8(sp)            /* restore return address                   */
313
314         RESTORE_ARGUMENT_REGISTERS(1)
315
316         aaddiu  sp,sp,(ARG_CNT+2)*8   /* remove stack frame                       */
317
318 #else /* SIZEOF_VOID_P == 8 */
319
320         aaddiu  sp,sp,-(ARG_CNT+2)*8  /* +4: keep stack 16-bytes aligned          */
321
322         ast     ra,4*4+0*4(sp)        /* save return address                      */
323
324         SAVE_ARGUMENT_REGISTERS(6)
325
326         move    a0,itmp1              /* pass methodinfo pointer                  */
327         move    a1,mptr               /* pass method pointer                      */
328         aaddiu  a2,sp,(ARG_CNT+2)*8   /* pass java sp                             */
329         move    a3,ra
330         jal     jit_asm_compile       /* call jit compiler                        */
331         move    pv,v0
332
333         ald     ra,4*4+0*4(sp)        /* restore return address                   */
334
335         RESTORE_ARGUMENT_REGISTERS(6)
336
337         aaddiu  sp,sp,(ARG_CNT+2)*8   /* remove stack frame                       */
338
339 #endif /* SIZEOF_VOID_P == 8 */
340
341         beqz    pv,L_asm_call_jit_compiler_exception
342
343         jr      pv                    /* and call method. The method returns      */
344                                       /* directly to the caller (ra).             */
345
346 L_asm_call_jit_compiler_exception:
347         aaddiu  sp,sp,-2*8
348         ast     ra,0*8(sp)
349         jal     exceptions_get_and_clear_exception
350         ald     ra,0*8(sp)
351         aaddiu  sp,sp,2*8
352
353         move    xptr,v0               /* get exception                            */
354         aaddiu  xpc,ra,-4             /* exception address is RA - 4              */
355         b       asm_handle_nat_exception
356
357         .end    asm_call_jit_compiler
358
359
360 /* asm_handle_exception ********************************************************
361
362    This function handles an exception. It does not use the usual calling
363    conventions. The exception pointer is passed in REG_ITMP1 and the
364    pc from the exception raising position is passed in REG_ITMP2. It searches
365    the local exception table for a handler. If no one is found, it unwinds
366    stacks and continues searching the callers.
367
368 *******************************************************************************/
369
370         .ent    asm_handle_nat_exception
371
372 asm_handle_nat_exception:
373 L_asm_handle_exception_stack_loop:
374 #if SIZEOF_VOID_P == 8
375         aaddiu  sp,sp,-6*8                  /* keep stack 16-byte aligned         */
376         ast     xptr,0*8(sp)                /* save exception pointer             */
377         ast     xpc,1*8(sp)                 /* save exception pc                  */
378         ast     ra,3*8(sp)                  /* save RA                            */
379         ast     zero,4*8(sp)                /* save maybe-leaf flag (cleared)     */
380 #else
381         aaddiu  sp,sp,-(4*4+6*8)            /* allocate stack                     */
382         ast     xptr,4*4+0*8(sp)            /* save exception pointer             */
383         ast     xpc,4*4+1*8(sp)             /* save exception pc                  */
384         ast     ra,4*4+3*8(sp)              /* save return address                */
385         ast     zero,4*4+4*8(sp)            /* save maybe-leaf flag (cleared)     */
386 #endif
387
388         move    a0,ra                       /* pass RA                            */
389         jal     md_codegen_get_pv_from_pc   /* get PV from RA                     */
390
391 #if SIZEOF_VOID_P == 8
392         ast     v0,2*8(sp)                  /* save PV                            */
393
394         ald     a0,0*8(sp)                  /* pass xptr                          */
395         ald     a1,1*8(sp)                  /* pass xpc                           */
396         move    a2,v0                       /* pass PV                            */
397         aaddiu  a3,sp,6*8                   /* pass Java SP                       */
398 #else
399         ast     v0,4*4+2*8(sp)              /* save data segment pointer          */
400
401         ald     a0,4*4+0*8(sp)              /* pass exception pointer             */
402         ald     a1,4*4+1*8(sp)              /* pass exception pc                  */
403         move    a2,v0                       /* pass data segment pointer          */
404         aaddiu  a3,sp,(4*4+6*8)             /* pass Java stack pointer            */
405 #endif
406
407         b       L_asm_handle_exception_continue
408
409         .aent    asm_handle_exception
410
411 asm_handle_exception:
412         aaddiu  sp,sp,-(ARG_CNT+TMP_CNT)*8  /* create maybe-leaf stackframe       */
413
414         SAVE_ARGUMENT_REGISTERS(0)          /* we save arg and temp registers in  */
415         SAVE_TEMPORARY_REGISTERS(ARG_CNT)   /* case this is a leaf method         */
416
417 #if SIZEOF_VOID_P == 8
418         aaddiu  sp,sp,-6*8                  /* allocate stack                     */
419         ast     xptr,0*8(sp)                /* save exception pointer             */
420         ast     pv,2*8(sp)                  /* save PV                            */
421         ast     ra,3*8(sp)                  /* save RA                            */
422         addu    t0,zero,1                   /* set maybe-leaf flag                */
423         ast     t0,4*8(sp)                  /* save maybe-leaf flag               */
424 #else
425         aaddiu  sp,sp,-(4*4+6*8)            /* allocate stack                     */
426         ast     xptr,4*4+0*8(sp)            /* save exception pointer             */
427         ast     xpc,4*4+1*8(sp)             /* save exception pc                  */
428         ast     pv,4*4+2*8(sp)              /* save data segment pointer          */
429         ast     ra,4*4+3*8(sp)              /* save return address                */
430         addu    t0,zero,1                   /* set maybe-leaf flag                */
431         ast     t0,4*4+4*8(sp)              /* save maybe-leaf flag               */
432 #endif
433
434         move    a0,xptr                     /* pass xptr                          */
435         move    a1,xpc                      /* pass xpc                           */
436         move    a2,pv                       /* pass PV                            */
437
438 #if SIZEOF_VOID_P == 8
439         aaddiu  a3,sp,(ARG_CNT+TMP_CNT+6)*8 /* pass Java SP                       */
440 #else
441         aaddiu  a3,sp,4*4+(ARG_CNT+TMP_CNT+6)*8 /* pass Java stack pointer        */
442 #endif
443
444 L_asm_handle_exception_continue:
445         jal     exceptions_handle_exception
446         
447         beqz    v0,L_asm_handle_exception_not_catched
448
449         move    xpc,v0                      /* move handlerpc into xpc            */
450
451 #if SIZEOF_VOID_P == 8
452         ald     xptr,0*8(sp)                /* restore exception pointer          */
453         ald     pv,2*8(sp)                  /* restore PV                         */
454         ald     ra,3*8(sp)                  /* restore RA                         */
455         ald     t0,4*8(sp)                  /* get maybe-leaf flag                */
456         aaddiu  sp,sp,6*8                   /* free stackframe                    */
457 #else
458         ald     xptr,4*4+0*8(sp)            /* restore exception pointer          */
459         ald     pv,4*4+2*8(sp)              /* restore data segment pointer       */
460         ald     ra,4*4+3*8(sp)              /* restore return address             */
461         ald     t0,4*4+4*8(sp)              /* get maybe-leaf flag                */
462         aaddiu  sp,sp,4*4+6*8               /* free stackframe                    */
463 #endif
464         
465         beqz    t0,L_asm_handle_exception_no_leaf
466
467         RESTORE_ARGUMENT_REGISTERS(0)       /* if this is a leaf method, we have  */
468         RESTORE_TEMPORARY_REGISTERS(ARG_CNT)/* to restore arg and temp registers  */
469         
470         aaddiu  sp,sp,(ARG_CNT+TMP_CNT)*8   /* remove maybe-leaf stackframe       */
471
472 L_asm_handle_exception_no_leaf:
473         jr      xpc                         /* jump to the handler                */
474
475 L_asm_handle_exception_not_catched:
476 #if SIZEOF_VOID_P == 8
477         ald     xptr,0*8(sp)                /* restore xptr                       */
478         ald     pv,2*8(sp)                  /* restore PV                         */
479         ald     ra,3*8(sp)                  /* restore RA                         */
480         ald     t0,4*8(sp)                  /* get maybe-leaf flag                */
481         aaddiu  sp,sp,6*8                   /* free stackframe                    */
482 #else
483         ald     xptr,4*4+0*8(sp)            /* restore xptr                       */
484         ald     pv,4*4+2*8(sp)              /* restore PV                         */
485         ald     ra,4*4+3*8(sp)              /* restore RA                         */
486         ald     t0,4*4+4*8(sp)              /* get maybe-leaf flag                */
487         aaddiu  sp,sp,4*4+6*8               /* free stackframe                    */
488 #endif
489         
490         beqz    t0,L_asm_handle_exception_no_leaf_stack
491
492         aaddiu  sp,sp,(ARG_CNT+TMP_CNT)*8   /* remove maybe-leaf stackframe       */
493         move    t0,zero                     /* clear the maybe-leaf flag          */
494
495 L_asm_handle_exception_no_leaf_stack:
496         lw      t1,FrameSize(pv)            /* get frame size                     */
497         aaddu   t1,sp,t1                    /* pointer to save area               */
498
499         lw      t2,IsLeaf(pv)               /* is leaf procedure                  */
500         bnez    t2,L_asm_handle_exception_no_ra_restore
501
502         ald     ra,-1*8(t1)                 /* restore ra                         */
503         aaddiu  t1,t1,-8                    /* t1--                               */
504
505 L_asm_handle_exception_no_ra_restore:
506         move    xpc,ra                      /* the new xpc is ra                  */
507         lw      t2,IntSave(pv)              /* t1 = saved int register count      */
508         ala     t3,ex_int2                  /* t3 = current pc                    */
509         sll     t2,t2,2                     /* t2 = register count * 4            */
510         asubu   t3,t3,t2                    /* t3 = IntSave - 4 * register count  */
511         jr      t3                          /* jump to save position              */
512
513         ald     s0,-8*8(t1)
514         ald     s1,-7*8(t1)
515         ald     s2,-6*8(t1)
516         ald     s3,-5*8(t1)
517         ald     s4,-4*8(t1)
518         ald     s5,-3*8(t1)
519         ald     s6,-2*8(t1)
520         ald     s7,-1*8(t1)
521
522 ex_int2:
523         sll     t2,t2,1               /* t2 = register count * 4 * 2              */
524         asubu   t1,t1,t2              /* t1 = t0 - 8 * register count             */
525
526         lw      t2,FltSave(pv)        /* t2 = saved flt register count            */
527         ala     t3,ex_flt2            /* t3 = current pc                          */
528         sll     t2,t2,2               /* t2 = register count * 4                  */
529         asubu   t3,t3,t2              /* t3 = ex_int_sav - 4 * register count     */
530         jr      t3                          /* jump to save position              */
531
532 #if SIZEOF_VOID_P == 8
533         ldc1    fs0,-4*8(t1)
534         ldc1    fs1,-3*8(t1)
535         ldc1    fs2,-2*8(t1)
536         ldc1    fs3,-1*8(t1)
537 #else /* SIZEOF_VOID_P == 8 */
538 # if !defined(ENABLE_SOFT_FLOAT)
539         ldc1    fs0,-4*8(t1)
540         ldc1    fs1,-3*8(t1)
541         ldc1    fs2,-2*8(t1)
542         ldc1    fs3,-1*8(t1)
543         ldc1    fs4,-1*8(t1)
544         ldc1    fs5,-1*8(t1)
545 # endif /* !defined(ENABLE_SOFT_FLOAT) */
546 #endif /* SIZEOF_VOID_P == 8 */
547
548 ex_flt2:
549         lw      t1,FrameSize(pv)            /* get frame size                     */
550         aaddu   sp,sp,t1                    /* unwind stack                       */
551         b       L_asm_handle_exception_stack_loop
552
553         .end    asm_handle_nat_exception
554
555
556 /* asm_abstractmethoderror *****************************************************
557
558    Creates and throws an AbstractMethodError.
559
560 *******************************************************************************/
561
562         .ent    asm_abstractmethoderror
563
564 asm_abstractmethoderror:
565         aaddiu  sp,sp,-2*8                  /* create stackframe                  */
566         ast     ra,0*8(sp)                  /* save return address                */
567         aaddiu  a0,sp,2*8                   /* pass java sp                       */
568         move    a1,ra                       /* pass exception address             */
569         jal     exceptions_asm_new_abstractmethoderror
570         ald     ra,0*8(sp)                  /* restore return address             */
571         aaddiu  sp,sp,2*8                   /* remove stackframe                  */
572
573         move    xptr,v0                     /* get exception pointer              */
574         aaddiu  xpc,ra,-4                   /* exception address is ra - 4        */
575         b       asm_handle_nat_exception
576
577         .end    asm_abstractmethoderror
578
579
580         .ent    compare_and_swap
581
582 compare_and_swap:
583 1:
584         all     v0,0(a0)
585         bne     v0,a1,2f
586         move    t0,a2
587         asc     t0,0(a0)
588         beqz    t0,1b
589 2:
590         sync
591         j       ra
592
593         .end    compare_and_swap
594
595
596 /* disable exec-stacks ********************************************************/
597
598 #if defined(__linux__) && defined(__ELF__)
599         .section .note.GNU-stack,"",%progbits
600 #endif
601
602
603 /*
604  * These are local overrides for various environment variables in Emacs.
605  * Please do not remove this and leave it at the end of the file, where
606  * Emacs will automagically detect them.
607  * ---------------------------------------------------------------------
608  * Local variables:
609  * mode: asm
610  * indent-tabs-mode: t
611  * c-basic-offset: 4
612  * tab-width: 4
613  * End:
614  * vim:noexpandtab:sw=4:ts=4:
615  */