c-i386.texi revision 38889
1@c Copyright (C) 1991, 92, 93, 94, 95, 1997 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@menu
17* i386-Options::                Options
18* i386-Syntax::                 AT&T Syntax versus Intel Syntax
19* i386-Opcodes::                Opcode Naming
20* i386-Regs::                   Register Naming
21* i386-prefixes::               Opcode Prefixes
22* i386-Memory::                 Memory References
23* i386-jumps::                  Handling of Jump Instructions
24* i386-Float::                  Floating Point
25* i386-16bit::                  Writing 16-bit Code
26* i386-Notes::                  Notes
27@end menu
28
29@node i386-Options
30@section Options
31
32@cindex options for i386 (none)
33@cindex i386 options (none)
34The 80386 has no machine dependent options.
35
36@node i386-Syntax
37@section AT&T Syntax versus Intel Syntax
38
39@cindex i386 syntax compatibility
40@cindex syntax compatibility, i386
41In order to maintain compatibility with the output of @code{@value{GCC}},
42@code{@value{AS}} supports AT&T System V/386 assembler syntax.  This is quite
43different from Intel syntax.  We mention these differences because
44almost all 80386 documents used only Intel syntax.  Notable differences
45between the two syntaxes are:
46
47@cindex immediate operands, i386
48@cindex i386 immediate operands
49@cindex register operands, i386
50@cindex i386 register operands
51@cindex jump/call operands, i386
52@cindex i386 jump/call operands
53@cindex operand delimiters, i386
54@itemize @bullet
55@item
56AT&T immediate operands are preceded by @samp{$}; Intel immediate
57operands are undelimited (Intel @samp{push 4} is AT&T @samp{pushl $4}).
58AT&T register operands are preceded by @samp{%}; Intel register operands
59are undelimited.  AT&T absolute (as opposed to PC relative) jump/call
60operands are prefixed by @samp{*}; they are undelimited in Intel syntax.
61
62@cindex i386 source, destination operands
63@cindex source, destination operands; i386
64@item
65AT&T and Intel syntax use the opposite order for source and destination
66operands.  Intel @samp{add eax, 4} is @samp{addl $4, %eax}.  The
67@samp{source, dest} convention is maintained for compatibility with
68previous Unix assemblers.
69
70@cindex opcode suffixes, i386
71@cindex sizes operands, i386
72@cindex i386 size suffixes
73@item
74In AT&T syntax the size of memory operands is determined from the last
75character of the opcode name.  Opcode suffixes of @samp{b}, @samp{w},
76and @samp{l} specify byte (8-bit), word (16-bit), and long (32-bit)
77memory references.  Intel syntax accomplishes this by prefixes memory
78operands (@emph{not} the opcodes themselves) with @samp{byte ptr},
79@samp{word ptr}, and @samp{dword ptr}.  Thus, Intel @samp{mov al, byte
80ptr @var{foo}} is @samp{movb @var{foo}, %al} in AT&T syntax.
81
82@cindex return instructions, i386
83@cindex i386 jump, call, return
84@item
85Immediate form long jumps and calls are
86@samp{lcall/ljmp $@var{section}, $@var{offset}} in AT&T syntax; the
87Intel syntax is
88@samp{call/jmp far @var{section}:@var{offset}}.  Also, the far return
89instruction
90is @samp{lret $@var{stack-adjust}} in AT&T syntax; Intel syntax is
91@samp{ret far @var{stack-adjust}}.
92
93@cindex sections, i386
94@cindex i386 sections
95@item
96The AT&T assembler does not provide support for multiple section
97programs.  Unix style systems expect all programs to be single sections.
98@end itemize
99
100@node i386-Opcodes
101@section Opcode Naming
102
103@cindex i386 opcode naming
104@cindex opcode naming, i386
105Opcode names are suffixed with one character modifiers which specify the
106size of operands.  The letters @samp{b}, @samp{w}, and @samp{l} specify
107byte, word, and long operands.  If no suffix is specified by an
108instruction and it contains no memory operands then @code{@value{AS}} tries to
109fill in the missing suffix based on the destination register operand
110(the last one by convention).  Thus, @samp{mov %ax, %bx} is equivalent
111to @samp{movw %ax, %bx}; also, @samp{mov $1, %bx} is equivalent to
112@samp{movw $1, %bx}.  Note that this is incompatible with the AT&T Unix
113assembler which assumes that a missing opcode suffix implies long
114operand size.  (This incompatibility does not affect compiler output
115since compilers always explicitly specify the opcode suffix.)
116
117Almost all opcodes have the same names in AT&T and Intel format.  There
118are a few exceptions.  The sign extend and zero extend instructions need
119two sizes to specify them.  They need a size to sign/zero extend
120@emph{from} and a size to zero extend @emph{to}.  This is accomplished
121by using two opcode suffixes in AT&T syntax.  Base names for sign extend
122and zero extend are @samp{movs@dots{}} and @samp{movz@dots{}} in AT&T
123syntax (@samp{movsx} and @samp{movzx} in Intel syntax).  The opcode
124suffixes are tacked on to this base name, the @emph{from} suffix before
125the @emph{to} suffix.  Thus, @samp{movsbl %al, %edx} is AT&T syntax for
126``move sign extend @emph{from} %al @emph{to} %edx.''  Possible suffixes,
127thus, are @samp{bl} (from byte to long), @samp{bw} (from byte to word),
128and @samp{wl} (from word to long).
129
130@cindex conversion instructions, i386
131@cindex i386 conversion instructions
132The Intel-syntax conversion instructions
133
134@itemize @bullet
135@item
136@samp{cbw} --- sign-extend byte in @samp{%al} to word in @samp{%ax},
137
138@item
139@samp{cwde} --- sign-extend word in @samp{%ax} to long in @samp{%eax},
140
141@item
142@samp{cwd} --- sign-extend word in @samp{%ax} to long in @samp{%dx:%ax},
143
144@item
145@samp{cdq} --- sign-extend dword in @samp{%eax} to quad in @samp{%edx:%eax},
146@end itemize
147
148@noindent
149are called @samp{cbtw}, @samp{cwtl}, @samp{cwtd}, and @samp{cltd} in
150AT&T naming.  @code{@value{AS}} accepts either naming for these instructions.
151
152@cindex jump instructions, i386
153@cindex call instructions, i386
154Far call/jump instructions are @samp{lcall} and @samp{ljmp} in
155AT&T syntax, but are @samp{call far} and @samp{jump far} in Intel
156convention.
157
158@node i386-Regs
159@section Register Naming
160
161@cindex i386 registers
162@cindex registers, i386
163Register operands are always prefixes with @samp{%}.  The 80386 registers
164consist of
165
166@itemize @bullet
167@item
168the 8 32-bit registers @samp{%eax} (the accumulator), @samp{%ebx},
169@samp{%ecx}, @samp{%edx}, @samp{%edi}, @samp{%esi}, @samp{%ebp} (the
170frame pointer), and @samp{%esp} (the stack pointer).
171
172@item
173the 8 16-bit low-ends of these: @samp{%ax}, @samp{%bx}, @samp{%cx},
174@samp{%dx}, @samp{%di}, @samp{%si}, @samp{%bp}, and @samp{%sp}.
175
176@item
177the 8 8-bit registers: @samp{%ah}, @samp{%al}, @samp{%bh},
178@samp{%bl}, @samp{%ch}, @samp{%cl}, @samp{%dh}, and @samp{%dl} (These
179are the high-bytes and low-bytes of @samp{%ax}, @samp{%bx},
180@samp{%cx}, and @samp{%dx})
181
182@item
183the 6 section registers @samp{%cs} (code section), @samp{%ds}
184(data section), @samp{%ss} (stack section), @samp{%es}, @samp{%fs},
185and @samp{%gs}.
186
187@item
188the 3 processor control registers @samp{%cr0}, @samp{%cr2}, and
189@samp{%cr3}.
190
191@item
192the 6 debug registers @samp{%db0}, @samp{%db1}, @samp{%db2},
193@samp{%db3}, @samp{%db6}, and @samp{%db7}.
194
195@item
196the 2 test registers @samp{%tr6} and @samp{%tr7}.
197
198@item
199the 8 floating point register stack @samp{%st} or equivalently
200@samp{%st(0)}, @samp{%st(1)}, @samp{%st(2)}, @samp{%st(3)},
201@samp{%st(4)}, @samp{%st(5)}, @samp{%st(6)}, and @samp{%st(7)}.
202@end itemize
203
204@node i386-prefixes
205@section Opcode Prefixes
206
207@cindex i386 opcode prefixes
208@cindex opcode prefixes, i386
209@cindex prefixes, i386
210Opcode prefixes are used to modify the following opcode.  They are used
211to repeat string instructions, to provide section overrides, to perform
212bus lock operations, and to give operand and address size (16-bit
213operands are specified in an instruction by prefixing what would
214normally be 32-bit operands with a ``operand size'' opcode prefix).
215Opcode prefixes are usually given as single-line instructions with no
216operands, and must directly precede the instruction they act upon.  For
217example, the @samp{scas} (scan string) instruction is repeated with:
218@smallexample
219        repne
220        scas
221@end smallexample
222
223Here is a list of opcode prefixes:
224
225@cindex section override prefixes, i386
226@itemize @bullet
227@item
228Section override prefixes @samp{cs}, @samp{ds}, @samp{ss}, @samp{es},
229@samp{fs}, @samp{gs}.  These are automatically added by specifying
230using the @var{section}:@var{memory-operand} form for memory references.
231
232@cindex size prefixes, i386
233@item
234Operand/Address size prefixes @samp{data16} and @samp{addr16}
235change 32-bit operands/addresses into 16-bit operands/addresses.  Note
236that 16-bit addressing modes (i.e. 8086 and 80286 addressing modes)
237are not supported (yet).
238
239@cindex bus lock prefixes, i386
240@cindex inhibiting interrupts, i386
241@item
242The bus lock prefix @samp{lock} inhibits interrupts during
243execution of the instruction it precedes.  (This is only valid with
244certain instructions; see a 80386 manual for details).
245
246@cindex coprocessor wait, i386
247@item
248The wait for coprocessor prefix @samp{wait} waits for the
249coprocessor to complete the current instruction.  This should never be
250needed for the 80386/80387 combination.
251
252@cindex repeat prefixes, i386
253@item
254The @samp{rep}, @samp{repe}, and @samp{repne} prefixes are added
255to string instructions to make them repeat @samp{%ecx} times.
256@end itemize
257
258@node i386-Memory
259@section Memory References
260
261@cindex i386 memory references
262@cindex memory references, i386
263An Intel syntax indirect memory reference of the form
264
265@smallexample
266@var{section}:[@var{base} + @var{index}*@var{scale} + @var{disp}]
267@end smallexample
268
269@noindent
270is translated into the AT&T syntax
271
272@smallexample
273@var{section}:@var{disp}(@var{base}, @var{index}, @var{scale})
274@end smallexample
275
276@noindent
277where @var{base} and @var{index} are the optional 32-bit base and
278index registers, @var{disp} is the optional displacement, and
279@var{scale}, taking the values 1, 2, 4, and 8, multiplies @var{index}
280to calculate the address of the operand.  If no @var{scale} is
281specified, @var{scale} is taken to be 1.  @var{section} specifies the
282optional section register for the memory operand, and may override the
283default section register (see a 80386 manual for section register
284defaults). Note that section overrides in AT&T syntax @emph{must} have
285be preceded by a @samp{%}.  If you specify a section override which
286coincides with the default section register, @code{@value{AS}} does @emph{not}
287output any section register override prefixes to assemble the given
288instruction.  Thus, section overrides can be specified to emphasize which
289section register is used for a given memory operand.
290
291Here are some examples of Intel and AT&T style memory references:
292
293@table @asis
294@item AT&T: @samp{-4(%ebp)}, Intel:  @samp{[ebp - 4]}
295@var{base} is @samp{%ebp}; @var{disp} is @samp{-4}. @var{section} is
296missing, and the default section is used (@samp{%ss} for addressing with
297@samp{%ebp} as the base register).  @var{index}, @var{scale} are both missing.
298
299@item AT&T: @samp{foo(,%eax,4)}, Intel: @samp{[foo + eax*4]}
300@var{index} is @samp{%eax} (scaled by a @var{scale} 4); @var{disp} is
301@samp{foo}.  All other fields are missing.  The section register here
302defaults to @samp{%ds}.
303
304@item AT&T: @samp{foo(,1)}; Intel @samp{[foo]}
305This uses the value pointed to by @samp{foo} as a memory operand.
306Note that @var{base} and @var{index} are both missing, but there is only
307@emph{one} @samp{,}.  This is a syntactic exception.
308
309@item AT&T: @samp{%gs:foo}; Intel @samp{gs:foo}
310This selects the contents of the variable @samp{foo} with section
311register @var{section} being @samp{%gs}.
312@end table
313
314Absolute (as opposed to PC relative) call and jump operands must be
315prefixed with @samp{*}.  If no @samp{*} is specified, @code{@value{AS}}
316always chooses PC relative addressing for jump/call labels.
317
318Any instruction that has a memory operand @emph{must} specify its size (byte,
319word, or long) with an opcode suffix (@samp{b}, @samp{w}, or @samp{l},
320respectively).
321
322@node i386-jumps
323@section Handling of Jump Instructions
324
325@cindex jump optimization, i386
326@cindex i386 jump optimization
327Jump instructions are always optimized to use the smallest possible
328displacements.  This is accomplished by using byte (8-bit) displacement
329jumps whenever the target is sufficiently close.  If a byte displacement
330is insufficient a long (32-bit) displacement is used.  We do not support
331word (16-bit) displacement jumps (i.e. prefixing the jump instruction
332with the @samp{addr16} opcode prefix), since the 80386 insists upon masking
333@samp{%eip} to 16 bits after the word displacement is added.
334
335Note that the @samp{jcxz}, @samp{jecxz}, @samp{loop}, @samp{loopz},
336@samp{loope}, @samp{loopnz} and @samp{loopne} instructions only come in byte
337displacements, so that if you use these instructions (@code{@value{GCC}} does
338not use them) you may get an error message (and incorrect code).  The AT&T
33980386 assembler tries to get around this problem by expanding @samp{jcxz foo}
340to
341
342@smallexample
343         jcxz cx_zero
344         jmp cx_nonzero
345cx_zero: jmp foo
346cx_nonzero:
347@end smallexample
348
349@node i386-Float
350@section Floating Point
351
352@cindex i386 floating point
353@cindex floating point, i386
354All 80387 floating point types except packed BCD are supported.
355(BCD support may be added without much difficulty).  These data
356types are 16-, 32-, and 64- bit integers, and single (32-bit),
357double (64-bit), and extended (80-bit) precision floating point.
358Each supported type has an opcode suffix and a constructor
359associated with it.  Opcode suffixes specify operand's data
360types.  Constructors build these data types into memory.
361
362@cindex @code{float} directive, i386
363@cindex @code{single} directive, i386
364@cindex @code{double} directive, i386
365@cindex @code{tfloat} directive, i386
366@itemize @bullet
367@item
368Floating point constructors are @samp{.float} or @samp{.single},
369@samp{.double}, and @samp{.tfloat} for 32-, 64-, and 80-bit formats.
370These correspond to opcode suffixes @samp{s}, @samp{l}, and @samp{t}.
371@samp{t} stands for temporary real, and that the 80387 only supports
372this format via the @samp{fldt} (load temporary real to stack top) and
373@samp{fstpt} (store temporary real and pop stack) instructions.
374
375@cindex @code{word} directive, i386
376@cindex @code{long} directive, i386
377@cindex @code{int} directive, i386
378@cindex @code{quad} directive, i386
379@item
380Integer constructors are @samp{.word}, @samp{.long} or @samp{.int}, and
381@samp{.quad} for the 16-, 32-, and 64-bit integer formats.  The corresponding
382opcode suffixes are @samp{s} (single), @samp{l} (long), and @samp{q}
383(quad).  As with the temporary real format the 64-bit @samp{q} format is
384only present in the @samp{fildq} (load quad integer to stack top) and
385@samp{fistpq} (store quad integer and pop stack) instructions.
386@end itemize
387
388Register to register operations do not require opcode suffixes,
389so that @samp{fst %st, %st(1)} is equivalent to @samp{fstl %st, %st(1)}.
390
391@node i386-16bit
392@section Writing 16-bit Code
393
394@cindex i386 16-bit code
395@cindex 16-bit code, i386
396@cindex real-mode code, i386
397@cindex @code{code16} directive, i386
398@cindex @code{code32} directive, i386
399While GAS normally writes only ``pure'' 32-bit i386 code, it has limited
400support for writing code to run in real mode or in 16-bit protected mode
401code segments.  To do this, insert a @samp{.code16} directive before the
402assembly language instructions to be run in 16-bit mode.  You can switch
403GAS back to writing normal 32-bit code with the @samp{.code32} directive.
404
405GAS understands exactly the same assembly language syntax in 16-bit mode as
406in 32-bit mode.  The function of any given instruction is exactly the same
407regardless of mode, as long as the resulting object code is executed in the
408mode for which GAS wrote it.  So, for example, the @samp{ret} mnemonic
409produces a 32-bit return instruction regardless of whether it is to be run
410in 16-bit or 32-bit mode.  (If GAS is in 16-bit mode, it will add an
411operand size prefix to the instruction to force it to be a 32-bit return.)
412
413This means, for one thing, that you can use @sc{gnu} @sc{cc} to write code to be run
414in real mode or 16-bit protected mode.  Just insert the statement
415@samp{asm(".code16");} at the beginning of your C source file, and while
416@sc{gnu} @sc{cc} will still be generating 32-bit code, GAS will automatically add 
417all the necessary size prefixes to make that code run in 16-bit mode.  Of
418course, since @sc{gnu} @sc{cc} only writes small-model code (it doesn't know how to
419attach segment selectors to pointers like native x86 compilers do), any
42016-bit code you write with @sc{gnu} @sc{cc} will essentially be limited to a 64K
421address space.  Also, there will be a code size and performance penalty
422due to all the extra address and operand size prefixes GAS has to add to
423the instructions.
424
425Note that placing GAS in 16-bit mode does not mean that the resulting
426code will necessarily run on a 16-bit pre-80386 processor.  To write code
427that runs on such a processor, you would have to refrain from using
428@emph{any} 32-bit constructs which require GAS to output address or
429operand size prefixes.  At the moment this would be rather difficult,
430because GAS currently supports @emph{only} 32-bit addressing modes: when
431writing 16-bit code, it @emph{always} outputs address size prefixes for any
432instruction that uses a non-register addressing mode.  So you can write
433code that runs on 16-bit processors, but only if that code never references
434memory.
435
436@node i386-Notes
437@section Notes
438
439@cindex i386 @code{mul}, @code{imul} instructions
440@cindex @code{mul} instruction, i386
441@cindex @code{imul} instruction, i386
442There is some trickery concerning the @samp{mul} and @samp{imul}
443instructions that deserves mention.  The 16-, 32-, and 64-bit expanding
444multiplies (base opcode @samp{0xf6}; extension 4 for @samp{mul} and 5
445for @samp{imul}) can be output only in the one operand form.  Thus,
446@samp{imul %ebx, %eax} does @emph{not} select the expanding multiply;
447the expanding multiply would clobber the @samp{%edx} register, and this
448would confuse @code{@value{GCC}} output.  Use @samp{imul %ebx} to get the
44964-bit product in @samp{%edx:%eax}.
450
451We have added a two operand form of @samp{imul} when the first operand
452is an immediate mode expression and the second operand is a register.
453This is just a shorthand, so that, multiplying @samp{%eax} by 69, for
454example, can be done with @samp{imul $69, %eax} rather than @samp{imul
455$69, %eax, %eax}.
456
457