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