]> Git Repo - binutils.git/blob - gas/config/tc-i386.c
misc fixes
[binutils.git] / gas / config / tc-i386.c
1 /* i386.c -- Assemble code for the Intel 80386
2    Copyright (C) 1989, 1991, 1992 Free Software Foundation.
3
4    This file is part of GAS, the GNU Assembler.
5
6    GAS is free software; you can redistribute it and/or modify
7    it under the terms of the GNU General Public License as published by
8    the Free Software Foundation; either version 2, or (at your option)
9    any later version.
10
11    GAS is distributed in the hope that it will be useful,
12    but WITHOUT ANY WARRANTY; without even the implied warranty of
13    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
14    GNU General Public License for more details.
15
16    You should have received a copy of the GNU General Public License
17    along with GAS; see the file COPYING.  If not, write to
18    the Free Software Foundation, 675 Mass Ave, Cambridge, MA 02139, USA.  */
19
20 /*
21   Intel 80386 machine specific gas.
22   Written by Eliot Dresselhaus ([email protected]).
23   Bugs & suggestions are completely welcome.  This is free software.
24   Please help us make it better.
25   */
26
27 #include <ctype.h>
28
29 #include "as.h"
30 #include "read.h"
31
32 #include "obstack.h"
33 #include "opcode/i386.h"
34
35 /* 'md_assemble ()' gathers together information and puts it into a
36    i386_insn. */
37
38 typedef struct
39   {
40     /* TM holds the template for the insn were currently assembling. */
41     template tm;
42     /* SUFFIX holds the opcode suffix (e.g. 'l' for 'movl') if given. */
43     char suffix;
44     /* Operands are coded with OPERANDS, TYPES, DISPS, IMMS, and REGS. */
45
46     /* OPERANDS gives the number of given operands. */
47     unsigned int operands;
48
49     /* REG_OPERANDS, DISP_OPERANDS, MEM_OPERANDS, IMM_OPERANDS give the number of
50            given register, displacement, memory operands and immediate operands. */
51     unsigned int reg_operands, disp_operands, mem_operands, imm_operands;
52
53     /* TYPES [i] is the type (see above #defines) which tells us how to
54            search through DISPS [i] & IMMS [i] & REGS [i] for the required
55            operand. */
56     unsigned int types[MAX_OPERANDS];
57
58     /* Displacements (if given) for each operand. */
59     expressionS *disps[MAX_OPERANDS];
60
61     /* Immediate operands (if given) for each operand. */
62     expressionS *imms[MAX_OPERANDS];
63
64     /* Register operands (if given) for each operand. */
65     reg_entry *regs[MAX_OPERANDS];
66
67     /* BASE_REG, INDEX_REG, and LOG2_SCALE_FACTOR are used to encode
68            the base index byte below.  */
69     reg_entry *base_reg;
70     reg_entry *index_reg;
71     unsigned int log2_scale_factor;
72
73     /* SEG gives the seg_entry of this insn.  It is equal to zero unless
74            an explicit segment override is given. */
75     const seg_entry *seg;       /* segment for memory operands (if given) */
76
77     /* PREFIX holds all the given prefix opcodes (usually null).
78            PREFIXES is the size of PREFIX. */
79     /* richfix: really unsigned? */
80     unsigned char prefix[MAX_PREFIXES];
81     unsigned int prefixes;
82
83     /* RM and IB are the modrm byte and the base index byte where the addressing
84            modes of this insn are encoded. */
85
86     modrm_byte rm;
87     base_index_byte bi;
88   }
89
90 i386_insn;
91
92 /* This array holds the chars that always start a comment.  If the
93    pre-processor is disabled, these aren't very useful */
94 const char comment_chars[] = "#";
95
96 /* This array holds the chars that only start a comment at the beginning of
97    a line.  If the line seems to have the form '# 123 filename'
98    .line and .file directives will appear in the pre-processed output */
99 /* Note that input_file.c hand checks for '#' at the beginning of the
100    first line of the input file.  This is because the compiler outputs
101    #NO_APP at the beginning of its output. */
102 /* Also note that comments started like this one will always work if
103    '/' isn't otherwise defined. */
104 const char line_comment_chars[] = "/";  /* removed '#' xoxorich. */
105 const char line_separator_chars[] = "";
106
107 /* Chars that can be used to separate mant from exp in floating point nums */
108 const char EXP_CHARS[] = "eE";
109
110 /* Chars that mean this number is a floating point constant */
111 /* As in 0f12.456 */
112 /* or    0d1.2345e12 */
113 const char FLT_CHARS[] = "fFdDxX";
114
115 /* tables for lexical analysis */
116 static char opcode_chars[256];
117 static char register_chars[256];
118 static char operand_chars[256];
119 static char space_chars[256];
120 static char identifier_chars[256];
121 static char digit_chars[256];
122
123 /* lexical macros */
124 #define is_opcode_char(x) (opcode_chars[(unsigned char) x])
125 #define is_operand_char(x) (operand_chars[(unsigned char) x])
126 #define is_register_char(x) (register_chars[(unsigned char) x])
127 #define is_space_char(x) (space_chars[(unsigned char) x])
128 #define is_identifier_char(x) (identifier_chars[(unsigned char) x])
129 #define is_digit_char(x) (digit_chars[(unsigned char) x])
130
131 /* put here all non-digit non-letter charcters that may occur in an operand */
132 static char operand_special_chars[] = "%$-+(,)*._~/<>|&^!:";
133
134 static char *ordinal_names[] =
135 {"first", "second", "third"};   /* for printfs */
136
137 /* md_assemble() always leaves the strings it's passed unaltered.  To
138    effect this we maintain a stack of saved characters that we've smashed
139    with '\0's (indicating end of strings for various sub-fields of the
140    assembler instruction). */
141 static char save_stack[32];
142 static char *save_stack_p;      /* stack pointer */
143 #define END_STRING_AND_SAVE(s)      *save_stack_p++ = *s; *s = '\0'
144 #define RESTORE_END_STRING(s)       *s = *--save_stack_p
145
146 /* The instruction we're assembling. */
147 static i386_insn i;
148
149 /* Per instruction expressionS buffers: 2 displacements & 2 immediate max. */
150 static expressionS disp_expressions[2], im_expressions[2];
151
152 /* pointers to ebp & esp entries in reg_hash hash table */
153 static reg_entry *ebp, *esp;
154
155 static int this_operand;        /* current operand we are working on */
156
157 /*
158   Interface to relax_segment.
159   There are 2 relax states for 386 jump insns: one for conditional & one
160   for unconditional jumps.  This is because the these two types of jumps
161   add different sizes to frags when we're figuring out what sort of jump
162   to choose to reach a given label.  */
163
164 /* types */
165 #define COND_JUMP 1             /* conditional jump */
166 #define UNCOND_JUMP 2           /* unconditional jump */
167 /* sizes */
168 #define BYTE 0
169 #define WORD 1
170 #define DWORD 2
171 #define UNKNOWN_SIZE 3
172
173 #define ENCODE_RELAX_STATE(type,size) ((type<<2) | (size))
174 #define SIZE_FROM_RELAX_STATE(s) \
175     ( (((s) & 0x3) == BYTE ? 1 : (((s) & 0x3) == WORD ? 2 : 4)) )
176
177 const relax_typeS md_relax_table[] =
178 {
179 /*
180           The fields are:
181           1) most positive reach of this state,
182           2) most negative reach of this state,
183           3) how many bytes this mode will add to the size of the current frag
184           4) which index into the table to try if we can't fit into this one.
185           */
186   {1, 1, 0, 0},
187   {1, 1, 0, 0},
188   {1, 1, 0, 0},
189   {1, 1, 0, 0},
190
191 /* For now we don't use word displacement jumps:  they may be
192            untrustworthy. */
193   {127 + 1, -128 + 1, 0, ENCODE_RELAX_STATE (COND_JUMP, DWORD)},
194 /* word conditionals add 3 bytes to frag:
195            2 opcode prefix; 1 displacement bytes */
196   {32767 + 2, -32768 + 2, 3, ENCODE_RELAX_STATE (COND_JUMP, DWORD)},
197 /* dword conditionals adds 4 bytes to frag:
198            1 opcode prefix; 3 displacement bytes */
199   {0, 0, 4, 0},
200   {1, 1, 0, 0},
201
202   {127 + 1, -128 + 1, 0, ENCODE_RELAX_STATE (UNCOND_JUMP, DWORD)},
203 /* word jmp adds 2 bytes to frag:
204            1 opcode prefix; 1 displacement bytes */
205   {32767 + 2, -32768 + 2, 2, ENCODE_RELAX_STATE (UNCOND_JUMP, DWORD)},
206 /* dword jmp adds 3 bytes to frag:
207            0 opcode prefix; 3 displacement bytes */
208   {0, 0, 3, 0},
209   {1, 1, 0, 0},
210
211 };
212
213 #if __STDC__ == 1
214
215 static char *output_invalid (int c);
216 static int fits_in_signed_byte (long num);
217 static int fits_in_signed_word (long num);
218 static int fits_in_unsigned_byte (long num);
219 static int fits_in_unsigned_word (long num);
220 static int i386_operand (char *operand_string);
221 static int smallest_imm_type (long num);
222 static reg_entry *parse_register (char *reg_string);
223 static unsigned long mode_from_disp_size (unsigned long t);
224 static unsigned long opcode_suffix_to_type (unsigned long s);
225 static void s_bss (void);
226
227 #else /* not __STDC__ */
228
229 static char *output_invalid ();
230 static int fits_in_signed_byte ();
231 static int fits_in_signed_word ();
232 static int fits_in_unsigned_byte ();
233 static int fits_in_unsigned_word ();
234 static int i386_operand ();
235 static int smallest_imm_type ();
236 static reg_entry *parse_register ();
237 static unsigned long mode_from_disp_size ();
238 static unsigned long opcode_suffix_to_type ();
239 static void s_bss ();
240
241 #endif /* not __STDC__ */
242
243
244 /* Ignore certain directives generated by gcc. This probably should
245    not be here. */
246 void
247 dummy ()
248 {
249   while (*input_line_pointer && *input_line_pointer != '\n')
250     input_line_pointer++;
251 }
252
253 const pseudo_typeS md_pseudo_table[] =
254 {
255   {"bss", s_bss, 0},
256   {"align", s_align_bytes, 0},
257   {"ffloat", float_cons, 'f'},
258   {"dfloat", float_cons, 'd'},
259   {"tfloat", float_cons, 'x'},
260   {"value", cons, 2},
261   {0, 0, 0}
262 };
263
264 /* for interface with expression () */
265 extern char *input_line_pointer;
266
267 /* obstack for constructing various things in md_begin */
268 struct obstack o;
269
270 /* hash table for opcode lookup */
271 static struct hash_control *op_hash = (struct hash_control *) 0;
272 /* hash table for register lookup */
273 static struct hash_control *reg_hash = (struct hash_control *) 0;
274 /* hash table for prefix lookup */
275 static struct hash_control *prefix_hash = (struct hash_control *) 0;
276 \f
277
278 void
279 md_begin ()
280 {
281   char *hash_err;
282
283   obstack_begin (&o, 4096);
284
285   /* initialize op_hash hash table */
286   op_hash = hash_new ();        /* xmalloc handles error */
287
288   {
289     register const template *optab;
290     register templates *core_optab;
291     char *prev_name;
292
293     optab = i386_optab;         /* setup for loop */
294     prev_name = optab->name;
295     obstack_grow (&o, optab, sizeof (template));
296     core_optab = (templates *) xmalloc (sizeof (templates));
297
298     for (optab++; optab < i386_optab_end; optab++)
299       {
300         if (!strcmp (optab->name, prev_name))
301           {
302             /* same name as before --> append to current template list */
303             obstack_grow (&o, optab, sizeof (template));
304           }
305         else
306           {
307             /* different name --> ship out current template list;
308                                    add to hash table; & begin anew */
309             /* Note: end must be set before start! since obstack_next_free changes
310                                    upon opstack_finish */
311             core_optab->end = (template *) obstack_next_free (&o);
312             core_optab->start = (template *) obstack_finish (&o);
313             hash_err = hash_insert (op_hash, prev_name, (char *) core_optab);
314             if (hash_err && *hash_err)
315               {
316               hash_error:
317                 as_fatal ("Internal Error:  Can't hash %s: %s", prev_name, hash_err);
318               }
319             prev_name = optab->name;
320             core_optab = (templates *) xmalloc (sizeof (templates));
321             obstack_grow (&o, optab, sizeof (template));
322           }
323       }
324   }
325
326   /* initialize reg_hash hash table */
327   reg_hash = hash_new ();
328   {
329     register const reg_entry *regtab;
330
331     for (regtab = i386_regtab; regtab < i386_regtab_end; regtab++)
332       {
333         hash_err = hash_insert (reg_hash, regtab->reg_name, regtab);
334         if (hash_err && *hash_err)
335           goto hash_error;
336       }
337   }
338
339   esp = (reg_entry *) hash_find (reg_hash, "esp");
340   ebp = (reg_entry *) hash_find (reg_hash, "ebp");
341
342   /* initialize reg_hash hash table */
343   prefix_hash = hash_new ();
344   {
345     register const prefix_entry *prefixtab;
346
347     for (prefixtab = i386_prefixtab;
348          prefixtab < i386_prefixtab_end; prefixtab++)
349       {
350         hash_err = hash_insert (prefix_hash, prefixtab->prefix_name, prefixtab);
351         if (hash_err && *hash_err)
352           goto hash_error;
353       }
354   }
355
356   /* fill in lexical tables:  opcode_chars, operand_chars, space_chars */
357   {
358     register unsigned int c;
359
360     memset (opcode_chars, '\0', sizeof (opcode_chars));
361     memset (operand_chars, '\0', sizeof (operand_chars));
362     memset (space_chars, '\0', sizeof (space_chars));
363     memset (identifier_chars, '\0', sizeof (identifier_chars));
364     memset (digit_chars, '\0', sizeof (digit_chars));
365
366     for (c = 0; c < 256; c++)
367       {
368         if (islower (c) || isdigit (c))
369           {
370             opcode_chars[c] = c;
371             register_chars[c] = c;
372           }
373         else if (isupper (c))
374           {
375             opcode_chars[c] = tolower (c);
376             register_chars[c] = opcode_chars[c];
377           }
378         else if (c == PREFIX_SEPERATOR)
379           {
380             opcode_chars[c] = c;
381           }
382         else if (c == ')' || c == '(')
383           {
384             register_chars[c] = c;
385           }
386
387         if (isupper (c) || islower (c) || isdigit (c))
388           operand_chars[c] = c;
389         else if (c && strchr (operand_special_chars, c))
390           operand_chars[c] = c;
391
392         if (isdigit (c) || c == '-')
393           digit_chars[c] = c;
394
395         if (isalpha (c) || c == '_' || c == '.' || isdigit (c))
396           identifier_chars[c] = c;
397
398         if (c == ' ' || c == '\t')
399           space_chars[c] = c;
400       }
401   }
402 }
403
404 void
405 md_end ()
406 {
407 }                               /* not much to do here. */
408 \f
409
410 #ifdef DEBUG386
411
412 /* debugging routines for md_assemble */
413 /* static void pi (), pte (), pt (), pe (), ps (); */
414
415 static void
416 pi (line, x)
417      char *line;
418      i386_insn *x;
419 {
420   register template *p;
421   int i;
422
423   fprintf (stdout, "%s: template ", line);
424   pte (&x->tm);
425   fprintf (stdout, "  modrm:  mode %x  reg %x  reg/mem %x",
426            x->rm.mode, x->rm.reg, x->rm.regmem);
427   fprintf (stdout, " base %x  index %x  scale %x\n",
428            x->bi.base, x->bi.index, x->bi.scale);
429   for (i = 0; i < x->operands; i++)
430     {
431       fprintf (stdout, "    #%d:  ", i + 1);
432       pt (x->types[i]);
433       fprintf (stdout, "\n");
434       if (x->types[i] & Reg)
435         fprintf (stdout, "%s\n", x->regs[i]->reg_name);
436       if (x->types[i] & Imm)
437         pe (x->imms[i]);
438       if (x->types[i] & (Disp | Abs))
439         pe (x->disps[i]);
440     }
441 }
442
443 static void
444 pte (t)
445      template *t;
446 {
447   int i;
448   fprintf (stdout, " %d operands ", t->operands);
449   fprintf (stdout, "opcode %x ",
450            t->base_opcode);
451   if (t->extension_opcode != None)
452     fprintf (stdout, "ext %x ", t->extension_opcode);
453   if (t->opcode_modifier & D)
454     fprintf (stdout, "D");
455   if (t->opcode_modifier & W)
456     fprintf (stdout, "W");
457   fprintf (stdout, "\n");
458   for (i = 0; i < t->operands; i++)
459     {
460       fprintf (stdout, "    #%d type ", i + 1);
461       pt (t->operand_types[i]);
462       fprintf (stdout, "\n");
463     }
464 }
465
466 static void
467 pe (e)
468      expressionS *e;
469 {
470   fprintf (stdout, "    segment       %s\n", segment_name (e->X_seg));
471   fprintf (stdout, "    add_number    %d (%x)\n",
472            e->X_add_number, e->X_add_number);
473   if (e->X_add_symbol)
474     {
475       fprintf (stdout, "    add_symbol    ");
476       ps (e->X_add_symbol);
477       fprintf (stdout, "\n");
478     }
479   if (e->X_subtract_symbol)
480     {
481       fprintf (stdout, "    sub_symbol    ");
482       ps (e->X_subtract_symbol);
483       fprintf (stdout, "\n");
484     }
485 }
486
487 static void
488 ps (s)
489      symbolS *s;
490 {
491   fprintf (stdout, "%s type %s%s",
492            S_GET_NAME (s),
493            S_IS_EXTERNAL (s) ? "EXTERNAL " : "",
494            segment_name (S_GET_SEGMENT (s)));
495 }
496
497 struct type_name
498   {
499     unsigned int mask;
500     char *tname;
501   }
502
503 type_names[] =
504 {
505   { Reg8, "r8" },
506   { Reg16, "r16" },
507   { Reg32, "r32" },
508   { Imm8, "i8" },
509   { Imm8S, "i8s" },
510   { Imm16, "i16" },
511   { Imm32, "i32" },
512   { Mem8, "Mem8" },
513   { Mem16, "Mem16" },
514   { Mem32, "Mem32" },
515   { BaseIndex, "BaseIndex" },
516   { Abs8, "Abs8" },
517   { Abs16, "Abs16" },
518   { Abs32, "Abs32" },
519   { Disp8, "d8" },
520   { Disp16, "d16" },
521   { Disp32, "d32" },
522   { SReg2, "SReg2" },
523   { SReg3, "SReg3" },
524   { Acc, "Acc" },
525   { InOutPortReg, "InOutPortReg" },
526   { ShiftCount, "ShiftCount" },
527   { Imm1, "i1" },
528   { Control, "control reg" },
529   { Test, "test reg" },
530   { FloatReg, "FReg" },
531   { FloatAcc, "FAcc" },
532   { JumpAbsolute, "Jump Absolute" },
533   { 0, "" }
534 };
535
536 static void
537 pt (t)
538      unsigned int t;
539 {
540   register struct type_name *ty;
541
542   if (t == Unknown)
543     {
544       fprintf (stdout, "Unknown");
545     }
546   else
547     {
548       for (ty = type_names; ty->mask; ty++)
549         if (t & ty->mask)
550           fprintf (stdout, "%s, ", ty->tname);
551     }
552   fflush (stdout);
553 }
554
555 #endif /* DEBUG386 */
556 \f
557 /*
558   This is the guts of the machine-dependent assembler.  LINE points to a
559   machine dependent instruction.  This funciton is supposed to emit
560   the frags/bytes it assembles to.
561   */
562 void
563 md_assemble (line)
564      char *line;
565 {
566   /* Holds temlate once we've found it. */
567   register template *t;
568
569   /* Possible templates for current insn */
570   templates *current_templates = (templates *) 0;
571
572   /* Initialize globals. */
573   memset (&i, '\0', sizeof (i));
574   memset (disp_expressions, '\0', sizeof (disp_expressions));
575   memset (im_expressions, '\0', sizeof (im_expressions));
576   save_stack_p = save_stack;    /* reset stack pointer */
577
578   /* Fist parse an opcode & call i386_operand for the operands.
579            We assume that the scrubber has arranged it so that line[0] is the valid
580            start of a (possibly prefixed) opcode. */
581   {
582     register char *l = line;    /* Fast place to put LINE. */
583
584     /* 1 if operand is pending after ','. */
585     unsigned int expecting_operand = 0;
586     /* 1 if we found a prefix only acceptable with string insns. */
587     unsigned int expecting_string_instruction = 0;
588     /* Non-zero if operand parens not balenced. */
589     unsigned int paren_not_balenced;
590     char *token_start = l;
591
592     while (!is_space_char (*l) && *l != END_OF_INSN)
593       {
594         if (!is_opcode_char (*l))
595           {
596             as_bad ("invalid character %s in opcode", output_invalid (*l));
597             return;
598           }
599         else if (*l != PREFIX_SEPERATOR)
600           {
601             *l = opcode_chars[(unsigned char) *l];      /* fold case of opcodes */
602             l++;
603           }
604         else
605           {                     /* this opcode's got a prefix */
606             register unsigned int q;
607             register prefix_entry *prefix;
608
609             if (l == token_start)
610               {
611                 as_bad ("expecting prefix; got nothing");
612                 return;
613               }
614             END_STRING_AND_SAVE (l);
615             prefix = (prefix_entry *) hash_find (prefix_hash, token_start);
616             if (!prefix)
617               {
618                 as_bad ("no such opcode prefix ('%s')", token_start);
619                 return;
620               }
621             RESTORE_END_STRING (l);
622             /* check for repeated prefix */
623             for (q = 0; q < i.prefixes; q++)
624               if (i.prefix[q] == prefix->prefix_code)
625                 {
626                   as_bad ("same prefix used twice; you don't really want this!");
627                   return;
628                 }
629             if (i.prefixes == MAX_PREFIXES)
630               {
631                 as_bad ("too many opcode prefixes");
632                 return;
633               }
634             i.prefix[i.prefixes++] = prefix->prefix_code;
635             if (prefix->prefix_code == REPE || prefix->prefix_code == REPNE)
636               expecting_string_instruction = 1;
637             /* skip past PREFIX_SEPERATOR and reset token_start */
638             token_start = ++l;
639           }
640       }
641     END_STRING_AND_SAVE (l);
642     if (token_start == l)
643       {
644         as_bad ("expecting opcode; got nothing");
645         return;
646       }
647
648     /* Lookup insn in hash; try intel & att naming conventions if appropriate;
649                    that is:  we only use the opcode suffix 'b' 'w' or 'l' if we need to. */
650     current_templates = (templates *) hash_find (op_hash, token_start);
651     if (!current_templates)
652       {
653         int last_index = strlen (token_start) - 1;
654         char last_char = token_start[last_index];
655         switch (last_char)
656           {
657           case DWORD_OPCODE_SUFFIX:
658           case WORD_OPCODE_SUFFIX:
659           case BYTE_OPCODE_SUFFIX:
660             token_start[last_index] = '\0';
661             current_templates = (templates *) hash_find (op_hash, token_start);
662             token_start[last_index] = last_char;
663             i.suffix = last_char;
664           }
665         if (!current_templates)
666           {
667             as_bad ("no such 386 instruction: `%s'", token_start);
668             return;
669           }
670       }
671     RESTORE_END_STRING (l);
672
673     /* check for rep/repne without a string instruction */
674     if (expecting_string_instruction &&
675         !IS_STRING_INSTRUCTION (current_templates->
676                                 start->base_opcode))
677       {
678         as_bad ("expecting string instruction after rep/repne");
679         return;
680       }
681
682     /* There may be operands to parse. */
683     if (*l != END_OF_INSN &&
684         /* For string instructions, we ignore any operands if given.  This
685            kludges, for example, 'rep/movsb %ds:(%esi), %es:(%edi)' where
686            the operands are always going to be the same, and are not really
687            encoded in machine code. */
688         !IS_STRING_INSTRUCTION (current_templates->
689                                 start->base_opcode))
690       {
691         /* parse operands */
692         do
693           {
694             /* skip optional white space before operand */
695             while (!is_operand_char (*l) && *l != END_OF_INSN)
696               {
697                 if (!is_space_char (*l))
698                   {
699                     as_bad ("invalid character %s before %s operand",
700                             output_invalid (*l),
701                             ordinal_names[i.operands]);
702                     return;
703                   }
704                 l++;
705               }
706             token_start = l;    /* after white space */
707             paren_not_balenced = 0;
708             while (paren_not_balenced || *l != ',')
709               {
710                 if (*l == END_OF_INSN)
711                   {
712                     if (paren_not_balenced)
713                       {
714                         as_bad ("unbalenced parenthesis in %s operand.",
715                                 ordinal_names[i.operands]);
716                         return;
717                       }
718                     else
719                       break;    /* we are done */
720                   }
721                 else if (!is_operand_char (*l))
722                   {
723                     as_bad ("invalid character %s in %s operand",
724                             output_invalid (*l),
725                             ordinal_names[i.operands]);
726                     return;
727                   }
728                 if (*l == '(')
729                   ++paren_not_balenced;
730                 if (*l == ')')
731                   --paren_not_balenced;
732                 l++;
733               }
734             if (l != token_start)
735               {                 /* yes, we've read in another operand */
736                 unsigned int operand_ok;
737                 this_operand = i.operands++;
738                 if (i.operands > MAX_OPERANDS)
739                   {
740                     as_bad ("spurious operands; (%d operands/instruction max)",
741                             MAX_OPERANDS);
742                     return;
743                   }
744                 /* now parse operand adding info to 'i' as we go along */
745                 END_STRING_AND_SAVE (l);
746                 operand_ok = i386_operand (token_start);
747                 RESTORE_END_STRING (l); /* restore old contents */
748                 if (!operand_ok)
749                   return;
750               }
751             else
752               {
753                 if (expecting_operand)
754                   {
755                   expecting_operand_after_comma:
756                     as_bad ("expecting operand after ','; got nothing");
757                     return;
758                   }
759                 if (*l == ',')
760                   {
761                     as_bad ("expecting operand before ','; got nothing");
762                     return;
763                   }
764               }
765
766             /* now *l must be either ',' or END_OF_INSN */
767             if (*l == ',')
768               {
769                 if (*++l == END_OF_INSN)
770                   {             /* just skip it, if it's \n complain */
771                     goto expecting_operand_after_comma;
772                   }
773                 expecting_operand = 1;
774               }
775           }
776         while (*l != END_OF_INSN);      /* until we get end of insn */
777       }
778   }
779
780   /* Now we've parsed the opcode into a set of templates, and have the
781      operands at hand.
782
783      Next, we find a template that matches the given insn,
784      making sure the overlap of the given operands types is consistent
785      with the template operand types. */
786
787 #define MATCH(overlap,given_type) \
788         (overlap && \
789          (overlap & (JumpAbsolute|BaseIndex|Mem8)) \
790          == (given_type & (JumpAbsolute|BaseIndex|Mem8)))
791
792   /* If m0 and m1 are register matches they must be consistent
793      with the expected operand types t0 and t1.
794      That is, if both m0 & m1 are register matches
795      i.e. ( ((m0 & (Reg)) && (m1 & (Reg)) ) ?
796      then, either 1. or 2. must be true:
797      1. the expected operand type register overlap is null:
798      (t0 & t1 & Reg) == 0
799      AND
800      the given register overlap is null:
801      (m0 & m1 & Reg) == 0
802      2. the expected operand type register overlap == the given
803      operand type overlap:  (t0 & t1 & m0 & m1 & Reg).
804      */
805 #define CONSISTENT_REGISTER_MATCH(m0, m1, t0, t1) \
806             ( ((m0 & (Reg)) && (m1 & (Reg))) ? \
807              ( ((t0 & t1 & (Reg)) == 0 && (m0 & m1 & (Reg)) == 0) || \
808               ((t0 & t1) & (m0 & m1) & (Reg)) \
809               ) : 1)
810   {
811     register unsigned int overlap0, overlap1;
812     expressionS *exp;
813     unsigned int overlap2;
814     unsigned int found_reverse_match;
815
816     overlap0 = overlap1 = overlap2 = found_reverse_match = 0;
817     for (t = current_templates->start;
818          t < current_templates->end;
819          t++)
820       {
821
822         /* must have right number of operands */
823         if (i.operands != t->operands)
824           continue;
825         else if (!t->operands)
826           break;                /* 0 operands always matches */
827
828         overlap0 = i.types[0] & t->operand_types[0];
829         switch (t->operands)
830           {
831           case 1:
832             if (!MATCH (overlap0, i.types[0]))
833               continue;
834             break;
835           case 2:
836           case 3:
837             overlap1 = i.types[1] & t->operand_types[1];
838             if (!MATCH (overlap0, i.types[0]) ||
839                 !MATCH (overlap1, i.types[1]) ||
840                 !CONSISTENT_REGISTER_MATCH (overlap0, overlap1,
841                                             t->operand_types[0],
842                                             t->operand_types[1]))
843               {
844
845                 /* check if other direction is valid ... */
846                 if (!(t->opcode_modifier & COMES_IN_BOTH_DIRECTIONS))
847                   continue;
848
849                 /* try reversing direction of operands */
850                 overlap0 = i.types[0] & t->operand_types[1];
851                 overlap1 = i.types[1] & t->operand_types[0];
852                 if (!MATCH (overlap0, i.types[0]) ||
853                     !MATCH (overlap1, i.types[1]) ||
854                     !CONSISTENT_REGISTER_MATCH (overlap0, overlap1,
855                                                 t->operand_types[0],
856                                                 t->operand_types[1]))
857                   {
858                     /* does not match either direction */
859                     continue;
860                   }
861                 /* found a reverse match here -- slip through */
862                 /* found_reverse_match holds which of D or FloatD we've found */
863                 found_reverse_match = t->opcode_modifier & COMES_IN_BOTH_DIRECTIONS;
864               }                 /* endif: not forward match */
865             /* found either forward/reverse 2 operand match here */
866             if (t->operands == 3)
867               {
868                 overlap2 = i.types[2] & t->operand_types[2];
869                 if (!MATCH (overlap2, i.types[2]) ||
870                     !CONSISTENT_REGISTER_MATCH (overlap0, overlap2,
871                                                 t->operand_types[0],
872                                                 t->operand_types[2]) ||
873                     !CONSISTENT_REGISTER_MATCH (overlap1, overlap2,
874                                                 t->operand_types[1],
875                                                 t->operand_types[2]))
876                   continue;
877               }
878             /* found either forward/reverse 2 or 3 operand match here:
879                slip through to break */
880           }
881         break;                  /* we've found a match; break out of loop */
882       }                         /* for (t = ... */
883     if (t == current_templates->end)
884       {                         /* we found no match */
885         as_bad ("operands given don't match any known 386 instruction");
886         return;
887       }
888
889     /* Copy the template we found (we may change it!). */
890     memcpy (&i.tm, t, sizeof (template));
891     t = &i.tm;                  /* alter new copy of template */
892
893     /* If there's no opcode suffix we try to invent one based on register
894        operands. */
895     if (!i.suffix && i.reg_operands)
896       {
897         /* We take i.suffix from the LAST register operand specified.  This
898            assumes that the last register operands is the destination register
899            operand. */
900         int o;
901         for (o = 0; o < MAX_OPERANDS; o++)
902           if (i.types[o] & Reg)
903             {
904               i.suffix = (i.types[o] == Reg8) ? BYTE_OPCODE_SUFFIX :
905                 (i.types[o] == Reg16) ? WORD_OPCODE_SUFFIX :
906                 DWORD_OPCODE_SUFFIX;
907             }
908       }
909
910     /* Make still unresolved immediate matches conform to size of immediate
911        given in i.suffix. Note:  overlap2 cannot be an immediate!
912        We assume this. */
913     if ((overlap0 & (Imm8 | Imm8S | Imm16 | Imm32))
914         && overlap0 != Imm8 && overlap0 != Imm8S
915         && overlap0 != Imm16 && overlap0 != Imm32)
916       {
917         if (!i.suffix)
918           {
919             as_bad ("no opcode suffix given; can't determine immediate size");
920             return;
921           }
922         overlap0 &= (i.suffix == BYTE_OPCODE_SUFFIX ? (Imm8 | Imm8S) :
923                      (i.suffix == WORD_OPCODE_SUFFIX ? Imm16 : Imm32));
924       }
925     if ((overlap1 & (Imm8 | Imm8S | Imm16 | Imm32))
926         && overlap1 != Imm8 && overlap1 != Imm8S
927         && overlap1 != Imm16 && overlap1 != Imm32)
928       {
929         if (!i.suffix)
930           {
931             as_bad ("no opcode suffix given; can't determine immediate size");
932             return;
933           }
934         overlap1 &= (i.suffix == BYTE_OPCODE_SUFFIX ? (Imm8 | Imm8S) :
935                      (i.suffix == WORD_OPCODE_SUFFIX ? Imm16 : Imm32));
936       }
937
938     i.types[0] = overlap0;
939     i.types[1] = overlap1;
940     i.types[2] = overlap2;
941
942     if (overlap0 & ImplicitRegister)
943       i.reg_operands--;
944     if (overlap1 & ImplicitRegister)
945       i.reg_operands--;
946     if (overlap2 & ImplicitRegister)
947       i.reg_operands--;
948     if (overlap0 & Imm1)
949       i.imm_operands = 0;       /* kludge for shift insns */
950
951     if (found_reverse_match)
952       {
953         unsigned int save;
954         save = t->operand_types[0];
955         t->operand_types[0] = t->operand_types[1];
956         t->operand_types[1] = save;
957       }
958
959     /* Finalize opcode.  First, we change the opcode based on the operand
960        size given by i.suffix: we never have to change things for byte insns,
961        or when no opcode suffix is need to size the operands. */
962
963     if (!i.suffix && (t->opcode_modifier & W))
964       {
965         as_bad ("no opcode suffix given and no register operands; can't size instruction");
966         return;
967       }
968
969     if (i.suffix && i.suffix != BYTE_OPCODE_SUFFIX)
970       {
971         /* Select between byte and word/dword operations. */
972         if (t->opcode_modifier & W)
973           t->base_opcode |= W;
974         /* Now select between word & dword operations via the
975                                    operand size prefix. */
976         if (i.suffix == WORD_OPCODE_SUFFIX)
977           {
978             if (i.prefixes == MAX_PREFIXES)
979               {
980                 as_bad ("%d prefixes given and 'w' opcode suffix gives too many prefixes",
981                         MAX_PREFIXES);
982                 return;
983               }
984             i.prefix[i.prefixes++] = WORD_PREFIX_OPCODE;
985           }
986       }
987
988     /* For insns with operands there are more diddles to do to the opcode. */
989     if (i.operands)
990       {
991         /* If we found a reverse match we must alter the opcode direction bit
992            found_reverse_match holds bit to set (different for int &
993            float insns). */
994
995         if (found_reverse_match)
996           {
997             t->base_opcode |= found_reverse_match;
998           }
999
1000         /* The imul $imm, %reg instruction is converted into
1001            imul $imm, %reg, %reg. */
1002         if (t->opcode_modifier & imulKludge)
1003           {
1004             /* Pretend we saw the 3 operand case. */
1005             i.regs[2] = i.regs[1];
1006             i.reg_operands = 2;
1007           }
1008
1009         /* Certain instructions expect the destination to be in the i.rm.reg
1010            field.  This is by far the exceptional case.  For these
1011            instructions, if the source operand is a register, we must reverse
1012            the i.rm.reg and i.rm.regmem fields.  We accomplish this by faking
1013            that the two register operands were given in the reverse order. */
1014         if ((t->opcode_modifier & ReverseRegRegmem) && i.reg_operands == 2)
1015           {
1016             unsigned int first_reg_operand = (i.types[0] & Reg) ? 0 : 1;
1017             unsigned int second_reg_operand = first_reg_operand + 1;
1018             reg_entry *tmp = i.regs[first_reg_operand];
1019             i.regs[first_reg_operand] = i.regs[second_reg_operand];
1020             i.regs[second_reg_operand] = tmp;
1021           }
1022
1023         if (t->opcode_modifier & ShortForm)
1024           {
1025             /* The register or float register operand is in operand 0 or 1. */
1026             unsigned int o = (i.types[0] & (Reg | FloatReg)) ? 0 : 1;
1027             /* Register goes in low 3 bits of opcode. */
1028             t->base_opcode |= i.regs[o]->reg_num;
1029           }
1030         else if (t->opcode_modifier & ShortFormW)
1031           {
1032             /* Short form with 0x8 width bit.  Register is always dest. operand */
1033             t->base_opcode |= i.regs[1]->reg_num;
1034             if (i.suffix == WORD_OPCODE_SUFFIX ||
1035                 i.suffix == DWORD_OPCODE_SUFFIX)
1036               t->base_opcode |= 0x8;
1037           }
1038         else if (t->opcode_modifier & Seg2ShortForm)
1039           {
1040             if (t->base_opcode == POP_SEG_SHORT && i.regs[0]->reg_num == 1)
1041               {
1042                 as_bad ("you can't 'pop cs' on the 386.");
1043                 return;
1044               }
1045             t->base_opcode |= (i.regs[0]->reg_num << 3);
1046           }
1047         else if (t->opcode_modifier & Seg3ShortForm)
1048           {
1049             /* 'push %fs' is 0x0fa0; 'pop %fs' is 0x0fa1.
1050                'push %gs' is 0x0fa8; 'pop %fs' is 0x0fa9.
1051                So, only if i.regs[0]->reg_num == 5 (%gs) do we need
1052                to change the opcode. */
1053             if (i.regs[0]->reg_num == 5)
1054               t->base_opcode |= 0x08;
1055           }
1056         else if (t->opcode_modifier & Modrm)
1057           {
1058             /* The opcode is completed (modulo t->extension_opcode which must
1059                be put into the modrm byte.
1060                Now, we make the modrm & index base bytes based on all the info
1061                we've collected. */
1062
1063             /* i.reg_operands MUST be the number of real register operands;
1064                implicit registers do not count. */
1065             if (i.reg_operands == 2)
1066               {
1067                 unsigned int source, dest;
1068                 source = (i.types[0] & (Reg | SReg2 | SReg3 | Control | Debug | Test)) ? 0 : 1;
1069                 dest = source + 1;
1070                 i.rm.mode = 3;
1071                 /* We must be careful to make sure that all
1072                    segment/control/test/debug registers go into the i.rm.reg
1073                    field (despite the whether they are source or destination
1074                    operands). */
1075                 if (i.regs[dest]->reg_type & (SReg2 | SReg3 | Control | Debug | Test))
1076                   {
1077                     i.rm.reg = i.regs[dest]->reg_num;
1078                     i.rm.regmem = i.regs[source]->reg_num;
1079                   }
1080                 else
1081                   {
1082                     i.rm.reg = i.regs[source]->reg_num;
1083                     i.rm.regmem = i.regs[dest]->reg_num;
1084                   }
1085               }
1086             else
1087               {                 /* if it's not 2 reg operands... */
1088                 if (i.mem_operands)
1089                   {
1090                     unsigned int fake_zero_displacement = 0;
1091                     unsigned int o = (i.types[0] & Mem) ? 0 : ((i.types[1] & Mem) ? 1 : 2);
1092
1093                     /* Encode memory operand into modrm byte and base index byte. */
1094
1095                     if (i.base_reg == esp && !i.index_reg)
1096                       {
1097                         /* <disp>(%esp) becomes two byte modrm with no index register. */
1098                         i.rm.regmem = ESCAPE_TO_TWO_BYTE_ADDRESSING;
1099                         i.rm.mode = mode_from_disp_size (i.types[o]);
1100                         i.bi.base = ESP_REG_NUM;
1101                         i.bi.index = NO_INDEX_REGISTER;
1102                         i.bi.scale = 0; /* Must be zero! */
1103                       }
1104                     else if (i.base_reg == ebp && !i.index_reg)
1105                       {
1106                         if (!(i.types[o] & Disp))
1107                           {
1108                             /* Must fake a zero byte displacement.
1109                                                                            There is no direct way to code '(%ebp)' directly. */
1110                             fake_zero_displacement = 1;
1111                             /* fake_zero_displacement code does not set this. */
1112                             i.types[o] |= Disp8;
1113                           }
1114                         i.rm.mode = mode_from_disp_size (i.types[o]);
1115                         i.rm.regmem = EBP_REG_NUM;
1116                       }
1117                     else if (!i.base_reg && (i.types[o] & BaseIndex))
1118                       {
1119                         /* There are three cases here.
1120                            Case 1:  '<32bit disp>(,1)' -- indirect absolute.
1121                            (Same as cases 2 & 3 with NO index register)
1122                            Case 2:  <32bit disp> (,<index>) -- no base register with disp
1123                            Case 3:  (, <index>)       --- no base register;
1124                            no disp (must add 32bit 0 disp). */
1125                         i.rm.regmem = ESCAPE_TO_TWO_BYTE_ADDRESSING;
1126                         i.rm.mode = 0;  /* 32bit mode */
1127                         i.bi.base = NO_BASE_REGISTER;
1128                         i.types[o] &= ~Disp;
1129                         i.types[o] |= Disp32;   /* Must be 32bit! */
1130                         if (i.index_reg)
1131                           {     /* case 2 or case 3 */
1132                             i.bi.index = i.index_reg->reg_num;
1133                             i.bi.scale = i.log2_scale_factor;
1134                             if (i.disp_operands == 0)
1135                               fake_zero_displacement = 1;       /* case 3 */
1136                           }
1137                         else
1138                           {
1139                             i.bi.index = NO_INDEX_REGISTER;
1140                             i.bi.scale = 0;
1141                           }
1142                       }
1143                     else if (i.disp_operands && !i.base_reg && !i.index_reg)
1144                       {
1145                         /* Operand is just <32bit disp> */
1146                         i.rm.regmem = EBP_REG_NUM;
1147                         i.rm.mode = 0;
1148                         i.types[o] &= ~Disp;
1149                         i.types[o] |= Disp32;
1150                       }
1151                     else
1152                       {
1153                         /* It's not a special case; rev'em up. */
1154                         i.rm.regmem = i.base_reg->reg_num;
1155                         i.rm.mode = mode_from_disp_size (i.types[o]);
1156                         if (i.index_reg)
1157                           {
1158                             i.rm.regmem = ESCAPE_TO_TWO_BYTE_ADDRESSING;
1159                             i.bi.base = i.base_reg->reg_num;
1160                             i.bi.index = i.index_reg->reg_num;
1161                             i.bi.scale = i.log2_scale_factor;
1162                             if (i.base_reg == ebp && i.disp_operands == 0)
1163                               { /* pace */
1164                                 fake_zero_displacement = 1;
1165                                 i.types[o] |= Disp8;
1166                                 i.rm.mode = mode_from_disp_size (i.types[o]);
1167                               }
1168                           }
1169                       }
1170                     if (fake_zero_displacement)
1171                       {
1172                         /* Fakes a zero displacement assuming that i.types[o]
1173                            holds the correct displacement size. */
1174                         exp = &disp_expressions[i.disp_operands++];
1175                         i.disps[o] = exp;
1176                         exp->X_seg = SEG_ABSOLUTE;
1177                         exp->X_add_number = 0;
1178                         exp->X_add_symbol = (symbolS *) 0;
1179                         exp->X_subtract_symbol = (symbolS *) 0;
1180                       }
1181
1182                     /* Select the correct segment for the memory operand. */
1183                     if (i.seg)
1184                       {
1185                         unsigned int seg_index;
1186                         const seg_entry *default_seg;
1187
1188                         if (i.rm.regmem == ESCAPE_TO_TWO_BYTE_ADDRESSING)
1189                           {
1190                             seg_index = (i.rm.mode << 3) | i.bi.base;
1191                             default_seg = two_byte_segment_defaults[seg_index];
1192                           }
1193                         else
1194                           {
1195                             seg_index = (i.rm.mode << 3) | i.rm.regmem;
1196                             default_seg = one_byte_segment_defaults[seg_index];
1197                           }
1198                         /* If the specified segment is not the default, use an
1199                            opcode prefix to select it */
1200                         if (i.seg != default_seg)
1201                           {
1202                             if (i.prefixes == MAX_PREFIXES)
1203                               {
1204                                 as_bad ("%d prefixes given and %s segment override gives too many prefixes",
1205                                         MAX_PREFIXES, i.seg->seg_name);
1206                                 return;
1207                               }
1208                             i.prefix[i.prefixes++] = i.seg->seg_prefix;
1209                           }
1210                       }
1211                   }
1212
1213                 /* Fill in i.rm.reg or i.rm.regmem field with register operand
1214                    (if any) based on t->extension_opcode. Again, we must be
1215                    careful to make sure that segment/control/debug/test
1216                    registers are coded into the i.rm.reg field. */
1217                 if (i.reg_operands)
1218                   {
1219                     unsigned int o =
1220                     (i.types[0] & (Reg | SReg2 | SReg3 | Control | Debug | Test)) ? 0 :
1221                     (i.types[1] & (Reg | SReg2 | SReg3 | Control | Debug | Test)) ? 1 : 2;
1222                     /* If there is an extension opcode to put here, the
1223                        register number must be put into the regmem field. */
1224                     if (t->extension_opcode != None)
1225                       i.rm.regmem = i.regs[o]->reg_num;
1226                     else
1227                       i.rm.reg = i.regs[o]->reg_num;
1228
1229                     /* Now, if no memory operand has set i.rm.mode = 0, 1, 2
1230                        we must set it to 3 to indicate this is a register
1231                        operand int the regmem field */
1232                     if (!i.mem_operands)
1233                       i.rm.mode = 3;
1234                   }
1235
1236                 /* Fill in i.rm.reg field with extension opcode (if any). */
1237                 if (t->extension_opcode != None)
1238                   i.rm.reg = t->extension_opcode;
1239               }
1240           }
1241       }
1242   }
1243
1244   /* Handle conversion of 'int $3' --> special int3 insn. */
1245   if (t->base_opcode == INT_OPCODE && i.imms[0]->X_add_number == 3)
1246     {
1247       t->base_opcode = INT3_OPCODE;
1248       i.imm_operands = 0;
1249     }
1250
1251   /* We are ready to output the insn. */
1252   {
1253     register char *p;
1254
1255     /* Output jumps. */
1256     if (t->opcode_modifier & Jump)
1257       {
1258         int n = i.disps[0]->X_add_number;
1259
1260         switch (i.disps[0]->X_seg)
1261           {
1262           case SEG_ABSOLUTE:
1263             if (fits_in_signed_byte (n))
1264               {
1265                 p = frag_more (2);
1266                 p[0] = t->base_opcode;
1267                 p[1] = n;
1268 #if 0                           /* leave out 16 bit jumps - pace */
1269               }
1270             else if (fits_in_signed_word (n))
1271               {
1272                 p = frag_more (4);
1273                 p[0] = WORD_PREFIX_OPCODE;
1274                 p[1] = t->base_opcode;
1275                 md_number_to_chars (&p[2], n, 2);
1276 #endif
1277               }
1278             else
1279               {                 /* It's an absolute dword displacement. */
1280                 if (t->base_opcode == JUMP_PC_RELATIVE)
1281                   {             /* pace */
1282                     /* unconditional jump */
1283                     p = frag_more (5);
1284                     p[0] = 0xe9;
1285                     md_number_to_chars (&p[1], n, 4);
1286                   }
1287                 else
1288                   {
1289                     /* conditional jump */
1290                     p = frag_more (6);
1291                     p[0] = TWO_BYTE_OPCODE_ESCAPE;
1292                     p[1] = t->base_opcode + 0x10;
1293                     md_number_to_chars (&p[2], n, 4);
1294                   }
1295               }
1296             break;
1297           default:
1298             /* It's a symbol; end frag & setup for relax.
1299                Make sure there are 6 chars left in the current frag; if not
1300                we'll have to start a new one. */
1301             /* I caught it failing with obstack_room == 6,
1302                so I changed to <=   pace */
1303             if (obstack_room (&frags) <= 6)
1304               {
1305                 frag_wane (frag_now);
1306                 frag_new (0);
1307               }
1308             p = frag_more (1);
1309             p[0] = t->base_opcode;
1310             frag_var (rs_machine_dependent,
1311                       6,        /* 2 opcode/prefix + 4 displacement */
1312                       1,
1313                       ((unsigned char) *p == JUMP_PC_RELATIVE
1314                        ? ENCODE_RELAX_STATE (UNCOND_JUMP, BYTE)
1315                        : ENCODE_RELAX_STATE (COND_JUMP, BYTE)),
1316                       i.disps[0]->X_add_symbol,
1317                       n, p);
1318             break;
1319           }
1320       }
1321     else if (t->opcode_modifier & (JumpByte | JumpDword))
1322       {
1323         int size = (t->opcode_modifier & JumpByte) ? 1 : 4;
1324         int n = i.disps[0]->X_add_number;
1325
1326         if (fits_in_unsigned_byte (t->base_opcode))
1327           {
1328             FRAG_APPEND_1_CHAR (t->base_opcode);
1329           }
1330         else
1331           {
1332             p = frag_more (2);  /* opcode can be at most two bytes */
1333             /* put out high byte first: can't use md_number_to_chars! */
1334             *p++ = (t->base_opcode >> 8) & 0xff;
1335             *p = t->base_opcode & 0xff;
1336           }
1337
1338         p = frag_more (size);
1339         switch (i.disps[0]->X_seg)
1340           {
1341           case SEG_ABSOLUTE:
1342             md_number_to_chars (p, n, size);
1343             if (size == 1 && !fits_in_signed_byte (n))
1344               {
1345                 as_bad ("loop/jecx only takes byte displacement; %d shortened to %d",
1346                         n, *p);
1347               }
1348             break;
1349           default:
1350             fix_new (frag_now, p - frag_now->fr_literal, size,
1351                      i.disps[0]->X_add_symbol, i.disps[0]->X_subtract_symbol,
1352                      i.disps[0]->X_add_number, 1, NO_RELOC);
1353             break;
1354           }
1355       }
1356     else if (t->opcode_modifier & JumpInterSegment)
1357       {
1358         p = frag_more (1 + 2 + 4);      /* 1 opcode; 2 segment; 4 offset */
1359         p[0] = t->base_opcode;
1360         if (i.imms[1]->X_seg == SEG_ABSOLUTE)
1361           md_number_to_chars (p + 1, i.imms[1]->X_add_number, 4);
1362         else
1363           fix_new (frag_now, p + 1 - frag_now->fr_literal, 4,
1364                    i.imms[1]->X_add_symbol,
1365                    i.imms[1]->X_subtract_symbol,
1366                    i.imms[1]->X_add_number, 0, NO_RELOC);
1367         if (i.imms[0]->X_seg != SEG_ABSOLUTE)
1368           as_bad ("can't handle non absolute segment in long call/jmp");
1369         md_number_to_chars (p + 5, i.imms[0]->X_add_number, 2);
1370       }
1371     else
1372       {
1373         /* Output normal instructions here. */
1374         unsigned char *q;
1375
1376         /* First the prefix bytes. */
1377         for (q = i.prefix; q < i.prefix + i.prefixes; q++)
1378           {
1379             p = frag_more (1);
1380             md_number_to_chars (p, (unsigned int) *q, 1);
1381           }
1382
1383         /* Now the opcode; be careful about word order here! */
1384         if (fits_in_unsigned_byte (t->base_opcode))
1385           {
1386             FRAG_APPEND_1_CHAR (t->base_opcode);
1387           }
1388         else if (fits_in_unsigned_word (t->base_opcode))
1389           {
1390             p = frag_more (2);
1391             /* put out high byte first: can't use md_number_to_chars! */
1392             *p++ = (t->base_opcode >> 8) & 0xff;
1393             *p = t->base_opcode & 0xff;
1394           }
1395         else
1396           {                     /* opcode is either 3 or 4 bytes */
1397             if (t->base_opcode & 0xff000000)
1398               {
1399                 p = frag_more (4);
1400                 *p++ = (t->base_opcode >> 24) & 0xff;
1401               }
1402             else
1403               p = frag_more (3);
1404             *p++ = (t->base_opcode >> 16) & 0xff;
1405             *p++ = (t->base_opcode >> 8) & 0xff;
1406             *p = (t->base_opcode) & 0xff;
1407           }
1408
1409         /* Now the modrm byte and base index byte (if present). */
1410         if (t->opcode_modifier & Modrm)
1411           {
1412             p = frag_more (1);
1413             /* md_number_to_chars (p, i.rm, 1); */
1414             md_number_to_chars (p, (i.rm.regmem << 0 | i.rm.reg << 3 | i.rm.mode << 6), 1);
1415             /* If i.rm.regmem == ESP (4) && i.rm.mode != Mode 3 (Register mode)
1416                                    ==> need second modrm byte. */
1417             if (i.rm.regmem == ESCAPE_TO_TWO_BYTE_ADDRESSING && i.rm.mode != 3)
1418               {
1419                 p = frag_more (1);
1420                 /* md_number_to_chars (p, i.bi, 1); */
1421                 md_number_to_chars (p, (i.bi.base << 0 | i.bi.index << 3 | i.bi.scale << 6), 1);
1422               }
1423           }
1424
1425         if (i.disp_operands)
1426           {
1427             register unsigned int n;
1428
1429             for (n = 0; n < i.operands; n++)
1430               {
1431                 if (i.disps[n])
1432                   {
1433                     if (i.disps[n]->X_seg == SEG_ABSOLUTE)
1434                       {
1435                         if (i.types[n] & (Disp8 | Abs8))
1436                           {
1437                             p = frag_more (1);
1438                             md_number_to_chars (p, i.disps[n]->X_add_number, 1);
1439                           }
1440                         else if (i.types[n] & (Disp16 | Abs16))
1441                           {
1442                             p = frag_more (2);
1443                             md_number_to_chars (p, i.disps[n]->X_add_number, 2);
1444                           }
1445                         else
1446                           {     /* Disp32|Abs32 */
1447                             p = frag_more (4);
1448                             md_number_to_chars (p, i.disps[n]->X_add_number, 4);
1449                           }
1450                       }
1451                     else
1452                       {         /* not SEG_ABSOLUTE */
1453                         /* need a 32-bit fixup (don't support 8bit non-absolute disps) */
1454                         p = frag_more (4);
1455                         fix_new (frag_now, p - frag_now->fr_literal, 4,
1456                                  i.disps[n]->X_add_symbol, i.disps[n]->X_subtract_symbol,
1457                                  i.disps[n]->X_add_number, 0, NO_RELOC);
1458                       }
1459                   }
1460               }
1461           }                     /* end displacement output */
1462
1463         /* output immediate */
1464         if (i.imm_operands)
1465           {
1466             register unsigned int n;
1467
1468             for (n = 0; n < i.operands; n++)
1469               {
1470                 if (i.imms[n])
1471                   {
1472                     if (i.imms[n]->X_seg == SEG_ABSOLUTE)
1473                       {
1474                         if (i.types[n] & (Imm8 | Imm8S))
1475                           {
1476                             p = frag_more (1);
1477                             md_number_to_chars (p, i.imms[n]->X_add_number, 1);
1478                           }
1479                         else if (i.types[n] & Imm16)
1480                           {
1481                             p = frag_more (2);
1482                             md_number_to_chars (p, i.imms[n]->X_add_number, 2);
1483                           }
1484                         else
1485                           {
1486                             p = frag_more (4);
1487                             md_number_to_chars (p, i.imms[n]->X_add_number, 4);
1488                           }
1489                       }
1490                     else
1491                       {         /* not SEG_ABSOLUTE */
1492                         /* need a 32-bit fixup (don't support 8bit non-absolute ims) */
1493                         /* try to support other sizes ... */
1494                         int size;
1495                         if (i.types[n] & (Imm8 | Imm8S))
1496                           size = 1;
1497                         else if (i.types[n] & Imm16)
1498                           size = 2;
1499                         else
1500                           size = 4;
1501                         p = frag_more (size);
1502                         fix_new (frag_now, p - frag_now->fr_literal, size,
1503                                  i.imms[n]->X_add_symbol, i.imms[n]->X_subtract_symbol,
1504                                  i.imms[n]->X_add_number, 0, NO_RELOC);
1505                       }
1506                   }
1507               }
1508           }                     /* end immediate output */
1509       }
1510
1511 #ifdef DEBUG386
1512     if (flagseen['D'])
1513       {
1514         pi (line, &i);
1515       }
1516 #endif /* DEBUG386 */
1517
1518   }
1519   return;
1520 }
1521 \f
1522 /* Parse OPERAND_STRING into the i386_insn structure I.  Returns non-zero
1523    on error. */
1524
1525 static int
1526 i386_operand (operand_string)
1527      char *operand_string;
1528 {
1529   register char *op_string = operand_string;
1530
1531   /* Address of '\0' at end of operand_string. */
1532   char *end_of_operand_string = operand_string + strlen (operand_string);
1533
1534   /* Start and end of displacement string expression (if found). */
1535   char *displacement_string_start = NULL;
1536   char *displacement_string_end = NULL;
1537
1538   /* We check for an absolute prefix (differentiating,
1539            for example, 'jmp pc_relative_label' from 'jmp *absolute_label'. */
1540   if (*op_string == ABSOLUTE_PREFIX)
1541     {
1542       op_string++;
1543       i.types[this_operand] |= JumpAbsolute;
1544     }
1545
1546   /* Check if operand is a register. */
1547   if (*op_string == REGISTER_PREFIX)
1548     {
1549       register reg_entry *r;
1550       if (!(r = parse_register (op_string)))
1551         {
1552           as_bad ("bad register name ('%s')", op_string);
1553           return 0;
1554         }
1555       /* Check for segment override, rather than segment register by
1556                    searching for ':' after %<x>s where <x> = s, c, d, e, f, g. */
1557       if ((r->reg_type & (SReg2 | SReg3)) && op_string[3] == ':')
1558         {
1559           switch (r->reg_num)
1560             {
1561             case 0:
1562               i.seg = (seg_entry *) & es;
1563               break;
1564             case 1:
1565               i.seg = (seg_entry *) & cs;
1566               break;
1567             case 2:
1568               i.seg = (seg_entry *) & ss;
1569               break;
1570             case 3:
1571               i.seg = (seg_entry *) & ds;
1572               break;
1573             case 4:
1574               i.seg = (seg_entry *) & fs;
1575               break;
1576             case 5:
1577               i.seg = (seg_entry *) & gs;
1578               break;
1579             }
1580           op_string += 4;       /* skip % <x> s : */
1581           operand_string = op_string;   /* Pretend given string starts here. */
1582           if (!is_digit_char (*op_string) && !is_identifier_char (*op_string)
1583               && *op_string != '(' && *op_string != ABSOLUTE_PREFIX)
1584             {
1585               as_bad ("bad memory operand after segment override");
1586               return 0;
1587             }
1588           /* Handle case of %es:*foo. */
1589           if (*op_string == ABSOLUTE_PREFIX)
1590             {
1591               op_string++;
1592               i.types[this_operand] |= JumpAbsolute;
1593             }
1594           goto do_memory_reference;
1595         }
1596       i.types[this_operand] |= r->reg_type;
1597       i.regs[this_operand] = r;
1598       i.reg_operands++;
1599     }
1600   else if (*op_string == IMMEDIATE_PREFIX)
1601     {                           /* ... or an immediate */
1602       char *save_input_line_pointer;
1603       segT exp_seg = SEG_GOOF;
1604       expressionS *exp;
1605
1606       if (i.imm_operands == MAX_IMMEDIATE_OPERANDS)
1607         {
1608           as_bad ("only 1 or 2 immediate operands are allowed");
1609           return 0;
1610         }
1611
1612       exp = &im_expressions[i.imm_operands++];
1613       i.imms[this_operand] = exp;
1614       save_input_line_pointer = input_line_pointer;
1615       input_line_pointer = ++op_string; /* must advance op_string! */
1616       exp_seg = expression (exp);
1617       input_line_pointer = save_input_line_pointer;
1618
1619       switch (exp_seg)
1620         {
1621         case SEG_ABSENT:        /* missing or bad expr becomes absolute 0 */
1622           as_bad ("missing or invalid immediate expression '%s' taken as 0",
1623                   operand_string);
1624           exp->X_seg = SEG_ABSOLUTE;
1625           exp->X_add_number = 0;
1626           exp->X_add_symbol = (symbolS *) 0;
1627           exp->X_subtract_symbol = (symbolS *) 0;
1628           i.types[this_operand] |= Imm;
1629           break;
1630         case SEG_ABSOLUTE:
1631           i.types[this_operand] |= smallest_imm_type (exp->X_add_number);
1632           break;
1633         case SEG_TEXT:
1634         case SEG_DATA:
1635         case SEG_BSS:
1636         case SEG_UNKNOWN:
1637           i.types[this_operand] |= Imm32;       /* this is an address ==> 32bit */
1638           break;
1639         default:
1640         seg_unimplemented:
1641           as_bad ("Unimplemented segment type %d in parse_operand", exp_seg);
1642           return 0;
1643         }
1644       /* shorten this type of this operand if the instruction wants
1645                  * fewer bits than are present in the immediate.  The bit field
1646                  * code can put out 'andb $0xffffff, %al', for example.   pace
1647                  * also 'movw $foo,(%eax)'
1648                  */
1649       switch (i.suffix)
1650         {
1651         case WORD_OPCODE_SUFFIX:
1652           i.types[this_operand] |= Imm16;
1653           break;
1654         case BYTE_OPCODE_SUFFIX:
1655           i.types[this_operand] |= Imm16 | Imm8 | Imm8S;
1656           break;
1657         }
1658     }
1659   else if (is_digit_char (*op_string) || is_identifier_char (*op_string)
1660            || *op_string == '(')
1661     {
1662       /* This is a memory reference of some sort. */
1663       register char *base_string;
1664       unsigned int found_base_index_form;
1665
1666     do_memory_reference:
1667       if (i.mem_operands == MAX_MEMORY_OPERANDS)
1668         {
1669           as_bad ("more than 1 memory reference in instruction");
1670           return 0;
1671         }
1672       i.mem_operands++;
1673
1674       /* Determine type of memory operand from opcode_suffix;
1675                    no opcode suffix implies general memory references. */
1676       switch (i.suffix)
1677         {
1678         case BYTE_OPCODE_SUFFIX:
1679           i.types[this_operand] |= Mem8;
1680           break;
1681         case WORD_OPCODE_SUFFIX:
1682           i.types[this_operand] |= Mem16;
1683           break;
1684         case DWORD_OPCODE_SUFFIX:
1685         default:
1686           i.types[this_operand] |= Mem32;
1687         }
1688
1689       /*  Check for base index form.  We detect the base index form by
1690                     looking for an ')' at the end of the operand, searching
1691                     for the '(' matching it, and finding a REGISTER_PREFIX or ','
1692                     after it. */
1693       base_string = end_of_operand_string - 1;
1694       found_base_index_form = 0;
1695       if (*base_string == ')')
1696         {
1697           unsigned int parens_balenced = 1;
1698           /* We've already checked that the number of left & right ()'s are equal,
1699                            so this loop will not be infinite. */
1700           do
1701             {
1702               base_string--;
1703               if (*base_string == ')')
1704                 parens_balenced++;
1705               if (*base_string == '(')
1706                 parens_balenced--;
1707             }
1708           while (parens_balenced);
1709           base_string++;        /* Skip past '('. */
1710           if (*base_string == REGISTER_PREFIX || *base_string == ',')
1711             found_base_index_form = 1;
1712         }
1713
1714       /* If we can't parse a base index register expression, we've found
1715                    a pure displacement expression.  We set up displacement_string_start
1716                    and displacement_string_end for the code below. */
1717       if (!found_base_index_form)
1718         {
1719           displacement_string_start = op_string;
1720           displacement_string_end = end_of_operand_string;
1721         }
1722       else
1723         {
1724           char *base_reg_name, *index_reg_name, *num_string;
1725           int num;
1726
1727           i.types[this_operand] |= BaseIndex;
1728
1729           /* If there is a displacement set-up for it to be parsed later. */
1730           if (base_string != op_string + 1)
1731             {
1732               displacement_string_start = op_string;
1733               displacement_string_end = base_string - 1;
1734             }
1735
1736           /* Find base register (if any). */
1737           if (*base_string != ',')
1738             {
1739               base_reg_name = base_string++;
1740               /* skip past register name & parse it */
1741               while (isalpha (*base_string))
1742                 base_string++;
1743               if (base_string == base_reg_name + 1)
1744                 {
1745                   as_bad ("can't find base register name after '(%c'",
1746                           REGISTER_PREFIX);
1747                   return 0;
1748                 }
1749               END_STRING_AND_SAVE (base_string);
1750               if (!(i.base_reg = parse_register (base_reg_name)))
1751                 {
1752                   as_bad ("bad base register name ('%s')", base_reg_name);
1753                   return 0;
1754                 }
1755               RESTORE_END_STRING (base_string);
1756             }
1757
1758           /* Now check seperator; must be ',' ==> index reg
1759                            OR num ==> no index reg. just scale factor
1760                            OR ')' ==> end. (scale factor = 1) */
1761           if (*base_string != ',' && *base_string != ')')
1762             {
1763               as_bad ("expecting ',' or ')' after base register in `%s'",
1764                       operand_string);
1765               return 0;
1766             }
1767
1768           /* There may index reg here; and there may be a scale factor. */
1769           if (*base_string == ',' && *(base_string + 1) == REGISTER_PREFIX)
1770             {
1771               index_reg_name = ++base_string;
1772               while (isalpha (*++base_string));
1773               END_STRING_AND_SAVE (base_string);
1774               if (!(i.index_reg = parse_register (index_reg_name)))
1775                 {
1776                   as_bad ("bad index register name ('%s')", index_reg_name);
1777                   return 0;
1778                 }
1779               RESTORE_END_STRING (base_string);
1780             }
1781
1782           /* Check for scale factor. */
1783           if (*base_string == ',' && isdigit (*(base_string + 1)))
1784             {
1785               num_string = ++base_string;
1786               while (is_digit_char (*base_string))
1787                 base_string++;
1788               if (base_string == num_string)
1789                 {
1790                   as_bad ("can't find a scale factor after ','");
1791                   return 0;
1792                 }
1793               END_STRING_AND_SAVE (base_string);
1794               /* We've got a scale factor. */
1795               if (!sscanf (num_string, "%d", &num))
1796                 {
1797                   as_bad ("can't parse scale factor from '%s'", num_string);
1798                   return 0;
1799                 }
1800               RESTORE_END_STRING (base_string);
1801               switch (num)
1802                 {               /* must be 1 digit scale */
1803                 case 1:
1804                   i.log2_scale_factor = 0;
1805                   break;
1806                 case 2:
1807                   i.log2_scale_factor = 1;
1808                   break;
1809                 case 4:
1810                   i.log2_scale_factor = 2;
1811                   break;
1812                 case 8:
1813                   i.log2_scale_factor = 3;
1814                   break;
1815                 default:
1816                   as_bad ("expecting scale factor of 1, 2, 4, 8; got %d", num);
1817                   return 0;
1818                 }
1819             }
1820           else
1821             {
1822               if (!i.index_reg && *base_string == ',')
1823                 {
1824                   as_bad ("expecting index register or scale factor after ','; got '%c'",
1825                           *(base_string + 1));
1826                   return 0;
1827                 }
1828             }
1829         }
1830
1831       /* If there's an expression begining the operand, parse it,
1832                    assuming displacement_string_start and displacement_string_end
1833                    are meaningful. */
1834       if (displacement_string_start)
1835         {
1836           register expressionS *exp;
1837           segT exp_seg = SEG_GOOF;
1838           char *save_input_line_pointer;
1839           exp = &disp_expressions[i.disp_operands];
1840           i.disps[this_operand] = exp;
1841           i.disp_operands++;
1842           save_input_line_pointer = input_line_pointer;
1843           input_line_pointer = displacement_string_start;
1844           END_STRING_AND_SAVE (displacement_string_end);
1845           exp_seg = expression (exp);
1846           if (*input_line_pointer)
1847             as_bad ("Ignoring junk '%s' after expression", input_line_pointer);
1848           RESTORE_END_STRING (displacement_string_end);
1849           input_line_pointer = save_input_line_pointer;
1850           switch (exp_seg)
1851             {
1852             case SEG_ABSENT:
1853               /* missing expr becomes absolute 0 */
1854               as_bad ("missing or invalid displacement '%s' taken as 0",
1855                       operand_string);
1856               i.types[this_operand] |= (Disp | Abs);
1857               exp->X_seg = SEG_ABSOLUTE;
1858               exp->X_add_number = 0;
1859               exp->X_add_symbol = (symbolS *) 0;
1860               exp->X_subtract_symbol = (symbolS *) 0;
1861               break;
1862             case SEG_ABSOLUTE:
1863               i.types[this_operand] |= SMALLEST_DISP_TYPE (exp->X_add_number);
1864               break;
1865             case SEG_TEXT:
1866             case SEG_DATA:
1867             case SEG_BSS:
1868             case SEG_UNKNOWN:   /* must be 32 bit displacement (i.e. address) */
1869               i.types[this_operand] |= Disp32;
1870               break;
1871             default:
1872               goto seg_unimplemented;
1873             }
1874         }
1875
1876       /* Make sure the memory operand we've been dealt is valid. */
1877       if (i.base_reg && i.index_reg &&
1878           !(i.base_reg->reg_type & i.index_reg->reg_type & Reg))
1879         {
1880           as_bad ("register size mismatch in (base,index,scale) expression");
1881           return 0;
1882         }
1883       /*
1884                  * special case for (%dx) while doing input/output op
1885                  */
1886       if ((i.base_reg &&
1887            (i.base_reg->reg_type == (Reg16 | InOutPortReg)) &&
1888            (i.index_reg == 0)))
1889         return 1;
1890       if ((i.base_reg && (i.base_reg->reg_type & Reg32) == 0) ||
1891           (i.index_reg && (i.index_reg->reg_type & Reg32) == 0))
1892         {
1893           as_bad ("base/index register must be 32 bit register");
1894           return 0;
1895         }
1896       if (i.index_reg && i.index_reg == esp)
1897         {
1898           as_bad ("%s may not be used as an index register", esp->reg_name);
1899           return 0;
1900         }
1901     }
1902   else
1903     {                           /* it's not a memory operand; argh! */
1904       as_bad ("invalid char %s begining %s operand '%s'",
1905               output_invalid (*op_string), ordinal_names[this_operand],
1906               op_string);
1907       return 0;
1908     }
1909   return 1;                     /* normal return */
1910 }
1911 \f
1912 /*
1913  *                      md_estimate_size_before_relax()
1914  *
1915  * Called just before relax().
1916  * Any symbol that is now undefined will not become defined.
1917  * Return the correct fr_subtype in the frag.
1918  * Return the initial "guess for fr_var" to caller.
1919  * The guess for fr_var is ACTUALLY the growth beyond fr_fix.
1920  * Whatever we do to grow fr_fix or fr_var contributes to our returned value.
1921  * Although it may not be explicit in the frag, pretend fr_var starts with a
1922  * 0 value.
1923  */
1924 int
1925 md_estimate_size_before_relax (fragP, segment)
1926      register fragS *fragP;
1927      register segT segment;
1928 {
1929   register unsigned char *opcode;
1930   register int old_fr_fix;
1931
1932   old_fr_fix = fragP->fr_fix;
1933   opcode = (unsigned char *) fragP->fr_opcode;
1934   /* We've already got fragP->fr_subtype right;  all we have to do is check
1935            for un-relaxable symbols. */
1936   if (S_GET_SEGMENT (fragP->fr_symbol) != segment)
1937     {
1938       /* symbol is undefined in this segment */
1939       switch (opcode[0])
1940         {
1941         case JUMP_PC_RELATIVE:  /* make jmp (0xeb) a dword displacement jump */
1942           opcode[0] = 0xe9;     /* dword disp jmp */
1943           fragP->fr_fix += 4;
1944           fix_new (fragP, old_fr_fix, 4,
1945                    fragP->fr_symbol,
1946                    (symbolS *) 0,
1947                    fragP->fr_offset, 1, NO_RELOC);
1948           break;
1949
1950         default:
1951           /* This changes the byte-displacement jump 0x7N -->
1952                            the dword-displacement jump 0x0f8N */
1953           opcode[1] = opcode[0] + 0x10;
1954           opcode[0] = TWO_BYTE_OPCODE_ESCAPE;   /* two-byte escape */
1955           fragP->fr_fix += 1 + 4;       /* we've added an opcode byte */
1956           fix_new (fragP, old_fr_fix + 1, 4,
1957                    fragP->fr_symbol,
1958                    (symbolS *) 0,
1959                    fragP->fr_offset, 1, NO_RELOC);
1960           break;
1961         }
1962       frag_wane (fragP);
1963     }
1964   return (fragP->fr_var + fragP->fr_fix - old_fr_fix);
1965 }                               /* md_estimate_size_before_relax() */
1966 \f
1967 /*
1968  *                      md_convert_frag();
1969  *
1970  * Called after relax() is finished.
1971  * In:  Address of frag.
1972  *      fr_type == rs_machine_dependent.
1973  *      fr_subtype is what the address relaxed to.
1974  *
1975  * Out: Any fixSs and constants are set up.
1976  *      Caller will turn frag into a ".space 0".
1977  */
1978 void
1979 md_convert_frag (headers, fragP)
1980      object_headers *headers;
1981      register fragS *fragP;
1982 {
1983   register unsigned char *opcode;
1984   unsigned char *where_to_put_displacement = NULL;
1985   unsigned int target_address;
1986   unsigned int opcode_address;
1987   unsigned int extension = 0;
1988   int displacement_from_opcode_start;
1989
1990   opcode = (unsigned char *) fragP->fr_opcode;
1991
1992   /* Address we want to reach in file space. */
1993   target_address = S_GET_VALUE (fragP->fr_symbol) + fragP->fr_offset;
1994
1995   /* Address opcode resides at in file space. */
1996   opcode_address = fragP->fr_address + fragP->fr_fix;
1997
1998   /* Displacement from opcode start to fill into instruction. */
1999   displacement_from_opcode_start = target_address - opcode_address;
2000
2001   switch (fragP->fr_subtype)
2002     {
2003     case ENCODE_RELAX_STATE (COND_JUMP, BYTE):
2004     case ENCODE_RELAX_STATE (UNCOND_JUMP, BYTE):
2005       /* don't have to change opcode */
2006       extension = 1;            /* 1 opcode + 1 displacement */
2007       where_to_put_displacement = &opcode[1];
2008       break;
2009
2010     case ENCODE_RELAX_STATE (COND_JUMP, WORD):
2011       opcode[1] = TWO_BYTE_OPCODE_ESCAPE;
2012       opcode[2] = opcode[0] + 0x10;
2013       opcode[0] = WORD_PREFIX_OPCODE;
2014       extension = 4;            /* 3 opcode + 2 displacement */
2015       where_to_put_displacement = &opcode[3];
2016       break;
2017
2018     case ENCODE_RELAX_STATE (UNCOND_JUMP, WORD):
2019       opcode[1] = 0xe9;
2020       opcode[0] = WORD_PREFIX_OPCODE;
2021       extension = 3;            /* 2 opcode + 2 displacement */
2022       where_to_put_displacement = &opcode[2];
2023       break;
2024
2025     case ENCODE_RELAX_STATE (COND_JUMP, DWORD):
2026       opcode[1] = opcode[0] + 0x10;
2027       opcode[0] = TWO_BYTE_OPCODE_ESCAPE;
2028       extension = 5;            /* 2 opcode + 4 displacement */
2029       where_to_put_displacement = &opcode[2];
2030       break;
2031
2032     case ENCODE_RELAX_STATE (UNCOND_JUMP, DWORD):
2033       opcode[0] = 0xe9;
2034       extension = 4;            /* 1 opcode + 4 displacement */
2035       where_to_put_displacement = &opcode[1];
2036       break;
2037
2038     default:
2039       BAD_CASE (fragP->fr_subtype);
2040       break;
2041     }
2042   /* now put displacement after opcode */
2043   md_number_to_chars ((char *) where_to_put_displacement,
2044                       displacement_from_opcode_start - extension,
2045                       SIZE_FROM_RELAX_STATE (fragP->fr_subtype));
2046   fragP->fr_fix += extension;
2047 }
2048 \f
2049
2050 int md_short_jump_size = 2;     /* size of byte displacement jmp */
2051 int md_long_jump_size = 5;      /* size of dword displacement jmp */
2052 int md_reloc_size = 8;          /* Size of relocation record */
2053
2054 void
2055 md_create_short_jump (ptr, from_addr, to_addr, frag, to_symbol)
2056      char *ptr;
2057      long from_addr, to_addr;
2058      fragS *frag;
2059      symbolS *to_symbol;
2060 {
2061   long offset;
2062
2063   offset = to_addr - (from_addr + 2);
2064   md_number_to_chars (ptr, (long) 0xeb, 1);     /* opcode for byte-disp jump */
2065   md_number_to_chars (ptr + 1, offset, 1);
2066 }
2067
2068 void
2069 md_create_long_jump (ptr, from_addr, to_addr, frag, to_symbol)
2070      char *ptr;
2071      long from_addr, to_addr;
2072      fragS *frag;
2073      symbolS *to_symbol;
2074 {
2075   long offset;
2076
2077   if (flagseen['m'])
2078     {
2079       offset = to_addr - S_GET_VALUE (to_symbol);
2080       md_number_to_chars (ptr, 0xe9, 1);        /* opcode for long jmp */
2081       md_number_to_chars (ptr + 1, offset, 4);
2082       fix_new (frag, (ptr + 1) - frag->fr_literal, 4,
2083                to_symbol, (symbolS *) 0, (long) 0, 0, NO_RELOC);
2084     }
2085   else
2086     {
2087       offset = to_addr - (from_addr + 5);
2088       md_number_to_chars (ptr, (long) 0xe9, 1);
2089       md_number_to_chars (ptr + 1, offset, 4);
2090     }
2091 }
2092 \f
2093 int
2094 md_parse_option (argP, cntP, vecP)
2095      char **argP;
2096      int *cntP;
2097      char ***vecP;
2098 {
2099   return 1;
2100 }
2101 \f
2102 void                            /* Knows about order of bytes in address. */
2103 md_number_to_chars (con, value, nbytes)
2104      char con[];                /* Return 'nbytes' of chars here. */
2105      long value;                /* The value of the bits. */
2106      int nbytes;                /* Number of bytes in the output. */
2107 {
2108   register char *p = con;
2109
2110   switch (nbytes)
2111     {
2112     case 1:
2113       p[0] = value & 0xff;
2114       break;
2115     case 2:
2116       p[0] = value & 0xff;
2117       p[1] = (value >> 8) & 0xff;
2118       break;
2119     case 4:
2120       p[0] = value & 0xff;
2121       p[1] = (value >> 8) & 0xff;
2122       p[2] = (value >> 16) & 0xff;
2123       p[3] = (value >> 24) & 0xff;
2124       break;
2125     default:
2126       BAD_CASE (nbytes);
2127     }
2128 }
2129
2130
2131 /* Apply a fixup (fixS) to segment data, once it has been determined
2132    by our caller that we have all the info we need to fix it up.
2133
2134    On the 386, immediates, displacements, and data pointers are all in
2135    the same (little-endian) format, so we don't need to care about which
2136    we are handling.  */
2137
2138 void
2139 md_apply_fix (fixP, value)
2140      fixS *fixP;                /* The fix we're to put in */
2141      long value;                /* The value of the bits. */
2142 {
2143   register char *p = fixP->fx_where + fixP->fx_frag->fr_literal;
2144
2145   switch (fixP->fx_size)
2146     {
2147     case 1:
2148       *p = value;
2149       break;
2150     case 2:
2151       *p++ = value;
2152       *p = (value >> 8);
2153       break;
2154     case 4:
2155       *p++ = value;
2156       *p++ = (value >> 8);
2157       *p++ = (value >> 16);
2158       *p = (value >> 24);
2159       break;
2160     default:
2161       BAD_CASE (fixP->fx_size);
2162     }
2163 }
2164
2165 long                            /* Knows about the byte order in a word. */
2166 md_chars_to_number (con, nbytes)
2167      unsigned char con[];       /* Low order byte 1st. */
2168      int nbytes;                /* Number of bytes in the input. */
2169 {
2170   long retval;
2171   for (retval = 0, con += nbytes - 1; nbytes--; con--)
2172     {
2173       retval <<= BITS_PER_CHAR;
2174       retval |= *con;
2175     }
2176   return retval;
2177 }
2178
2179 /* Not needed for coff since relocation structure does not
2180    contain bitfields. */
2181 #if defined(OBJ_AOUT) | defined(OBJ_BOUT)
2182 #ifdef comment
2183 /* Output relocation information in the target's format.  */
2184 void
2185 md_ri_to_chars (the_bytes, ri)
2186      char *the_bytes;
2187      struct reloc_info_generic *ri;
2188 {
2189   /* this is easy */
2190   md_number_to_chars (the_bytes, ri->r_address, 4);
2191   /* now the fun stuff */
2192   the_bytes[6] = (ri->r_symbolnum >> 16) & 0x0ff;
2193   the_bytes[5] = (ri->r_symbolnum >> 8) & 0x0ff;
2194   the_bytes[4] = ri->r_symbolnum & 0x0ff;
2195   the_bytes[7] = (((ri->r_extern << 3) & 0x08) | ((ri->r_length << 1) & 0x06) |
2196                   ((ri->r_pcrel << 0) & 0x01)) & 0x0F;
2197 }
2198
2199 #endif /* comment */
2200
2201 void
2202 tc_aout_fix_to_chars (where, fixP, segment_address_in_file)
2203      char *where;
2204      fixS *fixP;
2205      relax_addressT segment_address_in_file;
2206 {
2207   /*
2208          * In: length of relocation (or of address) in chars: 1, 2 or 4.
2209          * Out: GNU LD relocation length code: 0, 1, or 2.
2210          */
2211
2212   static unsigned char nbytes_r_length[] =
2213   {42, 0, 1, 42, 2};
2214   long r_symbolnum;
2215
2216   know (fixP->fx_addsy != NULL);
2217
2218   md_number_to_chars (where,
2219        fixP->fx_frag->fr_address + fixP->fx_where - segment_address_in_file,
2220                       4);
2221
2222   r_symbolnum = (S_IS_DEFINED (fixP->fx_addsy)
2223                  ? S_GET_TYPE (fixP->fx_addsy)
2224                  : fixP->fx_addsy->sy_number);
2225
2226   where[6] = (r_symbolnum >> 16) & 0x0ff;
2227   where[5] = (r_symbolnum >> 8) & 0x0ff;
2228   where[4] = r_symbolnum & 0x0ff;
2229   where[7] = ((((!S_IS_DEFINED (fixP->fx_addsy)) << 3) & 0x08)
2230               | ((nbytes_r_length[fixP->fx_size] << 1) & 0x06)
2231               | (((fixP->fx_pcrel << 0) & 0x01) & 0x0f));
2232
2233   return;
2234 }                               /* tc_aout_fix_to_chars() */
2235
2236 #endif /* OBJ_AOUT or OBJ_BOUT */
2237 \f
2238
2239 #define MAX_LITTLENUMS 6
2240
2241 /* Turn the string pointed to by litP into a floating point constant of type
2242    type, and emit the appropriate bytes.  The number of LITTLENUMS emitted
2243    is stored in *sizeP .  An error message is returned, or NULL on OK.
2244    */
2245 char *
2246 md_atof (type, litP, sizeP)
2247      char type;
2248      char *litP;
2249      int *sizeP;
2250 {
2251   int prec;
2252   LITTLENUM_TYPE words[MAX_LITTLENUMS];
2253   LITTLENUM_TYPE *wordP;
2254   char *t;
2255
2256   switch (type)
2257     {
2258     case 'f':
2259     case 'F':
2260       prec = 2;
2261       break;
2262
2263     case 'd':
2264     case 'D':
2265       prec = 4;
2266       break;
2267
2268     case 'x':
2269     case 'X':
2270       prec = 5;
2271       break;
2272
2273     default:
2274       *sizeP = 0;
2275       return "Bad call to md_atof ()";
2276     }
2277   t = atof_ieee (input_line_pointer, type, words);
2278   if (t)
2279     input_line_pointer = t;
2280
2281   *sizeP = prec * sizeof (LITTLENUM_TYPE);
2282   /* this loops outputs the LITTLENUMs in REVERSE order; in accord with
2283            the bigendian 386 */
2284   for (wordP = words + prec - 1; prec--;)
2285     {
2286       md_number_to_chars (litP, (long) (*wordP--), sizeof (LITTLENUM_TYPE));
2287       litP += sizeof (LITTLENUM_TYPE);
2288     }
2289   return "";                    /* Someone should teach Dean about null pointers */
2290 }
2291 \f
2292 char output_invalid_buf[8];
2293
2294 static char *
2295 output_invalid (c)
2296      char c;
2297 {
2298   if (isprint (c))
2299     sprintf (output_invalid_buf, "'%c'", c);
2300   else
2301     sprintf (output_invalid_buf, "(0x%x)", (unsigned) c);
2302   return output_invalid_buf;
2303 }
2304
2305 static reg_entry *
2306 parse_register (reg_string)
2307      char *reg_string;          /* reg_string starts *before* REGISTER_PREFIX */
2308 {
2309   register char *s = reg_string;
2310   register char *p;
2311   char reg_name_given[MAX_REG_NAME_SIZE];
2312
2313   s++;                          /* skip REGISTER_PREFIX */
2314   for (p = reg_name_given; is_register_char (*s); p++, s++)
2315     {
2316       *p = register_chars[*s];
2317       if (p >= reg_name_given + MAX_REG_NAME_SIZE)
2318         return (reg_entry *) 0;
2319     }
2320   *p = '\0';
2321   return (reg_entry *) hash_find (reg_hash, reg_name_given);
2322 }
2323
2324
2325 /* We have no need to default values of symbols.  */
2326
2327 /* ARGSUSED */
2328 symbolS *
2329 md_undefined_symbol (name)
2330      char *name;
2331 {
2332   return 0;
2333 }
2334
2335 /* Parse an operand that is machine-specific.
2336    We just return without modifying the expression if we have nothing
2337    to do.  */
2338
2339 /* ARGSUSED */
2340 void
2341 md_operand (expressionP)
2342      expressionS *expressionP;
2343 {
2344 }
2345
2346 /* Round up a section size to the appropriate boundary.  */
2347 long
2348 md_section_align (segment, size)
2349      segT segment;
2350      long size;
2351 {
2352   return size;                  /* Byte alignment is fine */
2353 }
2354
2355 /* Exactly what point is a PC-relative offset relative TO?
2356    On the i386, they're relative to the address of the offset, plus
2357    its size. (??? Is this right?  FIXME-SOON!) */
2358 long
2359 md_pcrel_from (fixP)
2360      fixS *fixP;
2361 {
2362   return fixP->fx_size + fixP->fx_where + fixP->fx_frag->fr_address;
2363 }
2364
2365 /* these were macros, but I don't trust macros that eval their
2366     arguments more than once.  Besides, gcc can static inline them.
2367     xoxorich.  */
2368
2369 static unsigned long
2370 mode_from_disp_size (t)
2371      unsigned long t;
2372 {
2373   return ((t & (Disp8))
2374           ? 1
2375           : ((t & (Disp32)) ? 2 : 0));
2376 }                               /* mode_from_disp_size() */
2377
2378 /* convert opcode suffix ('b' 'w' 'l' typically) into type specifyer */
2379
2380 static unsigned long
2381 opcode_suffix_to_type (s)
2382      unsigned long s;
2383 {
2384   return (s == BYTE_OPCODE_SUFFIX
2385           ? Byte : (s == WORD_OPCODE_SUFFIX
2386                     ? Word : DWord));
2387 }                               /* opcode_suffix_to_type() */
2388
2389 static int
2390 fits_in_signed_byte (num)
2391      long num;
2392 {
2393   return ((num >= -128) && (num <= 127));
2394 }                               /* fits_in_signed_byte() */
2395
2396 static int
2397 fits_in_unsigned_byte (num)
2398      long num;
2399 {
2400   return ((num & 0xff) == num);
2401 }                               /* fits_in_unsigned_byte() */
2402
2403 static int
2404 fits_in_unsigned_word (num)
2405      long num;
2406 {
2407   return ((num & 0xffff) == num);
2408 }                               /* fits_in_unsigned_word() */
2409
2410 static int
2411 fits_in_signed_word (num)
2412      long num;
2413 {
2414   return ((-32768 <= num) && (num <= 32767));
2415 }                               /* fits_in_signed_word() */
2416
2417 static int
2418 smallest_imm_type (num)
2419      long num;
2420 {
2421   return ((num == 1)
2422           ? (Imm1 | Imm8 | Imm8S | Imm16 | Imm32)
2423           : (fits_in_signed_byte (num)
2424              ? (Imm8S | Imm8 | Imm16 | Imm32)
2425              : (fits_in_unsigned_byte (num)
2426                 ? (Imm8 | Imm16 | Imm32)
2427                 : ((fits_in_signed_word (num) || fits_in_unsigned_word (num))
2428                    ? (Imm16 | Imm32)
2429                    : (Imm32)))));
2430 }                               /* smallest_imm_type() */
2431
2432 static void
2433 s_bss ()
2434 {
2435   register int temp;
2436
2437   temp = get_absolute_expression ();
2438   subseg_new (SEG_BSS, (subsegT) temp);
2439   demand_empty_rest_of_line ();
2440 }
2441
2442
2443 #ifdef I386COFF
2444
2445 short
2446 tc_coff_fix2rtype (fixP)
2447      fixS *fixP;
2448 {
2449   return (fixP->fx_pcrel ?
2450           (fixP->fx_size == 1 ? R_PCRBYTE :
2451            fixP->fx_size == 2 ? R_PCRWORD :
2452            R_PCRLONG) :
2453           (fixP->fx_size == 1 ? R_RELBYTE :
2454            fixP->fx_size == 2 ? R_RELWORD :
2455            R_DIR32));
2456
2457
2458 }
2459
2460 #endif
2461
2462 /* end of tc-i386.c */
This page took 0.162265 seconds and 4 git commands to generate.