* src/vm/jit/x86_64/asmpart.S (asm_patcher_wrapper): Removed unused
[cacao.git] / src / vm / jit / x86_64 / asmpart.S
1 /* src/vm/jit/x86_64/asmpart.S - Java-C interface functions for x86_64
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; 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 7217 2007-01-16 12:52:48Z twisti $
26
27 */
28
29
30 #include "config.h"
31
32 #include "vm/jit/x86_64/arch.h"
33 #include "vm/jit/x86_64/md-abi.h"
34 #include "vm/jit/x86_64/md-asm.h"
35 #include "vm/jit/x86_64/offsets.h"
36
37 #include "vm/jit/abi-asm.h"
38 #include "vm/jit/methodheader.h"
39
40
41         .text
42
43
44 /* export functions ***********************************************************/
45
46         .globl asm_vm_call_method
47         .globl asm_vm_call_method_int
48         .globl asm_vm_call_method_long
49         .globl asm_vm_call_method_float
50         .globl asm_vm_call_method_double
51         .globl asm_vm_call_method_exception_handler
52
53         .globl asm_call_jit_compiler
54
55         .globl asm_handle_exception
56         .globl asm_handle_nat_exception
57
58         .globl asm_abstractmethoderror
59
60         .globl asm_patcher_wrapper
61
62 #if defined(ENABLE_REPLACEMENT)
63         .globl asm_replacement_out
64         .globl asm_replacement_in
65 #endif
66
67         .globl asm_builtin_f2i
68         .globl asm_builtin_f2l
69         .globl asm_builtin_d2i
70         .globl asm_builtin_d2l
71
72         .globl asm_criticalsections
73         .globl asm_getclassvalues_atomic
74
75
76 /********************* function asm_calljavafunction ***************************
77 *                                                                              *
78 *   This function calls a Java-method (which possibly needs compilation)       *
79 *   with up to 4 address parameters.                                           *
80 *                                                                              *
81 *   This functions calls the JIT-compiler which eventually translates the      *
82 *   method into machine code.                                                  *
83 *                                                                              *
84 *   C-prototype:                                                               *
85 *    javaobject_header *asm_calljavamethod (methodinfo *m,                     *
86 *         void *arg1, void *arg2, void *arg3, void *arg4);                     *
87 *                                                                              *
88 *******************************************************************************/
89
90         .align  8
91
92         .quad   0                           /* catch type all                     */
93         .quad   0                           /* handler pc                         */
94         .quad   0                           /* end pc                             */
95         .quad   0                           /* start pc                           */
96         .long   1                           /* extable size                       */
97         .long   0                           /* ALIGNMENT PADDING                  */
98         .quad   0                           /* line number table  start           */
99         .quad   0                           /* line number table  size            */
100         .long   0                           /* ALIGNMENT PADDING                  */
101         .long   0                           /* fltsave                            */
102         .long   0                           /* intsave                            */
103         .long   0                           /* isleaf                             */
104         .long   0                           /* IsSync                             */
105         .long   0                           /* frame size                         */
106         .quad   0                           /* codeinfo pointer                   */
107
108 asm_vm_call_method:
109 asm_vm_call_method_int:
110 asm_vm_call_method_long:
111 asm_vm_call_method_float:
112 asm_vm_call_method_double:
113         sub     $(7*8),sp                   /* keep stack 16-byte aligned         */
114         mov     %rbx,0*8(sp)                /* %rbx is not a callee saved in cacao*/
115         mov     s0,1*8(sp)
116         mov     s1,2*8(sp)
117         mov     s2,3*8(sp)
118         mov     s3,4*8(sp)
119         mov     s4,5*8(sp)
120
121         mov     a0,itmp1                    /* move method pointer for compiler   */
122         xor     %rbp,%rbp                   /* set argument stack frame to zero   */
123
124         test    a1,a1                       /* maybe we have no args...           */
125         jle     L_copy_done
126
127         mov     a1,itmp3                    /* arg count                          */
128         mov     a2,itmp2                    /* pointer to arg block               */
129
130         mov     itmp2,%r14                  /* save argument block pointer        */
131         mov     itmp3,%r15                  /* save argument count                */
132
133         sub     $sizevmarg,itmp2            /* initialize pointer (smaller code)  */
134         add     $1,itmp3                    /* initialize argument count          */
135         xor     %r12,%r12                   /* initialize integer argument counter*/
136         xor     %r13,%r13                   /* initialize float argument counter  */
137
138 L_register_copy:
139         add     $sizevmarg,itmp2            /* goto next argument block           */
140         dec     itmp3                       /* argument count - 1                 */
141         jz      L_register_copy_done
142         andb    $0x02,offvmargtype(itmp2)   /* is this a float/double type?       */
143         jnz     L_register_handle_float     /* yes, handle it                     */
144
145         cmp     $INT_ARG_CNT,%r12           /* are we out of integer argument     */
146         je      L_register_copy             /* register? yes, next loop           */
147
148         lea     jumptable_integer(%rip),%rbp
149         mov     0(%rbp,%r12,8),%rbx
150         inc     %r12                      /* integer argument counter + 1         */
151         jmp     *%rbx
152
153 L_register_handle_float:
154         cmp     $FLT_ARG_CNT,%r13         /* are we out of float argument         */
155         je      L_register_copy           /* register? yes, next loop             */
156
157         lea     jumptable_float(%rip),%rbp
158         mov     0(%rbp,%r13,8),%rbx
159         inc     %r13                      /* float argument counter + 1           */
160         jmp     *%rbx
161         
162 L_register_copy_done:
163         mov     %r15,%rbp                 /* calculate remaining arguments        */
164         sub     %r12,%rbp                 /* - integer arguments in registers     */
165         sub     %r13,%rbp                 /* - float arguments in registers       */
166         jle     L_copy_done               /* are all assigned to registers?       */
167
168         and     $0xfffffffffffffffe,%rbp  /* keep stack 16-byte aligned           */
169         shl     $3,%rbp                   /* calculate stack size                 */
170         sub     %rbp,sp                   /* stack frame for arguments            */
171         mov     sp,%rbx                   /* use %rbx as temp sp                  */
172
173         sub     $sizevmarg,%r14           /* initialize pointer (smaller code)    */
174         add     $1,%r15                   /* initialize argument count            */
175                 
176 L_stack_copy_loop:
177         add     $sizevmarg,%r14           /* goto next argument block             */
178         dec     %r15                      /* are there any arguments left?        */
179         jz      L_copy_done               /* no test needed after dec             */
180
181         andb    $0x02,offvmargtype(%r14)    /* is this a float/double type?       */
182         jnz     L_stack_handle_float
183         dec     %r12                        /* arguments assigned to registers    */
184         jge     L_stack_copy_loop
185         jmp     L_stack_copy
186
187 L_stack_handle_float:
188         dec     %r13                        /* arguments assigned to registers    */
189         jge     L_stack_copy_loop
190
191 L_stack_copy:
192         mov     offvmargdata(%r14),itmp3    /* copy s8 argument onto stack        */
193         mov     itmp3,0(%rbx)
194         add     $8,%rbx                     /* increase sp to next argument       */
195         jmp     L_stack_copy_loop
196
197 L_copy_done:
198                                             /* itmp1 still contains method pointer*/
199         lea     L_asm_call_jit_compiler(%rip),mptr
200         mov     sp,itmp3                    /* calculate the old stack pointer    */
201         add     bp,itmp3
202         mov     mptr,6*8(itmp3)
203         lea     (6*8-256)(itmp3),mptr       /* We subtract 256 to force the next  */
204                                             /* move instruction to have a 32-bit  */
205                                             /* offset.                            */
206
207         mov     (0*8+256)(mptr),itmp3       /* method call as in Java             */
208         call    *itmp3                      /* call JIT compiler                  */
209
210         add     bp,sp                       /* remove argument stack frame if any */
211
212 L_asm_vm_call_method_return:
213         mov     0*8(sp),%rbx                /* restore callee saved registers     */
214         mov     1*8(sp),s0
215         mov     2*8(sp),s1
216         mov     3*8(sp),s2
217         mov     4*8(sp),s3
218         mov     5*8(sp),s4
219         add     $(7*8),sp                   /* free stack space                   */
220         ret
221                 
222 asm_vm_call_method_exception_handler:
223         mov     xptr,a0                     /* pass exception pointer             */
224         call    builtin_throw_exception@PLT
225         jmp     L_asm_vm_call_method_return
226
227
228 jumptable_integer:
229         .quad   handle_a0
230         .quad   handle_a1
231         .quad   handle_a2
232         .quad   handle_a3
233         .quad   handle_a4
234         .quad   handle_a5
235
236 handle_a0:
237         mov     offvmargdata(itmp2),a0
238         jmp     L_register_copy
239 handle_a1:
240         mov     offvmargdata(itmp2),a1
241         jmp     L_register_copy
242 handle_a2:
243         mov     offvmargdata(itmp2),a2
244         jmp     L_register_copy
245 handle_a3:
246         mov     offvmargdata(itmp2),a3
247         jmp     L_register_copy
248 handle_a4:
249         mov     offvmargdata(itmp2),a4
250         jmp     L_register_copy
251 handle_a5:
252         mov     offvmargdata(itmp2),a5
253         jmp     L_register_copy
254
255
256 jumptable_float:
257         .quad   handle_fa0
258         .quad   handle_fa1
259         .quad   handle_fa2
260         .quad   handle_fa3
261         .quad   handle_fa4
262         .quad   handle_fa5
263         .quad   handle_fa6
264         .quad   handle_fa7
265
266 handle_fa0:
267         movq    offvmargdata(itmp2),fa0
268         jmp     L_register_copy
269 handle_fa1:
270         movq    offvmargdata(itmp2),fa1
271         jmp     L_register_copy
272 handle_fa2:
273         movq    offvmargdata(itmp2),fa2
274         jmp     L_register_copy
275 handle_fa3:
276         movq    offvmargdata(itmp2),fa3
277         jmp     L_register_copy
278 handle_fa4:
279         movq    offvmargdata(itmp2),fa4
280         jmp     L_register_copy
281 handle_fa5:
282         movq    offvmargdata(itmp2),fa5
283         jmp     L_register_copy
284 handle_fa6:
285         movq    offvmargdata(itmp2),fa6
286         jmp     L_register_copy
287 handle_fa7:
288         movq    offvmargdata(itmp2),fa7
289         jmp     L_register_copy
290
291
292 /****************** function asm_call_jit_compiler *****************************
293 *                                                                              *
294 *   invokes the compiler for untranslated JavaVM methods.                      *
295 *                                                                              *
296 *   Register R0 contains a pointer to the method info structure (prepared      *
297 *   by createcompilerstub). Using the return address in R26 and the            *
298 *   offset in the LDA instruction or using the value in methodptr R28 the      *
299 *   patching address for storing the method address can be computed:           *
300 *                                                                              *
301 *   method address was either loaded using                                     *
302 *                                                                              *
303 *   i386_mov_imm_reg(a, REG_ITMP2)                ; invokestatic/special       *
304 *   i386_call_reg(REG_ITMP2)                                                   *
305 *                                                                              *
306 *   or                                                                         *
307 *                                                                              *
308 *   i386_mov_membase_reg(REG_SP, 0, REG_ITMP2)    ; invokevirtual/interface    *
309 *   i386_mov_membase_reg(REG_ITMP2, OFFSET(, vftbl), REG_ITMP3)                *
310 *   i386_mov_membase_reg(REG_ITMP3, OFFSET(vftbl, table[0]) + \                *
311 *       sizeof(methodptr) * m->vftblindex, REG_ITMP1)                          *
312 *   i386_call_reg(REG_ITMP1)                                                   *
313 *                                                                              *
314 *   in the static case the method pointer can be computed using the            *
315 *   return address and the lda function following the jmp instruction          *
316 *                                                                              *
317 *******************************************************************************/
318
319 asm_call_jit_compiler:
320 L_asm_call_jit_compiler:                /* required for PIC code              */
321         sub     $(ARG_CNT+1)*8,sp           /* +1: keep stack 16-byte aligned     */
322
323         SAVE_ARGUMENT_REGISTERS(0)
324
325         mov     itmp1,a0                    /* pass methodinfo pointer            */
326         mov     mptr,a1                     /* pass method pointer                */
327         mov     sp,a2                       /* pass java sp                       */
328         add     $(1+ARG_CNT+1)*8,a2
329         mov     (ARG_CNT+1)*8(sp),a3        /* pass ra to java function           */
330         call    jit_asm_compile@PLT
331
332         RESTORE_ARGUMENT_REGISTERS(0)
333
334         add     $(ARG_CNT+1)*8,sp           /* remove stack frame                 */
335
336         test    v0,v0                       /* check for exception                */
337         je      L_asm_call_jit_compiler_exception
338
339         jmp     *v0                         /* ...and now call the new method     */
340
341 L_asm_call_jit_compiler_exception:
342         call    exceptions_get_and_clear_exception@PLT
343         pop     xpc                         /* delete return address              */
344         sub     $3,xpc                      /* faulting address is ra - 3         */
345         jmp     L_asm_handle_exception
346
347
348 /* asm_handle_exception ********************************************************
349 *                                                                              *
350 *   This function handles an exception. It does not use the usual calling      *
351 *   conventions. The exception pointer is passed in REG_ITMP1 and the          *
352 *   pc from the exception raising position is passed in REG_ITMP2. It searches *
353 *   the local exception table for a handler. If no one is found, it unwinds    *
354 *   stacks and continues searching the callers.                                *
355 *                                                                              *
356 *******************************************************************************/
357
358 asm_handle_nat_exception:
359         add     $8,sp                       /* clear return address of native stub*/
360                 
361 asm_handle_exception:
362 L_asm_handle_exception:                 /* required for PIC code              */
363         sub     $((ARG_CNT+TMP_CNT)*8),sp   /* create maybe-leaf stackframe       */
364
365         SAVE_ARGUMENT_REGISTERS(0)          /* we save arg and temp registers in  */
366         SAVE_TEMPORARY_REGISTERS(ARG_CNT)   /* case this is a leaf method         */
367
368         mov     $((ARG_CNT+TMP_CNT)*8),a3   /* prepare a3 for handle_exception    */
369         mov     $1,t0                       /* set maybe-leaf flag                */
370
371 L_asm_handle_exception_stack_loop:
372         sub     $(6*8),sp
373         mov     xptr,0*8(sp)                /* save exception pointer             */
374         mov     xpc,1*8(sp)                 /* save exception pc                  */
375         add     sp,a3                       /* calculate Java sp into a3...       */
376         add     $(6*8),a3
377         mov     a3,3*8(sp)                  /* ...and save it                     */
378         mov     t0,4*8(sp)                  /* save maybe-leaf flag               */
379
380         mov     xpc,a0                      /* exception pc                       */
381         call    codegen_get_pv_from_pc@PLT
382         mov     v0,2*8(sp)                  /* save data segment pointer          */
383         
384         mov     0*8(sp),a0                  /* pass exception pointer             */
385         mov     1*8(sp),a1                  /* pass exception pc                  */
386         mov     v0,a2                       /* pass data segment pointer          */
387         mov     3*8(sp),a3                  /* pass Java stack pointer            */
388         call    exceptions_handle_exception@PLT
389
390         test    v0,v0
391         jz      L_asm_handle_exception_not_catched
392
393         mov     v0,xpc                      /* move handlerpc into xpc            */
394         mov     0*8(sp),xptr                /* restore exception pointer          */
395         mov     4*8(sp),t0                  /* get maybe-leaf flag                */
396         add     $(6*8),sp                   /* free stack frame                   */
397
398         test    t0,t0                       /* test for maybe-leaf flag           */
399         jz      L_asm_handle_exception_no_leaf
400
401         RESTORE_ARGUMENT_REGISTERS(0)       /* if this is a leaf method, we have  */
402         RESTORE_TEMPORARY_REGISTERS(ARG_CNT)/* to restore arg and temp registers  */
403
404         add     $((ARG_CNT+TMP_CNT)*8),sp   /* remove maybe-leaf stackframe       */
405
406 L_asm_handle_exception_no_leaf:
407         jmp     *xpc                        /* jump to the handler                */
408
409 L_asm_handle_exception_not_catched:
410         mov     0*8(sp),xptr                /* restore exception pointer          */
411         mov     2*8(sp),itmp3               /* restore data segment pointer       */
412         mov     4*8(sp),t0                  /* get maybe-leaf flag                */
413         add     $(6*8),sp
414
415         test    t0,t0
416         jz      L_asm_handle_exception_no_leaf_stack
417
418         add     $((ARG_CNT+TMP_CNT)*8),sp   /* remove maybe-leaf stackframe       */
419         xor     t0,t0                       /* clear the isleaf flags             */
420
421 L_asm_handle_exception_no_leaf_stack:
422         mov     FrameSize(itmp3),itmp2l     /* get frame size                     */
423         add     sp,itmp2                    /* pointer to save area               */
424         
425         mov     IntSave(itmp3),a0l          /* a0l = saved int register count     */
426         test    a0l,a0l
427         je      noint
428         
429         cmp     $1,a0l
430         je      int1
431         cmp     $2,a0l
432         je      int2
433         cmp     $3,a0l
434         je      int3
435         cmp     $4,a0l
436         je      int4
437         
438         mov     -5*8(itmp2),s0
439 int4:   
440         mov     -4*8(itmp2),s1
441 int3:   
442         mov     -3*8(itmp2),s2
443 int2:   
444         mov     -2*8(itmp2),s3
445 int1:   
446         mov     -1*8(itmp2),s4
447
448         shl     $3,a0l                      /* multiply by 8 bytes                */
449         sub     a0,itmp2
450                 
451 noint:
452 #if 0
453         mov     FltSave(itmp3),a0l          /* a0l = saved flt register count     */
454         test    a0l,a0l
455         je      noflt
456         
457         cmpl    $1,a0l
458         je      flt1
459         cmpl    $2,a0l
460         je      flt2
461         cmpl    $3,a0l
462         je      flt3
463         cmpl    $4,a0l
464         je      flt4
465
466         movq    -5*8(itmp2),%xmm11
467 flt4:   
468         movq    -4*8(itmp2),%xmm12
469 flt3:   
470         movq    -3*8(itmp2),%xmm13
471 flt2:   
472         movq    -2*8(itmp2),%xmm14
473 flt1:   
474         movq    -1*8(itmp2),%xmm15
475                 
476 noflt:
477 #endif
478         mov     FrameSize(itmp3),itmp2l     /* get frame size                     */
479         add     itmp2,sp                    /* unwind stack                       */
480
481                                             /* exception pointer is still set     */
482         pop     xpc                         /* the new xpc is return address      */
483         sub     $3,xpc                      /* subtract 3 bytes for call          */
484
485         xor     a3,a3                       /* prepare a3 for handle_exception    */
486         
487         jmp             L_asm_handle_exception_stack_loop
488
489
490 /* asm_abstractmethoderror *****************************************************
491
492    Creates and throws an AbstractMethodError.
493
494 *******************************************************************************/
495
496 asm_abstractmethoderror:
497         mov     sp,a0                       /* pass java sp                       */
498         add     $1*8,a0
499         mov     0*8(sp),a1                  /* pass exception address             */
500         sub     $3,a1
501         call    exceptions_asm_new_abstractmethoderror@PLT
502                                             /* exception pointer is return value  */
503         pop     xpc                         /* get exception address              */
504         sub     $3,xpc                      /* exception address is ra - 3        */
505         jmp     L_asm_handle_exception
506
507
508 /* asm_patcher_wrapper *********************************************************
509
510    XXX
511
512    Stack layout:
513      40   return address
514      32   pointer to virtual java_objectheader
515      24   machine code (which is patched back later)
516      16   unresolved class/method/field reference
517       8   data segment displacement from load instructions
518       0   pointer to patcher function
519      -8   bp
520
521 *******************************************************************************/
522
523 asm_patcher_wrapper:
524         push    bp                          /* save base pointer                  */
525         mov     sp,bp                       /* move actual sp to bp               */
526         sub     $(3+ARG_CNT+TMP_CNT)*8,sp
527         and     $0xfffffffffffffff0,sp      /* align sp to 16-byte (this is for   */
528                                             /* leaf functions)                    */
529
530         SAVE_ARGUMENT_REGISTERS(3)
531         SAVE_TEMPORARY_REGISTERS(3+ARG_CNT)
532
533         mov     itmp1,0*8(sp)               /* save itmp1 and itmp2               */
534         mov     itmp2,1*8(sp)               /* can be used by some instructions   */
535
536         mov     bp,a0                       /* pass SP of patcher stub            */
537         add     $(1*8),a0
538         mov     $0,a1                       /* pass PV (if NULL, use findmethod)  */
539         mov     $0,a2                       /* pass RA (it's on the stack)        */
540         call    patcher_wrapper@PLT
541         mov     v0,2*8(sp)                  /* save return value                  */
542
543         RESTORE_ARGUMENT_REGISTERS(3)
544         RESTORE_TEMPORARY_REGISTERS(3+ARG_CNT)
545
546         mov     0*8(sp),itmp1               /* restore itmp1 and itmp2            */
547         mov     1*8(sp),itmp2               /* can be used by some instructions   */
548         mov     2*8(sp),itmp3               /* restore return value               */
549
550         mov     bp,sp                       /* restore original sp                */
551         pop     bp                          /* restore bp                         */
552         add     $(5*8),sp                   /* remove patcher stackframe, keep RA */
553
554         test    itmp3,itmp3                 /* exception thrown?                  */
555         jne     L_asm_patcher_wrapper_exception
556         ret                                 /* call new patched code              */
557
558 L_asm_patcher_wrapper_exception:
559         mov     itmp3,xptr                  /* get exception                      */
560         pop     xpc                         /* get and remove return address      */
561         jmp     L_asm_handle_exception
562
563 #if defined(ENABLE_REPLACEMENT)
564
565 /* asm_replacement_out *********************************************************
566
567    This code is jumped to from the replacement-out stubs that are executed
568    when a thread reaches an activated replacement point.
569
570    The purpose of asm_replacement_out is to read out the parts of the
571    execution state that cannot be accessed from C code, store this state,
572    and then call the C function replace_me.
573
574    Stack layout:
575       8                 start of stack inside method to replace
576       0   rplpoint *    info on the replacement point that was reached
577
578 *******************************************************************************/
579
580 /* some room to accomodate changes of the stack frame size during replacement */
581         /* XXX we should find a cleaner solution here */
582 #define REPLACEMENT_ROOM  512
583
584 asm_replacement_out:
585     /* create stack frame */
586         sub     $(sizeexecutionstate + REPLACEMENT_ROOM),sp
587
588         /* save registers in execution state */
589         mov     %rax,(RAX*8+offes_intregs)(sp)
590         mov     %rbx,(RBX*8+offes_intregs)(sp)
591         mov     %rcx,(RCX*8+offes_intregs)(sp)
592         mov     %rdx,(RDX*8+offes_intregs)(sp)
593         mov     %rsi,(RSI*8+offes_intregs)(sp)
594         mov     %rdi,(RDI*8+offes_intregs)(sp)
595         mov     %rbp,(RBP*8+offes_intregs)(sp)
596         movq    $0  ,(RSP*8+offes_intregs)(sp) /* not used */
597         mov     %r8 ,(R8 *8+offes_intregs)(sp)
598         mov     %r9 ,(R9 *8+offes_intregs)(sp)
599         mov     %r10,(R10*8+offes_intregs)(sp)
600         mov     %r11,(R11*8+offes_intregs)(sp)
601         mov     %r12,(R12*8+offes_intregs)(sp)
602         mov     %r13,(R13*8+offes_intregs)(sp)
603         mov     %r14,(R14*8+offes_intregs)(sp)
604         mov     %r15,(R15*8+offes_intregs)(sp)
605
606         movq    %xmm0 ,(XMM0 *8+offes_fltregs)(sp)
607         movq    %xmm1 ,(XMM1 *8+offes_fltregs)(sp)
608         movq    %xmm2 ,(XMM2 *8+offes_fltregs)(sp)
609         movq    %xmm3 ,(XMM3 *8+offes_fltregs)(sp)
610         movq    %xmm4 ,(XMM4 *8+offes_fltregs)(sp)
611         movq    %xmm5 ,(XMM5 *8+offes_fltregs)(sp)
612         movq    %xmm6 ,(XMM6 *8+offes_fltregs)(sp)
613         movq    %xmm7 ,(XMM7 *8+offes_fltregs)(sp)
614         movq    %xmm8 ,(XMM8 *8+offes_fltregs)(sp)
615         movq    %xmm9 ,(XMM9 *8+offes_fltregs)(sp)
616         movq    %xmm10,(XMM10*8+offes_fltregs)(sp)
617         movq    %xmm11,(XMM11*8+offes_fltregs)(sp)
618         movq    %xmm12,(XMM12*8+offes_fltregs)(sp)
619         movq    %xmm13,(XMM13*8+offes_fltregs)(sp)
620         movq    %xmm14,(XMM14*8+offes_fltregs)(sp)
621         movq    %xmm15,(XMM15*8+offes_fltregs)(sp)
622
623         /* calculate sp of method */
624         mov     sp,itmp1
625         add     $(sizeexecutionstate + REPLACEMENT_ROOM + 8),itmp1
626         mov     itmp1,(offes_sp)(sp)
627
628         /* pv must be looked up via AVL tree */
629         movq    $0,(offes_pv)(sp)
630
631         /* call replace_me */
632         mov     -8(itmp1),a0                /* rplpoint *                         */
633     mov     sp,a1                       /* arg1: execution state              */
634     call    replace_me@PLT              /* call C function replace_me         */
635     call    abort@PLT                   /* NEVER REACHED                      */
636
637 /* asm_replacement_in **********************************************************
638
639    This code writes the given execution state and jumps to the replacement
640    code.
641
642    This function never returns!
643
644    C prototype:
645       void asm_replacement_in(executionstate *es, replace_safestack_t *st);
646
647 *******************************************************************************/
648
649 asm_replacement_in:
650         /* get arguments */
651         mov     a1,s1                       /* replace_safestack_t *st            */
652         mov     a0,%rbp                     /* executionstate *es == safe stack   */
653
654         /* switch to the safe stack */
655         mov     %rbp,sp
656
657         /* call replace_build_execution_state(st) */
658         mov             s1,a0
659         call    replace_build_execution_state@PLT
660
661         /* set new sp */
662         mov     (offes_sp)(%rbp),sp
663
664         /* push address of new code */
665         pushq   (offes_pc)(%rbp)
666
667         /* allocate an executionstate_t on the stack */
668         sub             $(sizeexecutionstate),sp
669
670         /* call replace_free_safestack(st,& of allocated executionstate_t) */
671         mov             sp,a1
672         mov             s1,a0
673         call    replace_free_safestack@PLT
674
675         /* copy registers from execution state */
676         movq    (XMM0 *8+offes_fltregs)(sp),%xmm0
677         movq    (XMM1 *8+offes_fltregs)(sp),%xmm1
678         movq    (XMM2 *8+offes_fltregs)(sp),%xmm2
679         movq    (XMM3 *8+offes_fltregs)(sp),%xmm3
680         movq    (XMM4 *8+offes_fltregs)(sp),%xmm4
681         movq    (XMM5 *8+offes_fltregs)(sp),%xmm5
682         movq    (XMM6 *8+offes_fltregs)(sp),%xmm6
683         movq    (XMM7 *8+offes_fltregs)(sp),%xmm7
684         movq    (XMM8 *8+offes_fltregs)(sp),%xmm8
685         movq    (XMM9 *8+offes_fltregs)(sp),%xmm9
686         movq    (XMM10*8+offes_fltregs)(sp),%xmm10
687         movq    (XMM11*8+offes_fltregs)(sp),%xmm11
688         movq    (XMM12*8+offes_fltregs)(sp),%xmm12
689         movq    (XMM13*8+offes_fltregs)(sp),%xmm13
690         movq    (XMM14*8+offes_fltregs)(sp),%xmm14
691         movq    (XMM15*8+offes_fltregs)(sp),%xmm15
692
693         mov     (RAX*8+offes_intregs)(sp),%rax
694         mov     (RBX*8+offes_intregs)(sp),%rbx
695         mov     (RCX*8+offes_intregs)(sp),%rcx
696         mov     (RDX*8+offes_intregs)(sp),%rdx
697         mov     (RSI*8+offes_intregs)(sp),%rsi
698         mov     (RDI*8+offes_intregs)(sp),%rdi
699         mov     (RBP*8+offes_intregs)(sp),%rbp
700         mov     (R8 *8+offes_intregs)(sp),%r8
701         mov     (R9 *8+offes_intregs)(sp),%r9
702         mov     (R10*8+offes_intregs)(sp),%r10
703         mov     (R11*8+offes_intregs)(sp),%r11
704         mov     (R12*8+offes_intregs)(sp),%r12
705         mov     (R13*8+offes_intregs)(sp),%r13
706         mov     (R14*8+offes_intregs)(sp),%r14
707         mov     (R15*8+offes_intregs)(sp),%r15
708
709         /* pop the execution state off the stack */
710         add             $(sizeexecutionstate),sp
711
712         /* jump to new code */
713         ret
714
715 #endif /* defined(ENABLE_REPLACEMENT) */
716
717
718 /* asm_builtin_x2x *************************************************************
719 *                                                                              *
720 *   Wrapper functions for float to int corner cases                            *
721 *                                                                              *
722 *******************************************************************************/
723
724 asm_builtin_f2i:
725         sub     $(ARG_CNT*8),sp
726         
727         SAVE_ARGUMENT_REGISTERS(0)
728         
729         movq    ftmp1,fa0
730         call    builtin_f2i@PLT
731         
732         RESTORE_ARGUMENT_REGISTERS(0)
733         
734         add     $(ARG_CNT*8),sp
735         ret
736
737
738 asm_builtin_f2l:
739         sub     $(ARG_CNT*8),sp
740         
741         SAVE_ARGUMENT_REGISTERS(0)
742         
743         movq    ftmp1,fa0
744         call    builtin_f2l@PLT
745         
746         RESTORE_ARGUMENT_REGISTERS(0)
747         
748         add     $(ARG_CNT*8),sp
749         ret
750
751
752 asm_builtin_d2i:
753         sub     $(ARG_CNT*8),sp
754         
755         SAVE_ARGUMENT_REGISTERS(0)
756         
757         movq    ftmp1,fa0
758         call    builtin_d2i@PLT
759         
760         RESTORE_ARGUMENT_REGISTERS(0)
761         
762         add     $(ARG_CNT*8),sp
763         ret
764
765
766 asm_builtin_d2l:
767         sub     $(ARG_CNT*8),sp
768         
769         SAVE_ARGUMENT_REGISTERS(0)
770         
771         movq    ftmp1,fa0
772         call    builtin_d2l@PLT
773         
774         RESTORE_ARGUMENT_REGISTERS(0)
775         
776         add     $(ARG_CNT*8),sp
777         ret
778
779
780 asm_getclassvalues_atomic:
781 _crit_restart:
782 _crit_begin:
783         movl    offbaseval(a0),itmp1l
784         movl    offdiffval(a0),itmp2l
785         movl    offbaseval(a1),itmp3l
786 _crit_end:
787         movl    itmp1l,offcast_super_baseval(a2)
788         movl    itmp2l,offcast_super_diffval(a2)
789         movl    itmp3l,offcast_sub_baseval(a2)
790         ret
791
792         .data
793                 
794 asm_criticalsections:
795 #if defined(ENABLE_THREADS)
796         .quad   _crit_begin
797         .quad   _crit_end
798         .quad   _crit_restart
799 #endif
800         .quad 0
801
802
803 /* Disable exec-stacks, required for Gentoo ***********************************/
804
805 #if defined(__GCC__) && defined(__ELF__)
806         .section .note.GNU-stack,"",@progbits
807 #endif
808
809
810 /*
811  * These are local overrides for various environment variables in Emacs.
812  * Please do not remove this and leave it at the end of the file, where
813  * Emacs will automagically detect them.
814  * ---------------------------------------------------------------------
815  * Local variables:
816  * mode: asm
817  * indent-tabs-mode: t
818  * c-basic-offset: 4
819  * tab-width: 4
820  * End:
821  * vim:noexpandtab:sw=4:ts=4:
822  */