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