* src/vm/exceptions.c (exceptions_handle_exception): Check for special
[cacao.git] / src / vm / jit / mips / asmpart.S
1 /* src/vm/jit/mips/asmpart.S - Java-C interface functions for MIPS
2
3    Copyright (C) 1996-2005, 2006 R. Grafl, A. Krall, C. Kruegel,
4    C. Oates, R. Obermaisser, M. Platter, M. Probst, S. Ring,
5    E. Steiner, C. Thalinger, D. Thuernbeck, P. Tomsich, C. Ullrich,
6    J. Wenninger, Institut f. Computersprachen - TU Wien
7
8    This file is part of CACAO.
9
10    This program is free software; you can redistribute it and/or
11    modify it under the terms of the GNU General Public License as
12    published by the Free Software Foundation; either version 2, or (at
13    your option) any later version.
14
15    This program is distributed in the hope that it will be useful, but
16    WITHOUT ANY WARRANTY; without even the implied warranty of
17    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
18    General Public License for more details.
19
20    You should have received a copy of the GNU General Public License
21    along with this program; if not, write to the Free Software
22    Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
23    02110-1301, USA.
24
25    Contact: cacao@cacaojvm.org
26
27    Authors: Andreas Krall
28
29    Changes: Christian Thalinger
30             Edwin Steiner
31
32    $Id: asmpart.S 4707 2006-03-30 09:52:49Z twisti $
33
34 */
35
36
37 #include "config.h"
38
39 #include "vm/jit/mips/md-abi.h"
40 #include "vm/jit/mips/md-asm.h"
41 #include "vm/jit/mips/offsets.h"
42
43 #include "vm/jit/abi.h"
44 #include "vm/jit/methodheader.h"
45
46
47         .text
48         .set    noat
49
50
51 /* export functions ***********************************************************/
52
53         .globl asm_vm_call_method
54         .globl asm_vm_call_method_int
55         .globl asm_vm_call_method_long
56         .globl asm_vm_call_method_float
57         .globl asm_vm_call_method_double
58         .globl asm_vm_call_method_exception_handler
59
60         .globl asm_call_jit_compiler
61         .globl asm_handle_exception
62         .globl asm_handle_nat_exception
63
64         .globl asm_wrapper_patcher
65
66         .globl asm_replacement_out
67         .globl asm_replacement_in
68
69         .globl asm_perform_threadswitch
70         .globl asm_initialize_thread_stack
71         .globl asm_switchstackandcall
72         .globl asm_getclassvalues_atomic
73         .globl asm_criticalsections
74
75         .globl compare_and_swap
76
77
78 /********************* function asm_calljavafunction ***************************
79 *                                                                              *
80 *   This function calls a Java-method (which possibly needs compilation)       *
81 *   with up to 4 address parameters.                                           *
82 *                                                                              *
83 *   This functions calls the JIT-compiler which eventually translates the      *
84 *   method into machine code.                                                  *
85 *                                                                              *
86 *   A possibly throwed exception will be returned to the caller as function    *
87 *   return value, so the java method cannot return a fucntion value (this      *
88 *   function usually calls 'main' and '<clinit>' which do not return a         *
89 *   function value).                                                           *
90 *                                                                              *
91 *   C-prototype:                                                               *
92 *    javaobject_header *asm_calljavafunction (methodinfo *m,                   *
93 *         void *arg1, void *arg2, void *arg3, void *arg4);                     *
94 *                                                                              *
95 *******************************************************************************/
96
97         .ent    asm_vm_call_method
98
99         .align  3
100
101         .dword  0                           /* catch type all                     */
102         .dword  0                           /* handler pc                         */
103         .dword  0                           /* end pc                             */
104         .dword  0                           /* start pc                           */
105         .word   1                           /* extable size                       */
106         .word   0                           /* 4-byte ALIGNMENT PADDING           */
107         .dword  0                           /* line number table start            */
108         .dword  0                           /* line number table size             */
109         .word   0                           /* 4-byte ALIGNMENT PADDING           */
110         .word   0                           /* fltsave                            */
111         .word   0                           /* intsave                            */
112         .word   0                           /* isleaf                             */
113         .word   0                           /* IsSync                             */
114         .word   0                           /* frame size                         */
115         .dword  0                           /* method pointer (pointer to name)   */
116
117 asm_vm_call_method:
118 asm_vm_call_method_int:
119 asm_vm_call_method_long:
120 asm_vm_call_method_float:
121 asm_vm_call_method_double:
122         .set    noreorder                 /* XXX we need to recompute pv          */
123
124         aaddiu  sp,sp,-12*8               /* allocate stack space (only 11 needed)*/
125         ast     ra,0(sp)                  /* save return address                  */
126
127         bal     L_asm_vm_call_method_compute_pv
128         ast     pv,1*8(sp)                /* procedure vector                     */
129 L_asm_vm_call_method_compute_pv:
130         aaddiu  pv,ra,-4*4
131         ast     s7,3*8(sp)
132
133         sdc1    fss0,5*8(sp)              /* save non JavaABI saved flt registers */
134         sdc1    fss1,6*8(sp)
135         sdc1    fss2,7*8(sp)
136         sdc1    fss3,8*8(sp)
137         sdc1    fss4,9*8(sp)
138         sdc1    fss5,10*8(sp)
139
140         ast     a0,4*8(sp)                /* save method pointer for compiler     */
141
142         move    t0,a2
143         move    s7,a1
144         blez    s7,calljava_argsloaded
145         nop
146
147         ald     a0,offvmargdata(t0)
148         ldc1    fa0,offvmargdata(t0)
149         daddi   s7,s7,-1
150         blez    s7,calljava_argsloaded
151         nop
152
153         ald     a1,offvmargdata+sizevmarg*1(t0)
154         ldc1    fa1,offvmargdata+sizevmarg*1(t0)
155         daddi   s7,s7,-1
156         blez    s7,calljava_argsloaded
157         nop
158
159         ald     a2,offvmargdata+sizevmarg*2(t0)
160         ldc1    fa2,offvmargdata+sizevmarg*2(t0)
161         daddi   s7,s7,-1
162         blez    s7,calljava_argsloaded
163         nop
164
165         ald     a3,offvmargdata+sizevmarg*3(t0)
166         ldc1    fa3,offvmargdata+sizevmarg*3(t0)
167         daddi   s7,s7,-1
168         blez    s7,calljava_argsloaded
169         nop
170
171         ald     a4,offvmargdata+sizevmarg*4(t0)
172         ldc1    fa4,offvmargdata+sizevmarg*4(t0)
173         daddi   s7,s7,-1
174         blez    s7,calljava_argsloaded
175         nop
176
177         ald     a5,offvmargdata+sizevmarg*5(t0)
178         ldc1    fa5,offvmargdata+sizevmarg*5(t0)
179         daddi   s7,s7,-1
180         blez    s7,calljava_argsloaded
181         nop
182
183         ald     a6,offvmargdata+sizevmarg*6(t0)
184         ldc1    fa6,offvmargdata+sizevmarg*6(t0)
185         daddi   s7,s7,-1
186         blez    s7,calljava_argsloaded
187         nop
188
189         ald     a7,offvmargdata+sizevmarg*7(t0)
190         ldc1    fa7,offvmargdata+sizevmarg*7(t0)
191         daddi   s7,s7,-1
192                 
193 calljava_argsloaded:
194         move    t8,sp                      /* save stack pointer                  */
195         blez    s7,calljava_nocopy
196         nop
197         subu    t1,zero,s7
198         sll     t2,t1,3
199         aaddu   sp,sp,t2
200         aaddu   t2,t2,t8
201
202 calljava_copyloop:
203     ald     t3,offvmargdata+sizevmarg*8(t0)
204         ast     t3,0(t2)
205         ala     t1,1(t1)
206         ala     t0,sizevmarg(t0)
207         ala     t2,8(t2)
208         bnez    t1,calljava_copyloop
209         nop
210
211 calljava_nocopy:
212         ald     itmp1,4*8(t8)             /* pass method pointer via itmp1        */
213
214         ala     mptr,asm_call_jit_compiler/* fake virtual function call (2 instr) */
215         ast     mptr,2*8(t8)              /* store function address               */
216         ala     mptr,1*8(t8)              /* set method pointer                   */
217
218         ald     pv,1*8(mptr)              /* method call as in Java               */
219         jalr    pv                        /* call JIT compiler                    */
220         nop
221 L_asm_vm_call_method_recompute_pv:
222 /*      aaddiu  pv,ra,(asm_vm_call_method - L_asm_vm_call_method_recompute_pv)*/
223         aaddiu  pv,ra,-76*4               /* recompute procedure vector           */
224
225         .set    reorder                   /* XXX we need to recompute pv          */
226
227 calljava_return2:
228         ald     ra,0(sp)                  /* restore return address               */
229         ald     pv,8(sp)                  /* restore procedure vector             */
230         ald     s7,3*8(sp)
231
232         ldc1    fss0,5*8(sp)              /* restore non JavaABI saved flt regs   */
233         ldc1    fss1,6*8(sp)
234         ldc1    fss2,7*8(sp)
235         ldc1    fss3,8*8(sp)
236         ldc1    fss4,9*8(sp)
237         ldc1    fss5,10*8(sp)
238
239         aaddiu  sp,sp,12*8                /* free stack space                     */
240         j       ra                        /* return                               */
241
242 asm_vm_call_method_exception_handler:
243         asll    s7,s7,3
244         aaddu   sp,s7,sp
245 #if !defined(NDEBUG)
246         move    a0,itmp1                  
247         jal     builtin_throw_exception
248 #endif
249         move    v0,zero                   /* clear return value for exception     */
250         b       calljava_return2
251
252         .end    asm_vm_call_method
253
254
255 /****************** function asm_call_jit_compiler *****************************
256 *                                                                              *
257 *   invokes the compiler for untranslated JavaVM methods.                      *
258 *                                                                              *
259 *   Register REG_ITEMP1 contains a pointer to the method info structure        *
260 *   (prepared by createcompilerstub). Using the return address in R31 and the  *
261 *   offset in the LDA instruction or using the value in methodptr R25 the      *
262 *   patching address for storing the method address can be computed:           *
263 *                                                                              *
264 *   method address was either loaded using                                     *
265 *   M_ALD (REG_PV, REG_PV, a)        ; invokestatic/special    ($28)           *
266 *   M_JSR (REG_RA, REG_PV);                                                    *
267 *   M_NOP                                                                      *
268 *   M_LDA (REG_PV, REG_RA, val)                                                *
269 *   or                                                                         *
270 *   M_ALD (REG_PV, REG_METHODPTR, m) ; invokevirtual/interface ($25)           *
271 *   M_JSR (REG_RA, REG_PV);                                                    *
272 *   M_NOP                                                                      *
273 *   in the static case the method pointer can be computed using the            *
274 *   return address and the lda function following the jmp instruction          *
275 *                                                                              *
276 *******************************************************************************/
277
278
279         .ent    asm_call_jit_compiler
280
281 asm_call_jit_compiler:
282         aaddiu  sp,sp,-(20*8+sizestackframeinfo) /* allocate stack space          */
283
284         SAVE_ARGUMENT_REGISTERS(0)
285
286         ast     mptr,16*8(sp)         /* save method pointer                      */
287         ast     ra,17*8(sp)           /* save return address                      */
288         ast     itmp1,18*8(sp)        /* save methodinfo pointer                  */
289
290         aaddiu  a0,sp,20*8            /* create stackframe info                   */
291         move    a1,zero               /* we don't have pv handy                   */
292         aaddiu  a2,sp,(20*8+sizestackframeinfo) /* pass java sp                   */
293         ald     a3,17*8(sp)           /* pass java ra                             */
294         move    a4,a3                 /* xpc is equal to ra                       */
295         jal     stacktrace_create_extern_stackframeinfo
296
297         ald     a0,18*8(sp)           /* pass methodinfo pointer                  */
298         jal     jit_compile           /* jit compiler                             */
299         ast     v0,18*8(sp)           /* save return value                        */
300
301         aaddiu  a0,sp,20*8            /* remove stackframe info                   */
302         jal     stacktrace_remove_stackframeinfo
303
304         ald     a0,17*8(sp)           /* pass return address                      */
305         aaddiu  a1,sp,20*8            /* pass stackframeinfo (for PV)             */
306         ald     a2,16*8(sp)           /* pass method pointer                      */
307         jal     md_assembler_get_patch_address /* get address of patch position   */
308         move    t0,v0                 /* move offset to t0 for later use          */
309
310         RESTORE_ARGUMENT_REGISTERS(0)
311
312         ald     ra,17*8(sp)           /* restore return address                   */
313         ald     v0,18*8(sp)           /* restore return value                     */
314         aaddiu  sp,sp,20*8+sizestackframeinfo /* deallocate stack area            */
315
316         beqz    v0,L_asm_call_jit_compiler_exception
317
318         ast     v0,0(t0)              /* store new method address                 */
319         move    pv,v0                 /* move method address into pv              */
320         jr      pv                    /* and call method. The method returns      */
321                                       /* directly to the caller (ra).             */
322
323 L_asm_call_jit_compiler_exception:
324 #if defined(USE_THREADS) && defined(NATIVE_THREADS)
325         aaddiu  sp,sp,-2*8
326         ast     ra,0*8(sp)
327         jal     builtin_asm_get_exceptionptrptr
328         ald     ra,0*8(sp)
329         aaddiu  sp,sp,2*8
330 #else
331         la      v0,_exceptionptr
332 #endif
333         ald     xptr,0(v0)            /* get the exception pointer                */
334         ast     zero,0(v0)            /* clear the exception pointer              */
335
336         aaddiu  xpc,ra,-4             /* faulting address is return adress - 4    */
337         b       asm_handle_nat_exception
338
339         .end    asm_call_jit_compiler
340
341
342 /* asm_handle_exception ********************************************************
343
344    This function handles an exception. It does not use the usual calling
345    conventions. The exception pointer is passed in REG_ITMP1 and the
346    pc from the exception raising position is passed in REG_ITMP2. It searches
347    the local exception table for a handler. If no one is found, it unwinds
348    stacks and continues searching the callers.
349
350 *******************************************************************************/
351
352         .ent    asm_handle_nat_exception
353
354 asm_handle_nat_exception:
355 L_asm_handle_exception_stack_loop:
356         aaddiu  sp,sp,-6*8                  /* allocate stack                     */
357         ast     xptr,0*8(sp)                /* save exception pointer             */
358         ast     xpc,1*8(sp)                 /* save exception pc                  */
359         ast     ra,3*8(sp)                  /* save return address                */
360         ast     zero,4*8(sp)                /* save maybe-leaf flag (cleared)     */
361
362         move    a0,ra                       /* pass return address                */
363         jal     md_codegen_findmethod       /* get PV from RA                     */
364         ast     v0,2*8(sp)                  /* save data segment pointer          */
365
366         ald     a0,0*8(sp)                  /* pass exception pointer             */
367         ald     a1,1*8(sp)                  /* pass exception pc                  */
368         move    a2,v0                       /* pass data segment pointer          */
369         aaddiu  a3,sp,6*8                   /* pass Java stack pointer            */
370
371         b       L_asm_handle_exception_continue
372
373         .aent    asm_handle_exception
374
375 asm_handle_exception:
376         aaddiu  sp,sp,-(ARG_CNT+TMP_CNT)*8  /* create maybe-leaf stackframe       */
377
378         SAVE_ARGUMENT_REGISTERS(0)          /* we save arg and temp registers in  */
379         SAVE_TEMPORARY_REGISTERS(ARG_CNT)   /* case this is a leaf method         */
380
381         aaddiu  sp,sp,-6*8                  /* allocate stack                     */
382         ast     xptr,0*8(sp)                /* save exception pointer             */
383         ast     xpc,1*8(sp)                 /* save exception pc                  */
384         ast     pv,2*8(sp)                  /* save data segment pointer          */
385         ast     ra,3*8(sp)                  /* save return address                */
386         addu    t0,zero,1                   /* set maybe-leaf flag                */
387         ast     t0,4*8(sp)                  /* save maybe-leaf flag               */
388
389         move    a0,xptr                     /* pass exception pointer             */
390         move    a1,xpc                      /* pass exception pc                  */
391         move    a2,pv                       /* pass data segment pointer          */
392         aaddiu  a3,sp,(ARG_CNT+TMP_CNT+6)*8 /* pass Java stack pointer            */
393
394 L_asm_handle_exception_continue:
395         jal     exceptions_handle_exception
396         
397         beqz    v0,L_asm_handle_exception_not_catched
398
399         move    xpc,v0                      /* move handlerpc into xpc            */
400         ald     xptr,0*8(sp)                /* restore exception pointer          */
401         ald     pv,2*8(sp)                  /* restore data segment pointer       */
402         ald     ra,3*8(sp)                  /* restore return address             */
403         ald     t0,4*8(sp)                  /* get maybe-leaf flag                */
404         aaddiu  sp,sp,6*8                   /* free stackframe                    */
405         
406         beqz    t0,L_asm_handle_exception_no_leaf
407
408         RESTORE_ARGUMENT_REGISTERS(0)       /* if this is a leaf method, we have  */
409         RESTORE_TEMPORARY_REGISTERS(ARG_CNT)/* to restore arg and temp registers  */
410         
411         aaddiu  sp,sp,(ARG_CNT+TMP_CNT)*8   /* remove maybe-leaf stackframe       */
412
413 L_asm_handle_exception_no_leaf:
414         jr      xpc                         /* jump to the handler                */
415
416 L_asm_handle_exception_not_catched:
417         ald     xptr,0*8(sp)                /* restore exception pointer          */
418         ald     pv,2*8(sp)                  /* restore data segment pointer       */
419         ald     ra,3*8(sp)                  /* restore return address             */
420         ald     t0,4*8(sp)                  /* get maybe-leaf flag                */
421         aaddiu  sp,sp,6*8                   /* free stackframe                    */
422         
423         beqz    t0,L_asm_handle_exception_no_leaf_stack
424
425         aaddiu  sp,sp,(ARG_CNT+TMP_CNT)*8   /* remove maybe-leaf stackframe       */
426         move    t0,zero                     /* clear the maybe-leaf flag          */
427
428 L_asm_handle_exception_no_leaf_stack:
429         lw      t1,FrameSize(pv)            /* get frame size                     */
430         aaddu   t1,sp,t1                    /* pointer to save area               */
431
432         lw      t2,IsLeaf(pv)               /* is leaf procedure                  */
433         bnez    t2,L_asm_handle_exception_no_ra_restore
434
435         ald     ra,-1*8(t1)                 /* restore ra                         */
436         aaddiu  t1,t1,-8                    /* t1--                               */
437
438 L_asm_handle_exception_no_ra_restore:
439         move    xpc,ra                      /* the new xpc is ra                  */
440         lw      t2,IntSave(pv)              /* t1 = saved int register count      */
441         ala     t3,ex_int2                  /* t3 = current pc                    */
442         sll     t2,t2,2                     /* t2 = register count * 4            */
443         asubu   t3,t3,t2                    /* t3 = IntSave - 4 * register count  */
444         jr      t3                          /* jump to save position              */
445
446         ald     s0,-8*8(t1)
447         ald     s1,-7*8(t1)
448         ald     s2,-6*8(t1)
449         ald     s3,-5*8(t1)
450         ald     s4,-4*8(t1)
451         ald     s5,-3*8(t1)
452         ald     s6,-2*8(t1)
453         ald     s7,-1*8(t1)
454 ex_int2:
455         sll     t2,t2,1               /* t2 = register count * 4 * 2              */
456         asubu   t1,t1,t2              /* t1 = t0 - 8 * register count             */
457
458         lw      t2,FltSave(pv)        /* t2 = saved flt register count            */
459         ala     t3,ex_flt2            /* t3 = current pc                          */
460         sll     t2,t2,2               /* t2 = register count * 4                  */
461         asubu   t3,t3,t2              /* t3 = ex_int_sav - 4 * register count     */
462         jr      t3                          /* jump to save position              */
463
464         ldc1    fs0,-4*8(t1)
465         ldc1    fs1,-3*8(t1)
466         ldc1    fs2,-2*8(t1)
467         ldc1    fs3,-1*8(t1)
468
469 ex_flt2:
470         lw      t1,FrameSize(pv)            /* get frame size                     */
471         aaddu   sp,sp,t1                    /* unwind stack                       */
472         b       L_asm_handle_exception_stack_loop
473
474         .end    asm_handle_nat_exception
475
476
477 /* asm_wrapper_patcher *********************************************************
478
479    XXX
480
481    Stack layout:
482      40   return address into JIT code (patch position)
483      32   pointer to virtual java_objectheader
484      24   machine code (which is patched back later)
485      16   unresolved class/method/field reference
486       8   data segment displacement from load instructions
487       0   patcher function pointer to call
488
489 *******************************************************************************/
490                 
491     .ent    asm_wrapper_patcher
492
493 asm_wrapper_patcher:
494         aaddiu  sp,sp,-((2+16+22+4)*8+sizestackframeinfo) /* create stack frame   */
495
496         SAVE_RETURN_REGISTERS(0)      /* save 1 int/1 float return registers      */
497         SAVE_ARGUMENT_REGISTERS(2)    /* save 8 int/8 float argument registers    */
498         SAVE_TEMPORARY_REGISTERS(18)  /* save 5 int/16 float temporary registers  */
499
500         ast     itmp1,(2+16+22+0)*8(sp) /* save itmp1                             */
501         ast     itmp2,(2+16+22+1)*8(sp) /* save itmp2                             */
502         ast     ra,(2+16+22+2)*8(sp)  /* save method return address (for leafs)   */
503         ast     pv,(2+16+22+3)*8(sp)  /* save pv of calling java function         */
504
505         aaddiu  a0,sp,(2+16+22+4)*8   /* create stackframe info                   */
506         move    a1,pv                 /* pass java pv                             */
507         aaddiu  a2,sp,((6+2+16+22+4)*8+sizestackframeinfo) /* pass java sp        */
508         move    a3,ra                 /* this is correct for leafs                */
509         ald     a4,((5+2+16+22+4)*8+sizestackframeinfo)(sp) /* pass xpc           */
510         jal     stacktrace_create_extern_stackframeinfo
511
512         aaddiu  a0,sp,((0+2+16+22+4)*8+sizestackframeinfo) /* pass sp             */
513         ald     itmp3,((0+2+16+22+4)*8+sizestackframeinfo)(sp) /* get function    */
514         ald     itmp1,(2+16+22+3)*8(sp) /* save pv to the position of fp          */
515         ast     itmp1,((0+2+16+22+4)*8+sizestackframeinfo)(sp)
516         jalr    itmp3
517         ast     v0,((0+2+16+22+4)*8+sizestackframeinfo)(sp) /* save return value  */
518
519         aaddiu  a0,sp,(2+16+22+4)*8   /* remove stackframe info                   */
520         jal     stacktrace_remove_stackframeinfo
521
522         RESTORE_RETURN_REGISTERS(0)   /* restore 1 int/1 float return registers   */
523         RESTORE_ARGUMENT_REGISTERS(2) /* restore 8 int/8 float argument registers */
524         RESTORE_TEMPORARY_REGISTERS(18) /* restore 5 int/16 float temporary reg.  */
525
526         ald     itmp1,(2+16+22+0)*8(sp) /* restore itmp1                          */
527         ald     itmp2,(2+16+22+1)*8(sp) /* restore itmp2                          */
528         ald     ra,(2+16+22+2)*8(sp)  /* restore method return address (for leafs)*/
529         ald     pv,(2+16+22+3)*8(sp)  /* restore pv of calling java function      */
530
531         ald     itmp3,((0+2+16+22+4)*8+sizestackframeinfo)(sp) /* get return value*/
532         beqz    itmp3,L_asm_wrapper_patcher_exception
533
534         ald     itmp3,((5+2+16+22+4)*8+sizestackframeinfo)(sp) /* get RA to JIT   */
535         aaddiu  sp,sp,((6+2+16+22+4)*8+sizestackframeinfo) /* remove stack frame  */
536
537         jr      itmp3                 /* jump to new patched code                 */
538
539 L_asm_wrapper_patcher_exception:
540         ald     xpc,((5+2+16+22+4)*8+sizestackframeinfo)(sp) /* RA to JIT is xpc  */
541         aaddiu  sp,sp,((6+2+16+22+4)*8+sizestackframeinfo) /* remove stack frame  */
542
543 #if defined(USE_THREADS) && defined(NATIVE_THREADS)
544         daddiu  sp,sp,-4*8
545         sd      xpc,0*8(sp)
546         sd      ra,1*8(sp)
547         sd      pv,2*8(sp)
548         jal     builtin_asm_get_exceptionptrptr
549         ld      xpc,0*8(sp)
550         ld      ra,1*8(sp)
551         ld      pv,2*8(sp)
552         daddiu  sp,sp,4*8
553 #else
554         la      v0,_exceptionptr
555 #endif
556         ld      xptr,0(v0)            /* get the exception pointer                */
557         sd      zero,0(v0)            /* clear the exception pointer              */
558         b       asm_handle_exception
559
560         .end    asm_wrapper_patcher
561
562                 
563 /* asm_replacement_out *********************************************************
564
565    This code is jumped to from the replacement-out stubs that are executed
566    when a thread reaches an activated replacement point.
567
568    The purpose of asm_replacement_out is to read out the parts of the
569    execution state that cannot be accessed from C code, store this state,
570    and then call the C function replace_me.
571
572    Stack layout:
573      16                 start of stack inside method to replace
574       0   rplpoint *    info on the replacement point that was reached
575
576    NOTE: itmp3 has been clobbered by the replacement-out stub!
577
578 *******************************************************************************/
579
580 /* some room to accomodate changes of the stack frame size during replacement */
581         /* XXX we should find a cleaner solution here */
582 #define REPLACEMENT_ROOM  512
583
584 #define REPLACEMENT_STACK_OFFSET ((sizeexecutionstate + REPLACEMENT_ROOM + 0xf) & ~0xf)
585
586         .ent asm_replacement_out
587
588 asm_replacement_out:
589     /* create stack frame */
590         daddiu  sp,sp,-REPLACEMENT_STACK_OFFSET
591
592         /* save registers in execution state */
593         sd      $0 ,( 0*8+offes_intregs)(sp)
594         sd      $1 ,( 1*8+offes_intregs)(sp)
595         sd      $2 ,( 2*8+offes_intregs)(sp)
596         sd      $3 ,( 3*8+offes_intregs)(sp)
597         sd      $4 ,( 4*8+offes_intregs)(sp)
598         sd      $5 ,( 5*8+offes_intregs)(sp)
599         sd      $6 ,( 6*8+offes_intregs)(sp)
600         sd      $7 ,( 7*8+offes_intregs)(sp)
601         sd      $8 ,( 8*8+offes_intregs)(sp)
602         sd      $9 ,( 9*8+offes_intregs)(sp)
603         sd      $10,(10*8+offes_intregs)(sp)
604         sd      $11,(11*8+offes_intregs)(sp)
605         sd      $12,(12*8+offes_intregs)(sp)
606         sd      $13,(13*8+offes_intregs)(sp)
607         sd      $14,(14*8+offes_intregs)(sp)
608         sd      $15,(15*8+offes_intregs)(sp)
609         sd      $16,(16*8+offes_intregs)(sp)
610         sd      $17,(17*8+offes_intregs)(sp)
611         sd      $18,(18*8+offes_intregs)(sp)
612         sd      $19,(19*8+offes_intregs)(sp)
613         sd      $20,(20*8+offes_intregs)(sp)
614         sd      $21,(21*8+offes_intregs)(sp)
615         sd      $22,(22*8+offes_intregs)(sp)
616         sd      $23,(23*8+offes_intregs)(sp)
617         sd      $24,(24*8+offes_intregs)(sp)
618         sd      $25,(25*8+offes_intregs)(sp)
619         sd      $26,(26*8+offes_intregs)(sp)
620         sd      $27,(27*8+offes_intregs)(sp)
621         sd      $28,(28*8+offes_intregs)(sp)
622         sd      $29,(29*8+offes_intregs)(sp)
623         sd      $30,(30*8+offes_intregs)(sp)
624         sd      $31,(31*8+offes_intregs)(sp)
625         
626         sdc1    $f0 ,( 0*8+offes_fltregs)(sp)
627         sdc1    $f1 ,( 1*8+offes_fltregs)(sp)
628         sdc1    $f2 ,( 2*8+offes_fltregs)(sp)
629         sdc1    $f3 ,( 3*8+offes_fltregs)(sp)
630         sdc1    $f4 ,( 4*8+offes_fltregs)(sp)
631         sdc1    $f5 ,( 5*8+offes_fltregs)(sp)
632         sdc1    $f6 ,( 6*8+offes_fltregs)(sp)
633         sdc1    $f7 ,( 7*8+offes_fltregs)(sp)
634         sdc1    $f8 ,( 8*8+offes_fltregs)(sp)
635         sdc1    $f9 ,( 9*8+offes_fltregs)(sp)
636         sdc1    $f10,(10*8+offes_fltregs)(sp)
637         sdc1    $f11,(11*8+offes_fltregs)(sp)
638         sdc1    $f12,(12*8+offes_fltregs)(sp)
639         sdc1    $f13,(13*8+offes_fltregs)(sp)
640         sdc1    $f14,(14*8+offes_fltregs)(sp)
641         sdc1    $f15,(15*8+offes_fltregs)(sp)
642         sdc1    $f16,(16*8+offes_fltregs)(sp)
643         sdc1    $f17,(17*8+offes_fltregs)(sp)
644         sdc1    $f18,(18*8+offes_fltregs)(sp)
645         sdc1    $f19,(19*8+offes_fltregs)(sp)
646         sdc1    $f20,(20*8+offes_fltregs)(sp)
647         sdc1    $f21,(21*8+offes_fltregs)(sp)
648         sdc1    $f22,(22*8+offes_fltregs)(sp)
649         sdc1    $f23,(23*8+offes_fltregs)(sp)
650         sdc1    $f24,(24*8+offes_fltregs)(sp)
651         sdc1    $f25,(25*8+offes_fltregs)(sp)
652         sdc1    $f26,(26*8+offes_fltregs)(sp)
653         sdc1    $f27,(27*8+offes_fltregs)(sp)
654         sdc1    $f28,(28*8+offes_fltregs)(sp)
655         sdc1    $f29,(29*8+offes_fltregs)(sp)
656         sdc1    $f30,(30*8+offes_fltregs)(sp)
657         sdc1    $f31,(31*8+offes_fltregs)(sp)
658         
659         /* calculate sp of method */
660         daddiu  itmp1,sp,(REPLACEMENT_STACK_OFFSET + 2*8)
661         sd      itmp1,(offes_sp)(sp)
662
663         /* store pv */
664         sd      pv,(offes_pv)(sp)
665
666         /* call replace_me */
667         ld      a0,-(2*8)(itmp1)            /* arg0: rplpoint *                   */
668     move    a1,sp                       /* arg1: execution state              */
669     jal     replace_me                  /* call C function replace_me         */
670         jal     abort                       /* NEVER REACHED                      */
671
672         .end asm_replacement_out
673
674 /* asm_replacement_in **********************************************************
675
676    This code writes the given execution state and jumps to the replacement
677    code.
678
679    This function never returns!
680
681    NOTE: itmp3 is not restored!
682
683    C prototype:
684       void asm_replacement_in(executionstate *es);
685
686 *******************************************************************************/
687
688         .ent asm_replacement_in
689         
690 asm_replacement_in:
691         /* a0 == executionstate *es */
692
693         /* set new sp and pv */
694         ld      sp,(offes_sp)(a0)
695         ld      pv,(offes_pv)(a0)
696         
697         /* copy registers from execution state */
698         /* $0 is zero                     */
699         ld      $1 ,( 1*8+offes_intregs)(a0)
700         ld      $2 ,( 2*8+offes_intregs)(a0)
701         ld      $3 ,( 2*8+offes_intregs)(a0)
702         /* a0 is loaded below             */
703         ld      $5 ,( 5*8+offes_intregs)(a0)
704         ld      $6 ,( 6*8+offes_intregs)(a0)
705         ld      $7 ,( 7*8+offes_intregs)(a0)
706         ld      $8 ,( 8*8+offes_intregs)(a0)
707         ld      $9 ,( 9*8+offes_intregs)(a0)
708         ld      $10,(10*8+offes_intregs)(a0)
709         ld      $11,(11*8+offes_intregs)(a0)
710         ld      $12,(12*8+offes_intregs)(a0)
711         ld      $13,(13*8+offes_intregs)(a0)
712         ld      $14,(14*8+offes_intregs)(a0)
713         ld      $15,(15*8+offes_intregs)(a0)
714         ld      $16,(16*8+offes_intregs)(a0)
715         ld      $17,(17*8+offes_intregs)(a0)
716         ld      $18,(18*8+offes_intregs)(a0)
717         ld      $19,(19*8+offes_intregs)(a0)
718         ld      $20,(20*8+offes_intregs)(a0)
719         ld      $21,(21*8+offes_intregs)(a0)
720         ld      $22,(22*8+offes_intregs)(a0)
721         ld      $23,(23*8+offes_intregs)(a0)
722         ld      $24,(24*8+offes_intregs)(a0)
723         ld      $25,(25*8+offes_intregs)(a0)
724         ld      $26,(26*8+offes_intregs)(a0)
725         ld      $27,(27*8+offes_intregs)(a0)
726         ld      $28,(28*8+offes_intregs)(a0)
727         /* $29 is sp                      */
728         /* $30 is pv                      */
729         ld      $31,(31*8+offes_intregs)(a0)
730         
731         ldc1    $f0 ,( 0*8+offes_fltregs)(a0)
732         ldc1    $f1 ,( 1*8+offes_fltregs)(a0)
733         ldc1    $f2 ,( 2*8+offes_fltregs)(a0)
734         ldc1    $f3 ,( 3*8+offes_fltregs)(a0)
735         ldc1    $f4 ,( 4*8+offes_fltregs)(a0)
736         ldc1    $f5 ,( 5*8+offes_fltregs)(a0)
737         ldc1    $f6 ,( 6*8+offes_fltregs)(a0)
738         ldc1    $f7 ,( 7*8+offes_fltregs)(a0)
739         ldc1    $f8 ,( 8*8+offes_fltregs)(a0)
740         ldc1    $f9 ,( 9*8+offes_fltregs)(a0)
741         ldc1    $f10,(10*8+offes_fltregs)(a0)
742         ldc1    $f11,(11*8+offes_fltregs)(a0)
743         ldc1    $f12,(12*8+offes_fltregs)(a0)
744         ldc1    $f13,(13*8+offes_fltregs)(a0)
745         ldc1    $f14,(14*8+offes_fltregs)(a0)
746         ldc1    $f15,(15*8+offes_fltregs)(a0)
747         ldc1    $f16,(16*8+offes_fltregs)(a0)
748         ldc1    $f17,(17*8+offes_fltregs)(a0)
749         ldc1    $f18,(18*8+offes_fltregs)(a0)
750         ldc1    $f19,(19*8+offes_fltregs)(a0)
751         ldc1    $f20,(20*8+offes_fltregs)(a0)
752         ldc1    $f21,(21*8+offes_fltregs)(a0)
753         ldc1    $f22,(22*8+offes_fltregs)(a0)
754         ldc1    $f23,(23*8+offes_fltregs)(a0)
755         ldc1    $f24,(24*8+offes_fltregs)(a0)
756         ldc1    $f25,(25*8+offes_fltregs)(a0)
757         ldc1    $f26,(26*8+offes_fltregs)(a0)
758         ldc1    $f27,(27*8+offes_fltregs)(a0)
759         ldc1    $f28,(28*8+offes_fltregs)(a0)
760         ldc1    $f29,(29*8+offes_fltregs)(a0)
761         ldc1    $f30,(30*8+offes_fltregs)(a0)
762         ldc1    $f31,(31*8+offes_fltregs)(a0)
763
764         /* load new pc */
765
766         ld      itmp3,offes_pc(a0)
767
768         /* load a0 */
769         
770         ld      a0,(4*8+offes_intregs)(a0)
771
772         /* jump to new code */
773
774         jr      itmp3
775
776         .end asm_replacement_in
777
778 /******************* function asm_initialize_thread_stack **********************
779 *                                                                              *
780 *   u1* asm_initialize_thread_stack (void *func, u1 *stack);                   *
781 *                                                                              *
782 *   initialize a thread stack                                                  *
783 *                                                                              *
784 *******************************************************************************/
785
786         .ent    asm_initialize_thread_stack
787
788 asm_initialize_thread_stack:
789         aaddiu  a1,a1,-14*8     /* allocate save area                             */
790         sd      zero, 0*8(a1)   /* s0 initalize thread area                       */
791         sd      zero, 1*8(a1)   /* s1                                             */
792         sd      zero, 2*8(a1)   /* s2                                             */
793         sd      zero, 3*8(a1)   /* s3                                             */
794         sd      zero, 4*8(a1)   /* s4                                             */
795         sd      zero, 5*8(a1)   /* s5                                             */
796         sd      zero, 6*8(a1)   /* s6                                             */
797         sd      zero, 7*8(a1)   /* s7                                             */
798         sd      zero, 8*8(a1)   /* s8                                             */
799         sd      zero, 9*8(a1)   /* fs0                                            */
800         sd      zero,10*8(a1)   /* fs1                                            */
801         sd      zero,11*8(a1)   /* fs2                                            */
802         sd      zero,12*8(a1)   /* fs3                                            */
803         sd      a0, 13*8(a1)
804         move    v0,a1
805         j       ra              /* return                                         */
806
807         .end    asm_initialize_thread_stack
808
809
810 /******************* function asm_perform_threadswitch *************************
811 *                                                                              *
812 *   void asm_perform_threadswitch (u1 **from, u1 **to, u1 **stackTop);         *
813 *                                                                              *
814 *   performs a threadswitch                                                    *
815 *                                                                              *
816 *******************************************************************************/
817
818         .ent    asm_perform_threadswitch
819
820 asm_perform_threadswitch:
821         aaddiu  sp,sp,-14*8     /* allocate new stack                             */
822         sd      s0,  0*8(sp)    /* save saved registers of old thread             */
823         sd      s1,  1*8(sp)
824         sd      s2,  2*8(sp)
825         sd      s3,  3*8(sp)
826         sd      s4,  4*8(sp)
827         sd      s5,  5*8(sp)
828         sd      s6,  6*8(sp)
829         sd      s7,  7*8(sp)
830         sd      s8,  8*8(sp)
831         sdc1    fs0, 9*8(sp)
832         sdc1    fs1,10*8(sp)
833         sdc1    fs2,11*8(sp)
834         sdc1    fs3,12*8(sp)
835         sd      ra, 13*8(sp)
836         ast     sp,0(a0)        /* save old stack pointer                         */
837         ast     sp,0(a2)        /* stackTop = old stack pointer                   */
838         ald     sp,0(a1)        /* load new stack pointer                         */
839         ld      s0,  0*8(sp)    /* load saved registers of new thread             */
840         ld      s1,  1*8(sp)
841         ld      s2,  2*8(sp)
842         ld      s3,  3*8(sp)
843         ld      s4,  4*8(sp)
844         ld      s5,  5*8(sp)
845         ld      s6,  6*8(sp)
846         ld      s7,  7*8(sp)
847         ld      s8,  8*8(sp)
848         ldc1    fs0, 9*8(sp)
849         ldc1    fs1,10*8(sp)
850         ldc1    fs2,11*8(sp)
851         ldc1    fs3,12*8(sp)
852         ld      ra, 13*8(sp)
853         aaddiu  sp,sp,14*8      /* deallocate new stack                           */
854         move    itmp3, ra
855         j       ra              /* return                                         */
856
857         .end    asm_perform_threadswitch
858
859
860 /********************* function asm_switchstackandcall *************************
861 *                                                                              *
862 *  void asm_switchstackandcall (void *stack, void *func, void **stacktopsave); *
863 *                                                                              *
864 *   Switches to a new stack, calls a function and switches back.               *
865 *       a0      new stack pointer                                              *
866 *       a1      function pointer                                               *
867 *               a2              pointer to variable where stack top should be stored           *
868 *                                                                              *
869 *******************************************************************************/
870
871         .ent    asm_switchstackandcall
872
873 asm_switchstackandcall:
874         aaddiu  a0,a0,-16       /* allocate new stack                             */
875         sd      ra,0(a0)        /* save return address on new stack               */
876         sd      sp,8(a0)        /* save old stack pointer on new stack            */
877         sd      sp,0(a2)        /* save old stack pointer to variable             */
878         move    sp,a0           /* switch to new stack                            */
879         
880         move    itmp3,a1
881         move    a0,a3
882         jalr    itmp3           /* and call function                              */
883
884         ld      ra,0(sp)        /* load return address                            */
885         ld      sp,8(sp)        /* switch to old stack                            */
886
887         j       ra              /* return                                         */
888
889         .end    asm_switchstackandcall
890
891
892         .ent    asm_getclassvalues_atomic
893
894 asm_getclassvalues_atomic:
895 _crit_restart:
896 _crit_begin:
897         lw      t0,offbaseval(a0)
898         lw      t1,offdiffval(a0)
899         lw      t2,offbaseval(a1)
900 _crit_end:
901         sw      t0,offcast_super_baseval(a2)
902         sw      t1,offcast_super_diffval(a2)
903         sw      t2,offcast_sub_baseval(a2)
904         j       ra
905
906         .end    asm_getclassvalues_atomic
907
908     .data
909
910 asm_criticalsections:
911 #if defined(USE_THREADS) && defined(NATIVE_THREADS)
912     .dword  _crit_begin
913     .dword  _crit_end
914     .dword  _crit_restart
915 #endif
916     .dword  0
917
918
919         .text
920
921         .ent    compare_and_swap
922
923 compare_and_swap:
924 1:
925         all     v0,0(a0)
926         bne     v0,a1,2f
927         move    t0,a2
928         asc     t0,0(a0)
929         beqz    t0,1b
930 2:
931         sync
932         j       ra
933
934         .end    compare_and_swap
935
936
937 /* Disable exec-stacks, required for Gentoo ***********************************/
938
939 #if defined(__GCC__) && defined(__ELF__)
940         .section .note.GNU-stack,"",@progbits
941 #endif
942
943
944 /*
945  * These are local overrides for various environment variables in Emacs.
946  * Please do not remove this and leave it at the end of the file, where
947  * Emacs will automagically detect them.
948  * ---------------------------------------------------------------------
949  * Local variables:
950  * mode: asm
951  * indent-tabs-mode: t
952  * c-basic-offset: 4
953  * tab-width: 4
954  * End:
955  * vim:noexpandtab:sw=4:ts=4:
956  */