c-i386.texi revision 77298
1@c Copyright (C) 1991, 92, 93, 94, 95, 97, 1998 Free Software Foundation, Inc.
2@c This is part of the GAS manual.
3@c For copying conditions, see the file as.texinfo.
4@ifset GENERIC
5@page
6@node i386-Dependent
7@chapter 80386 Dependent Features
8@end ifset
9@ifclear GENERIC
10@node Machine Dependencies
11@chapter 80386 Dependent Features
12@end ifclear
13
14@cindex i386 support
15@cindex i80306 support
16@cindex x86-64 support
17
18The i386 version @code{@value{AS}} supports both the original Intel 386
19architecture in both 16 and 32-bit mode as well as AMD x86-64 architecture
20extending the Intel architecture to 64-bits.
21
22@menu
23* i386-Options::                Options
24* i386-Syntax::                 AT&T Syntax versus Intel Syntax
25* i386-Mnemonics::              Instruction Naming
26* i386-Regs::                   Register Naming
27* i386-Prefixes::               Instruction Prefixes
28* i386-Memory::                 Memory References
29* i386-jumps::                  Handling of Jump Instructions
30* i386-Float::                  Floating Point
31* i386-SIMD::                   Intel's MMX and AMD's 3DNow! SIMD Operations
32* i386-16bit::                  Writing 16-bit Code
33* i386-Arch::                   Specifying an x86 CPU architecture
34* i386-Bugs::                   AT&T Syntax bugs
35* i386-Notes::                  Notes
36@end menu
37
38@node i386-Options
39@section Options
40
41@cindex options for i386
42@cindex options for x86-64
43@cindex i386 options
44@cindex x86-64 options 
45
46The i386 version of @code{@value{AS}} has a few machine
47dependent options:
48
49@table @code
50@cindex @samp{--32} option, i386
51@cindex @samp{--32} option, x86-64
52@cindex @samp{--64} option, i386
53@cindex @samp{--64} option, x86-64
54@item --32 | --64
55Select the word size, either 32 bits or 64 bits. Selecting 32-bit
56implies Intel i386 architecture, while 64-bit implies AMD x86-64
57architecture.
58
59These options are only available with the ELF object file format, and
60require that the necessary BFD support has been included (on a 32-bit
61platform you have to add --enable-64-bit-bfd to configure enable 64-bit
62usage and use x86-64 as target platform).
63@end table
64
65@node i386-Syntax
66@section AT&T Syntax versus Intel Syntax
67
68@cindex i386 intel_syntax pseudo op
69@cindex intel_syntax pseudo op, i386
70@cindex i386 att_syntax pseudo op
71@cindex att_syntax pseudo op, i386
72@cindex i386 syntax compatibility
73@cindex syntax compatibility, i386
74@cindex x86-64 intel_syntax pseudo op
75@cindex intel_syntax pseudo op, x86-64
76@cindex x86-64 att_syntax pseudo op
77@cindex att_syntax pseudo op, x86-64
78@cindex x86-64 syntax compatibility
79@cindex syntax compatibility, x86-64
80
81@code{@value{AS}} now supports assembly using Intel assembler syntax.
82@code{.intel_syntax} selects Intel mode, and @code{.att_syntax} switches
83back to the usual AT&T mode for compatibility with the output of
84@code{@value{GCC}}.  Either of these directives may have an optional
85argument, @code{prefix}, or @code{noprefix} specifying whether registers
86require a @samp{%} prefix.  AT&T System V/386 assembler syntax is quite
87different from Intel syntax.  We mention these differences because
88almost all 80386 documents use Intel syntax.  Notable differences
89between the two syntaxes are:
90
91@cindex immediate operands, i386
92@cindex i386 immediate operands
93@cindex register operands, i386
94@cindex i386 register operands
95@cindex jump/call operands, i386
96@cindex i386 jump/call operands
97@cindex operand delimiters, i386
98
99@cindex immediate operands, x86-64
100@cindex x86-64 immediate operands
101@cindex register operands, x86-64
102@cindex x86-64 register operands
103@cindex jump/call operands, x86-64
104@cindex x86-64 jump/call operands
105@cindex operand delimiters, x86-64
106@itemize @bullet
107@item
108AT&T immediate operands are preceded by @samp{$}; Intel immediate
109operands are undelimited (Intel @samp{push 4} is AT&T @samp{pushl $4}).
110AT&T register operands are preceded by @samp{%}; Intel register operands
111are undelimited.  AT&T absolute (as opposed to PC relative) jump/call
112operands are prefixed by @samp{*}; they are undelimited in Intel syntax.
113
114@cindex i386 source, destination operands
115@cindex source, destination operands; i386
116@cindex x86-64 source, destination operands
117@cindex source, destination operands; x86-64
118@item
119AT&T and Intel syntax use the opposite order for source and destination
120operands.  Intel @samp{add eax, 4} is @samp{addl $4, %eax}.  The
121@samp{source, dest} convention is maintained for compatibility with
122previous Unix assemblers.  Note that instructions with more than one
123source operand, such as the @samp{enter} instruction, do @emph{not} have
124reversed order.  @ref{i386-Bugs}.
125
126@cindex mnemonic suffixes, i386
127@cindex sizes operands, i386
128@cindex i386 size suffixes
129@cindex mnemonic suffixes, x86-64
130@cindex sizes operands, x86-64
131@cindex x86-64 size suffixes
132@item
133In AT&T syntax the size of memory operands is determined from the last
134character of the instruction mnemonic.  Mnemonic suffixes of @samp{b},
135@samp{w}, @samp{l} and @samp{q} specify byte (8-bit), word (16-bit), long
136(32-bit) and quadruple word (64-bit) memory references.  Intel syntax accomplishes
137this by prefixing memory operands (@emph{not} the instruction mnemonics) with
138@samp{byte ptr}, @samp{word ptr}, @samp{dword ptr} and @samp{qword ptr}.  Thus,
139Intel @samp{mov al, byte ptr @var{foo}} is @samp{movb @var{foo}, %al} in AT&T
140syntax.
141
142@cindex return instructions, i386
143@cindex i386 jump, call, return
144@cindex return instructions, x86-64
145@cindex x86-64 jump, call, return
146@item
147Immediate form long jumps and calls are
148@samp{lcall/ljmp $@var{section}, $@var{offset}} in AT&T syntax; the
149Intel syntax is
150@samp{call/jmp far @var{section}:@var{offset}}.  Also, the far return
151instruction
152is @samp{lret $@var{stack-adjust}} in AT&T syntax; Intel syntax is
153@samp{ret far @var{stack-adjust}}.
154
155@cindex sections, i386
156@cindex i386 sections
157@cindex sections, x86-64
158@cindex x86-64 sections
159@item
160The AT&T assembler does not provide support for multiple section
161programs.  Unix style systems expect all programs to be single sections.
162@end itemize
163
164@node i386-Mnemonics
165@section Instruction Naming
166
167@cindex i386 instruction naming
168@cindex instruction naming, i386
169@cindex x86-64 instruction naming
170@cindex instruction naming, x86-64
171
172Instruction mnemonics are suffixed with one character modifiers which
173specify the size of operands.  The letters @samp{b}, @samp{w}, @samp{l}
174and @samp{q} specify byte, word, long and quadruple word operands.  If
175no suffix is specified by an instruction then @code{@value{AS}} tries to
176fill in the missing suffix based on the destination register operand
177(the last one by convention).  Thus, @samp{mov %ax, %bx} is equivalent
178to @samp{movw %ax, %bx}; also, @samp{mov $1, %bx} is equivalent to
179@samp{movw $1, bx}.  Note that this is incompatible with the AT&T Unix
180assembler which assumes that a missing mnemonic suffix implies long
181operand size.  (This incompatibility does not affect compiler output
182since compilers always explicitly specify the mnemonic suffix.)
183
184Almost all instructions have the same names in AT&T and Intel format.
185There are a few exceptions.  The sign extend and zero extend
186instructions need two sizes to specify them.  They need a size to
187sign/zero extend @emph{from} and a size to zero extend @emph{to}.  This
188is accomplished by using two instruction mnemonic suffixes in AT&T
189syntax.  Base names for sign extend and zero extend are
190@samp{movs@dots{}} and @samp{movz@dots{}} in AT&T syntax (@samp{movsx}
191and @samp{movzx} in Intel syntax).  The instruction mnemonic suffixes
192are tacked on to this base name, the @emph{from} suffix before the
193@emph{to} suffix.  Thus, @samp{movsbl %al, %edx} is AT&T syntax for
194``move sign extend @emph{from} %al @emph{to} %edx.''  Possible suffixes,
195thus, are @samp{bl} (from byte to long), @samp{bw} (from byte to word),
196@samp{wl} (from word to long), @samp{bq} (from byte to quadruple word),
197@samp{wq} (from word to quadruple word), and @samp{lq} (from long to
198quadruple word).
199
200@cindex conversion instructions, i386
201@cindex i386 conversion instructions
202@cindex conversion instructions, x86-64
203@cindex x86-64 conversion instructions
204The Intel-syntax conversion instructions
205
206@itemize @bullet
207@item
208@samp{cbw} --- sign-extend byte in @samp{%al} to word in @samp{%ax},
209
210@item
211@samp{cwde} --- sign-extend word in @samp{%ax} to long in @samp{%eax},
212
213@item
214@samp{cwd} --- sign-extend word in @samp{%ax} to long in @samp{%dx:%ax},
215
216@item
217@samp{cdq} --- sign-extend dword in @samp{%eax} to quad in @samp{%edx:%eax},
218
219@item
220@samp{cdqe} --- sign-extend dword in @samp{%eax} to quad in @samp{%rax}
221(x86-64 only),
222
223@item
224@samp{cdo} --- sign-extend quad in @samp{%rax} to octuple in
225@samp{%rdx:%rax} (x86-64 only),
226@end itemize
227
228@noindent
229are called @samp{cbtw}, @samp{cwtl}, @samp{cwtd}, @samp{cltd}, @samp{cltq}, and
230@samp{cqto} in AT&T naming.  @code{@value{AS}} accepts either naming for these
231instructions.
232
233@cindex jump instructions, i386
234@cindex call instructions, i386
235@cindex jump instructions, x86-64
236@cindex call instructions, x86-64
237Far call/jump instructions are @samp{lcall} and @samp{ljmp} in
238AT&T syntax, but are @samp{call far} and @samp{jump far} in Intel
239convention.
240
241@node i386-Regs
242@section Register Naming
243
244@cindex i386 registers
245@cindex registers, i386
246@cindex x86-64 registers
247@cindex registers, x86-64
248Register operands are always prefixed with @samp{%}.  The 80386 registers
249consist of
250
251@itemize @bullet
252@item
253the 8 32-bit registers @samp{%eax} (the accumulator), @samp{%ebx},
254@samp{%ecx}, @samp{%edx}, @samp{%edi}, @samp{%esi}, @samp{%ebp} (the
255frame pointer), and @samp{%esp} (the stack pointer).
256
257@item
258the 8 16-bit low-ends of these: @samp{%ax}, @samp{%bx}, @samp{%cx},
259@samp{%dx}, @samp{%di}, @samp{%si}, @samp{%bp}, and @samp{%sp}.
260
261@item
262the 8 8-bit registers: @samp{%ah}, @samp{%al}, @samp{%bh},
263@samp{%bl}, @samp{%ch}, @samp{%cl}, @samp{%dh}, and @samp{%dl} (These
264are the high-bytes and low-bytes of @samp{%ax}, @samp{%bx},
265@samp{%cx}, and @samp{%dx})
266
267@item
268the 6 section registers @samp{%cs} (code section), @samp{%ds}
269(data section), @samp{%ss} (stack section), @samp{%es}, @samp{%fs},
270and @samp{%gs}.
271
272@item
273the 3 processor control registers @samp{%cr0}, @samp{%cr2}, and
274@samp{%cr3}.
275
276@item
277the 6 debug registers @samp{%db0}, @samp{%db1}, @samp{%db2},
278@samp{%db3}, @samp{%db6}, and @samp{%db7}.
279
280@item
281the 2 test registers @samp{%tr6} and @samp{%tr7}.
282
283@item
284the 8 floating point register stack @samp{%st} or equivalently
285@samp{%st(0)}, @samp{%st(1)}, @samp{%st(2)}, @samp{%st(3)},
286@samp{%st(4)}, @samp{%st(5)}, @samp{%st(6)}, and @samp{%st(7)}.
287These registers are overloaded by 8 MMX registers @samp{%mm0},
288@samp{%mm1}, @samp{%mm2}, @samp{%mm3}, @samp{%mm4}, @samp{%mm5},
289@samp{%mm6} and @samp{%mm7}.
290
291@item
292the 8 SSE registers registers @samp{%xmm0}, @samp{%xmm1}, @samp{%xmm2},
293@samp{%xmm3}, @samp{%xmm4}, @samp{%xmm5}, @samp{%xmm6} and @samp{%xmm7}.
294@end itemize
295
296The AMD x86-64 architecture extends the register set by:
297
298@itemize @bullet
299@item
300enhancing the 8 32-bit registers to 64-bit: @samp{%rax} (the
301accumulator), @samp{%rbx}, @samp{%rcx}, @samp{%rdx}, @samp{%rdi},
302@samp{%rsi}, @samp{%rbp} (the frame pointer), @samp{%rsp} (the stack
303pointer)
304
305@item
306the 8 extended registers @samp{%r8}--@samp{%r15}.
307
308@item
309the 8 32-bit low ends of the extended registers: @samp{%r8d}--@samp{%r15d}
310
311@item
312the 8 16-bit low ends of the extended registers: @samp{%r8w}--@samp{%r15w}
313
314@item
315the 8 8-bit low ends of the extended registers: @samp{%r8b}--@samp{%r15b}
316
317@item
318the 4 8-bit registers: @samp{%sil}, @samp{%dil}, @samp{%bpl}, @samp{%spl}.
319
320@item
321the 8 debug registers: @samp{%db8}--@samp{%db15}.
322
323@item
324the 8 SSE registers: @samp{%xmm8}--@samp{%xmm15}.
325@end itemize
326
327@node i386-Prefixes
328@section Instruction Prefixes
329
330@cindex i386 instruction prefixes
331@cindex instruction prefixes, i386
332@cindex prefixes, i386
333Instruction prefixes are used to modify the following instruction.  They
334are used to repeat string instructions, to provide section overrides, to
335perform bus lock operations, and to change operand and address sizes.
336(Most instructions that normally operate on 32-bit operands will use
33716-bit operands if the instruction has an ``operand size'' prefix.)
338Instruction prefixes are best written on the same line as the instruction
339they act upon. For example, the @samp{scas} (scan string) instruction is
340repeated with:
341
342@smallexample
343        repne scas %es:(%edi),%al
344@end smallexample
345
346You may also place prefixes on the lines immediately preceding the
347instruction, but this circumvents checks that @code{@value{AS}} does
348with prefixes, and will not work with all prefixes.
349
350Here is a list of instruction prefixes:
351
352@cindex section override prefixes, i386
353@itemize @bullet
354@item
355Section override prefixes @samp{cs}, @samp{ds}, @samp{ss}, @samp{es},
356@samp{fs}, @samp{gs}.  These are automatically added by specifying
357using the @var{section}:@var{memory-operand} form for memory references.
358
359@cindex size prefixes, i386
360@item
361Operand/Address size prefixes @samp{data16} and @samp{addr16}
362change 32-bit operands/addresses into 16-bit operands/addresses,
363while @samp{data32} and @samp{addr32} change 16-bit ones (in a
364@code{.code16} section) into 32-bit operands/addresses.  These prefixes
365@emph{must} appear on the same line of code as the instruction they
366modify. For example, in a 16-bit @code{.code16} section, you might
367write:
368
369@smallexample
370        addr32 jmpl *(%ebx)
371@end smallexample
372
373@cindex bus lock prefixes, i386
374@cindex inhibiting interrupts, i386
375@item
376The bus lock prefix @samp{lock} inhibits interrupts during execution of
377the instruction it precedes.  (This is only valid with certain
378instructions; see a 80386 manual for details).
379
380@cindex coprocessor wait, i386
381@item
382The wait for coprocessor prefix @samp{wait} waits for the coprocessor to
383complete the current instruction.  This should never be needed for the
38480386/80387 combination.
385
386@cindex repeat prefixes, i386
387@item
388The @samp{rep}, @samp{repe}, and @samp{repne} prefixes are added
389to string instructions to make them repeat @samp{%ecx} times (@samp{%cx}
390times if the current address size is 16-bits).
391@cindex REX prefixes, i386
392@item
393The @samp{rex} family of prefixes is used by x86-64 to encode
394extensions to i386 instruction set.  The @samp{rex} prefix has four
395bits --- an operand size overwrite (@code{64}) used to change operand size
396from 32-bit to 64-bit and X, Y and Z extensions bits used to extend the
397register set.
398
399You may write the @samp{rex} prefixes directly. The @samp{rex64xyz}
400instruction emits @samp{rex} prefix with all the bits set.  By omitting
401the @code{64}, @code{x}, @code{y} or @code{z} you may write other
402prefixes as well.  Normally, there is no need to write the prefixes
403explicitly, since gas will automatically generate them based on the
404instruction operands.
405@end itemize
406
407@node i386-Memory
408@section Memory References
409
410@cindex i386 memory references
411@cindex memory references, i386
412@cindex x86-64 memory references
413@cindex memory references, x86-64
414An Intel syntax indirect memory reference of the form
415
416@smallexample
417@var{section}:[@var{base} + @var{index}*@var{scale} + @var{disp}]
418@end smallexample
419
420@noindent
421is translated into the AT&T syntax
422
423@smallexample
424@var{section}:@var{disp}(@var{base}, @var{index}, @var{scale})
425@end smallexample
426
427@noindent
428where @var{base} and @var{index} are the optional 32-bit base and
429index registers, @var{disp} is the optional displacement, and
430@var{scale}, taking the values 1, 2, 4, and 8, multiplies @var{index}
431to calculate the address of the operand.  If no @var{scale} is
432specified, @var{scale} is taken to be 1.  @var{section} specifies the
433optional section register for the memory operand, and may override the
434default section register (see a 80386 manual for section register
435defaults). Note that section overrides in AT&T syntax @emph{must}
436be preceded by a @samp{%}.  If you specify a section override which
437coincides with the default section register, @code{@value{AS}} does @emph{not}
438output any section register override prefixes to assemble the given
439instruction.  Thus, section overrides can be specified to emphasize which
440section register is used for a given memory operand.
441
442Here are some examples of Intel and AT&T style memory references:
443
444@table @asis
445@item AT&T: @samp{-4(%ebp)}, Intel:  @samp{[ebp - 4]}
446@var{base} is @samp{%ebp}; @var{disp} is @samp{-4}. @var{section} is
447missing, and the default section is used (@samp{%ss} for addressing with
448@samp{%ebp} as the base register).  @var{index}, @var{scale} are both missing.
449
450@item AT&T: @samp{foo(,%eax,4)}, Intel: @samp{[foo + eax*4]}
451@var{index} is @samp{%eax} (scaled by a @var{scale} 4); @var{disp} is
452@samp{foo}.  All other fields are missing.  The section register here
453defaults to @samp{%ds}.
454
455@item AT&T: @samp{foo(,1)}; Intel @samp{[foo]}
456This uses the value pointed to by @samp{foo} as a memory operand.
457Note that @var{base} and @var{index} are both missing, but there is only
458@emph{one} @samp{,}.  This is a syntactic exception.
459
460@item AT&T: @samp{%gs:foo}; Intel @samp{gs:foo}
461This selects the contents of the variable @samp{foo} with section
462register @var{section} being @samp{%gs}.
463@end table
464
465Absolute (as opposed to PC relative) call and jump operands must be
466prefixed with @samp{*}.  If no @samp{*} is specified, @code{@value{AS}}
467always chooses PC relative addressing for jump/call labels.
468
469Any instruction that has a memory operand, but no register operand,
470@emph{must} specify its size (byte, word, long, or quadruple) with an
471instruction mnemonic suffix (@samp{b}, @samp{w}, @samp{l} or @samp{q},
472respectively).
473
474The x86-64 architecture adds an RIP (instruction pointer relative)
475addressing.  This addressing mode is specified by using @samp{rip} as a
476base register.  Only constant offsets are valid. For example:
477
478@table @asis
479@item AT&T: @samp{1234(%rip)}, Intel: @samp{[rip + 1234]}
480Points to the address 1234 bytes past the end of the current
481instruction.
482
483@item AT&T: @samp{symbol(%rip)}, Intel: @samp{[rip + symbol]}
484Points to the @code{symbol} in RIP relative way, this is shorter than
485the default absolute addressing.
486@end table
487
488Other addressing modes remain unchanged in x86-64 architecture, except
489registers used are 64-bit instead of 32-bit.
490
491@node i386-jumps
492@section Handling of Jump Instructions
493
494@cindex jump optimization, i386
495@cindex i386 jump optimization
496@cindex jump optimization, x86-64
497@cindex x86-64 jump optimization
498Jump instructions are always optimized to use the smallest possible
499displacements.  This is accomplished by using byte (8-bit) displacement
500jumps whenever the target is sufficiently close.  If a byte displacement
501is insufficient a long (32-bit) displacement is used.  We do not support
502word (16-bit) displacement jumps in 32-bit mode (i.e. prefixing the jump
503instruction with the @samp{data16} instruction prefix), since the 80386
504insists upon masking @samp{%eip} to 16 bits after the word displacement
505is added.
506
507Note that the @samp{jcxz}, @samp{jecxz}, @samp{loop}, @samp{loopz},
508@samp{loope}, @samp{loopnz} and @samp{loopne} instructions only come in byte
509displacements, so that if you use these instructions (@code{@value{GCC}} does
510not use them) you may get an error message (and incorrect code).  The AT&T
51180386 assembler tries to get around this problem by expanding @samp{jcxz foo}
512to
513
514@smallexample
515         jcxz cx_zero
516         jmp cx_nonzero
517cx_zero: jmp foo
518cx_nonzero:
519@end smallexample
520
521@node i386-Float
522@section Floating Point
523
524@cindex i386 floating point
525@cindex floating point, i386
526@cindex x86-64 floating point
527@cindex floating point, x86-64
528All 80387 floating point types except packed BCD are supported.
529(BCD support may be added without much difficulty).  These data
530types are 16-, 32-, and 64- bit integers, and single (32-bit),
531double (64-bit), and extended (80-bit) precision floating point.
532Each supported type has an instruction mnemonic suffix and a constructor
533associated with it.  Instruction mnemonic suffixes specify the operand's
534data type.  Constructors build these data types into memory.
535
536@cindex @code{float} directive, i386
537@cindex @code{single} directive, i386
538@cindex @code{double} directive, i386
539@cindex @code{tfloat} directive, i386
540@cindex @code{float} directive, x86-64
541@cindex @code{single} directive, x86-64
542@cindex @code{double} directive, x86-64
543@cindex @code{tfloat} directive, x86-64
544@itemize @bullet
545@item
546Floating point constructors are @samp{.float} or @samp{.single},
547@samp{.double}, and @samp{.tfloat} for 32-, 64-, and 80-bit formats.
548These correspond to instruction mnemonic suffixes @samp{s}, @samp{l},
549and @samp{t}. @samp{t} stands for 80-bit (ten byte) real.  The 80387
550only supports this format via the @samp{fldt} (load 80-bit real to stack
551top) and @samp{fstpt} (store 80-bit real and pop stack) instructions.
552
553@cindex @code{word} directive, i386
554@cindex @code{long} directive, i386
555@cindex @code{int} directive, i386
556@cindex @code{quad} directive, i386
557@cindex @code{word} directive, x86-64
558@cindex @code{long} directive, x86-64
559@cindex @code{int} directive, x86-64
560@cindex @code{quad} directive, x86-64
561@item
562Integer constructors are @samp{.word}, @samp{.long} or @samp{.int}, and
563@samp{.quad} for the 16-, 32-, and 64-bit integer formats.  The
564corresponding instruction mnemonic suffixes are @samp{s} (single),
565@samp{l} (long), and @samp{q} (quad).  As with the 80-bit real format,
566the 64-bit @samp{q} format is only present in the @samp{fildq} (load
567quad integer to stack top) and @samp{fistpq} (store quad integer and pop
568stack) instructions.
569@end itemize
570
571Register to register operations should not use instruction mnemonic suffixes.
572@samp{fstl %st, %st(1)} will give a warning, and be assembled as if you
573wrote @samp{fst %st, %st(1)}, since all register to register operations
574use 80-bit floating point operands. (Contrast this with @samp{fstl %st, mem},
575which converts @samp{%st} from 80-bit to 64-bit floating point format,
576then stores the result in the 4 byte location @samp{mem})
577
578@node i386-SIMD
579@section Intel's MMX and AMD's 3DNow! SIMD Operations
580
581@cindex MMX, i386
582@cindex 3DNow!, i386
583@cindex SIMD, i386
584@cindex MMX, x86-64
585@cindex 3DNow!, x86-64
586@cindex SIMD, x86-64
587
588@code{@value{AS}} supports Intel's MMX instruction set (SIMD
589instructions for integer data), available on Intel's Pentium MMX
590processors and Pentium II processors, AMD's K6 and K6-2 processors,
591Cyrix' M2 processor, and probably others.  It also supports AMD's 3DNow!
592instruction set (SIMD instructions for 32-bit floating point data)
593available on AMD's K6-2 processor and possibly others in the future.
594
595Currently, @code{@value{AS}} does not support Intel's floating point
596SIMD, Katmai (KNI).
597
598The eight 64-bit MMX operands, also used by 3DNow!, are called @samp{%mm0},
599@samp{%mm1}, ... @samp{%mm7}.  They contain eight 8-bit integers, four
60016-bit integers, two 32-bit integers, one 64-bit integer, or two 32-bit
601floating point values.  The MMX registers cannot be used at the same time
602as the floating point stack.
603
604See Intel and AMD documentation, keeping in mind that the operand order in
605instructions is reversed from the Intel syntax.
606
607@node i386-16bit
608@section Writing 16-bit Code
609
610@cindex i386 16-bit code
611@cindex 16-bit code, i386
612@cindex real-mode code, i386
613@cindex @code{code16gcc} directive, i386
614@cindex @code{code16} directive, i386
615@cindex @code{code32} directive, i386
616@cindex @code{code64} directive, i386
617@cindex @code{code64} directive, x86-64
618While @code{@value{AS}} normally writes only ``pure'' 32-bit i386 code
619or 64-bit x86-64 code depending on the default configuration,
620it also supports writing code to run in real mode or in 16-bit protected
621mode code segments.  To do this, put a @samp{.code16} or
622@samp{.code16gcc} directive before the assembly language instructions to
623be run in 16-bit mode.  You can switch @code{@value{AS}} back to writing
624normal 32-bit code with the @samp{.code32} directive.
625
626@samp{.code16gcc} provides experimental support for generating 16-bit
627code from gcc, and differs from @samp{.code16} in that @samp{call},
628@samp{ret}, @samp{enter}, @samp{leave}, @samp{push}, @samp{pop},
629@samp{pusha}, @samp{popa}, @samp{pushf}, and @samp{popf} instructions
630default to 32-bit size.  This is so that the stack pointer is
631manipulated in the same way over function calls, allowing access to
632function parameters at the same stack offsets as in 32-bit mode.
633@samp{.code16gcc} also automatically adds address size prefixes where
634necessary to use the 32-bit addressing modes that gcc generates.
635
636The code which @code{@value{AS}} generates in 16-bit mode will not
637necessarily run on a 16-bit pre-80386 processor.  To write code that
638runs on such a processor, you must refrain from using @emph{any} 32-bit
639constructs which require @code{@value{AS}} to output address or operand
640size prefixes.
641
642Note that writing 16-bit code instructions by explicitly specifying a
643prefix or an instruction mnemonic suffix within a 32-bit code section
644generates different machine instructions than those generated for a
64516-bit code segment.  In a 32-bit code section, the following code
646generates the machine opcode bytes @samp{66 6a 04}, which pushes the
647value @samp{4} onto the stack, decrementing @samp{%esp} by 2.
648
649@smallexample
650        pushw $4
651@end smallexample
652
653The same code in a 16-bit code section would generate the machine
654opcode bytes @samp{6a 04} (ie. without the operand size prefix), which
655is correct since the processor default operand size is assumed to be 16
656bits in a 16-bit code section.
657
658@node i386-Bugs
659@section AT&T Syntax bugs
660
661The UnixWare assembler, and probably other AT&T derived ix86 Unix
662assemblers, generate floating point instructions with reversed source
663and destination registers in certain cases.  Unfortunately, gcc and
664possibly many other programs use this reversed syntax, so we're stuck
665with it.
666
667For example
668
669@smallexample
670        fsub %st,%st(3)
671@end smallexample
672@noindent
673results in @samp{%st(3)} being updated to @samp{%st - %st(3)} rather
674than the expected @samp{%st(3) - %st}.  This happens with all the
675non-commutative arithmetic floating point operations with two register
676operands where the source register is @samp{%st} and the destination
677register is @samp{%st(i)}.
678
679@node i386-Arch
680@section Specifying CPU Architecture
681
682@cindex arch directive, i386
683@cindex i386 arch directive
684@cindex arch directive, x86-64
685@cindex x86-64 arch directive
686
687@code{@value{AS}} may be told to assemble for a particular CPU
688architecture with the @code{.arch @var{cpu_type}} directive.  This
689directive enables a warning when gas detects an instruction that is not
690supported on the CPU specified.  The choices for @var{cpu_type} are:
691
692@multitable @columnfractions .20 .20 .20 .20
693@item @samp{i8086} @tab @samp{i186} @tab @samp{i286} @tab @samp{i386}
694@item @samp{i486} @tab @samp{i586} @tab @samp{i686} @tab @samp{pentium}
695@item @samp{pentiumpro} @tab @samp{pentium4} @tab @samp{k6} @tab @samp{athlon}
696@item @samp{sledgehammer}
697@end multitable
698
699Apart from the warning, there is only one other effect on
700@code{@value{AS}} operation;  If you specify a CPU other than
701@samp{i486}, then shift by one instructions such as @samp{sarl $1, %eax}
702will automatically use a two byte opcode sequence.  The larger three
703byte opcode sequence is used on the 486 (and when no architecture is
704specified) because it executes faster on the 486.  Note that you can
705explicitly request the two byte opcode by writing @samp{sarl %eax}.
706
707@node i386-Notes
708@section Notes
709
710@cindex i386 @code{mul}, @code{imul} instructions
711@cindex @code{mul} instruction, i386
712@cindex @code{imul} instruction, i386
713@cindex @code{mul} instruction, x86-64
714@cindex @code{imul} instruction, x86-64
715There is some trickery concerning the @samp{mul} and @samp{imul}
716instructions that deserves mention.  The 16-, 32-, 64- and 128-bit expanding
717multiplies (base opcode @samp{0xf6}; extension 4 for @samp{mul} and 5
718for @samp{imul}) can be output only in the one operand form.  Thus,
719@samp{imul %ebx, %eax} does @emph{not} select the expanding multiply;
720the expanding multiply would clobber the @samp{%edx} register, and this
721would confuse @code{@value{GCC}} output.  Use @samp{imul %ebx} to get the
72264-bit product in @samp{%edx:%eax}.
723
724We have added a two operand form of @samp{imul} when the first operand
725is an immediate mode expression and the second operand is a register.
726This is just a shorthand, so that, multiplying @samp{%eax} by 69, for
727example, can be done with @samp{imul $69, %eax} rather than @samp{imul
728$69, %eax, %eax}.
729
730