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