3382ceade70a98ceb89d0cec768429eba998d02a
[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
31    $Id: asmpart.S 4640 2006-03-16 17:24:18Z twisti $
32
33 */
34
35
36 #include "config.h"
37
38 #include "vm/jit/mips/md-abi.h"
39 #include "vm/jit/mips/md-asm.h"
40 #include "vm/jit/mips/offsets.h"
41
42 #include "vm/jit/abi.h"
43 #include "vm/jit/methodheader.h"
44
45
46         .text
47         .set    noat
48
49
50 /* export functions ***********************************************************/
51
52         .globl asm_vm_call_method
53         .globl asm_vm_call_method_int
54         .globl asm_vm_call_method_long
55         .globl asm_vm_call_method_float
56         .globl asm_vm_call_method_double
57
58         .globl asm_call_jit_compiler
59         .globl asm_handle_exception
60         .globl asm_handle_nat_exception
61
62         .globl asm_wrapper_patcher
63
64         .globl asm_perform_threadswitch
65         .globl asm_initialize_thread_stack
66         .globl asm_switchstackandcall
67         .globl asm_getclassvalues_atomic
68         .globl asm_criticalsections
69
70         .globl compare_and_swap
71
72
73 /********************* function asm_calljavafunction ***************************
74 *                                                                              *
75 *   This function calls a Java-method (which possibly needs compilation)       *
76 *   with up to 4 address parameters.                                           *
77 *                                                                              *
78 *   This functions calls the JIT-compiler which eventually translates the      *
79 *   method into machine code.                                                  *
80 *                                                                              *
81 *   A possibly throwed exception will be returned to the caller as function    *
82 *   return value, so the java method cannot return a fucntion value (this      *
83 *   function usually calls 'main' and '<clinit>' which do not return a         *
84 *   function value).                                                           *
85 *                                                                              *
86 *   C-prototype:                                                               *
87 *    javaobject_header *asm_calljavafunction (methodinfo *m,                   *
88 *         void *arg1, void *arg2, void *arg3, void *arg4);                     *
89 *                                                                              *
90 *******************************************************************************/
91
92         .ent    asm_vm_call_method
93
94         .align  3
95
96         .dword  0                           /* catch type all                     */
97         .dword  calljava_xhandler2          /* handler pc                         */
98         .dword  calljava_xhandler2          /* end pc                             */
99         .dword  asm_vm_call_method          /* start pc                           */
100         .word   1                           /* extable size                       */
101         .word   0                           /* 4-byte ALIGNMENT PADDING           */
102         .dword  0                           /* line number table start            */
103         .dword  0                           /* line number table size             */
104         .word   0                           /* 4-byte ALIGNMENT PADDING           */
105         .word   0                           /* fltsave                            */
106         .word   0                           /* intsave                            */
107         .word   0                           /* isleaf                             */
108         .word   0                           /* IsSync                             */
109         .word   0                           /* frame size                         */
110         .dword  0                           /* method pointer (pointer to name)   */
111
112 asm_vm_call_method:
113 asm_vm_call_method_int:
114 asm_vm_call_method_long:
115 asm_vm_call_method_float:
116 asm_vm_call_method_double:
117         .set    noreorder                 /* XXX we need to recompute pv          */
118
119         aaddiu  sp,sp,-12*8               /* allocate stack space (only 11 needed)*/
120         ast     ra,0(sp)                  /* save return address                  */
121
122         bal     L_asm_vm_call_method_compute_pv
123         ast     pv,1*8(sp)                /* procedure vector                     */
124 L_asm_vm_call_method_compute_pv:
125         aaddiu  pv,ra,-4*4
126         ast     s7,3*8(sp)
127
128         sdc1    fss0,5*8(sp)              /* save non JavaABI saved flt registers */
129         sdc1    fss1,6*8(sp)
130         sdc1    fss2,7*8(sp)
131         sdc1    fss3,8*8(sp)
132         sdc1    fss4,9*8(sp)
133         sdc1    fss5,10*8(sp)
134
135         ast     a0,4*8(sp)                /* save method pointer for compiler     */
136
137         move    t0,a2
138         move    s7,a1
139         blez    s7,calljava_argsloaded
140         nop
141
142         ald     a0,offvmargdata(t0)
143         ldc1    fa0,offvmargdata(t0)
144         daddi   s7,s7,-1
145         blez    s7,calljava_argsloaded
146         nop
147
148         ald     a1,offvmargdata+sizevmarg*1(t0)
149         ldc1    fa1,offvmargdata+sizevmarg*1(t0)
150         daddi   s7,s7,-1
151         blez    s7,calljava_argsloaded
152         nop
153
154         ald     a2,offvmargdata+sizevmarg*2(t0)
155         ldc1    fa2,offvmargdata+sizevmarg*2(t0)
156         daddi   s7,s7,-1
157         blez    s7,calljava_argsloaded
158         nop
159
160         ald     a3,offvmargdata+sizevmarg*3(t0)
161         ldc1    fa3,offvmargdata+sizevmarg*3(t0)
162         daddi   s7,s7,-1
163         blez    s7,calljava_argsloaded
164         nop
165
166         ald     a4,offvmargdata+sizevmarg*4(t0)
167         ldc1    fa4,offvmargdata+sizevmarg*4(t0)
168         daddi   s7,s7,-1
169         blez    s7,calljava_argsloaded
170         nop
171
172         ald     a5,offvmargdata+sizevmarg*5(t0)
173         ldc1    fa5,offvmargdata+sizevmarg*5(t0)
174         daddi   s7,s7,-1
175         blez    s7,calljava_argsloaded
176         nop
177
178         ald     a6,offvmargdata+sizevmarg*6(t0)
179         ldc1    fa6,offvmargdata+sizevmarg*6(t0)
180         daddi   s7,s7,-1
181         blez    s7,calljava_argsloaded
182         nop
183
184         ald     a7,offvmargdata+sizevmarg*7(t0)
185         ldc1    fa7,offvmargdata+sizevmarg*7(t0)
186         daddi   s7,s7,-1
187                 
188 calljava_argsloaded:
189         move    t8,sp                      /* save stack pointer                  */
190         blez    s7,calljava_nocopy
191         nop
192         subu    t1,zero,s7
193         sll     t2,t1,3
194         aaddu   sp,sp,t2
195         aaddu   t2,t2,t8
196
197 calljava_copyloop:
198     ald     t3,offvmargdata+sizevmarg*8(t0)
199         ast     t3,0(t2)
200         ala     t1,1(t1)
201         ala     t0,sizevmarg(t0)
202         ala     t2,8(t2)
203         bnez    t1,calljava_copyloop
204         nop
205
206 calljava_nocopy:
207         ald     itmp1,4*8(t8)             /* pass method pointer via itmp1        */
208
209         ala     mptr,asm_call_jit_compiler/* fake virtual function call (2 instr) */
210         ast     mptr,2*8(t8)              /* store function address               */
211         ala     mptr,1*8(t8)              /* set method pointer                   */
212
213         ald     pv,1*8(mptr)              /* method call as in Java               */
214         jalr    pv                        /* call JIT compiler                    */
215         nop
216 L_asm_vm_call_method_recompute_pv:
217 /*      aaddiu  pv,ra,(asm_vm_call_method - L_asm_vm_call_method_recompute_pv)*/
218         aaddiu  pv,ra,-76*4               /* recompute procedure vector           */
219
220         .set    reorder                   /* XXX we need to recompute pv          */
221
222 calljava_return2:
223         ald     ra,0(sp)                  /* restore return address               */
224         ald     pv,8(sp)                  /* restore procedure vector             */
225         ald     s7,3*8(sp)
226
227         ldc1    fss0,5*8(sp)              /* restore non JavaABI saved flt regs   */
228         ldc1    fss1,6*8(sp)
229         ldc1    fss2,7*8(sp)
230         ldc1    fss3,8*8(sp)
231         ldc1    fss4,9*8(sp)
232         ldc1    fss5,10*8(sp)
233
234         aaddiu  sp,sp,12*8                /* free stack space                     */
235         j       ra                        /* return                               */
236
237 calljava_xhandler2:
238         asll    s7,s7,3
239         aaddu   sp,s7,sp
240         move    a0,itmp1                  
241         jal     builtin_throw_exception
242         b       calljava_return2
243
244         .end    asm_vm_call_method
245
246
247 /****************** function asm_call_jit_compiler *****************************
248 *                                                                              *
249 *   invokes the compiler for untranslated JavaVM methods.                      *
250 *                                                                              *
251 *   Register REG_ITEMP1 contains a pointer to the method info structure        *
252 *   (prepared by createcompilerstub). Using the return address in R31 and the  *
253 *   offset in the LDA instruction or using the value in methodptr R25 the      *
254 *   patching address for storing the method address can be computed:           *
255 *                                                                              *
256 *   method address was either loaded using                                     *
257 *   M_ALD (REG_PV, REG_PV, a)        ; invokestatic/special    ($28)           *
258 *   M_JSR (REG_RA, REG_PV);                                                    *
259 *   M_NOP                                                                      *
260 *   M_LDA (REG_PV, REG_RA, val)                                                *
261 *   or                                                                         *
262 *   M_ALD (REG_PV, REG_METHODPTR, m) ; invokevirtual/interface ($25)           *
263 *   M_JSR (REG_RA, REG_PV);                                                    *
264 *   M_NOP                                                                      *
265 *   in the static case the method pointer can be computed using the            *
266 *   return address and the lda function following the jmp instruction          *
267 *                                                                              *
268 *******************************************************************************/
269
270
271         .ent    asm_call_jit_compiler
272
273 asm_call_jit_compiler:
274         aaddiu  sp,sp,-(20*8+sizestackframeinfo) /* allocate stack space          */
275
276         SAVE_ARGUMENT_REGISTERS(0)
277
278         ast     mptr,16*8(sp)         /* save method pointer                      */
279         ast     ra,17*8(sp)           /* save return address                      */
280         ast     itmp1,18*8(sp)        /* save methodinfo pointer                  */
281
282         aaddiu  a0,sp,20*8            /* create stackframe info                   */
283         move    a1,zero               /* we don't have pv handy                   */
284         aaddiu  a2,sp,(20*8+sizestackframeinfo) /* pass java sp                   */
285         ald     a3,17*8(sp)           /* pass java ra                             */
286         move    a4,a3                 /* xpc is equal to ra                       */
287         jal     stacktrace_create_extern_stackframeinfo
288
289         ald     a0,18*8(sp)           /* pass methodinfo pointer                  */
290         jal     jit_compile           /* jit compiler                             */
291         ast     v0,18*8(sp)           /* save return value                        */
292
293         aaddiu  a0,sp,20*8            /* remove stackframe info                   */
294         jal     stacktrace_remove_stackframeinfo
295
296         ald     a0,17*8(sp)           /* pass return address                      */
297         aaddiu  a1,sp,20*8            /* pass stackframeinfo (for PV)             */
298         ald     a2,16*8(sp)           /* pass method pointer                      */
299         jal     md_assembler_get_patch_address /* get address of patch position   */
300         move    t0,v0                 /* move offset to t0 for later use          */
301
302         RESTORE_ARGUMENT_REGISTERS(0)
303
304         ald     ra,17*8(sp)           /* restore return address                   */
305         ald     v0,18*8(sp)           /* restore return value                     */
306         aaddiu  sp,sp,20*8+sizestackframeinfo /* deallocate stack area            */
307
308         beqz    v0,L_asm_call_jit_compiler_exception
309
310         ast     v0,0(t0)              /* store new method address                 */
311         move    pv,v0                 /* move method address into pv              */
312         jr      pv                    /* and call method. The method returns      */
313                                       /* directly to the caller (ra).             */
314
315 L_asm_call_jit_compiler_exception:
316 #if defined(USE_THREADS) && defined(NATIVE_THREADS)
317         aaddiu  sp,sp,-2*8
318         ast     ra,0*8(sp)
319         jal     builtin_asm_get_exceptionptrptr
320         ald     ra,0*8(sp)
321         aaddiu  sp,sp,2*8
322 #else
323         la      v0,_exceptionptr
324 #endif
325         ald     xptr,0(v0)            /* get the exception pointer                */
326         ast     zero,0(v0)            /* clear the exception pointer              */
327
328         aaddiu  xpc,ra,-4             /* faulting address is return adress - 4    */
329         b       asm_handle_nat_exception
330
331         .end    asm_call_jit_compiler
332
333
334 /* asm_handle_exception ********************************************************
335
336    This function handles an exception. It does not use the usual calling
337    conventions. The exception pointer is passed in REG_ITMP1 and the
338    pc from the exception raising position is passed in REG_ITMP2. It searches
339    the local exception table for a handler. If no one is found, it unwinds
340    stacks and continues searching the callers.
341
342 *******************************************************************************/
343
344         .ent    asm_handle_nat_exception
345
346 asm_handle_nat_exception:
347 L_asm_handle_exception_stack_loop:
348         aaddiu  sp,sp,-6*8                  /* allocate stack                     */
349         ast     xptr,0*8(sp)                /* save exception pointer             */
350         ast     xpc,1*8(sp)                 /* save exception pc                  */
351         ast     ra,3*8(sp)                  /* save return address                */
352         ast     zero,4*8(sp)                /* save maybe-leaf flag (cleared)     */
353
354         move    a0,ra                       /* pass return address                */
355         jal     md_codegen_findmethod       /* get PV from RA                     */
356         ast     v0,2*8(sp)                  /* save data segment pointer          */
357
358         ald     a0,0*8(sp)                  /* pass exception pointer             */
359         ald     a1,1*8(sp)                  /* pass exception pc                  */
360         move    a2,v0                       /* pass data segment pointer          */
361         aaddiu  a3,sp,6*8                   /* pass Java stack pointer            */
362
363         b       L_asm_handle_exception_continue
364
365         .aent    asm_handle_exception
366
367 asm_handle_exception:
368         aaddiu  sp,sp,-(ARG_CNT+TMP_CNT)*8  /* create maybe-leaf stackframe       */
369
370         SAVE_ARGUMENT_REGISTERS(0)          /* we save arg and temp registers in  */
371         SAVE_TEMPORARY_REGISTERS(ARG_CNT)   /* case this is a leaf method         */
372
373         aaddiu  sp,sp,-6*8                  /* allocate stack                     */
374         ast     xptr,0*8(sp)                /* save exception pointer             */
375         ast     xpc,1*8(sp)                 /* save exception pc                  */
376         ast     pv,2*8(sp)                  /* save data segment pointer          */
377         ast     ra,3*8(sp)                  /* save return address                */
378         addu    t0,zero,1                   /* set maybe-leaf flag                */
379         ast     t0,4*8(sp)                  /* save maybe-leaf flag               */
380
381         move    a0,xptr                     /* pass exception pointer             */
382         move    a1,xpc                      /* pass exception pc                  */
383         move    a2,pv                       /* pass data segment pointer          */
384         aaddiu  a3,sp,(ARG_CNT+TMP_CNT+6)*8 /* pass Java stack pointer            */
385
386 L_asm_handle_exception_continue:
387         jal     exceptions_handle_exception
388         
389         beqz    v0,L_asm_handle_exception_not_catched
390
391         move    xpc,v0                      /* move handlerpc into xpc            */
392         ald     xptr,0*8(sp)                /* restore exception pointer          */
393         ald     pv,2*8(sp)                  /* restore data segment pointer       */
394         ald     ra,3*8(sp)                  /* restore return address             */
395         ald     t0,4*8(sp)                  /* get maybe-leaf flag                */
396         aaddiu  sp,sp,6*8                   /* free stackframe                    */
397         
398         beqz    t0,L_asm_handle_exception_no_leaf
399
400         RESTORE_ARGUMENT_REGISTERS(0)       /* if this is a leaf method, we have  */
401         RESTORE_TEMPORARY_REGISTERS(ARG_CNT)/* to restore arg and temp registers  */
402         
403         aaddiu  sp,sp,(ARG_CNT+TMP_CNT)*8   /* remove maybe-leaf stackframe       */
404
405 L_asm_handle_exception_no_leaf:
406         jr      xpc                         /* jump to the handler                */
407
408 L_asm_handle_exception_not_catched:
409         ald     xptr,0*8(sp)                /* restore exception pointer          */
410         ald     pv,2*8(sp)                  /* restore data segment pointer       */
411         ald     ra,3*8(sp)                  /* restore return address             */
412         ald     t0,4*8(sp)                  /* get maybe-leaf flag                */
413         aaddiu  sp,sp,6*8                   /* free stackframe                    */
414         
415         beqz    t0,L_asm_handle_exception_no_leaf_stack
416
417         aaddiu  sp,sp,(ARG_CNT+TMP_CNT)*8   /* remove maybe-leaf stackframe       */
418         move    t0,zero                     /* clear the maybe-leaf flag          */
419
420 L_asm_handle_exception_no_leaf_stack:
421         lw      t1,FrameSize(pv)            /* get frame size                     */
422         aaddu   t1,sp,t1                    /* pointer to save area               */
423
424         lw      t2,IsLeaf(pv)               /* is leaf procedure                  */
425         bnez    t2,L_asm_handle_exception_no_ra_restore
426
427         ald     ra,-1*8(t1)                 /* restore ra                         */
428         aaddiu  t1,t1,-8                    /* t1--                               */
429
430 L_asm_handle_exception_no_ra_restore:
431         move    xpc,ra                      /* the new xpc is ra                  */
432         lw      t2,IntSave(pv)              /* t1 = saved int register count      */
433         ala     t3,ex_int2                  /* t3 = current pc                    */
434         sll     t2,t2,2                     /* t2 = register count * 4            */
435         asubu   t3,t3,t2                    /* t3 = IntSave - 4 * register count  */
436         jr      t3                          /* jump to save position              */
437
438         ald     s0,-8*8(t1)
439         ald     s1,-7*8(t1)
440         ald     s2,-6*8(t1)
441         ald     s3,-5*8(t1)
442         ald     s4,-4*8(t1)
443         ald     s5,-3*8(t1)
444         ald     s6,-2*8(t1)
445         ald     s7,-1*8(t1)
446 ex_int2:
447         sll     t2,t2,1               /* t2 = register count * 4 * 2              */
448         asubu   t1,t1,t2              /* t1 = t0 - 8 * register count             */
449
450         lw      t2,FltSave(pv)        /* t2 = saved flt register count            */
451         ala     t3,ex_flt2            /* t3 = current pc                          */
452         sll     t2,t2,2               /* t2 = register count * 4                  */
453         asubu   t3,t3,t2              /* t3 = ex_int_sav - 4 * register count     */
454         jr      t3                          /* jump to save position              */
455
456         ldc1    fs0,-4*8(t1)
457         ldc1    fs1,-3*8(t1)
458         ldc1    fs2,-2*8(t1)
459         ldc1    fs3,-1*8(t1)
460
461 ex_flt2:
462         lw      t1,FrameSize(pv)            /* get frame size                     */
463         aaddu   sp,sp,t1                    /* unwind stack                       */
464         b       L_asm_handle_exception_stack_loop
465
466         .end    asm_handle_nat_exception
467
468
469 /* asm_wrapper_patcher *********************************************************
470
471    XXX
472
473    Stack layout:
474      40   return address into JIT code (patch position)
475      32   pointer to virtual java_objectheader
476      24   machine code (which is patched back later)
477      16   unresolved class/method/field reference
478       8   data segment displacement from load instructions
479       0   patcher function pointer to call
480
481 *******************************************************************************/
482                 
483     .ent    asm_wrapper_patcher
484
485 asm_wrapper_patcher:
486         aaddiu  sp,sp,-((2+16+22+4)*8+sizestackframeinfo) /* create stack frame   */
487
488         SAVE_RETURN_REGISTERS(0)      /* save 1 int/1 float return registers      */
489         SAVE_ARGUMENT_REGISTERS(2)    /* save 8 int/8 float argument registers    */
490         SAVE_TEMPORARY_REGISTERS(18)  /* save 5 int/16 float temporary registers  */
491
492         ast     itmp1,(2+16+22+0)*8(sp) /* save itmp1                             */
493         ast     itmp2,(2+16+22+1)*8(sp) /* save itmp2                             */
494         ast     ra,(2+16+22+2)*8(sp)  /* save method return address (for leafs)   */
495         ast     pv,(2+16+22+3)*8(sp)  /* save pv of calling java function         */
496
497         aaddiu  a0,sp,(2+16+22+4)*8   /* create stackframe info                   */
498         move    a1,pv                 /* pass java pv                             */
499         aaddiu  a2,sp,((6+2+16+22+4)*8+sizestackframeinfo) /* pass java sp        */
500         move    a3,ra                 /* this is correct for leafs                */
501         ald     a4,((5+2+16+22+4)*8+sizestackframeinfo)(sp) /* pass xpc           */
502         jal     stacktrace_create_extern_stackframeinfo
503
504         aaddiu  a0,sp,((0+2+16+22+4)*8+sizestackframeinfo) /* pass sp             */
505         ald     itmp3,((0+2+16+22+4)*8+sizestackframeinfo)(sp) /* get function    */
506         ald     itmp1,(2+16+22+3)*8(sp) /* save pv to the position of fp          */
507         ast     itmp1,((0+2+16+22+4)*8+sizestackframeinfo)(sp)
508         jalr    itmp3
509         ast     v0,((0+2+16+22+4)*8+sizestackframeinfo)(sp) /* save return value  */
510
511         aaddiu  a0,sp,(2+16+22+4)*8   /* remove stackframe info                   */
512         jal     stacktrace_remove_stackframeinfo
513
514         RESTORE_RETURN_REGISTERS(0)   /* restore 1 int/1 float return registers   */
515         RESTORE_ARGUMENT_REGISTERS(2) /* restore 8 int/8 float argument registers */
516         RESTORE_TEMPORARY_REGISTERS(18) /* restore 5 int/16 float temporary reg.  */
517
518         ald     itmp1,(2+16+22+0)*8(sp) /* restore itmp1                          */
519         ald     itmp2,(2+16+22+1)*8(sp) /* restore itmp2                          */
520         ald     ra,(2+16+22+2)*8(sp)  /* restore method return address (for leafs)*/
521         ald     pv,(2+16+22+3)*8(sp)  /* restore pv of calling java function      */
522
523         ald     itmp3,((0+2+16+22+4)*8+sizestackframeinfo)(sp) /* get return value*/
524         beqz    itmp3,L_asm_wrapper_patcher_exception
525
526         ald     itmp3,((5+2+16+22+4)*8+sizestackframeinfo)(sp) /* get RA to JIT   */
527         aaddiu  sp,sp,((6+2+16+22+4)*8+sizestackframeinfo) /* remove stack frame  */
528
529         jr      itmp3                 /* jump to new patched code                 */
530
531 L_asm_wrapper_patcher_exception:
532         ald     xpc,((5+2+16+22+4)*8+sizestackframeinfo)(sp) /* RA to JIT is xpc  */
533         aaddiu  sp,sp,((6+2+16+22+4)*8+sizestackframeinfo) /* remove stack frame  */
534
535 #if defined(USE_THREADS) && defined(NATIVE_THREADS)
536         daddiu  sp,sp,-4*8
537         sd      xpc,0*8(sp)
538         sd      ra,1*8(sp)
539         sd      pv,2*8(sp)
540         jal     builtin_asm_get_exceptionptrptr
541         ld      xpc,0*8(sp)
542         ld      ra,1*8(sp)
543         ld      pv,2*8(sp)
544         daddiu  sp,sp,4*8
545 #else
546         la      v0,_exceptionptr
547 #endif
548         ld      xptr,0(v0)            /* get the exception pointer                */
549         sd      zero,0(v0)            /* clear the exception pointer              */
550         b       asm_handle_exception
551
552         .end    asm_wrapper_patcher
553
554                 
555 /******************* function asm_initialize_thread_stack **********************
556 *                                                                              *
557 *   u1* asm_initialize_thread_stack (void *func, u1 *stack);                   *
558 *                                                                              *
559 *   initialize a thread stack                                                  *
560 *                                                                              *
561 *******************************************************************************/
562
563         .ent    asm_initialize_thread_stack
564
565 asm_initialize_thread_stack:
566         aaddiu  a1,a1,-14*8     /* allocate save area                             */
567         sd      zero, 0*8(a1)   /* s0 initalize thread area                       */
568         sd      zero, 1*8(a1)   /* s1                                             */
569         sd      zero, 2*8(a1)   /* s2                                             */
570         sd      zero, 3*8(a1)   /* s3                                             */
571         sd      zero, 4*8(a1)   /* s4                                             */
572         sd      zero, 5*8(a1)   /* s5                                             */
573         sd      zero, 6*8(a1)   /* s6                                             */
574         sd      zero, 7*8(a1)   /* s7                                             */
575         sd      zero, 8*8(a1)   /* s8                                             */
576         sd      zero, 9*8(a1)   /* fs0                                            */
577         sd      zero,10*8(a1)   /* fs1                                            */
578         sd      zero,11*8(a1)   /* fs2                                            */
579         sd      zero,12*8(a1)   /* fs3                                            */
580         sd      a0, 13*8(a1)
581         move    v0,a1
582         j       ra              /* return                                         */
583
584         .end    asm_initialize_thread_stack
585
586
587 /******************* function asm_perform_threadswitch *************************
588 *                                                                              *
589 *   void asm_perform_threadswitch (u1 **from, u1 **to, u1 **stackTop);         *
590 *                                                                              *
591 *   performs a threadswitch                                                    *
592 *                                                                              *
593 *******************************************************************************/
594
595         .ent    asm_perform_threadswitch
596
597 asm_perform_threadswitch:
598         aaddiu  sp,sp,-14*8     /* allocate new stack                             */
599         sd      s0,  0*8(sp)    /* save saved registers of old thread             */
600         sd      s1,  1*8(sp)
601         sd      s2,  2*8(sp)
602         sd      s3,  3*8(sp)
603         sd      s4,  4*8(sp)
604         sd      s5,  5*8(sp)
605         sd      s6,  6*8(sp)
606         sd      s7,  7*8(sp)
607         sd      s8,  8*8(sp)
608         sdc1    fs0, 9*8(sp)
609         sdc1    fs1,10*8(sp)
610         sdc1    fs2,11*8(sp)
611         sdc1    fs3,12*8(sp)
612         sd      ra, 13*8(sp)
613         ast     sp,0(a0)        /* save old stack pointer                         */
614         ast     sp,0(a2)        /* stackTop = old stack pointer                   */
615         ald     sp,0(a1)        /* load new stack pointer                         */
616         ld      s0,  0*8(sp)    /* load saved registers of new thread             */
617         ld      s1,  1*8(sp)
618         ld      s2,  2*8(sp)
619         ld      s3,  3*8(sp)
620         ld      s4,  4*8(sp)
621         ld      s5,  5*8(sp)
622         ld      s6,  6*8(sp)
623         ld      s7,  7*8(sp)
624         ld      s8,  8*8(sp)
625         ldc1    fs0, 9*8(sp)
626         ldc1    fs1,10*8(sp)
627         ldc1    fs2,11*8(sp)
628         ldc1    fs3,12*8(sp)
629         ld      ra, 13*8(sp)
630         aaddiu  sp,sp,14*8      /* deallocate new stack                           */
631         move    itmp3, ra
632         j       ra              /* return                                         */
633
634         .end    asm_perform_threadswitch
635
636
637 /********************* function asm_switchstackandcall *************************
638 *                                                                              *
639 *  void asm_switchstackandcall (void *stack, void *func, void **stacktopsave); *
640 *                                                                              *
641 *   Switches to a new stack, calls a function and switches back.               *
642 *       a0      new stack pointer                                              *
643 *       a1      function pointer                                               *
644 *               a2              pointer to variable where stack top should be stored           *
645 *                                                                              *
646 *******************************************************************************/
647
648         .ent    asm_switchstackandcall
649
650 asm_switchstackandcall:
651         aaddiu  a0,a0,-16       /* allocate new stack                             */
652         sd      ra,0(a0)        /* save return address on new stack               */
653         sd      sp,8(a0)        /* save old stack pointer on new stack            */
654         sd      sp,0(a2)        /* save old stack pointer to variable             */
655         move    sp,a0           /* switch to new stack                            */
656         
657         move    itmp3,a1
658         move    a0,a3
659         jalr    itmp3           /* and call function                              */
660
661         ld      ra,0(sp)        /* load return address                            */
662         ld      sp,8(sp)        /* switch to old stack                            */
663
664         j       ra              /* return                                         */
665
666         .end    asm_switchstackandcall
667
668
669         .ent    asm_getclassvalues_atomic
670
671 asm_getclassvalues_atomic:
672 _crit_restart:
673 _crit_begin:
674         lw      t0,offbaseval(a0)
675         lw      t1,offdiffval(a0)
676         lw      t2,offbaseval(a1)
677 _crit_end:
678         sw      t0,offcast_super_baseval(a2)
679         sw      t1,offcast_super_diffval(a2)
680         sw      t2,offcast_sub_baseval(a2)
681         j       ra
682
683         .end    asm_getclassvalues_atomic
684
685     .data
686
687 asm_criticalsections:
688 #if defined(USE_THREADS) && defined(NATIVE_THREADS)
689     .dword  _crit_begin
690     .dword  _crit_end
691     .dword  _crit_restart
692 #endif
693     .dword  0
694
695
696         .text
697
698         .ent    compare_and_swap
699
700 compare_and_swap:
701 1:
702         all     v0,0(a0)
703         bne     v0,a1,2f
704         move    t0,a2
705         asc     t0,0(a0)
706         beqz    t0,1b
707 2:
708         sync
709         j       ra
710
711         .end    compare_and_swap
712
713
714 /* Disable exec-stacks, required for Gentoo ***********************************/
715
716 #if defined(__GCC__) && defined(__ELF__)
717         .section .note.GNU-stack,"",@progbits
718 #endif
719
720
721 /*
722  * These are local overrides for various environment variables in Emacs.
723  * Please do not remove this and leave it at the end of the file, where
724  * Emacs will automagically detect them.
725  * ---------------------------------------------------------------------
726  * Local variables:
727  * mode: asm
728  * indent-tabs-mode: t
729  * c-basic-offset: 4
730  * tab-width: 4
731  * End:
732  */