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