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