* src/vm/jit/alpha/asmpart.S: Replaced __GNU__ with __linux__ for
[cacao.git] / src / vm / jit / i386 / asmpart.S
1 /* src/vm/jit/i386/asmpart.S - Java-C interface functions for i386
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 7661 2007-04-03 22:29:59Z twisti $
26
27 */
28
29
30 #include "config.h"
31
32 #include "md-asm.h"
33
34 #include "vm/jit/i386/arch.h"
35 #include "vm/jit/i386/md-abi.h"
36 #include "vm/jit/i386/offsets.h"
37
38 #include "vm/jit/abi-asm.h"
39 #include "vm/jit/methodheader.h"
40
41
42         .text
43
44
45 /* export functions ***********************************************************/
46
47         .globl asm_md_init
48
49         .globl asm_vm_call_method
50         .globl asm_vm_call_method_int
51         .globl asm_vm_call_method_long
52         .globl asm_vm_call_method_float
53         .globl asm_vm_call_method_double
54         .globl asm_vm_call_method_exception_handler
55         .globl asm_vm_call_method_end
56
57         .globl asm_call_jit_compiler
58         .globl asm_handle_nat_exception
59         .globl asm_handle_exception
60
61         .globl asm_abstractmethoderror
62
63         .globl asm_patcher_wrapper
64
65 #if defined(ENABLE_REPLACEMENT)
66         .globl asm_replacement_out
67         .globl asm_replacement_in
68 #endif
69
70         .globl asm_builtin_f2i
71         .globl asm_builtin_f2l
72         .globl asm_builtin_d2i
73         .globl asm_builtin_d2l
74
75         .globl asm_compare_and_swap
76         .globl asm_memory_barrier
77
78         .globl asm_criticalsections
79         .globl asm_getclassvalues_atomic
80
81         .globl asm_get_cycle_count
82
83
84 /* asm_md_init *****************************************************************
85
86    Initialize machine dependent stuff.
87
88    See: http://www.srware.com/linux_numerics.txt
89
90    This puts the X86 FPU in 64-bit precision mode.  The default under
91    Linux is to use 80-bit mode, which produces subtle differences from
92    FreeBSD and other systems, eg, (int)(1000*atof("0.3")) is 300 in
93    64-bit mode, 299 in 80-bit mode.
94
95    Fixes: http://bugs.debian.org/cgi-bin/bugreport.cgi?bug=350729
96
97 *******************************************************************************/
98
99 asm_md_init:
100         sub     $4,sp                       /* allocate space for the FPU state   */
101         fnstcw  (sp)                        /* get the FPU state                  */
102         mov     (sp),%eax
103         and     $0xfcff,%ax                 /* remove the extended mode flag      */
104         or      $0x0200,%ax                 /* put the double mode flag           */
105         mov     %eax,(sp)                   /* store new FPU state                */
106         fldcw   (sp)                        /* setup new FPU state                */
107         add     $4,sp
108         ret
109
110
111 /********************* function asm_calljavafunction ***************************
112 *                                                                              *
113 *   This function calls a Java-method (which possibly needs compilation)       *
114 *   with up to 4 address parameters.                                           *
115 *                                                                              *
116 *   This functions calls the JIT-compiler which eventually translates the      *
117 *   method into machine code.                                                  *
118 *                                                                              *
119 *   C-prototype:                                                               *
120 *    javaobject_header *asm_vm_call_method(methodinfo *m,                      *
121 *         u4 count, u4 size, void *callblock);                                 *
122 *                                                                              *
123 *******************************************************************************/
124
125         .align  8
126
127         .long   0                           /* catch type all                     */
128         .long   0                           /* handler pc                         */
129         .long   0                           /* end pc                             */
130         .long   0                           /* start pc                           */
131         .long   1                           /* extable size                       */
132         .long   0                           /* line number table start            */
133         .long   0                           /* line number table size             */
134         .long   0                           /* fltsave                            */
135         .long   0                           /* intsave                            */
136         .long   0                           /* isleaf                             */
137         .long   0                           /* IsSync                             */
138         .long   0                           /* frame size                         */
139         .long   0                           /* codeinfo pointer                   */
140
141 asm_vm_call_method:
142 asm_vm_call_method_int:
143 asm_vm_call_method_long:
144 asm_vm_call_method_float:
145 asm_vm_call_method_double:
146         push    bp
147         mov     sp,bp                       /* save stackptr                      */
148         sub     $(4*4),sp                   /* create stackframe                  */
149         and     $0xfffffff0,sp              /* align stack to 16-byte             */
150
151         mov     t0,0*4(sp)                  /* save registers                     */
152         mov     s1,1*4(sp)
153         mov     s2,2*4(sp)
154
155         mov     4*4(bp),itmp1               /* pointer to arg block (4(push)+4(return)+4+4)*/
156         mov     3*4(bp),itmp2               /* arg count            (4(push)+4(return)+4 */
157
158         mov     sp,s1                       /* save the stackpointer              */
159
160         test    itmp2,itmp2                 /* maybe we have no args              */
161         jle     L_asm_vm_call_method_copy_done
162
163         mov     itmp2,itmp3                 /* calculate stack size               */
164         mov     itmp1,%edi                  /* save pointer to arg block          */
165
166 calljava_calcstacksize:
167         mov     offvmargtype(itmp1),t0
168         test    $1,t0                       /* two word type?                     */
169         jz      calljava_onewordtype
170
171         sub     $4,sp                       /* add 1 slot to stackframe size      */
172
173 calljava_onewordtype:
174         sub     $4,sp                       /* add 1 slot to stackframe size      */
175         sub     $1,itmp3
176         test    itmp3,itmp3                 /* any args left?                     */
177         jz      calljava_setstack
178
179         add     $sizevmarg,itmp1            /* goto next argument block           */
180         jmp     calljava_calcstacksize
181                 
182 calljava_setstack:                              
183         mov     %edi,itmp1                  /* restore pointer to arg block       */
184         and     $0xfffffff0,sp              /* align stack to 16-byte             */
185         mov     sp,itmp3                    /* initialize pointer for copying     */
186
187 calljava_copyloop:
188         mov     offvmargdata(itmp1),t0      /* get 4-bytes of argument            */
189         mov     t0,(itmp3)                  /* and store them on the stack        */
190         add     $4,itmp3                    /* increase sp to next argument       */
191
192         mov     offvmargtype(itmp1),t0      /* get the argument type              */
193         test    $1,t0                       /* two word type?                     */
194         jz      calljava_copynext
195
196         mov     offvmargdata+4(itmp1),t0    /* get upper 4-bytes of 2 word type   */
197         mov     t0,(itmp3)                      
198         add     $4,itmp3                    /* increase sp to next argument       */
199
200 calljava_copynext:              
201         sub     $1,itmp2                    /* are there any args left?           */
202         test    itmp2,itmp2
203         jle     L_asm_vm_call_method_copy_done
204
205         add     $sizevmarg,itmp1            /* goto next argument block           */
206         jmp     calljava_copyloop
207
208 L_asm_vm_call_method_copy_done:
209         mov     2*4(bp),itmp1               /* move function pointer to itmp1     */
210
211         lea     L_asm_call_jit_compiler,mptr
212         mov     mptr,3*4(s1)
213         lea     (3*4-256)(s1),mptr          /* We subtract 256 to force the next  */
214                                             /* move instruction to have a 32-bit  */
215                                             /* offset.                            */
216
217         mov     (0*4+256)(mptr),itmp3       /* method call as in Java             */
218         call    *itmp3                      /* call JIT compiler                  */
219
220 L_asm_vm_call_method_return:
221         mov     s1,sp                       /* restore stackpointer               */
222
223         mov     0*4(sp),t0                  /* restore registers                  */
224         mov     1*4(sp),s1
225         mov     2*4(sp),s2
226
227         leave
228         ret
229
230 asm_vm_call_method_exception_handler:
231         push    xptr                        /* pass exception pointer             */
232         call    builtin_throw_exception
233         add     $4,sp
234 asm_vm_call_method_end:
235         jmp     L_asm_vm_call_method_return
236
237
238 /* asm_call_jit_compiler *******************************************************
239
240    Invokes the compiler for untranslated JavaVM methods.
241
242    Register R0 contains a pointer to the method info structure (prepared
243    by createcompilerstub). Using the return address in R26 and the
244    offset in the LDA instruction or using the value in methodptr R28 the
245    patching address for storing the method address can be computed:
246
247    Method address was either loaded using
248
249    i386_mov_imm_reg(a, REG_ITMP2)                ; invokestatic/special
250    i386_call_reg(REG_ITMP2)
251
252    or
253
254    i386_mov_membase_reg(REG_SP, 0, REG_ITMP1)    ; invokevirtual/interface
255    i386_mov_membase_reg(REG_ITMP1, OFFSET(, vftbl), REG_ITMP2)
256    i386_mov_membase_reg(REG_ITMP2, OFFSET(vftbl, table[0]) + \
257        sizeof(methodptr) * m->vftblindex, REG_ITMP1)
258    i386_call_reg(REG_ITMP1)
259
260    In the static case the method pointer can be computed using the
261    return address and the lda function following the jmp instruction.
262
263 *******************************************************************************/
264
265 asm_call_jit_compiler:
266 L_asm_call_jit_compiler:                /* required for PIC code              */
267         sub     $(4*4),sp                   /* keep stack 16-byte aligned         */
268
269         mov     itmp1,0*4(sp)               /* pass methodinfo pointer            */
270         mov     mptr,1*4(sp)                /* pass method pointer                */
271         mov     sp,itmp2                    /* pass java sp                       */
272         add     $((1+4)*4),itmp2
273         mov     itmp2,2*4(sp)
274         mov     4*4(sp),itmp3               /* pass java ra                       */
275         mov     itmp3,3*4(sp)
276         call    jit_asm_compile
277
278         add     $(4*4),sp                   /* remove stack frame                 */
279
280         test    v0,v0                       /* check for exception                */
281         je      L_asm_call_jit_compiler_exception
282
283         jmp             *v0                         /* ...and now call the new method     */
284
285 L_asm_call_jit_compiler_exception:
286         call    exceptions_get_and_clear_exception
287                                             /* v0 == xptr                         */
288         pop     xpc                         /* get return address                 */
289         sub     $2,xpc                      /* faulting address is ra - 2         */
290         jmp     L_asm_handle_exception
291
292
293 /* asm_handle_exception ********************************************************
294 *                                                                              *
295 *   This function handles an exception. It does not use the usual calling      *
296 *   conventions. The exception pointer is passed in REG_ITMP1 and the          *
297 *   pc from the exception raising position is passed in REG_ITMP2. It searches *
298 *   the local exception table for a handler. If no one is found, it unwinds    *
299 *   stacks and continues searching the callers.                                *
300 *                                                                              *
301 *******************************************************************************/
302
303 asm_handle_nat_exception:
304         add     $4,sp                       /* clear return address of native stub*/
305                 
306 asm_handle_exception:
307 L_asm_handle_exception:                 /* required for PIC code              */
308         sub     $((ARG_CNT+TMP_CNT+3)*4),sp /* keep stack 16-byte aligned         */
309
310         SAVE_ARGUMENT_REGISTERS(0)          /* we save arg and temp registers in  */
311         SAVE_TEMPORARY_REGISTERS(ARG_CNT)   /* case this is a leaf method         */
312
313         mov     $((ARG_CNT+TMP_CNT+3)*4),itmp3 /* prepare a3 for handle_exception */
314         mov     $1,t0                       /* set maybe-leaf flag                */
315
316 L_asm_handle_exception_stack_loop:
317         sub     $(12*4),sp                  /* keep stack 16-byte aligned         */
318         mov     xptr,4*4(sp)                /* save exception pointer             */
319         mov     xpc,5*4(sp)                 /* save exception pc                  */
320         add     sp,itmp3                    /* calculate Java sp into a3...       */
321         add     $(12*4),itmp3
322         mov     itmp3,7*4(sp)               /* ...and save it                     */
323         mov     t0,8*4(sp)                  /* save maybe-leaf flag               */
324
325         mov     xpc,0*4(sp)                 /* pass exception pc                  */
326         call    codegen_get_pv_from_pc
327         mov     v0,6*4(sp)                  /* save data segment pointer          */
328
329         mov     4*4(sp),itmp3               /* pass exception pointer             */
330         mov     itmp3,0*4(sp)
331         mov     5*4(sp),itmp3               /* pass exception pc                  */
332         mov     itmp3,1*4(sp)
333         mov     v0,2*4(sp)                  /* pass data segment pointer          */
334         mov     7*4(sp),itmp3               /* pass Java stack pointer            */
335         mov     itmp3,3*4(sp)
336         call    exceptions_handle_exception
337
338         test    v0,v0
339         jz      L_asm_handle_exception_not_catched
340
341         mov     v0,xpc                      /* move handlerpc into xpc            */
342         mov     4*4(sp),xptr                /* restore exception pointer          */
343         mov     8*4(sp),t0                  /* get maybe-leaf flag                */
344         add     $(12*4),sp                  /* free stackframe                    */
345
346         test    t0,t0                       /* test for maybe-leaf flag           */
347         jz      L_asm_handle_exception_no_leaf
348
349         RESTORE_ARGUMENT_REGISTERS(0)       /* if this is a leaf method, we have  */
350         RESTORE_TEMPORARY_REGISTERS(ARG_CNT)/* to restore arg and temp registers  */
351
352         add     $((ARG_CNT+TMP_CNT+3)*4),sp /* remove maybe-leaf stackframe       */
353
354 L_asm_handle_exception_no_leaf:
355         jmp     *xpc                        /* jump to exception handler          */
356
357 L_asm_handle_exception_not_catched:
358         mov     4*4(sp),xptr                /* restore exception pointer          */
359         mov     6*4(sp),itmp3               /* restore data segment pointer       */
360         mov     8*4(sp),t0                  /* get maybe-leaf flag                */
361         add     $(12*4),sp                  /* free stackframe                    */
362
363         test    t0,t0
364         jz      L_asm_handle_exception_no_leaf_stack
365
366         add     $((ARG_CNT+TMP_CNT+3)*4),sp /* remove maybe-leaf stackframe       */
367         xor     t0,t0                       /* clear the maybe-leaf flag          */
368
369 L_asm_handle_exception_no_leaf_stack:
370         mov     FrameSize(itmp3),itmp2      /* get frame size                     */
371         add     sp,itmp2                    /* pointer to save area               */
372
373         push    xptr                        /* we are out of registers            */
374
375         mov     IntSave(itmp3),itmp1        /* itmp1 = saved int register count   */
376         test    itmp1,itmp1
377         je      noint
378
379         cmp     $1,itmp1
380         je      int1
381         cmp     $2,itmp1
382         je      int2
383
384         mov     -3*4(itmp2),s0
385 int2:   
386         mov     -2*4(itmp2),s1
387 int1:   
388         mov     -1*4(itmp2),s2
389
390         shl     $2,itmp1                    /* multiply by 4 bytes                */
391         sub     itmp1,itmp2
392                 
393 noint:
394 #if 0
395         mov     FltSave(itmp3),itmp1        /* itmp1 = saved flt register count   */
396         test    itmp1,itmp1
397         je      noflt
398
399         cmp     $1,itmp1
400         je      flt1
401         cmp     $2,itmp1
402         je      flt2
403         cmp     $3,itmp1
404         je      flt3
405                 
406         fldl    -4*8(itmp2)
407         fstp    %st(1)
408 flt3:
409         fldl    -3*8(itmp2)
410         fstp    %st(2)
411 flt2:
412         fldl    -2*8(itmp2)
413         fstp    %st(3)
414 flt1:
415         fldl    -1*8(itmp2)
416         fstp    %st(4)
417                 
418 noflt:
419 #endif
420         pop     xptr                        /* restore exception pointer          */
421         mov     FrameSize(itmp3),itmp2      /* get frame size                     */
422         add     itmp2,sp                    /* unwind stack                       */
423
424         pop     xpc                         /* the new xpc is return address      */
425         sub     $2,xpc                      /* subtract 2-bytes for call          */
426
427         xor     itmp3,itmp3                 /* prepare a3 for handle_exception    */
428
429         jmp     L_asm_handle_exception_stack_loop
430                 
431
432 /* asm_abstractmethoderror *****************************************************
433
434    Creates and throws an AbstractMethodError.
435
436 *******************************************************************************/
437
438 asm_abstractmethoderror:
439         sub     $(3*4),sp                   /* keep stack 16-byte aligned         */
440         mov     sp,itmp1                    /* pass java sp                       */
441         add     $((1+3)*4),itmp1
442         mov     itmp1,0*4(sp)
443         mov     3*4(sp),itmp2               /* pass exception address             */
444         sub     $2,itmp2
445         mov     itmp2,1*4(sp)
446         call    exceptions_asm_new_abstractmethoderror
447                                             /* exception pointer is return value  */
448         add     $(3*4),sp                   /* remove stack frame                 */
449
450         pop     xpc                         /* get exception address              */
451         sub     $2,xpc                      /* exception address is ra - 2        */
452         jmp     L_asm_handle_exception
453
454
455 /* asm_patcher_wrapper *********************************************************
456
457    XXX
458
459    Stack layout:
460      24   return address
461      20   REG_ITMP3
462      16   pointer to virtual java_objectheader
463      12   last byte of machine code (xmcode)
464       8   machine code (which is patched back later)
465       4   unresolved field reference
466       0   patcher function pointer to call
467
468 *******************************************************************************/
469
470 asm_patcher_wrapper:
471         sub     $((1+4+4)*4),sp             /* keep stack 16-byte aligned         */
472
473         mov     itmp1,(0+4)*4(sp)           /* save itmp1 and itmp2               */
474         mov     itmp2,(1+4)*4(sp)
475
476         mov     sp,itmp1                    /* pass SP of patcher stub            */
477         add     $((1+4+4)*4),itmp1
478         mov     itmp1,0*4(sp)
479         movl    $0,1*4(sp)                  /* pass PV (if NULL, use findmethod)  */
480         movl    $0,2*4(sp)                  /* pass RA (it's on the stack)        */
481         call    patcher_wrapper
482         mov     v0,itmp3                    /* save return value                  */
483
484         mov     (0+4)*4(sp),itmp1           /* restore itmp1 and itmp2            */
485         mov     (1+4)*4(sp),itmp2
486
487         test    itmp3,itmp3                 /* exception thrown?                  */
488         jne     L_asm_patcher_wrapper_exception
489
490         mov     (5+1+4+4)*4(sp),itmp3       /* restore itmp3                      */
491         add     $((6+1+4+4)*4),sp           /* remove stack frame, keep RA        */
492
493         ret                                 /* jump to new patched code           */
494
495 L_asm_patcher_wrapper_exception:
496         add     $((6+1+4+4)*4),sp           /* remove stack frame, keep RA        */
497         mov     itmp3,xptr                  /* get exception                      */
498         pop     xpc                         /* get and remove return address      */
499         jmp     L_asm_handle_exception
500
501 #if defined(ENABLE_REPLACEMENT)
502
503 /* asm_replacement_out *********************************************************
504
505    This code is jumped to from the replacement-out stubs that are executed
506    when a thread reaches an activated replacement point.
507
508    The purpose of asm_replacement_out is to read out the parts of the
509    execution state that cannot be accessed from C code, store this state,
510    and then call the C function replace_me.
511
512    Stack layout:
513       4                 start of stack inside method to replace
514       0   rplpoint *    info on the replacement point that was reached
515
516 *******************************************************************************/
517
518 /* some room to accomodate changes of the stack frame size during replacement */
519         /* XXX we should find a cleaner solution here */
520 #define REPLACEMENT_ROOM  512
521
522 asm_replacement_out:
523     /* create stack frame */
524         sub     $(sizeexecutionstate + REPLACEMENT_ROOM),sp
525
526         /* save registers in execution state */
527         mov     %eax,(EAX*4+offes_intregs)(sp)
528         mov     %ebx,(EBX*4+offes_intregs)(sp)
529         mov     %ecx,(ECX*4+offes_intregs)(sp)
530         mov     %edx,(EDX*4+offes_intregs)(sp)
531         mov     %esi,(ESI*4+offes_intregs)(sp)
532         mov     %edi,(EDI*4+offes_intregs)(sp)
533         mov     %ebp,(EBP*4+offes_intregs)(sp)
534         movl    $0  ,(ESP*4+offes_intregs)(sp) /* not used */
535
536         /* calculate sp of method */
537         mov     sp,itmp1
538         add     $(sizeexecutionstate + REPLACEMENT_ROOM + 4),itmp1
539         mov     itmp1,(offes_sp)(sp)
540
541         /* pv must be looked up via AVL tree */
542         movl    $0,(offes_pv)(sp)
543
544         /* call replace_me */
545         mov     -4(itmp1),itmp1             /* rplpoint *                         */
546     push    sp                          /* arg1: execution state              */
547     push    itmp1                       /* arg0: replacement point            */
548     call    replace_me                  /* call C function replace_me         */
549
550
551 /* asm_replacement_in **********************************************************
552
553    This code writes the given execution state and jumps to the replacement
554    code.
555
556    This function never returns!
557
558    C prototype:
559       void asm_replacement_in(executionstate *es, replace_safestack_t *st);
560
561 *******************************************************************************/
562
563 asm_replacement_in:
564         /* get arguments */
565         mov     8(sp),%esi                  /* replace_safestack_t *st            */
566         mov     4(sp),%ebp                  /* executionstate *es == safe stack   */
567
568         /* switch to the safe stack and build a stack frame */
569         mov     %ebp,sp
570         sub             $(1*4),sp
571
572         /* call replace_build_execution_state(st) */
573         mov             %esi,(0*4)(sp)
574         call    replace_build_execution_state
575
576         /* set new sp */
577         mov     (offes_sp)(%ebp),sp
578
579         /* push address of new code */
580         push    (offes_pc)(%ebp)
581
582         /* allocate an executionstate_t on the stack */
583         sub             $(sizeexecutionstate),sp
584
585         /* call replace_free_safestack(st,& of allocated executionstate_t) */
586         push    sp   /* tmpes */
587         push    %esi /* st    */
588         call    replace_free_safestack
589         add     $(2*4),sp
590
591         /* copy registers from execution state */
592         mov     (EAX*4+offes_intregs)(sp),%eax
593         mov     (EBX*4+offes_intregs)(sp),%ebx
594         mov     (ECX*4+offes_intregs)(sp),%ecx
595         mov     (EDX*4+offes_intregs)(sp),%edx
596         mov     (ESI*4+offes_intregs)(sp),%esi
597         mov     (EDI*4+offes_intregs)(sp),%edi
598         mov     (EBP*4+offes_intregs)(sp),%ebp
599
600         /* pop the execution state off the stack */
601         add             $(sizeexecutionstate),sp
602
603         /* jump to new code, hold your thumbs! ;) */
604         ret
605
606 #endif /* defined(ENABLE_REPLACEMENT) */
607
608
609 /************************ function asm_builtin_x2x *****************************
610 *                                                                              *
611 *   Wrapper functions for corner cases                                         *
612 *                                                                              *
613 *******************************************************************************/
614
615 asm_builtin_f2i:
616         sub     $(3*4),%esp
617         fsts    (%esp)
618         call    builtin_f2i
619         add     $(3*4),%esp
620         ret
621
622 asm_builtin_d2i:
623         sub     $(3*4),%esp
624         fstl    (%esp)
625         call    builtin_d2i
626         add     $(3*4),%esp
627         ret
628
629 asm_builtin_f2l:
630         sub     $(3*4),%esp
631         fsts    (%esp)
632         call    builtin_f2l
633         add     $(3*4),%esp
634         ret
635
636 asm_builtin_d2l:
637         sub     $(3*4),%esp
638         fstl    (%esp)
639         call    builtin_d2l
640         add     $(3*4),%esp
641         ret
642
643
644 /* asm_compare_and_swap ********************************************************
645
646    Does an atomic compare and swap.  Required for the lock
647    implementation.
648
649    Atomically do the following: Check if the location still contains
650    `oldval`. If so, replace it by `newval` and return `oldval`.
651
652    RETURN VALUE:
653        the old value at *p
654
655    long compare_and_swap(volatile long *p, long oldval, long newval);
656
657 *******************************************************************************/
658
659 asm_compare_and_swap:
660         mov     1*4(sp),%ecx            /* load p into a register                 */
661         mov     2*4(sp),%eax            /* load oldval into return register       */
662         mov     3*4(sp),%edx            /* load newval into a register            */
663         lock; cmpxchgl %edx,0(%ecx)
664         ret
665
666
667 /* asm_memory_barrier **********************************************************
668
669    A memory barrier for the Java Memory Model.
670
671 *******************************************************************************/
672
673 asm_memory_barrier:
674         lock; add $0,0(sp)
675         ret
676
677                 
678 asm_getclassvalues_atomic:
679 _crit_restart2:
680         mov     4(%esp),%ecx        /* super */
681         mov     8(%esp),%edx        /* sub */
682 _crit_begin2:
683         mov     offbaseval(%ecx),%eax
684         mov     offdiffval(%ecx),%ecx
685         mov     offbaseval(%edx),%edx
686 _crit_end2:
687         push    %ebx
688         mov     16(%esp),%ebx      /* out */
689         mov     %eax,offcast_super_baseval(%ebx)
690         mov     %ecx,offcast_super_diffval(%ebx)
691         mov     %edx,offcast_sub_baseval(%ebx)
692         pop     %ebx
693         ret
694
695         .data
696
697 asm_criticalsections:
698 #if defined(ENABLE_THREADS)
699 #if 0
700         .long   _crit_begin1
701         .long   _crit_end1
702         .long   _crit_restart1
703 #endif
704         .long   _crit_begin2
705         .long   _crit_end2
706         .long   _crit_restart2
707 #endif
708         .long 0
709
710
711 /* disable exec-stacks ********************************************************/
712
713 #if defined(__linux__) && defined(__ELF__)
714         .section .note.GNU-stack,"",@progbits
715 #endif
716
717
718 /* asm_get_cycle_count *********************************************************
719
720    Get the current time-stamp counter from the CPU.
721
722 *******************************************************************************/
723
724 asm_get_cycle_count:
725         rdtsc
726         ret
727
728
729 /*
730  * These are local overrides for various environment variables in Emacs.
731  * Please do not remove this and leave it at the end of the file, where
732  * Emacs will automagically detect them.
733  * ---------------------------------------------------------------------
734  * Local variables:
735  * mode: asm
736  * indent-tabs-mode: t
737  * c-basic-offset: 4
738  * tab-width: 4
739  * End:
740  * vim:noexpandtab:sw=4:ts=4:
741  */