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