* types.h: Include path fixes.
[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 3323 2005-10-04 18:33:30Z 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         lw      t0,-12(ra)            /* load instruction LD PV,xxx($y)           */
351         srl     t0,t0,21              /* shift right register number $y           */
352         and     t0,t0,31              /* isolate register number                  */
353         addiu   t0,t0,-mptrreg        /* test for REG_METHODPTR                   */
354         beqz    t0,noregchange       
355
356         lw      t0,0(ra)              /* load instruction LDA PV,xxx(RA)          */
357         sll     t0,t0,16
358         sra     t0,t0,16              /* isolate offset                           */
359         aaddu   mptr,t0,ra            /* compute update address                   */
360
361 noregchange:
362         aaddiu  sp,sp,-(20*8+sizestackframeinfo) /* allocate stack space          */
363
364         SAVE_ARGUMENT_REGISTERS(0)
365
366         ast     mptr,16*8(sp)         /* save method pointer                      */
367         ast     ra,17*8(sp)           /* save return address                      */
368         ast     itmp1,18*8(sp)        /* save methodinfo pointer                  */
369
370         aaddiu  a0,sp,20*8            /* create stackframe info                   */
371         move    a1,zero               /* we don't have pv handy                   */
372         aaddiu  a2,sp,(20*8+sizestackframeinfo) /* pass java sp                   */
373         move    a3,ra                 /* pass java ra                             */
374         move    a4,a3                 /* xpc is equal to ra                       */
375         jal     stacktrace_create_extern_stackframeinfo
376
377         ald     a0,18*8(sp)           /* pass methodinfo pointer                  */
378         jal     jit_compile           /* jit compiler                             */
379         ast     v0,18*8(sp)           /* save return value                        */
380
381         aaddiu  a0,sp,20*8            /* remove stackframe info                   */
382         jal     stacktrace_remove_stackframeinfo
383
384         RESTORE_ARGUMENT_REGISTERS(0)
385
386         ald     mptr,16*8(sp)         /* restore method pointer                   */
387         ald     ra,17*8(sp)           /* restore return address                   */
388         ald     v0,18*8(sp)           /* restore return value                     */
389         aaddiu  sp,sp,20*8+sizestackframeinfo /* deallocate stack area            */
390
391         beqz    v0,L_asm_call_jit_compiler_exception
392
393         lw      t0,-12(ra)            /* load instruction LDQ PV,xxx($yy)         */
394         sll     t0,t0,16
395         sra     t0,t0,16              /* isolate offset                           */
396
397         aaddu   t0,t0,mptr            /* compute update address via method pointer*/
398         ast     v0,0(t0)              /* save new method address there            */
399
400         move    pv,v0                 /* move method address into pv              */
401
402         jr      pv                    /* and call method. The method returns      */
403                                       /* directly to the caller (ra).             */
404
405 L_asm_call_jit_compiler_exception:
406 #if defined(USE_THREADS) && defined(NATIVE_THREADS)
407         aaddiu  sp,sp,-2*8
408         ast     ra,0*8(sp)
409         jal     builtin_asm_get_exceptionptrptr
410         ald     ra,0*8(sp)
411         aaddiu  sp,sp,2*8
412 #else
413         la      v0,_exceptionptr
414 #endif
415         ald     xptr,0(v0)            /* get the exception pointer                */
416         ast     zero,0(v0)            /* clear the exception pointer              */
417
418         aaddiu  xpc,ra,-4             /* faulting address is return adress - 4    */
419         b       asm_handle_nat_exception
420
421         .end    asm_call_jit_compiler
422
423
424 /********************* function asm_handle_exception ***************************
425 *                                                                              *
426 *   This function handles an exception. It does not use the usual calling      *
427 *   conventions. The exception pointer is passed in REG_ITMP1 and the          *
428 *   pc from the exception raising position is passed in REG_ITMP2. It searches *
429 *   the local exception table for a handler. If no one is found, it unwinds    *
430 *   stacks and continues searching the callers.                                *
431 *                                                                              *
432 *   void asm_handle_exception (exceptionptr, exceptionpc);                     *
433 *                                                                              *
434 *******************************************************************************/
435
436         .ent    asm_handle_nat_exception
437
438 asm_handle_nat_exception:
439         lw      t0,0(ra)              /* load instruction LDA PV,xxx(RA)          */
440         sll     t0,t0,16
441         sra     t0,t0,16              /* isolate offset                           */
442         aaddu   pv,t0,ra              /* compute update address                   */
443
444         .aent    asm_handle_exception
445
446 asm_handle_exception:
447         aaddiu  sp,sp,-14*8           /* allocate stack                           */
448
449         sd      v0,0*8(sp)            /* save possible used registers             */
450         sd      t0,1*8(sp)            /* also registers used by trace_exception   */
451         sd      t1,2*8(sp)
452         sd      t2,3*8(sp)
453         sd      t3,4*8(sp)
454         sd      t8,5*8(sp)
455         sd      a0,6*8(sp)
456         sd      a1,7*8(sp)
457         sd      a2,8*8(sp)
458         sd      a3,9*8(sp)
459         sd      a4,10*8(sp)
460         sd      a5,11*8(sp)
461         sd      a6,12*8(sp)
462         sd      a7,13*8(sp)
463
464         addu    t3,zero,1             /* set no unwind flag                       */
465 ex_stack_loop:
466         aaddiu  sp,sp,-6*8            /* allocate stack                           */
467         sd      xptr,0*8(sp)          /* save used registers                      */
468         sd      xpc,1*8(sp)
469         sd      pv,2*8(sp)
470         sd      ra,3*8(sp)
471         sd      t3,4*8(sp)
472
473         move    a0,xptr
474         ald     a1,MethodPointer(pv)
475         move    a2,xpc
476 /*      move    a3,t3 */
477         move    a3,zero
478         addu    a4,zero,1
479         jal     builtin_trace_exception /* trace_exception(xptr,methodptr)        */
480         
481         ld      xptr,0*8(sp)          /* restore used register                    */
482         ld      xpc,1*8(sp)
483         ld      pv,2*8(sp)
484         ld      ra,3*8(sp)
485         ld      t3,4*8(sp)
486         aaddiu  sp,sp,6*8             /* deallocate stack                         */
487         
488         lw      t0,ExTableSize(pv)    /* t0 = exception table size                */
489         beqz    t0,empty_table        /* if empty table skip                      */
490         aaddiu  t1,pv,ExTableStart    /* t1 = start of exception table            */
491
492 ex_table_loop:
493         ald     t2,ExStartPC(t1)      /* t2 = exception start pc                  */
494         sle     t2,t2,xpc             /* t2 = (startpc <= xpc)                    */
495         beqz    t2,ex_table_cont      /* if (false) continue                      */
496         ald     t2,ExEndPC(t1)        /* t2 = exception end pc                    */
497         slt     t2,xpc,t2             /* t2 = (xpc < endpc)                       */
498         beqz    t2,ex_table_cont      /* if (false) continue                      */
499         ald     a1,ExCatchType(t1)    /* arg1 = exception catch type              */
500         beqz    a1,ex_handle_it       /* NULL catches everything                  */
501
502         lw      itmp3,offclassloaded(a1)
503         bnez    itmp3,L_class_loaded
504
505         aaddiu  sp,sp,-8*8            /* allocate stack                           */
506         sd      t0,0*8(sp)            /* save used register                       */
507         sd      t1,1*8(sp)
508         sd      t3,2*8(sp)
509         sd      xptr,3*8(sp)
510         sd      xpc,4*8(sp)
511         sd      pv,5*8(sp)
512         sd      ra,6*8(sp)
513         sd      a1,7*8(sp)
514                 
515         move    a0,a1
516         jal     load_class_bootstrap
517                 
518         ld      t0,0*8(sp)            /* restore used register                    */
519         ld      t1,1*8(sp)
520         ld      t3,2*8(sp)
521         ld      xptr,3*8(sp)
522         ld      xpc,4*8(sp)
523         ld      pv,5*8(sp)
524         ld      ra,6*8(sp)
525         ld      a1,7*8(sp)
526         aaddiu  sp,sp,8*8             /* deallocate stack                         */
527         
528 L_class_loaded:
529         lw      itmp3,offclasslinked(a1)
530         aaddiu  sp,sp,-8*8            /* allocate stack                           */
531         sd      a1,7*8(sp)
532         bnez    itmp3,L_class_linked
533
534         sd      t0,0*8(sp)            /* save used register                       */
535         sd      t1,1*8(sp)
536         sd      t3,2*8(sp)
537         sd      xptr,3*8(sp)
538         sd      xpc,4*8(sp)
539         sd      pv,5*8(sp)
540         sd      ra,6*8(sp)
541                 
542         move    a0,a1
543         jal     link_class
544                 
545         ld      t0,0*8(sp)            /* restore used register                    */
546         ld      t1,1*8(sp)
547         ld      t3,2*8(sp)
548         ld      xptr,3*8(sp)
549         ld      xpc,4*8(sp)
550         ld      pv,5*8(sp)
551         ld      ra,6*8(sp)
552
553 L_class_linked:
554 _crit_restart1:
555         ld      a1,7*8(sp)
556 _crit_begin1:
557         ald     a0,offobjvftbl(xptr)  /* a0 = vftblptr(xptr)                      */
558         ald     a1,offclassvftbl(a1)  /* a1 = vftblptr(catchtype) class (not obj) */
559         lw      a0,offbaseval(a0)     /* a0 = baseval(xptr)                       */
560         lw      v0,offbaseval(a1)     /* a2 = baseval(catchtype)                  */
561         lw      a1,offdiffval(a1)     /* a1 = diffval(catchtype)                  */
562 _crit_end1:
563         subu    a0,a0,v0              /* a0 = baseval(xptr) - baseval(catchtype)  */
564         sltu    v0,a1,a0              /* v0 = xptr is instanceof catchtype        */
565         aaddiu  sp,sp,8*8             /* deallocate stack                         */
566         bnez    v0,ex_table_cont      /* if (false) continue                      */
567
568 ex_handle_it:
569         ald     xpc,ExHandlerPC(t1)   /* xpc = exception handler pc               */
570
571         beqz    t3,ex_jump            /* if (!(no stack unwinding) skip           */
572
573         ld      v0,0*8(sp)            /* restore possible used registers          */
574         ld      t0,1*8(sp)            /* also registers used by trace_exception   */
575         ld      t1,2*8(sp)
576         ld      t2,3*8(sp)
577         ld      t3,4*8(sp)
578         ld      t8,5*8(sp)
579         ld      a0,6*8(sp)
580         ld      a1,7*8(sp)
581         ld      a2,8*8(sp)
582         ld      a3,9*8(sp)
583         ld      a4,10*8(sp)
584         ld      a5,11*8(sp)
585         ld      a6,12*8(sp)
586         ld      a7,13*8(sp)
587         
588         aaddiu  sp,sp,14*8            /* deallocate stack                         */
589
590 ex_jump:
591         jr      xpc                   /* jump to the handler                      */
592
593 ex_table_cont:
594         aaddiu  t1,t1,ExEntrySize     /* next exception table entry               */
595         addiu   t0,t0,-1              /* decrement entry counter                  */
596         bgtz    t0,ex_table_loop      /* if (t0 > 0) next entry                   */
597
598 empty_table:
599         beqz    t3,ex_already_cleared /* if here the first time, then             */
600         aaddiu  sp,sp,14*8            /* deallocate stack and                     */
601         move    t3,zero               /* clear the no unwind flag                 */
602 ex_already_cleared:
603         lw      t0,IsSync(pv)         /* t0 = SyncOffset                          */
604         beqz    t0,no_monitor_exit    /* if zero no monitorexit                   */
605
606 #if defined(USE_THREADS)
607         aaddu   t0,sp,t0              /* add stackptr to Offset                   */
608         ald     a0,-8(t0)             /* load monitorexit pointer                 */
609
610         aaddiu  sp,sp,-8*8            /* allocate stack                           */
611         sd      t0,0*8(sp)            /* save used register                       */
612         sd      t1,1*8(sp)
613         sd      t3,2*8(sp)
614         sd      xptr,3*8(sp)
615         sd      xpc,4*8(sp)
616         sd      pv,5*8(sp)
617         sd      ra,6*8(sp)
618
619         jal     builtin_monitorexit   /* builtin_monitorexit(objectptr)           */
620         
621         ld      t0,0*8(sp)            /* restore used register                    */
622         ld      t1,1*8(sp)
623         ld      t3,2*8(sp)
624         ld      xptr,3*8(sp)
625         ld      xpc,4*8(sp)
626         ld      pv,5*8(sp)
627         ld      ra,6*8(sp)
628         aaddiu  sp,sp,8*8             /* deallocate stack                         */
629 #endif
630
631 no_monitor_exit:
632         lw      t0,FrameSize(pv)      /* t0 = frame size                          */
633         aaddu   sp,sp,t0              /* unwind stack                             */
634         move    t0,sp                 /* t0 = pointer to save area                */
635         lw      t1,IsLeaf(pv)         /* t1 = is leaf procedure                   */
636         bnez    t1,ex_no_restore      /* if (leaf) skip                           */
637         ld      ra,-8(t0)             /* restore ra                               */
638         aaddiu  t0,t0,-8              /* t0--                                     */
639 ex_no_restore:
640         move    xpc,ra                /* the new xpc is ra                        */
641         lw      t1,IntSave(pv)        /* t1 = saved int register count            */
642         ala     t2,ex_int2            /* t2 = current pc                          */
643         sll     t1,t1,2               /* t1 = register count * 4                  */
644         asubu   t2,t2,t1              /* t2 = ex_int_sav - 4 * register count     */
645         jr      t2                    /* jump to save position                    */
646         ld      s0,-8*8(t0)
647         ld      s1,-7*8(t0)
648         ld      s2,-6*8(t0)
649         ld      s3,-5*8(t0)
650         ld      s4,-4*8(t0)
651         ld      s5,-3*8(t0)
652         ld      s6,-2*8(t0)
653         ld      s7,-1*8(t0)
654 ex_int2:
655         sll     t1,t1,1               /* t1 = register count * 4 * 2              */
656         asubu   t0,t0,t1              /* t0 = t0 - 8 * register count             */
657
658         lw      t1,FltSave(pv)        /* t1 = saved flt register count            */
659         ala     t2,ex_flt2            /* t2 = current pc                          */
660         sll     t1,t1,2               /* t1 = register count * 4                  */
661         asubu   t2,t2,t1              /* t2 = ex_int_sav - 4 * register count     */
662         jr      t2                    /* jump to save position                    */
663         ldc1    fs0,-4*8(t0)
664         ldc1    fs1,-3*8(t0)
665         ldc1    fs2,-2*8(t0)
666         ldc1    fs3,-1*8(t0)
667 ex_flt2:
668         lw      t0,0(ra)              /* load instruction LDA PV,xxx(RA)          */
669         sll     t0,t0,16
670         sra     t0,t0,16              /* isolate offset                           */
671         aaddu   pv,t0,ra              /* compute update address                   */
672         b       ex_stack_loop
673
674         .end    asm_handle_nat_exception
675
676
677 /* asm_wrapper_patcher *********************************************************
678
679    XXX
680
681    Stack layout:
682      40   return address into JIT code (patch position)
683      32   pointer to virtual java_objectheader
684      24   machine code (which is patched back later)
685      16   unresolved class/method/field reference
686       8   data segment displacement from load instructions
687       0   patcher function pointer to call
688
689 *******************************************************************************/
690                 
691     .ent    asm_wrapper_patcher
692
693 asm_wrapper_patcher:
694         aaddiu  sp,sp,-((16+21+4)*8+sizestackframeinfo) /* create stack frame     */
695
696         SAVE_ARGUMENT_REGISTERS(0)    /* save 8 int/8 float argument registers    */
697         SAVE_TEMPORARY_REGISTERS(16)  /* save 5 int/16 float temporary registers  */
698
699         ast     itmp1,(16+21+0)*8(sp) /* save itmp1                               */
700         ast     itmp2,(16+21+1)*8(sp) /* save itmp2                               */
701         ast     ra,(16+21+2)*8(sp)    /* save method return address (for leafs)   */
702         ast     pv,(16+21+3)*8(sp)    /* save pv of calling java function         */
703
704         aaddiu  a0,sp,(16+21+4)*8     /* create stackframe info                   */
705         move    a1,pv                 /* pass java pv                             */
706         aaddiu  a2,sp,((6+16+21+4)*8+sizestackframeinfo) /* pass java sp          */
707         move    a3,ra                 /* this is correct for leafs                */
708         ald     a4,((5+16+21+4)*8+sizestackframeinfo)(sp) /* pass xpc             */
709         jal     stacktrace_create_extern_stackframeinfo
710
711         aaddiu  a0,sp,((0+16+21+4)*8+sizestackframeinfo) /* pass sp               */
712         ald     itmp3,((0+16+21+4)*8+sizestackframeinfo)(sp) /* get function      */
713         ald     itmp1,(16+21+3)*8(sp) /* save pv to the position of fp            */
714         ast     itmp1,((0+16+21+4)*8+sizestackframeinfo)(sp)
715         jalr    itmp3
716         ast     v0,((0+16+21+4)*8+sizestackframeinfo)(sp) /* save return value    */
717
718         aaddiu  a0,sp,(16+21+4)*8     /* remove stackframe info                   */
719         jal     stacktrace_remove_stackframeinfo
720
721         RESTORE_ARGUMENT_REGISTERS(0) /* restore 8 int/8 float argument registers */
722         RESTORE_TEMPORARY_REGISTERS(16) /* restore 5 int/16 float temporary reg.  */
723
724         ald     itmp1,(16+21+0)*8(sp) /* restore itmp1                            */
725         ald     itmp2,(16+21+1)*8(sp) /* restore itmp2                            */
726         ald     ra,(16+21+2)*8(sp)    /* restore method return address (for leafs)*/
727         ald     pv,(16+21+3)*8(sp)    /* restore pv of calling java function      */
728
729         ald     v0,((0+16+21+4)*8+sizestackframeinfo)(sp) /* restore return value */
730
731         ald     itmp3,((5+16+21+4)*8+sizestackframeinfo)(sp) /* get ra to jit code*/
732         aaddiu  sp,sp,((6+16+21+4)*8+sizestackframeinfo) /* remove stack frame    */
733
734         beqz    v0,L_asm_wrapper_patcher_exception
735
736         jr      itmp3                 /* jump to new patched code                 */
737
738 L_asm_wrapper_patcher_exception:
739         move    xpc,itmp3             /* return address into JIT code is xpc      */
740
741 #if defined(USE_THREADS) && defined(NATIVE_THREADS)
742         daddiu  sp,sp,-4*8
743         sd      xpc,0*8(sp)
744         sd      ra,1*8(sp)
745         sd      pv,2*8(sp)
746         jal     builtin_asm_get_exceptionptrptr
747         ld      xpc,0*8(sp)
748         ld      ra,1*8(sp)
749         ld      pv,2*8(sp)
750         daddiu  sp,sp,4*8
751 #else
752         la      v0,_exceptionptr
753 #endif
754         ld      xptr,0(v0)            /* get the exception pointer                */
755         sd      zero,0(v0)            /* clear the exception pointer              */
756         b       asm_handle_exception
757
758         .end    asm_wrapper_patcher
759
760                 
761 /******************* function asm_initialize_thread_stack **********************
762 *                                                                              *
763 *   u1* asm_initialize_thread_stack (void *func, u1 *stack);                   *
764 *                                                                              *
765 *   initialize a thread stack                                                  *
766 *                                                                              *
767 *******************************************************************************/
768
769         .ent    asm_initialize_thread_stack
770
771 asm_initialize_thread_stack:
772         aaddiu  a1,a1,-14*8     /* allocate save area                             */
773         sd      zero, 0*8(a1)   /* s0 initalize thread area                       */
774         sd      zero, 1*8(a1)   /* s1                                             */
775         sd      zero, 2*8(a1)   /* s2                                             */
776         sd      zero, 3*8(a1)   /* s3                                             */
777         sd      zero, 4*8(a1)   /* s4                                             */
778         sd      zero, 5*8(a1)   /* s5                                             */
779         sd      zero, 6*8(a1)   /* s6                                             */
780         sd      zero, 7*8(a1)   /* s7                                             */
781         sd      zero, 8*8(a1)   /* s8                                             */
782         sd      zero, 9*8(a1)   /* fs0                                            */
783         sd      zero,10*8(a1)   /* fs1                                            */
784         sd      zero,11*8(a1)   /* fs2                                            */
785         sd      zero,12*8(a1)   /* fs3                                            */
786         sd      a0, 13*8(a1)
787         move    v0,a1
788         j       ra              /* return                                         */
789
790         .end    asm_initialize_thread_stack
791
792
793 /******************* function asm_perform_threadswitch *************************
794 *                                                                              *
795 *   void asm_perform_threadswitch (u1 **from, u1 **to, u1 **stackTop);         *
796 *                                                                              *
797 *   performs a threadswitch                                                    *
798 *                                                                              *
799 *******************************************************************************/
800
801         .ent    asm_perform_threadswitch
802
803 asm_perform_threadswitch:
804         aaddiu  sp,sp,-14*8     /* allocate new stack                             */
805         sd      s0,  0*8(sp)    /* save saved registers of old thread             */
806         sd      s1,  1*8(sp)
807         sd      s2,  2*8(sp)
808         sd      s3,  3*8(sp)
809         sd      s4,  4*8(sp)
810         sd      s5,  5*8(sp)
811         sd      s6,  6*8(sp)
812         sd      s7,  7*8(sp)
813         sd      s8,  8*8(sp)
814         sdc1    fs0, 9*8(sp)
815         sdc1    fs1,10*8(sp)
816         sdc1    fs2,11*8(sp)
817         sdc1    fs3,12*8(sp)
818         sd      ra, 13*8(sp)
819         ast     sp,0(a0)        /* save old stack pointer                         */
820         ast     sp,0(a2)        /* stackTop = old stack pointer                   */
821         ald     sp,0(a1)        /* load new stack pointer                         */
822         ld      s0,  0*8(sp)    /* load saved registers of new thread             */
823         ld      s1,  1*8(sp)
824         ld      s2,  2*8(sp)
825         ld      s3,  3*8(sp)
826         ld      s4,  4*8(sp)
827         ld      s5,  5*8(sp)
828         ld      s6,  6*8(sp)
829         ld      s7,  7*8(sp)
830         ld      s8,  8*8(sp)
831         ldc1    fs0, 9*8(sp)
832         ldc1    fs1,10*8(sp)
833         ldc1    fs2,11*8(sp)
834         ldc1    fs3,12*8(sp)
835         ld      ra, 13*8(sp)
836         aaddiu  sp,sp,14*8      /* deallocate new stack                           */
837         move    itmp3, ra
838         j       ra              /* return                                         */
839
840         .end    asm_perform_threadswitch
841
842
843 /********************* function asm_switchstackandcall *************************
844 *                                                                              *
845 *  void asm_switchstackandcall (void *stack, void *func, void **stacktopsave); *
846 *                                                                              *
847 *   Switches to a new stack, calls a function and switches back.               *
848 *       a0      new stack pointer                                              *
849 *       a1      function pointer                                               *
850 *               a2              pointer to variable where stack top should be stored           *
851 *                                                                              *
852 *******************************************************************************/
853
854         .ent    asm_switchstackandcall
855
856 asm_switchstackandcall:
857         aaddiu  a0,a0,-16       /* allocate new stack                             */
858         sd      ra,0(a0)        /* save return address on new stack               */
859         sd      sp,8(a0)        /* save old stack pointer on new stack            */
860         sd      sp,0(a2)        /* save old stack pointer to variable             */
861         move    sp,a0           /* switch to new stack                            */
862         
863         move    itmp3,a1
864         move    a0,a3
865         jalr    itmp3           /* and call function                              */
866
867         ld      ra,0(sp)        /* load return address                            */
868         ld      sp,8(sp)        /* switch to old stack                            */
869
870         j       ra              /* return                                         */
871
872         .end    asm_switchstackandcall
873
874
875         .ent    asm_getclassvalues_atomic
876
877 asm_getclassvalues_atomic:
878 _crit_restart2:
879 _crit_begin2:
880         lw      t0,offbaseval(a0)
881         lw      t1,offdiffval(a0)
882         lw      t2,offbaseval(a1)
883 _crit_end2:
884         sw      t0,offcast_super_baseval(a2)
885         sw      t1,offcast_super_diffval(a2)
886         sw      t2,offcast_sub_baseval(a2)
887         j       ra
888
889         .end    asm_getclassvalues_atomic
890
891     .data
892
893 asm_criticalsections:
894 #if defined(USE_THREADS) && defined(NATIVE_THREADS)
895     .dword  _crit_begin1
896     .dword  _crit_end1
897     .dword  _crit_restart1
898     .dword  _crit_begin2
899     .dword  _crit_end2
900     .dword  _crit_restart2
901 #endif
902     .dword  0
903
904
905         .text
906
907         .ent    compare_and_swap
908
909 compare_and_swap:
910 1:
911         all     v0,0(a0)
912         bne     v0,a1,2f
913         move    t0,a2
914         asc     t0,0(a0)
915         beqz    t0,1b
916 2:
917         sync
918         j       ra
919
920         .end    compare_and_swap
921
922
923 /*
924  * These are local overrides for various environment variables in Emacs.
925  * Please do not remove this and leave it at the end of the file, where
926  * Emacs will automagically detect them.
927  * ---------------------------------------------------------------------
928  * Local variables:
929  * mode: asm
930  * indent-tabs-mode: t
931  * c-basic-offset: 4
932  * tab-width: 4
933  * End:
934  */