1 /* i386.c -- Assemble code for the Intel 80386
2 Copyright (C) 1989, 1991, 1992 Free Software Foundation.
4 This file is part of GAS, the GNU Assembler.
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)
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.
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. */
21 Intel 80386 machine specific gas.
23 Bugs & suggestions are completely welcome. This is free software.
24 Please help us make it better.
30 #include "opcode/i386.h"
32 /* 'md_assemble ()' gathers together information and puts it into a
36 /* TM holds the template for the insn were currently assembling. */
38 /* SUFFIX holds the opcode suffix (e.g. 'l' for 'movl') if given. */
40 /* Operands are coded with OPERANDS, TYPES, DISPS, IMMS, and REGS. */
42 /* OPERANDS gives the number of given operands. */
43 unsigned int operands;
45 /* REG_OPERANDS, DISP_OPERANDS, MEM_OPERANDS, IMM_OPERANDS give the number of
46 given register, displacement, memory operands and immediate operands. */
47 unsigned int reg_operands, disp_operands, mem_operands, imm_operands;
49 /* TYPES [i] is the type (see above #defines) which tells us how to
50 search through DISPS [i] & IMMS [i] & REGS [i] for the required
52 unsigned int types[MAX_OPERANDS];
54 /* Displacements (if given) for each operand. */
55 expressionS *disps[MAX_OPERANDS];
57 /* Immediate operands (if given) for each operand. */
58 expressionS *imms[MAX_OPERANDS];
60 /* Register operands (if given) for each operand. */
61 reg_entry *regs[MAX_OPERANDS];
63 /* BASE_REG, INDEX_REG, and LOG2_SCALE_FACTOR are used to encode
64 the base index byte below. */
67 unsigned int log2_scale_factor;
69 /* SEG gives the seg_entry of this insn. It is equal to zero unless
70 an explicit segment override is given. */
71 const seg_entry *seg; /* segment for memory operands (if given) */
73 /* PREFIX holds all the given prefix opcodes (usually null).
74 PREFIXES is the size of PREFIX. */
75 /* richfix: really unsigned? */
76 unsigned char prefix[MAX_PREFIXES];
77 unsigned int prefixes;
79 /* RM and IB are the modrm byte and the base index byte where the addressing
80 modes of this insn are encoded. */
86 /* This array holds the chars that always start a comment. If the
87 pre-processor is disabled, these aren't very useful */
88 const char comment_chars[] = "#";
90 /* This array holds the chars that only start a comment at the beginning of
91 a line. If the line seems to have the form '# 123 filename'
92 .line and .file directives will appear in the pre-processed output */
93 /* Note that input_file.c hand checks for '#' at the beginning of the
94 first line of the input file. This is because the compiler outputs
95 #NO_APP at the beginning of its output. */
96 /* Also note that comments started like this one will always work if
97 '/' isn't otherwise defined. */
98 const char line_comment_chars[] = "/"; /* removed '#' xoxorich. */
100 /* Chars that can be used to separate mant from exp in floating point nums */
101 const char EXP_CHARS[] = "eE";
103 /* Chars that mean this number is a floating point constant */
106 const char FLT_CHARS[] = "fFdDxX";
108 /* tables for lexical analysis */
109 static char opcode_chars[256];
110 static char register_chars[256];
111 static char operand_chars[256];
112 static char space_chars[256];
113 static char identifier_chars[256];
114 static char digit_chars[256];
117 #define is_opcode_char(x) (opcode_chars[(unsigned char) x])
118 #define is_operand_char(x) (operand_chars[(unsigned char) x])
119 #define is_register_char(x) (register_chars[(unsigned char) x])
120 #define is_space_char(x) (space_chars[(unsigned char) x])
121 #define is_identifier_char(x) (identifier_chars[(unsigned char) x])
122 #define is_digit_char(x) (digit_chars[(unsigned char) x])
124 /* put here all non-digit non-letter charcters that may occur in an operand */
125 static char operand_special_chars[] = "%$-+(,)*._~/<>|&^!:";
127 static char *ordinal_names[] = { "first", "second", "third" }; /* for printfs */
129 /* md_assemble() always leaves the strings it's passed unaltered. To
130 effect this we maintain a stack of saved characters that we've smashed
131 with '\0's (indicating end of strings for various sub-fields of the
132 assembler instruction). */
133 static char save_stack[32];
134 static char *save_stack_p; /* stack pointer */
135 #define END_STRING_AND_SAVE(s) *save_stack_p++ = *s; *s = '\0'
136 #define RESTORE_END_STRING(s) *s = *--save_stack_p
138 /* The instruction we're assembling. */
141 /* Per instruction expressionS buffers: 2 displacements & 2 immediate max. */
142 static expressionS disp_expressions[2], im_expressions[2];
144 /* pointers to ebp & esp entries in reg_hash hash table */
145 static reg_entry *ebp, *esp;
147 static int this_operand; /* current operand we are working on */
150 Interface to relax_segment.
151 There are 2 relax states for 386 jump insns: one for conditional & one
152 for unconditional jumps. This is because the these two types of jumps
153 add different sizes to frags when we're figuring out what sort of jump
154 to choose to reach a given label. */
157 #define COND_JUMP 1 /* conditional jump */
158 #define UNCOND_JUMP 2 /* unconditional jump */
163 #define UNKNOWN_SIZE 3
165 #define ENCODE_RELAX_STATE(type,size) ((type<<2) | (size))
166 #define SIZE_FROM_RELAX_STATE(s) \
167 ( (((s) & 0x3) == BYTE ? 1 : (((s) & 0x3) == WORD ? 2 : 4)) )
169 const relax_typeS md_relax_table[] = {
172 1) most positive reach of this state,
173 2) most negative reach of this state,
174 3) how many bytes this mode will add to the size of the current frag
175 4) which index into the table to try if we can't fit into this one.
182 /* For now we don't use word displacement jumps: they may be
184 {127+1, -128+1, 0, ENCODE_RELAX_STATE(COND_JUMP,DWORD) },
185 /* word conditionals add 3 bytes to frag:
186 2 opcode prefix; 1 displacement bytes */
187 {32767+2, -32768+2, 3, ENCODE_RELAX_STATE(COND_JUMP,DWORD) },
188 /* dword conditionals adds 4 bytes to frag:
189 1 opcode prefix; 3 displacement bytes */
193 {127+1, -128+1, 0, ENCODE_RELAX_STATE(UNCOND_JUMP,DWORD) },
194 /* word jmp adds 2 bytes to frag:
195 1 opcode prefix; 1 displacement bytes */
196 {32767+2, -32768+2, 2, ENCODE_RELAX_STATE(UNCOND_JUMP,DWORD) },
197 /* dword jmp adds 3 bytes to frag:
198 0 opcode prefix; 3 displacement bytes */
206 static char *output_invalid(int c);
207 static int fits_in_signed_byte(long num);
208 static int fits_in_signed_word(long num);
209 static int fits_in_unsigned_byte(long num);
210 static int fits_in_unsigned_word(long num);
211 static int i386_operand(char *operand_string);
212 static int smallest_imm_type(long num);
213 static reg_entry *parse_register(char *reg_string);
214 static unsigned long mode_from_disp_size(unsigned long t);
215 static unsigned long opcode_suffix_to_type(unsigned long s);
217 #else /* not __STDC__ */
219 static char *output_invalid();
220 static int fits_in_signed_byte();
221 static int fits_in_signed_word();
222 static int fits_in_unsigned_byte();
223 static int fits_in_unsigned_word();
224 static int i386_operand();
225 static int smallest_imm_type();
226 static reg_entry *parse_register();
227 static unsigned long mode_from_disp_size();
228 static unsigned long opcode_suffix_to_type();
230 #endif /* not __STDC__ */
233 /* Ignore certain directives generated by gcc. This probably should
237 while (*input_line_pointer && *input_line_pointer != '\n')
238 input_line_pointer++;
241 const pseudo_typeS md_pseudo_table[] = {
242 { "align", s_align_bytes, 0 },
243 { "ffloat", float_cons, 'f' },
244 { "dfloat", float_cons, 'd' },
245 { "tfloat", float_cons, 'x' },
246 { "value", cons, 2 },
250 /* for interface with expression () */
251 extern char * input_line_pointer;
253 /* obstack for constructing various things in md_begin */
256 /* hash table for opcode lookup */
257 static struct hash_control *op_hash = (struct hash_control *) 0;
258 /* hash table for register lookup */
259 static struct hash_control *reg_hash = (struct hash_control *) 0;
260 /* hash table for prefix lookup */
261 static struct hash_control *prefix_hash = (struct hash_control *) 0;
268 obstack_begin (&o,4096);
270 /* initialize op_hash hash table */
271 op_hash = hash_new(); /* xmalloc handles error */
274 register const template *optab;
275 register templates *core_optab;
278 optab = i386_optab; /* setup for loop */
279 prev_name = optab->name;
280 obstack_grow (&o, optab, sizeof(template));
281 core_optab = (templates *) xmalloc (sizeof (templates));
283 for (optab++; optab < i386_optab_end; optab++) {
284 if (! strcmp (optab->name, prev_name)) {
285 /* same name as before --> append to current template list */
286 obstack_grow (&o, optab, sizeof(template));
288 /* different name --> ship out current template list;
289 add to hash table; & begin anew */
290 /* Note: end must be set before start! since obstack_next_free changes
291 upon opstack_finish */
292 core_optab->end = (template *) obstack_next_free(&o);
293 core_optab->start = (template *) obstack_finish(&o);
294 hash_err = hash_insert (op_hash, prev_name, (char *) core_optab);
295 if (hash_err && *hash_err) {
297 as_fatal("Internal Error: Can't hash %s: %s", prev_name, hash_err);
299 prev_name = optab->name;
300 core_optab = (templates *) xmalloc (sizeof(templates));
301 obstack_grow (&o, optab, sizeof(template));
306 /* initialize reg_hash hash table */
307 reg_hash = hash_new();
309 register const reg_entry *regtab;
311 for (regtab = i386_regtab; regtab < i386_regtab_end; regtab++) {
312 hash_err = hash_insert (reg_hash, regtab->reg_name, regtab);
313 if (hash_err && *hash_err) goto hash_error;
317 esp = (reg_entry *) hash_find (reg_hash, "esp");
318 ebp = (reg_entry *) hash_find (reg_hash, "ebp");
320 /* initialize reg_hash hash table */
321 prefix_hash = hash_new();
323 register const prefix_entry *prefixtab;
325 for (prefixtab = i386_prefixtab;
326 prefixtab < i386_prefixtab_end; prefixtab++) {
327 hash_err = hash_insert (prefix_hash, prefixtab->prefix_name, prefixtab);
328 if (hash_err && *hash_err) goto hash_error;
332 /* fill in lexical tables: opcode_chars, operand_chars, space_chars */
334 register unsigned int c;
336 memset(opcode_chars, '\0', sizeof(opcode_chars));
337 memset(operand_chars, '\0', sizeof(operand_chars));
338 memset(space_chars, '\0', sizeof(space_chars));
339 memset(identifier_chars, '\0', sizeof(identifier_chars));
340 memset(digit_chars, '\0', sizeof(digit_chars));
342 for (c = 0; c < 256; c++) {
343 if (islower(c) || isdigit(c)) {
345 register_chars[c] = c;
346 } else if (isupper(c)) {
347 opcode_chars[c] = tolower(c);
348 register_chars[c] = opcode_chars[c];
349 } else if (c == PREFIX_SEPERATOR) {
351 } else if (c == ')' || c == '(') {
352 register_chars[c] = c;
355 if (isupper(c) || islower(c) || isdigit(c))
356 operand_chars[c] = c;
357 else if (c && strchr(operand_special_chars, c))
358 operand_chars[c] = c;
360 if (isdigit(c) || c == '-') digit_chars[c] = c;
362 if (isalpha(c) || c == '_' || c == '.' || isdigit(c))
363 identifier_chars[c] = c;
365 if (c == ' ' || c == '\t') space_chars[c] = c;
370 void md_end() {} /* not much to do here. */
375 /* debugging routines for md_assemble */
376 /* static void pi (), pte (), pt (), pe (), ps (); */
378 static void pi (line, x)
382 register template *p;
385 fprintf (stdout, "%s: template ", line);
387 fprintf (stdout, " modrm: mode %x reg %x reg/mem %x",
388 x->rm.mode, x->rm.reg, x->rm.regmem);
389 fprintf (stdout, " base %x index %x scale %x\n",
390 x->bi.base, x->bi.index, x->bi.scale);
391 for (i = 0; i < x->operands; i++) {
392 fprintf (stdout, " #%d: ", i+1);
394 fprintf (stdout, "\n");
395 if (x->types[i] & Reg) fprintf (stdout, "%s\n", x->regs[i]->reg_name);
396 if (x->types[i] & Imm) pe (x->imms[i]);
397 if (x->types[i] & (Disp|Abs)) pe (x->disps[i]);
405 fprintf (stdout, " %d operands ", t->operands);
406 fprintf (stdout, "opcode %x ",
408 if (t->extension_opcode != None)
409 fprintf (stdout, "ext %x ", t->extension_opcode);
410 if (t->opcode_modifier&D)
411 fprintf (stdout, "D");
412 if (t->opcode_modifier&W)
413 fprintf (stdout, "W");
414 fprintf (stdout, "\n");
415 for (i = 0; i < t->operands; i++) {
416 fprintf (stdout, " #%d type ", i+1);
417 pt (t->operand_types[i]);
418 fprintf (stdout, "\n");
425 fprintf (stdout, " segment %s\n", segment_name (e->X_seg));
426 fprintf (stdout, " add_number %d (%x)\n",
427 e->X_add_number, e->X_add_number);
428 if (e->X_add_symbol) {
429 fprintf (stdout, " add_symbol ");
430 ps (e->X_add_symbol);
431 fprintf (stdout, "\n");
433 if (e->X_subtract_symbol) {
434 fprintf (stdout, " sub_symbol ");
435 ps (e->X_subtract_symbol);
436 fprintf (stdout, "\n");
443 fprintf (stdout, "%s type %s%s",
445 S_IS_EXTERNAL(s) ? "EXTERNAL " : "",
446 segment_name(S_GET_SEGMENT(s)));
453 { Reg8, "r8" }, { Reg16, "r16" }, { Reg32, "r32" }, { Imm8, "i8" },
455 { Imm16, "i16" }, { Imm32, "i32" }, { Mem8, "Mem8"}, { Mem16, "Mem16"},
456 { Mem32, "Mem32"}, { BaseIndex, "BaseIndex" },
457 { Abs8, "Abs8" }, { Abs16, "Abs16" }, { Abs32, "Abs32" },
458 { Disp8, "d8" }, { Disp16, "d16" },
459 { Disp32, "d32" }, { SReg2, "SReg2" }, { SReg3, "SReg3" }, { Acc, "Acc" },
460 { InOutPortReg, "InOutPortReg" }, { ShiftCount, "ShiftCount" },
461 { Imm1, "i1" }, { Control, "control reg" }, {Test, "test reg"},
462 { FloatReg, "FReg"}, {FloatAcc, "FAcc"},
463 { JumpAbsolute, "Jump Absolute"},
470 register struct type_name *ty;
473 fprintf (stdout, "Unknown");
475 for (ty = type_names; ty->mask; ty++)
476 if (t & ty->mask) fprintf (stdout, "%s, ", ty->tname);
481 #endif /* DEBUG386 */
484 This is the guts of the machine-dependent assembler. LINE points to a
485 machine dependent instruction. This funciton is supposed to emit
486 the frags/bytes it assembles to.
488 void md_assemble (line)
491 /* Holds temlate once we've found it. */
492 register template *t;
494 /* Possible templates for current insn */
495 templates *current_templates = (templates *) 0;
497 /* Initialize globals. */
498 memset(&i, '\0', sizeof(i));
499 memset(disp_expressions, '\0', sizeof(disp_expressions));
500 memset(im_expressions, '\0', sizeof(im_expressions));
501 save_stack_p = save_stack; /* reset stack pointer */
503 /* Fist parse an opcode & call i386_operand for the operands.
504 We assume that the scrubber has arranged it so that line[0] is the valid
505 start of a (possibly prefixed) opcode. */
507 register char *l = line; /* Fast place to put LINE. */
509 /* 1 if operand is pending after ','. */
510 unsigned int expecting_operand = 0;
511 /* 1 if we found a prefix only acceptable with string insns. */
512 unsigned int expecting_string_instruction = 0;
513 /* Non-zero if operand parens not balenced. */
514 unsigned int paren_not_balenced;
515 char * token_start = l;
517 while (! is_space_char(*l) && *l != END_OF_INSN) {
518 if (! is_opcode_char(*l)) {
519 as_bad("invalid character %s in opcode", output_invalid(*l));
521 } else if (*l != PREFIX_SEPERATOR) {
522 *l = opcode_chars[(unsigned char) *l]; /* fold case of opcodes */
524 } else { /* this opcode's got a prefix */
525 register unsigned int q;
526 register prefix_entry * prefix;
528 if (l == token_start) {
529 as_bad("expecting prefix; got nothing");
532 END_STRING_AND_SAVE (l);
533 prefix = (prefix_entry *) hash_find (prefix_hash, token_start);
535 as_bad("no such opcode prefix ('%s')", token_start);
538 RESTORE_END_STRING (l);
539 /* check for repeated prefix */
540 for (q = 0; q < i.prefixes; q++)
541 if (i.prefix[q] == prefix->prefix_code) {
542 as_bad("same prefix used twice; you don't really want this!");
545 if (i.prefixes == MAX_PREFIXES) {
546 as_bad("too many opcode prefixes");
549 i.prefix[i.prefixes++] = prefix->prefix_code;
550 if (prefix->prefix_code == REPE || prefix->prefix_code == REPNE)
551 expecting_string_instruction = 1;
552 /* skip past PREFIX_SEPERATOR and reset token_start */
556 END_STRING_AND_SAVE (l);
557 if (token_start == l) {
558 as_bad("expecting opcode; got nothing");
562 /* Lookup insn in hash; try intel & att naming conventions if appropriate;
563 that is: we only use the opcode suffix 'b' 'w' or 'l' if we need to. */
564 current_templates = (templates *) hash_find (op_hash, token_start);
565 if (! current_templates) {
566 int last_index = strlen(token_start) - 1;
567 char last_char = token_start[last_index];
569 case DWORD_OPCODE_SUFFIX:
570 case WORD_OPCODE_SUFFIX:
571 case BYTE_OPCODE_SUFFIX:
572 token_start[last_index] = '\0';
573 current_templates = (templates *) hash_find (op_hash, token_start);
574 token_start[last_index] = last_char;
575 i.suffix = last_char;
577 if (!current_templates) {
578 as_bad("no such 386 instruction: `%s'", token_start); return;
581 RESTORE_END_STRING (l);
583 /* check for rep/repne without a string instruction */
584 if (expecting_string_instruction &&
585 ! IS_STRING_INSTRUCTION (current_templates->
586 start->base_opcode)) {
587 as_bad("expecting string instruction after rep/repne");
591 /* There may be operands to parse. */
592 if (*l != END_OF_INSN &&
593 /* For string instructions, we ignore any operands if given. This
594 kludges, for example, 'rep/movsb %ds:(%esi), %es:(%edi)' where
595 the operands are always going to be the same, and are not really
596 encoded in machine code. */
597 ! IS_STRING_INSTRUCTION (current_templates->
598 start->base_opcode)) {
601 /* skip optional white space before operand */
602 while (! is_operand_char(*l) && *l != END_OF_INSN) {
603 if (! is_space_char(*l)) {
604 as_bad("invalid character %s before %s operand",
606 ordinal_names[i.operands]);
611 token_start = l; /* after white space */
612 paren_not_balenced = 0;
613 while (paren_not_balenced || *l != ',') {
614 if (*l == END_OF_INSN) {
615 if (paren_not_balenced) {
616 as_bad("unbalenced parenthesis in %s operand.",
617 ordinal_names[i.operands]);
619 } else break; /* we are done */
620 } else if (! is_operand_char(*l)) {
621 as_bad("invalid character %s in %s operand",
623 ordinal_names[i.operands]);
626 if (*l == '(') ++paren_not_balenced;
627 if (*l == ')') --paren_not_balenced;
630 if (l != token_start) { /* yes, we've read in another operand */
631 unsigned int operand_ok;
632 this_operand = i.operands++;
633 if (i.operands > MAX_OPERANDS) {
634 as_bad("spurious operands; (%d operands/instruction max)",
638 /* now parse operand adding info to 'i' as we go along */
639 END_STRING_AND_SAVE (l);
640 operand_ok = i386_operand (token_start);
641 RESTORE_END_STRING (l); /* restore old contents */
642 if (!operand_ok) return;
644 if (expecting_operand) {
645 expecting_operand_after_comma:
646 as_bad("expecting operand after ','; got nothing");
650 as_bad("expecting operand before ','; got nothing");
655 /* now *l must be either ',' or END_OF_INSN */
657 if (*++l == END_OF_INSN) { /* just skip it, if it's \n complain */
658 goto expecting_operand_after_comma;
660 expecting_operand = 1;
662 } while (*l != END_OF_INSN); /* until we get end of insn */
666 /* Now we've parsed the opcode into a set of templates, and have the
668 Next, we find a template that matches the given insn,
669 making sure the overlap of the given operands types is consistent
670 with the template operand types. */
672 #define MATCH(overlap,given_type) \
674 (overlap & (JumpAbsolute|BaseIndex|Mem8)) \
675 == (given_type & (JumpAbsolute|BaseIndex|Mem8)))
677 /* If m0 and m1 are register matches they must be consistent
678 with the expected operand types t0 and t1.
679 That is, if both m0 & m1 are register matches
680 i.e. ( ((m0 & (Reg)) && (m1 & (Reg)) ) ?
681 then, either 1. or 2. must be true:
682 1. the expected operand type register overlap is null:
685 the given register overlap is null:
687 2. the expected operand type register overlap == the given
688 operand type overlap: (t0 & t1 & m0 & m1 & Reg).
690 #define CONSISTENT_REGISTER_MATCH(m0, m1, t0, t1) \
691 ( ((m0 & (Reg)) && (m1 & (Reg))) ? \
692 ( ((t0 & t1 & (Reg)) == 0 && (m0 & m1 & (Reg)) == 0) || \
693 ((t0 & t1) & (m0 & m1) & (Reg)) \
696 register unsigned int overlap0, overlap1;
698 unsigned int overlap2;
699 unsigned int found_reverse_match;
701 overlap0 = overlap1 = overlap2 = found_reverse_match = 0;
702 for (t = current_templates->start;
703 t < current_templates->end;
706 /* must have right number of operands */
707 if (i.operands != t->operands) continue;
708 else if (!t->operands) break; /* 0 operands always matches */
710 overlap0 = i.types[0] & t->operand_types[0];
711 switch (t->operands) {
713 if (! MATCH (overlap0,i.types[0])) continue;
716 overlap1 = i.types[1] & t->operand_types[1];
717 if (! MATCH (overlap0,i.types[0]) ||
718 ! MATCH (overlap1,i.types[1]) ||
719 ! CONSISTENT_REGISTER_MATCH(overlap0, overlap1,
721 t->operand_types[1])) {
723 /* check if other direction is valid ... */
724 if (! (t->opcode_modifier & COMES_IN_BOTH_DIRECTIONS))
727 /* try reversing direction of operands */
728 overlap0 = i.types[0] & t->operand_types[1];
729 overlap1 = i.types[1] & t->operand_types[0];
730 if (! MATCH (overlap0,i.types[0]) ||
731 ! MATCH (overlap1,i.types[1]) ||
732 ! CONSISTENT_REGISTER_MATCH (overlap0, overlap1,
734 t->operand_types[1])) {
735 /* does not match either direction */
738 /* found a reverse match here -- slip through */
739 /* found_reverse_match holds which of D or FloatD we've found */
740 found_reverse_match = t->opcode_modifier & COMES_IN_BOTH_DIRECTIONS;
741 } /* endif: not forward match */
742 /* found either forward/reverse 2 operand match here */
743 if (t->operands == 3) {
744 overlap2 = i.types[2] & t->operand_types[2];
745 if (! MATCH (overlap2,i.types[2]) ||
746 ! CONSISTENT_REGISTER_MATCH (overlap0, overlap2,
748 t->operand_types[2]) ||
749 ! CONSISTENT_REGISTER_MATCH (overlap1, overlap2,
751 t->operand_types[2]))
754 /* found either forward/reverse 2 or 3 operand match here:
755 slip through to break */
757 break; /* we've found a match; break out of loop */
759 if (t == current_templates->end) { /* we found no match */
760 as_bad("operands given don't match any known 386 instruction");
764 /* Copy the template we found (we may change it!). */
765 memcpy(&i.tm, t, sizeof(template));
766 t = &i.tm; /* alter new copy of template */
768 /* If there's no opcode suffix we try to invent one based on register
770 if (! i.suffix && i.reg_operands) {
771 /* We take i.suffix from the LAST register operand specified. This
772 assumes that the last register operands is the destination register
775 for (o = 0; o < MAX_OPERANDS; o++)
776 if (i.types[o] & Reg) {
777 i.suffix = (i.types[o] == Reg8) ? BYTE_OPCODE_SUFFIX :
778 (i.types[o] == Reg16) ? WORD_OPCODE_SUFFIX :
783 /* Make still unresolved immediate matches conform to size of immediate
784 given in i.suffix. Note: overlap2 cannot be an immediate!
786 if ((overlap0 & (Imm8|Imm8S|Imm16|Imm32))
787 && overlap0 != Imm8 && overlap0 != Imm8S
788 && overlap0 != Imm16 && overlap0 != Imm32) {
790 as_bad("no opcode suffix given; can't determine immediate size");
793 overlap0 &= (i.suffix == BYTE_OPCODE_SUFFIX ? (Imm8|Imm8S) :
794 (i.suffix == WORD_OPCODE_SUFFIX ? Imm16 : Imm32));
796 if ((overlap1 & (Imm8|Imm8S|Imm16|Imm32))
797 && overlap1 != Imm8 && overlap1 != Imm8S
798 && overlap1 != Imm16 && overlap1 != Imm32) {
800 as_bad("no opcode suffix given; can't determine immediate size");
803 overlap1 &= (i.suffix == BYTE_OPCODE_SUFFIX ? (Imm8|Imm8S) :
804 (i.suffix == WORD_OPCODE_SUFFIX ? Imm16 : Imm32));
807 i.types[0] = overlap0;
808 i.types[1] = overlap1;
809 i.types[2] = overlap2;
811 if (overlap0 & ImplicitRegister) i.reg_operands--;
812 if (overlap1 & ImplicitRegister) i.reg_operands--;
813 if (overlap2 & ImplicitRegister) i.reg_operands--;
814 if (overlap0 & Imm1) i.imm_operands = 0; /* kludge for shift insns */
816 if (found_reverse_match) {
818 save = t->operand_types[0];
819 t->operand_types[0] = t->operand_types[1];
820 t->operand_types[1] = save;
823 /* Finalize opcode. First, we change the opcode based on the operand
824 size given by i.suffix: we never have to change things for byte insns,
825 or when no opcode suffix is need to size the operands. */
827 if (! i.suffix && (t->opcode_modifier & W)) {
828 as_bad("no opcode suffix given and no register operands; can't size instruction");
832 if (i.suffix && i.suffix != BYTE_OPCODE_SUFFIX) {
833 /* Select between byte and word/dword operations. */
834 if (t->opcode_modifier & W)
836 /* Now select between word & dword operations via the
837 operand size prefix. */
838 if (i.suffix == WORD_OPCODE_SUFFIX) {
839 if (i.prefixes == MAX_PREFIXES) {
840 as_bad("%d prefixes given and 'w' opcode suffix gives too many prefixes",
844 i.prefix[i.prefixes++] = WORD_PREFIX_OPCODE;
848 /* For insns with operands there are more diddles to do to the opcode. */
850 /* If we found a reverse match we must alter the opcode direction bit
851 found_reverse_match holds bit to set (different for int &
854 if (found_reverse_match) {
855 t->base_opcode |= found_reverse_match;
859 The imul $imm, %reg instruction is converted into
860 imul $imm, %reg, %reg. */
861 if (t->opcode_modifier & imulKludge) {
862 i.regs[2] = i.regs[1]; /* Pretend we saw the 3 operand case. */
866 /* Certain instructions expect the destination to be in the i.rm.reg
867 field. This is by far the exceptional case. For these instructions,
868 if the source operand is a register, we must reverse the i.rm.reg
869 and i.rm.regmem fields. We accomplish this by faking that the
870 two register operands were given in the reverse order. */
871 if ((t->opcode_modifier & ReverseRegRegmem) && i.reg_operands == 2) {
872 unsigned int first_reg_operand = (i.types[0] & Reg) ? 0 : 1;
873 unsigned int second_reg_operand = first_reg_operand + 1;
874 reg_entry *tmp = i.regs[first_reg_operand];
875 i.regs[first_reg_operand] = i.regs[second_reg_operand];
876 i.regs[second_reg_operand] = tmp;
879 if (t->opcode_modifier & ShortForm) {
880 /* The register or float register operand is in operand 0 or 1. */
881 unsigned int o = (i.types[0] & (Reg|FloatReg)) ? 0 : 1;
882 /* Register goes in low 3 bits of opcode. */
883 t->base_opcode |= i.regs[o]->reg_num;
884 } else if (t->opcode_modifier & ShortFormW) {
885 /* Short form with 0x8 width bit. Register is always dest. operand */
886 t->base_opcode |= i.regs[1]->reg_num;
887 if (i.suffix == WORD_OPCODE_SUFFIX ||
888 i.suffix == DWORD_OPCODE_SUFFIX)
889 t->base_opcode |= 0x8;
890 } else if (t->opcode_modifier & Seg2ShortForm) {
891 if (t->base_opcode == POP_SEG_SHORT && i.regs[0]->reg_num == 1) {
892 as_bad("you can't 'pop cs' on the 386.");
895 t->base_opcode |= (i.regs[0]->reg_num << 3);
896 } else if (t->opcode_modifier & Seg3ShortForm) {
897 /* 'push %fs' is 0x0fa0; 'pop %fs' is 0x0fa1.
898 'push %gs' is 0x0fa8; 'pop %fs' is 0x0fa9.
899 So, only if i.regs[0]->reg_num == 5 (%gs) do we need
900 to change the opcode. */
901 if (i.regs[0]->reg_num == 5)
902 t->base_opcode |= 0x08;
903 } else if (t->opcode_modifier & Modrm) {
904 /* The opcode is completed (modulo t->extension_opcode which must
905 be put into the modrm byte.
906 Now, we make the modrm & index base bytes based on all the info
909 /* i.reg_operands MUST be the number of real register operands;
910 implicit registers do not count. */
911 if (i.reg_operands == 2) {
912 unsigned int source, dest;
913 source = (i.types[0] & (Reg|SReg2|SReg3|Control|Debug|Test)) ? 0 : 1;
916 /* We must be careful to make sure that all segment/control/test/
917 debug registers go into the i.rm.reg field (despite the whether
918 they are source or destination operands). */
919 if (i.regs[dest]->reg_type & (SReg2|SReg3|Control|Debug|Test)) {
920 i.rm.reg = i.regs[dest]->reg_num;
921 i.rm.regmem = i.regs[source]->reg_num;
923 i.rm.reg = i.regs[source]->reg_num;
924 i.rm.regmem = i.regs[dest]->reg_num;
926 } else { /* if it's not 2 reg operands... */
927 if (i.mem_operands) {
928 unsigned int fake_zero_displacement = 0;
929 unsigned int o = (i.types[0] & Mem) ? 0 : ((i.types[1] & Mem) ? 1 : 2);
931 /* Encode memory operand into modrm byte and base index byte. */
933 if (i.base_reg == esp && ! i.index_reg) {
934 /* <disp>(%esp) becomes two byte modrm with no index register. */
935 i.rm.regmem = ESCAPE_TO_TWO_BYTE_ADDRESSING;
936 i.rm.mode = mode_from_disp_size(i.types[o]);
937 i.bi.base = ESP_REG_NUM;
938 i.bi.index = NO_INDEX_REGISTER;
939 i.bi.scale = 0; /* Must be zero! */
940 } else if (i.base_reg == ebp && !i.index_reg) {
941 if (! (i.types[o] & Disp)) {
942 /* Must fake a zero byte displacement.
943 There is no direct way to code '(%ebp)' directly. */
944 fake_zero_displacement = 1;
945 /* fake_zero_displacement code does not set this. */
948 i.rm.mode = mode_from_disp_size(i.types[o]);
949 i.rm.regmem = EBP_REG_NUM;
950 } else if (! i.base_reg && (i.types[o] & BaseIndex)) {
951 /* There are three cases here.
952 Case 1: '<32bit disp>(,1)' -- indirect absolute.
953 (Same as cases 2 & 3 with NO index register)
954 Case 2: <32bit disp> (,<index>) -- no base register with disp
955 Case 3: (, <index>) --- no base register;
956 no disp (must add 32bit 0 disp). */
957 i.rm.regmem = ESCAPE_TO_TWO_BYTE_ADDRESSING;
958 i.rm.mode = 0; /* 32bit mode */
959 i.bi.base = NO_BASE_REGISTER;
961 i.types[o] |= Disp32; /* Must be 32bit! */
962 if (i.index_reg) { /* case 2 or case 3 */
963 i.bi.index = i.index_reg->reg_num;
964 i.bi.scale = i.log2_scale_factor;
965 if (i.disp_operands == 0)
966 fake_zero_displacement = 1; /* case 3 */
968 i.bi.index = NO_INDEX_REGISTER;
971 } else if (i.disp_operands && !i.base_reg && !i.index_reg) {
972 /* Operand is just <32bit disp> */
973 i.rm.regmem = EBP_REG_NUM;
976 i.types[o] |= Disp32;
978 /* It's not a special case; rev'em up. */
979 i.rm.regmem = i.base_reg->reg_num;
980 i.rm.mode = mode_from_disp_size(i.types[o]);
982 i.rm.regmem = ESCAPE_TO_TWO_BYTE_ADDRESSING;
983 i.bi.base = i.base_reg->reg_num;
984 i.bi.index = i.index_reg->reg_num;
985 i.bi.scale = i.log2_scale_factor;
986 if (i.base_reg == ebp && i.disp_operands == 0) { /* pace */
987 fake_zero_displacement = 1;
989 i.rm.mode = mode_from_disp_size(i.types[o]);
993 if (fake_zero_displacement) {
994 /* Fakes a zero displacement assuming that i.types[o] holds
995 the correct displacement size. */
996 exp = &disp_expressions[i.disp_operands++];
998 exp->X_seg = SEG_ABSOLUTE;
999 exp->X_add_number = 0;
1000 exp->X_add_symbol = (symbolS *) 0;
1001 exp->X_subtract_symbol = (symbolS *) 0;
1004 /* Select the correct segment for the memory operand. */
1006 unsigned int seg_index;
1007 const seg_entry *default_seg;
1009 if (i.rm.regmem == ESCAPE_TO_TWO_BYTE_ADDRESSING) {
1010 seg_index = (i.rm.mode<<3) | i.bi.base;
1011 default_seg = two_byte_segment_defaults[seg_index];
1013 seg_index = (i.rm.mode<<3) | i.rm.regmem;
1014 default_seg = one_byte_segment_defaults[seg_index];
1016 /* If the specified segment is not the default, use an
1017 opcode prefix to select it */
1018 if (i.seg != default_seg) {
1019 if (i.prefixes == MAX_PREFIXES) {
1020 as_bad("%d prefixes given and %s segment override gives too many prefixes",
1021 MAX_PREFIXES, i.seg->seg_name);
1024 i.prefix[i.prefixes++] = i.seg->seg_prefix;
1029 /* Fill in i.rm.reg or i.rm.regmem field with register operand
1030 (if any) based on t->extension_opcode. Again, we must be careful
1031 to make sure that segment/control/debug/test registers are coded
1032 into the i.rm.reg field. */
1033 if (i.reg_operands) {
1035 (i.types[0] & (Reg|SReg2|SReg3|Control|Debug|Test)) ? 0 :
1036 (i.types[1] & (Reg|SReg2|SReg3|Control|Debug|Test)) ? 1 : 2;
1037 /* If there is an extension opcode to put here, the register number
1038 must be put into the regmem field. */
1039 if (t->extension_opcode != None)
1040 i.rm.regmem = i.regs[o]->reg_num;
1041 else i.rm.reg = i.regs[o]->reg_num;
1043 /* Now, if no memory operand has set i.rm.mode = 0, 1, 2
1044 we must set it to 3 to indicate this is a register operand
1045 int the regmem field */
1046 if (! i.mem_operands) i.rm.mode = 3;
1049 /* Fill in i.rm.reg field with extension opcode (if any). */
1050 if (t->extension_opcode != None)
1051 i.rm.reg = t->extension_opcode;
1057 /* Handle conversion of 'int $3' --> special int3 insn. */
1058 if (t->base_opcode == INT_OPCODE && i.imms[0]->X_add_number == 3) {
1059 t->base_opcode = INT3_OPCODE;
1063 /* We are ready to output the insn. */
1068 if (t->opcode_modifier & Jump) {
1069 int n = i.disps[0]->X_add_number;
1071 switch (i.disps[0]->X_seg) {
1073 if (fits_in_signed_byte(n)) {
1075 p[0] = t->base_opcode;
1077 #if 0 /* leave out 16 bit jumps - pace */
1078 } else if (fits_in_signed_word(n)) {
1080 p[0] = WORD_PREFIX_OPCODE;
1081 p[1] = t->base_opcode;
1082 md_number_to_chars (&p[2], n, 2);
1084 } else { /* It's an absolute dword displacement. */
1085 if (t->base_opcode == JUMP_PC_RELATIVE) { /* pace */
1086 /* unconditional jump */
1089 md_number_to_chars (&p[1], n, 4);
1091 /* conditional jump */
1093 p[0] = TWO_BYTE_OPCODE_ESCAPE;
1094 p[1] = t->base_opcode + 0x10;
1095 md_number_to_chars (&p[2], n, 4);
1100 /* It's a symbol; end frag & setup for relax.
1101 Make sure there are 6 chars left in the current frag; if not
1102 we'll have to start a new one. */
1103 /* I caught it failing with obstack_room == 6,
1104 so I changed to <= pace */
1105 if (obstack_room (&frags) <= 6) {
1106 frag_wane(frag_now);
1110 p[0] = t->base_opcode;
1111 frag_var (rs_machine_dependent,
1112 6, /* 2 opcode/prefix + 4 displacement */
1114 ((unsigned char) *p == JUMP_PC_RELATIVE
1115 ? ENCODE_RELAX_STATE (UNCOND_JUMP, BYTE)
1116 : ENCODE_RELAX_STATE (COND_JUMP, BYTE)),
1117 i.disps[0]->X_add_symbol,
1121 } else if (t->opcode_modifier & (JumpByte|JumpDword)) {
1122 int size = (t->opcode_modifier & JumpByte) ? 1 : 4;
1123 int n = i.disps[0]->X_add_number;
1125 if (fits_in_unsigned_byte(t->base_opcode)) {
1126 FRAG_APPEND_1_CHAR (t->base_opcode);
1128 p = frag_more (2); /* opcode can be at most two bytes */
1129 /* put out high byte first: can't use md_number_to_chars! */
1130 *p++ = (t->base_opcode >> 8) & 0xff;
1131 *p = t->base_opcode & 0xff;
1134 p = frag_more (size);
1135 switch (i.disps[0]->X_seg) {
1137 md_number_to_chars (p, n, size);
1138 if (size == 1 && ! fits_in_signed_byte(n)) {
1139 as_bad("loop/jecx only takes byte displacement; %d shortened to %d",
1144 fix_new (frag_now, p - frag_now->fr_literal, size,
1145 i.disps[0]->X_add_symbol, i.disps[0]->X_subtract_symbol,
1146 i.disps[0]->X_add_number, 1, NO_RELOC);
1149 } else if (t->opcode_modifier & JumpInterSegment) {
1150 p = frag_more (1 + 2 + 4); /* 1 opcode; 2 segment; 4 offset */
1151 p[0] = t->base_opcode;
1152 if (i.imms[1]->X_seg == SEG_ABSOLUTE)
1153 md_number_to_chars (p + 1, i.imms[1]->X_add_number, 4);
1155 fix_new (frag_now, p + 1 - frag_now->fr_literal, 4,
1156 i.imms[1]->X_add_symbol,
1157 i.imms[1]->X_subtract_symbol,
1158 i.imms[1]->X_add_number, 0, NO_RELOC);
1159 if (i.imms[0]->X_seg != SEG_ABSOLUTE)
1160 as_bad("can't handle non absolute segment in long call/jmp");
1161 md_number_to_chars (p + 5, i.imms[0]->X_add_number, 2);
1163 /* Output normal instructions here. */
1166 /* First the prefix bytes. */
1167 for (q = i.prefix; q < i.prefix + i.prefixes; q++) {
1169 md_number_to_chars (p, (unsigned int) *q, 1);
1172 /* Now the opcode; be careful about word order here! */
1173 if (fits_in_unsigned_byte(t->base_opcode)) {
1174 FRAG_APPEND_1_CHAR (t->base_opcode);
1175 } else if (fits_in_unsigned_word(t->base_opcode)) {
1177 /* put out high byte first: can't use md_number_to_chars! */
1178 *p++ = (t->base_opcode >> 8) & 0xff;
1179 *p = t->base_opcode & 0xff;
1180 } else { /* opcode is either 3 or 4 bytes */
1181 if (t->base_opcode & 0xff000000) {
1183 *p++ = (t->base_opcode >> 24) & 0xff;
1184 } else p = frag_more (3);
1185 *p++ = (t->base_opcode >> 16) & 0xff;
1186 *p++ = (t->base_opcode >> 8) & 0xff;
1187 *p = (t->base_opcode ) & 0xff;
1190 /* Now the modrm byte and base index byte (if present). */
1191 if (t->opcode_modifier & Modrm) {
1193 /* md_number_to_chars (p, i.rm, 1); */
1194 md_number_to_chars (p, (i.rm.regmem<<0 | i.rm.reg<<3 | i.rm.mode<<6), 1);
1195 /* If i.rm.regmem == ESP (4) && i.rm.mode != Mode 3 (Register mode)
1196 ==> need second modrm byte. */
1197 if (i.rm.regmem == ESCAPE_TO_TWO_BYTE_ADDRESSING && i.rm.mode != 3) {
1199 /* md_number_to_chars (p, i.bi, 1); */
1200 md_number_to_chars (p,(i.bi.base<<0 | i.bi.index<<3 | i.bi.scale<<6), 1);
1204 if (i.disp_operands) {
1205 register unsigned int n;
1207 for (n = 0; n < i.operands; n++) {
1209 if (i.disps[n]->X_seg == SEG_ABSOLUTE) {
1210 if (i.types[n] & (Disp8|Abs8)) {
1212 md_number_to_chars (p, i.disps[n]->X_add_number, 1);
1213 } else if (i.types[n] & (Disp16|Abs16)) {
1215 md_number_to_chars (p, i.disps[n]->X_add_number, 2);
1216 } else { /* Disp32|Abs32 */
1218 md_number_to_chars (p, i.disps[n]->X_add_number, 4);
1220 } else { /* not SEG_ABSOLUTE */
1221 /* need a 32-bit fixup (don't support 8bit non-absolute disps) */
1223 fix_new (frag_now, p - frag_now->fr_literal, 4,
1224 i.disps[n]->X_add_symbol, i.disps[n]->X_subtract_symbol,
1225 i.disps[n]->X_add_number, 0, NO_RELOC);
1229 } /* end displacement output */
1231 /* output immediate */
1232 if (i.imm_operands) {
1233 register unsigned int n;
1235 for (n = 0; n < i.operands; n++) {
1237 if (i.imms[n]->X_seg == SEG_ABSOLUTE) {
1238 if (i.types[n] & (Imm8|Imm8S)) {
1240 md_number_to_chars (p, i.imms[n]->X_add_number, 1);
1241 } else if (i.types[n] & Imm16) {
1243 md_number_to_chars (p, i.imms[n]->X_add_number, 2);
1246 md_number_to_chars (p, i.imms[n]->X_add_number, 4);
1248 } else { /* not SEG_ABSOLUTE */
1249 /* need a 32-bit fixup (don't support 8bit non-absolute ims) */
1250 /* try to support other sizes ... */
1252 if (i.types[n] & (Imm8|Imm8S))
1254 else if (i.types[n] & Imm16)
1258 p = frag_more (size);
1259 fix_new (frag_now, p - frag_now->fr_literal, size,
1260 i.imms[n]->X_add_symbol, i.imms[n]->X_subtract_symbol,
1261 i.imms[n]->X_add_number, 0, NO_RELOC);
1265 } /* end immediate output */
1269 if (flagseen ['D']) {
1272 #endif /* DEBUG386 */
1278 /* Parse OPERAND_STRING into the i386_insn structure I. Returns non-zero
1281 static int i386_operand (operand_string)
1282 char *operand_string;
1284 register char *op_string = operand_string;
1286 /* Address of '\0' at end of operand_string. */
1287 char * end_of_operand_string = operand_string + strlen(operand_string);
1289 /* Start and end of displacement string expression (if found). */
1290 char *displacement_string_start = NULL;
1291 char *displacement_string_end = NULL;
1293 /* We check for an absolute prefix (differentiating,
1294 for example, 'jmp pc_relative_label' from 'jmp *absolute_label'. */
1295 if (*op_string == ABSOLUTE_PREFIX) {
1297 i.types[this_operand] |= JumpAbsolute;
1300 /* Check if operand is a register. */
1301 if (*op_string == REGISTER_PREFIX) {
1302 register reg_entry *r;
1303 if (!(r = parse_register (op_string))) {
1304 as_bad("bad register name ('%s')", op_string);
1307 /* Check for segment override, rather than segment register by
1308 searching for ':' after %<x>s where <x> = s, c, d, e, f, g. */
1309 if ((r->reg_type & (SReg2|SReg3)) && op_string[3] == ':') {
1310 switch (r->reg_num) {
1312 i.seg = (seg_entry *) &es; break;
1314 i.seg = (seg_entry *) &cs; break;
1316 i.seg = (seg_entry *) &ss; break;
1318 i.seg = (seg_entry *) &ds; break;
1320 i.seg = (seg_entry *) &fs; break;
1322 i.seg = (seg_entry *) &gs; break;
1324 op_string += 4; /* skip % <x> s : */
1325 operand_string = op_string; /* Pretend given string starts here. */
1326 if (!is_digit_char(*op_string) && !is_identifier_char(*op_string)
1327 && *op_string != '(' && *op_string != ABSOLUTE_PREFIX) {
1328 as_bad("bad memory operand after segment override");
1331 /* Handle case of %es:*foo. */
1332 if (*op_string == ABSOLUTE_PREFIX) {
1334 i.types[this_operand] |= JumpAbsolute;
1336 goto do_memory_reference;
1338 i.types[this_operand] |= r->reg_type;
1339 i.regs[this_operand] = r;
1341 } else if (*op_string == IMMEDIATE_PREFIX) { /* ... or an immediate */
1342 char *save_input_line_pointer;
1343 segT exp_seg = SEG_GOOF;
1346 if (i.imm_operands == MAX_IMMEDIATE_OPERANDS) {
1347 as_bad("only 1 or 2 immediate operands are allowed");
1351 exp = &im_expressions[i.imm_operands++];
1352 i.imms[this_operand] = exp;
1353 save_input_line_pointer = input_line_pointer;
1354 input_line_pointer = ++op_string; /* must advance op_string! */
1355 exp_seg = expression(exp);
1356 input_line_pointer = save_input_line_pointer;
1359 case SEG_ABSENT: /* missing or bad expr becomes absolute 0 */
1360 as_bad("missing or invalid immediate expression '%s' taken as 0",
1362 exp->X_seg = SEG_ABSOLUTE;
1363 exp->X_add_number = 0;
1364 exp->X_add_symbol = (symbolS *) 0;
1365 exp->X_subtract_symbol = (symbolS *) 0;
1366 i.types[this_operand] |= Imm;
1369 i.types[this_operand] |= smallest_imm_type(exp->X_add_number);
1371 case SEG_TEXT: case SEG_DATA: case SEG_BSS: case SEG_UNKNOWN:
1372 i.types[this_operand] |= Imm32; /* this is an address ==> 32bit */
1376 as_bad("Unimplemented segment type %d in parse_operand", exp_seg);
1379 /* shorten this type of this operand if the instruction wants
1380 * fewer bits than are present in the immediate. The bit field
1381 * code can put out 'andb $0xffffff, %al', for example. pace
1382 * also 'movw $foo,(%eax)'
1385 case WORD_OPCODE_SUFFIX:
1386 i.types[this_operand] |= Imm16;
1388 case BYTE_OPCODE_SUFFIX:
1389 i.types[this_operand] |= Imm16 | Imm8 | Imm8S;
1392 } else if (is_digit_char(*op_string) || is_identifier_char(*op_string)
1393 || *op_string == '(') {
1394 /* This is a memory reference of some sort. */
1395 register char * base_string;
1396 unsigned int found_base_index_form;
1398 do_memory_reference:
1399 if (i.mem_operands == MAX_MEMORY_OPERANDS) {
1400 as_bad("more than 1 memory reference in instruction");
1405 /* Determine type of memory operand from opcode_suffix;
1406 no opcode suffix implies general memory references. */
1408 case BYTE_OPCODE_SUFFIX:
1409 i.types[this_operand] |= Mem8;
1411 case WORD_OPCODE_SUFFIX:
1412 i.types[this_operand] |= Mem16;
1414 case DWORD_OPCODE_SUFFIX:
1416 i.types[this_operand] |= Mem32;
1419 /* Check for base index form. We detect the base index form by
1420 looking for an ')' at the end of the operand, searching
1421 for the '(' matching it, and finding a REGISTER_PREFIX or ','
1423 base_string = end_of_operand_string - 1;
1424 found_base_index_form = 0;
1425 if (*base_string == ')') {
1426 unsigned int parens_balenced = 1;
1427 /* We've already checked that the number of left & right ()'s are equal,
1428 so this loop will not be infinite. */
1431 if (*base_string == ')') parens_balenced++;
1432 if (*base_string == '(') parens_balenced--;
1433 } while (parens_balenced);
1434 base_string++; /* Skip past '('. */
1435 if (*base_string == REGISTER_PREFIX || *base_string == ',')
1436 found_base_index_form = 1;
1439 /* If we can't parse a base index register expression, we've found
1440 a pure displacement expression. We set up displacement_string_start
1441 and displacement_string_end for the code below. */
1442 if (! found_base_index_form) {
1443 displacement_string_start = op_string;
1444 displacement_string_end = end_of_operand_string;
1446 char *base_reg_name, *index_reg_name, *num_string;
1449 i.types[this_operand] |= BaseIndex;
1451 /* If there is a displacement set-up for it to be parsed later. */
1452 if (base_string != op_string + 1) {
1453 displacement_string_start = op_string;
1454 displacement_string_end = base_string - 1;
1457 /* Find base register (if any). */
1458 if (*base_string != ',') {
1459 base_reg_name = base_string++;
1460 /* skip past register name & parse it */
1461 while (isalpha(*base_string)) base_string++;
1462 if (base_string == base_reg_name+1) {
1463 as_bad("can't find base register name after '(%c'",
1467 END_STRING_AND_SAVE (base_string);
1468 if (! (i.base_reg = parse_register (base_reg_name))) {
1469 as_bad("bad base register name ('%s')", base_reg_name);
1472 RESTORE_END_STRING (base_string);
1475 /* Now check seperator; must be ',' ==> index reg
1476 OR num ==> no index reg. just scale factor
1477 OR ')' ==> end. (scale factor = 1) */
1478 if (*base_string != ',' && *base_string != ')') {
1479 as_bad("expecting ',' or ')' after base register in `%s'",
1484 /* There may index reg here; and there may be a scale factor. */
1485 if (*base_string == ',' && *(base_string+1) == REGISTER_PREFIX) {
1486 index_reg_name = ++base_string;
1487 while (isalpha(*++base_string));
1488 END_STRING_AND_SAVE (base_string);
1489 if (! (i.index_reg = parse_register(index_reg_name))) {
1490 as_bad("bad index register name ('%s')", index_reg_name);
1493 RESTORE_END_STRING (base_string);
1496 /* Check for scale factor. */
1497 if (*base_string == ',' && isdigit(*(base_string+1))) {
1498 num_string = ++base_string;
1499 while (is_digit_char(*base_string)) base_string++;
1500 if (base_string == num_string) {
1501 as_bad("can't find a scale factor after ','");
1504 END_STRING_AND_SAVE (base_string);
1505 /* We've got a scale factor. */
1506 if (! sscanf (num_string, "%d", &num)) {
1507 as_bad("can't parse scale factor from '%s'", num_string);
1510 RESTORE_END_STRING (base_string);
1511 switch (num) { /* must be 1 digit scale */
1512 case 1: i.log2_scale_factor = 0; break;
1513 case 2: i.log2_scale_factor = 1; break;
1514 case 4: i.log2_scale_factor = 2; break;
1515 case 8: i.log2_scale_factor = 3; break;
1517 as_bad("expecting scale factor of 1, 2, 4, 8; got %d", num);
1521 if (! i.index_reg && *base_string == ',') {
1522 as_bad("expecting index register or scale factor after ','; got '%c'",
1529 /* If there's an expression begining the operand, parse it,
1530 assuming displacement_string_start and displacement_string_end
1532 if (displacement_string_start) {
1533 register expressionS *exp;
1534 segT exp_seg = SEG_GOOF;
1535 char *save_input_line_pointer;
1536 exp = &disp_expressions[i.disp_operands];
1537 i.disps [this_operand] = exp;
1539 save_input_line_pointer = input_line_pointer;
1540 input_line_pointer = displacement_string_start;
1541 END_STRING_AND_SAVE (displacement_string_end);
1542 exp_seg = expression(exp);
1543 if(*input_line_pointer)
1544 as_bad("Ignoring junk '%s' after expression",input_line_pointer);
1545 RESTORE_END_STRING (displacement_string_end);
1546 input_line_pointer = save_input_line_pointer;
1549 /* missing expr becomes absolute 0 */
1550 as_bad("missing or invalid displacement '%s' taken as 0",
1552 i.types[this_operand] |= (Disp|Abs);
1553 exp->X_seg = SEG_ABSOLUTE;
1554 exp->X_add_number = 0;
1555 exp->X_add_symbol = (symbolS *) 0;
1556 exp->X_subtract_symbol = (symbolS *) 0;
1559 i.types[this_operand] |= SMALLEST_DISP_TYPE (exp->X_add_number);
1561 case SEG_TEXT: case SEG_DATA: case SEG_BSS:
1562 case SEG_UNKNOWN: /* must be 32 bit displacement (i.e. address) */
1563 i.types[this_operand] |= Disp32;
1566 goto seg_unimplemented;
1570 /* Make sure the memory operand we've been dealt is valid. */
1571 if (i.base_reg && i.index_reg &&
1572 ! (i.base_reg->reg_type & i.index_reg->reg_type & Reg)) {
1573 as_bad("register size mismatch in (base,index,scale) expression");
1577 * special case for (%dx) while doing input/output op
1580 (i.base_reg->reg_type == (Reg16|InOutPortReg)) &&
1581 (i.index_reg == 0)))
1583 if ((i.base_reg && (i.base_reg->reg_type & Reg32) == 0) ||
1584 (i.index_reg && (i.index_reg->reg_type & Reg32) == 0)) {
1585 as_bad("base/index register must be 32 bit register");
1588 if (i.index_reg && i.index_reg == esp) {
1589 as_bad("%s may not be used as an index register", esp->reg_name);
1592 } else { /* it's not a memory operand; argh! */
1593 as_bad("invalid char %s begining %s operand '%s'",
1594 output_invalid(*op_string), ordinal_names[this_operand],
1598 return 1; /* normal return */
1602 * md_estimate_size_before_relax()
1604 * Called just before relax().
1605 * Any symbol that is now undefined will not become defined.
1606 * Return the correct fr_subtype in the frag.
1607 * Return the initial "guess for fr_var" to caller.
1608 * The guess for fr_var is ACTUALLY the growth beyond fr_fix.
1609 * Whatever we do to grow fr_fix or fr_var contributes to our returned value.
1610 * Although it may not be explicit in the frag, pretend fr_var starts with a
1614 md_estimate_size_before_relax (fragP, segment)
1615 register fragS * fragP;
1616 register segT segment;
1618 register unsigned char * opcode;
1619 register int old_fr_fix;
1621 old_fr_fix = fragP -> fr_fix;
1622 opcode = (unsigned char *) fragP -> fr_opcode;
1623 /* We've already got fragP->fr_subtype right; all we have to do is check
1624 for un-relaxable symbols. */
1625 if (S_GET_SEGMENT(fragP -> fr_symbol) != segment) {
1626 /* symbol is undefined in this segment */
1627 switch (opcode[0]) {
1628 case JUMP_PC_RELATIVE: /* make jmp (0xeb) a dword displacement jump */
1629 opcode[0] = 0xe9; /* dword disp jmp */
1630 fragP -> fr_fix += 4;
1631 fix_new (fragP, old_fr_fix, 4,
1634 fragP -> fr_offset, 1, NO_RELOC);
1638 /* This changes the byte-displacement jump 0x7N -->
1639 the dword-displacement jump 0x0f8N */
1640 opcode[1] = opcode[0] + 0x10;
1641 opcode[0] = TWO_BYTE_OPCODE_ESCAPE; /* two-byte escape */
1642 fragP -> fr_fix += 1 + 4; /* we've added an opcode byte */
1643 fix_new (fragP, old_fr_fix + 1, 4,
1646 fragP -> fr_offset, 1, NO_RELOC);
1651 return (fragP -> fr_var + fragP -> fr_fix - old_fr_fix);
1652 } /* md_estimate_size_before_relax() */
1655 * md_convert_frag();
1657 * Called after relax() is finished.
1658 * In: Address of frag.
1659 * fr_type == rs_machine_dependent.
1660 * fr_subtype is what the address relaxed to.
1662 * Out: Any fixSs and constants are set up.
1663 * Caller will turn frag into a ".space 0".
1666 md_convert_frag (headers, fragP)
1667 object_headers *headers;
1668 register fragS * fragP;
1670 register unsigned char *opcode;
1671 unsigned char *where_to_put_displacement = NULL;
1672 unsigned int target_address;
1673 unsigned int opcode_address;
1674 unsigned int extension = 0;
1675 int displacement_from_opcode_start;
1677 opcode = (unsigned char *) fragP -> fr_opcode;
1679 /* Address we want to reach in file space. */
1680 target_address = S_GET_VALUE(fragP->fr_symbol) + fragP->fr_offset;
1682 /* Address opcode resides at in file space. */
1683 opcode_address = fragP->fr_address + fragP->fr_fix;
1685 /* Displacement from opcode start to fill into instruction. */
1686 displacement_from_opcode_start = target_address - opcode_address;
1688 switch (fragP->fr_subtype) {
1689 case ENCODE_RELAX_STATE (COND_JUMP, BYTE):
1690 case ENCODE_RELAX_STATE (UNCOND_JUMP, BYTE):
1691 /* don't have to change opcode */
1692 extension = 1; /* 1 opcode + 1 displacement */
1693 where_to_put_displacement = &opcode[1];
1696 case ENCODE_RELAX_STATE (COND_JUMP, WORD):
1697 opcode[1] = TWO_BYTE_OPCODE_ESCAPE;
1698 opcode[2] = opcode[0] + 0x10;
1699 opcode[0] = WORD_PREFIX_OPCODE;
1700 extension = 4; /* 3 opcode + 2 displacement */
1701 where_to_put_displacement = &opcode[3];
1704 case ENCODE_RELAX_STATE (UNCOND_JUMP, WORD):
1706 opcode[0] = WORD_PREFIX_OPCODE;
1707 extension = 3; /* 2 opcode + 2 displacement */
1708 where_to_put_displacement = &opcode[2];
1711 case ENCODE_RELAX_STATE (COND_JUMP, DWORD):
1712 opcode[1] = opcode[0] + 0x10;
1713 opcode[0] = TWO_BYTE_OPCODE_ESCAPE;
1714 extension = 5; /* 2 opcode + 4 displacement */
1715 where_to_put_displacement = &opcode[2];
1718 case ENCODE_RELAX_STATE (UNCOND_JUMP, DWORD):
1720 extension = 4; /* 1 opcode + 4 displacement */
1721 where_to_put_displacement = &opcode[1];
1725 BAD_CASE(fragP -> fr_subtype);
1728 /* now put displacement after opcode */
1729 md_number_to_chars ((char *) where_to_put_displacement,
1730 displacement_from_opcode_start - extension,
1731 SIZE_FROM_RELAX_STATE (fragP->fr_subtype));
1732 fragP -> fr_fix += extension;
1736 int md_short_jump_size = 2; /* size of byte displacement jmp */
1737 int md_long_jump_size = 5; /* size of dword displacement jmp */
1738 int md_reloc_size = 8; /* Size of relocation record */
1740 void md_create_short_jump(ptr, from_addr, to_addr, frag, to_symbol)
1742 long from_addr, to_addr;
1748 offset = to_addr - (from_addr + 2);
1749 md_number_to_chars (ptr, (long) 0xeb, 1); /* opcode for byte-disp jump */
1750 md_number_to_chars (ptr + 1, offset, 1);
1753 void md_create_long_jump (ptr, from_addr, to_addr, frag, to_symbol)
1755 long from_addr, to_addr;
1761 if (flagseen['m']) {
1762 offset = to_addr - S_GET_VALUE(to_symbol);
1763 md_number_to_chars (ptr, 0xe9, 1); /* opcode for long jmp */
1764 md_number_to_chars (ptr + 1, offset, 4);
1765 fix_new (frag, (ptr+1) - frag->fr_literal, 4,
1766 to_symbol, (symbolS *) 0, (long) 0, 0, NO_RELOC);
1768 offset = to_addr - (from_addr + 5);
1769 md_number_to_chars(ptr, (long) 0xe9, 1);
1770 md_number_to_chars(ptr + 1, offset, 4);
1775 md_parse_option(argP,cntP,vecP)
1783 void /* Knows about order of bytes in address. */
1784 md_number_to_chars (con, value, nbytes)
1785 char con []; /* Return 'nbytes' of chars here. */
1786 long value; /* The value of the bits. */
1787 int nbytes; /* Number of bytes in the output. */
1789 register char * p = con;
1793 p[0] = value & 0xff;
1796 p[0] = value & 0xff;
1797 p[1] = (value >> 8) & 0xff;
1800 p[0] = value & 0xff;
1801 p[1] = (value>>8) & 0xff;
1802 p[2] = (value>>16) & 0xff;
1803 p[3] = (value>>24) & 0xff;
1811 /* Apply a fixup (fixS) to segment data, once it has been determined
1812 by our caller that we have all the info we need to fix it up.
1814 On the 386, immediates, displacements, and data pointers are all in
1815 the same (little-endian) format, so we don't need to care about which
1819 md_apply_fix (fixP, value)
1820 fixS * fixP; /* The fix we're to put in */
1821 long value; /* The value of the bits. */
1823 register char * p = fixP->fx_where + fixP->fx_frag->fr_literal;
1825 switch (fixP->fx_size) {
1840 BAD_CASE (fixP->fx_size);
1844 long /* Knows about the byte order in a word. */
1845 md_chars_to_number (con, nbytes)
1846 unsigned char con[]; /* Low order byte 1st. */
1847 int nbytes; /* Number of bytes in the input. */
1850 for (retval=0, con+=nbytes-1; nbytes--; con--)
1852 retval <<= BITS_PER_CHAR;
1858 /* Not needed for coff since relocation structure does not
1859 contain bitfields. */
1860 #if defined(OBJ_AOUT) | defined(OBJ_BOUT)
1862 /* Output relocation information in the target's format. */
1864 md_ri_to_chars(the_bytes, ri)
1866 struct reloc_info_generic *ri;
1869 md_number_to_chars(the_bytes, ri->r_address, 4);
1870 /* now the fun stuff */
1871 the_bytes[6] = (ri->r_symbolnum >> 16) & 0x0ff;
1872 the_bytes[5] = (ri->r_symbolnum >> 8) & 0x0ff;
1873 the_bytes[4] = ri->r_symbolnum & 0x0ff;
1874 the_bytes[7] = (((ri->r_extern << 3) & 0x08) | ((ri->r_length << 1) & 0x06) |
1875 ((ri->r_pcrel << 0) & 0x01)) & 0x0F;
1877 #endif /* comment */
1879 void tc_aout_fix_to_chars(where, fixP, segment_address_in_file)
1882 relax_addressT segment_address_in_file;
1885 * In: length of relocation (or of address) in chars: 1, 2 or 4.
1886 * Out: GNU LD relocation length code: 0, 1, or 2.
1889 static unsigned char nbytes_r_length [] = { 42, 0, 1, 42, 2 };
1892 know(fixP->fx_addsy != NULL);
1894 md_number_to_chars(where,
1895 fixP->fx_frag->fr_address + fixP->fx_where - segment_address_in_file,
1898 r_symbolnum = (S_IS_DEFINED(fixP->fx_addsy)
1899 ? S_GET_TYPE(fixP->fx_addsy)
1900 : fixP->fx_addsy->sy_number);
1902 where[6] = (r_symbolnum >> 16) & 0x0ff;
1903 where[5] = (r_symbolnum >> 8) & 0x0ff;
1904 where[4] = r_symbolnum & 0x0ff;
1905 where[7] = ((((!S_IS_DEFINED(fixP->fx_addsy)) << 3) & 0x08)
1906 | ((nbytes_r_length[fixP->fx_size] << 1) & 0x06)
1907 | (((fixP->fx_pcrel << 0) & 0x01) & 0x0f));
1910 } /* tc_aout_fix_to_chars() */
1912 #endif /* OBJ_AOUT or OBJ_BOUT */
1915 #define MAX_LITTLENUMS 6
1917 /* Turn the string pointed to by litP into a floating point constant of type
1918 type, and emit the appropriate bytes. The number of LITTLENUMS emitted
1919 is stored in *sizeP . An error message is returned, or NULL on OK.
1922 md_atof(type,litP,sizeP)
1928 LITTLENUM_TYPE words[MAX_LITTLENUMS];
1929 LITTLENUM_TYPE *wordP;
1950 return "Bad call to md_atof ()";
1952 t = atof_ieee (input_line_pointer,type,words);
1954 input_line_pointer=t;
1956 *sizeP = prec * sizeof(LITTLENUM_TYPE);
1957 /* this loops outputs the LITTLENUMs in REVERSE order; in accord with
1958 the bigendian 386 */
1959 for(wordP = words + prec - 1;prec--;) {
1960 md_number_to_chars (litP, (long) (*wordP--), sizeof(LITTLENUM_TYPE));
1961 litP += sizeof(LITTLENUM_TYPE);
1963 return ""; /* Someone should teach Dean about null pointers */
1966 char output_invalid_buf[8];
1968 static char * output_invalid (c)
1971 if (isprint(c)) sprintf (output_invalid_buf, "'%c'", c);
1972 else sprintf (output_invalid_buf, "(0x%x)", (unsigned) c);
1973 return output_invalid_buf;
1976 static reg_entry *parse_register (reg_string)
1977 char *reg_string; /* reg_string starts *before* REGISTER_PREFIX */
1979 register char *s = reg_string;
1981 char reg_name_given[MAX_REG_NAME_SIZE];
1983 s++; /* skip REGISTER_PREFIX */
1984 for (p = reg_name_given; is_register_char (*s); p++, s++) {
1985 *p = register_chars [*s];
1986 if (p >= reg_name_given + MAX_REG_NAME_SIZE)
1987 return (reg_entry *) 0;
1990 return (reg_entry *) hash_find (reg_hash, reg_name_given);
1994 /* We have no need to default values of symbols. */
1998 md_undefined_symbol (name)
2004 /* Parse an operand that is machine-specific.
2005 We just return without modifying the expression if we have nothing
2010 md_operand (expressionP)
2011 expressionS *expressionP;
2015 /* Round up a section size to the appropriate boundary. */
2017 md_section_align (segment, size)
2021 return size; /* Byte alignment is fine */
2024 /* Exactly what point is a PC-relative offset relative TO?
2025 On the i386, they're relative to the address of the offset, plus
2026 its size. (??? Is this right? FIXME-SOON!) */
2028 md_pcrel_from (fixP)
2031 return fixP->fx_size + fixP->fx_where + fixP->fx_frag->fr_address;
2034 /* these were macros, but I don't trust macros that eval their
2035 arguments more than once. Besides, gcc can static inline them.
2038 static unsigned long mode_from_disp_size(t)
2041 return((t & (Disp8))
2043 : ((t & (Disp32)) ? 2 : 0));
2044 } /* mode_from_disp_size() */
2046 /* convert opcode suffix ('b' 'w' 'l' typically) into type specifyer */
2048 static unsigned long opcode_suffix_to_type(s)
2051 return(s == BYTE_OPCODE_SUFFIX
2052 ? Byte : (s == WORD_OPCODE_SUFFIX
2054 } /* opcode_suffix_to_type() */
2056 static int fits_in_signed_byte(num)
2059 return((num >= -128) && (num <= 127));
2060 } /* fits_in_signed_byte() */
2062 static int fits_in_unsigned_byte(num)
2065 return((num & 0xff) == num);
2066 } /* fits_in_unsigned_byte() */
2068 static int fits_in_unsigned_word(num)
2071 return((num & 0xffff) == num);
2072 } /* fits_in_unsigned_word() */
2074 static int fits_in_signed_word(num)
2077 return((-32768 <= num) && (num <= 32767));
2078 } /* fits_in_signed_word() */
2080 static int smallest_imm_type(num)
2084 ? (Imm1|Imm8|Imm8S|Imm16|Imm32)
2085 : (fits_in_signed_byte(num)
2086 ? (Imm8S|Imm8|Imm16|Imm32)
2087 : (fits_in_unsigned_byte(num)
2088 ? (Imm8|Imm16|Imm32)
2089 : ((fits_in_signed_word(num) || fits_in_unsigned_word(num))
2092 } /* smallest_imm_type() */
2100 /* end of tc-i386.c */