* Implemented idiv/irem, ldiv/lrem, aastore, arraycheckcast inline
[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 3002 2005-07-12 16:02:45Z twisti $
32
33 */
34
35
36 #include "config.h"
37
38 #include "vm/jit/mips/offsets.h"
39 #include "vm/jit/mips/asmoffsets.h"
40 #include "vm/jit/mips/md-asm.h"
41
42
43         .text
44         .set    noat
45
46
47 /* exported functions and variables *******************************************/
48
49         .globl asm_calljavafunction
50         .globl asm_calljavafunction_int
51
52         .globl asm_calljavafunction2
53         .globl asm_calljavafunction2int
54         .globl asm_calljavafunction2long
55         .globl asm_calljavafunction2float
56         .globl asm_calljavafunction2double
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_calljavafunction
93
94         .align  3
95
96         .dword  0                         /* catch type all                       */
97         .dword  calljava_xhandler         /* handler pc                           */
98         .dword  calljava_xhandler         /* end pc                               */
99         .dword  asm_calljavafunction      /* start pc                             */
100         .word   1                         /* extable size                         */
101         .word   0                         /* fltsave                              */
102         .word   0                         /* intsave                              */
103         .word   0                         /* isleaf                               */
104         .word   0                         /* IsSync                               */
105         .word   10*8                      /* frame size                           */
106         .dword  0                         /* method pointer (pointer to name)     */
107
108 asm_calljavafunction:
109 asm_calljavafunction_int:
110         aaddiu  sp,sp,-10*8               /* allocate stack space                 */
111         ast     ra,0(sp)                  /* save return address                  */
112
113         .set    noreorder
114
115         bal     call_java_pc
116         ast     pv,3*8(sp)                /* procedure vector (delay slot)        */
117 call_java_pc:
118         aaddiu  pv,ra,-4*4
119
120         .set    reorder
121         
122         sdc1    fss0,4*8(sp)              /* save non JavaABI saved flt registers */
123         sdc1    fss1,5*8(sp)
124         sdc1    fss2,6*8(sp)
125         sdc1    fss3,7*8(sp)
126         sdc1    fss4,8*8(sp)
127         sdc1    fss5,9*8(sp)
128
129         move    itmp1,a0                  /* pass method pointer via tmp1         */
130
131         move    a0,a1                     /* pass the remaining parameters        */
132         move    a1,a2
133         move    a2,a3
134         move    a3,a4
135
136         ala     mptr,asm_call_jit_compiler/* fake virtual function call (2 instr) */
137         ast     mptr,1*8(sp)              /* store function address               */
138         move    mptr,sp                   /* set method pointer                   */
139
140         .set    noreorder
141
142         ald     pv,1*8(mptr)              /* method call as in Java               */
143         jalr    pv                        /* call JIT compiler                    */
144         nop
145         aaddiu  pv,ra,-22*4               /* recompute procedure vector           */
146
147         .set    reorder
148
149 calljava_return:
150         ald     ra,0(sp)                  /* restore return address               */
151         ald     pv,3*8(sp)                /* restore procedure vector             */
152
153         ldc1    fss0,4*8(sp)              /* restore non JavaABI saved flt regs   */
154         ldc1    fss1,5*8(sp)
155         ldc1    fss2,6*8(sp)
156         ldc1    fss3,7*8(sp)
157         ldc1    fss4,8*8(sp)
158         ldc1    fss5,9*8(sp)
159
160         aaddiu  sp,sp,10*8                /* free stack space                     */
161         j       ra                        /* return                               */
162
163 calljava_xhandler:
164         move    a0,itmp1                  
165         jal     builtin_throw_exception
166         move    v0,zero                   /* clear return value for exception     */
167         b       calljava_return
168
169         .end    asm_calljavafunction
170
171
172         .ent    asm_calljavafunction2
173
174         .align  3
175
176         .dword  0                         /* catch type all                       */
177         .dword  calljava_xhandler2        /* handler pc                           */
178         .dword  calljava_xhandler2        /* end pc                               */
179         .dword  asm_calljavafunction2     /* start pc                             */
180         .word   1                         /* extable size                         */
181         .word   0                         /* fltsave                              */
182         .word   1                         /* intsave                              */
183         .word   0                         /* isleaf                               */
184         .word   0                         /* IsSync                               */
185         .word   12*8                      /* frame size                           */
186         .dword  0                         /* method pointer (pointer to name)     */
187
188 asm_calljavafunction2:
189 asm_calljavafunction2int:
190 asm_calljavafunction2long:
191 asm_calljavafunction2float:
192 asm_calljavafunction2double:
193         aaddiu  sp,sp,-12*8               /* allocate stack space (only 11 needed)*/
194         ast     ra,0(sp)                  /* save return address                  */
195
196         .set    noreorder
197         bal     call_java_pc2
198         ast     pv,1*8(sp)                /* procedure vector                     */
199 call_java_pc2:
200         aaddiu  pv,ra,-4*4
201         ast     s7,3*8(sp)
202
203         .set    reorder
204         
205         sdc1    fss0,5*8(sp)              /* save non JavaABI saved flt registers */
206         sdc1    fss1,6*8(sp)
207         sdc1    fss2,7*8(sp)
208         sdc1    fss3,8*8(sp)
209         sdc1    fss4,9*8(sp)
210         sdc1    fss5,10*8(sp)
211
212         ast     a0,4*8(sp)                /* save method pointer for compiler     */
213
214         move    t0,a3
215         move    s7,a1
216         blez    s7,calljava_argsloaded
217
218         ald     a0,offjniitem(t0)
219         ldc1    fa0,offjniitem(t0)
220         daddi   s7,s7,-1
221         blez    s7,calljava_argsloaded
222
223         ald     a1,offjniitem+sizejniblock*1(t0)
224         ldc1    fa1,offjniitem+sizejniblock*1(t0)
225         daddi   s7,s7,-1
226         blez    s7,calljava_argsloaded
227
228         ald     a2,offjniitem+sizejniblock*2(t0)
229         ldc1    fa2,offjniitem+sizejniblock*2(t0)
230         daddi   s7,s7,-1
231         blez    s7,calljava_argsloaded
232
233         ald     a3,offjniitem+sizejniblock*3(t0)
234         ldc1    fa3,offjniitem+sizejniblock*3(t0)
235         daddi   s7,s7,-1
236         blez    s7,calljava_argsloaded
237
238         ald     a4,offjniitem+sizejniblock*4(t0)
239         ldc1    fa4,offjniitem+sizejniblock*4(t0)
240         daddi   s7,s7,-1
241         blez    s7,calljava_argsloaded
242
243         ald     a5,offjniitem+sizejniblock*5(t0)
244         ldc1    fa5,offjniitem+sizejniblock*5(t0)
245         daddi   s7,s7,-1
246         blez    s7,calljava_argsloaded
247
248         ald     a6,offjniitem+sizejniblock*6(t0)
249         ldc1    fa6,offjniitem+sizejniblock*6(t0)
250         daddi   s7,s7,-1
251         blez    s7,calljava_argsloaded
252
253         ald     a7,offjniitem+sizejniblock*7(t0)
254         ldc1    fa7,offjniitem+sizejniblock*7(t0)
255         daddi   s7,s7,-1
256                 
257 calljava_argsloaded:
258         move    t8,sp                      /* save stack pointer                  */
259         blez    s7,calljava_nocopy
260         subu    t1,zero,s7
261         sll     t2,t1,3
262         aaddu   sp,sp,t2
263         aaddu   t2,t2,t8
264
265 calljava_copyloop:
266     ald     t3,offjniitem+sizejniblock*8(t0)
267         ast     t3,0(t2)
268         ala     t1,1(t1)
269         ala     t0,sizejniblock(t0)
270         ala     t2,8(t2)
271         bnez    t1,calljava_copyloop
272
273 calljava_nocopy:
274         ald     itmp1,4*8(t8)             /* pass method pointer via itmp1        */
275
276         ala     mptr,asm_call_jit_compiler/* fake virtual function call (2 instr) */
277         ast     mptr,2*8(sp)              /* store function address               */
278         ala     mptr,1*8(sp)              /* set method pointer                   */
279
280         .set    noreorder
281
282         ald     pv,1*8(mptr)              /* method call as in Java               */
283         jalr    pv                        /* call JIT compiler                    */
284         nop
285         aaddiu  pv,ra,-76*4               /* recompute procedure vector           */
286
287         .set    reorder
288
289 calljava_return2:
290         ald     ra,0(sp)                  /* restore return address               */
291         ald     pv,8(sp)                  /* restore procedure vector             */
292         ald     s7,3*8(sp)
293
294         ldc1    fss0,5*8(sp)              /* restore non JavaABI saved flt regs   */
295         ldc1    fss1,6*8(sp)
296         ldc1    fss2,7*8(sp)
297         ldc1    fss3,8*8(sp)
298         ldc1    fss4,9*8(sp)
299         ldc1    fss5,10*8(sp)
300
301         aaddiu  sp,sp,12*8                /* free stack space                     */
302         j       ra                        /* return                               */
303
304 calljava_xhandler2:
305         asll    s7,s7,3
306         aaddu   sp,s7,sp
307         move    a0,itmp1                  
308         jal     builtin_throw_exception
309         b       calljava_return2
310
311         .end    asm_calljavafunction2
312
313
314 /****************** function asm_call_jit_compiler *****************************
315 *                                                                              *
316 *   invokes the compiler for untranslated JavaVM methods.                      *
317 *                                                                              *
318 *   Register REG_ITEMP1 contains a pointer to the method info structure        *
319 *   (prepared by createcompilerstub). Using the return address in R31 and the  *
320 *   offset in the LDA instruction or using the value in methodptr R25 the      *
321 *   patching address for storing the method address can be computed:           *
322 *                                                                              *
323 *   method address was either loaded using                                     *
324 *   M_ALD (REG_PV, REG_PV, a)        ; invokestatic/special    ($28)           *
325 *   M_JSR (REG_RA, REG_PV);                                                    *
326 *   M_NOP                                                                      *
327 *   M_LDA (REG_PV, REG_RA, val)                                                *
328 *   or                                                                         *
329 *   M_ALD (REG_PV, REG_METHODPTR, m) ; invokevirtual/interface ($25)           *
330 *   M_JSR (REG_RA, REG_PV);                                                    *
331 *   M_NOP                                                                      *
332 *   in the static case the method pointer can be computed using the            *
333 *   return address and the lda function following the jmp instruction          *
334 *                                                                              *
335 *******************************************************************************/
336
337
338         .ent    asm_call_jit_compiler
339
340 asm_call_jit_compiler:
341         lw      t0,-12(ra)            /* load instruction LD PV,xxx($y)           */
342         srl     t0,t0,21              /* shift right register number $y           */
343         and     t0,t0,31              /* isolate register number                  */
344         addiu   t0,t0,-mptrreg        /* test for REG_METHODPTR                   */
345         beqz    t0,noregchange       
346
347         lw      t0,0(ra)              /* load instruction LDA PV,xxx(RA)          */
348         sll     t0,t0,16
349         sra     t0,t0,16              /* isolate offset                           */
350         aaddu   mptr,t0,ra            /* compute update address                   */
351
352 noregchange:
353         aaddiu  sp,sp,-18*8           /* allocate stack space                     */
354
355         SAVE_ARGUMENT_REGISTERS(0)
356
357         sd      mptr,16*8(sp)         /* save method pointer                      */
358         sd      ra,17*8(sp)           /* save return address                      */
359
360         move    a0,itmp1              /* pass 'methodinfo' pointer to             */
361         jal     jit_compile           /* jit compiler                             */
362
363         RESTORE_ARGUMENT_REGISTERS(0)
364
365         ld      mptr,16*8(sp)         /* restore method pointer                   */
366         ld      ra,17*8(sp)           /* restore return address                   */
367         aaddiu  sp,sp,18*8            /* deallocate stack area                    */
368
369         beqz    v0,L_asm_call_jit_compiler_exception
370
371         lw      t0,-12(ra)            /* load instruction LDQ PV,xxx($yy)         */
372         sll     t0,t0,16
373         sra     t0,t0,16              /* isolate offset                           */
374
375         aaddu   t0,t0,mptr            /* compute update address via method pointer*/
376         ast     v0,0(t0)              /* save new method address there            */
377
378         move    pv,v0                 /* move method address into pv              */
379
380         jr      pv                    /* and call method. The method returns      */
381                                       /* directly to the caller (ra).             */
382
383 L_asm_call_jit_compiler_exception:
384 #if defined(USE_THREADS) && defined(NATIVE_THREADS)
385         aaddiu  sp,sp,-2*8
386         ast     ra,0*8(sp)
387         jal     builtin_asm_get_exceptionptrptr
388         ald     ra,0*8(sp)
389         aaddiu  sp,sp,2*8
390 #else
391         la      v0,_exceptionptr
392 #endif
393         ald     xptr,0(v0)            /* get the exception pointer                */
394         ast     zero,0(v0)            /* clear the exception pointer              */
395
396         aaddiu  xpc,ra,-4             /* faulting address is return adress - 4    */
397         b       asm_handle_nat_exception
398
399         .end    asm_call_jit_compiler
400
401
402 /********************* function asm_handle_exception ***************************
403 *                                                                              *
404 *   This function handles an exception. It does not use the usual calling      *
405 *   conventions. The exception pointer is passed in REG_ITMP1 and the          *
406 *   pc from the exception raising position is passed in REG_ITMP2. It searches *
407 *   the local exception table for a handler. If no one is found, it unwinds    *
408 *   stacks and continues searching the callers.                                *
409 *                                                                              *
410 *   void asm_handle_exception (exceptionptr, exceptionpc);                     *
411 *                                                                              *
412 *******************************************************************************/
413
414         .ent    asm_handle_nat_exception
415
416 asm_handle_nat_exception:
417         lw      t0,0(ra)              /* load instruction LDA PV,xxx(RA)          */
418         sll     t0,t0,16
419         sra     t0,t0,16              /* isolate offset                           */
420         aaddu   pv,t0,ra              /* compute update address                   */
421
422         .aent    asm_handle_exception
423
424 asm_handle_exception:
425         aaddiu  sp,sp,-14*8           /* allocate stack                           */
426
427         sd      v0,0*8(sp)            /* save possible used registers             */
428         sd      t0,1*8(sp)            /* also registers used by trace_exception   */
429         sd      t1,2*8(sp)
430         sd      t2,3*8(sp)
431         sd      t3,4*8(sp)
432         sd      t8,5*8(sp)
433         sd      a0,6*8(sp)
434         sd      a1,7*8(sp)
435         sd      a2,8*8(sp)
436         sd      a3,9*8(sp)
437         sd      a4,10*8(sp)
438         sd      a5,11*8(sp)
439         sd      a6,12*8(sp)
440         sd      a7,13*8(sp)
441
442         addu    t3,zero,1             /* set no unwind flag                       */
443 ex_stack_loop:
444         aaddiu  sp,sp,-6*8            /* allocate stack                           */
445         sd      xptr,0*8(sp)          /* save used registers                      */
446         sd      xpc,1*8(sp)
447         sd      pv,2*8(sp)
448         sd      ra,3*8(sp)
449         sd      t3,4*8(sp)
450
451         move    a0,xptr
452         ald     a1,MethodPointer(pv)
453         move    a2,xpc
454 /*      move    a3,t3 */
455         move    a3,zero
456         addu    a4,zero,1
457         jal     builtin_trace_exception /* trace_exception(xptr,methodptr)        */
458         
459         ld      xptr,0*8(sp)          /* restore used register                    */
460         ld      xpc,1*8(sp)
461         ld      pv,2*8(sp)
462         ld      ra,3*8(sp)
463         ld      t3,4*8(sp)
464         aaddiu  sp,sp,6*8             /* deallocate stack                         */
465         
466         lw      t0,ExTableSize(pv)    /* t0 = exception table size                */
467         beqz    t0,empty_table        /* if empty table skip                      */
468         aaddiu  t1,pv,ExTableStart    /* t1 = start of exception table            */
469
470 ex_table_loop:
471         ald     t2,ExStartPC(t1)      /* t2 = exception start pc                  */
472         sle     t2,t2,xpc             /* t2 = (startpc <= xpc)                    */
473         beqz    t2,ex_table_cont      /* if (false) continue                      */
474         ald     t2,ExEndPC(t1)        /* t2 = exception end pc                    */
475         slt     t2,xpc,t2             /* t2 = (xpc < endpc)                       */
476         beqz    t2,ex_table_cont      /* if (false) continue                      */
477         ald     a1,ExCatchType(t1)    /* arg1 = exception catch type              */
478         beqz    a1,ex_handle_it       /* NULL catches everything                  */
479
480         lw      itmp3,offclassloaded(a1)
481         bnez    itmp3,L_class_loaded
482
483         aaddiu  sp,sp,-8*8            /* allocate stack                           */
484         sd      t0,0*8(sp)            /* save used register                       */
485         sd      t1,1*8(sp)
486         sd      t3,2*8(sp)
487         sd      xptr,3*8(sp)
488         sd      xpc,4*8(sp)
489         sd      pv,5*8(sp)
490         sd      ra,6*8(sp)
491         sd      a1,7*8(sp)
492                 
493         move    a0,a1
494         jal     load_class_bootstrap
495                 
496         ld      t0,0*8(sp)            /* restore used register                    */
497         ld      t1,1*8(sp)
498         ld      t3,2*8(sp)
499         ld      xptr,3*8(sp)
500         ld      xpc,4*8(sp)
501         ld      pv,5*8(sp)
502         ld      ra,6*8(sp)
503         ld      a1,7*8(sp)
504         aaddiu  sp,sp,8*8             /* deallocate stack                         */
505         
506 L_class_loaded:
507         lw      itmp3,offclasslinked(a1)
508         aaddiu  sp,sp,-8*8            /* allocate stack                           */
509         sd      a1,7*8(sp)
510         bnez    itmp3,L_class_linked
511
512         sd      t0,0*8(sp)            /* save used register                       */
513         sd      t1,1*8(sp)
514         sd      t3,2*8(sp)
515         sd      xptr,3*8(sp)
516         sd      xpc,4*8(sp)
517         sd      pv,5*8(sp)
518         sd      ra,6*8(sp)
519                 
520         move    a0,a1
521         jal     link_class
522                 
523         ld      t0,0*8(sp)            /* restore used register                    */
524         ld      t1,1*8(sp)
525         ld      t3,2*8(sp)
526         ld      xptr,3*8(sp)
527         ld      xpc,4*8(sp)
528         ld      pv,5*8(sp)
529         ld      ra,6*8(sp)
530
531 L_class_linked:
532 _crit_restart1:
533         ld      a1,7*8(sp)
534 _crit_begin1:
535         ald     a0,offobjvftbl(xptr)  /* a0 = vftblptr(xptr)                      */
536         ald     a1,offclassvftbl(a1)  /* a1 = vftblptr(catchtype) class (not obj) */
537         lw      a0,offbaseval(a0)     /* a0 = baseval(xptr)                       */
538         lw      v0,offbaseval(a1)     /* a2 = baseval(catchtype)                  */
539         lw      a1,offdiffval(a1)     /* a1 = diffval(catchtype)                  */
540 _crit_end1:
541         subu    a0,a0,v0              /* a0 = baseval(xptr) - baseval(catchtype)  */
542         sltu    v0,a1,a0              /* v0 = xptr is instanceof catchtype        */
543         aaddiu  sp,sp,8*8             /* deallocate stack                         */
544         bnez    v0,ex_table_cont      /* if (false) continue                      */
545
546 ex_handle_it:
547         ald     xpc,ExHandlerPC(t1)   /* xpc = exception handler pc               */
548
549         beqz    t3,ex_jump            /* if (!(no stack unwinding) skip           */
550
551         ld      v0,0*8(sp)            /* restore possible used registers          */
552         ld      t0,1*8(sp)            /* also registers used by trace_exception   */
553         ld      t1,2*8(sp)
554         ld      t2,3*8(sp)
555         ld      t3,4*8(sp)
556         ld      t8,5*8(sp)
557         ld      a0,6*8(sp)
558         ld      a1,7*8(sp)
559         ld      a2,8*8(sp)
560         ld      a3,9*8(sp)
561         ld      a4,10*8(sp)
562         ld      a5,11*8(sp)
563         ld      a6,12*8(sp)
564         ld      a7,13*8(sp)
565         
566         aaddiu  sp,sp,14*8            /* deallocate stack                         */
567
568 ex_jump:
569         jr      xpc                   /* jump to the handler                      */
570
571 ex_table_cont:
572         aaddiu  t1,t1,ExEntrySize     /* next exception table entry               */
573         addiu   t0,t0,-1              /* decrement entry counter                  */
574         bgtz    t0,ex_table_loop      /* if (t0 > 0) next entry                   */
575
576 empty_table:
577         beqz    t3,ex_already_cleared /* if here the first time, then             */
578         aaddiu  sp,sp,14*8            /* deallocate stack and                     */
579         move    t3,zero               /* clear the no unwind flag                 */
580 ex_already_cleared:
581         lw      t0,IsSync(pv)         /* t0 = SyncOffset                          */
582         beqz    t0,no_monitor_exit    /* if zero no monitorexit                   */
583
584 #if defined(USE_THREADS)
585         aaddu   t0,sp,t0              /* add stackptr to Offset                   */
586         ald     a0,-8(t0)             /* load monitorexit pointer                 */
587
588         aaddiu  sp,sp,-8*8            /* allocate stack                           */
589         sd      t0,0*8(sp)            /* save used register                       */
590         sd      t1,1*8(sp)
591         sd      t3,2*8(sp)
592         sd      xptr,3*8(sp)
593         sd      xpc,4*8(sp)
594         sd      pv,5*8(sp)
595         sd      ra,6*8(sp)
596
597         jal     builtin_monitorexit   /* builtin_monitorexit(objectptr)           */
598         
599         ld      t0,0*8(sp)            /* restore used register                    */
600         ld      t1,1*8(sp)
601         ld      t3,2*8(sp)
602         ld      xptr,3*8(sp)
603         ld      xpc,4*8(sp)
604         ld      pv,5*8(sp)
605         ld      ra,6*8(sp)
606         aaddiu  sp,sp,8*8             /* deallocate stack                         */
607 #endif
608
609 no_monitor_exit:
610         lw      t0,FrameSize(pv)      /* t0 = frame size                          */
611         aaddu   sp,sp,t0              /* unwind stack                             */
612         move    t0,sp                 /* t0 = pointer to save area                */
613         lw      t1,IsLeaf(pv)         /* t1 = is leaf procedure                   */
614         bnez    t1,ex_no_restore      /* if (leaf) skip                           */
615         ld      ra,-8(t0)             /* restore ra                               */
616         aaddiu  t0,t0,-8              /* t0--                                     */
617 ex_no_restore:
618         move    xpc,ra                /* the new xpc is ra                        */
619         lw      t1,IntSave(pv)        /* t1 = saved int register count            */
620         ala     t2,ex_int2            /* t2 = current pc                          */
621         sll     t1,t1,2               /* t1 = register count * 4                  */
622         asubu   t2,t2,t1              /* t2 = ex_int_sav - 4 * register count     */
623         jr      t2                    /* jump to save position                    */
624         ld      s0,-8*8(t0)
625         ld      s1,-7*8(t0)
626         ld      s2,-6*8(t0)
627         ld      s3,-5*8(t0)
628         ld      s4,-4*8(t0)
629         ld      s5,-3*8(t0)
630         ld      s6,-2*8(t0)
631         ld      s7,-1*8(t0)
632 ex_int2:
633         sll     t1,t1,1               /* t1 = register count * 4 * 2              */
634         asubu   t0,t0,t1              /* t0 = t0 - 8 * register count             */
635
636         lw      t1,FltSave(pv)        /* t1 = saved flt register count            */
637         ala     t2,ex_flt2            /* t2 = current pc                          */
638         sll     t1,t1,2               /* t1 = register count * 4                  */
639         asubu   t2,t2,t1              /* t2 = ex_int_sav - 4 * register count     */
640         jr      t2                    /* jump to save position                    */
641         ldc1    fs0,-4*8(t0)
642         ldc1    fs1,-3*8(t0)
643         ldc1    fs2,-2*8(t0)
644         ldc1    fs3,-1*8(t0)
645 ex_flt2:
646         lw      t0,0(ra)              /* load instruction LDA PV,xxx(RA)          */
647         sll     t0,t0,16
648         sra     t0,t0,16              /* isolate offset                           */
649         aaddu   pv,t0,ra              /* compute update address                   */
650         b       ex_stack_loop
651
652         .end    asm_handle_nat_exception
653
654
655 /* asm_wrapper_patcher *********************************************************
656
657    XXX
658
659    Stack layout:
660          32   return address into JIT code (patch position)
661      24   pointer to virtual java_objectheader
662      16   machine code (which is patched back later)
663       8   unresolved class/method/field reference
664       0   patcher function pointer to call
665
666 *******************************************************************************/
667                 
668     .ent    asm_wrapper_patcher
669
670 asm_wrapper_patcher:
671         aaddiu  sp,sp,-(16+21+4+1)*8  /* create stack frame                       */
672
673         SAVE_ARGUMENT_REGISTERS(0)    /* save 8 int/8 float argument registers    */
674         SAVE_TEMPORARY_REGISTERS(16)  /* save 5 int/16 float temporary registers  */
675
676         ast     itmp1,(16+21+0)*8(sp) /* save itmp1                               */
677         ast     itmp2,(16+21+1)*8(sp) /* save itmp2                               */
678         ast     ra,(16+21+2+1)*8(sp)  /* save method return address (for leafs)   */
679         ast     pv,(16+21+3+1)*8(sp)  /* save pv of calling java function         */
680
681         aaddiu  a0,sp,(0+16+21+4+1)*8 /* pass sp                                  */
682         ald     itmp3,(0+16+21+4+1)*8(sp) /* get function pointer                 */
683         ald     itmp1,(16+21+3+1)*8(sp) /* save pv to the position of fp          */
684         ast     itmp1,(0+16+21+4+1)*8(sp)
685         jalr    itmp3
686
687         RESTORE_ARGUMENT_REGISTERS(0) /* restore 8 int/8 float argument registers */
688         RESTORE_TEMPORARY_REGISTERS(16) /* restore 5 int/16 float temporary reg.  */
689
690         ald     itmp1,(16+21+0)*8(sp) /* restore itmp1                            */
691         ald     itmp2,(16+21+1)*8(sp) /* restore itmp2                            */
692         ald     ra,(16+21+2+1)*8(sp)  /* restore method return address (for leafs)*/
693         ald     pv,(16+21+3+1)*8(sp)  /* restore pv of calling java function      */
694
695         ald     itmp3,(4+16+21+4+1)*8(sp) /* get return address (into JIT code)   */
696         aaddiu  sp,sp,(5+16+21+4+1)*8 /* remove stack frame                       */
697
698         beqz    v0,L_asm_wrapper_patcher_exception
699
700         jr      itmp3                 /* jump to new patched code                 */
701
702 L_asm_wrapper_patcher_exception:
703         move    xpc,itmp3             /* return address into JIT code is xpc      */
704
705 #if defined(USE_THREADS) && defined(NATIVE_THREADS)
706         daddiu  sp,sp,-4*8
707         sd      xpc,0*8(sp)
708         sd      ra,1*8(sp)
709         sd      pv,2*8(sp)
710         jal     builtin_asm_get_exceptionptrptr
711         ld      xpc,0*8(sp)
712         ld      ra,1*8(sp)
713         ld      pv,2*8(sp)
714         daddiu  sp,sp,4*8
715 #else
716         la      v0,_exceptionptr
717 #endif
718         ld      xptr,0(v0)            /* get the exception pointer                */
719         sd      zero,0(v0)            /* clear the exception pointer              */
720         b       asm_handle_exception
721
722         .end    asm_wrapper_patcher
723
724                 
725 /******************* function asm_initialize_thread_stack **********************
726 *                                                                              *
727 *   u1* asm_initialize_thread_stack (void *func, u1 *stack);                   *
728 *                                                                              *
729 *   initialize a thread stack                                                  *
730 *                                                                              *
731 *******************************************************************************/
732
733         .ent    asm_initialize_thread_stack
734
735 asm_initialize_thread_stack:
736         aaddiu  a1,a1,-14*8     /* allocate save area                             */
737         sd      zero, 0*8(a1)   /* s0 initalize thread area                       */
738         sd      zero, 1*8(a1)   /* s1                                             */
739         sd      zero, 2*8(a1)   /* s2                                             */
740         sd      zero, 3*8(a1)   /* s3                                             */
741         sd      zero, 4*8(a1)   /* s4                                             */
742         sd      zero, 5*8(a1)   /* s5                                             */
743         sd      zero, 6*8(a1)   /* s6                                             */
744         sd      zero, 7*8(a1)   /* s7                                             */
745         sd      zero, 8*8(a1)   /* s8                                             */
746         sd      zero, 9*8(a1)   /* fs0                                            */
747         sd      zero,10*8(a1)   /* fs1                                            */
748         sd      zero,11*8(a1)   /* fs2                                            */
749         sd      zero,12*8(a1)   /* fs3                                            */
750         sd      a0, 13*8(a1)
751         move    v0,a1
752         j       ra              /* return                                         */
753
754         .end    asm_initialize_thread_stack
755
756
757 /******************* function asm_perform_threadswitch *************************
758 *                                                                              *
759 *   void asm_perform_threadswitch (u1 **from, u1 **to, u1 **stackTop);         *
760 *                                                                              *
761 *   performs a threadswitch                                                    *
762 *                                                                              *
763 *******************************************************************************/
764
765         .ent    asm_perform_threadswitch
766
767 asm_perform_threadswitch:
768         aaddiu  sp,sp,-14*8     /* allocate new stack                             */
769         sd      s0,  0*8(sp)    /* save saved registers of old thread             */
770         sd      s1,  1*8(sp)
771         sd      s2,  2*8(sp)
772         sd      s3,  3*8(sp)
773         sd      s4,  4*8(sp)
774         sd      s5,  5*8(sp)
775         sd      s6,  6*8(sp)
776         sd      s7,  7*8(sp)
777         sd      s8,  8*8(sp)
778         sdc1    fs0, 9*8(sp)
779         sdc1    fs1,10*8(sp)
780         sdc1    fs2,11*8(sp)
781         sdc1    fs3,12*8(sp)
782         sd      ra, 13*8(sp)
783         ast     sp,0(a0)        /* save old stack pointer                         */
784         ast     sp,0(a2)        /* stackTop = old stack pointer                   */
785         ald     sp,0(a1)        /* load new stack pointer                         */
786         ld      s0,  0*8(sp)    /* load saved registers of new thread             */
787         ld      s1,  1*8(sp)
788         ld      s2,  2*8(sp)
789         ld      s3,  3*8(sp)
790         ld      s4,  4*8(sp)
791         ld      s5,  5*8(sp)
792         ld      s6,  6*8(sp)
793         ld      s7,  7*8(sp)
794         ld      s8,  8*8(sp)
795         ldc1    fs0, 9*8(sp)
796         ldc1    fs1,10*8(sp)
797         ldc1    fs2,11*8(sp)
798         ldc1    fs3,12*8(sp)
799         ld      ra, 13*8(sp)
800         aaddiu  sp,sp,14*8      /* deallocate new stack                           */
801         move    itmp3, ra
802         j       ra              /* return                                         */
803
804         .end    asm_perform_threadswitch
805
806
807 /********************* function asm_switchstackandcall *************************
808 *                                                                              *
809 *  void asm_switchstackandcall (void *stack, void *func, void **stacktopsave); *
810 *                                                                              *
811 *   Switches to a new stack, calls a function and switches back.               *
812 *       a0      new stack pointer                                              *
813 *       a1      function pointer                                               *
814 *               a2              pointer to variable where stack top should be stored           *
815 *                                                                              *
816 *******************************************************************************/
817
818         .ent    asm_switchstackandcall
819
820 asm_switchstackandcall:
821         aaddiu  a0,a0,-16       /* allocate new stack                             */
822         sd      ra,0(a0)        /* save return address on new stack               */
823         sd      sp,8(a0)        /* save old stack pointer on new stack            */
824         sd      sp,0(a2)        /* save old stack pointer to variable             */
825         move    sp,a0           /* switch to new stack                            */
826         
827         move    itmp3,a1
828         move    a0,a3
829         jalr    itmp3           /* and call function                              */
830
831         ld      ra,0(sp)        /* load return address                            */
832         ld      sp,8(sp)        /* switch to old stack                            */
833
834         j       ra              /* return                                         */
835
836         .end    asm_switchstackandcall
837
838
839         .ent    asm_getclassvalues_atomic
840
841 asm_getclassvalues_atomic:
842 _crit_restart2:
843 _crit_begin2:
844         lw      t0,offbaseval(a0)
845         lw      t1,offdiffval(a0)
846         lw      t2,offbaseval(a1)
847 _crit_end2:
848         sw      t0,offcast_super_baseval(a2)
849         sw      t1,offcast_super_diffval(a2)
850         sw      t2,offcast_sub_baseval(a2)
851         j       ra
852
853         .end    asm_getclassvalues_atomic
854
855     .data
856
857 asm_criticalsections:
858 #if defined(USE_THREADS) && defined(NATIVE_THREADS)
859     .dword  _crit_begin1
860     .dword  _crit_end1
861     .dword  _crit_restart1
862     .dword  _crit_begin2
863     .dword  _crit_end2
864     .dword  _crit_restart2
865 #endif
866     .dword  0
867
868
869         .text
870
871         .ent    compare_and_swap
872
873 compare_and_swap:
874 1:
875         all     v0,0(a0)
876         bne     v0,a1,2f
877         move    t0,a2
878         asc     t0,0(a0)
879         beqz    t0,1b
880 2:
881         sync
882         j       ra
883
884         .end    compare_and_swap
885
886
887 /*
888  * These are local overrides for various environment variables in Emacs.
889  * Please do not remove this and leave it at the end of the file, where
890  * Emacs will automagically detect them.
891  * ---------------------------------------------------------------------
892  * Local variables:
893  * mode: asm
894  * indent-tabs-mode: t
895  * c-basic-offset: 4
896  * tab-width: 4
897  * End:
898  */