source: trunk/src/opengl/mesa/assyntax.h@ 3721

Last change on this file since 3721 was 3582, checked in by jeroen, 25 years ago

* empty log message *

File size: 63.4 KB
Line 
1/* $Id: assyntax.h,v 1.2 2000-05-21 20:04:51 jeroen Exp $ */
2
3#ifndef __ASSYNTAX_H__
4#define __ASSYNTAX_H__
5
6/*
7 * Copyright 1992 Vrije Universiteit, The Netherlands
8 *
9 * Permission to use, copy, modify, and distribute this software and its
10 * documentation for any purpose and without fee is hereby granted, provided
11 * that the above copyright notice appear in all copies and that both that
12 * copyright notice and this permission notice appear in supporting
13 * documentation, and that the name of the Vrije Universiteit not be used in
14 * advertising or publicity pertaining to distribution of the software without
15 * specific, written prior permission. The Vrije Universiteit makes no
16 * representations about the suitability of this software for any purpose.
17 * It is provided "as is" without express or implied warranty.
18 *
19 * The Vrije Universiteit DISCLAIMS ALL WARRANTIES WITH REGARD TO THIS SOFTWARE,
20 * INCLUDING ALL IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS, IN NO
21 * EVENT SHALL The Vrije Universiteit BE LIABLE FOR ANY SPECIAL, INDIRECT OR
22 * CONSEQUENTIAL DAMAGES OR ANY DAMAGES WHATSOEVER RESULTING FROM LOSS OF USE,
23 * DATA OR PROFITS, WHETHER IN AN ACTION OF CONTRACT, NEGLIGENCE OR OTHER
24 * TORTIOUS ACTION, ARISING OUT OF OR IN CONNECTION WITH THE USE OR
25 * PERFORMANCE OF THIS SOFTWARE.
26 */
27
28/*
29 * assyntax.h
30 *
31 * Select the syntax appropriate to the 386 assembler being used
32 * To add support for more assemblers add more columns to the CHOICE
33 * macro. Note that register names must also have uppercase names
34 * to avoid macro recursion. e.g., #define ah %ah recurses!
35 *
36 * NB 1. Some of the macros for certain assemblers imply that the code is to
37 * run in protected mode!! Caveat emptor.
38 *
39 * NB 2. 486 specific instructions are not included. This is to discourage
40 * their accidental use in code that is intended to run on 386 and 486
41 * systems.
42 *
43 * Supported assemblers:
44 *
45 * (a) AT&T SysVr4 as(1): define ATT_ASSEMBLER
46 * (b) GNU Assembler gas: define GNU_ASSEMBLER (default)
47 * (c) Amsterdam Compiler kit: define ACK_ASSEMBLER
48 * (d) The Netwide Assembler: define NASM_ASSEMBLER
49 * (e) Microsoft Assembler: define MASM_ASSEMBLER (UNTESTED!)
50 *
51 * The following naming conventions have been used to identify the various
52 * data types:
53 * _SR = segment register version
54 * Integer:
55 * _Q = quadword = 64 bits
56 * _L = long = 32 bits
57 * _W = short = 16 bits
58 * _B = byte = 8 bits
59 * Floating-point:
60 * _X = m80real = 80 bits
61 * _D = double = 64 bits
62 * _S = single = 32 bits
63 *
64 * Author: Gregory J. Sharp, Sept 1992
65 * Vrije Universiteit, Amsterdam, The Netherlands
66 *
67 * [support for Intel syntax added by Josh Vanderhoof, 1999]
68 */
69
70#if !(defined(NASM_ASSEMBLER) || defined(MASM_ASSEMBLER))
71
72#if !defined(ATT_ASSEMBLER) && !defined(GNU_ASSEMBLER) && !defined(ACK_ASSEMBLER)
73#define GNU_ASSEMBLER
74#endif
75
76#if (defined(__STDC__) && !defined(UNIXCPP)) || (defined (sun) && defined (i386) \
77 && defined (SVR4) && defined (__STDC__) && !defined (__GNUC__))
78#define CONCAT(x, y) x ## y
79#else
80#define CONCAT(x, y) x/**/y
81#endif
82
83#ifdef ACK_ASSEMBLER
84
85/* Assume we write code for 32-bit protected mode! */
86
87/* Redefine register names for GAS & AT&T assemblers */
88#define AL al
89#define AH ah
90#define AX ax
91#define EAX ax
92#define BL bl
93#define BH bh
94#define BX bx
95#define EBX bx
96#define CL cl
97#define CH ch
98#define CX cx
99#define ECX cx
100#define DL dl
101#define DH dh
102#define DX dx
103#define EDX dx
104#define BP bp
105#define EBP bp
106#define SI si
107#define ESI si
108#define DI di
109#define EDI di
110#define SP sp
111#define ESP sp
112#define CS cs
113#define SS ss
114#define DS ds
115#define ES es
116#define FS fs
117#define GS gs
118/* Control Registers */
119#define CR0 cr0
120#define CR1 cr1
121#define CR2 cr2
122#define CR3 cr3
123/* Debug Registers */
124#define DR0 dr0
125#define DR1 dr1
126#define DR2 dr2
127#define DR3 dr3
128#define DR4 dr4
129#define DR5 dr5
130#define DR6 dr6
131#define DR7 dr7
132/* Floating-point Stack */
133#define ST st
134
135#define AS_BEGIN .sect .text; .sect .rom; .sect .data; .sect .bss; .sect .text
136
137
138#define _WTOG o16 /* word toggle for _W instructions */
139#define _LTOG /* long toggle for _L instructions */
140#define ADDR_TOGGLE a16
141#define OPSZ_TOGGLE o16
142#define USE16 .use16
143#define USE32 .use32
144
145#define CHOICE(a,b,c) c
146
147#else /* AT&T or GAS */
148
149/* Redefine register names for GAS & AT&T assemblers */
150#define AL %al
151#define AH %ah
152#define AX %ax
153#define EAX %eax
154#define BL %bl
155#define BH %bh
156#define BX %bx
157#define EBX %ebx
158#define CL %cl
159#define CH %ch
160#define CX %cx
161#define ECX %ecx
162#define DL %dl
163#define DH %dh
164#define DX %dx
165#define EDX %edx
166#define BP %bp
167#define EBP %ebp
168#define SI %si
169#define ESI %esi
170#define DI %di
171#define EDI %edi
172#define SP %sp
173#define ESP %esp
174#define CS %cs
175#define SS %ss
176#define DS %ds
177#define ES %es
178#define FS %fs
179#define GS %gs
180/* Control Registers */
181#define CR0 %cr0
182#define CR1 %cr1
183#define CR2 %cr2
184#define CR3 %cr3
185/* Debug Registers */
186#define DR0 %db0
187#define DR1 %db1
188#define DR2 %db2
189#define DR3 %db3
190#define DR4 %db4
191#define DR5 %db5
192#define DR6 %db6
193#define DR7 %db7
194/* Floating-point Stack */
195#define _STX0 %st(0)
196#define _STX1 %st(1)
197#define _STX2 %st(2)
198#define _STX3 %st(3)
199#define _STX4 %st(4)
200#define _STX5 %st(5)
201#define _STX6 %st(6)
202#define _STX7 %st(7)
203#define ST(x) CONCAT(_STX,x)
204/* MMX Registers */
205#define MM0 %mm0
206#define MM1 %mm1
207#define MM2 %mm2
208#define MM3 %mm3
209#define MM4 %mm4
210#define MM5 %mm5
211#define MM6 %mm6
212#define MM7 %mm7
213/* SSE Registers */
214#define XMM0 %xmm0
215#define XMM1 %xmm1
216#define XMM2 %xmm2
217#define XMM3 %xmm3
218#define XMM4 %xmm4
219#define XMM5 %xmm5
220#define XMM6 %xmm6
221#define XMM7 %xmm7
222
223#define AS_BEGIN
224#define USE16
225#define USE32
226
227#ifdef GNU_ASSEMBLER
228
229#define ADDR_TOGGLE aword
230#define OPSZ_TOGGLE word
231
232#define CHOICE(a,b,c) b
233
234#else
235/*
236 * AT&T ASSEMBLER SYNTAX
237 * *********************
238 */
239#define CHOICE(a,b,c) a
240
241#define ADDR_TOGGLE addr16
242#define OPSZ_TOGGLE data16
243
244#endif /* GNU_ASSEMBLER */
245#endif /* ACK_ASSEMBLER */
246
247
248#if defined(__QNX__) || defined(Lynx) || (defined(SYSV) || defined(SVR4)) && !defined(ACK_ASSEMBLER) || defined(__ELF__) || defined(__GNU__)
249#define GLNAME(a) a
250#else
251#define GLNAME(a) CONCAT(_,a)
252#endif
253
254
255 /****************************************/
256 /* */
257 /* Select the various choices */
258 /* */
259 /****************************************/
260
261
262/* Redefine assembler directives */
263/*********************************/
264#define GLOBL CHOICE(.globl, .globl, .extern)
265/*
266#define ALIGNTEXT32 CHOICE(.align 32, .align ARG2(5,0x90), .align 32)
267*/
268#define ALIGNTEXT32 CHOICE(.align 32, .balign 32, .align 32)
269#define ALIGNTEXT16 CHOICE(.align 16, .balign 16, .align 16)
270#define ALIGNTEXT8 CHOICE(.align 8, .balign 8, .align 8)
271#define ALIGNTEXT4 CHOICE(.align 4, .balign 4, .align 4)
272#define ALIGNTEXT2 CHOICE(.align 2, .balign 2, .align 2)
273/* ALIGNTEXT4ifNOP is the same as ALIGNTEXT4, but only if the space is
274 * guaranteed to be filled with NOPs. Otherwise it does nothing.
275 */
276#define ALIGNTEXT32ifNOP CHOICE(.align 32, .balign ARG2(32,0x90), /*can't do it*/)
277#define ALIGNTEXT16ifNOP CHOICE(.align 16, .balign ARG2(16,0x90), /*can't do it*/)
278#define ALIGNTEXT8ifNOP CHOICE(.align 8, .balign ARG2(8,0x90), /*can't do it*/)
279#define ALIGNTEXT4ifNOP CHOICE(.align 4, .balign ARG2(4,0x90), /*can't do it*/)
280#define ALIGNDATA32 CHOICE(.align 32, .balign ARG2(32,0x0), .align 32)
281#define ALIGNDATA16 CHOICE(.align 16, .balign ARG2(16,0x0), .align 16)
282#define ALIGNDATA8 CHOICE(.align 8, .balign ARG2(8,0x0), .align 8)
283#define ALIGNDATA4 CHOICE(.align 4, .balign ARG2(4,0x0), .align 4)
284#define ALIGNDATA2 CHOICE(.align 2, .balign ARG2(2,0x0), .align 2)
285#define FILE(s) CHOICE(.file s, .file s, .file s)
286#define STRING(s) CHOICE(.string s, .asciz s, .asciz s)
287#define D_LONG CHOICE(.long, .long, .data4)
288#define D_WORD CHOICE(.value, .short, .data2)
289#define D_BYTE CHOICE(.byte, .byte, .data1)
290#define SPACE CHOICE(.comm, .space, .space)
291#define COMM CHOICE(.comm, .comm, .comm)
292#define SEG_DATA CHOICE(.data, .data, .sect .data)
293#define SEG_TEXT CHOICE(.text, .text, .sect .text)
294#define SEG_BSS CHOICE(.bss, .bss, .sect .bss)
295
296#ifdef GNU_ASSEMBLER
297#define D_SPACE(n) . = . + n
298#else
299#define D_SPACE(n) .space n
300#endif
301
302/* Addressing Modes */
303/* Immediate Mode */
304#define ADDR(a) CHOICE(CONCAT($,a), CONCAT($,a), a)
305#define CONST(a) CHOICE(CONCAT($,a), CONCAT($,a), a)
306
307/* Indirect Mode */
308#define CONTENT(a) CHOICE(a, a, (a)) /* take contents of variable */
309#define REGIND(a) CHOICE((a), (a), (a)) /* Register a indirect */
310/* Register b indirect plus displacement a */
311#define REGOFF(a, b) CHOICE(a(b), a(b), a(b))
312/* Reg indirect Base + Index + Displacement - this is mainly for 16-bit mode
313 * which has no scaling
314 */
315#define REGBID(b,i,d) CHOICE(d(b,i), d(b,i), d(b)(i))
316/* Reg indirect Base + (Index * Scale) + Displacement */
317#define REGBISD(b,i,s,d) CHOICE(d(b,i,s), d(b,i,s), d(b)(i*s))
318/* Displaced Scaled Index: */
319#define REGDIS(d,i,s) CHOICE(d(,i,s), d(,i,s), d(i * s))
320/* Indexed Base: */
321#define REGBI(b,i) CHOICE((b,i), (b,i), (b)(i))
322/* Displaced Base: */
323#define REGDB(d,b) CHOICE(d(b), d(b), d(b))
324/* Variable indirect: */
325#define VARINDIRECT(var) CHOICE(*var, *var, (var))
326/* Use register contents as jump/call target: */
327#define CODEPTR(reg) CHOICE(*reg, *reg, reg)
328
329/* For expressions requiring bracketing
330 * eg. (CRT0_PM | CRT_EM)
331 */
332
333#define EXPR(a) CHOICE([a], (a), [a])
334#define ENOT(a) CHOICE(0!a, ~a, ~a)
335#define EMUL(a,b) CHOICE(a\*b, a*b, a*b)
336#define EDIV(a,b) CHOICE(a\/b, a/b, a/b)
337
338/*
339 * We have to beat the problem of commas within arguments to choice.
340 * eg. choice (add a,b, add b,a) will get argument mismatch. Luckily ANSI
341 * and other known cpp definitions evaluate arguments before substitution
342 * so the following works.
343 */
344#define ARG2(a, b) a,b
345#define ARG3(a,b,c) a,b,c
346
347/* Redefine assembler commands */
348#define AAA CHOICE(aaa, aaa, aaa)
349#define AAD CHOICE(aad, aad, aad)
350#define AAM CHOICE(aam, aam, aam)
351#define AAS CHOICE(aas, aas, aas)
352#define ADC_L(a, b) CHOICE(adcl ARG2(a,b), adcl ARG2(a,b), _LTOG adc ARG2(b,a))
353#define ADC_W(a, b) CHOICE(adcw ARG2(a,b), adcw ARG2(a,b), _WTOG adc ARG2(b,a))
354#define ADC_B(a, b) CHOICE(adcb ARG2(a,b), adcb ARG2(a,b), adcb ARG2(b,a))
355#define ADD_L(a, b) CHOICE(addl ARG2(a,b), addl ARG2(a,b), _LTOG add ARG2(b,a))
356#define ADD_W(a, b) CHOICE(addw ARG2(a,b), addw ARG2(a,b), _WTOG add ARG2(b,a))
357#define ADD_B(a, b) CHOICE(addb ARG2(a,b), addb ARG2(a,b), addb ARG2(b,a))
358#define AND_L(a, b) CHOICE(andl ARG2(a,b), andl ARG2(a,b), _LTOG and ARG2(b,a))
359#define AND_W(a, b) CHOICE(andw ARG2(a,b), andw ARG2(a,b), _WTOG and ARG2(b,a))
360#define AND_B(a, b) CHOICE(andb ARG2(a,b), andb ARG2(a,b), andb ARG2(b,a))
361#define ARPL(a,b) CHOICE(arpl ARG2(a,b), arpl ARG2(a,b), arpl ARG2(b,a))
362#define BOUND_L(a, b) CHOICE(boundl ARG2(a,b), boundl ARG2(b,a), _LTOG bound ARG2(b,a))
363#define BOUND_W(a, b) CHOICE(boundw ARG2(a,b), boundw ARG2(b,a), _WTOG bound ARG2(b,a))
364#define BSF_L(a, b) CHOICE(bsfl ARG2(a,b), bsfl ARG2(a,b), _LTOG bsf ARG2(b,a))
365#define BSF_W(a, b) CHOICE(bsfw ARG2(a,b), bsfw ARG2(a,b), _WTOG bsf ARG2(b,a))
366#define BSR_L(a, b) CHOICE(bsrl ARG2(a,b), bsrl ARG2(a,b), _LTOG bsr ARG2(b,a))
367#define BSR_W(a, b) CHOICE(bsrw ARG2(a,b), bsrw ARG2(a,b), _WTOG bsr ARG2(b,a))
368#define BT_L(a, b) CHOICE(btl ARG2(a,b), btl ARG2(a,b), _LTOG bt ARG2(b,a))
369#define BT_W(a, b) CHOICE(btw ARG2(a,b), btw ARG2(a,b), _WTOG bt ARG2(b,a))
370#define BTC_L(a, b) CHOICE(btcl ARG2(a,b), btcl ARG2(a,b), _LTOG btc ARG2(b,a))
371#define BTC_W(a, b) CHOICE(btcw ARG2(a,b), btcw ARG2(a,b), _WTOG btc ARG2(b,a))
372#define BTR_L(a, b) CHOICE(btrl ARG2(a,b), btrl ARG2(a,b), _LTOG btr ARG2(b,a))
373#define BTR_W(a, b) CHOICE(btrw ARG2(a,b), btrw ARG2(a,b), _WTOG btr ARG2(b,a))
374#define BTS_L(a, b) CHOICE(btsl ARG2(a,b), btsl ARG2(a,b), _LTOG bts ARG2(b,a))
375#define BTS_W(a, b) CHOICE(btsw ARG2(a,b), btsw ARG2(a,b), _WTOG bts ARG2(b,a))
376#define CALL(a) CHOICE(call a, call a, call a)
377#define CALLF(s,a) CHOICE(lcall ARG2(s,a), lcall ARG2(s,a), callf s:a)
378#define CBW CHOICE(cbtw, cbw, cbw)
379#define CWDE CHOICE(cwtd, cwde, cwde)
380#define CLC CHOICE(clc, clc, clc)
381#define CLD CHOICE(cld, cld, cld)
382#define CLI CHOICE(cli, cli, cli)
383#define CLTS CHOICE(clts, clts, clts)
384#define CMC CHOICE(cmc, cmc, cmc)
385#define CMP_L(a, b) CHOICE(cmpl ARG2(a,b), cmpl ARG2(a,b), _LTOG cmp ARG2(b,a))
386#define CMP_W(a, b) CHOICE(cmpw ARG2(a,b), cmpw ARG2(a,b), _WTOG cmp ARG2(b,a))
387#define CMP_B(a, b) CHOICE(cmpb ARG2(a,b), cmpb ARG2(a,b), cmpb ARG2(b,a))
388#define CMPS_L CHOICE(cmpsl, cmpsl, _LTOG cmps)
389#define CMPS_W CHOICE(cmpsw, cmpsw, _WTOG cmps)
390#define CMPS_B CHOICE(cmpsb, cmpsb, cmpsb)
391#define CWD CHOICE(cwtl, cwd, cwd)
392#define CDQ CHOICE(cltd, cdq, cdq)
393#define DAA CHOICE(daa, daa, daa)
394#define DAS CHOICE(das, das, das)
395#define DEC_L(a) CHOICE(decl a, decl a, _LTOG dec a)
396#define DEC_W(a) CHOICE(decw a, decw a, _WTOG dec a)
397#define DEC_B(a) CHOICE(decb a, decb a, decb a)
398#define DIV_L(a) CHOICE(divl a, divl a, div a)
399#define DIV_W(a) CHOICE(divw a, divw a, div a)
400#define DIV_B(a) CHOICE(divb a, divb a, divb a)
401#define ENTER(a,b) CHOICE(enter ARG2(a,b), enter ARG2(a,b), enter ARG2(b,a))
402#define HLT CHOICE(hlt, hlt, hlt)
403#define IDIV_L(a) CHOICE(idivl a, idivl a, _LTOG idiv a)
404#define IDIV_W(a) CHOICE(idivw a, idivw a, _WTOG idiv a)
405#define IDIV_B(a) CHOICE(idivb a, idivb a, idivb a)
406/* More forms than this for imul!! */
407#define IMUL_L(a, b) CHOICE(imull ARG2(a,b), imull ARG2(a,b), _LTOG imul ARG2(b,a))
408#define IMUL_W(a, b) CHOICE(imulw ARG2(a,b), imulw ARG2(a,b), _WTOG imul ARG2(b,a))
409#define IMUL_B(a) CHOICE(imulb a, imulb a, imulb a)
410#define IN_L CHOICE(inl (DX), inl ARG2(DX,EAX), _LTOG in DX)
411#define IN_W CHOICE(inw (DX), inw ARG2(DX,AX), _WTOG in DX)
412#define IN_B CHOICE(inb (DX), inb ARG2(DX,AL), inb DX)
413/* Please AS code writer: use the following ONLY, if you refer to ports<256
414 * directly, but not in IN1_W(DX), for instance, even if IN1_ looks nicer
415 */
416#if defined (sun)
417#define IN1_L(a) CHOICE(inl (a), inl ARG2(a,EAX), _LTOG in a)
418#define IN1_W(a) CHOICE(inw (a), inw ARG2(a,AX), _WTOG in a)
419#define IN1_B(a) CHOICE(inb (a), inb ARG2(a,AL), inb a)
420#else
421#define IN1_L(a) CHOICE(inl a, inl ARG2(a,EAX), _LTOG in a)
422#define IN1_W(a) CHOICE(inw a, inw ARG2(a,AX), _WTOG in a)
423#define IN1_B(a) CHOICE(inb a, inb ARG2(a,AL), inb a)
424#endif
425#define INC_L(a) CHOICE(incl a, incl a, _LTOG inc a)
426#define INC_W(a) CHOICE(incw a, incw a, _WTOG inc a)
427#define INC_B(a) CHOICE(incb a, incb a, incb a)
428#define INS_L CHOICE(insl, insl, _LTOG ins)
429#define INS_W CHOICE(insw, insw, _WTOG ins)
430#define INS_B CHOICE(insb, insb, insb)
431#define INT(a) CHOICE(int a, int a, int a)
432#define INT3 CHOICE(int CONST(3), int3, int CONST(3))
433#define INTO CHOICE(into, into, into)
434#define IRET CHOICE(iret, iret, iret)
435#define IRETD CHOICE(iret, iret, iretd)
436#define JA(a) CHOICE(ja a, ja a, ja a)
437#define JAE(a) CHOICE(jae a, jae a, jae a)
438#define JB(a) CHOICE(jb a, jb a, jb a)
439#define JBE(a) CHOICE(jbe a, jbe a, jbe a)
440#define JC(a) CHOICE(jc a, jc a, jc a)
441#define JE(a) CHOICE(je a, je a, je a)
442#define JG(a) CHOICE(jg a, jg a, jg a)
443#define JGE(a) CHOICE(jge a, jge a, jge a)
444#define JL(a) CHOICE(jl a, jl a, jl a)
445#define JLE(a) CHOICE(jle a, jle a, jle a)
446#define JNA(a) CHOICE(jna a, jna a, jna a)
447#define JNAE(a) CHOICE(jnae a, jnae a, jnae a)
448#define JNB(a) CHOICE(jnb a, jnb a, jnb a)
449#define JNBE(a) CHOICE(jnbe a, jnbe a, jnbe a)
450#define JNC(a) CHOICE(jnc a, jnc a, jnc a)
451#define JNE(a) CHOICE(jne a, jne a, jne a)
452#define JNG(a) CHOICE(jng a, jng a, jng a)
453#define JNGE(a) CHOICE(jnge a, jnge a, jnge a)
454#define JNL(a) CHOICE(jnl a, jnl a, jnl a)
455#define JNLE(a) CHOICE(jnle a, jnle a, jnle a)
456#define JNO(a) CHOICE(jno a, jno a, jno a)
457#define JNP(a) CHOICE(jnp a, jnp a, jnp a)
458#define JNS(a) CHOICE(jns a, jns a, jns a)
459#define JNZ(a) CHOICE(jnz a, jnz a, jnz a)
460#define JO(a) CHOICE(jo a, jo a, jo a)
461#define JP(a) CHOICE(jp a, jp a, jp a)
462#define JPE(a) CHOICE(jpe a, jpe a, jpe a)
463#define JPO(a) CHOICE(jpo a, jpo a, jpo a)
464#define JS(a) CHOICE(js a, js a, js a)
465#define JZ(a) CHOICE(jz a, jz a, jz a)
466#define JMP(a) CHOICE(jmp a, jmp a, jmp a)
467#define JMPF(s,a) CHOICE(ljmp ARG2(s,a), ljmp ARG2(s,a), jmpf s:a)
468#define LAHF CHOICE(lahf, lahf, lahf)
469#if !defined(_REAL_MODE) && !defined(_V86_MODE)
470#define LAR(a, b) CHOICE(lar ARG2(a, b), lar ARG2(a, b), lar ARG2(b, a))
471#endif
472#define LEA_L(a, b) CHOICE(leal ARG2(a,b), leal ARG2(a,b), _LTOG lea ARG2(b,a))
473#define LEA_W(a, b) CHOICE(leaw ARG2(a,b), leaw ARG2(a,b), _WTOG lea ARG2(b,a))
474#define LEAVE CHOICE(leave, leave, leave)
475#define LGDT(a) CHOICE(lgdt a, lgdt a, lgdt a)
476#define LIDT(a) CHOICE(lidt a, lidt a, lidt a)
477#define LDS(a, b) CHOICE(ldsl ARG2(a,b), lds ARG2(a,b), lds ARG2(b,a))
478#define LES(a, b) CHOICE(lesl ARG2(a,b), les ARG2(a,b), les ARG2(b,a))
479#define LFS(a, b) CHOICE(lfsl ARG2(a,b), lfs ARG2(a,b), lfs ARG2(b,a))
480#define LGS(a, b) CHOICE(lgsl ARG2(a,b), lgs ARG2(a,b), lgs ARG2(b,a))
481#define LSS(a, b) CHOICE(lssl ARG2(a,b), lss ARG2(a,b), lss ARG2(b,a))
482#define LLDT(a) CHOICE(lldt a, lldt a, lldt a)
483#define LMSW(a) CHOICE(lmsw a, lmsw a, lmsw a)
484#define LOCK CHOICE(lock, lock, lock)
485#define LODS_L CHOICE(lodsl, lodsl, _LTOG lods)
486#define LODS_W CHOICE(lodsw, lodsw, _WTOG lods)
487#define LODS_B CHOICE(lodsb, lodsb, lodsb)
488#define LOOP(a) CHOICE(loop a, loop a, loop a)
489#define LOOPE(a) CHOICE(loope a, loope a, loope a)
490#define LOOPZ(a) CHOICE(loopz a, loopz a, loopz a)
491#define LOOPNE(a) CHOICE(loopne a, loopne a, loopne a)
492#define LOOPNZ(a) CHOICE(loopnz a, loopnz a, loopnz a)
493#if !defined(_REAL_MODE) && !defined(_V86_MODE)
494#define LSL(a, b) CHOICE(lsl ARG2(a,b), lsl ARG2(a,b), lsl ARG2(b,a))
495#endif
496#define LTR(a) CHOICE(ltr a, ltr a, ltr a)
497#define MOV_SR(a, b) CHOICE(movw ARG2(a,b), mov ARG2(a,b), mov ARG2(b,a))
498#define MOV_L(a, b) CHOICE(movl ARG2(a,b), movl ARG2(a,b), _LTOG mov ARG2(b,a))
499#define MOV_W(a, b) CHOICE(movw ARG2(a,b), movw ARG2(a,b), _WTOG mov ARG2(b,a))
500#define MOV_B(a, b) CHOICE(movb ARG2(a,b), movb ARG2(a,b), movb ARG2(b,a))
501#define MOVS_L CHOICE(movsl, movsl, _LTOG movs)
502#define MOVS_W CHOICE(movsw, movsw, _WTOG movs)
503#define MOVS_B CHOICE(movsb, movsb, movsb)
504#define MOVSX_BL(a, b) CHOICE(movsbl ARG2(a,b), movsbl ARG2(a,b), movsx ARG2(b,a))
505#define MOVSX_BW(a, b) CHOICE(movsbw ARG2(a,b), movsbw ARG2(a,b), movsx ARG2(b,a))
506#define MOVSX_WL(a, b) CHOICE(movswl ARG2(a,b), movswl ARG2(a,b), movsx ARG2(b,a))
507#define MOVZX_BL(a, b) CHOICE(movzbl ARG2(a,b), movzbl ARG2(a,b), movzx ARG2(b,a))
508#define MOVZX_BW(a, b) CHOICE(movzbw ARG2(a,b), movzbw ARG2(a,b), movzx ARG2(b,a))
509#define MOVZX_WL(a, b) CHOICE(movzwl ARG2(a,b), movzwl ARG2(a,b), movzx ARG2(b,a))
510#define MUL_L(a) CHOICE(mull a, mull a, _LTOG mul a)
511#define MUL_W(a) CHOICE(mulw a, mulw a, _WTOG mul a)
512#define MUL_B(a) CHOICE(mulb a, mulb a, mulb a)
513#define NEG_L(a) CHOICE(negl a, negl a, _LTOG neg a)
514#define NEG_W(a) CHOICE(negw a, negw a, _WTOG neg a)
515#define NEG_B(a) CHOICE(negb a, negb a, negb a)
516#define NOP CHOICE(nop, nop, nop)
517#define NOT_L(a) CHOICE(notl a, notl a, _LTOG not a)
518#define NOT_W(a) CHOICE(notw a, notw a, _WTOG not a)
519#define NOT_B(a) CHOICE(notb a, notb a, notb a)
520#define OR_L(a,b) CHOICE(orl ARG2(a,b), orl ARG2(a,b), _LTOG or ARG2(b,a))
521#define OR_W(a,b) CHOICE(orw ARG2(a,b), orw ARG2(a,b), _WTOG or ARG2(b,a))
522#define OR_B(a,b) CHOICE(orb ARG2(a,b), orb ARG2(a,b), orb ARG2(b,a))
523#define OUT_L CHOICE(outl (DX), outl ARG2(EAX,DX), _LTOG out DX)
524#define OUT_W CHOICE(outw (DX), outw ARG2(AX,DX), _WTOG out DX)
525#define OUT_B CHOICE(outb (DX), outb ARG2(AL,DX), outb DX)
526/* Please AS code writer: use the following ONLY, if you refer to ports<256
527 * directly, but not in OUT1_W(DX), for instance, even if OUT1_ looks nicer
528 */
529#define OUT1_L(a) CHOICE(outl (a), outl ARG2(EAX,a), _LTOG out a)
530#define OUT1_W(a) CHOICE(outw (a), outw ARG2(AX,a), _WTOG out a)
531#define OUT1_B(a) CHOICE(outb (a), outb ARG2(AL,a), outb a)
532#define OUTS_L CHOICE(outsl, outsl, _LTOG outs)
533#define OUTS_W CHOICE(outsw, outsw, _WTOG outs)
534#define OUTS_B CHOICE(outsb, outsb, outsb)
535#define POP_SR(a) CHOICE(pop a, pop a, pop a)
536#define POP_L(a) CHOICE(popl a, popl a, _LTOG pop a)
537#define POP_W(a) CHOICE(popw a, popw a, _WTOG pop a)
538#define POPA_L CHOICE(popal, popal, _LTOG popa)
539#define POPA_W CHOICE(popaw, popaw, _WTOG popa)
540#define POPF_L CHOICE(popfl, popfl, _LTOG popf)
541#define POPF_W CHOICE(popfw, popfw, _WTOG popf)
542#define PUSH_SR(a) CHOICE(push a, push a, push a)
543#define PUSH_L(a) CHOICE(pushl a, pushl a, _LTOG push a)
544#define PUSH_W(a) CHOICE(pushw a, pushw a, _WTOG push a)
545#define PUSH_B(a) CHOICE(push a, pushb a, push a)
546#define PUSHA_L CHOICE(pushal, pushal, _LTOG pusha)
547#define PUSHA_W CHOICE(pushaw, pushaw, _WTOG pusha)
548#define PUSHF_L CHOICE(pushfl, pushfl, _LTOG pushf)
549#define PUSHF_W CHOICE(pushfw, pushfw, _WTOG pushf)
550#define RCL_L(a, b) CHOICE(rcll ARG2(a,b), rcll ARG2(a,b), _LTOG rcl ARG2(b,a))
551#define RCL_W(a, b) CHOICE(rclw ARG2(a,b), rclw ARG2(a,b), _WTOG rcl ARG2(b,a))
552#define RCL_B(a, b) CHOICE(rclb ARG2(a,b), rclb ARG2(a,b), rclb ARG2(b,a))
553#define RCR_L(a, b) CHOICE(rcrl ARG2(a,b), rcrl ARG2(a,b), _LTOG rcr ARG2(b,a))
554#define RCR_W(a, b) CHOICE(rcrw ARG2(a,b), rcrw ARG2(a,b), _WTOG rcr ARG2(b,a))
555#define RCR_B(a, b) CHOICE(rcrb ARG2(a,b), rcrb ARG2(a,b), rcrb ARG2(b,a))
556#define ROL_L(a, b) CHOICE(roll ARG2(a,b), roll ARG2(a,b), _LTOG rol ARG2(b,a))
557#define ROL_W(a, b) CHOICE(rolw ARG2(a,b), rolw ARG2(a,b), _WTOG rol ARG2(b,a))
558#define ROL_B(a, b) CHOICE(rolb ARG2(a,b), rolb ARG2(a,b), rolb ARG2(b,a))
559#define ROR_L(a, b) CHOICE(rorl ARG2(a,b), rorl ARG2(a,b), _LTOG ror ARG2(b,a))
560#define ROR_W(a, b) CHOICE(rorw ARG2(a,b), rorw ARG2(a,b), _WTOG ror ARG2(b,a))
561#define ROR_B(a, b) CHOICE(rorb ARG2(a,b), rorb ARG2(a,b), rorb ARG2(b,a))
562#define REP CHOICE(rep ;, rep ;, repe)
563#define REPE CHOICE(repz ;, repe ;, repe)
564#define REPNE CHOICE(repnz ;, repne ;, repne)
565#define REPNZ REPNE
566#define REPZ REPE
567#define RET CHOICE(ret, ret, ret)
568#define SAHF CHOICE(sahf, sahf, sahf)
569#define SAL_L(a, b) CHOICE(sall ARG2(a,b), sall ARG2(a,b), _LTOG sal ARG2(b,a))
570#define SAL_W(a, b) CHOICE(salw ARG2(a,b), salw ARG2(a,b), _WTOG sal ARG2(b,a))
571#define SAL_B(a, b) CHOICE(salb ARG2(a,b), salb ARG2(a,b), salb ARG2(b,a))
572#define SAR_L(a, b) CHOICE(sarl ARG2(a,b), sarl ARG2(a,b), _LTOG sar ARG2(b,a))
573#define SAR_W(a, b) CHOICE(sarw ARG2(a,b), sarw ARG2(a,b), _WTOG sar ARG2(b,a))
574#define SAR_B(a, b) CHOICE(sarb ARG2(a,b), sarb ARG2(a,b), sarb ARG2(b,a))
575#define SBB_L(a, b) CHOICE(sbbl ARG2(a,b), sbbl ARG2(a,b), _LTOG sbb ARG2(b,a))
576#define SBB_W(a, b) CHOICE(sbbw ARG2(a,b), sbbw ARG2(a,b), _WTOG sbb ARG2(b,a))
577#define SBB_B(a, b) CHOICE(sbbb ARG2(a,b), sbbb ARG2(a,b), sbbb ARG2(b,a))
578#define SCAS_L CHOICE(scasl, scasl, _LTOG scas)
579#define SCAS_W CHOICE(scasw, scasw, _WTOG scas)
580#define SCAS_B CHOICE(scasb, scasb, scasb)
581#define SETA(a) CHOICE(seta a, seta a, seta a)
582#define SETAE(a) CHOICE(setae a, setae a, setae a)
583#define SETB(a) CHOICE(setb a, setb a, setb a)
584#define SETBE(a) CHOICE(setbe a, setbe a, setbe a)
585#define SETC(a) CHOICE(setc a, setb a, setb a)
586#define SETE(a) CHOICE(sete a, sete a, sete a)
587#define SETG(a) CHOICE(setg a, setg a, setg a)
588#define SETGE(a) CHOICE(setge a, setge a, setge a)
589#define SETL(a) CHOICE(setl a, setl a, setl a)
590#define SETLE(a) CHOICE(setle a, setle a, setle a)
591#define SETNA(a) CHOICE(setna a, setna a, setna a)
592#define SETNAE(a) CHOICE(setnae a, setnae a, setnae a)
593#define SETNB(a) CHOICE(setnb a, setnb a, setnb a)
594#define SETNBE(a) CHOICE(setnbe a, setnbe a, setnbe a)
595#define SETNC(a) CHOICE(setnc a, setnb a, setnb a)
596#define SETNE(a) CHOICE(setne a, setne a, setne a)
597#define SETNG(a) CHOICE(setng a, setng a, setng a)
598#define SETNGE(a) CHOICE(setnge a, setnge a, setnge a)
599#define SETNL(a) CHOICE(setnl a, setnl a, setnl a)
600#define SETNLE(a) CHOICE(setnle a, setnle a, setnle a)
601#define SETNO(a) CHOICE(setno a, setno a, setno a)
602#define SETNP(a) CHOICE(setnp a, setnp a, setnp a)
603#define SETNS(a) CHOICE(setns a, setns a, setna a)
604#define SETNZ(a) CHOICE(setnz a, setnz a, setnz a)
605#define SETO(a) CHOICE(seto a, seto a, seto a)
606#define SETP(a) CHOICE(setp a, setp a, setp a)
607#define SETPE(a) CHOICE(setpe a, setpe a, setpe a)
608#define SETPO(a) CHOICE(setpo a, setpo a, setpo a)
609#define SETS(a) CHOICE(sets a, sets a, seta a)
610#define SETZ(a) CHOICE(setz a, setz a, setz a)
611#define SGDT(a) CHOICE(sgdt a, sgdt a, sgdt a)
612#define SIDT(a) CHOICE(sidt a, sidt a, sidt a)
613#define SHL_L(a, b) CHOICE(shll ARG2(a,b), shll ARG2(a,b), _LTOG shl ARG2(b,a))
614#define SHL_W(a, b) CHOICE(shlw ARG2(a,b), shlw ARG2(a,b), _WTOG shl ARG2(b,a))
615#define SHL_B(a, b) CHOICE(shlb ARG2(a,b), shlb ARG2(a,b), shlb ARG2(b,a))
616#define SHLD_L(a,b,c) CHOICE(shldl ARG3(a,b,c), shldl ARG3(a,b,c), _LTOG shld ARG3(c,b,a))
617#define SHLD2_L(a,b) CHOICE(shldl ARG2(a,b), shldl ARG3(CL,a,b), _LTOG shld ARG3(b,a,CL))
618#define SHLD_W(a,b,c) CHOICE(shldw ARG3(a,b,c), shldw ARG3(a,b,c), _WTOG shld ARG3(c,b,a))
619#define SHLD2_W(a,b) CHOICE(shldw ARG2(a,b), shldw ARG3(CL,a,b), _WTOG shld ARG3(b,a,CL))
620#define SHR_L(a, b) CHOICE(shrl ARG2(a,b), shrl ARG2(a,b), _LTOG shr ARG2(b,a))
621#define SHR_W(a, b) CHOICE(shrw ARG2(a,b), shrw ARG2(a,b), _WTOG shr ARG2(b,a))
622#define SHR_B(a, b) CHOICE(shrb ARG2(a,b), shrb ARG2(a,b), shrb ARG2(b,a))
623#define SHRD_L(a,b,c) CHOICE(shrdl ARG3(a,b,c), shrdl ARG3(a,b,c), _LTOG shrd ARG3(c,b,a))
624#define SHRD2_L(a,b) CHOICE(shrdl ARG2(a,b), shrdl ARG3(CL,a,b), _LTOG shrd ARG3(b,a,CL))
625#define SHRD_W(a,b,c) CHOICE(shrdw ARG3(a,b,c), shrdw ARG3(a,b,c), _WTOG shrd ARG3(c,b,a))
626#define SHRD2_W(a,b) CHOICE(shrdw ARG2(a,b), shrdw ARG3(CL,a,b), _WTOG shrd ARG3(b,a,CL))
627#define SLDT(a) CHOICE(sldt a, sldt a, sldt a)
628#define SMSW(a) CHOICE(smsw a, smsw a, smsw a)
629#define STC CHOICE(stc, stc, stc)
630#define STD CHOICE(std, std, std)
631#define STI CHOICE(sti, sti, sti)
632#define STOS_L CHOICE(stosl, stosl, _LTOG stos)
633#define STOS_W CHOICE(stosw, stosw, _WTOG stos)
634#define STOS_B CHOICE(stosb, stosb, stosb)
635#define STR(a) CHOICE(str a, str a, str a)
636#define SUB_L(a, b) CHOICE(subl ARG2(a,b), subl ARG2(a,b), _LTOG sub ARG2(b,a))
637#define SUB_W(a, b) CHOICE(subw ARG2(a,b), subw ARG2(a,b), _WTOG sub ARG2(b,a))
638#define SUB_B(a, b) CHOICE(subb ARG2(a,b), subb ARG2(a,b), subb ARG2(b,a))
639#define TEST_L(a, b) CHOICE(testl ARG2(a,b), testl ARG2(a,b), _LTOG test ARG2(b,a))
640#define TEST_W(a, b) CHOICE(testw ARG2(a,b), testw ARG2(a,b), _WTOG test ARG2(b,a))
641#define TEST_B(a, b) CHOICE(testb ARG2(a,b), testb ARG2(a,b), testb ARG2(b,a))
642#define VERR(a) CHOICE(verr a, verr a, verr a)
643#define VERW(a) CHOICE(verw a, verw a, verw a)
644#define WAIT CHOICE(wait, wait, wait)
645#define XCHG_L(a, b) CHOICE(xchgl ARG2(a,b), xchgl ARG2(a,b), _LTOG xchg ARG2(b,a))
646#define XCHG_W(a, b) CHOICE(xchgw ARG2(a,b), xchgw ARG2(a,b), _WTOG xchg ARG2(b,a))
647#define XCHG_B(a, b) CHOICE(xchgb ARG2(a,b), xchgb ARG2(a,b), xchgb ARG2(b,a))
648#define XLAT CHOICE(xlat, xlat, xlat)
649#define XOR_L(a, b) CHOICE(xorl ARG2(a,b), xorl ARG2(a,b), _LTOG xor ARG2(b,a))
650#define XOR_W(a, b) CHOICE(xorw ARG2(a,b), xorw ARG2(a,b), _WTOG xor ARG2(b,a))
651#define XOR_B(a, b) CHOICE(xorb ARG2(a,b), xorb ARG2(a,b), xorb ARG2(b,a))
652
653
654/* Floating Point Instructions */
655#define F2XM1 CHOICE(f2xm1, f2xm1, f2xm1)
656#define FABS CHOICE(fabs, fabs, fabs)
657#define FADD_D(a) CHOICE(faddl a, faddl a, faddd a)
658#define FADD_S(a) CHOICE(fadds a, fadds a, fadds a)
659#define FADD2(a, b) CHOICE(fadd ARG2(a,b), fadd ARG2(a,b), fadd ARG2(b,a))
660#define FADDP(a, b) CHOICE(faddp ARG2(a,b), faddp ARG2(a,b), faddp ARG2(b,a))
661#define FIADD_L(a) CHOICE(fiaddl a, fiaddl a, fiaddl a)
662#define FIADD_W(a) CHOICE(fiadd a, fiadds a, fiadds a)
663#define FBLD(a) CHOICE(fbld a, fbld a, fbld a)
664#define FBSTP(a) CHOICE(fbstp a, fbstp a, fbstp a)
665#define FCHS CHOICE(fchs, fchs, fchs)
666#define FCLEX CHOICE(fclex, wait; fnclex, wait; fclex)
667#define FNCLEX CHOICE(fnclex, fnclex, fclex)
668#define FCOM(a) CHOICE(fcom a, fcom a, fcom a)
669#define FCOM_D(a) CHOICE(fcoml a, fcoml a, fcomd a)
670#define FCOM_S(a) CHOICE(fcoms a, fcoms a, fcoms a)
671#define FCOMP(a) CHOICE(fcomp a, fcomp a, fcomp a)
672#define FCOMP_D(a) CHOICE(fcompl a, fcompl a, fcompd a)
673#define FCOMP_S(a) CHOICE(fcomps a, fcomps a, fcomps a)
674#define FCOMPP CHOICE(fcompp, fcompp, fcompp)
675#define FCOS CHOICE(fcos, fcos, fcos)
676#define FDECSTP CHOICE(fdecstp, fdecstp, fdecstp)
677#define FDIV_D(a) CHOICE(fdivl a, fdivl a, fdivd a)
678#define FDIV_S(a) CHOICE(fdivs a, fdivs a, fdivs a)
679#define FDIV2(a, b) CHOICE(fdiv ARG2(a,b), fdiv ARG2(a,b), fdiv ARG2(b,a))
680#define FDIVP(a, b) CHOICE(fdivp ARG2(a,b), fdivp ARG2(a,b), fdivp ARG2(b,a))
681#define FIDIV_L(a) CHOICE(fidivl a, fidivl a, fidivl a)
682#define FIDIV_W(a) CHOICE(fidiv a, fidivs a, fidivs a)
683#define FDIVR_D(a) CHOICE(fdivrl a, fdivrl a, fdivrd a)
684#define FDIVR_S(a) CHOICE(fdivrs a, fdivrs a, fdivrs a)
685#define FDIVR2(a, b) CHOICE(fdivr ARG2(a,b), fdivr ARG2(a,b), fdivr ARG2(b,a))
686#define FDIVRP(a, b) CHOICE(fdivrp ARG2(a,b), fdivrp ARG2(a,b), fdivrp ARG2(b,a))
687#define FIDIVR_L(a) CHOICE(fidivrl a, fidivrl a, fidivrl a)
688#define FIDIVR_W(a) CHOICE(fidivr a, fidivrs a, fidivrs a)
689#define FFREE(a) CHOICE(ffree a, ffree a, ffree a)
690#define FICOM_L(a) CHOICE(ficoml a, ficoml a, ficoml a)
691#define FICOM_W(a) CHOICE(ficom a, ficoms a, ficoms a)
692#define FICOMP_L(a) CHOICE(ficompl a, ficompl a, ficompl a)
693#define FICOMP_W(a) CHOICE(ficomp a, ficomps a, ficomps a)
694#define FILD_Q(a) CHOICE(fildll a, fildq a, fildq a)
695#define FILD_L(a) CHOICE(fildl a, fildl a, fildl a)
696#define FILD_W(a) CHOICE(fild a, filds a, filds a)
697#define FINCSTP CHOICE(fincstp, fincstp, fincstp)
698#define FINIT CHOICE(finit, wait; fninit, wait; finit)
699#define FNINIT CHOICE(fninit, fninit, finit)
700#define FIST_L(a) CHOICE(fistl a, fistl a, fistl a)
701#define FIST_W(a) CHOICE(fist a, fists a, fists a)
702#define FISTP_Q(a) CHOICE(fistpll a, fistpq a, fistpq a)
703#define FISTP_L(a) CHOICE(fistpl a, fistpl a, fistpl a)
704#define FISTP_W(a) CHOICE(fistp a, fistps a, fistps a)
705#define FLD_X(a) CHOICE(fldt a, fldt a, fldx a) /* 80 bit data type! */
706#define FLD_D(a) CHOICE(fldl a, fldl a, fldd a)
707#define FLD_S(a) CHOICE(flds a, flds a, flds a)
708#define FLD1 CHOICE(fld1, fld1, fld1)
709#define FLDL2T CHOICE(fldl2t, fldl2t, fldl2t)
710#define FLDL2E CHOICE(fldl2e, fldl2e, fldl2e)
711#define FLDPI CHOICE(fldpi, fldpi, fldpi)
712#define FLDLG2 CHOICE(fldlg2, fldlg2, fldlg2)
713#define FLDLN2 CHOICE(fldln2, fldln2, fldln2)
714#define FLDZ CHOICE(fldz, fldz, fldz)
715#define FLDCW(a) CHOICE(fldcw a, fldcw a, fldcw a)
716#define FLDENV(a) CHOICE(fldenv a, fldenv a, fldenv a)
717#define FMUL_S(a) CHOICE(fmuls a, fmuls a, fmuls a)
718#define FMUL_D(a) CHOICE(fmull a, fmull a, fmuld a)
719#define FMUL2(a, b) CHOICE(fmul ARG2(a,b), fmul ARG2(a,b), fmul ARG2(b,a))
720#define FMULP(a, b) CHOICE(fmulp ARG2(a,b), fmulp ARG2(a,b), fmulp ARG2(b,a))
721#define FIMUL_L(a) CHOICE(fimull a, fimull a, fimull a)
722#define FIMUL_W(a) CHOICE(fimul a, fimuls a, fimuls a)
723#define FNOP CHOICE(fnop, fnop, fnop)
724#define FPATAN CHOICE(fpatan, fpatan, fpatan)
725#define FPREM CHOICE(fprem, fprem, fprem)
726#define FPREM1 CHOICE(fprem1, fprem1, fprem1)
727#define FPTAN CHOICE(fptan, fptan, fptan)
728#define FRNDINT CHOICE(frndint, frndint, frndint)
729#define FRSTOR(a) CHOICE(frstor a, frstor a, frstor a)
730#define FSAVE(a) CHOICE(fsave a, wait; fnsave a, wait; fsave a)
731#define FNSAVE(a) CHOICE(fnsave a, fnsave a, fsave a)
732#define FSCALE CHOICE(fscale, fscale, fscale)
733#define FSIN CHOICE(fsin, fsin, fsin)
734#define FSINCOS CHOICE(fsincos, fsincos, fsincos)
735#define FSQRT CHOICE(fsqrt, fsqrt, fsqrt)
736#define FST_D(a) CHOICE(fstl a, fstl a, fstd a)
737#define FST_S(a) CHOICE(fsts a, fsts a, fsts a)
738#define FSTP_X(a) CHOICE(fstpt a, fstpt a, fstpx a)
739#define FSTP_D(a) CHOICE(fstpl a, fstpl a, fstpd a)
740#define FSTP_S(a) CHOICE(fstps a, fstps a, fstps a)
741#define FSTP(a) CHOICE(fstp a, fstp a, fstp a)
742#define FSTCW(a) CHOICE(fstcw a, wait; fnstcw a, wait; fstcw a)
743#define FNSTCW(a) CHOICE(fnstcw a, fnstcw a, fstcw a)
744#define FSTENV(a) CHOICE(fstenv a, wait; fnstenv a, fstenv a)
745#define FNSTENV(a) CHOICE(fnstenv a, fnstenv a, fstenv a)
746#define FSTSW(a) CHOICE(fstsw a, wait; fnstsw a, wait; fstsw a)
747#define FNSTSW(a) CHOICE(fnstsw a, fnstsw a, fstsw a)
748#define FSUB_S(a) CHOICE(fsubs a, fsubs a, fsubs a)
749#define FSUB_D(a) CHOICE(fsubl a, fsubl a, fsubd a)
750#define FSUB2(a, b) CHOICE(fsub ARG2(a,b), fsub ARG2(a,b), fsub ARG2(b,a))
751#define FSUBP(a, b) CHOICE(fsubp ARG2(a,b), fsubp ARG2(a,b), fsubp ARG2(b,a))
752#define FISUB_L(a) CHOICE(fisubl a, fisubl a, fisubl a)
753#define FISUB_W(a) CHOICE(fisub a, fisubs a, fisubs a)
754#define FSUBR_S(a) CHOICE(fsubrs a, fsubrs a, fsubrs a)
755#define FSUBR_D(a) CHOICE(fsubrl a, fsubrl a, fsubrd a)
756#define FSUBR2(a, b) CHOICE(fsubr ARG2(a,b), fsubr ARG2(a,b), fsubr ARG2(b,a))
757#define FSUBRP(a, b) CHOICE(fsubrp ARG2(a,b), fsubrp ARG2(a,b), fsubrp ARG2(b,a))
758#define FISUBR_L(a) CHOICE(fisubrl a, fisubrl a, fisubrl a)
759#define FISUBR_W(a) CHOICE(fisubr a, fisubrs a, fisubrs a)
760#define FTST CHOICE(ftst, ftst, ftst)
761#define FUCOM(a) CHOICE(fucom a, fucom a, fucom a)
762#define FUCOMP(a) CHOICE(fucomp a, fucomp a, fucomp a)
763#define FUCOMPP CHOICE(fucompp, fucompp, fucompp)
764#define FWAIT CHOICE(wait, wait, wait)
765#define FXAM CHOICE(fxam, fxam, fxam)
766#define FXCH(a) CHOICE(fxch a, fxch a, fxch a)
767#define FXTRACT CHOICE(fxtract, fxtract, fxtract)
768#define FYL2X CHOICE(fyl2x, fyl2x, fyl2x)
769#define FYL2XP1 CHOICE(fyl2xp1, fyl2xp1, fyl2xp1)
770
771/* New instructions */
772#define CPUID CHOICE(D_BYTE ARG2(15, 162), cpuid, D_BYTE ARG2(15, 162))
773#define RDTSC CHOICE(D_BYTE ARG2(15, 49), rdtsc, D_BYTE ARG2(15, 49))
774
775#else /* NASM_ASSEMBLER || MASM_ASSEMBLER is defined */
776
777 /****************************************/
778 /* */
779 /* Intel style assemblers. */
780 /* (NASM and MASM) */
781 /* */
782 /****************************************/
783
784#define P_EAX EAX
785#define L_EAX EAX
786#define W_AX AX
787#define B_AH AH
788#define B_AL AL
789
790#define P_EBX EBX
791#define L_EBX EBX
792#define W_BX BX
793#define B_BH BH
794#define B_BL BL
795
796#define P_ECX ECX
797#define L_ECX ECX
798#define W_CX CX
799#define B_CH CH
800#define B_CL CL
801
802#define P_EDX EDX
803#define L_EDX EDX
804#define W_DX DX
805#define B_DH DH
806#define B_DL DL
807
808#define P_EBP EBP
809#define L_EBP EBP
810#define W_BP BP
811
812#define P_ESI ESI
813#define L_ESI ESI
814#define W_SI SI
815
816#define P_EDI EDI
817#define L_EDI EDI
818#define W_DI DI
819
820#define P_ESP ESP
821#define L_ESP ESP
822#define W_SP SP
823
824#define W_CS CS
825#define W_SS SS
826#define W_DS DS
827#define W_ES ES
828#define W_FS FS
829#define W_GS GS
830
831#define X_ST ST
832#define D_ST ST
833#define L_ST ST
834
835#define P_MM0 mm0
836#define P_MM1 mm1
837#define P_MM2 mm2
838#define P_MM3 mm3
839#define P_MM4 mm4
840#define P_MM5 mm5
841#define P_MM6 mm6
842#define P_MM7 mm7
843
844#define P_XMM0 xmm0
845#define P_XMM1 xmm1
846#define P_XMM2 xmm2
847#define P_XMM3 xmm3
848#define P_XMM4 xmm4
849#define P_XMM5 xmm5
850#define P_XMM6 xmm6
851#define P_XMM7 xmm7
852
853#if defined(NASM_ASSEMBLER)
854
855#define ST(n) st ## n
856
857#define TBYTE_PTR tword
858#define QWORD_PTR qword
859#define DWORD_PTR dword
860#define WORD_PTR word
861#define BYTE_PTR byte
862
863#define OFFSET
864
865#define GLOBL GLOBAL
866#define ALIGNTEXT32 ALIGN 32
867#define ALIGNTEXT16 ALIGN 16
868#define ALIGNTEXT8 ALIGN 8
869#define ALIGNTEXT4 ALIGN 4
870#define ALIGNTEXT2 ALIGN 2
871#define ALIGNTEXT32ifNOP ALIGN 32
872#define ALIGNTEXT16ifNOP ALIGN 16
873#define ALIGNTEXT8ifNOP ALIGN 8
874#define ALIGNTEXT4ifNOP ALIGN 4
875#define ALIGNDATA32 ALIGN 32
876#define ALIGNDATA16 ALIGN 16
877#define ALIGNDATA8 ALIGN 8
878#define ALIGNDATA4 ALIGN 4
879#define ALIGNDATA2 ALIGN 2
880#define FILE(s)
881#define STRING(s) db s
882#define D_LONG dd
883#define D_WORD dw
884#define D_BYTE db
885/* #define SPACE */
886/* #define COMM */
887#if defined(__WATCOMC__)
888SECTION _TEXT public align=16 class=CODE use32 flat
889SECTION _DATA public align=16 class=DATA use32 flat
890#define SEG_TEXT SECTION _TEXT
891#define SEG_DATA SECTION _DATA
892#define SEG_BSS SECTION .bss
893#else
894#define SEG_DATA SECTION .data
895#define SEG_TEXT SECTION .text
896#define SEG_BSS SECTION .bss
897#endif
898
899#define D_SPACE(n) db n REP 0
900
901#define AS_BEGIN
902
903#define NEAR near /* Jcc's should be handled better than this... */
904
905#else /* MASM */
906
907#define TBYTE_PTR tbyte ptr
908#define QWORD_PTR qword ptr
909#define DWORD_PTR dword ptr
910#define WORD_PTR word ptr
911#define BYTE_PTR byte ptr
912
913#define OFFSET offset
914
915#define GLOBL GLOBAL
916#define ALIGNTEXT32 ALIGN 32
917#define ALIGNTEXT16 ALIGN 16
918#define ALIGNTEXT8 ALIGN 8
919#define ALIGNTEXT4 ALIGN 4
920#define ALIGNTEXT2 ALIGN 2
921#define ALIGNTEXT32ifNOP ALIGN 32
922#define ALIGNTEXT16ifNOP ALIGN 16
923#define ALIGNTEXT8ifNOP ALIGN 8
924#define ALIGNTEXT4ifNOP ALIGN 4
925#define ALIGNDATA32 ALIGN 32
926#define ALIGNDATA16 ALIGN 16
927#define ALIGNDATA8 ALIGN 8
928#define ALIGNDATA4 ALIGN 4
929#define ALIGNDATA2 ALIGN 2
930#define FILE(s)
931#define STRING(s) db s
932#define D_LONG dd
933#define D_WORD dw
934#define D_BYTE db
935/* #define SPACE */
936/* #define COMM */
937#define SEG_DATA .DATA
938#define SEG_TEXT .CODE
939#define SEG_BSS .DATA
940
941#define D_SPACE(n) db n REP 0
942
943#define AS_BEGIN
944
945#define NEAR
946
947#endif
948
949#if defined(Lynx) || (defined(SYSV) || defined(SVR4)) \
950 || (defined(linux) || defined(__OS2ELF__)) && defined(__ELF__) \
951 || defined(__FreeBSD__) && __FreeBSD__ >= 3
952#define GLNAME(a) a
953#else
954#define GLNAME(a) _ ## a
955#endif
956
957/*
958 * Addressing Modes
959 */
960
961/* Immediate Mode */
962#define P_ADDR(a) OFFSET a
963#define X_ADDR(a) OFFSET a
964#define D_ADDR(a) OFFSET a
965#define L_ADDR(a) OFFSET a
966#define W_ADDR(a) OFFSET a
967#define B_ADDR(a) OFFSET a
968
969#define P_CONST(a) a
970#define X_CONST(a) a
971#define D_CONST(a) a
972#define L_CONST(a) a
973#define W_CONST(a) a
974#define B_CONST(a) a
975
976/* Indirect Mode */
977#define P_CONTENT(a) a
978#define X_CONTENT(a) TBYTE_PTR a
979#define D_CONTENT(a) QWORD_PTR a
980#define L_CONTENT(a) DWORD_PTR a
981#define W_CONTENT(a) WORD_PTR a
982#define B_CONTENT(a) BYTE_PTR a
983
984/* Register a indirect */
985#define P_REGIND(a) [a]
986#define X_REGIND(a) TBYTE_PTR [a]
987#define D_REGIND(a) QWORD_PTR [a]
988#define L_REGIND(a) DWORD_PTR [a]
989#define W_REGIND(a) WORD_PTR [a]
990#define B_REGIND(a) BYTE_PTR [a]
991
992/* Register b indirect plus displacement a */
993#define P_REGOFF(a, b) [b + a]
994#define X_REGOFF(a, b) TBYTE_PTR [b + a]
995#define D_REGOFF(a, b) QWORD_PTR [b + a]
996#define L_REGOFF(a, b) DWORD_PTR [b + a]
997#define W_REGOFF(a, b) WORD_PTR [b + a]
998#define B_REGOFF(a, b) BYTE_PTR [b + a]
999
1000/* Reg indirect Base + Index + Displacement - this is mainly for 16-bit mode
1001 * which has no scaling
1002 */
1003#define P_REGBID(b, i, d) [b + i + d]
1004#define X_REGBID(b, i, d) TBYTE_PTR [b + i + d]
1005#define D_REGBID(b, i, d) QWORD_PTR [b + i + d]
1006#define L_REGBID(b, i, d) DWORD_PTR [b + i + d]
1007#define W_REGBID(b, i, d) WORD_PTR [b + i + d]
1008#define B_REGBID(b, i, d) BYTE_PTR [b + i + d]
1009
1010/* Reg indirect Base + (Index * Scale) + Displacement */
1011#define P_REGBISD(b, i, s, d) [b + i * s + d]
1012#define X_REGBISD(b, i, s, d) TBYTE_PTR [b + i * s + d]
1013#define D_REGBISD(b, i, s, d) QWORD_PTR [b + i * s + d]
1014#define L_REGBISD(b, i, s, d) DWORD_PTR [b + i * s + d]
1015#define W_REGBISD(b, i, s, d) WORD_PTR [b + i * s + d]
1016#define B_REGBISD(b, i, s, d) BYTE_PTR [b + i * s + d]
1017
1018/* Displaced Scaled Index: */
1019#define P_REGDIS(d, i, s) [i * s + d]
1020#define X_REGDIS(d, i, s) TBYTE_PTR [i * s + d]
1021#define D_REGDIS(d, i, s) QWORD_PTR [i * s + d]
1022#define L_REGDIS(d, i, s) DWORD_PTR [i * s + d]
1023#define W_REGDIS(d, i, s) WORD_PTR [i * s + d]
1024#define B_REGDIS(d, i, s) BYTE_PTR [i * s + d]
1025
1026/* Indexed Base: */
1027#define P_REGBI(b, i) [b + i]
1028#define X_REGBI(b, i) TBYTE_PTR [b + i]
1029#define D_REGBI(b, i) QWORD_PTR [b + i]
1030#define L_REGBI(b, i) DWORD_PTR [b + i]
1031#define W_REGBI(b, i) WORD_PTR [b + i]
1032#define B_REGBI(b, i) BYTE_PTR [b + i]
1033
1034/* Displaced Base: */
1035#define P_REGDB(d, b) [b + d]
1036#define X_REGDB(d, b) TBYTE_PTR [b + d]
1037#define D_REGDB(d, b) QWORD_PTR [b + d]
1038#define L_REGDB(d, b) DWORD_PTR [b + d]
1039#define W_REGDB(d, b) WORD_PTR [b + d]
1040#define B_REGDB(d, b) BYTE_PTR [b + d]
1041
1042/* Variable indirect: */
1043#define VARINDIRECT(var) var
1044
1045/* Use register contents as jump/call target: */
1046#define CODEPTR(reg) reg
1047
1048/*
1049 * Redefine assembler commands
1050 */
1051
1052#define P_(a) P_ ## a
1053#define X_(a) X_ ## a
1054#define D_(a) D_ ## a
1055#define S_(a) L_ ## a
1056#define L_(a) L_ ## a
1057#define W_(a) W_ ## a
1058#define B_(a) B_ ## a
1059
1060#define AAA aaa
1061#define AAD aad
1062#define AAM aam
1063#define AAS aas
1064#define ADC_L(a, b) adc L_(b), L_(a)
1065#define ADC_W(a, b) adc W_(b), W_(a)
1066#define ADC_B(a, b) adc B_(b), B_(a)
1067#define ADD_L(a, b) add L_(b), L_(a)
1068#define ADD_W(a, b) add W_(b), W_(a)
1069#define ADD_B(a, b) add B_(b), B_(a)
1070#define AND_L(a, b) and L_(b), L_(a)
1071#define AND_W(a, b) and W_(b), W_(a)
1072#define AND_B(a, b) and B_(b), B_(a)
1073#define ARPL(a,b) arpl W_(b), a
1074#define BOUND_L(a, b) bound L_(b), L_(a)
1075#define BOUND_W(a, b) bound W_(b), W_(a)
1076#define BSF_L(a, b) bsf L_(b), L_(a)
1077#define BSF_W(a, b) bsf W_(b), W_(a)
1078#define BSR_L(a, b) bsr L_(b), L_(a)
1079#define BSR_W(a, b) bsr W_(b), W_(a)
1080#define BT_L(a, b) bt L_(b), L_(a)
1081#define BT_W(a, b) bt W_(b), W_(a)
1082#define BTC_L(a, b) btc L_(b), L_(a)
1083#define BTC_W(a, b) btc W_(b), W_(a)
1084#define BTR_L(a, b) btr L_(b), L_(a)
1085#define BTR_W(a, b) btr W_(b), W_(a)
1086#define BTS_L(a, b) bts L_(b), L_(a)
1087#define BTS_W(a, b) bts W_(b), W_(a)
1088#define CALL(a) call a
1089#define CALLF(s,a) call far s:a
1090#define CBW cbw
1091#define CWDE cwde
1092#define CLC clc
1093#define CLD cld
1094#define CLI cli
1095#define CLTS clts
1096#define CMC cmc
1097#define CMP_L(a, b) cmp L_(b), L_(a)
1098#define CMP_W(a, b) cmp W_(b), W_(a)
1099#define CMP_B(a, b) cmp B_(b), B_(a)
1100#define CMPS_L cmpsd
1101#define CMPS_W cmpsw
1102#define CMPS_B cmpsb
1103#define CWD cwd
1104#define CDQ cdq
1105#define DAA daa
1106#define DAS das
1107#define DEC_L(a) dec L_(a)
1108#define DEC_W(a) dec W_(a)
1109#define DEC_B(a) dec B_(a)
1110#define DIV_L(a) div L_(a)
1111#define DIV_W(a) div W_(a)
1112#define DIV_B(a) div B_(a)
1113#define ENTER(a,b) enter b, a
1114#define HLT hlt
1115#define IDIV_L(a) idiv L_(a)
1116#define IDIV_W(a) idiv W_(a)
1117#define IDIV_B(a) idiv B_(a)
1118#define IMUL_L(a, b) imul L_(b), L_(a)
1119#define IMUL_W(a, b) imul W_(b), W_(a)
1120#define IMUL_B(a) imul B_(a)
1121#define IN_L in EAX, DX
1122#define IN_W in AX, DX
1123#define IN_B in AL, DX
1124#define IN1_L(a) in1 L_(a)
1125#define IN1_W(a) in1 W_(a)
1126#define IN1_B(a) in1 B_(a)
1127#define INC_L(a) inc L_(a)
1128#define INC_W(a) inc W_(a)
1129#define INC_B(a) inc B_(a)
1130#define INS_L ins
1131#define INS_W ins
1132#define INS_B ins
1133#define INT(a) int B_(a)
1134#define INT3 int3
1135#define INTO into
1136#define IRET iret
1137#define IRETD iretd
1138#define JA(a) ja NEAR a
1139#define JAE(a) jae NEAR a
1140#define JB(a) jb NEAR a
1141#define JBE(a) jbe NEAR a
1142#define JC(a) jc NEAR a
1143#define JE(a) je NEAR a
1144#define JG(a) jg NEAR a
1145#define JGE(a) jge NEAR a
1146#define JL(a) jl NEAR a
1147#define JLE(a) jle NEAR a
1148#define JNA(a) jna NEAR a
1149#define JNAE(a) jnae NEAR a
1150#define JNB(a) jnb NEAR a
1151#define JNBE(a) jnbe NEAR a
1152#define JNC(a) jnc NEAR a
1153#define JNE(a) jne NEAR a
1154#define JNG(a) jng NEAR a
1155#define JNGE(a) jnge NEAR a
1156#define JNL(a) jnl NEAR a
1157#define JNLE(a) jnle NEAR a
1158#define JNO(a) jno NEAR a
1159#define JNP(a) jnp NEAR a
1160#define JNS(a) jns NEAR a
1161#define JNZ(a) jnz NEAR a
1162#define JO(a) jo NEAR a
1163#define JP(a) jp NEAR a
1164#define JPE(a) jpe NEAR a
1165#define JPO(a) jpo NEAR a
1166#define JS(a) js NEAR a
1167#define JZ(a) jz NEAR a
1168#define JMP(a) jmp a
1169#define JMPF(s,a) jmpf
1170#define LAHF lahf
1171#define LAR(a, b) lar b, a
1172#define LEA_L(a, b) lea P_(b), P_(a)
1173#define LEA_W(a, b) lea P_(b), P_(a)
1174#define LEAVE leave
1175#define LGDT(a) lgdt a
1176#define LIDT(a) lidt a
1177#define LDS(a, b) lds b, a
1178#define LES(a, b) les b, a
1179#define LFS(a, b) lfs b, a
1180#define LGS(a, b) lgs b, a
1181#define LSS(a, b) lss b, a
1182#define LLDT(a) lldt a
1183#define LMSW(a) lmsw a
1184#define LOCK lock
1185#define LODS_L lodsd
1186#define LODS_W lodsw
1187#define LODS_B lodsb
1188#define LOOP(a) loop a
1189#define LOOPE(a) loope a
1190#define LOOPZ(a) loopz a
1191#define LOOPNE(a) loopne a
1192#define LOOPNZ(a) loopnz a
1193#define LSL(a, b) lsl b, a
1194#define LTR(a) ltr a
1195#define MOV_SR(a, b) mov S_(b), S_(a)
1196#define MOV_L(a, b) mov L_(b), L_(a)
1197#define MOV_W(a, b) mov W_(b), W_(a)
1198#define MOV_B(a, b) mov B_(b), B_(a)
1199#define MOVS_L movsd
1200#define MOVS_W movsw
1201#define MOVS_B movsb
1202#define MOVSX_BL(a, b) movsx B_(b), B_(a)
1203#define MOVSX_BW(a, b) movsx B_(b), B_(a)
1204#define MOVSX_WL(a, b) movsx W_(b), W_(a)
1205#define MOVZX_BL(a, b) movzx B_(b), B_(a)
1206#define MOVZX_BW(a, b) movzx B_(b), B_(a)
1207#define MOVZX_WL(a, b) movzx W_(b), W_(a)
1208#define MUL_L(a) mul L_(a)
1209#define MUL_W(a) mul W_(a)
1210#define MUL_B(a) mul B_(a)
1211#define NEG_L(a) neg L_(a)
1212#define NEG_W(a) neg W_(a)
1213#define NEG_B(a) neg B_(a)
1214#define NOP nop
1215#define NOT_L(a) not L_(a)
1216#define NOT_W(a) not W_(a)
1217#define NOT_B(a) not B_(a)
1218#define OR_L(a,b) or L_(b), L_(a)
1219#define OR_W(a,b) or W_(b), W_(a)
1220#define OR_B(a,b) or B_(b), B_(a)
1221#define OUT_L out DX, EAX
1222#define OUT_W out DX, AX
1223#define OUT_B out DX, AL
1224#define OUT1_L(a) out1 L_(a)
1225#define OUT1_W(a) out1 W_(a)
1226#define OUT1_B(a) out1 B_(a)
1227#define OUTS_L outsd
1228#define OUTS_W outsw
1229#define OUTS_B outsb
1230#define POP_SR(a) pop S_(a)
1231#define POP_L(a) pop L_(a)
1232#define POP_W(a) pop W_(a)
1233#define POPA_L popad
1234#define POPA_W popa
1235#define POPF_L popfd
1236#define POPF_W popf
1237#define PUSH_SR(a) push S_(a)
1238#define PUSH_L(a) push L_(a)
1239#define PUSH_W(a) push W_(a)
1240#define PUSH_B(a) push B_(a)
1241#define PUSHA_L pushad
1242#define PUSHA_W pusha
1243#define PUSHF_L pushfd
1244#define PUSHF_W pushf
1245#define RCL_L(a, b) rcl L_(b), L_(a)
1246#define RCL_W(a, b) rcl W_(b), W_(a)
1247#define RCL_B(a, b) rcl B_(b), B_(a)
1248#define RCR_L(a, b) rcr L_(b), L_(a)
1249#define RCR_W(a, b) rcr W_(b), W_(a)
1250#define RCR_B(a, b) rcr B_(b), B_(a)
1251#define ROL_L(a, b) rol L_(b), L_(a)
1252#define ROL_W(a, b) rol W_(b), W_(a)
1253#define ROL_B(a, b) rol B_(b), B_(a)
1254#define ROR_L(a, b) ror L_(b), L_(a)
1255#define ROR_W(a, b) ror W_(b), W_(a)
1256#define ROR_B(a, b) ror B_(b), B_(a)
1257#define REP rep
1258#define REPE repe
1259#define REPNE repne
1260#define REPNZ REPNE
1261#define REPZ REPE
1262#define RET ret
1263#define SAHF sahf
1264#define SAL_L(a, b) sal L_(b), L_(a)
1265#define SAL_W(a, b) sal W_(b), W_(a)
1266#define SAL_B(a, b) sal B_(b), B_(a)
1267#define SAR_L(a, b) sar L_(b), L_(a)
1268#define SAR_W(a, b) sar W_(b), W_(a)
1269#define SAR_B(a, b) sar B_(b), B_(a)
1270#define SBB_L(a, b) sbb L_(b), L_(a)
1271#define SBB_W(a, b) sbb W_(b), W_(a)
1272#define SBB_B(a, b) sbb B_(b), B_(a)
1273#define SCAS_L scas
1274#define SCAS_W scas
1275#define SCAS_B scas
1276#define SETA(a) seta a
1277#define SETAE(a) setae a
1278#define SETB(a) setb a
1279#define SETBE(a) setbe a
1280#define SETC(a) setc a
1281#define SETE(a) sete a
1282#define SETG(a) setg a
1283#define SETGE(a) setge a
1284#define SETL(a) setl a
1285#define SETLE(a) setle a
1286#define SETNA(a) setna a
1287#define SETNAE(a) setnae a
1288#define SETNB(a) setnb a
1289#define SETNBE(a) setnbe a
1290#define SETNC(a) setnc a
1291#define SETNE(a) setne a
1292#define SETNG(a) setng a
1293#define SETNGE(a) setnge a
1294#define SETNL(a) setnl a
1295#define SETNLE(a) setnle a
1296#define SETNO(a) setno a
1297#define SETNP(a) setnp a
1298#define SETNS(a) setns a
1299#define SETNZ(a) setnz a
1300#define SETO(a) seto a
1301#define SETP(a) setp a
1302#define SETPE(a) setpe a
1303#define SETPO(a) setpo a
1304#define SETS(a) sets a
1305#define SETZ(a) setz a
1306#define SGDT(a) sgdt a
1307#define SIDT(a) sidt a
1308#define SHL_L(a, b) shl L_(b), L_(a)
1309#define SHL_W(a, b) shl W_(b), W_(a)
1310#define SHL_B(a, b) shl B_(b), B_(a)
1311#define SHLD_L(a,b,c) shld
1312#define SHLD2_L(a,b) shld L_(b), L_(a)
1313#define SHLD_W(a,b,c) shld
1314#define SHLD2_W(a,b) shld W_(b), W_(a)
1315#define SHR_L(a, b) shr L_(b), L_(a)
1316#define SHR_W(a, b) shr W_(b), W_(a)
1317#define SHR_B(a, b) shr B_(b), B_(a)
1318#define SHRD_L(a,b,c) shrd
1319#define SHRD2_L(a,b) shrd L_(b), L_(a)
1320#define SHRD_W(a,b,c) shrd
1321#define SHRD2_W(a,b) shrd W_(b), W_(a)
1322#define SLDT(a) sldt a
1323#define SMSW(a) smsw a
1324#define STC stc
1325#define STD std
1326#define STI sti
1327#define STOS_L stos
1328#define STOS_W stos
1329#define STOS_B stos
1330#define STR(a) str a
1331#define SUB_L(a, b) sub L_(b), L_(a)
1332#define SUB_W(a, b) sub W_(b), W_(a)
1333#define SUB_B(a, b) sub B_(b), B_(a)
1334#define TEST_L(a, b) test L_(b), L_(a)
1335#define TEST_W(a, b) test W_(b), W_(a)
1336#define TEST_B(a, b) test B_(b), B_(a)
1337#define VERR(a) verr a
1338#define VERW(a) verw a
1339#define WAIT wait
1340#define XCHG_L(a, b) xchg L_(b), L_(a)
1341#define XCHG_W(a, b) xchg W_(b), W_(a)
1342#define XCHG_B(a, b) xchg B_(b), B_(a)
1343#define XLAT xlat
1344#define XOR_L(a, b) xor L_(b), L_(a)
1345#define XOR_W(a, b) xor W_(b), W_(a)
1346#define XOR_B(a, b) xor B_(b), B_(a)
1347#define F2XM1 f2xm1
1348#define FABS fabs
1349#define FADD_D(a) fadd D_(a)
1350#define FADD_S(a) fadd S_(a)
1351#define FADD2(a, b) fadd b, a
1352#define FADDP(a, b) faddp b, a
1353#define FIADD_L(a) fiadd L_(a)
1354#define FIADD_W(a) fiadd W_(a)
1355#define FBLD(a) fbld a
1356#define FBSTP(a) fbstp a
1357#define FCHS fchs
1358#define FCLEX fclex
1359#define FNCLEX fnclex
1360#define FCOM(a) fcom a
1361#define FCOM_D(a) fcom D_(a)
1362#define FCOM_S(a) fcom S_(a)
1363#define FCOMP(a) fcomp a
1364#define FCOMP_D(a) fcomp D_(a)
1365#define FCOMP_S(a) fcomp S_(a)
1366#define FCOMPP fcompp
1367#define FCOS fcos
1368#define FDECSTP fdecstp
1369#define FDIV_D(a) fdiv D_(a)
1370#define FDIV_S(a) fdiv S_(a)
1371#define FDIV2(a, b) fdiv b, a
1372#define FDIVP(a, b) fdivp b, a
1373#define FIDIV_L(a) fidiv L_(a)
1374#define FIDIV_W(a) fidiv W_(a)
1375#define FDIVR_D(a) fdivr D_(a)
1376#define FDIVR_S(a) fdivr S_(a)
1377#define FDIVR2(a, b) fdivr b, a
1378#define FDIVRP(a, b) fdivrp b, a
1379#define FIDIVR_L(a) fidivr L_(a)
1380#define FIDIVR_W(a) fidivr W_(a)
1381#define FFREE(a) ffree a
1382#define FICOM_L(a) ficom L_(a)
1383#define FICOM_W(a) ficom W_(a)
1384#define FICOMP_L(a) ficomp L_(a)
1385#define FICOMP_W(a) ficomp W_(a)
1386#define FILD_Q(a) fild D_(a)
1387#define FILD_L(a) fild L_(a)
1388#define FILD_W(a) fild W_(a)
1389#define FINCSTP fincstp
1390#define FINIT finit
1391#define FNINIT fninit
1392#define FIST_L(a) fist L_(a)
1393#define FIST_W(a) fist W_(a)
1394#define FISTP_Q(a) fistp D_(a)
1395#define FISTP_L(a) fistp L_(a)
1396#define FISTP_W(a) fistp W_(a)
1397#define FLD_X(a) fld X_(a)
1398#define FLD_D(a) fld D_(a)
1399#define FLD_S(a) fld S_(a)
1400#define FLD1 fld1
1401#define FLDL2T fldl2t
1402#define FLDL2E fldl2e
1403#define FLDPI fldpi
1404#define FLDLG2 fldlg2
1405#define FLDLN2 fldln2
1406#define FLDZ fldz
1407#define FLDCW(a) fldcw a
1408#define FLDENV(a) fldenv a
1409#define FMUL_S(a) fmul S_(a)
1410#define FMUL_D(a) fmul D_(a)
1411#define FMUL2(a, b) fmul b, a
1412#define FMULP(a, b) fmulp b, a
1413#define FIMUL_L(a) fimul L_(a)
1414#define FIMUL_W(a) fimul W_(a)
1415#define FNOP fnop
1416#define FPATAN fpatan
1417#define FPREM fprem
1418#define FPREM1 fprem1
1419#define FPTAN fptan
1420#define FRNDINT frndint
1421#define FRSTOR(a) frstor a
1422#define FSAVE(a) fsave a
1423#define FNSAVE(a) fnsave a
1424#define FSCALE fscale
1425#define FSIN fsin
1426#define FSINCOS fsincos
1427#define FSQRT fsqrt
1428#define FST_D(a) fst D_(a)
1429#define FST_S(a) fst S_(a)
1430#define FSTP_X(a) fstp X_(a)
1431#define FSTP_D(a) fstp D_(a)
1432#define FSTP_S(a) fstp S_(a)
1433#define FSTP(a) fstp a
1434#define FSTCW(a) fstcw a
1435#define FNSTCW(a) fnstcw a
1436#define FSTENV(a) fstenv a
1437#define FNSTENV(a) fnstenv a
1438#define FSTSW(a) fstsw a
1439#define FNSTSW(a) fnstsw a
1440#define FSUB_S(a) fsub S_(a)
1441#define FSUB_D(a) fsub D_(a)
1442#define FSUB2(a, b) fsub b, a
1443#define FSUBP(a, b) fsubp b, a
1444#define FISUB_L(a) fisub L_(a)
1445#define FISUB_W(a) fisub W_(a)
1446#define FSUBR_S(a) fsubr S_(a)
1447#define FSUBR_D(a) fsubr D_(a)
1448#define FSUBR2(a, b) fsubr b, a
1449#define FSUBRP(a, b) fsubrp b, a
1450#define FISUBR_L(a) fisubr L_(a)
1451#define FISUBR_W(a) fisubr W_(a)
1452#define FTST ftst
1453#define FUCOM(a) fucom a
1454#define FUCOMP(a) fucomp a
1455#define FUCOMPP fucompp
1456#define FWAIT fwait
1457#define FXAM fxam
1458#define FXCH(a) fxch a
1459#define FXTRACT fxtract
1460#define FYL2X fyl2x
1461#define FYL2XP1 fyl2xp1
1462
1463/* New instructions */
1464#define CPUID D_BYTE 15, 162
1465#define RDTSC D_BYTE 15, 49
1466
1467#endif /* NASM_ASSEMBLER, MASM_ASSEMBLER */
1468
1469 /****************************************/
1470 /* */
1471 /* Extensions to x86 insn set - */
1472 /* MMX, 3DNow! */
1473 /* */
1474 /****************************************/
1475
1476#if defined(NASM_ASSEMBLER) || defined(MASM_ASSEMBLER)
1477#define P_ARG1(a) P_ ## a
1478#define P_ARG2(a, b) P_ ## b, P_ ## a
1479#define P_ARG3(a, b, c) P_ ## c, P_ ## b, P_ ## a
1480#else
1481#define P_ARG1(a) a
1482#define P_ARG2(a, b) a, b
1483#define P_ARG3(a, b, c) a, b, c
1484#endif
1485
1486/* MMX */
1487#define MOVD(a, b) movd P_ARG2(a, b)
1488#define MOVQ(a, b) movq P_ARG2(a, b)
1489
1490#define PADDB(a, b) paddb P_ARG2(a, b)
1491#define PADDW(a, b) paddw P_ARG2(a, b)
1492#define PADDD(a, b) paddd P_ARG2(a, b)
1493
1494#define PADDSB(a, b) paddsb P_ARG2(a, b)
1495#define PADDSW(a, b) paddsw P_ARG2(a, b)
1496
1497#define PADDUSB(a, b) paddusb P_ARG2(a, b)
1498#define PADDUSW(a, b) paddusw P_ARG2(a, b)
1499
1500#define PSUBB(a, b) psubb P_ARG2(a, b)
1501#define PSUBW(a, b) psubw P_ARG2(a, b)
1502#define PSUBD(a, b) psubd P_ARG2(a, b)
1503
1504#define PSUBSB(a, b) psubsb P_ARG2(a, b)
1505#define PSUBSW(a, b) psubsw P_ARG2(a, b)
1506
1507#define PSUBUSB(a, b) psubusb P_ARG2(a, b)
1508#define PSUBUSW(a, b) psubusw P_ARG2(a, b)
1509
1510#define PCMPEQB(a, b) pcmpeqb P_ARG2(a, b)
1511#define PCMPEQW(a, b) pcmpeqw P_ARG2(a, b)
1512#define PCMPEQD(a, b) pcmpeqd P_ARG2(a, b)
1513
1514#define PCMPGTB(a, b) pcmpgtb P_ARG2(a, b)
1515#define PCMPGTW(a, b) pcmpgtw P_ARG2(a, b)
1516#define PCMPGTD(a, b) pcmpgtd P_ARG2(a, b)
1517
1518#define PMULHW(a, b) pmulhw P_ARG2(a, b)
1519#define PMULLW(a, b) pmullw P_ARG2(a, b)
1520
1521#define PMADDWD(a, b) pmaddwd P_ARG2(a, b)
1522
1523#define PAND(a, b) pand P_ARG2(a, b)
1524
1525#define PANDN(a, b) pandn P_ARG2(a, b)
1526
1527#define POR(a, b) por P_ARG2(a, b)
1528
1529#define PXOR(a, b) pxor P_ARG2(a, b)
1530
1531#define PSRAW(a, b) psraw P_ARG2(a, b)
1532#define PSRAD(a, b) psrad P_ARG2(a, b)
1533
1534#define PSRLW(a, b) psrlw P_ARG2(a, b)
1535#define PSRLD(a, b) psrld P_ARG2(a, b)
1536#define PSRLQ(a, b) psrlq P_ARG2(a, b)
1537
1538#define PSLLW(a, b) psllw P_ARG2(a, b)
1539#define PSLLD(a, b) pslld P_ARG2(a, b)
1540#define PSLLQ(a, b) psllq P_ARG2(a, b)
1541
1542#define PACKSSWB(a, b) packsswb P_ARG2(a, b)
1543#define PACKSSDW(a, b) packssdw P_ARG2(a, b)
1544#define PACKUSWB(a, b) packuswb P_ARG2(a, b)
1545
1546#define PUNPCKHBW(a, b) punpckhbw P_ARG2(a, b)
1547#define PUNPCKHWD(a, b) punpckhwd P_ARG2(a, b)
1548#define PUNPCKHDQ(a, b) punpckhdq P_ARG2(a, b)
1549#define PUNPCKLBW(a, b) punpcklbw P_ARG2(a, b)
1550#define PUNPCKLWD(a, b) punpcklwd P_ARG2(a, b)
1551#define PUNPCKLDQ(a, b) punpckldq P_ARG2(a, b)
1552
1553#define EMMS emms
1554
1555/* AMD 3DNow! */
1556#define PAVGUSB(a, b) pavgusb P_ARG2(a, b)
1557#define PFADD(a, b) pfadd P_ARG2(a, b)
1558#define PFSUB(a, b) pfsub P_ARG2(a, b)
1559#define PFSUBR(a, b) pfsubr P_ARG2(a, b)
1560#define PFACC(a, b) pfacc P_ARG2(a, b)
1561#define PFCMPGE(a, b) pfcmpge P_ARG2(a, b)
1562#define PFCMPGT(a, b) pfcmpgt P_ARG2(a, b)
1563#define PFCMPEQ(a, b) pfcmpeq P_ARG2(a, b)
1564#define PFMIN(a, b) pfmin P_ARG2(a, b)
1565#define PFMAX(a, b) pfmax P_ARG2(a, b)
1566#define PI2FD(a, b) pi2fd P_ARG2(a, b)
1567#define PF2ID(a, b) pf2id P_ARG2(a, b)
1568#define PFRCP(a, b) pfrcp P_ARG2(a, b)
1569#define PFRSQRT(a, b) pfrsqrt P_ARG2(a, b)
1570#define PFMUL(a, b) pfmul P_ARG2(a, b)
1571#define PFRCPIT1(a, b) pfrcpit1 P_ARG2(a, b)
1572#define PFRSQIT1(a, b) pfrsqit1 P_ARG2(a, b)
1573#define PFRCPIT2(a, b) pfrcpit2 P_ARG2(a, b)
1574#define PMULHRW(a, b) pmulhrw P_ARG2(a, b)
1575
1576#define FEMMS femms
1577#define PREFETCH(a) prefetch P_ARG1(a)
1578#define PREFETCHW(a) prefetchw P_ARG1(a)
1579
1580/* Intel SSE */
1581#define ADDPS(a, b) addps P_ARG2(a, b)
1582#define ADDSS(a, b) addss P_ARG2(a, b)
1583#define ANDNPS(a, b) andnps P_ARG2(a, b)
1584#define ANDPS(a, b) andps P_ARG2(a, b)
1585/*
1586 NASM only knows the pseudo ops for these.
1587 #define CMPPS(a, b, c) cmpps P_ARG3(a, b, c)
1588 #define CMPSS(a, b, c) cmpss P_ARG3(a, b, c)
1589*/
1590#define CMPEQPS(a, b) cmpeqps P_ARG2(a, b)
1591#define CMPLTPS(a, b) cmpltps P_ARG2(a, b)
1592#define CMPLEPS(a, b) cmpleps P_ARG2(a, b)
1593#define CMPUNORDPS(a, b) cmpunordps P_ARG2(a, b)
1594#define CMPNEQPS(a, b) cmpneqps P_ARG2(a, b)
1595#define CMPNLTPS(a, b) cmpnltps P_ARG2(a, b)
1596#define CMPNLEPS(a, b) cmpnleps P_ARG2(a, b)
1597#define CMPORDPS(a, b) cmpordps P_ARG2(a, b)
1598#define CMPEQSS(a, b) cmpeqss P_ARG2(a, b)
1599#define CMPLTSS(a, b) cmpltss P_ARG2(a, b)
1600#define CMPLESS(a, b) cmpless P_ARG2(a, b)
1601#define CMPUNORDSS(a, b) cmpunordss P_ARG2(a, b)
1602#define CMPNEQSS(a, b) cmpneqss P_ARG2(a, b)
1603#define CMPNLTSS(a, b) cmpnltss P_ARG2(a, b)
1604#define CMPNLESS(a, b) cmpnless P_ARG2(a, b)
1605#define CMPORDSS(a, b) cmpordss P_ARG2(a, b)
1606#define COMISS(a, b) comiss P_ARG2(a, b)
1607#define CVTPI2PS(a, b) cvtpi2ps P_ARG2(a, b)
1608#define CVTPS2PI(a, b) cvtps2pi P_ARG2(a, b)
1609#define CVTSI2SS(a, b) cvtsi2ss P_ARG2(a, b)
1610#define CVTSS2SI(a, b) cvtss2si P_ARG2(a, b)
1611#define CVTTPS2PI(a, b) cvttps2pi P_ARG2(a, b)
1612#define CVTTSS2SI(a, b) cvttss2si P_ARG2(a, b)
1613#define DIVPS(a, b) divps P_ARG2(a, b)
1614#define DIVSS(a, b) divss P_ARG2(a, b)
1615#define FXRSTOR(a) fxrstor P_ARG1(a)
1616#define FXSAVE(a) fxsave P_ARG1(a)
1617#define LDMXCSR(a) ldmxcsr P_ARG1(a)
1618#define MAXPS(a, b) maxps P_ARG2(a, b)
1619#define MAXSS(a, b) maxss P_ARG2(a, b)
1620#define MINPS(a, b) minps P_ARG2(a, b)
1621#define MINSS(a, b) minss P_ARG2(a, b)
1622#define MOVAPS(a, b) movaps P_ARG2(a, b)
1623#define MOVHLPS(a, b) movhlps P_ARG2(a, b)
1624#define MOVHPS(a, b) movhps P_ARG2(a, b)
1625#define MOVLHPS(a, b) movlhps P_ARG2(a, b)
1626#define MOVLPS(a, b) movlps P_ARG2(a, b)
1627#define MOVMSKPS(a, b) movmskps P_ARG2(a, b)
1628#define MOVSS(a, b) movss P_ARG2(a, b)
1629#define MOVUPS(a, b) movups P_ARG2(a, b)
1630#define MULPS(a, b) mulps P_ARG2(a, b)
1631#define MULSS(a, b) mulss P_ARG2(a, b)
1632#define ORPS(a, b) orps P_ARG2(a, b)
1633#define RCPPS(a, b) rcpps P_ARG2(a, b)
1634#define RCPSS(a, b) rcpss P_ARG2(a, b)
1635#define RSQRTPS(a, b) rsqrtps P_ARG2(a, b)
1636#define RSQRTSS(a, b) rsqrtss P_ARG2(a, b)
1637#define SHUFPS(a, b, c) shufps P_ARG3(a, b, c)
1638#define SQRTPS(a, b) sqrtps P_ARG2(a, b)
1639#define SQRTSS(a, b) sqrtss P_ARG2(a, b)
1640#define STMXCSR(a) stmxcsr P_ARG1(a)
1641#define SUBPS(a, b) subps P_ARG2(a, b)
1642#define UCOMISS(a, b) ucomiss P_ARG2(a, b)
1643#define UNPCKHPS(a, b) unpckhps P_ARG2(a, b)
1644#define UNPCKLPS(a, b) unpcklps P_ARG2(a, b)
1645#define XORPS(a, b) xorps P_ARG2(a, b)
1646
1647
1648#endif /* __ASSYNTAX_H__ */
Note: See TracBrowser for help on using the repository browser.