* Again, new and simpler stacktraces
[cacao.git] / src / vm / jit / alpha / asmpart.S
1 /* src/vm/jit/alpha/asmpart.S - Java-C interface functions for alpha
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             Reinhard Grafl
29
30    Changes: Joseph Wenninger
31             Christian Thalinger
32
33    $Id: asmpart.S 2992 2005-07-11 21:52:07Z twisti $
34
35 */
36
37
38 #include "config.h"        
39 #include "vm/jit/alpha/offsets.h"
40 #include "vm/jit/alpha/asmoffsets.h"
41 #include "vm/jit/alpha/md-asm.h"
42
43
44         .text
45         .set    noat
46         .set    noreorder
47
48
49 /********************* exported functions and variables ***********************/
50
51         .globl asm_sync_instruction_cache
52         .globl has_no_x_instr_set
53
54         .globl asm_calljavafunction
55         .globl asm_calljavafunction_int
56
57         .globl asm_calljavafunction2
58         .globl asm_calljavafunction2int
59         .globl asm_calljavafunction2long
60         .globl asm_calljavafunction2float
61         .globl asm_calljavafunction2double
62
63         .globl asm_call_jit_compiler
64         .globl asm_handle_exception
65         .globl asm_handle_nat_exception
66
67         .globl asm_wrapper_patcher
68
69         .globl asm_perform_threadswitch
70         .globl asm_initialize_thread_stack
71         .globl asm_switchstackandcall
72         .globl asm_criticalsections
73         .globl asm_getclassvalues_atomic
74
75
76 /* asm_sync_instruction_cache **************************************************
77
78    XXX
79
80 *******************************************************************************/
81
82         .ent    asm_sync_instruction_cache
83
84 asm_sync_instruction_cache:
85         call_pal PAL_imb              /* synchronize instruction cache            */
86         jmp     zero,(ra)
87
88         .end    asm_sync_instruction_cache
89
90 /*********************** function has_no_x_instr_set ***************************
91 *                                                                              *
92 *   determines if the byte support instruction set (21164a and higher)         *
93 *   is available.                                                              *
94 *                                                                              *
95 *******************************************************************************/
96
97         .ent    has_no_x_instr_set
98 has_no_x_instr_set:
99
100         .long   0x47e03c20                /* amask   1,v0                         */
101         jmp     zero,(ra)                 /* return                               */
102
103         .end    has_no_x_instr_set
104
105
106 /********************* function asm_calljavafunction ***************************
107 *                                                                              *
108 *   This function calls a Java-method (which possibly needs compilation)       *
109 *   with up to 4 address parameters.                                           *
110 *                                                                              *
111 *   This functions calls the JIT-compiler which eventually translates the      *
112 *   method into machine code.                                                  *
113 *                                                                              *
114 *   C-prototype:                                                               *
115 *    javaobject_header *asm_calljavafunction (methodinfo *m,                   *
116 *         void *arg1, void *arg2, void *arg3, void *arg4);                     *
117 *                                                                              *
118 *******************************************************************************/
119
120         .ent    asm_calljavafunction
121
122 call_name:
123         .ascii  "calljavafunction\0\0"
124
125         .align  2 /*3*/
126         .quad   0                         /* catch type all                       */
127         .quad   calljava_xhandler         /* handler pc                           */
128         .quad   calljava_xhandler         /* end pc                               */
129         .quad   asm_calljavafunction      /* start pc                             */
130         .long   1                         /* extable size                         */
131         .long   0                         /* PADDING */
132         .quad   0                         /* line number table start             */
133         .quad   0                         /* line number table size             */
134         .long   0                         /* PADDING */
135         .long   0                         /* fltsave */
136         .long   0                         /* intsave                              */
137         .long   0                         /* isleaf                               */
138         .long   0                         /* IsSync                               */
139         .long   32                        /* frame size                           */
140         .quad   0                         /* method pointer (pointer to name)     */
141
142 asm_calljavafunction:
143 asm_calljavafunction_int:
144         ldgp    gp,0(pv)
145         lda     sp,-32(sp)                /* allocate stack space                 */
146         stq     gp,24(sp)                 /* save global pointer                  */
147         stq     ra,0(sp)                  /* save return address                  */
148
149         stq     a0,16(sp)                 /* save method pointer for compiler     */
150         lda     v0,16(sp)                 /* pass pointer to method pointer via v0*/
151
152         mov     a1,a0                     /* pass the remaining parameters        */
153         mov     a2,a1
154         mov     a3,a2
155         mov     a4,a3
156
157         lda     itmp2,asm_call_jit_compiler/* fake virtual function call (2 instr)*/
158         stq     itmp2,8(sp)               /* store function address               */
159         mov     sp,itmp2                  /* set method pointer                   */
160
161         ldq     pv,8(itmp2)               /* method call as in Java               */
162         jmp     ra,(pv)                   /* call JIT compiler                    */
163 calljava_jit:
164         lda     pv,(asm_calljavafunction - calljava_jit)(ra)
165
166 calljava_return:
167         ldq     ra,0(sp)                  /* restore return address               */
168         ldq     gp,24(sp)                 /* restore global pointer               */
169         lda     sp,32(sp)                 /* free stack space                     */
170
171 calljava_ret:
172         jmp     zero,(ra)
173
174 calljava_xhandler:
175         ldq     gp,24(sp)                 /* restore global pointer               */
176         mov     xptr,a0
177         jsr     ra,builtin_throw_exception
178         ldq     ra,0(sp)                  /* restore return address               */
179         lda     sp,32(sp)                 /* free stack space                     */
180         mov     zero,v0                   /* return NULL                          */
181         jmp     zero,(ra)
182         .end    asm_calljavafunction
183
184
185
186
187         .ent    asm_calljavafunction2
188
189 call_name2:
190         .align  3
191
192         .quad   0                         /* catch type all                       */
193         .quad   calljava_xhandler2        /* handler pc                           */
194         .quad   calljava_xhandler2        /* end pc                               */
195         .quad   asm_calljavafunction2     /* start pc                             */
196         .long   1                         /* extable size                         */
197         .long   0                         /* PADDING                              */
198         .quad   0                         /* line number table start              */
199         .quad   0                         /* line number table size               */
200         .long   0                         /* PADDING                              */
201         .long   0                         /* fltsave                              */
202         .long   1                         /* intsave                              */
203         .long   0                         /* isleaf                               */
204         .long   0                         /* IsSync                               */
205         .long   40                        /* frame size                           */
206         .quad   0                         /* method pointer (pointer to name)     */
207
208 asm_calljavafunction2:
209 asm_calljavafunction2int:
210 asm_calljavafunction2long:
211 asm_calljavafunction2float:
212 asm_calljavafunction2double:
213         ldgp    gp,0(pv)
214         lda     sp,-5*8(sp)               /* allocate stack space                 */
215         stq     ra,0*8(sp)                /* save return address                  */
216         stq     gp,1*8(sp)                /* save global pointer                  */
217         stq     s6,3*8(sp)
218
219         stq     a0,4*8(sp)                /* save method pointer for compiler     */
220         mov     a3,t0                     /* pointer to arg block                 */
221         mov     a1,s6                     /* arg count                            */
222
223         ble     s6,calljava_argsloaded
224         lda     s6,-1(s6)
225         ldq     a0,offjniitem(t0)
226         ldt     $f16,offjniitem(t0)
227         ble     s6,calljava_argsloaded
228
229         lda     s6,-1(s6)
230         ldq     a1,offjniitem+sizejniblock*1(t0)
231         ldt     $f17,offjniitem+sizejniblock*1(t0)
232         ble     s6,calljava_argsloaded
233
234         lda     s6,-1(s6)
235         ldq     a2,offjniitem+sizejniblock*2(t0)
236         ldt     $f18,offjniitem+sizejniblock*2(t0)
237         ble     s6,calljava_argsloaded
238
239         lda     s6,-1(s6)
240         ldq     a3,offjniitem+sizejniblock*3(t0)
241         ldt     $f19,offjniitem+sizejniblock*3(t0)
242         ble     s6,calljava_argsloaded
243
244         lda     s6,-1(s6)
245         ldq     a4,offjniitem+sizejniblock*4(t0)
246         ldt     $f20,offjniitem+sizejniblock*4(t0)
247         ble     s6,calljava_argsloaded
248
249         lda     s6,-1(s6)
250         ldq     a5,offjniitem+sizejniblock*5(t0)
251         ldt     $f21,offjniitem+sizejniblock*5(t0)
252 calljava_argsloaded:
253         mov     sp,t4
254         ble     s6,calljava_nocopy
255         negq    s6,t1
256         s8addq  t1,sp,sp
257         s8addq  t1,t4,t2
258
259 calljava_copyloop:
260         ldq     t3,offjniitem+sizejniblock*6(t0)
261         stq     t3,0(t2)
262         lda     t1,1(t1)
263         lda     t0,sizejniblock(t0)
264         lda     t2,8(t2)
265         bne     t1,calljava_copyloop
266
267 calljava_nocopy:
268         lda     v0,4*8(t4)                /* pass pointer to method pointer via v0*/
269
270         lda     itmp2,asm_call_jit_compiler/* fake virtual function call (2 instr)*/
271         stq     itmp2,16(t4)              /* store function address               */
272         lda     itmp2,8(t4)               /* set method pointer                   */
273
274         ldq     pv,8(itmp2)               /* method call as in Java               */
275         jmp     ra,(pv)                   /* call JIT compiler                    */
276 calljava_jit2:
277         lda     pv,(asm_calljavafunction2 - calljava_jit2)(ra)
278
279         s8addq  s6,sp,sp
280 calljava_return2:
281         ldq     ra,0*8(sp)                /* restore return address               */
282         ldq     gp,1*8(sp)                /* restore global pointer               */
283         ldq     s6,3*8(sp)
284         lda     sp,5*8(sp)                /* free stack space                     */
285
286 calljava_ret2:
287         jmp     zero,(ra)
288
289 calljava_xhandler2:
290         s8addq  s6,sp,sp
291         ldq     gp,1*8(sp)                /* restore global pointer               */
292         mov     itmp1,a0
293         jsr     ra,builtin_throw_exception
294         ldq     ra,0*8(sp)                /* restore return address               */
295         ldq     s6,3*8(sp)
296         lda     sp,5*8(sp)                /* free stack space                     */
297         mov     zero,v0                   /* return NULL                          */
298         jmp     zero,(ra)
299
300         .end    asm_calljavafunction2
301
302
303 /****************** function asm_call_jit_compiler *****************************
304 *                                                                              *
305 *   invokes the compiler for untranslated JavaVM methods.                      *
306 *                                                                              *
307 *   Register R0 contains a pointer to the method info structure (prepared      *
308 *   by createcompilerstub). Using the return address in R26 and the            *
309 *   offset in the LDA instruction or using the value in methodptr R28 the      *
310 *   patching address for storing the method address can be computed:           *
311 *                                                                              *
312 *   method address was either loaded using                                     *
313 *   M_LDQ (REG_PV, REG_PV, a)        ; invokestatic/special    ($27)           *
314 *   M_LDA (REG_PV, REG_RA, low)                                                *
315 *   M_LDAH(REG_PV, REG_RA, high)     ; optional                                *
316 *   or                                                                         *
317 *   M_LDQ (REG_PV, REG_METHODPTR, m) ; invokevirtual/interface ($28)           *
318 *   in the static case the method pointer can be computed using the            *
319 *   return address and the lda function following the jmp instruction          *
320 *                                                                              *
321 *******************************************************************************/
322
323         .ent    asm_call_jit_compiler
324
325 asm_call_jit_compiler:
326         ldgp    gp,0(pv)
327         ldl     t8,-8(ra)             /* load instruction LDQ PV,xxx($yy)         */
328         srl     t8,16,t8              /* shift right register number $yy          */
329         and     t8,31,t8              /* isolate register number                  */
330         subl    t8,28,t8              /* test for REG_METHODPTR                   */
331         beq     t8,noregchange       
332         ldl     t8,0(ra)              /* load instruction LDA PV,xxx(RA)          */
333         sll     t8,48,t8
334         sra     t8,48,t8              /* isolate offset                           */
335         addq    t8,ra,$28             /* compute update address                   */
336         ldl     t8,4(ra)              /* load instruction LDAH PV,xxx(PV)         */
337         srl     t8,16,t8              /* isolate instruction code                 */
338         lda     t8,-0x177b(t8)        /* test for LDAH                            */
339         bne     t8,noregchange       
340         ldl     t8,4(ra)              /* load instruction LDAH PV,xxx(PV)         */
341         sll     t8,16,t8              /* compute high offset                      */
342         addl    t8,0,t8               /* sign extend high offset                  */
343         addq    t8,$28,$28            /* compute update address                   */
344 noregchange:
345         lda     sp,-14*8(sp)          /* reserve stack space                      */
346
347         SAVE_ARGUMENT_REGISTERS(0)    /* save 6 int/6 float argument registers    */
348
349         stq     $28,12*8(sp)          /* save method pointer                      */
350         stq     ra,13*8(sp)           /* save return address                      */
351
352         ldq     a0,0(v0)              /* pass 'methodinfo' pointer to             */
353         jsr     ra,jit_compile        /* jit compiler                             */
354         ldgp    gp,0(ra)
355
356         RESTORE_ARGUMENT_REGISTERS(0) /* restore 6 int/6 float argument registers */
357
358         ldq     $28,12*8(sp)          /* load method pointer                      */
359         ldq     ra,13*8(sp)           /* load return address                      */
360         lda     sp,14*8(sp)           /* deallocate stack area                    */
361
362         beq     v0,L_asm_call_jit_compiler_exception
363
364         ldl     t8,-8(ra)             /* load instruction LDQ PV,xxx($yy)         */
365         sll     t8,48,t8
366         sra     t8,48,t8              /* isolate offset                           */
367
368         addq    t8,$28,t8             /* compute update address via method pointer*/
369         stq     v0,0(t8)              /* save new method address there            */
370
371         call_pal PAL_imb              /* synchronise instruction cache            */
372
373         mov     v0,pv                 /* load method address into pv              */
374         jmp     zero,(pv)             /* and call method. The method returns      */
375                                       /* directly to the caller (ra).             */
376
377 L_asm_call_jit_compiler_exception:
378         subq    sp,1*8,sp
379         stq     ra,0*8(sp)
380
381         mov     zero,a0               /* fill in the correct stacktrace           */
382         lda     a1,1*8(sp)            /* pass sp of parent Java function          */
383         mov     ra,a2                 /* pass ra to parent Java function          */
384         mov     ra,a3                 /* xpc is the same as ra                    */
385         jsr     ra,stacktrace_extern_fillInStackTrace
386         mov     v0,xptr
387
388         ldq     ra,0*8(sp)
389         addq    sp,1*8,sp
390
391         subq    ra,4,xpc
392         br      asm_handle_nat_exception
393
394         .end    asm_call_jit_compiler
395
396
397 /********************* function asm_handle_exception ***************************
398 *                                                                              *
399 *   This function handles an exception. It does not use the usual calling      *
400 *   conventions. The exception pointer is passed in REG_ITMP1 and the          *
401 *   pc from the exception raising position is passed in REG_ITMP2. It searches *
402 *   the local exception table for a handler. If no one is found, it unwinds    *
403 *   stacks and continues searching the callers.                                *
404 *                                                                              *
405 *   void asm_handle_exception (exceptionptr, exceptionpc);                     *
406 *                                                                              *
407 *******************************************************************************/
408
409         .ent    asm_handle_nat_exception
410
411 asm_handle_nat_exception:
412         ldl     t0,0(ra)              /* load instruction LDA PV,xxx(RA)          */
413         sll     t0,48,t0
414         sra     t0,48,t0              /* isolate offset                           */
415         addq    t0,ra,pv              /* compute update address                   */
416         ldl     t0,4(ra)              /* load instruction LDAH PV,xxx(PV)         */
417         srl     t0,16,t0              /* isolate instruction code                 */
418         lda     t0,-0x177b(t0)        /* test for LDAH                            */
419         bne     t0,asm_handle_exception
420         ldl     t0,4(ra)              /* load instruction LDAH PV,xxx(PV)         */
421         sll     t0,16,t0              /* compute high offset                      */
422         addl    t0,0,t0               /* sign extend high offset                  */
423         addq    t0,pv,pv              /* compute update address                   */
424
425         .aent    asm_handle_exception
426
427 asm_handle_exception:
428         lda     sp,-18*8(sp)          /* allocate stack                           */
429         stq     t0,0*8(sp)            /* save possible used registers             */
430         stq     t1,1*8(sp)            /* also registers used by trace_exception   */
431         stq     t2,2*8(sp)
432         stq     t3,3*8(sp)
433         stq     t4,4*8(sp)
434         stq     t5,5*8(sp)
435         stq     t6,6*8(sp)
436         stq     t7,7*8(sp)
437         stq     t8,8*8(sp)
438         stq     t9,9*8(sp)
439         stq     t10,10*8(sp)
440         stq     v0,11*8(sp)
441         stq     a0,12*8(sp)
442         stq     a1,13*8(sp)
443         stq     a2,14*8(sp)
444         stq     a3,15*8(sp)
445         stq     a4,16*8(sp)
446         stq     a5,17*8(sp)
447
448         lda     t3,1(zero)            /* set no unwind flag                       */
449 ex_stack_loop:
450         lda     sp,-5*8(sp)           /* allocate stack                           */
451         stq     xptr,0*8(sp)          /* save used register                       */
452         stq     xpc,1*8(sp)
453         stq     pv,2*8(sp)
454         stq     ra,3*8(sp)
455         stq     t3,4*8(sp)
456
457         mov     xptr,a0
458         ldq     a1,MethodPointer(pv)
459         mov     xpc,a2
460 /*      mov     t3,a3 */
461         lda             a3,0(zero)
462         lda             a4,1(zero)
463         br      ra,ex_trace           /* set ra for gp loading                    */
464 ex_trace:
465         ldgp    gp,0(ra)              /* load gp                                  */
466         jsr     ra,builtin_trace_exception /* trace_exception(xptr,methodptr)     */
467         
468         ldq     xptr,0*8(sp)          /* restore used register                    */
469         ldq     xpc,1*8(sp)
470         ldq     pv,2*8(sp)
471         ldq     ra,3*8(sp)
472         ldq     t3,4*8(sp)
473         lda     sp,5*8(sp)            /* deallocate stack                         */
474         
475         ldl     t0,ExTableSize(pv)    /* t0 = exception table size                */
476         beq     t0,empty_table        /* if empty table skip                      */
477
478         lda     t1,ExTableStart(pv)   /* t1 = start of exception table            */
479
480 ex_table_loop:
481         ldq     t2,ExStartPC(t1)      /* t2 = exception start pc                  */
482         cmple   t2,xpc,t2             /* t2 = (startpc <= xpc)                    */
483         beq     t2,ex_table_cont      /* if (false) continue                      */
484         ldq     t2,ExEndPC(t1)        /* t2 = exception end pc                    */
485         cmplt   xpc,t2,t2             /* t2 = (xpc < endpc)                       */
486         beq     t2,ex_table_cont      /* if (false) continue                      */
487         ldq     a1,ExCatchType(t1)    /* arg1 = exception catch type              */
488         beq     a1,ex_handle_it       /* NULL catches everything                  */
489
490         ldl     itmp3,offclassloaded(a1)
491         bne     itmp3,L_class_loaded
492
493         subq    sp,8*8,sp             /* allocate stack                           */
494         stq     t0,0*8(sp)            /* save used register                       */
495         stq     t1,1*8(sp)
496         stq     t3,2*8(sp)
497         stq     xptr,3*8(sp)
498         stq     xpc,4*8(sp)
499         stq     pv,5*8(sp)
500         stq     ra,6*8(sp)
501         stq     a1,7*8(sp)
502
503         mov     a1,a0
504
505         br      ra,L_class_load_ra    /* set ra for gp loading                    */
506 L_class_load_ra:
507         ldgp    gp,0(ra)              /* load gp                                  */
508         jsr     ra,load_class_bootstrap
509
510         ldq     t0,0*8(sp)            /* restore used register                    */
511         ldq     t1,1*8(sp)
512         ldq     t3,2*8(sp)
513         ldq     xptr,3*8(sp)
514         ldq     xpc,4*8(sp)
515         ldq     pv,5*8(sp)
516         ldq     ra,6*8(sp)
517         ldq     a1,7*8(sp)
518         addq    sp,8*8,sp             /* deallocate stack                         */
519
520 L_class_loaded:
521         ldl     itmp3,offclasslinked(a1)
522         subq    sp,8*8,sp             /* allocate stack                           */
523         stq     a1,7*8(sp)
524         bne     itmp3,L_class_linked
525
526         stq     t0,0*8(sp)            /* save used register                       */
527         stq     t1,1*8(sp)
528         stq     t3,2*8(sp)
529         stq     xptr,3*8(sp)
530         stq     xpc,4*8(sp)
531         stq     pv,5*8(sp)
532         stq     ra,6*8(sp)
533
534         mov     a1,a0
535
536         br      ra,L_class_link_ra    /* set ra for gp loading                    */
537 L_class_link_ra:
538         ldgp    gp,0(ra)              /* load gp                                  */
539         jsr     ra,link_class
540
541         ldq     t0,0*8(sp)            /* restore used register                    */
542         ldq     t1,1*8(sp)
543         ldq     t3,2*8(sp)
544         ldq     xptr,3*8(sp)
545         ldq     xpc,4*8(sp)
546         ldq     pv,5*8(sp)
547         ldq     ra,6*8(sp)
548
549 L_class_linked:
550 _crit_restart1:
551         ldq     a1,7*8(sp)
552 _crit_begin1:
553         ldq     a0,offobjvftbl(xptr)  /* a0 = vftblptr(xptr)                      */
554         ldq     a1,offclassvftbl(a1)  /* a1 = vftblptr(catchtype) class (not obj) */
555         ldl     a0,offbaseval(a0)     /* a0 = baseval(xptr)                       */
556         ldl     v0,offbaseval(a1)     /* a2 = baseval(catchtype)                  */
557         ldl     a1,offdiffval(a1)     /* a1 = diffval(catchtype)                  */
558 _crit_end1:
559         subl    a0,v0,a0              /* a0 = baseval(xptr) - baseval(catchtype)  */
560         cmpule  a0,a1,v0              /* v0 = xptr is instanceof catchtype        */
561         addq    sp,8*8,sp             /* deallocate stack                         */
562         beq     v0,ex_table_cont      /* if (false) continue                      */
563
564 ex_handle_it:
565         ldq     xpc,ExHandlerPC(t1)   /* xpc = exception handler pc               */
566
567         beq     t3,ex_jump            /* if (!(no stack unwinding) skip           */
568
569         ldq     t0,0*8(sp)            /* restore possible used registers          */
570         ldq     t1,1*8(sp)            /* also registers used by trace_exception   */
571         ldq     t2,2*8(sp)
572         ldq     t3,3*8(sp)
573         ldq     t4,4*8(sp)
574         ldq     t5,5*8(sp)
575         ldq     t6,6*8(sp)
576         ldq     t7,7*8(sp)
577         ldq     t8,8*8(sp)
578         ldq     t9,9*8(sp)
579         ldq     t10,10*8(sp)
580         ldq     v0,11*8(sp)
581         ldq     a0,12*8(sp)
582         ldq     a1,13*8(sp)
583         ldq     a2,14*8(sp)
584         ldq     a3,15*8(sp)
585         ldq     a4,16*8(sp)
586         ldq     a5,17*8(sp)
587         lda     sp,18*8(sp)           /* deallocate stack                         */
588
589 ex_jump:
590         jmp     zero,(xpc)            /* jump to the handler                      */
591
592 ex_table_cont:
593         lda     t1,ExEntrySize(t1)    /* next exception table entry               */
594         subl    t0,1,t0               /* decrement entry counter                  */
595         bgt     t0,ex_table_loop      /* if (t0 > 0) next entry                   */
596
597 empty_table:
598         beq     t3,ex_already_cleared /* if here the first time, then             */
599         lda     sp,18*8(sp)           /* deallocate stack and                     */
600         clr     t3                    /* clear the no unwind flag                 */
601 ex_already_cleared:
602         ldl     t0,IsSync(pv)         /* t0 = SyncOffset                          */
603         beq     t0,no_monitor_exit    /* if zero no monitorexit                   */
604
605 #if defined(USE_THREADS)
606         addq    sp,t0,t0              /* add stackptr to Offset                   */
607         ldq     a0,-8(t0)             /* load monitorexit pointer                 */
608
609         lda     sp,-7*8(sp)           /* allocate stack                           */
610         stq     t0,0*8(sp)            /* save used register                       */
611         stq     t1,1*8(sp)
612         stq     t3,2*8(sp)
613         stq     xptr,3*8(sp)
614         stq     xpc,4*8(sp)
615         stq     pv,5*8(sp)
616         stq     ra,6*8(sp)
617
618         br      ra,ex_mon_load        /* set ra for gp loading                    */
619 ex_mon_load:
620         ldgp    gp,0(ra)              /* load gp                                  */
621         jsr     ra,builtin_monitorexit/* builtin_monitorexit(objectptr)           */
622         
623         ldq     t0,0*8(sp)            /* restore used register                    */
624         ldq     t1,1*8(sp)
625         ldq     t3,2*8(sp)
626         ldq     xptr,3*8(sp)
627         ldq     xpc,4*8(sp)
628         ldq     pv,5*8(sp)
629         ldq     ra,6*8(sp)
630         lda     sp,7*8(sp)            /* deallocate stack                         */
631 #endif
632
633 no_monitor_exit:
634         ldl     t0,FrameSize(pv)      /* t0 = frame size                          */
635         addq    sp,t0,sp              /* unwind stack                             */
636         mov     sp,t0                 /* t0 = pointer to save area                */
637         ldl     t1,IsLeaf(pv)         /* t1 = is leaf procedure                   */
638         bne     t1,ex_no_restore      /* if (leaf) skip                           */
639         ldq     ra,-8(t0)             /* restore ra                               */
640         lda     t0,-8(t0)             /* t0--                                     */
641 ex_no_restore:
642         mov     ra,xpc                /* the new xpc is ra                        */
643         ldl     t1,IntSave(pv)        /* t1 = saved int register count            */
644         br      t2,ex_int1            /* t2 = current pc                          */
645 ex_int1:
646         lda     t2,44(t2)             /* lda t2,ex_int2-ex_int1(t2) !!!!!!!!!!!!! */
647         negl    t1,t1                 /* negate register count                    */
648         s4addq  t1,t2,t2              /* t2 = ex_int_sav - 4 * register count     */
649         jmp     zero,(t2)             /* jump to save position                    */
650         ldq     s0,-56(t0)
651         ldq     s1,-48(t0)
652         ldq     s2,-40(t0)
653         ldq     s3,-32(t0)
654         ldq     s4,-24(t0)
655         ldq     s5,-16(t0)
656         ldq     s6,-8(t0)
657 ex_int2:
658         s8addq  t1,t0,t0              /* t0 = t0 - 8 * register count             */
659
660         ldl     t1,FltSave(pv)        /* t1 = saved flt register count            */
661         br      t2,ex_flt1            /* t2 = current pc                          */
662 ex_flt1:
663         lda     t2,48(t2)             /* lda t2,ex_flt2-ex_flt1(t2) !!!!!!!!!!!!! */
664         negl    t1,t1                 /* negate register count                    */
665         s4addq  t1,t2,t2              /* t2 = ex_flt_sav - 4 * register count     */
666         jmp     zero,(t2)             /* jump to save position                    */
667         ldt     fs0,-64(t0)
668         ldt     fs1,-56(t0)
669         ldt     fs2,-48(t0)
670         ldt     fs3,-40(t0)
671         ldt     fs4,-32(t0)
672         ldt     fs5,-24(t0)
673         ldt     fs6,-16(t0)
674         ldt     fs7,-8(t0)
675 ex_flt2:
676         ldl     t0,0(ra)              /* load instruction LDA PV,xxx(RA)          */
677         sll     t0,48,t0
678         sra     t0,48,t0              /* isolate offset                           */
679         addq    t0,ra,pv              /* compute update address                   */
680         ldl     t0,4(ra)              /* load instruction LDAH PV,xxx(PV)         */
681         srl     t0,16,t0              /* isolate instruction code                 */
682         lda     t0,-0x177b(t0)        /* test for LDAH                            */
683         bne     t0,ex_stack_loop       
684         ldl     t0,4(ra)              /* load instruction LDAH PV,xxx(RA)         */
685         sll     t0,16,t0              /* compute high offset                      */
686         addl    t0,0,t0               /* sign extend high offset                  */
687         addq    t0,pv,pv              /* compute update address                   */
688         br      ex_stack_loop
689
690         .end    asm_handle_nat_exception
691
692
693 /* asm_wrapper_patcher *********************************************************
694
695    XXX
696
697    Stack layout:
698          32   return address into JIT code (patch position)
699      24   pointer to virtual java_objectheader
700      16   machine code (which is patched back later)
701       8   unresolved class/method/field reference
702       0   patcher function pointer to call (pv afterwards)
703
704    ATTENTION: itmp3 == gp! But we don't need gp do call the patcher function.
705
706 *******************************************************************************/
707                 
708         .ent    asm_wrapper_patcher
709
710 asm_wrapper_patcher:
711         lda     sp,-((12+27+4)*8+sizestackframeinfo)(sp) /* create stack frame    */
712
713         SAVE_ARGUMENT_REGISTERS(0)    /* save 6 int/6 float argument registers    */
714         SAVE_TEMPORARY_REGISTERS(12)  /* save 11 int/16 float temporary registers */
715
716         stq     itmp1,(12+27+0)*8(sp) /* save itmp1                               */
717         stq     itmp2,(12+27+1)*8(sp) /* save itmp2                               */
718         stq     ra,(12+27+2)*8(sp)    /* save method return address (for leafs)   */
719         stq     pv,(12+27+3)*8(sp)    /* save pv of calling java function         */
720
721         br      ra,L_asm_wrapper_patcher_load_gp
722 L_asm_wrapper_patcher_load_gp:
723         ldgp    gp,0(ra)              /* load gp (it's not set correctly in jit)  */
724
725         lda     a0,(12+27+4)*8(sp)    /* create stackframe info                   */
726         mov     pv,a1                 /* pass java pv                             */
727         lda     a2,((5+12+27+4)*8+sizestackframeinfo)(sp) /* pass java sp         */
728         ldq     a3,(12+27+2)*8(sp)    /* this is correct for leafs                */
729         ldq     a4,((4+12+27+4)*8+sizestackframeinfo)(sp) /* pass xpc             */
730         jsr     ra,stacktrace_create_extern_stackframeinfo
731         ldgp    gp,0(ra)
732
733         lda     a0,((0+12+27+4)*8+sizestackframeinfo)(sp) /* pass sp              */
734         ldq     pv,((0+12+27+4)*8+sizestackframeinfo)(sp) /* get function pointer */
735         ldq     itmp1,(12+27+3)*8(sp) /* save pv to the position of fp            */
736         stq     itmp1,((0+12+27+4)*8+sizestackframeinfo)(sp)
737         jmp     ra,(pv)               /* call the patcher function                */
738         ldgp    gp,0(ra)
739
740         lda     a0,(12+27+4)*8(sp)    /* remove stackframe info                   */
741         jsr     ra,stacktrace_remove_stackframeinfo
742         ldgp    gp,0(ra)
743
744         RESTORE_ARGUMENT_REGISTERS(0) /* restore 6 int/6 float argument registers */
745         RESTORE_TEMPORARY_REGISTERS(12)/* restore 11 integer temporary registers  */
746
747         ldq     itmp1,(12+27+0)*8(sp) /* restore itmp1                            */
748         ldq     itmp2,(12+27+1)*8(sp) /* restore itmp2                            */
749         ldq     ra,(12+27+2)*8(sp)    /* restore method return address (for leafs)*/
750         ldq     pv,(12+27+3)*8(sp)    /* restore pv of calling java function      */
751
752         ldq     itmp3,((4+12+27+4)*8+sizestackframeinfo)(sp)/* get RA to jit code */
753         lda     sp,((5+12+27+4)*8+sizestackframeinfo)(sp)  /* remove stack frame  */
754
755         beq     v0,L_asm_wrapper_patcher_exception
756
757         jmp     zero,(itmp3)          /* jump to new patched code                 */
758
759 L_asm_wrapper_patcher_exception:
760         mov     itmp3,xpc             /* return address into JIT code is xpc      */
761
762         br      itmp1,L_asm_wrapper_patcher_exception_load_gp
763 L_asm_wrapper_patcher_exception_load_gp:
764         ldgp    gp,0(itmp1)           /* itmp3 == gp, load the current gp         */
765
766 #if defined(USE_THREADS) && defined(NATIVE_THREADS)
767         subq    sp,3*8,sp
768         stq     xpc,0*8(sp)           /* save return address (xpc)                */
769         stq     ra,1*8(sp)
770         stq     pv,2*8(sp)
771         jsr     ra,builtin_asm_get_exceptionptrptr
772         ldq     xpc,0*8(sp)           /* restore return address (xpc)             */
773         ldq     ra,1*8(sp)
774         ldq     pv,2*8(sp)
775         addq    sp,3*8,sp
776 #else
777         lda     v0,_exceptionptr
778 #endif
779         ldq     xptr,0(v0)            /* get the exception pointer                */
780         stq     zero,0(v0)            /* clear the exception pointer              */
781         br      asm_handle_exception  /* we have the pv of the calling java func. */
782
783         .end    asm_wrapper_patcher
784
785                 
786 /******************* function asm_initialize_thread_stack **********************
787 *                                                                              *
788 *   initialized a thread stack                                                 *
789 *                                                                              *
790 *******************************************************************************/
791
792         .ent    asm_initialize_thread_stack
793
794 asm_initialize_thread_stack:
795         lda     a1,-128(a1)
796         stq     zero, 0(a1)
797         stq     zero, 8(a1)
798         stq     zero, 16(a1)
799         stq     zero, 24(a1)
800         stq     zero, 32(a1)
801         stq     zero, 40(a1)
802         stq     zero, 48(a1)
803         stt     fzero, 56(a1)
804         stt     fzero, 64(a1)
805         stt     fzero, 72(a1)
806         stt     fzero, 80(a1)
807         stt     fzero, 88(a1)
808         stt     fzero, 96(a1)
809         stt     fzero, 104(a1)
810         stt     fzero, 112(a1)
811         stq     a0, 120(a1)
812         mov     a1, v0
813         jmp     zero,(ra)
814
815         .end    asm_initialize_thread_stack
816
817
818 /******************* function asm_perform_threadswitch *************************
819 *                                                                              *
820 *   void asm_perform_threadswitch (u1 **from, u1 **to, u1 **stackTop);         *
821 *                                                                              *
822 *   performs a threadswitch                                                    *
823 *                                                                              *
824 *******************************************************************************/
825
826         .ent    asm_perform_threadswitch
827
828 asm_perform_threadswitch:
829         subq    sp,128,sp
830         stq     s0, 0(sp)
831         stq     s1, 8(sp)
832         stq     s2, 16(sp)
833         stq     s3, 24(sp)
834         stq     s4, 32(sp)
835         stq     s5, 40(sp)
836         stq     s6, 48(sp)
837         stt     fs0, 56(sp)
838         stt     fs1, 64(sp)
839         stt     fs2, 72(sp)
840         stt     fs3, 80(sp)
841         stt     fs4, 88(sp)
842         stt     fs5, 96(sp)
843         stt     fs6, 104(sp)
844         stt     fs7, 112(sp)
845         stq     ra, 120(sp)
846         stq     sp, 0(a0)
847         stq     sp, 0(a2)
848         ldq     sp, 0(a1)
849         ldq     s0, 0(sp)
850         ldq     s1, 8(sp)
851         ldq     s2, 16(sp)
852         ldq     s3, 24(sp)
853         ldq     s4, 32(sp)
854         ldq     s5, 40(sp)
855         ldq     s6, 48(sp)
856         ldt     fs0, 56(sp)
857         ldt     fs1, 64(sp)
858         ldt     fs2, 72(sp)
859         ldt     fs3, 80(sp)
860         ldt     fs4, 88(sp)
861         ldt     fs5, 96(sp)
862         ldt     fs6, 104(sp)
863         ldt     fs7, 112(sp)
864         ldq     ra, 120(sp)
865         mov     ra, pv
866         addq    sp, 128, sp
867         jmp     zero,(ra)
868
869         .end    asm_perform_threadswitch
870
871
872 /********************* function asm_switchstackandcall *************************
873 *                                                                              *
874 *  void *asm_switchstackandcall (void *stack, void *func, void **stacktopsave, *
875 *                               void *p);                                      *
876 *                                                                              *
877 *   Switches to a new stack, calls a function and switches back.               *
878 *       a0      new stack pointer                                              *
879 *       a1      function pointer                                               *
880 *               a2              pointer to variable where stack top should be stored           *
881 *               a3      pointer to user data, is passed to the function                *
882 *                                                                              *
883 *******************************************************************************/
884
885
886         .ent    asm_switchstackandcall
887
888 asm_switchstackandcall:
889         lda     a0,-2*8(a0)     /* allocate new stack                                 */
890         stq     ra,0(a0)        /* save return address on new stack                   */
891         stq     sp,1*8(a0)      /* save old stack pointer on new stack                */
892         stq sp,0(a2)        /* save old stack pointer to variable                 */
893         mov     a0,sp           /* switch to new stack                                */
894         
895         mov     a1,pv           /* load function pointer                              */
896         mov a3,a0           /* pass pointer */
897         jmp     ra,(pv)         /* and call function                                  */
898
899         ldq     ra,0(sp)        /* load return address                                */
900         ldq     sp,1*8(sp)      /* switch to old stack                                */
901
902         jmp     zero,(ra)       /* return                                             */
903
904         .end    asm_switchstackandcall
905
906         .ent    asm_getclassvalues_atomic
907
908 asm_getclassvalues_atomic:
909 _crit_restart2:
910 _crit_begin2:
911         ldl     t0,offbaseval(a0)
912         ldl     t1,offdiffval(a0)
913         ldl     t2,offbaseval(a1)
914 _crit_end2:
915         stl     t0,offcast_super_baseval(a2)
916         stl     t1,offcast_super_diffval(a2)
917         stl     t2,offcast_sub_baseval(a2)
918         jmp      zero,(ra)
919
920         .end    asm_getclassvalues_atomic
921
922     .data
923
924 asm_criticalsections:
925 #if defined(USE_THREADS) && defined(NATIVE_THREADS)
926     .quad   _crit_begin1
927     .quad   _crit_end1
928     .quad   _crit_restart1
929     .quad   _crit_begin2
930     .quad   _crit_end2
931     .quad   _crit_restart2
932 #endif
933     .quad   0
934
935
936 /*
937  * These are local overrides for various environment variables in Emacs.
938  * Please do not remove this and leave it at the end of the file, where
939  * Emacs will automagically detect them.
940  * ---------------------------------------------------------------------
941  * Local variables:
942  * mode: asm
943  * indent-tabs-mode: t
944  * c-basic-offset: 4
945  * tab-width: 4
946  * End:
947  */