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