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