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