* src/vm/jit/alpha/asmpart.S (asm_perform_threadswitch)
[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 4922 2006-05-15 14:39:05Z 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         .globl asm_handle_exception
62         .globl asm_handle_nat_exception
63
64         .globl asm_wrapper_patcher
65
66         .globl asm_replacement_out
67         .globl asm_replacement_in
68
69         .globl asm_getclassvalues_atomic
70         .globl asm_criticalsections
71
72         .globl compare_and_swap
73
74
75 /********************* function asm_calljavafunction ***************************
76 *                                                                              *
77 *   This function calls a Java-method (which possibly needs compilation)       *
78 *   with up to 4 address parameters.                                           *
79 *                                                                              *
80 *   This functions calls the JIT-compiler which eventually translates the      *
81 *   method into machine code.                                                  *
82 *                                                                              *
83 *   A possibly throwed exception will be returned to the caller as function    *
84 *   return value, so the java method cannot return a fucntion value (this      *
85 *   function usually calls 'main' and '<clinit>' which do not return a         *
86 *   function value).                                                           *
87 *                                                                              *
88 *   C-prototype:                                                               *
89 *    javaobject_header *asm_calljavafunction (methodinfo *m,                   *
90 *         void *arg1, void *arg2, void *arg3, void *arg4);                     *
91 *                                                                              *
92 *******************************************************************************/
93
94         .ent    asm_vm_call_method
95
96         .align  3
97
98         .dword  0                           /* catch type all                     */
99         .dword  0                           /* handler pc                         */
100         .dword  0                           /* end pc                             */
101         .dword  0                           /* start pc                           */
102         .word   1                           /* extable size                       */
103         .word   0                           /* 4-byte ALIGNMENT PADDING           */
104         .dword  0                           /* line number table start            */
105         .dword  0                           /* line number table size             */
106         .word   0                           /* 4-byte ALIGNMENT PADDING           */
107         .word   0                           /* fltsave                            */
108         .word   0                           /* intsave                            */
109         .word   0                           /* isleaf                             */
110         .word   0                           /* IsSync                             */
111         .word   0                           /* frame size                         */
112         .dword  0                           /* method pointer (pointer to name)   */
113
114 asm_vm_call_method:
115 asm_vm_call_method_int:
116 asm_vm_call_method_long:
117 asm_vm_call_method_float:
118 asm_vm_call_method_double:
119         .set    noreorder                 /* XXX we need to recompute pv          */
120
121         aaddiu  sp,sp,-12*8               /* allocate stack space (only 11 needed)*/
122         ast     ra,0(sp)                  /* save return address                  */
123
124         bal     L_asm_vm_call_method_compute_pv
125         ast     pv,1*8(sp)                /* procedure vector                     */
126 L_asm_vm_call_method_compute_pv:
127         aaddiu  pv,ra,-4*4
128         ast     s7,3*8(sp)
129
130         sdc1    fss0,5*8(sp)              /* save non JavaABI saved flt registers */
131         sdc1    fss1,6*8(sp)
132         sdc1    fss2,7*8(sp)
133         sdc1    fss3,8*8(sp)
134         sdc1    fss4,9*8(sp)
135         sdc1    fss5,10*8(sp)
136
137         ast     a0,4*8(sp)                /* save method pointer for compiler     */
138
139         move    t0,a2
140         move    s7,a1
141         blez    s7,calljava_argsloaded
142         nop
143
144         ald     a0,offvmargdata(t0)
145         ldc1    fa0,offvmargdata(t0)
146         daddi   s7,s7,-1
147         blez    s7,calljava_argsloaded
148         nop
149
150         ald     a1,offvmargdata+sizevmarg*1(t0)
151         ldc1    fa1,offvmargdata+sizevmarg*1(t0)
152         daddi   s7,s7,-1
153         blez    s7,calljava_argsloaded
154         nop
155
156         ald     a2,offvmargdata+sizevmarg*2(t0)
157         ldc1    fa2,offvmargdata+sizevmarg*2(t0)
158         daddi   s7,s7,-1
159         blez    s7,calljava_argsloaded
160         nop
161
162         ald     a3,offvmargdata+sizevmarg*3(t0)
163         ldc1    fa3,offvmargdata+sizevmarg*3(t0)
164         daddi   s7,s7,-1
165         blez    s7,calljava_argsloaded
166         nop
167
168         ald     a4,offvmargdata+sizevmarg*4(t0)
169         ldc1    fa4,offvmargdata+sizevmarg*4(t0)
170         daddi   s7,s7,-1
171         blez    s7,calljava_argsloaded
172         nop
173
174         ald     a5,offvmargdata+sizevmarg*5(t0)
175         ldc1    fa5,offvmargdata+sizevmarg*5(t0)
176         daddi   s7,s7,-1
177         blez    s7,calljava_argsloaded
178         nop
179
180         ald     a6,offvmargdata+sizevmarg*6(t0)
181         ldc1    fa6,offvmargdata+sizevmarg*6(t0)
182         daddi   s7,s7,-1
183         blez    s7,calljava_argsloaded
184         nop
185
186         ald     a7,offvmargdata+sizevmarg*7(t0)
187         ldc1    fa7,offvmargdata+sizevmarg*7(t0)
188         daddi   s7,s7,-1
189                 
190 calljava_argsloaded:
191         move    t8,sp                      /* save stack pointer                  */
192         blez    s7,calljava_nocopy
193         nop
194         subu    t1,zero,s7
195         sll     t2,t1,3
196         aaddu   sp,sp,t2
197         aaddu   t2,t2,t8
198
199 calljava_copyloop:
200     ald     t3,offvmargdata+sizevmarg*8(t0)
201         ast     t3,0(t2)
202         ala     t1,1(t1)
203         ala     t0,sizevmarg(t0)
204         ala     t2,8(t2)
205         bnez    t1,calljava_copyloop
206         nop
207
208 calljava_nocopy:
209         ald     itmp1,4*8(t8)             /* pass method pointer via itmp1        */
210
211         ala     mptr,asm_call_jit_compiler/* fake virtual function call (2 instr) */
212         ast     mptr,2*8(t8)              /* store function address               */
213         ala     mptr,1*8(t8)              /* set method pointer                   */
214
215         ald     pv,1*8(mptr)              /* method call as in Java               */
216         jalr    pv                        /* call JIT compiler                    */
217         nop
218 L_asm_vm_call_method_recompute_pv:
219 /*      aaddiu  pv,ra,(asm_vm_call_method - L_asm_vm_call_method_recompute_pv)*/
220         aaddiu  pv,ra,-76*4               /* recompute procedure vector           */
221
222         .set    reorder                   /* XXX we need to recompute pv          */
223
224 calljava_return2:
225         ald     ra,0(sp)                  /* restore return address               */
226         ald     pv,8(sp)                  /* restore procedure vector             */
227         ald     s7,3*8(sp)
228
229         ldc1    fss0,5*8(sp)              /* restore non JavaABI saved flt regs   */
230         ldc1    fss1,6*8(sp)
231         ldc1    fss2,7*8(sp)
232         ldc1    fss3,8*8(sp)
233         ldc1    fss4,9*8(sp)
234         ldc1    fss5,10*8(sp)
235
236         aaddiu  sp,sp,12*8                /* free stack space                     */
237         j       ra                        /* return                               */
238
239 asm_vm_call_method_exception_handler:
240         asll    s7,s7,3
241         aaddu   sp,s7,sp
242         move    a0,itmp1                  
243         jal     builtin_throw_exception
244         b       calljava_return2
245
246         .end    asm_vm_call_method
247
248
249 /****************** function asm_call_jit_compiler *****************************
250 *                                                                              *
251 *   invokes the compiler for untranslated JavaVM methods.                      *
252 *                                                                              *
253 *   Register REG_ITEMP1 contains a pointer to the method info structure        *
254 *   (prepared by createcompilerstub). Using the return address in R31 and the  *
255 *   offset in the LDA instruction or using the value in methodptr R25 the      *
256 *   patching address for storing the method address can be computed:           *
257 *                                                                              *
258 *   method address was either loaded using                                     *
259 *   M_ALD (REG_PV, REG_PV, a)        ; invokestatic/special    ($28)           *
260 *   M_JSR (REG_RA, REG_PV);                                                    *
261 *   M_NOP                                                                      *
262 *   M_LDA (REG_PV, REG_RA, val)                                                *
263 *   or                                                                         *
264 *   M_ALD (REG_PV, REG_METHODPTR, m) ; invokevirtual/interface ($25)           *
265 *   M_JSR (REG_RA, REG_PV);                                                    *
266 *   M_NOP                                                                      *
267 *   in the static case the method pointer can be computed using the            *
268 *   return address and the lda function following the jmp instruction          *
269 *                                                                              *
270 *******************************************************************************/
271
272
273         .ent    asm_call_jit_compiler
274
275 asm_call_jit_compiler:
276         aaddiu  sp,sp,-(ARG_CNT+2)*8  /* allocate stack space                     */
277
278         ast     ra,0*8(sp)            /* save return address                      */
279
280         SAVE_ARGUMENT_REGISTERS(1)
281
282         move    a0,itmp1              /* pass methodinfo pointer                  */
283         move    a1,mptr               /* pass method pointer                      */
284         aaddiu  a2,sp,(ARG_CNT+2)*8   /* pass java sp                             */
285         move    a3,ra
286         jal     jit_asm_compile       /* call jit compiler                        */
287         move    pv,v0
288
289         ald     ra,0*8(sp)            /* restore return address                   */
290
291         RESTORE_ARGUMENT_REGISTERS(1)
292
293         aaddiu  sp,sp,(ARG_CNT+2)*8   /* remove stack frame                       */
294
295         beqz    pv,L_asm_call_jit_compiler_exception
296
297         jr      pv                    /* and call method. The method returns      */
298                                       /* directly to the caller (ra).             */
299
300 L_asm_call_jit_compiler_exception:
301 #if defined(ENABLE_THREADS)
302         aaddiu  sp,sp,-2*8
303         ast     ra,0*8(sp)
304         jal     builtin_asm_get_exceptionptrptr
305         ald     ra,0*8(sp)
306         aaddiu  sp,sp,2*8
307 #else
308         la      v0,_exceptionptr
309 #endif
310         ald     xptr,0(v0)            /* get the exception pointer                */
311         ast     zero,0(v0)            /* clear the exception pointer              */
312
313         aaddiu  xpc,ra,-4             /* faulting address is return adress - 4    */
314         b       asm_handle_nat_exception
315
316         .end    asm_call_jit_compiler
317
318
319 /* asm_handle_exception ********************************************************
320
321    This function handles an exception. It does not use the usual calling
322    conventions. The exception pointer is passed in REG_ITMP1 and the
323    pc from the exception raising position is passed in REG_ITMP2. It searches
324    the local exception table for a handler. If no one is found, it unwinds
325    stacks and continues searching the callers.
326
327 *******************************************************************************/
328
329         .ent    asm_handle_nat_exception
330
331 asm_handle_nat_exception:
332 L_asm_handle_exception_stack_loop:
333         aaddiu  sp,sp,-6*8                  /* allocate stack                     */
334         ast     xptr,0*8(sp)                /* save exception pointer             */
335         ast     xpc,1*8(sp)                 /* save exception pc                  */
336         ast     ra,3*8(sp)                  /* save return address                */
337         ast     zero,4*8(sp)                /* save maybe-leaf flag (cleared)     */
338
339         move    a0,ra                       /* pass return address                */
340         jal     md_codegen_findmethod       /* get PV from RA                     */
341         ast     v0,2*8(sp)                  /* save data segment pointer          */
342
343         ald     a0,0*8(sp)                  /* pass exception pointer             */
344         ald     a1,1*8(sp)                  /* pass exception pc                  */
345         move    a2,v0                       /* pass data segment pointer          */
346         aaddiu  a3,sp,6*8                   /* pass Java stack pointer            */
347
348         b       L_asm_handle_exception_continue
349
350         .aent    asm_handle_exception
351
352 asm_handle_exception:
353         aaddiu  sp,sp,-(ARG_CNT+TMP_CNT)*8  /* create maybe-leaf stackframe       */
354
355         SAVE_ARGUMENT_REGISTERS(0)          /* we save arg and temp registers in  */
356         SAVE_TEMPORARY_REGISTERS(ARG_CNT)   /* case this is a leaf method         */
357
358         aaddiu  sp,sp,-6*8                  /* allocate stack                     */
359         ast     xptr,0*8(sp)                /* save exception pointer             */
360         ast     xpc,1*8(sp)                 /* save exception pc                  */
361         ast     pv,2*8(sp)                  /* save data segment pointer          */
362         ast     ra,3*8(sp)                  /* save return address                */
363         addu    t0,zero,1                   /* set maybe-leaf flag                */
364         ast     t0,4*8(sp)                  /* save maybe-leaf flag               */
365
366         move    a0,xptr                     /* pass exception pointer             */
367         move    a1,xpc                      /* pass exception pc                  */
368         move    a2,pv                       /* pass data segment pointer          */
369         aaddiu  a3,sp,(ARG_CNT+TMP_CNT+6)*8 /* pass Java stack pointer            */
370
371 L_asm_handle_exception_continue:
372         jal     exceptions_handle_exception
373         
374         beqz    v0,L_asm_handle_exception_not_catched
375
376         move    xpc,v0                      /* move handlerpc into xpc            */
377         ald     xptr,0*8(sp)                /* restore exception pointer          */
378         ald     pv,2*8(sp)                  /* restore data segment pointer       */
379         ald     ra,3*8(sp)                  /* restore return address             */
380         ald     t0,4*8(sp)                  /* get maybe-leaf flag                */
381         aaddiu  sp,sp,6*8                   /* free stackframe                    */
382         
383         beqz    t0,L_asm_handle_exception_no_leaf
384
385         RESTORE_ARGUMENT_REGISTERS(0)       /* if this is a leaf method, we have  */
386         RESTORE_TEMPORARY_REGISTERS(ARG_CNT)/* to restore arg and temp registers  */
387         
388         aaddiu  sp,sp,(ARG_CNT+TMP_CNT)*8   /* remove maybe-leaf stackframe       */
389
390 L_asm_handle_exception_no_leaf:
391         jr      xpc                         /* jump to the handler                */
392
393 L_asm_handle_exception_not_catched:
394         ald     xptr,0*8(sp)                /* restore exception pointer          */
395         ald     pv,2*8(sp)                  /* restore data segment pointer       */
396         ald     ra,3*8(sp)                  /* restore return address             */
397         ald     t0,4*8(sp)                  /* get maybe-leaf flag                */
398         aaddiu  sp,sp,6*8                   /* free stackframe                    */
399         
400         beqz    t0,L_asm_handle_exception_no_leaf_stack
401
402         aaddiu  sp,sp,(ARG_CNT+TMP_CNT)*8   /* remove maybe-leaf stackframe       */
403         move    t0,zero                     /* clear the maybe-leaf flag          */
404
405 L_asm_handle_exception_no_leaf_stack:
406         lw      t1,FrameSize(pv)            /* get frame size                     */
407         aaddu   t1,sp,t1                    /* pointer to save area               */
408
409         lw      t2,IsLeaf(pv)               /* is leaf procedure                  */
410         bnez    t2,L_asm_handle_exception_no_ra_restore
411
412         ald     ra,-1*8(t1)                 /* restore ra                         */
413         aaddiu  t1,t1,-8                    /* t1--                               */
414
415 L_asm_handle_exception_no_ra_restore:
416         move    xpc,ra                      /* the new xpc is ra                  */
417         lw      t2,IntSave(pv)              /* t1 = saved int register count      */
418         ala     t3,ex_int2                  /* t3 = current pc                    */
419         sll     t2,t2,2                     /* t2 = register count * 4            */
420         asubu   t3,t3,t2                    /* t3 = IntSave - 4 * register count  */
421         jr      t3                          /* jump to save position              */
422
423         ald     s0,-8*8(t1)
424         ald     s1,-7*8(t1)
425         ald     s2,-6*8(t1)
426         ald     s3,-5*8(t1)
427         ald     s4,-4*8(t1)
428         ald     s5,-3*8(t1)
429         ald     s6,-2*8(t1)
430         ald     s7,-1*8(t1)
431 ex_int2:
432         sll     t2,t2,1               /* t2 = register count * 4 * 2              */
433         asubu   t1,t1,t2              /* t1 = t0 - 8 * register count             */
434
435         lw      t2,FltSave(pv)        /* t2 = saved flt register count            */
436         ala     t3,ex_flt2            /* t3 = current pc                          */
437         sll     t2,t2,2               /* t2 = register count * 4                  */
438         asubu   t3,t3,t2              /* t3 = ex_int_sav - 4 * register count     */
439         jr      t3                          /* jump to save position              */
440
441         ldc1    fs0,-4*8(t1)
442         ldc1    fs1,-3*8(t1)
443         ldc1    fs2,-2*8(t1)
444         ldc1    fs3,-1*8(t1)
445
446 ex_flt2:
447         lw      t1,FrameSize(pv)            /* get frame size                     */
448         aaddu   sp,sp,t1                    /* unwind stack                       */
449         b       L_asm_handle_exception_stack_loop
450
451         .end    asm_handle_nat_exception
452
453
454 /* asm_wrapper_patcher *********************************************************
455
456    XXX
457
458    Stack layout:
459      40   return address into JIT code (patch position)
460      32   pointer to virtual java_objectheader
461      24   machine code (which is patched back later)
462      16   unresolved class/method/field reference
463       8   data segment displacement from load instructions
464       0   patcher function pointer to call
465
466 *******************************************************************************/
467                 
468     .ent    asm_wrapper_patcher
469
470 asm_wrapper_patcher:
471         aaddiu  sp,sp,-((2+16+22+4)*8+sizestackframeinfo) /* create stack frame   */
472
473         SAVE_RETURN_REGISTERS(0)      /* save 1 int/1 float return registers      */
474         SAVE_ARGUMENT_REGISTERS(2)    /* save 8 int/8 float argument registers    */
475         SAVE_TEMPORARY_REGISTERS(18)  /* save 5 int/16 float temporary registers  */
476
477         ast     itmp1,(2+16+22+0)*8(sp) /* save itmp1                             */
478         ast     itmp2,(2+16+22+1)*8(sp) /* save itmp2                             */
479         ast     ra,(2+16+22+2)*8(sp)  /* save method return address (for leafs)   */
480         ast     pv,(2+16+22+3)*8(sp)  /* save pv of calling java function         */
481
482         aaddiu  a0,sp,(2+16+22+4)*8   /* create stackframe info                   */
483         move    a1,pv                 /* pass java pv                             */
484         aaddiu  a2,sp,((6+2+16+22+4)*8+sizestackframeinfo) /* pass java sp        */
485         move    a3,ra                 /* this is correct for leafs                */
486         ald     a4,((5+2+16+22+4)*8+sizestackframeinfo)(sp) /* pass xpc           */
487         jal     stacktrace_create_extern_stackframeinfo
488
489         aaddiu  a0,sp,((0+2+16+22+4)*8+sizestackframeinfo) /* pass sp             */
490         ald     itmp3,((0+2+16+22+4)*8+sizestackframeinfo)(sp) /* get function    */
491         ald     itmp1,(2+16+22+3)*8(sp) /* save pv to the position of fp          */
492         ast     itmp1,((0+2+16+22+4)*8+sizestackframeinfo)(sp)
493         jalr    itmp3
494         ast     v0,((0+2+16+22+4)*8+sizestackframeinfo)(sp) /* save return value  */
495
496         aaddiu  a0,sp,(2+16+22+4)*8   /* remove stackframe info                   */
497         jal     stacktrace_remove_stackframeinfo
498
499         RESTORE_RETURN_REGISTERS(0)   /* restore 1 int/1 float return registers   */
500         RESTORE_ARGUMENT_REGISTERS(2) /* restore 8 int/8 float argument registers */
501         RESTORE_TEMPORARY_REGISTERS(18) /* restore 5 int/16 float temporary reg.  */
502
503         ald     itmp1,(2+16+22+0)*8(sp) /* restore itmp1                          */
504         ald     itmp2,(2+16+22+1)*8(sp) /* restore itmp2                          */
505         ald     ra,(2+16+22+2)*8(sp)  /* restore method return address (for leafs)*/
506         ald     pv,(2+16+22+3)*8(sp)  /* restore pv of calling java function      */
507
508         ald     itmp3,((0+2+16+22+4)*8+sizestackframeinfo)(sp) /* get return value*/
509         beqz    itmp3,L_asm_wrapper_patcher_exception
510
511         ald     itmp3,((5+2+16+22+4)*8+sizestackframeinfo)(sp) /* get RA to JIT   */
512         aaddiu  sp,sp,((6+2+16+22+4)*8+sizestackframeinfo) /* remove stack frame  */
513
514         jr      itmp3                 /* jump to new patched code                 */
515
516 L_asm_wrapper_patcher_exception:
517         ald     xpc,((5+2+16+22+4)*8+sizestackframeinfo)(sp) /* RA to JIT is xpc  */
518         aaddiu  sp,sp,((6+2+16+22+4)*8+sizestackframeinfo) /* remove stack frame  */
519
520 #if defined(ENABLE_THREADS)
521         daddiu  sp,sp,-4*8
522         sd      xpc,0*8(sp)
523         sd      ra,1*8(sp)
524         sd      pv,2*8(sp)
525         jal     builtin_asm_get_exceptionptrptr
526         ld      xpc,0*8(sp)
527         ld      ra,1*8(sp)
528         ld      pv,2*8(sp)
529         daddiu  sp,sp,4*8
530 #else
531         la      v0,_exceptionptr
532 #endif
533         ld      xptr,0(v0)            /* get the exception pointer                */
534         sd      zero,0(v0)            /* clear the exception pointer              */
535         b       asm_handle_exception
536
537         .end    asm_wrapper_patcher
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  */