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