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