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