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