* src/vm/jit/alpha/codegen.c (codegen): Use codeinfo instead of
[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, 2006 R. Grafl, A. Krall, C. Kruegel,
4    C. Oates, R. Obermaisser, M. Platter, M. Probst, S. Ring,
5    E. Steiner, C. Thalinger, D. Thuernbeck, P. Tomsich, C. Ullrich,
6    J. Wenninger, Institut f. Computersprachen - TU Wien
7
8    This file is part of CACAO.
9
10    This program is free software; you can redistribute it and/or
11    modify it under the terms of the GNU General Public License as
12    published by the Free Software Foundation; either version 2, or (at
13    your option) any later version.
14
15    This program is distributed in the hope that it will be useful, but
16    WITHOUT ANY WARRANTY; without even the implied warranty of
17    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
18    General Public License for more details.
19
20    You should have received a copy of the GNU General Public License
21    along with this program; if not, write to the Free Software
22    Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
23    02110-1301, USA.
24
25    Contact: cacao@cacaojvm.org
26
27    Authors: Andreas Krall
28             Reinhard Grafl
29
30    Changes: Joseph Wenninger
31             Christian Thalinger
32                 Edwin Steiner
33
34    $Id: asmpart.S 5042 2006-06-20 11:55:40Z twisti $
35
36 */
37
38
39 #include "config.h"
40
41 #include "vm/jit/alpha/md-abi.h"
42 #include "vm/jit/alpha/md-asm.h"
43 #include "vm/jit/alpha/offsets.h"
44
45 #include "vm/jit/abi-asm.h"
46 #include "vm/jit/methodheader.h"
47
48
49         .text
50         .set    noat
51         .set    noreorder
52
53
54 /* export functions ***********************************************************/
55
56         .globl asm_vm_call_method
57         .globl asm_vm_call_method_int
58         .globl asm_vm_call_method_long
59         .globl asm_vm_call_method_float
60         .globl asm_vm_call_method_double
61         .globl asm_vm_call_method_exception_handler
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_replacement_out
70         .globl asm_replacement_in
71
72         .globl asm_criticalsections
73         .globl asm_getclassvalues_atomic
74
75         .globl asm_md_init
76         .globl asm_cacheflush
77
78
79 /* asm_vm_call_method **********************************************************
80 *                                                                              *
81 *   This function calls a Java-method (which possibly needs compilation)       *
82 *   with up to 4 address parameters.                                           *
83 *                                                                              *
84 *   This functions calls the JIT-compiler which eventually translates the      *
85 *   method into machine code.                                                  *
86 *                                                                              *
87 *   C-prototype:                                                               *
88 *    javaobject_header *asm_calljavafunction (methodinfo *m,                   *
89 *         void *arg1, void *arg2, void *arg3, void *arg4);                     *
90 *                                                                              *
91 *******************************************************************************/
92
93         .ent    asm_vm_call_method
94
95         .align  3
96
97         .quad   0                           /* catch type all                     */
98         .quad   0                           /* handler pc                         */
99         .quad   0                           /* end pc                             */
100         .quad   0                           /* start pc                           */
101         .long   1                           /* extable size                       */
102         .long   0                           /* ALIGNMENT PADDING                  */
103         .quad   0                           /* line number table start            */
104         .quad   0                           /* line number table size             */
105         .long   0                           /* ALIGNMENT PADDING                  */
106         .long   0                           /* fltsave                            */
107         .long   1                           /* intsave                            */
108         .long   0                           /* isleaf                             */
109         .long   0                           /* IsSync                             */
110         .long   0                           /* frame size                         */
111         .quad   0                           /* codeinfo pointer                   */
112
113 asm_vm_call_method:
114 asm_vm_call_method_int:
115 asm_vm_call_method_long:
116 asm_vm_call_method_float:
117 asm_vm_call_method_double:
118         ldgp    gp,0(pv)
119         lda     sp,-5*8(sp)               /* allocate stack space                 */
120         stq     ra,0*8(sp)                /* save return address                  */
121         stq     gp,1*8(sp)                /* save global pointer                  */
122         stq     s6,3*8(sp)
123
124         stq     a0,4*8(sp)                /* save method pointer for compiler     */
125
126         mov     a2,t0                     /* pointer to arg block                 */
127         mov     a1,s6                     /* arg count                            */
128
129         ble     s6,calljava_argsloaded
130         lda     s6,-1(s6)
131         ldq     a0,offvmargdata(t0)
132         ldt     $f16,offvmargdata(t0)
133         ble     s6,calljava_argsloaded
134
135         lda     s6,-1(s6)
136         ldq     a1,offvmargdata+sizevmarg*1(t0)
137         ldt     $f17,offvmargdata+sizevmarg*1(t0)
138         ble     s6,calljava_argsloaded
139
140         lda     s6,-1(s6)
141         ldq     a2,offvmargdata+sizevmarg*2(t0)
142         ldt     $f18,offvmargdata+sizevmarg*2(t0)
143         ble     s6,calljava_argsloaded
144
145         lda     s6,-1(s6)
146         ldq     a3,offvmargdata+sizevmarg*3(t0)
147         ldt     $f19,offvmargdata+sizevmarg*3(t0)
148         ble     s6,calljava_argsloaded
149
150         lda     s6,-1(s6)
151         ldq     a4,offvmargdata+sizevmarg*4(t0)
152         ldt     $f20,offvmargdata+sizevmarg*4(t0)
153         ble     s6,calljava_argsloaded
154
155         lda     s6,-1(s6)
156         ldq     a5,offvmargdata+sizevmarg*5(t0)
157         ldt     $f21,offvmargdata+sizevmarg*5(t0)
158 calljava_argsloaded:
159         mov     sp,t4
160         ble     s6,calljava_nocopy
161         negq    s6,t1
162         s8addq  t1,sp,sp
163         s8addq  t1,t4,t2
164
165 calljava_copyloop:
166         ldq     t3,offvmargdata+sizevmarg*6(t0)
167         stq     t3,0(t2)
168         lda     t1,1(t1)
169         lda     t0,sizevmarg(t0)
170         lda     t2,8(t2)
171         bne     t1,calljava_copyloop
172
173 calljava_nocopy:
174         ldq     itmp1,4*8(t4)             /* pass method pointer via itmp1        */
175
176         lda     mptr,asm_call_jit_compiler/* fake virtual function call (2 instr) */
177         stq     mptr,2*8(t4)              /* store function address               */
178         lda     mptr,1*8(t4)              /* set method pointer                   */
179
180         ldq     pv,1*8(mptr)              /* method call as in Java               */
181         jmp     ra,(pv)                   /* call JIT compiler                    */
182 calljava_jit2:
183         lda     pv,(asm_vm_call_method - calljava_jit2)(ra)
184
185         s8addq  s6,sp,sp
186 calljava_return2:
187         ldq     ra,0*8(sp)                /* restore return address               */
188         ldq     gp,1*8(sp)                /* restore global pointer               */
189         ldq     s6,3*8(sp)
190         lda     sp,5*8(sp)                /* free stack space                     */
191
192 calljava_ret2:
193         jmp     zero,(ra)
194
195 asm_vm_call_method_exception_handler:
196         s8addq  s6,sp,sp
197         ldq     gp,1*8(sp)                /* restore global pointer               */
198         mov     itmp1,a0
199         jsr     ra,builtin_throw_exception
200         ldq     ra,0*8(sp)                /* restore return address               */
201         ldq     s6,3*8(sp)
202         lda     sp,5*8(sp)                /* free stack space                     */
203         jmp     zero,(ra)
204
205         .end    asm_vm_call_method
206
207
208 /* asm_call_jit_compiler *******************************************************
209
210    Invokes the compiler for untranslated Java methods.
211
212 *******************************************************************************/
213
214         .ent    asm_call_jit_compiler
215
216 asm_call_jit_compiler:
217         ldgp    gp,0(pv)
218         lda     sp,-(ARG_CNT+2)*8(sp) /* +2: keep stack 16-byte aligned           */
219
220         stq     ra,0*8(sp)            /* save return address                      */
221
222         SAVE_ARGUMENT_REGISTERS(1)    /* save 6 int/6 float argument registers    */
223
224         mov     itmp1,a0              /* pass methodinfo pointer                  */
225         mov     mptr,a1               /* pass method pointer                      */
226         lda     a2,(ARG_CNT+2)*8(sp)  /* pass java sp                             */
227         mov     ra,a3
228         jsr     ra,jit_asm_compile    /* call jit compiler                        */
229         mov     v0,pv
230
231         ldq     ra,0*8(sp)            /* load return address                      */
232
233         RESTORE_ARGUMENT_REGISTERS(1) /* restore 6 int/6 float argument registers */
234
235         lda     sp,(ARG_CNT+2)*8(sp)  /* remove stack frame                       */
236
237         beq     pv,L_asm_call_jit_compiler_exception
238
239         jmp     zero,(pv)             /* and call method, the method returns      */
240                                       /* directly to the caller (ra).             */
241
242 L_asm_call_jit_compiler_exception:
243 #if defined(ENABLE_THREADS)
244         subq    sp,2*8,sp
245         stq     ra,0*8(sp)            /* save return address (xpc)                */
246         jsr     ra,builtin_asm_get_exceptionptrptr
247         ldq     ra,0*8(sp)            /* restore return address (xpc)             */
248         addq    sp,2*8,sp
249 #else
250         lda     v0,_exceptionptr
251 #endif
252         ldq     xptr,0(v0)            /* get the exception pointer                */
253         stq     zero,0(v0)            /* clear the exception pointer              */
254
255         subq    ra,4,xpc
256         br      L_asm_handle_nat_exception
257
258         .end    asm_call_jit_compiler
259
260
261 /* asm_handle_exception ********************************************************
262
263    This function handles an exception. It does not use the usual calling
264    conventions. The exception pointer is passed in REG_ITMP1 and the
265    pc from the exception raising position is passed in REG_ITMP2. It searches
266    the local exception table for a handler. If no one is found, it unwinds
267    stacks and continues searching the callers.
268
269    ATTENTION: itmp3 == gp!
270
271 *******************************************************************************/
272
273         .ent    asm_handle_nat_exception
274
275 asm_handle_nat_exception:
276 L_asm_handle_nat_exception:       /* required for PIC code                    */
277         ldl     t0,0(ra)              /* load instruction LDA PV,xxx(RA)          */
278         sll     t0,48,t0
279         sra     t0,48,t0              /* isolate offset                           */
280         addq    t0,ra,pv              /* compute update address                   */
281         ldl     t0,4(ra)              /* load instruction LDAH PV,xxx(PV)         */
282         srl     t0,16,t0              /* isolate instruction code                 */
283         lda     t0,-0x177b(t0)        /* test for LDAH                            */
284         bne     t0,L_asm_handle_exception
285         ldl     t0,4(ra)              /* load instruction LDAH PV,xxx(PV)         */
286         sll     t0,16,t0              /* compute high offset                      */
287         addl    t0,0,t0               /* sign extend high offset                  */
288         addq    t0,pv,pv              /* compute update address                   */
289
290         .aent    asm_handle_exception
291
292 asm_handle_exception:
293 L_asm_handle_exception:                 /* required for PIC code              */
294         lda     sp,-(ARG_CNT+TMP_CNT)*8(sp) /* create maybe-leaf stackframe       */
295
296         SAVE_ARGUMENT_REGISTERS(0)          /* we save arg and temp registers in  */
297         SAVE_TEMPORARY_REGISTERS(ARG_CNT)   /* case this is a leaf method         */
298
299         lda     a3,(ARG_CNT+TMP_CNT)*8(zero)/* prepare a3 for handle_exception */
300         lda     a4,1(zero)                  /* set maybe-leaf flag                */
301
302 L_asm_handle_exception_stack_loop:
303         lda     sp,-5*8(sp)                 /* allocate stack                     */
304         stq     xptr,0*8(sp)                /* save exception pointer             */
305         stq     xpc,1*8(sp)                 /* save exception pc                  */
306         stq     pv,2*8(sp)                  /* save data segment pointer          */
307         stq     ra,3*8(sp)                  /* save return address                */
308         addq    a3,sp,a3                    /* calculate Java sp into a3...       */
309         addq    a3,5*8,a3
310         stq     a4,4*8(sp)                  /* save maybe-leaf flag               */
311
312         br      ra,L_asm_handle_exception_load_gp /* set ra for gp loading        */
313 L_asm_handle_exception_load_gp:
314         ldgp    gp,0(ra)                    /* load gp                            */
315
316         mov     xptr,a0                     /* pass exception pointer             */
317         mov     xpc,a1                      /* pass exception pc                  */
318         mov     pv,a2                       /* pass data segment pointer          */
319                                             /* a3 is still set                    */
320         jsr     ra,exceptions_handle_exception
321
322         beq     v0,L_asm_handle_exception_not_catched
323
324         mov     v0,xpc                      /* move handlerpc into xpc            */
325         ldq     xptr,0*8(sp)                /* restore exception pointer          */
326         ldq     pv,2*8(sp)                  /* restore data segment pointer       */
327         ldq     ra,3*8(sp)                  /* restore return address             */
328         ldq     a4,4*8(sp)                  /* get maybe-leaf flag                */
329         lda     sp,5*8(sp)                  /* free stack frame                   */
330
331         beq     a4,L_asm_handle_exception_no_leaf
332
333         RESTORE_ARGUMENT_REGISTERS(0)       /* if this is a leaf method, we have  */
334         RESTORE_TEMPORARY_REGISTERS(ARG_CNT)/* to restore arg and temp registers  */
335         
336         lda     sp,(ARG_CNT+TMP_CNT)*8(sp)  /* remove maybe-leaf stackframe       */
337
338 L_asm_handle_exception_no_leaf:
339         jmp     zero,(xpc)                  /* jump to the handler                */
340
341 L_asm_handle_exception_not_catched:
342         ldq     xptr,0*8(sp)                /* restore exception pointer          */
343         ldq     pv,2*8(sp)                  /* restore data segment pointer       */
344         ldq     ra,3*8(sp)                  /* restore return address             */
345         ldq     a4,4*8(sp)                  /* get maybe-leaf flag                */
346         lda     sp,5*8(sp)
347
348         beq     a4,L_asm_handle_exception_no_leaf_stack
349
350         lda     sp,(ARG_CNT+TMP_CNT)*8(sp)  /* remove maybe-leaf stackframe       */
351         mov     zero,a4                     /* clear the maybe-leaf flag          */
352
353 L_asm_handle_exception_no_leaf_stack:
354         ldl     t0,FrameSize(pv)            /* get frame size                     */
355         addq    t0,sp,t0                    /* pointer to save area               */
356
357         ldl     t1,IsLeaf(pv)               /* is leaf procedure                  */
358         bne     t1,L_asm_handle_exception_no_ra_restore
359
360         ldq     ra,-1*8(t0)                 /* restore ra                         */
361         subq    t0,8,t0                     /* t0--                               */
362
363 L_asm_handle_exception_no_ra_restore:
364         mov     ra,xpc                      /* the new xpc is ra                  */
365         ldl     t1,IntSave(pv)              /* t1 = saved int register count      */
366         br      t2,ex_int1                  /* t2 = current pc                    */
367 ex_int1:
368         lda     t2,(ex_int2-ex_int1)(t2)
369         negl    t1,t1                       /* negate register count              */
370         s4addq  t1,t2,t2                    /* t2 = IntSave - register count * 4  */
371         jmp     zero,(t2)                   /* jump to save position              */
372
373         ldq     s0,-7*8(t0)
374         ldq     s1,-6*8(t0)
375         ldq     s2,-5*8(t0)
376         ldq     s3,-4*8(t0)
377         ldq     s4,-3*8(t0)
378         ldq     s5,-2*8(t0)
379         ldq     s6,-1*8(t0)
380
381 ex_int2:
382         s8addq  t1,t0,t0                    /* t0 = t0 - 8 * register count       */
383
384         ldl     t1,FltSave(pv)              /* t1 = saved flt register count      */
385         br      t2,ex_flt1                  /* t2 = current pc                    */
386 ex_flt1:
387         lda     t2,(ex_flt2-ex_flt1)(t2)
388         negl    t1,t1                       /* negate register count              */
389         s4addq  t1,t2,t2                    /* t2 = FltSave - 4 * register count  */
390         jmp     zero,(t2)                   /* jump to save position              */
391
392         ldt     fs0,-8*8(t0)
393         ldt     fs1,-7*8(t0)
394         ldt     fs2,-6*8(t0)
395         ldt     fs3,-5*8(t0)
396         ldt     fs4,-4*8(t0)
397         ldt     fs5,-3*8(t0)
398         ldt     fs6,-2*8(t0)
399         ldt     fs7,-1*8(t0)
400
401 ex_flt2:
402         ldl     t0,FrameSize(pv)            /* get frame size                     */
403         addq    sp,t0,sp                    /* unwind stack                       */
404         mov     zero,a3                     /* prepare a3 for handle_exception    */
405
406         ldl     t0,0(ra)              /* load instruction LDA PV,xxx(RA)          */
407         sll     t0,48,t0
408         sra     t0,48,t0              /* isolate offset                           */
409         addq    t0,ra,pv              /* compute update address                   */
410         ldl     t0,4(ra)              /* load instruction LDAH PV,xxx(PV)         */
411         srl     t0,16,t0              /* isolate instruction code                 */
412         lda     t0,-0x177b(t0)        /* test for LDAH                            */
413         bne     t0,L_asm_handle_exception_stack_loop
414         ldl     t0,4(ra)              /* load instruction LDAH PV,xxx(RA)         */
415         sll     t0,16,t0              /* compute high offset                      */
416         addl    t0,0,t0               /* sign extend high offset                  */
417         addq    t0,pv,pv              /* compute update address                   */
418
419         br      L_asm_handle_exception_stack_loop
420
421         .end    asm_handle_nat_exception
422
423
424 /* asm_wrapper_patcher *********************************************************
425
426    XXX
427
428    Stack layout:
429      40   return address into JIT code (patch position)
430      32   pointer to virtual java_objectheader
431      24   machine code (which is patched back later)
432      16   unresolved class/method/field reference
433       8   data segment displacement from load instructions
434       0   patcher function pointer to call (pv afterwards)
435
436    ATTENTION: itmp3 == gp! But we don't need gp do call the patcher function.
437
438 *******************************************************************************/
439                 
440         .ent    asm_wrapper_patcher
441
442 asm_wrapper_patcher:
443         lda     sp,-((2+12+27+4)*8+sizestackframeinfo)(sp) /* create stack frame  */
444
445         SAVE_RETURN_REGISTERS(0)      /* save 1 int/1 float return registers      */
446         SAVE_ARGUMENT_REGISTERS(2)    /* save 6 int/6 float argument registers    */
447         SAVE_TEMPORARY_REGISTERS(14)  /* save 11 int/16 float temporary registers */
448
449         stq     itmp1,(2+12+27+0)*8(sp) /* save itmp1                             */
450         stq     itmp2,(2+12+27+1)*8(sp) /* save itmp2                             */
451         stq     ra,(2+12+27+2)*8(sp)  /* save method return address (for leafs)   */
452         stq     pv,(2+12+27+3)*8(sp)  /* save pv of calling java function         */
453
454         br      ra,L_asm_wrapper_patcher_load_gp
455 L_asm_wrapper_patcher_load_gp:
456         ldgp    gp,0(ra)              /* load gp (it's not set correctly in jit)  */
457
458         lda     a0,(2+12+27+4)*8(sp)  /* create stackframe info                   */
459         mov     pv,a1                 /* pass java pv                             */
460         lda     a2,((6+2+12+27+4)*8+sizestackframeinfo)(sp) /* pass java sp       */
461         ldq     a3,(2+12+27+2)*8(sp)  /* this is correct for leafs                */
462         ldq     a4,((5+2+12+27+4)*8+sizestackframeinfo)(sp) /* pass xpc           */
463         jsr     ra,stacktrace_create_extern_stackframeinfo
464         ldgp    gp,0(ra)
465
466         lda     a0,((0+2+12+27+4)*8+sizestackframeinfo)(sp) /* pass sp            */
467         ldq     pv,((0+2+12+27+4)*8+sizestackframeinfo)(sp) /* get function       */
468         ldq     itmp1,(2+12+27+3)*8(sp) /* save pv to the position of fp          */
469         stq     itmp1,((0+2+12+27+4)*8+sizestackframeinfo)(sp)
470         jmp     ra,(pv)               /* call the patcher function                */
471         ldgp    gp,0(ra)
472         stq     v0,((0+2+12+27+4)*8+sizestackframeinfo)(sp) /* save return value  */
473
474         lda     a0,(2+12+27+4)*8(sp)  /* remove stackframe info                   */
475         jsr     ra,stacktrace_remove_stackframeinfo
476         ldgp    gp,0(ra)
477
478         RESTORE_RETURN_REGISTERS(0)   /* restore 1 int/1 float return registers   */
479         RESTORE_ARGUMENT_REGISTERS(2) /* restore 6 int/6 float argument registers */
480         RESTORE_TEMPORARY_REGISTERS(14) /* restore 11 integer temporary registers */
481
482         ldq     itmp1,(2+12+27+0)*8(sp) /* restore itmp1                          */
483         ldq     itmp2,(2+12+27+1)*8(sp) /* restore itmp2                          */
484         ldq     ra,(2+12+27+2)*8(sp)  /* restore method return address (for leafs)*/
485         ldq     pv,(2+12+27+3)*8(sp)  /* restore pv of calling java function      */
486
487         ldq     itmp3,((0+2+12+27+4)*8+sizestackframeinfo)(sp) /* get return value*/
488         beq     itmp3,L_asm_wrapper_patcher_exception
489
490         ldq     itmp3,((5+2+12+27+4)*8+sizestackframeinfo)(sp)/* get RA to JIT    */
491         lda     sp,((6+2+12+27+4)*8+sizestackframeinfo)(sp) /* remove stack frame */
492
493         jmp     zero,(itmp3)          /* jump to new patched code                 */
494
495 L_asm_wrapper_patcher_exception:
496         ldq     xpc,((5+2+12+27+4)*8+sizestackframeinfo)(sp) /* RA is xpc         */
497         lda     sp,((6+2+12+27+4)*8+sizestackframeinfo)(sp) /* remove stack frame */
498
499         br      itmp1,L_asm_wrapper_patcher_exception_load_gp
500 L_asm_wrapper_patcher_exception_load_gp:
501         ldgp    gp,0(itmp1)           /* itmp3 == gp, load the current gp         */
502
503 #if defined(ENABLE_THREADS)
504         subq    sp,3*8,sp
505         stq     xpc,0*8(sp)           /* save return address (xpc)                */
506         stq     ra,1*8(sp)
507         stq     pv,2*8(sp)
508         jsr     ra,builtin_asm_get_exceptionptrptr
509         ldq     xpc,0*8(sp)           /* restore return address (xpc)             */
510         ldq     ra,1*8(sp)
511         ldq     pv,2*8(sp)
512         addq    sp,3*8,sp
513 #else
514         lda     v0,_exceptionptr
515 #endif
516         ldq     xptr,0(v0)            /* get the exception pointer                */
517         stq     zero,0(v0)            /* clear the exception pointer              */
518         br      L_asm_handle_exception/* we have the pv of the calling java func. */
519
520         .end    asm_wrapper_patcher
521
522                 
523 /* asm_replacement_out *********************************************************
524
525    This code is jumped to from the replacement-out stubs that are executed
526    when a thread reaches an activated replacement point.
527
528    The purpose of asm_replacement_out is to read out the parts of the
529    execution state that cannot be accessed from C code, store this state,
530    and then call the C function replace_me.
531
532    Stack layout:
533      16                 start of stack inside method to replace
534       0   rplpoint *    info on the replacement point that was reached
535
536    NOTE: itmp3 has been clobbered by the replacement-out stub!
537
538 *******************************************************************************/
539
540 /* some room to accomodate changes of the stack frame size during replacement */
541         /* XXX we should find a cleaner solution here */
542 #define REPLACEMENT_ROOM  512
543
544 #define REPLACEMENT_STACK_OFFSET ((sizeexecutionstate + REPLACEMENT_ROOM + 0xf) & ~0xf)
545
546         .ent asm_replacement_out
547
548 asm_replacement_out:
549     /* create stack frame */
550         lda     sp,-(REPLACEMENT_STACK_OFFSET)(sp)
551
552         /* save registers in execution state */
553         stq     $0 ,( 0*8+offes_intregs)(sp)
554         stq     $1 ,( 1*8+offes_intregs)(sp)
555         stq     $2 ,( 2*8+offes_intregs)(sp)
556         stq     $3 ,( 3*8+offes_intregs)(sp)
557         stq     $4 ,( 4*8+offes_intregs)(sp)
558         stq     $5 ,( 5*8+offes_intregs)(sp)
559         stq     $6 ,( 6*8+offes_intregs)(sp)
560         stq     $7 ,( 7*8+offes_intregs)(sp)
561         stq     $8 ,( 8*8+offes_intregs)(sp)
562         stq     $9 ,( 9*8+offes_intregs)(sp)
563         stq     $10,(10*8+offes_intregs)(sp)
564         stq     $11,(11*8+offes_intregs)(sp)
565         stq     $12,(12*8+offes_intregs)(sp)
566         stq     $13,(13*8+offes_intregs)(sp)
567         stq     $14,(14*8+offes_intregs)(sp)
568         stq     $15,(15*8+offes_intregs)(sp)
569         stq     $16,(16*8+offes_intregs)(sp)
570         stq     $17,(17*8+offes_intregs)(sp)
571         stq     $18,(18*8+offes_intregs)(sp)
572         stq     $19,(19*8+offes_intregs)(sp)
573         stq     $20,(20*8+offes_intregs)(sp)
574         stq     $21,(21*8+offes_intregs)(sp)
575         stq     $22,(22*8+offes_intregs)(sp)
576         stq     $23,(23*8+offes_intregs)(sp)
577         stq     $24,(24*8+offes_intregs)(sp)
578         stq     $25,(25*8+offes_intregs)(sp)
579         stq     $26,(26*8+offes_intregs)(sp)
580         stq     $27,(27*8+offes_intregs)(sp)
581         stq     $28,(28*8+offes_intregs)(sp)
582         stq     $29,(29*8+offes_intregs)(sp)
583         stq     $30,(30*8+offes_intregs)(sp)
584         stq     $31,(31*8+offes_intregs)(sp)
585         
586         stt     $f0 ,( 0*8+offes_fltregs)(sp)
587         stt     $f1 ,( 1*8+offes_fltregs)(sp)
588         stt     $f2 ,( 2*8+offes_fltregs)(sp)
589         stt     $f3 ,( 3*8+offes_fltregs)(sp)
590         stt     $f4 ,( 4*8+offes_fltregs)(sp)
591         stt     $f5 ,( 5*8+offes_fltregs)(sp)
592         stt     $f6 ,( 6*8+offes_fltregs)(sp)
593         stt     $f7 ,( 7*8+offes_fltregs)(sp)
594         stt     $f8 ,( 8*8+offes_fltregs)(sp)
595         stt     $f9 ,( 9*8+offes_fltregs)(sp)
596         stt     $f10,(10*8+offes_fltregs)(sp)
597         stt     $f11,(11*8+offes_fltregs)(sp)
598         stt     $f12,(12*8+offes_fltregs)(sp)
599         stt     $f13,(13*8+offes_fltregs)(sp)
600         stt     $f14,(14*8+offes_fltregs)(sp)
601         stt     $f15,(15*8+offes_fltregs)(sp)
602         stt     $f16,(16*8+offes_fltregs)(sp)
603         stt     $f17,(17*8+offes_fltregs)(sp)
604         stt     $f18,(18*8+offes_fltregs)(sp)
605         stt     $f19,(19*8+offes_fltregs)(sp)
606         stt     $f20,(20*8+offes_fltregs)(sp)
607         stt     $f21,(21*8+offes_fltregs)(sp)
608         stt     $f22,(22*8+offes_fltregs)(sp)
609         stt     $f23,(23*8+offes_fltregs)(sp)
610         stt     $f24,(24*8+offes_fltregs)(sp)
611         stt     $f25,(25*8+offes_fltregs)(sp)
612         stt     $f26,(26*8+offes_fltregs)(sp)
613         stt     $f27,(27*8+offes_fltregs)(sp)
614         stt     $f28,(28*8+offes_fltregs)(sp)
615         stt     $f29,(29*8+offes_fltregs)(sp)
616         stt     $f30,(30*8+offes_fltregs)(sp)
617         stt     $f31,(31*8+offes_fltregs)(sp)
618         
619         /* calculate sp of method */
620         lda     itmp1,(REPLACEMENT_STACK_OFFSET + 2*8)(sp)
621         stq     itmp1,(offes_sp)(sp)
622
623         br      ra,L_asm_replacement_out_load_gp
624 L_asm_replacement_out_load_gp:
625         ldgp    gp,0(ra)                    /* load gp                            */
626
627         /* store pv */
628         stq     pv,(offes_pv)(sp)
629
630         /* call replace_me */
631         ldq     a0,-(2*8)(itmp1)            /* arg0: rplpoint *                   */
632     mov     sp,a1                       /* arg1: execution state              */
633     jmp     zero,replace_me             /* call C function replace_me         */
634     jmp     zero,abort                  /* NEVER REACHED                      */
635
636         .end asm_replacement_out
637
638 /* asm_replacement_in **********************************************************
639
640    This code writes the given execution state and jumps to the replacement
641    code.
642
643    This function never returns!
644
645    NOTE: itmp3 is not restored!
646
647    C prototype:
648       void asm_replacement_in(executionstate *es);
649
650 *******************************************************************************/
651
652         .ent asm_replacement_in
653         
654 asm_replacement_in:
655         /* a0 == executionstate *es */
656
657         /* set new sp and pv */
658         ldq     sp,(offes_sp)(a0)
659         ldq     pv,(offes_pv)(a0)
660         
661         /* copy registers from execution state */
662         ldq     $0 ,( 0*8+offes_intregs)(a0)
663         ldq     $1 ,( 1*8+offes_intregs)(a0)
664         ldq     $2 ,( 2*8+offes_intregs)(a0)
665         ldq     $3 ,( 3*8+offes_intregs)(a0)
666         ldq     $4 ,( 4*8+offes_intregs)(a0)
667         ldq     $5 ,( 5*8+offes_intregs)(a0)
668         ldq     $6 ,( 6*8+offes_intregs)(a0)
669         ldq     $7 ,( 7*8+offes_intregs)(a0)
670         ldq     $8 ,( 8*8+offes_intregs)(a0)
671         ldq     $9 ,( 9*8+offes_intregs)(a0)
672         ldq     $10,(10*8+offes_intregs)(a0)
673         ldq     $11,(11*8+offes_intregs)(a0)
674         ldq     $12,(12*8+offes_intregs)(a0)
675         ldq     $13,(13*8+offes_intregs)(a0)
676         ldq     $14,(14*8+offes_intregs)(a0)
677         ldq     $15,(15*8+offes_intregs)(a0)
678         /* a0 is loaded below             */
679         ldq     $17,(17*8+offes_intregs)(a0)
680         ldq     $18,(18*8+offes_intregs)(a0)
681         ldq     $19,(19*8+offes_intregs)(a0)
682         ldq     $20,(20*8+offes_intregs)(a0)
683         ldq     $21,(21*8+offes_intregs)(a0)
684         ldq     $22,(22*8+offes_intregs)(a0)
685         ldq     $23,(23*8+offes_intregs)(a0)
686         ldq     $24,(24*8+offes_intregs)(a0)
687         ldq     $25,(25*8+offes_intregs)(a0)
688         ldq     $26,(26*8+offes_intregs)(a0)
689         /* $27 is pv                      */
690         ldq     $28,(28*8+offes_intregs)(a0)
691         ldq     $29,(29*8+offes_intregs)(a0)
692         /* $30 is sp                      */
693         /* $31 is zero                    */
694         
695         ldt     $f0 ,( 0*8+offes_fltregs)(a0)
696         ldt     $f1 ,( 1*8+offes_fltregs)(a0)
697         ldt     $f2 ,( 2*8+offes_fltregs)(a0)
698         ldt     $f3 ,( 3*8+offes_fltregs)(a0)
699         ldt     $f4 ,( 4*8+offes_fltregs)(a0)
700         ldt     $f5 ,( 5*8+offes_fltregs)(a0)
701         ldt     $f6 ,( 6*8+offes_fltregs)(a0)
702         ldt     $f7 ,( 7*8+offes_fltregs)(a0)
703         ldt     $f8 ,( 8*8+offes_fltregs)(a0)
704         ldt     $f9 ,( 9*8+offes_fltregs)(a0)
705         ldt     $f10,(10*8+offes_fltregs)(a0)
706         ldt     $f11,(11*8+offes_fltregs)(a0)
707         ldt     $f12,(12*8+offes_fltregs)(a0)
708         ldt     $f13,(13*8+offes_fltregs)(a0)
709         ldt     $f14,(14*8+offes_fltregs)(a0)
710         ldt     $f15,(15*8+offes_fltregs)(a0)
711         ldt     $f16,(16*8+offes_fltregs)(a0)
712         ldt     $f17,(17*8+offes_fltregs)(a0)
713         ldt     $f18,(18*8+offes_fltregs)(a0)
714         ldt     $f19,(19*8+offes_fltregs)(a0)
715         ldt     $f20,(20*8+offes_fltregs)(a0)
716         ldt     $f21,(21*8+offes_fltregs)(a0)
717         ldt     $f22,(22*8+offes_fltregs)(a0)
718         ldt     $f23,(23*8+offes_fltregs)(a0)
719         ldt     $f24,(24*8+offes_fltregs)(a0)
720         ldt     $f25,(25*8+offes_fltregs)(a0)
721         ldt     $f26,(26*8+offes_fltregs)(a0)
722         ldt     $f27,(27*8+offes_fltregs)(a0)
723         ldt     $f28,(28*8+offes_fltregs)(a0)
724         ldt     $f29,(29*8+offes_fltregs)(a0)
725         ldt     $f30,(30*8+offes_fltregs)(a0)
726         ldt     $f31,(31*8+offes_fltregs)(a0)
727
728         /* load new pc */
729
730         ldq     itmp3,offes_pc(a0)
731
732         /* load a0 */
733         
734         ldq     a0,(16*8+offes_intregs)(a0)
735         
736         /* jump to new code */
737
738         jmp     zero,(itmp3)
739
740         .end asm_replacement_in
741
742
743         .ent    asm_getclassvalues_atomic
744
745 asm_getclassvalues_atomic:
746 _crit_restart:
747 _crit_begin:
748         ldl     t0,offbaseval(a0)
749         ldl     t1,offdiffval(a0)
750         ldl     t2,offbaseval(a1)
751 _crit_end:
752         stl     t0,offcast_super_baseval(a2)
753         stl     t1,offcast_super_diffval(a2)
754         stl     t2,offcast_sub_baseval(a2)
755         jmp     zero,(ra)
756
757         .end    asm_getclassvalues_atomic
758
759
760     .data
761
762 asm_criticalsections:
763 #if defined(ENABLE_THREADS)
764     .quad   _crit_begin
765     .quad   _crit_end
766     .quad   _crit_restart
767 #endif
768     .quad   0
769
770
771 /* asm_md_init *****************************************************************
772
773    Initialize machine dependent stuff.
774
775    Determines if the byte support instruction set (21164a and higher)
776    is available.
777
778 *******************************************************************************/
779
780         .ent    asm_md_init
781
782 asm_md_init:
783         .long   0x47e03c20                  /* amask   1,v0                       */
784         jmp     zero,(ra)                   /* return                             */
785
786         .end    asm_md_init
787
788
789 /* asm_cacheflush **************************************************************
790
791    XXX
792
793 *******************************************************************************/
794
795         .ent    asm_cacheflush
796
797 asm_cacheflush:
798         call_pal PAL_imb              /* synchronize instruction cache            */
799         jmp     zero,(ra)
800
801         .end    asm_cacheflush
802
803
804 /* Disable exec-stacks, required for Gentoo ***********************************/
805
806 #if defined(__GCC__) && defined(__ELF__)
807         .section .note.GNU-stack,"",@progbits
808 #endif
809
810
811 /*
812  * These are local overrides for various environment variables in Emacs.
813  * Please do not remove this and leave it at the end of the file, where
814  * Emacs will automagically detect them.
815  * ---------------------------------------------------------------------
816  * Local variables:
817  * mode: asm
818  * indent-tabs-mode: t
819  * c-basic-offset: 4
820  * tab-width: 4
821  * End:
822  * vim:noexpandtab:sw=4:ts=4:
823  */