* src/vm/jit/powerpc64/emit.c (emit_patcher_stubs): Removed, this is obsolete.
[cacao.git] / src / vm / jit / powerpc64 / asmpart.S
1 /* src/vm/jit/powerpc64/asmpart.S - Java-C interface functions for PowerPC64
2                 
3    Copyright (C) 1996-2005, 2006, 2007 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.text;  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 */
26
27
28 #include "config.h"
29
30 #define __ASSEMBLY__
31
32 #include "md-abi.h"
33 #include "md-asm.h"
34
35 #include "vm/jit/abi-asm.h"
36 #include "vm/jit/methodheader.h"
37
38
39 /* export functions ***********************************************************/
40
41         .globl asm_vm_call_method_exception_handler
42         .globl asm_vm_call_method_end
43
44         .globl asm_call_jit_compiler
45
46         .globl asm_handle_nat_exception
47         .globl asm_handle_exception
48
49         .globl asm_abstractmethoderror
50
51 #if defined(ENABLE_REPLACEMENT)
52         .globl asm_replacement_out
53         .globl .asm_replacement_in
54 #endif
55
56         .globl asm_cacheflush
57
58
59 /* asm_vm_call_method **********************************************************
60 *                                                                              *
61 *   This function calls a Java-method (which possibly needs compilation)       *
62 *   with up to 4 address parameters.                                           *
63 *                                                                              *
64 *   This functions calls the JIT-compiler which eventually translates the      *
65 *   method into machine code.                                                  *
66 *                                                                              *
67 *   C-prototype:                                                               *
68 *    javaobject_header *asm_calljavamethod (methodinfo *m,                     *
69 *         void *arg1, void *arg2, void *arg3, void *arg4);                     *
70 *                                                                              *
71 *******************************************************************************/
72         /* this is the method header see src/vm/jit/methodheader.h */
73
74         .align  3
75
76         .quad   0                           /* catch type all                     */
77         .quad   0                           /* handler pc                         */
78         .quad   0                           /* end pc                             */
79         .quad   0                           /* start pc                           */
80         .long   1                           /* extable size                       */
81         .long   0                           /* ALIGNMENT PADDING                  */
82         .quad   0                           /* line number table  start           */
83         .quad   0                           /* line number table  size            */
84         .long   0                           /* ALIGNMENT PADDING                  */
85         .long   0                           /* fltsave                            */
86         .long   0                           /* intsave                            */
87         .long   0                           /* isleaf                             */
88         .long   0                           /* IsSync                             */
89         .long   0                           /* frame size                         */
90         .quad   0                           /* codeinfo pointer                   */
91
92 #ifdef ENABLE_LIBJVM
93         
94         .globl asm_vm_call_method
95         .globl asm_vm_call_method_int
96         .globl asm_vm_call_method_long
97         .globl asm_vm_call_method_float
98         .globl asm_vm_call_method_double
99         .section ".opd","aw"
100         .align 3
101
102         asm_vm_call_method:
103         asm_vm_call_method_int:
104         asm_vm_call_method_long:
105         asm_vm_call_method_float:
106         asm_vm_call_method_double:
107                 .quad   .asm_vm_call_method,.TOC.@tocbase,0
108                 .previous
109                 .size asm_vm_call_method, 24
110                 .type .asm_vm_call_method,@function
111                 .globl .asm_vm_call_method
112 #else
113         asm_vm_call_method:
114         .globl asm_vm_call_method
115         asm_vm_call_method_int:
116         .globl asm_vm_call_method_int
117         asm_vm_call_method_long:
118         .globl asm_vm_call_method_long
119         asm_vm_call_method_float:
120         .globl asm_vm_call_method_float
121         asm_vm_call_method_double:
122         .globl asm_vm_call_method_double
123 #endif
124
125 .asm_vm_call_method:
126 .asm_vm_call_method_int:
127 .asm_vm_call_method_long:
128 .asm_vm_call_method_float:
129 .asm_vm_call_method_double:
130         mflr    r0
131         std     r0,LA_LR_OFFSET(sp)
132         stdu    sp,-40*8(sp)
133         
134         std     s0,8*8(sp)                /* save used callee saved registers     */
135         std     a0,9*8(sp)                /* save method pointer for compiler     */
136
137         std     pv,11*8(sp)               /* save PV register                     */
138
139         std     itmp3,12*8(sp)            /* registers r14-r31 are callee saved   */
140         stfd    ftmp1,13*8(sp)            /* registers f14-f31 are callee saved   */
141         stfd    ftmp2,14*8(sp)
142
143
144         SAVE_TEMPORARY_REGISTERS(15)     
145         mr      s0, r1                  /* save stack pointer */
146
147         /* a1 contains a pointer to a unit64_t structure filled with all INT_ARG_REG,
148         followed by ADR_ARG_CNT and FLT_ARG_CNT, afterwards what else needs to be copied onto
149         the stack 
150         a2 contains the number of additional stack slots to be copied
151         */
152
153 L_register_copy:
154         mr      t1, a1
155         mr      t2, a2
156
157         ld      a0 ,  0*8(t1)
158         ld      a1 ,  1*8(t1)
159         ld      a2 ,  2*8(t1)
160         ld      a3 ,  3*8(t1)
161         ld      a4 ,  4*8(t1)
162         ld      a5 ,  5*8(t1)
163         ld      a6 ,  6*8(t1)
164         ld      a7 ,  7*8(t1)
165
166         lfd     fa0 , 8*8(t1)
167         lfd     fa1 , 9*8(t1)
168         lfd     fa2 ,10*8(t1)
169         lfd     fa3 ,11*8(t1)
170         lfd     fa4 ,12*8(t1)
171         lfd     fa5 ,13*8(t1)
172         lfd     fa6 ,14*8(t1)
173         lfd     fa7 ,15*8(t1)
174         lfd     fa8 ,16*8(t1)
175         lfd     fa9 ,17*8(t1)
176         lfd     fa10,18*8(t1)
177         lfd     fa11,19*8(t1)
178         lfd     fa12,20*8(t1)
179
180         mr.     t2,t2
181         beq L_stack_copy_done
182
183 L_stack_copy:
184         addi    t1,t1,20*8              /* before first possible stack slot arg */
185         mr      t3,t2                   /* argument counter */
186         sldi    t2,t2,8                 /* calculate size of stack */
187         sub     sp,sp,t2                /* increase the stack */
188         mr      t2,sp                   /* t2 points to bottom of stack now */
189
190 L_stack_copy_loop:
191         addi    t1,t1,8                 /* next possible stack slot to copy */
192         mr.     t3,t3                   /* more stack slots to copy ? */
193         beq     L_stack_copy_done
194         ld      itmp3, 0(t1)
195         std     itmp3, 0(t2)
196         addi    t2,t2,8
197         addi    t3,t3,-1
198         b L_stack_copy_loop
199
200 L_stack_copy_done:
201         mr      itmp1, s0               /* fake invokevirtual invocation */
202         addi    itmp1, itmp1, 9*8       /* address of methods pv */
203         ld      pv,0*8(itmp1)
204         mtctr   pv
205         bctrl
206 1:
207         mflr    itmp1
208         addi    pv,itmp1,(.asm_vm_call_method - 1b)@l
209
210 L_asm_vm_call_method_return:
211         mr      sp,s0                     /* restore the function's sp            */
212
213         ld      s0,8*8(sp)                /* restore used callee saved registers  */
214
215         ld      pv,11*8(sp)               /* save PV register                     */
216
217         ld      itmp3,12*8(sp)
218         lfd     ftmp1,13*8(sp)            /* registers f14-f31 are callee saved   */
219         lfd     ftmp2,14*8(sp)
220
221         RESTORE_TEMPORARY_REGISTERS(15) 
222
223         ld     r0,40*8+LA_LR_OFFSET(r1)
224         mtlr   r0
225         addi   r1,r1,40*8
226         blr
227
228 asm_vm_call_method_exception_handler:
229         mr      r3,itmp1
230         bl      builtin_throw_exception
231         b       L_asm_vm_call_method_return
232
233 asm_vm_call_method_end:
234         nop
235
236 /* asm_call_jit_compiler *******************************************************
237
238    Invokes the compiler for untranslated JavaVM methods.
239
240 *******************************************************************************/
241
242 asm_call_jit_compiler:
243 L_asm_call_jit_compiler:                /* required for PIC code              */
244         mflr    r0
245         std     r0,LA_LR_OFFSET(sp)         /* save return address                */
246         stdu    r1,-(LA_SIZE+PA_SIZE+ARG_CNT*8)(sp)
247
248         SAVE_ARGUMENT_REGISTERS(LA_SIZE_IN_POINTERS+PA_SIZE_IN_POINTERS)
249
250         mr      a0,itmp1
251         mr      a1,mptr
252         addi    a2,sp,(LA_SIZE + PA_SIZE+ ARG_CNT*8)
253         ld      a3,(LA_SIZE + PA_SIZE + ARG_CNT*8)+LA_LR_OFFSET(sp)
254         bl      jit_asm_compile
255         ori     r0,r0,0                     /* nop needed after jump to function desc. */
256         mr      pv,v0                       /* move address to pv register        */
257
258         RESTORE_ARGUMENT_REGISTERS(LA_SIZE_IN_POINTERS+PA_SIZE_IN_POINTERS)
259
260         ld     itmp1,(LA_SIZE + PA_SIZE + ARG_CNT*8)+LA_LR_OFFSET(sp)
261         mtlr   itmp1
262
263         addi    sp,sp,(LA_SIZE + PA_SIZE + ARG_CNT*8)
264
265         mr.     pv,pv                       /* test for exception                 */
266         beq     L_asm_call_jit_compiler_exception
267
268         mtctr   pv                          /* move method address to control reg */
269         bctr                                /* and call the Java method           */
270
271 L_asm_call_jit_compiler_exception:
272         mflr    r0
273         std     r0,LA_LR_OFFSET(sp)
274         stdu    sp,-LA_SIZE_ALIGNED(sp)     /* preserve linkage area              */
275         bl      exceptions_get_and_clear_exception
276         ld      xpc,LA_SIZE_ALIGNED+LA_LR_OFFSET(sp)
277         mtlr    xpc     
278         addi    sp,sp,LA_SIZE_ALIGNED
279
280         mr      xptr,v0                     /* get exception                      */
281         addi    xpc,xpc,-4                  /* exception address is ra - 4        */
282         b       L_asm_handle_nat_exception
283
284
285 /********************* function asm_handle_exception ***************************
286 *                                                                              *
287 *   This function handles an exception. It does not use the usual calling      *
288 *   conventions. The exception pointer is passed in REG_ITMP1 and the          *
289 *   pc from the exception raising position is passed in REG_ITMP2. It searches *
290 *   the local exception table for a handler. If no one is found, it unwinds    *
291 *   stacks and continues searching the callers.                                *
292 *                                                                              *
293 *   void asm_handle_exception (exceptionptr, exceptionpc);                     *
294 *                                                                              *
295 *******************************************************************************/
296                 
297 asm_handle_nat_exception:
298 L_asm_handle_nat_exception:             /* required for PIC code              */
299 L_asm_handle_exception_stack_loop:
300         mflr    r0
301         addi    sp,sp,-(LA_SIZE+PA_SIZE+((4+6)*8))  /* allocate stack (+4 for darwin)     */
302         std     xptr,LA_SIZE+PA_SIZE+(4+0)*8(sp)    /* save exception pointer             */
303         std     xpc,LA_SIZE+PA_SIZE+(4+1)*8(sp)     /* save exception pc                  */
304         std     r0,LA_SIZE+PA_SIZE+(4+3)*8(sp)      /* save return address                */
305         li      itmp3,0
306         std     itmp3,LA_SIZE+PA_SIZE+(4+4)*8(sp)   /* save maybe-leaf flag (cleared)     */
307
308         mr      a0,r0                       /* pass return address                */
309         bl      md_codegen_get_pv_from_pc   /* get PV from RA                     */
310         std     v0,LA_SIZE+PA_SIZE+(4+2)*8(sp)      /* save data segment pointer          */
311
312         ld      a0,LA_SIZE+PA_SIZE+(4+0)*8(sp)      /* pass xptr                          */
313         ld      a1,LA_SIZE+PA_SIZE+(4+1)*8(sp)      /* pass xpc                           */
314         ld      a2,LA_SIZE+PA_SIZE+(4+2)*8(sp)      /* pass PV (v0 == a0)                 */
315         addi    a3,sp,LA_SIZE+PA_SIZE+((4+6)*8)     /* pass Java SP                       */
316
317         b       L_asm_handle_exception_continue
318
319
320 asm_handle_exception:
321 L_asm_handle_exception:                 /* required for PIC code              */
322         addi    sp,sp,-(ARG_CNT+TMP_CNT)*8  /* create maybe-leaf stackframe       */
323
324         SAVE_ARGUMENT_REGISTERS(0)          /* we save arg and temp registers in  */
325         SAVE_TEMPORARY_REGISTERS(ARG_CNT)   /* case this is a leaf method         */
326
327         addi    sp,sp,-(LA_SIZE+PA_SIZE+(4+6)*8)        /* allocate stack                     */
328         std     xptr,LA_SIZE+PA_SIZE+(4+0)*8(sp)        /* save exception pointer             */
329         std     pv,LA_SIZE+PA_SIZE+(4+2)*8(sp)          /* save data segment pointer          */
330         mflr    r0                                      /* save return address                */
331         std     r0,LA_SIZE+PA_SIZE+(4+3)*8(sp)          
332         li      t0, 1
333         std     t0, LA_SIZE+PA_SIZE+(4+4)*8(sp)         /* maybe-leaf flag */
334         
335         mr      a0,xptr                     /* pass exception pointer             */
336         mr      a1,xpc                      /* pass exception pc                  */
337         mr      a2,pv                       /* pass data segment pointer          */
338         addi    a3,sp,LA_SIZE+PA_SIZE+(ARG_CNT+TMP_CNT)*8+(4+6)*8
339
340
341 L_asm_handle_exception_continue:
342         bl      exceptions_handle_exception
343
344         mr.     v0,v0
345         beq     L_asm_handle_exception_not_catched
346
347         mr      xpc,v0                              /* move handlerpc into xpc            */
348         ld      xptr,LA_SIZE+PA_SIZE+(4+0)*8(sp)    /* restore exception pointer          */
349         ld      pv,LA_SIZE+PA_SIZE+(4+2)*8(sp)      /* restore data segment pointer       */
350         ld      r0,LA_SIZE+PA_SIZE+(4+3)*8(sp)      /* restore return address             */
351         mtlr    r0
352         ld      t0,LA_SIZE+PA_SIZE+(4+4)*8(sp)      /* get maybe-leaf flag                */
353         addi    sp,sp,LA_SIZE+PA_SIZE+(4+6)*8       /* free stack frame                   */
354
355         mr.     t0,t0
356         beq     L_asm_handle_exception_no_leaf
357
358         RESTORE_ARGUMENT_REGISTERS(0)       /* if this is a leaf method, we have  */
359         RESTORE_TEMPORARY_REGISTERS(ARG_CNT)/* to restore arg and temp registers  */
360
361         addi    sp,sp,(ARG_CNT+TMP_CNT)*8   /* remove maybe-leaf stackframe       */
362
363 L_asm_handle_exception_no_leaf:
364         mtctr   xpc                         /* jump to the handler                */
365         bctr
366
367 L_asm_handle_exception_not_catched:
368         ld      xptr,LA_SIZE+PA_SIZE+(4+0)*8(sp)        /* restore exception pointer          */
369         ld      pv,LA_SIZE+PA_SIZE+(4+2)*8(sp)          /* restore data segment pointer       */
370         ld      r0,LA_SIZE+PA_SIZE+(4+3)*8(sp)          /* restore return address             */
371         mtlr    r0
372         ld      t0,LA_SIZE+PA_SIZE+(4+4)*8(sp)          /* get maybe-leaf flag                */
373         addi    sp,sp,LA_SIZE+PA_SIZE+(4+6)*8           /* free stack frame                   */
374
375         mr.     t0,t0
376         beq     L_asm_handle_exception_no_leaf_stack
377
378         addi    sp,sp,(ARG_CNT+TMP_CNT)*8   /* remove maybe-leaf stackframe       */
379         li      t0,0                        /* clear the maybe-leaf flag          */
380
381 L_asm_handle_exception_no_leaf_stack:
382         lwz     t1,FrameSize(pv)            /* get frame size                     */
383         add     t1,sp,t1                    /* pointer to save area               */
384
385         lwz     t2,IsLeaf(pv)               /* is leaf procedure                  */
386         mr.     t2,t2
387         bne     L_asm_handle_exception_no_ra_restore
388
389         ld      r0,LA_LR_OFFSET(t1)         /* restore ra                         */
390         mtlr    r0
391
392 L_asm_handle_exception_no_ra_restore:
393         mflr    xpc                         /* the new xpc is ra                  */
394         mr      t4,xpc                      /* save RA */
395         lwz     t2,IntSave(pv)              /* t1 = saved int register count      */
396         bl      ex_int1
397 ex_int1:
398         mflr    t3                          /* t3 = current pc                    */
399         addi    t3,t3,(ex_int2-ex_int1)@l
400         slwi    t2,t2,2                     /* t2 = register count * 4            */
401         subf    t3,t2,t3                    /* t3 = IntSave - t2                  */
402         mtctr   t3
403         bctr
404
405         ld      s0,-9*8(t1)
406         ld      s1,-8*8(t1)
407         ld      s2,-7*8(t1)
408         ld      s3,-6*8(t1)
409         ld      s4,-5*8(t1)
410         ld      s5,-4*8(t1)
411         ld      s6,-3*8(t1)
412         ld      s7,-2*8(t1)
413         ld      s8,-1*8(t1)
414
415 ex_int2:
416         subf    t1,t2,t1                    /* t1 = t1 - register count * 4       */
417         lwz     t2,FltSave(pv)
418         bl      ex_flt1
419 ex_flt1:
420         mflr    t3
421         addi    t3,t3,(ex_flt2-ex_flt1)@l
422         slwi    t2,t2,2                     /* t2 = register count * 4            */
423         subf    t3,t2,t3                    /* t3 = FltSave - t2                  */
424         mtctr   t3
425         bctr
426
427         lfd     fs0,-10*8(t1)
428         lfd     fs1,-9*8(t1)
429         lfd     fs2,-8*8(t1)
430         lfd     fs3,-7*8(t1)
431         lfd     fs4,-6*8(t1)
432         lfd     fs5,-5*8(t1)
433         lfd     fs6,-4*8(t1)
434         lfd     fs7,-3*8(t1)
435         lfd     fs8,-2*8(t1)
436         lfd     fs9,-1*8(t1)
437
438 ex_flt2:
439         mtlr    t4                                   /* restore RA */
440         lwz     t1,FrameSize(pv)                     
441         add     sp,sp,t1                             /* unwind stack */
442         b       L_asm_handle_exception_stack_loop
443
444
445 /* asm_abstractmethoderror *****************************************************
446
447    Creates and throws an AbstractMethodError.
448
449 *******************************************************************************/
450
451 asm_abstractmethoderror:
452         mflr    r0
453         std     r0,LA_LR_OFFSET(sp)
454         stdu    sp,-LA_SIZE_ALIGNED(sp)     /* preserve linkage area              */
455         addi    a0,sp,LA_SIZE_ALIGNED       /* pass java sp                       */
456         mr      a1,r0                       /* pass exception address             */
457         bl      exceptions_asm_new_abstractmethoderror
458         ld      r0,LA_SIZE_ALIGNED+LA_LR_OFFSET(sp)
459         mtlr    r0                          /* restore return address             */
460         addi    sp,sp,LA_SIZE_ALIGNED
461
462         mr      xptr,v0                     /* get exception pointer              */
463         mr      xpc,r0                      /* we can't use r0 directly in addi   */
464         addi    xpc,xpc,-4                  /* exception address is ra - 4        */
465         b       L_asm_handle_nat_exception
466
467
468 #if defined(ENABLE_REPLACEMENT)
469
470 /* asm_replacement_out *********************************************************
471
472    This code is jumped to from the replacement-out stubs that are executed
473    when a thread reaches an activated replacement point.
474
475    The purpose of asm_replacement_out is to read out the parts of the
476    execution state that cannot be accessed from C code, store this state,
477    and then call the C function replace_me.
478
479    Stack layout:
480       16                start of stack inside method to replace
481       0   rplpoint *    info on the replacement point that was reached
482
483    NOTE: itmp3 has been clobbered by the replacement-out stub!
484
485 *******************************************************************************/
486
487 /* some room to accomodate changes of the stack frame size during replacement */
488         /* XXX we should find a cleaner solution here */
489 #define REPLACEMENT_ROOM  512
490
491 asm_replacement_out:
492     /* create stack frame */
493         addi    sp,sp,-(sizeexecutionstate + REPLACEMENT_ROOM) /* XXX align */
494
495         /* save link register */
496         mflr    r16
497
498         /* save registers in execution state */
499         std     r0 ,( 0*8+offes_intregs)(sp)
500         std     r1 ,( 1*8+offes_intregs)(sp)
501         std     r2 ,( 2*8+offes_intregs)(sp)
502         std     r3 ,( 3*8+offes_intregs)(sp)
503         std     r4 ,( 4*8+offes_intregs)(sp)
504         std     r5 ,( 5*8+offes_intregs)(sp)
505         std     r6 ,( 6*8+offes_intregs)(sp)
506         std     r7 ,( 7*8+offes_intregs)(sp)
507         std     r8 ,( 8*8+offes_intregs)(sp)
508         std     r9 ,( 9*8+offes_intregs)(sp)
509         std     r10,(10*8+offes_intregs)(sp)
510         std     r11,(11*8+offes_intregs)(sp)
511         std     r12,(12*8+offes_intregs)(sp)
512         std     r13,(13*8+offes_intregs)(sp)
513         std     r14,(14*8+offes_intregs)(sp)
514         std     r15,(15*8+offes_intregs)(sp)
515         std     r16,(16*8+offes_intregs)(sp) /* link register */
516         std     r17,(17*8+offes_intregs)(sp)
517         std     r18,(18*8+offes_intregs)(sp)
518         std     r19,(19*8+offes_intregs)(sp)
519         std     r20,(20*8+offes_intregs)(sp)
520         std     r21,(21*8+offes_intregs)(sp)
521         std     r22,(22*8+offes_intregs)(sp)
522         std     r23,(23*8+offes_intregs)(sp)
523         std     r24,(24*8+offes_intregs)(sp)
524         std     r25,(25*8+offes_intregs)(sp)
525         std     r26,(26*8+offes_intregs)(sp)
526         std     r27,(27*8+offes_intregs)(sp)
527         std     r28,(28*8+offes_intregs)(sp)
528         std     r29,(29*8+offes_intregs)(sp)
529         std     r30,(30*8+offes_intregs)(sp)
530         std     r31,(31*8+offes_intregs)(sp)
531         
532         stfd    fr0 ,( 0*8+offes_fltregs)(sp)
533         stfd    fr1 ,( 1*8+offes_fltregs)(sp)
534         stfd    fr2 ,( 2*8+offes_fltregs)(sp)
535         stfd    fr3 ,( 3*8+offes_fltregs)(sp)
536         stfd    fr4 ,( 4*8+offes_fltregs)(sp)
537         stfd    fr5 ,( 5*8+offes_fltregs)(sp)
538         stfd    fr6 ,( 6*8+offes_fltregs)(sp)
539         stfd    fr7 ,( 7*8+offes_fltregs)(sp)
540         stfd    fr8 ,( 8*8+offes_fltregs)(sp)
541         stfd    fr9 ,( 9*8+offes_fltregs)(sp)
542         stfd    fr10,(10*8+offes_fltregs)(sp)
543         stfd    fr11,(11*8+offes_fltregs)(sp)
544         stfd    fr12,(12*8+offes_fltregs)(sp)
545         stfd    fr13,(13*8+offes_fltregs)(sp)
546         stfd    fr14,(14*8+offes_fltregs)(sp)
547         stfd    fr15,(15*8+offes_fltregs)(sp)
548         stfd    fr16,(16*8+offes_fltregs)(sp)
549         stfd    fr17,(17*8+offes_fltregs)(sp)
550         stfd    fr18,(18*8+offes_fltregs)(sp)
551         stfd    fr19,(19*8+offes_fltregs)(sp)
552         stfd    fr20,(20*8+offes_fltregs)(sp)
553         stfd    fr21,(21*8+offes_fltregs)(sp)
554         stfd    fr22,(22*8+offes_fltregs)(sp)
555         stfd    fr23,(23*8+offes_fltregs)(sp)
556         stfd    fr24,(24*8+offes_fltregs)(sp)
557         stfd    fr25,(25*8+offes_fltregs)(sp)
558         stfd    fr26,(26*8+offes_fltregs)(sp)
559         stfd    fr27,(27*8+offes_fltregs)(sp)
560         stfd    fr28,(28*8+offes_fltregs)(sp)
561         stfd    fr29,(29*8+offes_fltregs)(sp)
562         stfd    fr30,(30*8+offes_fltregs)(sp)
563         stfd    fr31,(31*8+offes_fltregs)(sp)
564         
565         /* calculate sp of method */
566         addi    itmp1,sp,(sizeexecutionstate + REPLACEMENT_ROOM + 4*4)
567         stw     itmp1,(offes_sp)(sp)
568
569         /* store pv */
570         stw     pv,(offes_pv)(sp)
571
572         /* call replace_me */
573         lwz     a0,-(4*4)(itmp1)            /* arg0: rplpoint *                   */
574         mr      a1,sp                       /* arg1: execution state              */
575         addi    sp,sp,-(LA_SIZE_ALIGNED)
576         b       replace_me                  /* call C function replace_me         */
577
578 /* asm_replacement_in **********************************************************
579
580    This code writes the given execution state and jumps to the replacement
581    code.
582
583    This function never returns!
584
585    NOTE: itmp3 is not restored!
586
587    C prototype:
588       void asm_replacement_in(executionstate *es);
589
590 *******************************************************************************/
591
592 .asm_replacement_in:
593         /* a0 == executionstate *es */
594
595         /* set new sp and pv */
596         ld     sp,(offes_sp)(a0)
597         ld     pv,(offes_pv)(a0)
598         
599         /* copy registers from execution state */
600         ld     r0 ,( 0*8+offes_intregs)(a0)
601         /* r1 is sp                       */
602         /* r2 is reserved                 */
603         /* a0 is loaded below             */
604         ld     r4 ,( 4*8+offes_intregs)(a0)
605         ld     r5 ,( 5*8+offes_intregs)(a0)
606         ld     r6 ,( 6*8+offes_intregs)(a0)
607         ld     r7 ,( 7*8+offes_intregs)(a0)
608         ld     r8 ,( 8*8+offes_intregs)(a0)
609         ld     r9 ,( 9*8+offes_intregs)(a0)
610         ld     r10,(10*8+offes_intregs)(a0)
611         ld     r11,(11*8+offes_intregs)(a0)
612         ld     r12,(12*8+offes_intregs)(a0)
613         /* r13 is pv                      */
614         ld     r14,(14*8+offes_intregs)(a0)
615         ld     r15,(15*8+offes_intregs)(a0)
616         ld     r16,(16*8+offes_intregs)(a0) /* link register */
617         ld     r17,(17*8+offes_intregs)(a0)
618         ld     r18,(18*8+offes_intregs)(a0)
619         ld     r19,(19*8+offes_intregs)(a0)
620         ld     r20,(20*8+offes_intregs)(a0)
621         ld     r21,(21*8+offes_intregs)(a0)
622         ld     r22,(22*8+offes_intregs)(a0)
623         ld     r23,(23*8+offes_intregs)(a0)
624         ld     r24,(24*8+offes_intregs)(a0)
625         ld     r25,(25*8+offes_intregs)(a0)
626         ld     r26,(26*8+offes_intregs)(a0)
627         ld     r27,(27*8+offes_intregs)(a0)
628         ld     r28,(28*8+offes_intregs)(a0)
629         ld     r29,(29*8+offes_intregs)(a0)
630         ld     r30,(30*8+offes_intregs)(a0)
631         ld     r31,(31*8+offes_intregs)(a0)
632         
633         lfd     fr0 ,( 0*8+offes_fltregs)(a0)
634         lfd     fr1 ,( 1*8+offes_fltregs)(a0)
635         lfd     fr2 ,( 2*8+offes_fltregs)(a0)
636         lfd     fr3 ,( 3*8+offes_fltregs)(a0)
637         lfd     fr4 ,( 4*8+offes_fltregs)(a0)
638         lfd     fr5 ,( 5*8+offes_fltregs)(a0)
639         lfd     fr6 ,( 6*8+offes_fltregs)(a0)
640         lfd     fr7 ,( 7*8+offes_fltregs)(a0)
641         lfd     fr8 ,( 8*8+offes_fltregs)(a0)
642         lfd     fr9 ,( 9*8+offes_fltregs)(a0)
643         lfd     fr10,(10*8+offes_fltregs)(a0)
644         lfd     fr11,(11*8+offes_fltregs)(a0)
645         lfd     fr12,(12*8+offes_fltregs)(a0)
646         lfd     fr13,(13*8+offes_fltregs)(a0)
647         lfd     fr14,(14*8+offes_fltregs)(a0)
648         lfd     fr15,(15*8+offes_fltregs)(a0)
649         lfd     fr16,(16*8+offes_fltregs)(a0)
650         lfd     fr17,(17*8+offes_fltregs)(a0)
651         lfd     fr18,(18*8+offes_fltregs)(a0)
652         lfd     fr19,(19*8+offes_fltregs)(a0)
653         lfd     fr20,(20*8+offes_fltregs)(a0)
654         lfd     fr21,(21*8+offes_fltregs)(a0)
655         lfd     fr22,(22*8+offes_fltregs)(a0)
656         lfd     fr23,(23*8+offes_fltregs)(a0)
657         lfd     fr24,(24*8+offes_fltregs)(a0)
658         lfd     fr25,(25*8+offes_fltregs)(a0)
659         lfd     fr26,(26*8+offes_fltregs)(a0)
660         lfd     fr27,(27*8+offes_fltregs)(a0)
661         lfd     fr28,(28*8+offes_fltregs)(a0)
662         lfd     fr29,(29*8+offes_fltregs)(a0)
663         lfd     fr30,(30*8+offes_fltregs)(a0)
664         lfd     fr31,(31*8+offes_fltregs)(a0)
665
666         /* restore link register */
667
668         mtlr    r16
669         
670         /* load new pc */
671
672         ld     itmp3,offes_pc(a0)
673
674         /* load a0 */
675         
676         ld     a0,(3*8+offes_intregs)(a0)
677
678         /* jump to new code */
679
680         mtctr   itmp3
681         bctr
682
683 #endif /* defined(ENABLE_REPLACEMENT) */
684
685 /* asm_cacheflush **************************************************************
686         copied from linux/arch/ppc64/kernel/vdso64/cacheflush.S
687         assumes 128 byte cache line size.
688         All registers used may be trashed for fun and profit.
689 *******************************************************************************/
690
691         .section ".opd","aw"
692         .align 3
693 asm_cacheflush:
694                 .quad   .asm_cacheflush,.TOC.@tocbase,0
695                 .previous
696                 .size asm_cacheflush, 24
697                 .type .asm_cacheflush,@function
698                 .globl .asm_cacheflush 
699 .asm_cacheflush:
700         /* construct the AND mask */
701         li      r6,   0xffffffffffff8000
702         ori     r6,r6,0x000000000000ff80
703
704         add     r4,r3,r4
705         and.    r3,r3,r6
706         addi    r4,r4,127
707         and.    r4,r4,r6
708         mr      r5,r3
709 1:
710         cmpld   r3,r4
711         bge     0f
712         dcbst   0,r3
713         addi    r3,r3,128
714         b       1b
715 0:
716         sync
717 1:
718         cmpld   r5,r4
719         bge     0f
720         icbi    0,r5
721         addi    r5,r5,128
722         b       1b
723 0:
724         sync
725         isync
726         blr
727
728
729 /* disable exec-stacks ********************************************************/
730
731 #if defined(__linux__) && defined(__ELF__)
732         .section .note.GNU-stack,"",%progbits
733 #endif
734
735
736 /*
737  * These are local overrides for various environment variables in Emacs.
738  * Please do not remove this and leave it at the end of the file, where
739  * Emacs will automagically detect them.
740  * ---------------------------------------------------------------------
741  * Local variables:
742  * mode: asm
743  * indent-tabs-mode: t
744  * c-basic-offset: 4
745  * tab-width: 4
746  * End:
747  * vim:noexpandtab:sw=4:ts=4:
748  */