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