* Removed all Id tags.
[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 #if defined(ENABLE_REPLACEMENT)
59         .globl asm_replacement_out
60         .globl asm_replacement_in
61 #endif
62
63         .globl compare_and_swap
64
65
66 /* asm_vm_call_method **********************************************************
67 *                                                                              *
68 *   This function calls a Java-method (which possibly needs compilation)       *
69 *   with up to 4 address parameters.                                           *
70 *                                                                              *
71 *   This functions calls the JIT-compiler which eventually translates the      *
72 *   method into machine code.                                                  *
73 *                                                                              *
74 *   A possibly throwed exception will be returned to the caller as function    *
75 *   return value, so the java method cannot return a fucntion value (this      *
76 *   function usually calls 'main' and '<clinit>' which do not return a         *
77 *   function value).                                                           *
78 *                                                                              *
79 *   C-prototype:                                                               *
80 *    javaobject_header *asm_calljavafunction (methodinfo *m,                   *
81 *         void *arg1, void *arg2, void *arg3, void *arg4);                     *
82 *                                                                              *
83 *******************************************************************************/
84
85         .ent    asm_vm_call_method
86
87         .align  3
88
89 #if SIZEOF_VOID_P == 8
90
91         .dword  0                           /* catch type all                     */
92         .dword  0                           /* handler pc                         */
93         .dword  0                           /* end pc                             */
94         .dword  0                           /* start pc                           */
95         .word   1                           /* extable size                       */
96         .word   0                           /* 4-byte ALIGNMENT PADDING           */
97         .dword  0                           /* line number table start            */
98         .dword  0                           /* line number table size             */
99         .word   0                           /* 4-byte ALIGNMENT PADDING           */
100         .word   0                           /* fltsave                            */
101         .word   0                           /* intsave                            */
102         .word   0                           /* isleaf                             */
103         .word   0                           /* IsSync                             */
104         .word   0                           /* frame size                         */
105         .dword  0                           /* codeinfo pointer                   */
106
107 #else /* SIZEOF_VOID_P == 8 */
108
109         .word   0                           /* catch type all                     */
110         .word   0                           /* handler pc                         */
111         .word   0                           /* end pc                             */
112         .word   0                           /* start pc                           */
113         .word   1                           /* extable size                       */
114         .word   0                           /* line number table start            */
115         .word   0                           /* line number table size             */
116         .word   0                           /* fltsave                            */
117         .word   0                           /* intsave                            */
118         .word   0                           /* isleaf                             */
119         .word   0                           /* IsSync                             */
120         .word   0                           /* frame size                         */
121         .word   0                           /* method pointer (pointer to name)   */
122
123 #endif /* SIZEOF_VOID_P == 8 */
124
125 asm_vm_call_method:
126 asm_vm_call_method_int:
127 asm_vm_call_method_long:
128 asm_vm_call_method_float:
129 asm_vm_call_method_double:
130         .set    noreorder                 /* XXX we need to recompute pv          */
131
132         aaddiu  sp,sp,-12*8               /* allocate stack space (only 11 needed)*/
133         ast     ra,0*8(sp)                /* save return address                  */
134
135         bal     L_asm_vm_call_method_compute_pv
136         ast     pv,1*8(sp)                /* procedure vector                     */
137 L_asm_vm_call_method_compute_pv:
138         aaddiu  pv,ra,-4*4
139
140         ast     s0,3*8(sp)                /* save callee saved register           */
141         ast     a0,4*8(sp)                /* save method PV                       */
142
143 #if SIZEOF_VOID_P == 8
144         sdc1    fss0,5*8(sp)              /* save non JavaABI saved flt registers */
145         sdc1    fss1,6*8(sp)
146         sdc1    fss2,7*8(sp)
147         sdc1    fss3,8*8(sp)
148         sdc1    fss4,9*8(sp)
149         sdc1    fss5,10*8(sp)
150 #endif
151
152         move    t0,a1                     /* address of data structure            */
153         move    t1,a2                     /* stack argument count                 */
154         move    s0,sp                     /* save stack pointer                   */
155
156 #if SIZEOF_VOID_P == 8
157
158         ld      a0,0*8(t0)
159         ld      a1,1*8(t0)
160         ld      a2,2*8(t0)
161         ld      a3,3*8(t0)
162         ld      a4,4*8(t0)
163         ld      a5,5*8(t0)
164         ld      a6,6*8(t0)
165         ld      a7,7*8(t0)
166
167         ldc1    fa0,8*8(t0)
168         ldc1    fa1,9*8(t0)
169         ldc1    fa2,10*8(t0)
170         ldc1    fa3,11*8(t0)
171         ldc1    fa4,12*8(t0)
172         ldc1    fa5,13*8(t0)
173         ldc1    fa6,14*8(t0)
174         ldc1    fa7,15*8(t0)
175
176 #else /* SIZEOF_VOID_P == 8 */
177
178 # if WORDS_BIGENDIAN == 1
179         lw      a0,0*8+4(t0)
180         lw      a1,1*8+4(t0)
181         lw      a2,2*8+4(t0)
182         lw      a3,3*8+4(t0)
183 # else
184         lw      a0,0*8(t0)
185         lw      a1,1*8(t0)
186         lw      a2,2*8(t0)
187         lw      a3,3*8(t0)
188 # endif
189
190 # if !defined(ENABLE_SOFT_FLOAT)
191         ldc1    fa0,4*8(t0)
192         ldc1    fa1,5*8(t0)
193 # endif
194
195 #endif /* SIZEOF_VOID_P == 8 */
196
197         beqz    t1,L_asm_vm_call_method_stack_copy_done
198         nop
199
200         sll     t2,t1,3                   /* calculate stackframe size (* 8)      */
201         asubu   sp,sp,t2                  /* create stackframe                    */
202         move    t2,sp                     /* temporary stack pointer              */
203
204 L_asm_vm_call_method_stack_copy_loop:
205 #if SIZEOF_VOID_P == 8
206         ld      t3,16*8(t0)               /* load argument                        */
207         sd      t3,0(t2)                  /* store argument on stack              */
208 #else
209 # if !defined(ENABLE_SOFT_FLOAT)
210         lw      t3,6*8+0(t0)              /* load argument                        */
211         lw      t4,6*8+4(t0)
212         sw      t3,0(t2)                  /* store argument on stack              */
213         sw      t4,4(t2)
214 # else
215 #  error implement me
216 # endif
217 #endif
218
219         aaddi   t1,t1,-1                  /* subtract 1 argument                  */
220         aaddi   t0,t0,8                   /* load address of next argument        */
221         aaddi   t2,t2,8                   /* increase stack pointer               */
222
223         bgtz    t1,L_asm_vm_call_method_stack_copy_loop
224         nop
225
226 L_asm_vm_call_method_stack_copy_done:
227         ala     mptr,4*8(s0)              /* get address of PV                    */
228         ald     pv,0*8(mptr)              /* load PV                              */
229         jalr    pv
230         nop
231 L_asm_vm_call_method_recompute_pv:
232 #if SIZEOF_VOID_P == 8
233         aaddiu  pv,ra,-76*4               /* recompute procedure vector           */
234 #else
235         aaddiu  pv,ra,(asm_vm_call_method - L_asm_vm_call_method_recompute_pv)
236 #endif
237
238         .set    reorder                   /* XXX we need to recompute pv          */
239
240         move    sp,s0                     /* restore stack pointer                */
241
242 calljava_return2:
243         ald     ra,0*8(sp)                /* restore return address               */
244         ald     pv,1*8(sp)                /* restore procedure vector             */
245         ald     s0,3*8(sp)
246
247 #if SIZEOF_VOID_P == 8
248         ldc1    fss0,5*8(sp)              /* restore non JavaABI saved flt regs   */
249         ldc1    fss1,6*8(sp)
250         ldc1    fss2,7*8(sp)
251         ldc1    fss3,8*8(sp)
252         ldc1    fss4,9*8(sp)
253         ldc1    fss5,10*8(sp)
254 #endif
255
256         aaddiu  sp,sp,12*8                /* free stack space                     */
257         j       ra                        /* return                               */
258
259 asm_vm_call_method_exception_handler:
260         move    sp,s0                     /* restore stack pointer                */
261 #if SIZEOF_VOID_P == 4
262         aaddiu  sp,sp,-4*4                /* reserve space for 1 argument         */
263 #endif
264
265         move    a0,itmp1                  
266         jal     builtin_throw_exception
267 #if SIZEOF_VOID_P == 4
268         aaddiu  sp,sp,4*4
269 #endif
270 asm_vm_call_method_end:
271         b       calljava_return2
272
273         .end    asm_vm_call_method
274
275
276 /****************** function asm_call_jit_compiler *****************************
277 *                                                                              *
278 *   invokes the compiler for untranslated JavaVM methods.                      *
279 *                                                                              *
280 *   Register REG_ITEMP1 contains a pointer to the method info structure        *
281 *   (prepared by createcompilerstub). Using the return address in R31 and the  *
282 *   offset in the LDA instruction or using the value in methodptr R25 the      *
283 *   patching address for storing the method address can be computed:           *
284 *                                                                              *
285 *   method address was either loaded using                                     *
286 *   M_ALD (REG_PV, REG_PV, a)        ; invokestatic/special    ($28)           *
287 *   M_JSR (REG_RA, REG_PV);                                                    *
288 *   M_NOP                                                                      *
289 *   M_LDA (REG_PV, REG_RA, val)                                                *
290 *   or                                                                         *
291 *   M_ALD (REG_PV, REG_METHODPTR, m) ; invokevirtual/interface ($25)           *
292 *   M_JSR (REG_RA, REG_PV);                                                    *
293 *   M_NOP                                                                      *
294 *   in the static case the method pointer can be computed using the            *
295 *   return address and the lda function following the jmp instruction          *
296 *                                                                              *
297 *******************************************************************************/
298
299         .ent    asm_call_jit_compiler
300
301 asm_call_jit_compiler:
302 #if SIZEOF_VOID_P == 8
303
304         aaddiu  sp,sp,-(ARG_CNT+2)*8  /* +2: keep stack 16-bytes aligned          */
305
306         ast     ra,0*8(sp)            /* save return address                      */
307
308         SAVE_ARGUMENT_REGISTERS(1)
309
310         move    a0,itmp1              /* pass methodinfo pointer                  */
311         move    a1,mptr               /* pass method pointer                      */
312         aaddiu  a2,sp,(ARG_CNT+2)*8   /* pass java sp                             */
313         move    a3,ra
314         jal     jit_asm_compile       /* call jit compiler                        */
315         move    pv,v0
316
317         ald     ra,0*8(sp)            /* restore return address                   */
318
319         RESTORE_ARGUMENT_REGISTERS(1)
320
321         aaddiu  sp,sp,(ARG_CNT+2)*8   /* remove stack frame                       */
322
323 #else /* SIZEOF_VOID_P == 8 */
324
325         aaddiu  sp,sp,-(ARG_CNT+2)*8  /* +4: keep stack 16-bytes aligned          */
326
327         ast     ra,4*4+0*4(sp)        /* save return address                      */
328
329         SAVE_ARGUMENT_REGISTERS(6)
330
331         move    a0,itmp1              /* pass methodinfo pointer                  */
332         move    a1,mptr               /* pass method pointer                      */
333         aaddiu  a2,sp,(ARG_CNT+2)*8   /* pass java sp                             */
334         move    a3,ra
335         jal     jit_asm_compile       /* call jit compiler                        */
336         move    pv,v0
337
338         ald     ra,4*4+0*4(sp)        /* restore return address                   */
339
340         RESTORE_ARGUMENT_REGISTERS(6)
341
342         aaddiu  sp,sp,(ARG_CNT+2)*8   /* remove stack frame                       */
343
344 #endif /* SIZEOF_VOID_P == 8 */
345
346         beqz    pv,L_asm_call_jit_compiler_exception
347
348         jr      pv                    /* and call method. The method returns      */
349                                       /* directly to the caller (ra).             */
350
351 L_asm_call_jit_compiler_exception:
352         aaddiu  sp,sp,-2*8
353         ast     ra,0*8(sp)
354         jal     exceptions_get_and_clear_exception
355         ald     ra,0*8(sp)
356         aaddiu  sp,sp,2*8
357
358         move    xptr,v0               /* get exception                            */
359         aaddiu  xpc,ra,-4             /* exception address is RA - 4              */
360         b       asm_handle_nat_exception
361
362         .end    asm_call_jit_compiler
363
364
365 /* asm_handle_exception ********************************************************
366
367    This function handles an exception. It does not use the usual calling
368    conventions. The exception pointer is passed in REG_ITMP1 and the
369    pc from the exception raising position is passed in REG_ITMP2. It searches
370    the local exception table for a handler. If no one is found, it unwinds
371    stacks and continues searching the callers.
372
373 *******************************************************************************/
374
375         .ent    asm_handle_nat_exception
376
377 asm_handle_nat_exception:
378 L_asm_handle_exception_stack_loop:
379 #if SIZEOF_VOID_P == 8
380         aaddiu  sp,sp,-6*8                  /* keep stack 16-byte aligned         */
381         ast     xptr,0*8(sp)                /* save exception pointer             */
382         ast     xpc,1*8(sp)                 /* save exception pc                  */
383         ast     ra,3*8(sp)                  /* save RA                            */
384         ast     zero,4*8(sp)                /* save maybe-leaf flag (cleared)     */
385 #else
386         aaddiu  sp,sp,-(4*4+6*8)            /* allocate stack                     */
387         ast     xptr,4*4+0*8(sp)            /* save exception pointer             */
388         ast     xpc,4*4+1*8(sp)             /* save exception pc                  */
389         ast     ra,4*4+3*8(sp)              /* save return address                */
390         ast     zero,4*4+4*8(sp)            /* save maybe-leaf flag (cleared)     */
391 #endif
392
393         move    a0,ra                       /* pass RA                            */
394         jal     md_codegen_get_pv_from_pc   /* get PV from RA                     */
395
396 #if SIZEOF_VOID_P == 8
397         ast     v0,2*8(sp)                  /* save PV                            */
398
399         ald     a0,0*8(sp)                  /* pass xptr                          */
400         ald     a1,1*8(sp)                  /* pass xpc                           */
401         move    a2,v0                       /* pass PV                            */
402         aaddiu  a3,sp,6*8                   /* pass Java SP                       */
403 #else
404         ast     v0,4*4+2*8(sp)              /* save data segment pointer          */
405
406         ald     a0,4*4+0*8(sp)              /* pass exception pointer             */
407         ald     a1,4*4+1*8(sp)              /* pass exception pc                  */
408         move    a2,v0                       /* pass data segment pointer          */
409         aaddiu  a3,sp,(4*4+6*8)             /* pass Java stack pointer            */
410 #endif
411
412         b       L_asm_handle_exception_continue
413
414         .aent    asm_handle_exception
415
416 asm_handle_exception:
417         aaddiu  sp,sp,-(ARG_CNT+TMP_CNT)*8  /* create maybe-leaf stackframe       */
418
419         SAVE_ARGUMENT_REGISTERS(0)          /* we save arg and temp registers in  */
420         SAVE_TEMPORARY_REGISTERS(ARG_CNT)   /* case this is a leaf method         */
421
422 #if SIZEOF_VOID_P == 8
423         aaddiu  sp,sp,-6*8                  /* allocate stack                     */
424         ast     xptr,0*8(sp)                /* save exception pointer             */
425         ast     pv,2*8(sp)                  /* save PV                            */
426         ast     ra,3*8(sp)                  /* save RA                            */
427         addu    t0,zero,1                   /* set maybe-leaf flag                */
428         ast     t0,4*8(sp)                  /* save maybe-leaf flag               */
429 #else
430         aaddiu  sp,sp,-(4*4+6*8)            /* allocate stack                     */
431         ast     xptr,4*4+0*8(sp)            /* save exception pointer             */
432         ast     xpc,4*4+1*8(sp)             /* save exception pc                  */
433         ast     pv,4*4+2*8(sp)              /* save data segment pointer          */
434         ast     ra,4*4+3*8(sp)              /* save return address                */
435         addu    t0,zero,1                   /* set maybe-leaf flag                */
436         ast     t0,4*4+4*8(sp)              /* save maybe-leaf flag               */
437 #endif
438
439         move    a0,xptr                     /* pass xptr                          */
440         move    a1,xpc                      /* pass xpc                           */
441         move    a2,pv                       /* pass PV                            */
442
443 #if SIZEOF_VOID_P == 8
444         aaddiu  a3,sp,(ARG_CNT+TMP_CNT+6)*8 /* pass Java SP                       */
445 #else
446         aaddiu  a3,sp,4*4+(ARG_CNT+TMP_CNT+6)*8 /* pass Java stack pointer        */
447 #endif
448
449 L_asm_handle_exception_continue:
450         jal     exceptions_handle_exception
451         
452         beqz    v0,L_asm_handle_exception_not_catched
453
454         move    xpc,v0                      /* move handlerpc into xpc            */
455
456 #if SIZEOF_VOID_P == 8
457         ald     xptr,0*8(sp)                /* restore exception pointer          */
458         ald     pv,2*8(sp)                  /* restore PV                         */
459         ald     ra,3*8(sp)                  /* restore RA                         */
460         ald     t0,4*8(sp)                  /* get maybe-leaf flag                */
461         aaddiu  sp,sp,6*8                   /* free stackframe                    */
462 #else
463         ald     xptr,4*4+0*8(sp)            /* restore exception pointer          */
464         ald     pv,4*4+2*8(sp)              /* restore data segment pointer       */
465         ald     ra,4*4+3*8(sp)              /* restore return address             */
466         ald     t0,4*4+4*8(sp)              /* get maybe-leaf flag                */
467         aaddiu  sp,sp,4*4+6*8               /* free stackframe                    */
468 #endif
469         
470         beqz    t0,L_asm_handle_exception_no_leaf
471
472         RESTORE_ARGUMENT_REGISTERS(0)       /* if this is a leaf method, we have  */
473         RESTORE_TEMPORARY_REGISTERS(ARG_CNT)/* to restore arg and temp registers  */
474         
475         aaddiu  sp,sp,(ARG_CNT+TMP_CNT)*8   /* remove maybe-leaf stackframe       */
476
477 L_asm_handle_exception_no_leaf:
478         jr      xpc                         /* jump to the handler                */
479
480 L_asm_handle_exception_not_catched:
481 #if SIZEOF_VOID_P == 8
482         ald     xptr,0*8(sp)                /* restore xptr                       */
483         ald     pv,2*8(sp)                  /* restore PV                         */
484         ald     ra,3*8(sp)                  /* restore RA                         */
485         ald     t0,4*8(sp)                  /* get maybe-leaf flag                */
486         aaddiu  sp,sp,6*8                   /* free stackframe                    */
487 #else
488         ald     xptr,4*4+0*8(sp)            /* restore xptr                       */
489         ald     pv,4*4+2*8(sp)              /* restore PV                         */
490         ald     ra,4*4+3*8(sp)              /* restore RA                         */
491         ald     t0,4*4+4*8(sp)              /* get maybe-leaf flag                */
492         aaddiu  sp,sp,4*4+6*8               /* free stackframe                    */
493 #endif
494         
495         beqz    t0,L_asm_handle_exception_no_leaf_stack
496
497         aaddiu  sp,sp,(ARG_CNT+TMP_CNT)*8   /* remove maybe-leaf stackframe       */
498         move    t0,zero                     /* clear the maybe-leaf flag          */
499
500 L_asm_handle_exception_no_leaf_stack:
501         lw      t1,FrameSize(pv)            /* get frame size                     */
502         aaddu   t1,sp,t1                    /* pointer to save area               */
503
504         lw      t2,IsLeaf(pv)               /* is leaf procedure                  */
505         bnez    t2,L_asm_handle_exception_no_ra_restore
506
507         ald     ra,-1*8(t1)                 /* restore ra                         */
508         aaddiu  t1,t1,-8                    /* t1--                               */
509
510 L_asm_handle_exception_no_ra_restore:
511         move    xpc,ra                      /* the new xpc is ra                  */
512         lw      t2,IntSave(pv)              /* t1 = saved int register count      */
513         ala     t3,ex_int2                  /* t3 = current pc                    */
514         sll     t2,t2,2                     /* t2 = register count * 4            */
515         asubu   t3,t3,t2                    /* t3 = IntSave - 4 * register count  */
516         jr      t3                          /* jump to save position              */
517
518         ald     s0,-8*8(t1)
519         ald     s1,-7*8(t1)
520         ald     s2,-6*8(t1)
521         ald     s3,-5*8(t1)
522         ald     s4,-4*8(t1)
523         ald     s5,-3*8(t1)
524         ald     s6,-2*8(t1)
525         ald     s7,-1*8(t1)
526
527 ex_int2:
528         sll     t2,t2,1               /* t2 = register count * 4 * 2              */
529         asubu   t1,t1,t2              /* t1 = t0 - 8 * register count             */
530
531         lw      t2,FltSave(pv)        /* t2 = saved flt register count            */
532         ala     t3,ex_flt2            /* t3 = current pc                          */
533         sll     t2,t2,2               /* t2 = register count * 4                  */
534         asubu   t3,t3,t2              /* t3 = ex_int_sav - 4 * register count     */
535         jr      t3                          /* jump to save position              */
536
537 #if SIZEOF_VOID_P == 8
538         ldc1    fs0,-4*8(t1)
539         ldc1    fs1,-3*8(t1)
540         ldc1    fs2,-2*8(t1)
541         ldc1    fs3,-1*8(t1)
542 #else /* SIZEOF_VOID_P == 8 */
543 # if !defined(ENABLE_SOFT_FLOAT)
544         ldc1    fs0,-4*8(t1)
545         ldc1    fs1,-3*8(t1)
546         ldc1    fs2,-2*8(t1)
547         ldc1    fs3,-1*8(t1)
548         ldc1    fs4,-1*8(t1)
549         ldc1    fs5,-1*8(t1)
550 # endif /* !defined(ENABLE_SOFT_FLOAT) */
551 #endif /* SIZEOF_VOID_P == 8 */
552
553 ex_flt2:
554         lw      t1,FrameSize(pv)            /* get frame size                     */
555         aaddu   sp,sp,t1                    /* unwind stack                       */
556         b       L_asm_handle_exception_stack_loop
557
558         .end    asm_handle_nat_exception
559
560
561 /* asm_abstractmethoderror *****************************************************
562
563    Creates and throws an AbstractMethodError.
564
565 *******************************************************************************/
566
567         .ent    asm_abstractmethoderror
568
569 asm_abstractmethoderror:
570         aaddiu  sp,sp,-2*8                  /* create stackframe                  */
571         ast     ra,0*8(sp)                  /* save return address                */
572         aaddiu  a0,sp,2*8                   /* pass java sp                       */
573         move    a1,ra                       /* pass exception address             */
574         jal     exceptions_asm_new_abstractmethoderror
575         ald     ra,0*8(sp)                  /* restore return address             */
576         aaddiu  sp,sp,2*8                   /* remove stackframe                  */
577
578         move    xptr,v0                     /* get exception pointer              */
579         aaddiu  xpc,ra,-4                   /* exception address is ra - 4        */
580         b       asm_handle_nat_exception
581
582         .end    asm_abstractmethoderror
583
584
585 #if defined(ENABLE_REPLACEMENT)
586                 
587 /* asm_replacement_out *********************************************************
588
589    This code is jumped to from the replacement-out stubs that are executed
590    when a thread reaches an activated replacement point.
591
592    The purpose of asm_replacement_out is to read out the parts of the
593    execution state that cannot be accessed from C code, store this state,
594    and then call the C function replace_me.
595
596    Stack layout:
597      16                 start of stack inside method to replace
598       0   rplpoint *    info on the replacement point that was reached
599
600    NOTE: itmp3 has been clobbered by the replacement-out stub!
601
602 *******************************************************************************/
603
604 /* some room to accomodate changes of the stack frame size during replacement */
605         /* XXX we should find a cleaner solution here */
606 #define REPLACEMENT_ROOM  512
607
608 #define REPLACEMENT_STACK_OFFSET ((sizeexecutionstate + REPLACEMENT_ROOM + 0xf) & ~0xf)
609
610         .ent asm_replacement_out
611
612 asm_replacement_out:
613     /* create stack frame */
614         aaddiu  sp,sp,-REPLACEMENT_STACK_OFFSET
615
616         /* save registers in execution state */
617         ast     $0 ,( 0*8+offes_intregs)(sp)
618         ast     $1 ,( 1*8+offes_intregs)(sp)
619         ast     $2 ,( 2*8+offes_intregs)(sp)
620         ast     $3 ,( 3*8+offes_intregs)(sp)
621         ast     $4 ,( 4*8+offes_intregs)(sp)
622         ast     $5 ,( 5*8+offes_intregs)(sp)
623         ast     $6 ,( 6*8+offes_intregs)(sp)
624         ast     $7 ,( 7*8+offes_intregs)(sp)
625         ast     $8 ,( 8*8+offes_intregs)(sp)
626         ast     $9 ,( 9*8+offes_intregs)(sp)
627         ast     $10,(10*8+offes_intregs)(sp)
628         ast     $11,(11*8+offes_intregs)(sp)
629         ast     $12,(12*8+offes_intregs)(sp)
630         ast     $13,(13*8+offes_intregs)(sp)
631         ast     $14,(14*8+offes_intregs)(sp)
632         ast     $15,(15*8+offes_intregs)(sp)
633         ast     $16,(16*8+offes_intregs)(sp)
634         ast     $17,(17*8+offes_intregs)(sp)
635         ast     $18,(18*8+offes_intregs)(sp)
636         ast     $19,(19*8+offes_intregs)(sp)
637         ast     $20,(20*8+offes_intregs)(sp)
638         ast     $21,(21*8+offes_intregs)(sp)
639         ast     $22,(22*8+offes_intregs)(sp)
640         ast     $23,(23*8+offes_intregs)(sp)
641         ast     $24,(24*8+offes_intregs)(sp)
642         ast     $25,(25*8+offes_intregs)(sp)
643         ast     $26,(26*8+offes_intregs)(sp)
644         ast     $27,(27*8+offes_intregs)(sp)
645         ast     $28,(28*8+offes_intregs)(sp)
646         ast     $29,(29*8+offes_intregs)(sp)
647         ast     $30,(30*8+offes_intregs)(sp)
648         ast     $31,(31*8+offes_intregs)(sp)
649
650 #if SIZEOF_VOID_P == 8
651
652         sdc1    $f0 ,( 0*8+offes_fltregs)(sp)
653         sdc1    $f1 ,( 1*8+offes_fltregs)(sp)
654         sdc1    $f2 ,( 2*8+offes_fltregs)(sp)
655         sdc1    $f3 ,( 3*8+offes_fltregs)(sp)
656         sdc1    $f4 ,( 4*8+offes_fltregs)(sp)
657         sdc1    $f5 ,( 5*8+offes_fltregs)(sp)
658         sdc1    $f6 ,( 6*8+offes_fltregs)(sp)
659         sdc1    $f7 ,( 7*8+offes_fltregs)(sp)
660         sdc1    $f8 ,( 8*8+offes_fltregs)(sp)
661         sdc1    $f9 ,( 9*8+offes_fltregs)(sp)
662         sdc1    $f10,(10*8+offes_fltregs)(sp)
663         sdc1    $f11,(11*8+offes_fltregs)(sp)
664         sdc1    $f12,(12*8+offes_fltregs)(sp)
665         sdc1    $f13,(13*8+offes_fltregs)(sp)
666         sdc1    $f14,(14*8+offes_fltregs)(sp)
667         sdc1    $f15,(15*8+offes_fltregs)(sp)
668         sdc1    $f16,(16*8+offes_fltregs)(sp)
669         sdc1    $f17,(17*8+offes_fltregs)(sp)
670         sdc1    $f18,(18*8+offes_fltregs)(sp)
671         sdc1    $f19,(19*8+offes_fltregs)(sp)
672         sdc1    $f20,(20*8+offes_fltregs)(sp)
673         sdc1    $f21,(21*8+offes_fltregs)(sp)
674         sdc1    $f22,(22*8+offes_fltregs)(sp)
675         sdc1    $f23,(23*8+offes_fltregs)(sp)
676         sdc1    $f24,(24*8+offes_fltregs)(sp)
677         sdc1    $f25,(25*8+offes_fltregs)(sp)
678         sdc1    $f26,(26*8+offes_fltregs)(sp)
679         sdc1    $f27,(27*8+offes_fltregs)(sp)
680         sdc1    $f28,(28*8+offes_fltregs)(sp)
681         sdc1    $f29,(29*8+offes_fltregs)(sp)
682         sdc1    $f30,(30*8+offes_fltregs)(sp)
683         sdc1    $f31,(31*8+offes_fltregs)(sp)
684
685 #else /* SIZEOF_VOID_P == 8 */
686
687         sdc1    $f0 ,( 0*8+offes_fltregs)(sp)
688         sdc1    $f2 ,( 2*8+offes_fltregs)(sp)
689         sdc1    $f4 ,( 4*8+offes_fltregs)(sp)
690         sdc1    $f6 ,( 6*8+offes_fltregs)(sp)
691         sdc1    $f8 ,( 8*8+offes_fltregs)(sp)
692         sdc1    $f10,(10*8+offes_fltregs)(sp)
693         sdc1    $f12,(12*8+offes_fltregs)(sp)
694         sdc1    $f14,(14*8+offes_fltregs)(sp)
695         sdc1    $f16,(16*8+offes_fltregs)(sp)
696         sdc1    $f18,(18*8+offes_fltregs)(sp)
697         sdc1    $f20,(20*8+offes_fltregs)(sp)
698         sdc1    $f22,(22*8+offes_fltregs)(sp)
699         sdc1    $f24,(24*8+offes_fltregs)(sp)
700         sdc1    $f26,(26*8+offes_fltregs)(sp)
701         sdc1    $f28,(28*8+offes_fltregs)(sp)
702         sdc1    $f30,(30*8+offes_fltregs)(sp)
703
704 #endif /* SIZEOF_VOID_P == 8 */
705         
706         /* calculate sp of method */
707         aaddiu  itmp1,sp,(REPLACEMENT_STACK_OFFSET + 2*8)
708         ast     itmp1,(offes_sp)(sp)
709
710         /* store pv */
711         ast     pv,(offes_pv)(sp)
712
713         /* call replace_me */
714         ald     a0,-(2*8)(itmp1)            /* arg0: rplpoint *                   */
715     move    a1,sp                       /* arg1: execution state              */
716     jal     replace_me                  /* call C function replace_me         */
717         jal     abort                       /* NEVER REACHED                      */
718
719         .end asm_replacement_out
720
721 /* asm_replacement_in **********************************************************
722
723    This code writes the given execution state and jumps to the replacement
724    code.
725
726    This function never returns!
727
728    NOTE: itmp3 is not restored!
729
730    C prototype:
731       void asm_replacement_in(executionstate *es);
732
733 *******************************************************************************/
734
735         .ent asm_replacement_in
736         
737 asm_replacement_in:
738         /* a0 == executionstate *es */
739
740         /* set new sp and pv */
741         ald     sp,(offes_sp)(a0)
742         ald     pv,(offes_pv)(a0)
743         
744         /* copy registers from execution state */
745         /* $0 is zero                     */
746         ald     $1 ,( 1*8+offes_intregs)(a0)
747         ald     $2 ,( 2*8+offes_intregs)(a0)
748         ald     $3 ,( 2*8+offes_intregs)(a0)
749         /* a0 is loaded below             */
750         ald     $5 ,( 5*8+offes_intregs)(a0)
751         ald     $6 ,( 6*8+offes_intregs)(a0)
752         ald     $7 ,( 7*8+offes_intregs)(a0)
753         ald     $8 ,( 8*8+offes_intregs)(a0)
754         ald     $9 ,( 9*8+offes_intregs)(a0)
755         ald     $10,(10*8+offes_intregs)(a0)
756         ald     $11,(11*8+offes_intregs)(a0)
757         ald     $12,(12*8+offes_intregs)(a0)
758         ald     $13,(13*8+offes_intregs)(a0)
759         ald     $14,(14*8+offes_intregs)(a0)
760         ald     $15,(15*8+offes_intregs)(a0)
761         ald     $16,(16*8+offes_intregs)(a0)
762         ald     $17,(17*8+offes_intregs)(a0)
763         ald     $18,(18*8+offes_intregs)(a0)
764         ald     $19,(19*8+offes_intregs)(a0)
765         ald     $20,(20*8+offes_intregs)(a0)
766         ald     $21,(21*8+offes_intregs)(a0)
767         ald     $22,(22*8+offes_intregs)(a0)
768         ald     $23,(23*8+offes_intregs)(a0)
769         ald     $24,(24*8+offes_intregs)(a0)
770         ald     $25,(25*8+offes_intregs)(a0)
771         ald     $26,(26*8+offes_intregs)(a0)
772         ald     $27,(27*8+offes_intregs)(a0)
773         ald     $28,(28*8+offes_intregs)(a0)
774         /* $29 is sp                      */
775         /* $30 is pv                      */
776         ald     $31,(31*8+offes_intregs)(a0)
777         
778 #if SIZEOF_VOID_P == 8
779
780         ldc1    $f0 ,( 0*8+offes_fltregs)(a0)
781         ldc1    $f1 ,( 1*8+offes_fltregs)(a0)
782         ldc1    $f2 ,( 2*8+offes_fltregs)(a0)
783         ldc1    $f3 ,( 3*8+offes_fltregs)(a0)
784         ldc1    $f4 ,( 4*8+offes_fltregs)(a0)
785         ldc1    $f5 ,( 5*8+offes_fltregs)(a0)
786         ldc1    $f6 ,( 6*8+offes_fltregs)(a0)
787         ldc1    $f7 ,( 7*8+offes_fltregs)(a0)
788         ldc1    $f8 ,( 8*8+offes_fltregs)(a0)
789         ldc1    $f9 ,( 9*8+offes_fltregs)(a0)
790         ldc1    $f10,(10*8+offes_fltregs)(a0)
791         ldc1    $f11,(11*8+offes_fltregs)(a0)
792         ldc1    $f12,(12*8+offes_fltregs)(a0)
793         ldc1    $f13,(13*8+offes_fltregs)(a0)
794         ldc1    $f14,(14*8+offes_fltregs)(a0)
795         ldc1    $f15,(15*8+offes_fltregs)(a0)
796         ldc1    $f16,(16*8+offes_fltregs)(a0)
797         ldc1    $f17,(17*8+offes_fltregs)(a0)
798         ldc1    $f18,(18*8+offes_fltregs)(a0)
799         ldc1    $f19,(19*8+offes_fltregs)(a0)
800         ldc1    $f20,(20*8+offes_fltregs)(a0)
801         ldc1    $f21,(21*8+offes_fltregs)(a0)
802         ldc1    $f22,(22*8+offes_fltregs)(a0)
803         ldc1    $f23,(23*8+offes_fltregs)(a0)
804         ldc1    $f24,(24*8+offes_fltregs)(a0)
805         ldc1    $f25,(25*8+offes_fltregs)(a0)
806         ldc1    $f26,(26*8+offes_fltregs)(a0)
807         ldc1    $f27,(27*8+offes_fltregs)(a0)
808         ldc1    $f28,(28*8+offes_fltregs)(a0)
809         ldc1    $f29,(29*8+offes_fltregs)(a0)
810         ldc1    $f30,(30*8+offes_fltregs)(a0)
811         ldc1    $f31,(31*8+offes_fltregs)(a0)
812
813 #else /* SIZEOF_VOID_P == 8 */
814
815         ldc1    $f0 ,( 0*8+offes_fltregs)(a0)
816         ldc1    $f2 ,( 2*8+offes_fltregs)(a0)
817         ldc1    $f4 ,( 4*8+offes_fltregs)(a0)
818         ldc1    $f6 ,( 6*8+offes_fltregs)(a0)
819         ldc1    $f8 ,( 8*8+offes_fltregs)(a0)
820         ldc1    $f10,(10*8+offes_fltregs)(a0)
821         ldc1    $f12,(12*8+offes_fltregs)(a0)
822         ldc1    $f14,(14*8+offes_fltregs)(a0)
823         ldc1    $f16,(16*8+offes_fltregs)(a0)
824         ldc1    $f18,(18*8+offes_fltregs)(a0)
825         ldc1    $f20,(20*8+offes_fltregs)(a0)
826         ldc1    $f22,(22*8+offes_fltregs)(a0)
827         ldc1    $f24,(24*8+offes_fltregs)(a0)
828         ldc1    $f26,(26*8+offes_fltregs)(a0)
829         ldc1    $f28,(28*8+offes_fltregs)(a0)
830         ldc1    $f30,(30*8+offes_fltregs)(a0)
831
832 #endif /* SIZEOF_VOID_P == 8 */
833
834         /* load new pc */
835
836         ald     itmp3,offes_pc(a0)
837
838         /* load a0 */
839         
840         ald     a0,(4*8+offes_intregs)(a0)
841
842         /* jump to new code */
843
844         jr      itmp3
845
846         .end asm_replacement_in
847
848 #endif /* defined(ENABLE_REPLACEMENT) */
849
850
851         .ent    compare_and_swap
852
853 compare_and_swap:
854 1:
855         all     v0,0(a0)
856         bne     v0,a1,2f
857         move    t0,a2
858         asc     t0,0(a0)
859         beqz    t0,1b
860 2:
861         sync
862         j       ra
863
864         .end    compare_and_swap
865
866
867 /* disable exec-stacks ********************************************************/
868
869 #if defined(__linux__) && defined(__ELF__)
870         .section .note.GNU-stack,"",%progbits
871 #endif
872
873
874 /*
875  * These are local overrides for various environment variables in Emacs.
876  * Please do not remove this and leave it at the end of the file, where
877  * Emacs will automagically detect them.
878  * ---------------------------------------------------------------------
879  * Local variables:
880  * mode: asm
881  * indent-tabs-mode: t
882  * c-basic-offset: 4
883  * tab-width: 4
884  * End:
885  * vim:noexpandtab:sw=4:ts=4:
886  */