[ARM] Fix NULL dereference of march_ext_opt
[deliverable/binutils-gdb.git] / gas / config / tc-i386.c
... / ...
CommitLineData
1/* tc-i386.c -- Assemble code for the Intel 80386
2 Copyright (C) 1989-2018 Free Software Foundation, Inc.
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 3, 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 the Free
18 Software Foundation, 51 Franklin Street - Fifth Floor, Boston, MA
19 02110-1301, USA. */
20
21/* Intel 80386 machine specific gas.
22 Written by Eliot Dresselhaus (eliot@mgm.mit.edu).
23 x86_64 support by Jan Hubicka (jh@suse.cz)
24 VIA PadLock support by Michal Ludvig (mludvig@suse.cz)
25 Bugs & suggestions are completely welcome. This is free software.
26 Please help us make it better. */
27
28#include "as.h"
29#include "safe-ctype.h"
30#include "subsegs.h"
31#include "dwarf2dbg.h"
32#include "dw2gencfi.h"
33#include "elf/x86-64.h"
34#include "opcodes/i386-init.h"
35
36#ifndef REGISTER_WARNINGS
37#define REGISTER_WARNINGS 1
38#endif
39
40#ifndef INFER_ADDR_PREFIX
41#define INFER_ADDR_PREFIX 1
42#endif
43
44#ifndef DEFAULT_ARCH
45#define DEFAULT_ARCH "i386"
46#endif
47
48#ifndef INLINE
49#if __GNUC__ >= 2
50#define INLINE __inline__
51#else
52#define INLINE
53#endif
54#endif
55
56/* Prefixes will be emitted in the order defined below.
57 WAIT_PREFIX must be the first prefix since FWAIT is really is an
58 instruction, and so must come before any prefixes.
59 The preferred prefix order is SEG_PREFIX, ADDR_PREFIX, DATA_PREFIX,
60 REP_PREFIX/HLE_PREFIX, LOCK_PREFIX. */
61#define WAIT_PREFIX 0
62#define SEG_PREFIX 1
63#define ADDR_PREFIX 2
64#define DATA_PREFIX 3
65#define REP_PREFIX 4
66#define HLE_PREFIX REP_PREFIX
67#define BND_PREFIX REP_PREFIX
68#define LOCK_PREFIX 5
69#define REX_PREFIX 6 /* must come last. */
70#define MAX_PREFIXES 7 /* max prefixes per opcode */
71
72/* we define the syntax here (modulo base,index,scale syntax) */
73#define REGISTER_PREFIX '%'
74#define IMMEDIATE_PREFIX '$'
75#define ABSOLUTE_PREFIX '*'
76
77/* these are the instruction mnemonic suffixes in AT&T syntax or
78 memory operand size in Intel syntax. */
79#define WORD_MNEM_SUFFIX 'w'
80#define BYTE_MNEM_SUFFIX 'b'
81#define SHORT_MNEM_SUFFIX 's'
82#define LONG_MNEM_SUFFIX 'l'
83#define QWORD_MNEM_SUFFIX 'q'
84#define XMMWORD_MNEM_SUFFIX 'x'
85#define YMMWORD_MNEM_SUFFIX 'y'
86#define ZMMWORD_MNEM_SUFFIX 'z'
87/* Intel Syntax. Use a non-ascii letter since since it never appears
88 in instructions. */
89#define LONG_DOUBLE_MNEM_SUFFIX '\1'
90
91#define END_OF_INSN '\0'
92
93/*
94 'templates' is for grouping together 'template' structures for opcodes
95 of the same name. This is only used for storing the insns in the grand
96 ole hash table of insns.
97 The templates themselves start at START and range up to (but not including)
98 END.
99 */
100typedef struct
101{
102 const insn_template *start;
103 const insn_template *end;
104}
105templates;
106
107/* 386 operand encoding bytes: see 386 book for details of this. */
108typedef struct
109{
110 unsigned int regmem; /* codes register or memory operand */
111 unsigned int reg; /* codes register operand (or extended opcode) */
112 unsigned int mode; /* how to interpret regmem & reg */
113}
114modrm_byte;
115
116/* x86-64 extension prefix. */
117typedef int rex_byte;
118
119/* 386 opcode byte to code indirect addressing. */
120typedef struct
121{
122 unsigned base;
123 unsigned index;
124 unsigned scale;
125}
126sib_byte;
127
128/* x86 arch names, types and features */
129typedef struct
130{
131 const char *name; /* arch name */
132 unsigned int len; /* arch string length */
133 enum processor_type type; /* arch type */
134 i386_cpu_flags flags; /* cpu feature flags */
135 unsigned int skip; /* show_arch should skip this. */
136}
137arch_entry;
138
139/* Used to turn off indicated flags. */
140typedef struct
141{
142 const char *name; /* arch name */
143 unsigned int len; /* arch string length */
144 i386_cpu_flags flags; /* cpu feature flags */
145}
146noarch_entry;
147
148static void update_code_flag (int, int);
149static void set_code_flag (int);
150static void set_16bit_gcc_code_flag (int);
151static void set_intel_syntax (int);
152static void set_intel_mnemonic (int);
153static void set_allow_index_reg (int);
154static void set_check (int);
155static void set_cpu_arch (int);
156#ifdef TE_PE
157static void pe_directive_secrel (int);
158#endif
159static void signed_cons (int);
160static char *output_invalid (int c);
161static int i386_finalize_immediate (segT, expressionS *, i386_operand_type,
162 const char *);
163static int i386_finalize_displacement (segT, expressionS *, i386_operand_type,
164 const char *);
165static int i386_att_operand (char *);
166static int i386_intel_operand (char *, int);
167static int i386_intel_simplify (expressionS *);
168static int i386_intel_parse_name (const char *, expressionS *);
169static const reg_entry *parse_register (char *, char **);
170static char *parse_insn (char *, char *);
171static char *parse_operands (char *, const char *);
172static void swap_operands (void);
173static void swap_2_operands (int, int);
174static void optimize_imm (void);
175static void optimize_disp (void);
176static const insn_template *match_template (char);
177static int check_string (void);
178static int process_suffix (void);
179static int check_byte_reg (void);
180static int check_long_reg (void);
181static int check_qword_reg (void);
182static int check_word_reg (void);
183static int finalize_imm (void);
184static int process_operands (void);
185static const seg_entry *build_modrm_byte (void);
186static void output_insn (void);
187static void output_imm (fragS *, offsetT);
188static void output_disp (fragS *, offsetT);
189#ifndef I386COFF
190static void s_bss (int);
191#endif
192#if defined (OBJ_ELF) || defined (OBJ_MAYBE_ELF)
193static void handle_large_common (int small ATTRIBUTE_UNUSED);
194#endif
195
196static const char *default_arch = DEFAULT_ARCH;
197
198/* This struct describes rounding control and SAE in the instruction. */
199struct RC_Operation
200{
201 enum rc_type
202 {
203 rne = 0,
204 rd,
205 ru,
206 rz,
207 saeonly
208 } type;
209 int operand;
210};
211
212static struct RC_Operation rc_op;
213
214/* The struct describes masking, applied to OPERAND in the instruction.
215 MASK is a pointer to the corresponding mask register. ZEROING tells
216 whether merging or zeroing mask is used. */
217struct Mask_Operation
218{
219 const reg_entry *mask;
220 unsigned int zeroing;
221 /* The operand where this operation is associated. */
222 int operand;
223};
224
225static struct Mask_Operation mask_op;
226
227/* The struct describes broadcasting, applied to OPERAND. FACTOR is
228 broadcast factor. */
229struct Broadcast_Operation
230{
231 /* Type of broadcast: no broadcast, {1to8}, or {1to16}. */
232 int type;
233
234 /* Index of broadcasted operand. */
235 int operand;
236};
237
238static struct Broadcast_Operation broadcast_op;
239
240/* VEX prefix. */
241typedef struct
242{
243 /* VEX prefix is either 2 byte or 3 byte. EVEX is 4 byte. */
244 unsigned char bytes[4];
245 unsigned int length;
246 /* Destination or source register specifier. */
247 const reg_entry *register_specifier;
248} vex_prefix;
249
250/* 'md_assemble ()' gathers together information and puts it into a
251 i386_insn. */
252
253union i386_op
254 {
255 expressionS *disps;
256 expressionS *imms;
257 const reg_entry *regs;
258 };
259
260enum i386_error
261 {
262 operand_size_mismatch,
263 operand_type_mismatch,
264 register_type_mismatch,
265 number_of_operands_mismatch,
266 invalid_instruction_suffix,
267 bad_imm4,
268 old_gcc_only,
269 unsupported_with_intel_mnemonic,
270 unsupported_syntax,
271 unsupported,
272 invalid_vsib_address,
273 invalid_vector_register_set,
274 unsupported_vector_index_register,
275 unsupported_broadcast,
276 broadcast_not_on_src_operand,
277 broadcast_needed,
278 unsupported_masking,
279 mask_not_on_destination,
280 no_default_mask,
281 unsupported_rc_sae,
282 rc_sae_operand_not_last_imm,
283 invalid_register_operand,
284 };
285
286struct _i386_insn
287 {
288 /* TM holds the template for the insn were currently assembling. */
289 insn_template tm;
290
291 /* SUFFIX holds the instruction size suffix for byte, word, dword
292 or qword, if given. */
293 char suffix;
294
295 /* OPERANDS gives the number of given operands. */
296 unsigned int operands;
297
298 /* REG_OPERANDS, DISP_OPERANDS, MEM_OPERANDS, IMM_OPERANDS give the number
299 of given register, displacement, memory operands and immediate
300 operands. */
301 unsigned int reg_operands, disp_operands, mem_operands, imm_operands;
302
303 /* TYPES [i] is the type (see above #defines) which tells us how to
304 use OP[i] for the corresponding operand. */
305 i386_operand_type types[MAX_OPERANDS];
306
307 /* Displacement expression, immediate expression, or register for each
308 operand. */
309 union i386_op op[MAX_OPERANDS];
310
311 /* Flags for operands. */
312 unsigned int flags[MAX_OPERANDS];
313#define Operand_PCrel 1
314
315 /* Relocation type for operand */
316 enum bfd_reloc_code_real reloc[MAX_OPERANDS];
317
318 /* BASE_REG, INDEX_REG, and LOG2_SCALE_FACTOR are used to encode
319 the base index byte below. */
320 const reg_entry *base_reg;
321 const reg_entry *index_reg;
322 unsigned int log2_scale_factor;
323
324 /* SEG gives the seg_entries of this insn. They are zero unless
325 explicit segment overrides are given. */
326 const seg_entry *seg[2];
327
328 /* Copied first memory operand string, for re-checking. */
329 char *memop1_string;
330
331 /* PREFIX holds all the given prefix opcodes (usually null).
332 PREFIXES is the number of prefix opcodes. */
333 unsigned int prefixes;
334 unsigned char prefix[MAX_PREFIXES];
335
336 /* RM and SIB are the modrm byte and the sib byte where the
337 addressing modes of this insn are encoded. */
338 modrm_byte rm;
339 rex_byte rex;
340 rex_byte vrex;
341 sib_byte sib;
342 vex_prefix vex;
343
344 /* Masking attributes. */
345 struct Mask_Operation *mask;
346
347 /* Rounding control and SAE attributes. */
348 struct RC_Operation *rounding;
349
350 /* Broadcasting attributes. */
351 struct Broadcast_Operation *broadcast;
352
353 /* Compressed disp8*N attribute. */
354 unsigned int memshift;
355
356 /* Prefer load or store in encoding. */
357 enum
358 {
359 dir_encoding_default = 0,
360 dir_encoding_load,
361 dir_encoding_store
362 } dir_encoding;
363
364 /* Prefer 8bit or 32bit displacement in encoding. */
365 enum
366 {
367 disp_encoding_default = 0,
368 disp_encoding_8bit,
369 disp_encoding_32bit
370 } disp_encoding;
371
372 /* Prefer the REX byte in encoding. */
373 bfd_boolean rex_encoding;
374
375 /* Disable instruction size optimization. */
376 bfd_boolean no_optimize;
377
378 /* How to encode vector instructions. */
379 enum
380 {
381 vex_encoding_default = 0,
382 vex_encoding_vex2,
383 vex_encoding_vex3,
384 vex_encoding_evex
385 } vec_encoding;
386
387 /* REP prefix. */
388 const char *rep_prefix;
389
390 /* HLE prefix. */
391 const char *hle_prefix;
392
393 /* Have BND prefix. */
394 const char *bnd_prefix;
395
396 /* Have NOTRACK prefix. */
397 const char *notrack_prefix;
398
399 /* Error message. */
400 enum i386_error error;
401 };
402
403typedef struct _i386_insn i386_insn;
404
405/* Link RC type with corresponding string, that'll be looked for in
406 asm. */
407struct RC_name
408{
409 enum rc_type type;
410 const char *name;
411 unsigned int len;
412};
413
414static const struct RC_name RC_NamesTable[] =
415{
416 { rne, STRING_COMMA_LEN ("rn-sae") },
417 { rd, STRING_COMMA_LEN ("rd-sae") },
418 { ru, STRING_COMMA_LEN ("ru-sae") },
419 { rz, STRING_COMMA_LEN ("rz-sae") },
420 { saeonly, STRING_COMMA_LEN ("sae") },
421};
422
423/* List of chars besides those in app.c:symbol_chars that can start an
424 operand. Used to prevent the scrubber eating vital white-space. */
425const char extra_symbol_chars[] = "*%-([{}"
426#ifdef LEX_AT
427 "@"
428#endif
429#ifdef LEX_QM
430 "?"
431#endif
432 ;
433
434#if (defined (TE_I386AIX) \
435 || ((defined (OBJ_ELF) || defined (OBJ_MAYBE_ELF)) \
436 && !defined (TE_GNU) \
437 && !defined (TE_LINUX) \
438 && !defined (TE_NACL) \
439 && !defined (TE_NETWARE) \
440 && !defined (TE_FreeBSD) \
441 && !defined (TE_DragonFly) \
442 && !defined (TE_NetBSD)))
443/* This array holds the chars that always start a comment. If the
444 pre-processor is disabled, these aren't very useful. The option
445 --divide will remove '/' from this list. */
446const char *i386_comment_chars = "#/";
447#define SVR4_COMMENT_CHARS 1
448#define PREFIX_SEPARATOR '\\'
449
450#else
451const char *i386_comment_chars = "#";
452#define PREFIX_SEPARATOR '/'
453#endif
454
455/* This array holds the chars that only start a comment at the beginning of
456 a line. If the line seems to have the form '# 123 filename'
457 .line and .file directives will appear in the pre-processed output.
458 Note that input_file.c hand checks for '#' at the beginning of the
459 first line of the input file. This is because the compiler outputs
460 #NO_APP at the beginning of its output.
461 Also note that comments started like this one will always work if
462 '/' isn't otherwise defined. */
463const char line_comment_chars[] = "#/";
464
465const char line_separator_chars[] = ";";
466
467/* Chars that can be used to separate mant from exp in floating point
468 nums. */
469const char EXP_CHARS[] = "eE";
470
471/* Chars that mean this number is a floating point constant
472 As in 0f12.456
473 or 0d1.2345e12. */
474const char FLT_CHARS[] = "fFdDxX";
475
476/* Tables for lexical analysis. */
477static char mnemonic_chars[256];
478static char register_chars[256];
479static char operand_chars[256];
480static char identifier_chars[256];
481static char digit_chars[256];
482
483/* Lexical macros. */
484#define is_mnemonic_char(x) (mnemonic_chars[(unsigned char) x])
485#define is_operand_char(x) (operand_chars[(unsigned char) x])
486#define is_register_char(x) (register_chars[(unsigned char) x])
487#define is_space_char(x) ((x) == ' ')
488#define is_identifier_char(x) (identifier_chars[(unsigned char) x])
489#define is_digit_char(x) (digit_chars[(unsigned char) x])
490
491/* All non-digit non-letter characters that may occur in an operand. */
492static char operand_special_chars[] = "%$-+(,)*._~/<>|&^!:[@]";
493
494/* md_assemble() always leaves the strings it's passed unaltered. To
495 effect this we maintain a stack of saved characters that we've smashed
496 with '\0's (indicating end of strings for various sub-fields of the
497 assembler instruction). */
498static char save_stack[32];
499static char *save_stack_p;
500#define END_STRING_AND_SAVE(s) \
501 do { *save_stack_p++ = *(s); *(s) = '\0'; } while (0)
502#define RESTORE_END_STRING(s) \
503 do { *(s) = *--save_stack_p; } while (0)
504
505/* The instruction we're assembling. */
506static i386_insn i;
507
508/* Possible templates for current insn. */
509static const templates *current_templates;
510
511/* Per instruction expressionS buffers: max displacements & immediates. */
512static expressionS disp_expressions[MAX_MEMORY_OPERANDS];
513static expressionS im_expressions[MAX_IMMEDIATE_OPERANDS];
514
515/* Current operand we are working on. */
516static int this_operand = -1;
517
518/* We support four different modes. FLAG_CODE variable is used to distinguish
519 these. */
520
521enum flag_code {
522 CODE_32BIT,
523 CODE_16BIT,
524 CODE_64BIT };
525
526static enum flag_code flag_code;
527static unsigned int object_64bit;
528static unsigned int disallow_64bit_reloc;
529static int use_rela_relocations = 0;
530
531#if ((defined (OBJ_MAYBE_COFF) && defined (OBJ_MAYBE_AOUT)) \
532 || defined (OBJ_ELF) || defined (OBJ_MAYBE_ELF) \
533 || defined (TE_PE) || defined (TE_PEP) || defined (OBJ_MACH_O))
534
535/* The ELF ABI to use. */
536enum x86_elf_abi
537{
538 I386_ABI,
539 X86_64_ABI,
540 X86_64_X32_ABI
541};
542
543static enum x86_elf_abi x86_elf_abi = I386_ABI;
544#endif
545
546#if defined (TE_PE) || defined (TE_PEP)
547/* Use big object file format. */
548static int use_big_obj = 0;
549#endif
550
551#if defined (OBJ_ELF) || defined (OBJ_MAYBE_ELF)
552/* 1 if generating code for a shared library. */
553static int shared = 0;
554#endif
555
556/* 1 for intel syntax,
557 0 if att syntax. */
558static int intel_syntax = 0;
559
560/* 1 for Intel64 ISA,
561 0 if AMD64 ISA. */
562static int intel64;
563
564/* 1 for intel mnemonic,
565 0 if att mnemonic. */
566static int intel_mnemonic = !SYSV386_COMPAT;
567
568/* 1 if support old (<= 2.8.1) versions of gcc. */
569static int old_gcc = OLDGCC_COMPAT;
570
571/* 1 if pseudo registers are permitted. */
572static int allow_pseudo_reg = 0;
573
574/* 1 if register prefix % not required. */
575static int allow_naked_reg = 0;
576
577/* 1 if the assembler should add BND prefix for all control-transferring
578 instructions supporting it, even if this prefix wasn't specified
579 explicitly. */
580static int add_bnd_prefix = 0;
581
582/* 1 if pseudo index register, eiz/riz, is allowed . */
583static int allow_index_reg = 0;
584
585/* 1 if the assembler should ignore LOCK prefix, even if it was
586 specified explicitly. */
587static int omit_lock_prefix = 0;
588
589/* 1 if the assembler should encode lfence, mfence, and sfence as
590 "lock addl $0, (%{re}sp)". */
591static int avoid_fence = 0;
592
593/* 1 if the assembler should generate relax relocations. */
594
595static int generate_relax_relocations
596 = DEFAULT_GENERATE_X86_RELAX_RELOCATIONS;
597
598static enum check_kind
599 {
600 check_none = 0,
601 check_warning,
602 check_error
603 }
604sse_check, operand_check = check_warning;
605
606/* Optimization:
607 1. Clear the REX_W bit with register operand if possible.
608 2. Above plus use 128bit vector instruction to clear the full vector
609 register.
610 */
611static int optimize = 0;
612
613/* Optimization:
614 1. Clear the REX_W bit with register operand if possible.
615 2. Above plus use 128bit vector instruction to clear the full vector
616 register.
617 3. Above plus optimize "test{q,l,w} $imm8,%r{64,32,16}" to
618 "testb $imm7,%r8".
619 */
620static int optimize_for_space = 0;
621
622/* Register prefix used for error message. */
623static const char *register_prefix = "%";
624
625/* Used in 16 bit gcc mode to add an l suffix to call, ret, enter,
626 leave, push, and pop instructions so that gcc has the same stack
627 frame as in 32 bit mode. */
628static char stackop_size = '\0';
629
630/* Non-zero to optimize code alignment. */
631int optimize_align_code = 1;
632
633/* Non-zero to quieten some warnings. */
634static int quiet_warnings = 0;
635
636/* CPU name. */
637static const char *cpu_arch_name = NULL;
638static char *cpu_sub_arch_name = NULL;
639
640/* CPU feature flags. */
641static i386_cpu_flags cpu_arch_flags = CPU_UNKNOWN_FLAGS;
642
643/* If we have selected a cpu we are generating instructions for. */
644static int cpu_arch_tune_set = 0;
645
646/* Cpu we are generating instructions for. */
647enum processor_type cpu_arch_tune = PROCESSOR_UNKNOWN;
648
649/* CPU feature flags of cpu we are generating instructions for. */
650static i386_cpu_flags cpu_arch_tune_flags;
651
652/* CPU instruction set architecture used. */
653enum processor_type cpu_arch_isa = PROCESSOR_UNKNOWN;
654
655/* CPU feature flags of instruction set architecture used. */
656i386_cpu_flags cpu_arch_isa_flags;
657
658/* If set, conditional jumps are not automatically promoted to handle
659 larger than a byte offset. */
660static unsigned int no_cond_jump_promotion = 0;
661
662/* Encode SSE instructions with VEX prefix. */
663static unsigned int sse2avx;
664
665/* Encode scalar AVX instructions with specific vector length. */
666static enum
667 {
668 vex128 = 0,
669 vex256
670 } avxscalar;
671
672/* Encode scalar EVEX LIG instructions with specific vector length. */
673static enum
674 {
675 evexl128 = 0,
676 evexl256,
677 evexl512
678 } evexlig;
679
680/* Encode EVEX WIG instructions with specific evex.w. */
681static enum
682 {
683 evexw0 = 0,
684 evexw1
685 } evexwig;
686
687/* Value to encode in EVEX RC bits, for SAE-only instructions. */
688static enum rc_type evexrcig = rne;
689
690/* Pre-defined "_GLOBAL_OFFSET_TABLE_". */
691static symbolS *GOT_symbol;
692
693/* The dwarf2 return column, adjusted for 32 or 64 bit. */
694unsigned int x86_dwarf2_return_column;
695
696/* The dwarf2 data alignment, adjusted for 32 or 64 bit. */
697int x86_cie_data_alignment;
698
699/* Interface to relax_segment.
700 There are 3 major relax states for 386 jump insns because the
701 different types of jumps add different sizes to frags when we're
702 figuring out what sort of jump to choose to reach a given label. */
703
704/* Types. */
705#define UNCOND_JUMP 0
706#define COND_JUMP 1
707#define COND_JUMP86 2
708
709/* Sizes. */
710#define CODE16 1
711#define SMALL 0
712#define SMALL16 (SMALL | CODE16)
713#define BIG 2
714#define BIG16 (BIG | CODE16)
715
716#ifndef INLINE
717#ifdef __GNUC__
718#define INLINE __inline__
719#else
720#define INLINE
721#endif
722#endif
723
724#define ENCODE_RELAX_STATE(type, size) \
725 ((relax_substateT) (((type) << 2) | (size)))
726#define TYPE_FROM_RELAX_STATE(s) \
727 ((s) >> 2)
728#define DISP_SIZE_FROM_RELAX_STATE(s) \
729 ((((s) & 3) == BIG ? 4 : (((s) & 3) == BIG16 ? 2 : 1)))
730
731/* This table is used by relax_frag to promote short jumps to long
732 ones where necessary. SMALL (short) jumps may be promoted to BIG
733 (32 bit long) ones, and SMALL16 jumps to BIG16 (16 bit long). We
734 don't allow a short jump in a 32 bit code segment to be promoted to
735 a 16 bit offset jump because it's slower (requires data size
736 prefix), and doesn't work, unless the destination is in the bottom
737 64k of the code segment (The top 16 bits of eip are zeroed). */
738
739const relax_typeS md_relax_table[] =
740{
741 /* The fields are:
742 1) most positive reach of this state,
743 2) most negative reach of this state,
744 3) how many bytes this mode will have in the variable part of the frag
745 4) which index into the table to try if we can't fit into this one. */
746
747 /* UNCOND_JUMP states. */
748 {127 + 1, -128 + 1, 1, ENCODE_RELAX_STATE (UNCOND_JUMP, BIG)},
749 {127 + 1, -128 + 1, 1, ENCODE_RELAX_STATE (UNCOND_JUMP, BIG16)},
750 /* dword jmp adds 4 bytes to frag:
751 0 extra opcode bytes, 4 displacement bytes. */
752 {0, 0, 4, 0},
753 /* word jmp adds 2 byte2 to frag:
754 0 extra opcode bytes, 2 displacement bytes. */
755 {0, 0, 2, 0},
756
757 /* COND_JUMP states. */
758 {127 + 1, -128 + 1, 1, ENCODE_RELAX_STATE (COND_JUMP, BIG)},
759 {127 + 1, -128 + 1, 1, ENCODE_RELAX_STATE (COND_JUMP, BIG16)},
760 /* dword conditionals adds 5 bytes to frag:
761 1 extra opcode byte, 4 displacement bytes. */
762 {0, 0, 5, 0},
763 /* word conditionals add 3 bytes to frag:
764 1 extra opcode byte, 2 displacement bytes. */
765 {0, 0, 3, 0},
766
767 /* COND_JUMP86 states. */
768 {127 + 1, -128 + 1, 1, ENCODE_RELAX_STATE (COND_JUMP86, BIG)},
769 {127 + 1, -128 + 1, 1, ENCODE_RELAX_STATE (COND_JUMP86, BIG16)},
770 /* dword conditionals adds 5 bytes to frag:
771 1 extra opcode byte, 4 displacement bytes. */
772 {0, 0, 5, 0},
773 /* word conditionals add 4 bytes to frag:
774 1 displacement byte and a 3 byte long branch insn. */
775 {0, 0, 4, 0}
776};
777
778static const arch_entry cpu_arch[] =
779{
780 /* Do not replace the first two entries - i386_target_format()
781 relies on them being there in this order. */
782 { STRING_COMMA_LEN ("generic32"), PROCESSOR_GENERIC32,
783 CPU_GENERIC32_FLAGS, 0 },
784 { STRING_COMMA_LEN ("generic64"), PROCESSOR_GENERIC64,
785 CPU_GENERIC64_FLAGS, 0 },
786 { STRING_COMMA_LEN ("i8086"), PROCESSOR_UNKNOWN,
787 CPU_NONE_FLAGS, 0 },
788 { STRING_COMMA_LEN ("i186"), PROCESSOR_UNKNOWN,
789 CPU_I186_FLAGS, 0 },
790 { STRING_COMMA_LEN ("i286"), PROCESSOR_UNKNOWN,
791 CPU_I286_FLAGS, 0 },
792 { STRING_COMMA_LEN ("i386"), PROCESSOR_I386,
793 CPU_I386_FLAGS, 0 },
794 { STRING_COMMA_LEN ("i486"), PROCESSOR_I486,
795 CPU_I486_FLAGS, 0 },
796 { STRING_COMMA_LEN ("i586"), PROCESSOR_PENTIUM,
797 CPU_I586_FLAGS, 0 },
798 { STRING_COMMA_LEN ("i686"), PROCESSOR_PENTIUMPRO,
799 CPU_I686_FLAGS, 0 },
800 { STRING_COMMA_LEN ("pentium"), PROCESSOR_PENTIUM,
801 CPU_I586_FLAGS, 0 },
802 { STRING_COMMA_LEN ("pentiumpro"), PROCESSOR_PENTIUMPRO,
803 CPU_PENTIUMPRO_FLAGS, 0 },
804 { STRING_COMMA_LEN ("pentiumii"), PROCESSOR_PENTIUMPRO,
805 CPU_P2_FLAGS, 0 },
806 { STRING_COMMA_LEN ("pentiumiii"),PROCESSOR_PENTIUMPRO,
807 CPU_P3_FLAGS, 0 },
808 { STRING_COMMA_LEN ("pentium4"), PROCESSOR_PENTIUM4,
809 CPU_P4_FLAGS, 0 },
810 { STRING_COMMA_LEN ("prescott"), PROCESSOR_NOCONA,
811 CPU_CORE_FLAGS, 0 },
812 { STRING_COMMA_LEN ("nocona"), PROCESSOR_NOCONA,
813 CPU_NOCONA_FLAGS, 0 },
814 { STRING_COMMA_LEN ("yonah"), PROCESSOR_CORE,
815 CPU_CORE_FLAGS, 1 },
816 { STRING_COMMA_LEN ("core"), PROCESSOR_CORE,
817 CPU_CORE_FLAGS, 0 },
818 { STRING_COMMA_LEN ("merom"), PROCESSOR_CORE2,
819 CPU_CORE2_FLAGS, 1 },
820 { STRING_COMMA_LEN ("core2"), PROCESSOR_CORE2,
821 CPU_CORE2_FLAGS, 0 },
822 { STRING_COMMA_LEN ("corei7"), PROCESSOR_COREI7,
823 CPU_COREI7_FLAGS, 0 },
824 { STRING_COMMA_LEN ("l1om"), PROCESSOR_L1OM,
825 CPU_L1OM_FLAGS, 0 },
826 { STRING_COMMA_LEN ("k1om"), PROCESSOR_K1OM,
827 CPU_K1OM_FLAGS, 0 },
828 { STRING_COMMA_LEN ("iamcu"), PROCESSOR_IAMCU,
829 CPU_IAMCU_FLAGS, 0 },
830 { STRING_COMMA_LEN ("k6"), PROCESSOR_K6,
831 CPU_K6_FLAGS, 0 },
832 { STRING_COMMA_LEN ("k6_2"), PROCESSOR_K6,
833 CPU_K6_2_FLAGS, 0 },
834 { STRING_COMMA_LEN ("athlon"), PROCESSOR_ATHLON,
835 CPU_ATHLON_FLAGS, 0 },
836 { STRING_COMMA_LEN ("sledgehammer"), PROCESSOR_K8,
837 CPU_K8_FLAGS, 1 },
838 { STRING_COMMA_LEN ("opteron"), PROCESSOR_K8,
839 CPU_K8_FLAGS, 0 },
840 { STRING_COMMA_LEN ("k8"), PROCESSOR_K8,
841 CPU_K8_FLAGS, 0 },
842 { STRING_COMMA_LEN ("amdfam10"), PROCESSOR_AMDFAM10,
843 CPU_AMDFAM10_FLAGS, 0 },
844 { STRING_COMMA_LEN ("bdver1"), PROCESSOR_BD,
845 CPU_BDVER1_FLAGS, 0 },
846 { STRING_COMMA_LEN ("bdver2"), PROCESSOR_BD,
847 CPU_BDVER2_FLAGS, 0 },
848 { STRING_COMMA_LEN ("bdver3"), PROCESSOR_BD,
849 CPU_BDVER3_FLAGS, 0 },
850 { STRING_COMMA_LEN ("bdver4"), PROCESSOR_BD,
851 CPU_BDVER4_FLAGS, 0 },
852 { STRING_COMMA_LEN ("znver1"), PROCESSOR_ZNVER,
853 CPU_ZNVER1_FLAGS, 0 },
854 { STRING_COMMA_LEN ("btver1"), PROCESSOR_BT,
855 CPU_BTVER1_FLAGS, 0 },
856 { STRING_COMMA_LEN ("btver2"), PROCESSOR_BT,
857 CPU_BTVER2_FLAGS, 0 },
858 { STRING_COMMA_LEN (".8087"), PROCESSOR_UNKNOWN,
859 CPU_8087_FLAGS, 0 },
860 { STRING_COMMA_LEN (".287"), PROCESSOR_UNKNOWN,
861 CPU_287_FLAGS, 0 },
862 { STRING_COMMA_LEN (".387"), PROCESSOR_UNKNOWN,
863 CPU_387_FLAGS, 0 },
864 { STRING_COMMA_LEN (".687"), PROCESSOR_UNKNOWN,
865 CPU_687_FLAGS, 0 },
866 { STRING_COMMA_LEN (".mmx"), PROCESSOR_UNKNOWN,
867 CPU_MMX_FLAGS, 0 },
868 { STRING_COMMA_LEN (".sse"), PROCESSOR_UNKNOWN,
869 CPU_SSE_FLAGS, 0 },
870 { STRING_COMMA_LEN (".sse2"), PROCESSOR_UNKNOWN,
871 CPU_SSE2_FLAGS, 0 },
872 { STRING_COMMA_LEN (".sse3"), PROCESSOR_UNKNOWN,
873 CPU_SSE3_FLAGS, 0 },
874 { STRING_COMMA_LEN (".ssse3"), PROCESSOR_UNKNOWN,
875 CPU_SSSE3_FLAGS, 0 },
876 { STRING_COMMA_LEN (".sse4.1"), PROCESSOR_UNKNOWN,
877 CPU_SSE4_1_FLAGS, 0 },
878 { STRING_COMMA_LEN (".sse4.2"), PROCESSOR_UNKNOWN,
879 CPU_SSE4_2_FLAGS, 0 },
880 { STRING_COMMA_LEN (".sse4"), PROCESSOR_UNKNOWN,
881 CPU_SSE4_2_FLAGS, 0 },
882 { STRING_COMMA_LEN (".avx"), PROCESSOR_UNKNOWN,
883 CPU_AVX_FLAGS, 0 },
884 { STRING_COMMA_LEN (".avx2"), PROCESSOR_UNKNOWN,
885 CPU_AVX2_FLAGS, 0 },
886 { STRING_COMMA_LEN (".avx512f"), PROCESSOR_UNKNOWN,
887 CPU_AVX512F_FLAGS, 0 },
888 { STRING_COMMA_LEN (".avx512cd"), PROCESSOR_UNKNOWN,
889 CPU_AVX512CD_FLAGS, 0 },
890 { STRING_COMMA_LEN (".avx512er"), PROCESSOR_UNKNOWN,
891 CPU_AVX512ER_FLAGS, 0 },
892 { STRING_COMMA_LEN (".avx512pf"), PROCESSOR_UNKNOWN,
893 CPU_AVX512PF_FLAGS, 0 },
894 { STRING_COMMA_LEN (".avx512dq"), PROCESSOR_UNKNOWN,
895 CPU_AVX512DQ_FLAGS, 0 },
896 { STRING_COMMA_LEN (".avx512bw"), PROCESSOR_UNKNOWN,
897 CPU_AVX512BW_FLAGS, 0 },
898 { STRING_COMMA_LEN (".avx512vl"), PROCESSOR_UNKNOWN,
899 CPU_AVX512VL_FLAGS, 0 },
900 { STRING_COMMA_LEN (".vmx"), PROCESSOR_UNKNOWN,
901 CPU_VMX_FLAGS, 0 },
902 { STRING_COMMA_LEN (".vmfunc"), PROCESSOR_UNKNOWN,
903 CPU_VMFUNC_FLAGS, 0 },
904 { STRING_COMMA_LEN (".smx"), PROCESSOR_UNKNOWN,
905 CPU_SMX_FLAGS, 0 },
906 { STRING_COMMA_LEN (".xsave"), PROCESSOR_UNKNOWN,
907 CPU_XSAVE_FLAGS, 0 },
908 { STRING_COMMA_LEN (".xsaveopt"), PROCESSOR_UNKNOWN,
909 CPU_XSAVEOPT_FLAGS, 0 },
910 { STRING_COMMA_LEN (".xsavec"), PROCESSOR_UNKNOWN,
911 CPU_XSAVEC_FLAGS, 0 },
912 { STRING_COMMA_LEN (".xsaves"), PROCESSOR_UNKNOWN,
913 CPU_XSAVES_FLAGS, 0 },
914 { STRING_COMMA_LEN (".aes"), PROCESSOR_UNKNOWN,
915 CPU_AES_FLAGS, 0 },
916 { STRING_COMMA_LEN (".pclmul"), PROCESSOR_UNKNOWN,
917 CPU_PCLMUL_FLAGS, 0 },
918 { STRING_COMMA_LEN (".clmul"), PROCESSOR_UNKNOWN,
919 CPU_PCLMUL_FLAGS, 1 },
920 { STRING_COMMA_LEN (".fsgsbase"), PROCESSOR_UNKNOWN,
921 CPU_FSGSBASE_FLAGS, 0 },
922 { STRING_COMMA_LEN (".rdrnd"), PROCESSOR_UNKNOWN,
923 CPU_RDRND_FLAGS, 0 },
924 { STRING_COMMA_LEN (".f16c"), PROCESSOR_UNKNOWN,
925 CPU_F16C_FLAGS, 0 },
926 { STRING_COMMA_LEN (".bmi2"), PROCESSOR_UNKNOWN,
927 CPU_BMI2_FLAGS, 0 },
928 { STRING_COMMA_LEN (".fma"), PROCESSOR_UNKNOWN,
929 CPU_FMA_FLAGS, 0 },
930 { STRING_COMMA_LEN (".fma4"), PROCESSOR_UNKNOWN,
931 CPU_FMA4_FLAGS, 0 },
932 { STRING_COMMA_LEN (".xop"), PROCESSOR_UNKNOWN,
933 CPU_XOP_FLAGS, 0 },
934 { STRING_COMMA_LEN (".lwp"), PROCESSOR_UNKNOWN,
935 CPU_LWP_FLAGS, 0 },
936 { STRING_COMMA_LEN (".movbe"), PROCESSOR_UNKNOWN,
937 CPU_MOVBE_FLAGS, 0 },
938 { STRING_COMMA_LEN (".cx16"), PROCESSOR_UNKNOWN,
939 CPU_CX16_FLAGS, 0 },
940 { STRING_COMMA_LEN (".ept"), PROCESSOR_UNKNOWN,
941 CPU_EPT_FLAGS, 0 },
942 { STRING_COMMA_LEN (".lzcnt"), PROCESSOR_UNKNOWN,
943 CPU_LZCNT_FLAGS, 0 },
944 { STRING_COMMA_LEN (".hle"), PROCESSOR_UNKNOWN,
945 CPU_HLE_FLAGS, 0 },
946 { STRING_COMMA_LEN (".rtm"), PROCESSOR_UNKNOWN,
947 CPU_RTM_FLAGS, 0 },
948 { STRING_COMMA_LEN (".invpcid"), PROCESSOR_UNKNOWN,
949 CPU_INVPCID_FLAGS, 0 },
950 { STRING_COMMA_LEN (".clflush"), PROCESSOR_UNKNOWN,
951 CPU_CLFLUSH_FLAGS, 0 },
952 { STRING_COMMA_LEN (".nop"), PROCESSOR_UNKNOWN,
953 CPU_NOP_FLAGS, 0 },
954 { STRING_COMMA_LEN (".syscall"), PROCESSOR_UNKNOWN,
955 CPU_SYSCALL_FLAGS, 0 },
956 { STRING_COMMA_LEN (".rdtscp"), PROCESSOR_UNKNOWN,
957 CPU_RDTSCP_FLAGS, 0 },
958 { STRING_COMMA_LEN (".3dnow"), PROCESSOR_UNKNOWN,
959 CPU_3DNOW_FLAGS, 0 },
960 { STRING_COMMA_LEN (".3dnowa"), PROCESSOR_UNKNOWN,
961 CPU_3DNOWA_FLAGS, 0 },
962 { STRING_COMMA_LEN (".padlock"), PROCESSOR_UNKNOWN,
963 CPU_PADLOCK_FLAGS, 0 },
964 { STRING_COMMA_LEN (".pacifica"), PROCESSOR_UNKNOWN,
965 CPU_SVME_FLAGS, 1 },
966 { STRING_COMMA_LEN (".svme"), PROCESSOR_UNKNOWN,
967 CPU_SVME_FLAGS, 0 },
968 { STRING_COMMA_LEN (".sse4a"), PROCESSOR_UNKNOWN,
969 CPU_SSE4A_FLAGS, 0 },
970 { STRING_COMMA_LEN (".abm"), PROCESSOR_UNKNOWN,
971 CPU_ABM_FLAGS, 0 },
972 { STRING_COMMA_LEN (".bmi"), PROCESSOR_UNKNOWN,
973 CPU_BMI_FLAGS, 0 },
974 { STRING_COMMA_LEN (".tbm"), PROCESSOR_UNKNOWN,
975 CPU_TBM_FLAGS, 0 },
976 { STRING_COMMA_LEN (".adx"), PROCESSOR_UNKNOWN,
977 CPU_ADX_FLAGS, 0 },
978 { STRING_COMMA_LEN (".rdseed"), PROCESSOR_UNKNOWN,
979 CPU_RDSEED_FLAGS, 0 },
980 { STRING_COMMA_LEN (".prfchw"), PROCESSOR_UNKNOWN,
981 CPU_PRFCHW_FLAGS, 0 },
982 { STRING_COMMA_LEN (".smap"), PROCESSOR_UNKNOWN,
983 CPU_SMAP_FLAGS, 0 },
984 { STRING_COMMA_LEN (".mpx"), PROCESSOR_UNKNOWN,
985 CPU_MPX_FLAGS, 0 },
986 { STRING_COMMA_LEN (".sha"), PROCESSOR_UNKNOWN,
987 CPU_SHA_FLAGS, 0 },
988 { STRING_COMMA_LEN (".clflushopt"), PROCESSOR_UNKNOWN,
989 CPU_CLFLUSHOPT_FLAGS, 0 },
990 { STRING_COMMA_LEN (".prefetchwt1"), PROCESSOR_UNKNOWN,
991 CPU_PREFETCHWT1_FLAGS, 0 },
992 { STRING_COMMA_LEN (".se1"), PROCESSOR_UNKNOWN,
993 CPU_SE1_FLAGS, 0 },
994 { STRING_COMMA_LEN (".clwb"), PROCESSOR_UNKNOWN,
995 CPU_CLWB_FLAGS, 0 },
996 { STRING_COMMA_LEN (".avx512ifma"), PROCESSOR_UNKNOWN,
997 CPU_AVX512IFMA_FLAGS, 0 },
998 { STRING_COMMA_LEN (".avx512vbmi"), PROCESSOR_UNKNOWN,
999 CPU_AVX512VBMI_FLAGS, 0 },
1000 { STRING_COMMA_LEN (".avx512_4fmaps"), PROCESSOR_UNKNOWN,
1001 CPU_AVX512_4FMAPS_FLAGS, 0 },
1002 { STRING_COMMA_LEN (".avx512_4vnniw"), PROCESSOR_UNKNOWN,
1003 CPU_AVX512_4VNNIW_FLAGS, 0 },
1004 { STRING_COMMA_LEN (".avx512_vpopcntdq"), PROCESSOR_UNKNOWN,
1005 CPU_AVX512_VPOPCNTDQ_FLAGS, 0 },
1006 { STRING_COMMA_LEN (".avx512_vbmi2"), PROCESSOR_UNKNOWN,
1007 CPU_AVX512_VBMI2_FLAGS, 0 },
1008 { STRING_COMMA_LEN (".avx512_vnni"), PROCESSOR_UNKNOWN,
1009 CPU_AVX512_VNNI_FLAGS, 0 },
1010 { STRING_COMMA_LEN (".avx512_bitalg"), PROCESSOR_UNKNOWN,
1011 CPU_AVX512_BITALG_FLAGS, 0 },
1012 { STRING_COMMA_LEN (".clzero"), PROCESSOR_UNKNOWN,
1013 CPU_CLZERO_FLAGS, 0 },
1014 { STRING_COMMA_LEN (".mwaitx"), PROCESSOR_UNKNOWN,
1015 CPU_MWAITX_FLAGS, 0 },
1016 { STRING_COMMA_LEN (".ospke"), PROCESSOR_UNKNOWN,
1017 CPU_OSPKE_FLAGS, 0 },
1018 { STRING_COMMA_LEN (".rdpid"), PROCESSOR_UNKNOWN,
1019 CPU_RDPID_FLAGS, 0 },
1020 { STRING_COMMA_LEN (".ptwrite"), PROCESSOR_UNKNOWN,
1021 CPU_PTWRITE_FLAGS, 0 },
1022 { STRING_COMMA_LEN (".ibt"), PROCESSOR_UNKNOWN,
1023 CPU_IBT_FLAGS, 0 },
1024 { STRING_COMMA_LEN (".shstk"), PROCESSOR_UNKNOWN,
1025 CPU_SHSTK_FLAGS, 0 },
1026 { STRING_COMMA_LEN (".gfni"), PROCESSOR_UNKNOWN,
1027 CPU_GFNI_FLAGS, 0 },
1028 { STRING_COMMA_LEN (".vaes"), PROCESSOR_UNKNOWN,
1029 CPU_VAES_FLAGS, 0 },
1030 { STRING_COMMA_LEN (".vpclmulqdq"), PROCESSOR_UNKNOWN,
1031 CPU_VPCLMULQDQ_FLAGS, 0 },
1032 { STRING_COMMA_LEN (".wbnoinvd"), PROCESSOR_UNKNOWN,
1033 CPU_WBNOINVD_FLAGS, 0 },
1034 { STRING_COMMA_LEN (".pconfig"), PROCESSOR_UNKNOWN,
1035 CPU_PCONFIG_FLAGS, 0 },
1036};
1037
1038static const noarch_entry cpu_noarch[] =
1039{
1040 { STRING_COMMA_LEN ("no87"), CPU_ANY_X87_FLAGS },
1041 { STRING_COMMA_LEN ("no287"), CPU_ANY_287_FLAGS },
1042 { STRING_COMMA_LEN ("no387"), CPU_ANY_387_FLAGS },
1043 { STRING_COMMA_LEN ("no687"), CPU_ANY_687_FLAGS },
1044 { STRING_COMMA_LEN ("nommx"), CPU_ANY_MMX_FLAGS },
1045 { STRING_COMMA_LEN ("nosse"), CPU_ANY_SSE_FLAGS },
1046 { STRING_COMMA_LEN ("nosse2"), CPU_ANY_SSE2_FLAGS },
1047 { STRING_COMMA_LEN ("nosse3"), CPU_ANY_SSE3_FLAGS },
1048 { STRING_COMMA_LEN ("nossse3"), CPU_ANY_SSSE3_FLAGS },
1049 { STRING_COMMA_LEN ("nosse4.1"), CPU_ANY_SSE4_1_FLAGS },
1050 { STRING_COMMA_LEN ("nosse4.2"), CPU_ANY_SSE4_2_FLAGS },
1051 { STRING_COMMA_LEN ("nosse4"), CPU_ANY_SSE4_1_FLAGS },
1052 { STRING_COMMA_LEN ("noavx"), CPU_ANY_AVX_FLAGS },
1053 { STRING_COMMA_LEN ("noavx2"), CPU_ANY_AVX2_FLAGS },
1054 { STRING_COMMA_LEN ("noavx512f"), CPU_ANY_AVX512F_FLAGS },
1055 { STRING_COMMA_LEN ("noavx512cd"), CPU_ANY_AVX512CD_FLAGS },
1056 { STRING_COMMA_LEN ("noavx512er"), CPU_ANY_AVX512ER_FLAGS },
1057 { STRING_COMMA_LEN ("noavx512pf"), CPU_ANY_AVX512PF_FLAGS },
1058 { STRING_COMMA_LEN ("noavx512dq"), CPU_ANY_AVX512DQ_FLAGS },
1059 { STRING_COMMA_LEN ("noavx512bw"), CPU_ANY_AVX512BW_FLAGS },
1060 { STRING_COMMA_LEN ("noavx512vl"), CPU_ANY_AVX512VL_FLAGS },
1061 { STRING_COMMA_LEN ("noavx512ifma"), CPU_ANY_AVX512IFMA_FLAGS },
1062 { STRING_COMMA_LEN ("noavx512vbmi"), CPU_ANY_AVX512VBMI_FLAGS },
1063 { STRING_COMMA_LEN ("noavx512_4fmaps"), CPU_ANY_AVX512_4FMAPS_FLAGS },
1064 { STRING_COMMA_LEN ("noavx512_4vnniw"), CPU_ANY_AVX512_4VNNIW_FLAGS },
1065 { STRING_COMMA_LEN ("noavx512_vpopcntdq"), CPU_ANY_AVX512_VPOPCNTDQ_FLAGS },
1066 { STRING_COMMA_LEN ("noavx512_vbmi2"), CPU_ANY_AVX512_VBMI2_FLAGS },
1067 { STRING_COMMA_LEN ("noavx512_vnni"), CPU_ANY_AVX512_VNNI_FLAGS },
1068 { STRING_COMMA_LEN ("noavx512_bitalg"), CPU_ANY_AVX512_BITALG_FLAGS },
1069 { STRING_COMMA_LEN ("noibt"), CPU_ANY_IBT_FLAGS },
1070 { STRING_COMMA_LEN ("noshstk"), CPU_ANY_SHSTK_FLAGS },
1071};
1072
1073#ifdef I386COFF
1074/* Like s_lcomm_internal in gas/read.c but the alignment string
1075 is allowed to be optional. */
1076
1077static symbolS *
1078pe_lcomm_internal (int needs_align, symbolS *symbolP, addressT size)
1079{
1080 addressT align = 0;
1081
1082 SKIP_WHITESPACE ();
1083
1084 if (needs_align
1085 && *input_line_pointer == ',')
1086 {
1087 align = parse_align (needs_align - 1);
1088
1089 if (align == (addressT) -1)
1090 return NULL;
1091 }
1092 else
1093 {
1094 if (size >= 8)
1095 align = 3;
1096 else if (size >= 4)
1097 align = 2;
1098 else if (size >= 2)
1099 align = 1;
1100 else
1101 align = 0;
1102 }
1103
1104 bss_alloc (symbolP, size, align);
1105 return symbolP;
1106}
1107
1108static void
1109pe_lcomm (int needs_align)
1110{
1111 s_comm_internal (needs_align * 2, pe_lcomm_internal);
1112}
1113#endif
1114
1115const pseudo_typeS md_pseudo_table[] =
1116{
1117#if !defined(OBJ_AOUT) && !defined(USE_ALIGN_PTWO)
1118 {"align", s_align_bytes, 0},
1119#else
1120 {"align", s_align_ptwo, 0},
1121#endif
1122 {"arch", set_cpu_arch, 0},
1123#ifndef I386COFF
1124 {"bss", s_bss, 0},
1125#else
1126 {"lcomm", pe_lcomm, 1},
1127#endif
1128 {"ffloat", float_cons, 'f'},
1129 {"dfloat", float_cons, 'd'},
1130 {"tfloat", float_cons, 'x'},
1131 {"value", cons, 2},
1132 {"slong", signed_cons, 4},
1133 {"noopt", s_ignore, 0},
1134 {"optim", s_ignore, 0},
1135 {"code16gcc", set_16bit_gcc_code_flag, CODE_16BIT},
1136 {"code16", set_code_flag, CODE_16BIT},
1137 {"code32", set_code_flag, CODE_32BIT},
1138#ifdef BFD64
1139 {"code64", set_code_flag, CODE_64BIT},
1140#endif
1141 {"intel_syntax", set_intel_syntax, 1},
1142 {"att_syntax", set_intel_syntax, 0},
1143 {"intel_mnemonic", set_intel_mnemonic, 1},
1144 {"att_mnemonic", set_intel_mnemonic, 0},
1145 {"allow_index_reg", set_allow_index_reg, 1},
1146 {"disallow_index_reg", set_allow_index_reg, 0},
1147 {"sse_check", set_check, 0},
1148 {"operand_check", set_check, 1},
1149#if defined (OBJ_ELF) || defined (OBJ_MAYBE_ELF)
1150 {"largecomm", handle_large_common, 0},
1151#else
1152 {"file", dwarf2_directive_file, 0},
1153 {"loc", dwarf2_directive_loc, 0},
1154 {"loc_mark_labels", dwarf2_directive_loc_mark_labels, 0},
1155#endif
1156#ifdef TE_PE
1157 {"secrel32", pe_directive_secrel, 0},
1158#endif
1159 {0, 0, 0}
1160};
1161
1162/* For interface with expression (). */
1163extern char *input_line_pointer;
1164
1165/* Hash table for instruction mnemonic lookup. */
1166static struct hash_control *op_hash;
1167
1168/* Hash table for register lookup. */
1169static struct hash_control *reg_hash;
1170\f
1171 /* Various efficient no-op patterns for aligning code labels.
1172 Note: Don't try to assemble the instructions in the comments.
1173 0L and 0w are not legal. */
1174static const unsigned char f32_1[] =
1175 {0x90}; /* nop */
1176static const unsigned char f32_2[] =
1177 {0x66,0x90}; /* xchg %ax,%ax */
1178static const unsigned char f32_3[] =
1179 {0x8d,0x76,0x00}; /* leal 0(%esi),%esi */
1180static const unsigned char f32_4[] =
1181 {0x8d,0x74,0x26,0x00}; /* leal 0(%esi,1),%esi */
1182static const unsigned char f32_5[] =
1183 {0x90, /* nop */
1184 0x8d,0x74,0x26,0x00}; /* leal 0(%esi,1),%esi */
1185static const unsigned char f32_6[] =
1186 {0x8d,0xb6,0x00,0x00,0x00,0x00}; /* leal 0L(%esi),%esi */
1187static const unsigned char f32_7[] =
1188 {0x8d,0xb4,0x26,0x00,0x00,0x00,0x00}; /* leal 0L(%esi,1),%esi */
1189static const unsigned char f32_8[] =
1190 {0x90, /* nop */
1191 0x8d,0xb4,0x26,0x00,0x00,0x00,0x00}; /* leal 0L(%esi,1),%esi */
1192static const unsigned char f32_9[] =
1193 {0x89,0xf6, /* movl %esi,%esi */
1194 0x8d,0xbc,0x27,0x00,0x00,0x00,0x00}; /* leal 0L(%edi,1),%edi */
1195static const unsigned char f32_10[] =
1196 {0x8d,0x76,0x00, /* leal 0(%esi),%esi */
1197 0x8d,0xbc,0x27,0x00,0x00,0x00,0x00}; /* leal 0L(%edi,1),%edi */
1198static const unsigned char f32_11[] =
1199 {0x8d,0x74,0x26,0x00, /* leal 0(%esi,1),%esi */
1200 0x8d,0xbc,0x27,0x00,0x00,0x00,0x00}; /* leal 0L(%edi,1),%edi */
1201static const unsigned char f32_12[] =
1202 {0x8d,0xb6,0x00,0x00,0x00,0x00, /* leal 0L(%esi),%esi */
1203 0x8d,0xbf,0x00,0x00,0x00,0x00}; /* leal 0L(%edi),%edi */
1204static const unsigned char f32_13[] =
1205 {0x8d,0xb6,0x00,0x00,0x00,0x00, /* leal 0L(%esi),%esi */
1206 0x8d,0xbc,0x27,0x00,0x00,0x00,0x00}; /* leal 0L(%edi,1),%edi */
1207static const unsigned char f32_14[] =
1208 {0x8d,0xb4,0x26,0x00,0x00,0x00,0x00, /* leal 0L(%esi,1),%esi */
1209 0x8d,0xbc,0x27,0x00,0x00,0x00,0x00}; /* leal 0L(%edi,1),%edi */
1210static const unsigned char f16_3[] =
1211 {0x8d,0x74,0x00}; /* lea 0(%esi),%esi */
1212static const unsigned char f16_4[] =
1213 {0x8d,0xb4,0x00,0x00}; /* lea 0w(%si),%si */
1214static const unsigned char f16_5[] =
1215 {0x90, /* nop */
1216 0x8d,0xb4,0x00,0x00}; /* lea 0w(%si),%si */
1217static const unsigned char f16_6[] =
1218 {0x89,0xf6, /* mov %si,%si */
1219 0x8d,0xbd,0x00,0x00}; /* lea 0w(%di),%di */
1220static const unsigned char f16_7[] =
1221 {0x8d,0x74,0x00, /* lea 0(%si),%si */
1222 0x8d,0xbd,0x00,0x00}; /* lea 0w(%di),%di */
1223static const unsigned char f16_8[] =
1224 {0x8d,0xb4,0x00,0x00, /* lea 0w(%si),%si */
1225 0x8d,0xbd,0x00,0x00}; /* lea 0w(%di),%di */
1226static const unsigned char jump_31[] =
1227 {0xeb,0x1d,0x90,0x90,0x90,0x90,0x90, /* jmp .+31; lotsa nops */
1228 0x90,0x90,0x90,0x90,0x90,0x90,0x90,0x90,
1229 0x90,0x90,0x90,0x90,0x90,0x90,0x90,0x90,
1230 0x90,0x90,0x90,0x90,0x90,0x90,0x90,0x90};
1231/* 32-bit NOPs patterns. */
1232static const unsigned char *const f32_patt[] = {
1233 f32_1, f32_2, f32_3, f32_4, f32_5, f32_6, f32_7, f32_8,
1234 f32_9, f32_10, f32_11, f32_12, f32_13, f32_14
1235};
1236/* 16-bit NOPs patterns. */
1237static const unsigned char *const f16_patt[] = {
1238 f32_1, f32_2, f16_3, f16_4, f16_5, f16_6, f16_7, f16_8
1239};
1240/* nopl (%[re]ax) */
1241static const unsigned char alt_3[] =
1242 {0x0f,0x1f,0x00};
1243/* nopl 0(%[re]ax) */
1244static const unsigned char alt_4[] =
1245 {0x0f,0x1f,0x40,0x00};
1246/* nopl 0(%[re]ax,%[re]ax,1) */
1247static const unsigned char alt_5[] =
1248 {0x0f,0x1f,0x44,0x00,0x00};
1249/* nopw 0(%[re]ax,%[re]ax,1) */
1250static const unsigned char alt_6[] =
1251 {0x66,0x0f,0x1f,0x44,0x00,0x00};
1252/* nopl 0L(%[re]ax) */
1253static const unsigned char alt_7[] =
1254 {0x0f,0x1f,0x80,0x00,0x00,0x00,0x00};
1255/* nopl 0L(%[re]ax,%[re]ax,1) */
1256static const unsigned char alt_8[] =
1257 {0x0f,0x1f,0x84,0x00,0x00,0x00,0x00,0x00};
1258/* nopw 0L(%[re]ax,%[re]ax,1) */
1259static const unsigned char alt_9[] =
1260 {0x66,0x0f,0x1f,0x84,0x00,0x00,0x00,0x00,0x00};
1261/* nopw %cs:0L(%[re]ax,%[re]ax,1) */
1262static const unsigned char alt_10[] =
1263 {0x66,0x2e,0x0f,0x1f,0x84,0x00,0x00,0x00,0x00,0x00};
1264/* 32-bit and 64-bit NOPs patterns. */
1265static const unsigned char *const alt_patt[] = {
1266 f32_1, f32_2, alt_3, alt_4, alt_5, alt_6, alt_7, alt_8,
1267 alt_9, alt_10
1268};
1269/* 64-bit only: nopw %cs:0L(%eax,%eax,1) */
1270static const unsigned char alt64_11[] =
1271 {0x67,0x66,0x2e,0x0f,0x1f,0x84,0x00,0x00,0x00,0x00,0x00};
1272/* 64-bit NOPs patterns. */
1273static const unsigned char *const alt64_patt[] = {
1274 f32_1, f32_2, alt_3, alt_4, alt_5, alt_6, alt_7, alt_8,
1275 alt_9, alt_10, alt64_11
1276};
1277
1278/* Genenerate COUNT bytes of NOPs to WHERE from PATT with the maximum
1279 size of a single NOP instruction MAX_SINGLE_NOP_SIZE. */
1280
1281static void
1282i386_output_nops (char *where, const unsigned char *const *patt,
1283 int count, int max_single_nop_size)
1284
1285{
1286 while (count > max_single_nop_size)
1287 {
1288 count -= max_single_nop_size;
1289 memcpy (where + count, patt[max_single_nop_size - 1],
1290 max_single_nop_size);
1291 }
1292
1293 if (count)
1294 memcpy (where, patt[count - 1], count);
1295}
1296
1297
1298/* Genenerate COUNT bytes of NOPs to WHERE with the maximum size of a
1299 single NOP instruction LIMIT. */
1300
1301void
1302i386_generate_nops (fragS *f, char *where, offsetT count, int limit)
1303{
1304 /* Output NOPs for .nop directive. */
1305 int max_single_nop_size;
1306 const unsigned char *const *patt;
1307
1308 if (flag_code == CODE_16BIT)
1309 {
1310 patt = f16_patt;
1311 max_single_nop_size = sizeof (f16_patt) / sizeof (f16_patt[0]);
1312 }
1313 else if (flag_code == CODE_64BIT)
1314 {
1315 patt = alt64_patt;
1316 max_single_nop_size = sizeof (alt64_patt) / sizeof (alt64_patt[0]);
1317 }
1318 else
1319 {
1320 patt = alt_patt;
1321 max_single_nop_size = sizeof (alt_patt) / sizeof (alt_patt[0]);
1322 }
1323 if (limit == 0)
1324 limit = max_single_nop_size;
1325 else if (limit > max_single_nop_size)
1326 {
1327 as_bad_where (f->fr_file, f->fr_line,
1328 _("invalide single nop size: %d (expect within [0, %d])"),
1329 limit, max_single_nop_size);
1330 return;
1331 }
1332
1333 i386_output_nops (where, patt, count, limit);
1334}
1335
1336void
1337i386_align_code (fragS *fragP, int count)
1338{
1339 /* Only align for at least a positive non-zero boundary. */
1340 if (count <= 0 || count > MAX_MEM_FOR_RS_ALIGN_CODE)
1341 return;
1342
1343 /* We need to decide which NOP sequence to use for 32bit and
1344 64bit. When -mtune= is used:
1345
1346 1. For PROCESSOR_I386, PROCESSOR_I486, PROCESSOR_PENTIUM and
1347 PROCESSOR_GENERIC32, f32_patt will be used.
1348 2. For the rest, alt_patt will be used.
1349
1350 When -mtune= isn't used, alt_patt will be used if
1351 cpu_arch_isa_flags has CpuNop. Otherwise, f32_patt will
1352 be used.
1353
1354 When -march= or .arch is used, we can't use anything beyond
1355 cpu_arch_isa_flags. */
1356
1357 if (flag_code == CODE_16BIT)
1358 {
1359 if (count > 8)
1360 {
1361 memcpy (fragP->fr_literal + fragP->fr_fix,
1362 jump_31, count);
1363 /* Adjust jump offset. */
1364 fragP->fr_literal[fragP->fr_fix + 1] = count - 2;
1365 }
1366 else
1367 memcpy (fragP->fr_literal + fragP->fr_fix,
1368 f16_patt[count - 1], count);
1369 }
1370 else
1371 {
1372 const unsigned char *const *patt = NULL;
1373
1374 if (fragP->tc_frag_data.isa == PROCESSOR_UNKNOWN)
1375 {
1376 /* PROCESSOR_UNKNOWN means that all ISAs may be used. */
1377 switch (cpu_arch_tune)
1378 {
1379 case PROCESSOR_UNKNOWN:
1380 /* We use cpu_arch_isa_flags to check if we SHOULD
1381 optimize with nops. */
1382 if (fragP->tc_frag_data.isa_flags.bitfield.cpunop)
1383 patt = alt_patt;
1384 else
1385 patt = f32_patt;
1386 break;
1387 case PROCESSOR_PENTIUM4:
1388 case PROCESSOR_NOCONA:
1389 case PROCESSOR_CORE:
1390 case PROCESSOR_CORE2:
1391 case PROCESSOR_COREI7:
1392 case PROCESSOR_L1OM:
1393 case PROCESSOR_K1OM:
1394 case PROCESSOR_GENERIC64:
1395 case PROCESSOR_K6:
1396 case PROCESSOR_ATHLON:
1397 case PROCESSOR_K8:
1398 case PROCESSOR_AMDFAM10:
1399 case PROCESSOR_BD:
1400 case PROCESSOR_ZNVER:
1401 case PROCESSOR_BT:
1402 patt = alt_patt;
1403 break;
1404 case PROCESSOR_I386:
1405 case PROCESSOR_I486:
1406 case PROCESSOR_PENTIUM:
1407 case PROCESSOR_PENTIUMPRO:
1408 case PROCESSOR_IAMCU:
1409 case PROCESSOR_GENERIC32:
1410 patt = f32_patt;
1411 break;
1412 }
1413 }
1414 else
1415 {
1416 switch (fragP->tc_frag_data.tune)
1417 {
1418 case PROCESSOR_UNKNOWN:
1419 /* When cpu_arch_isa is set, cpu_arch_tune shouldn't be
1420 PROCESSOR_UNKNOWN. */
1421 abort ();
1422 break;
1423
1424 case PROCESSOR_I386:
1425 case PROCESSOR_I486:
1426 case PROCESSOR_PENTIUM:
1427 case PROCESSOR_IAMCU:
1428 case PROCESSOR_K6:
1429 case PROCESSOR_ATHLON:
1430 case PROCESSOR_K8:
1431 case PROCESSOR_AMDFAM10:
1432 case PROCESSOR_BD:
1433 case PROCESSOR_ZNVER:
1434 case PROCESSOR_BT:
1435 case PROCESSOR_GENERIC32:
1436 /* We use cpu_arch_isa_flags to check if we CAN optimize
1437 with nops. */
1438 if (fragP->tc_frag_data.isa_flags.bitfield.cpunop)
1439 patt = alt_patt;
1440 else
1441 patt = f32_patt;
1442 break;
1443 case PROCESSOR_PENTIUMPRO:
1444 case PROCESSOR_PENTIUM4:
1445 case PROCESSOR_NOCONA:
1446 case PROCESSOR_CORE:
1447 case PROCESSOR_CORE2:
1448 case PROCESSOR_COREI7:
1449 case PROCESSOR_L1OM:
1450 case PROCESSOR_K1OM:
1451 if (fragP->tc_frag_data.isa_flags.bitfield.cpunop)
1452 patt = alt_patt;
1453 else
1454 patt = f32_patt;
1455 break;
1456 case PROCESSOR_GENERIC64:
1457 patt = alt_patt;
1458 break;
1459 }
1460 }
1461
1462 if (patt == f32_patt)
1463 {
1464 /* If the padding is less than 15 bytes, we use the normal
1465 ones. Otherwise, we use a jump instruction and adjust
1466 its offset. */
1467 int limit;
1468
1469 /* For 64bit, the limit is 3 bytes. */
1470 if (flag_code == CODE_64BIT
1471 && fragP->tc_frag_data.isa_flags.bitfield.cpulm)
1472 limit = 3;
1473 else
1474 limit = 15;
1475 if (count < limit)
1476 memcpy (fragP->fr_literal + fragP->fr_fix,
1477 patt[count - 1], count);
1478 else
1479 {
1480 memcpy (fragP->fr_literal + fragP->fr_fix,
1481 jump_31, count);
1482 /* Adjust jump offset. */
1483 fragP->fr_literal[fragP->fr_fix + 1] = count - 2;
1484 }
1485 }
1486 else
1487 {
1488 /* Maximum length of an instruction is 10 byte. If the
1489 padding is greater than 10 bytes and we don't use jump,
1490 we have to break it into smaller pieces. */
1491 i386_output_nops (fragP->fr_literal + fragP->fr_fix,
1492 patt, count, 10);
1493 }
1494 }
1495 fragP->fr_var = count;
1496}
1497
1498static INLINE int
1499operand_type_all_zero (const union i386_operand_type *x)
1500{
1501 switch (ARRAY_SIZE(x->array))
1502 {
1503 case 3:
1504 if (x->array[2])
1505 return 0;
1506 /* Fall through. */
1507 case 2:
1508 if (x->array[1])
1509 return 0;
1510 /* Fall through. */
1511 case 1:
1512 return !x->array[0];
1513 default:
1514 abort ();
1515 }
1516}
1517
1518static INLINE void
1519operand_type_set (union i386_operand_type *x, unsigned int v)
1520{
1521 switch (ARRAY_SIZE(x->array))
1522 {
1523 case 3:
1524 x->array[2] = v;
1525 /* Fall through. */
1526 case 2:
1527 x->array[1] = v;
1528 /* Fall through. */
1529 case 1:
1530 x->array[0] = v;
1531 /* Fall through. */
1532 break;
1533 default:
1534 abort ();
1535 }
1536}
1537
1538static INLINE int
1539operand_type_equal (const union i386_operand_type *x,
1540 const union i386_operand_type *y)
1541{
1542 switch (ARRAY_SIZE(x->array))
1543 {
1544 case 3:
1545 if (x->array[2] != y->array[2])
1546 return 0;
1547 /* Fall through. */
1548 case 2:
1549 if (x->array[1] != y->array[1])
1550 return 0;
1551 /* Fall through. */
1552 case 1:
1553 return x->array[0] == y->array[0];
1554 break;
1555 default:
1556 abort ();
1557 }
1558}
1559
1560static INLINE int
1561cpu_flags_all_zero (const union i386_cpu_flags *x)
1562{
1563 switch (ARRAY_SIZE(x->array))
1564 {
1565 case 4:
1566 if (x->array[3])
1567 return 0;
1568 /* Fall through. */
1569 case 3:
1570 if (x->array[2])
1571 return 0;
1572 /* Fall through. */
1573 case 2:
1574 if (x->array[1])
1575 return 0;
1576 /* Fall through. */
1577 case 1:
1578 return !x->array[0];
1579 default:
1580 abort ();
1581 }
1582}
1583
1584static INLINE int
1585cpu_flags_equal (const union i386_cpu_flags *x,
1586 const union i386_cpu_flags *y)
1587{
1588 switch (ARRAY_SIZE(x->array))
1589 {
1590 case 4:
1591 if (x->array[3] != y->array[3])
1592 return 0;
1593 /* Fall through. */
1594 case 3:
1595 if (x->array[2] != y->array[2])
1596 return 0;
1597 /* Fall through. */
1598 case 2:
1599 if (x->array[1] != y->array[1])
1600 return 0;
1601 /* Fall through. */
1602 case 1:
1603 return x->array[0] == y->array[0];
1604 break;
1605 default:
1606 abort ();
1607 }
1608}
1609
1610static INLINE int
1611cpu_flags_check_cpu64 (i386_cpu_flags f)
1612{
1613 return !((flag_code == CODE_64BIT && f.bitfield.cpuno64)
1614 || (flag_code != CODE_64BIT && f.bitfield.cpu64));
1615}
1616
1617static INLINE i386_cpu_flags
1618cpu_flags_and (i386_cpu_flags x, i386_cpu_flags y)
1619{
1620 switch (ARRAY_SIZE (x.array))
1621 {
1622 case 4:
1623 x.array [3] &= y.array [3];
1624 /* Fall through. */
1625 case 3:
1626 x.array [2] &= y.array [2];
1627 /* Fall through. */
1628 case 2:
1629 x.array [1] &= y.array [1];
1630 /* Fall through. */
1631 case 1:
1632 x.array [0] &= y.array [0];
1633 break;
1634 default:
1635 abort ();
1636 }
1637 return x;
1638}
1639
1640static INLINE i386_cpu_flags
1641cpu_flags_or (i386_cpu_flags x, i386_cpu_flags y)
1642{
1643 switch (ARRAY_SIZE (x.array))
1644 {
1645 case 4:
1646 x.array [3] |= y.array [3];
1647 /* Fall through. */
1648 case 3:
1649 x.array [2] |= y.array [2];
1650 /* Fall through. */
1651 case 2:
1652 x.array [1] |= y.array [1];
1653 /* Fall through. */
1654 case 1:
1655 x.array [0] |= y.array [0];
1656 break;
1657 default:
1658 abort ();
1659 }
1660 return x;
1661}
1662
1663static INLINE i386_cpu_flags
1664cpu_flags_and_not (i386_cpu_flags x, i386_cpu_flags y)
1665{
1666 switch (ARRAY_SIZE (x.array))
1667 {
1668 case 4:
1669 x.array [3] &= ~y.array [3];
1670 /* Fall through. */
1671 case 3:
1672 x.array [2] &= ~y.array [2];
1673 /* Fall through. */
1674 case 2:
1675 x.array [1] &= ~y.array [1];
1676 /* Fall through. */
1677 case 1:
1678 x.array [0] &= ~y.array [0];
1679 break;
1680 default:
1681 abort ();
1682 }
1683 return x;
1684}
1685
1686#define CPU_FLAGS_ARCH_MATCH 0x1
1687#define CPU_FLAGS_64BIT_MATCH 0x2
1688#define CPU_FLAGS_AES_MATCH 0x4
1689#define CPU_FLAGS_PCLMUL_MATCH 0x8
1690#define CPU_FLAGS_AVX_MATCH 0x10
1691
1692#define CPU_FLAGS_32BIT_MATCH \
1693 (CPU_FLAGS_ARCH_MATCH | CPU_FLAGS_AES_MATCH \
1694 | CPU_FLAGS_PCLMUL_MATCH | CPU_FLAGS_AVX_MATCH)
1695#define CPU_FLAGS_PERFECT_MATCH \
1696 (CPU_FLAGS_32BIT_MATCH | CPU_FLAGS_64BIT_MATCH)
1697
1698/* Return CPU flags match bits. */
1699
1700static int
1701cpu_flags_match (const insn_template *t)
1702{
1703 i386_cpu_flags x = t->cpu_flags;
1704 int match = cpu_flags_check_cpu64 (x) ? CPU_FLAGS_64BIT_MATCH : 0;
1705
1706 x.bitfield.cpu64 = 0;
1707 x.bitfield.cpuno64 = 0;
1708
1709 if (cpu_flags_all_zero (&x))
1710 {
1711 /* This instruction is available on all archs. */
1712 match |= CPU_FLAGS_32BIT_MATCH;
1713 }
1714 else
1715 {
1716 /* This instruction is available only on some archs. */
1717 i386_cpu_flags cpu = cpu_arch_flags;
1718
1719 cpu = cpu_flags_and (x, cpu);
1720 if (!cpu_flags_all_zero (&cpu))
1721 {
1722 if (x.bitfield.cpuavx)
1723 {
1724 /* We only need to check AES/PCLMUL/SSE2AVX with AVX. */
1725 if (cpu.bitfield.cpuavx)
1726 {
1727 /* Check SSE2AVX. */
1728 if (!t->opcode_modifier.sse2avx|| sse2avx)
1729 {
1730 match |= (CPU_FLAGS_ARCH_MATCH
1731 | CPU_FLAGS_AVX_MATCH);
1732 /* Check AES. */
1733 if (!x.bitfield.cpuaes || cpu.bitfield.cpuaes)
1734 match |= CPU_FLAGS_AES_MATCH;
1735 /* Check PCLMUL. */
1736 if (!x.bitfield.cpupclmul
1737 || cpu.bitfield.cpupclmul)
1738 match |= CPU_FLAGS_PCLMUL_MATCH;
1739 }
1740 }
1741 else
1742 match |= CPU_FLAGS_ARCH_MATCH;
1743 }
1744 else if (x.bitfield.cpuavx512vl)
1745 {
1746 /* Match AVX512VL. */
1747 if (cpu.bitfield.cpuavx512vl)
1748 {
1749 /* Need another match. */
1750 cpu.bitfield.cpuavx512vl = 0;
1751 if (!cpu_flags_all_zero (&cpu))
1752 match |= CPU_FLAGS_32BIT_MATCH;
1753 else
1754 match |= CPU_FLAGS_ARCH_MATCH;
1755 }
1756 else
1757 match |= CPU_FLAGS_ARCH_MATCH;
1758 }
1759 else
1760 match |= CPU_FLAGS_32BIT_MATCH;
1761 }
1762 }
1763 return match;
1764}
1765
1766static INLINE i386_operand_type
1767operand_type_and (i386_operand_type x, i386_operand_type y)
1768{
1769 switch (ARRAY_SIZE (x.array))
1770 {
1771 case 3:
1772 x.array [2] &= y.array [2];
1773 /* Fall through. */
1774 case 2:
1775 x.array [1] &= y.array [1];
1776 /* Fall through. */
1777 case 1:
1778 x.array [0] &= y.array [0];
1779 break;
1780 default:
1781 abort ();
1782 }
1783 return x;
1784}
1785
1786static INLINE i386_operand_type
1787operand_type_or (i386_operand_type x, i386_operand_type y)
1788{
1789 switch (ARRAY_SIZE (x.array))
1790 {
1791 case 3:
1792 x.array [2] |= y.array [2];
1793 /* Fall through. */
1794 case 2:
1795 x.array [1] |= y.array [1];
1796 /* Fall through. */
1797 case 1:
1798 x.array [0] |= y.array [0];
1799 break;
1800 default:
1801 abort ();
1802 }
1803 return x;
1804}
1805
1806static INLINE i386_operand_type
1807operand_type_xor (i386_operand_type x, i386_operand_type y)
1808{
1809 switch (ARRAY_SIZE (x.array))
1810 {
1811 case 3:
1812 x.array [2] ^= y.array [2];
1813 /* Fall through. */
1814 case 2:
1815 x.array [1] ^= y.array [1];
1816 /* Fall through. */
1817 case 1:
1818 x.array [0] ^= y.array [0];
1819 break;
1820 default:
1821 abort ();
1822 }
1823 return x;
1824}
1825
1826static const i386_operand_type acc32 = OPERAND_TYPE_ACC32;
1827static const i386_operand_type acc64 = OPERAND_TYPE_ACC64;
1828static const i386_operand_type control = OPERAND_TYPE_CONTROL;
1829static const i386_operand_type inoutportreg
1830 = OPERAND_TYPE_INOUTPORTREG;
1831static const i386_operand_type reg16_inoutportreg
1832 = OPERAND_TYPE_REG16_INOUTPORTREG;
1833static const i386_operand_type disp16 = OPERAND_TYPE_DISP16;
1834static const i386_operand_type disp32 = OPERAND_TYPE_DISP32;
1835static const i386_operand_type disp32s = OPERAND_TYPE_DISP32S;
1836static const i386_operand_type disp16_32 = OPERAND_TYPE_DISP16_32;
1837static const i386_operand_type anydisp
1838 = OPERAND_TYPE_ANYDISP;
1839static const i386_operand_type regxmm = OPERAND_TYPE_REGXMM;
1840static const i386_operand_type regmask = OPERAND_TYPE_REGMASK;
1841static const i386_operand_type imm8 = OPERAND_TYPE_IMM8;
1842static const i386_operand_type imm8s = OPERAND_TYPE_IMM8S;
1843static const i386_operand_type imm16 = OPERAND_TYPE_IMM16;
1844static const i386_operand_type imm32 = OPERAND_TYPE_IMM32;
1845static const i386_operand_type imm32s = OPERAND_TYPE_IMM32S;
1846static const i386_operand_type imm64 = OPERAND_TYPE_IMM64;
1847static const i386_operand_type imm16_32 = OPERAND_TYPE_IMM16_32;
1848static const i386_operand_type imm16_32s = OPERAND_TYPE_IMM16_32S;
1849static const i386_operand_type imm16_32_32s = OPERAND_TYPE_IMM16_32_32S;
1850static const i386_operand_type vec_imm4 = OPERAND_TYPE_VEC_IMM4;
1851
1852enum operand_type
1853{
1854 reg,
1855 imm,
1856 disp,
1857 anymem
1858};
1859
1860static INLINE int
1861operand_type_check (i386_operand_type t, enum operand_type c)
1862{
1863 switch (c)
1864 {
1865 case reg:
1866 return t.bitfield.reg;
1867
1868 case imm:
1869 return (t.bitfield.imm8
1870 || t.bitfield.imm8s
1871 || t.bitfield.imm16
1872 || t.bitfield.imm32
1873 || t.bitfield.imm32s
1874 || t.bitfield.imm64);
1875
1876 case disp:
1877 return (t.bitfield.disp8
1878 || t.bitfield.disp16
1879 || t.bitfield.disp32
1880 || t.bitfield.disp32s
1881 || t.bitfield.disp64);
1882
1883 case anymem:
1884 return (t.bitfield.disp8
1885 || t.bitfield.disp16
1886 || t.bitfield.disp32
1887 || t.bitfield.disp32s
1888 || t.bitfield.disp64
1889 || t.bitfield.baseindex);
1890
1891 default:
1892 abort ();
1893 }
1894
1895 return 0;
1896}
1897
1898/* Return 1 if there is no conflict in 8bit/16bit/32bit/64bit/80bit on
1899 operand J for instruction template T. */
1900
1901static INLINE int
1902match_reg_size (const insn_template *t, unsigned int j)
1903{
1904 return !((i.types[j].bitfield.byte
1905 && !t->operand_types[j].bitfield.byte)
1906 || (i.types[j].bitfield.word
1907 && !t->operand_types[j].bitfield.word)
1908 || (i.types[j].bitfield.dword
1909 && !t->operand_types[j].bitfield.dword)
1910 || (i.types[j].bitfield.qword
1911 && !t->operand_types[j].bitfield.qword)
1912 || (i.types[j].bitfield.tbyte
1913 && !t->operand_types[j].bitfield.tbyte));
1914}
1915
1916/* Return 1 if there is no conflict in SIMD register on
1917 operand J for instruction template T. */
1918
1919static INLINE int
1920match_simd_size (const insn_template *t, unsigned int j)
1921{
1922 return !((i.types[j].bitfield.xmmword
1923 && !t->operand_types[j].bitfield.xmmword)
1924 || (i.types[j].bitfield.ymmword
1925 && !t->operand_types[j].bitfield.ymmword)
1926 || (i.types[j].bitfield.zmmword
1927 && !t->operand_types[j].bitfield.zmmword));
1928}
1929
1930/* Return 1 if there is no conflict in any size on operand J for
1931 instruction template T. */
1932
1933static INLINE int
1934match_mem_size (const insn_template *t, unsigned int j)
1935{
1936 return (match_reg_size (t, j)
1937 && !((i.types[j].bitfield.unspecified
1938 && !i.broadcast
1939 && !t->operand_types[j].bitfield.unspecified)
1940 || (i.types[j].bitfield.fword
1941 && !t->operand_types[j].bitfield.fword)
1942 /* For scalar opcode templates to allow register and memory
1943 operands at the same time, some special casing is needed
1944 here. */
1945 || ((t->operand_types[j].bitfield.regsimd
1946 && !t->opcode_modifier.broadcast
1947 && (t->operand_types[j].bitfield.dword
1948 || t->operand_types[j].bitfield.qword))
1949 ? (i.types[j].bitfield.xmmword
1950 || i.types[j].bitfield.ymmword
1951 || i.types[j].bitfield.zmmword)
1952 : !match_simd_size(t, j))));
1953}
1954
1955/* Return 1 if there is no size conflict on any operands for
1956 instruction template T. */
1957
1958static INLINE int
1959operand_size_match (const insn_template *t)
1960{
1961 unsigned int j;
1962 int match = 1;
1963
1964 /* Don't check jump instructions. */
1965 if (t->opcode_modifier.jump
1966 || t->opcode_modifier.jumpbyte
1967 || t->opcode_modifier.jumpdword
1968 || t->opcode_modifier.jumpintersegment)
1969 return match;
1970
1971 /* Check memory and accumulator operand size. */
1972 for (j = 0; j < i.operands; j++)
1973 {
1974 if (!i.types[j].bitfield.reg && !i.types[j].bitfield.regsimd
1975 && t->operand_types[j].bitfield.anysize)
1976 continue;
1977
1978 if (t->operand_types[j].bitfield.reg
1979 && !match_reg_size (t, j))
1980 {
1981 match = 0;
1982 break;
1983 }
1984
1985 if (t->operand_types[j].bitfield.regsimd
1986 && !match_simd_size (t, j))
1987 {
1988 match = 0;
1989 break;
1990 }
1991
1992 if (t->operand_types[j].bitfield.acc
1993 && (!match_reg_size (t, j) || !match_simd_size (t, j)))
1994 {
1995 match = 0;
1996 break;
1997 }
1998
1999 if (i.types[j].bitfield.mem && !match_mem_size (t, j))
2000 {
2001 match = 0;
2002 break;
2003 }
2004 }
2005
2006 if (match)
2007 return match;
2008 else if (!t->opcode_modifier.d && !t->opcode_modifier.floatd)
2009 {
2010mismatch:
2011 i.error = operand_size_mismatch;
2012 return 0;
2013 }
2014
2015 /* Check reverse. */
2016 gas_assert (i.operands == 2);
2017
2018 match = 1;
2019 for (j = 0; j < 2; j++)
2020 {
2021 if ((t->operand_types[j].bitfield.reg
2022 || t->operand_types[j].bitfield.acc)
2023 && !match_reg_size (t, j ? 0 : 1))
2024 goto mismatch;
2025
2026 if (i.types[j].bitfield.mem
2027 && !match_mem_size (t, j ? 0 : 1))
2028 goto mismatch;
2029 }
2030
2031 return match;
2032}
2033
2034static INLINE int
2035operand_type_match (i386_operand_type overlap,
2036 i386_operand_type given)
2037{
2038 i386_operand_type temp = overlap;
2039
2040 temp.bitfield.jumpabsolute = 0;
2041 temp.bitfield.unspecified = 0;
2042 temp.bitfield.byte = 0;
2043 temp.bitfield.word = 0;
2044 temp.bitfield.dword = 0;
2045 temp.bitfield.fword = 0;
2046 temp.bitfield.qword = 0;
2047 temp.bitfield.tbyte = 0;
2048 temp.bitfield.xmmword = 0;
2049 temp.bitfield.ymmword = 0;
2050 temp.bitfield.zmmword = 0;
2051 if (operand_type_all_zero (&temp))
2052 goto mismatch;
2053
2054 if (given.bitfield.baseindex == overlap.bitfield.baseindex
2055 && given.bitfield.jumpabsolute == overlap.bitfield.jumpabsolute)
2056 return 1;
2057
2058mismatch:
2059 i.error = operand_type_mismatch;
2060 return 0;
2061}
2062
2063/* If given types g0 and g1 are registers they must be of the same type
2064 unless the expected operand type register overlap is null.
2065 Memory operand size of certain SIMD instructions is also being checked
2066 here. */
2067
2068static INLINE int
2069operand_type_register_match (i386_operand_type g0,
2070 i386_operand_type t0,
2071 i386_operand_type g1,
2072 i386_operand_type t1)
2073{
2074 if (!g0.bitfield.reg
2075 && !g0.bitfield.regsimd
2076 && (!operand_type_check (g0, anymem)
2077 || g0.bitfield.unspecified
2078 || !t0.bitfield.regsimd))
2079 return 1;
2080
2081 if (!g1.bitfield.reg
2082 && !g1.bitfield.regsimd
2083 && (!operand_type_check (g1, anymem)
2084 || g1.bitfield.unspecified
2085 || !t1.bitfield.regsimd))
2086 return 1;
2087
2088 if (g0.bitfield.byte == g1.bitfield.byte
2089 && g0.bitfield.word == g1.bitfield.word
2090 && g0.bitfield.dword == g1.bitfield.dword
2091 && g0.bitfield.qword == g1.bitfield.qword
2092 && g0.bitfield.xmmword == g1.bitfield.xmmword
2093 && g0.bitfield.ymmword == g1.bitfield.ymmword
2094 && g0.bitfield.zmmword == g1.bitfield.zmmword)
2095 return 1;
2096
2097 if (!(t0.bitfield.byte & t1.bitfield.byte)
2098 && !(t0.bitfield.word & t1.bitfield.word)
2099 && !(t0.bitfield.dword & t1.bitfield.dword)
2100 && !(t0.bitfield.qword & t1.bitfield.qword)
2101 && !(t0.bitfield.xmmword & t1.bitfield.xmmword)
2102 && !(t0.bitfield.ymmword & t1.bitfield.ymmword)
2103 && !(t0.bitfield.zmmword & t1.bitfield.zmmword))
2104 return 1;
2105
2106 i.error = register_type_mismatch;
2107
2108 return 0;
2109}
2110
2111static INLINE unsigned int
2112register_number (const reg_entry *r)
2113{
2114 unsigned int nr = r->reg_num;
2115
2116 if (r->reg_flags & RegRex)
2117 nr += 8;
2118
2119 if (r->reg_flags & RegVRex)
2120 nr += 16;
2121
2122 return nr;
2123}
2124
2125static INLINE unsigned int
2126mode_from_disp_size (i386_operand_type t)
2127{
2128 if (t.bitfield.disp8)
2129 return 1;
2130 else if (t.bitfield.disp16
2131 || t.bitfield.disp32
2132 || t.bitfield.disp32s)
2133 return 2;
2134 else
2135 return 0;
2136}
2137
2138static INLINE int
2139fits_in_signed_byte (addressT num)
2140{
2141 return num + 0x80 <= 0xff;
2142}
2143
2144static INLINE int
2145fits_in_unsigned_byte (addressT num)
2146{
2147 return num <= 0xff;
2148}
2149
2150static INLINE int
2151fits_in_unsigned_word (addressT num)
2152{
2153 return num <= 0xffff;
2154}
2155
2156static INLINE int
2157fits_in_signed_word (addressT num)
2158{
2159 return num + 0x8000 <= 0xffff;
2160}
2161
2162static INLINE int
2163fits_in_signed_long (addressT num ATTRIBUTE_UNUSED)
2164{
2165#ifndef BFD64
2166 return 1;
2167#else
2168 return num + 0x80000000 <= 0xffffffff;
2169#endif
2170} /* fits_in_signed_long() */
2171
2172static INLINE int
2173fits_in_unsigned_long (addressT num ATTRIBUTE_UNUSED)
2174{
2175#ifndef BFD64
2176 return 1;
2177#else
2178 return num <= 0xffffffff;
2179#endif
2180} /* fits_in_unsigned_long() */
2181
2182static INLINE int
2183fits_in_disp8 (offsetT num)
2184{
2185 int shift = i.memshift;
2186 unsigned int mask;
2187
2188 if (shift == -1)
2189 abort ();
2190
2191 mask = (1 << shift) - 1;
2192
2193 /* Return 0 if NUM isn't properly aligned. */
2194 if ((num & mask))
2195 return 0;
2196
2197 /* Check if NUM will fit in 8bit after shift. */
2198 return fits_in_signed_byte (num >> shift);
2199}
2200
2201static INLINE int
2202fits_in_imm4 (offsetT num)
2203{
2204 return (num & 0xf) == num;
2205}
2206
2207static INLINE int
2208fits_in_imm7 (offsetT num)
2209{
2210 return (num & 0x7f) == num;
2211}
2212
2213static INLINE int
2214fits_in_imm31 (offsetT num)
2215{
2216 return (num & 0x7fffffff) == num;
2217}
2218
2219static i386_operand_type
2220smallest_imm_type (offsetT num)
2221{
2222 i386_operand_type t;
2223
2224 operand_type_set (&t, 0);
2225 t.bitfield.imm64 = 1;
2226
2227 if (cpu_arch_tune != PROCESSOR_I486 && num == 1)
2228 {
2229 /* This code is disabled on the 486 because all the Imm1 forms
2230 in the opcode table are slower on the i486. They're the
2231 versions with the implicitly specified single-position
2232 displacement, which has another syntax if you really want to
2233 use that form. */
2234 t.bitfield.imm1 = 1;
2235 t.bitfield.imm8 = 1;
2236 t.bitfield.imm8s = 1;
2237 t.bitfield.imm16 = 1;
2238 t.bitfield.imm32 = 1;
2239 t.bitfield.imm32s = 1;
2240 }
2241 else if (fits_in_signed_byte (num))
2242 {
2243 t.bitfield.imm8 = 1;
2244 t.bitfield.imm8s = 1;
2245 t.bitfield.imm16 = 1;
2246 t.bitfield.imm32 = 1;
2247 t.bitfield.imm32s = 1;
2248 }
2249 else if (fits_in_unsigned_byte (num))
2250 {
2251 t.bitfield.imm8 = 1;
2252 t.bitfield.imm16 = 1;
2253 t.bitfield.imm32 = 1;
2254 t.bitfield.imm32s = 1;
2255 }
2256 else if (fits_in_signed_word (num) || fits_in_unsigned_word (num))
2257 {
2258 t.bitfield.imm16 = 1;
2259 t.bitfield.imm32 = 1;
2260 t.bitfield.imm32s = 1;
2261 }
2262 else if (fits_in_signed_long (num))
2263 {
2264 t.bitfield.imm32 = 1;
2265 t.bitfield.imm32s = 1;
2266 }
2267 else if (fits_in_unsigned_long (num))
2268 t.bitfield.imm32 = 1;
2269
2270 return t;
2271}
2272
2273static offsetT
2274offset_in_range (offsetT val, int size)
2275{
2276 addressT mask;
2277
2278 switch (size)
2279 {
2280 case 1: mask = ((addressT) 1 << 8) - 1; break;
2281 case 2: mask = ((addressT) 1 << 16) - 1; break;
2282 case 4: mask = ((addressT) 2 << 31) - 1; break;
2283#ifdef BFD64
2284 case 8: mask = ((addressT) 2 << 63) - 1; break;
2285#endif
2286 default: abort ();
2287 }
2288
2289#ifdef BFD64
2290 /* If BFD64, sign extend val for 32bit address mode. */
2291 if (flag_code != CODE_64BIT
2292 || i.prefix[ADDR_PREFIX])
2293 if ((val & ~(((addressT) 2 << 31) - 1)) == 0)
2294 val = (val ^ ((addressT) 1 << 31)) - ((addressT) 1 << 31);
2295#endif
2296
2297 if ((val & ~mask) != 0 && (val & ~mask) != ~mask)
2298 {
2299 char buf1[40], buf2[40];
2300
2301 sprint_value (buf1, val);
2302 sprint_value (buf2, val & mask);
2303 as_warn (_("%s shortened to %s"), buf1, buf2);
2304 }
2305 return val & mask;
2306}
2307
2308enum PREFIX_GROUP
2309{
2310 PREFIX_EXIST = 0,
2311 PREFIX_LOCK,
2312 PREFIX_REP,
2313 PREFIX_DS,
2314 PREFIX_OTHER
2315};
2316
2317/* Returns
2318 a. PREFIX_EXIST if attempting to add a prefix where one from the
2319 same class already exists.
2320 b. PREFIX_LOCK if lock prefix is added.
2321 c. PREFIX_REP if rep/repne prefix is added.
2322 d. PREFIX_DS if ds prefix is added.
2323 e. PREFIX_OTHER if other prefix is added.
2324 */
2325
2326static enum PREFIX_GROUP
2327add_prefix (unsigned int prefix)
2328{
2329 enum PREFIX_GROUP ret = PREFIX_OTHER;
2330 unsigned int q;
2331
2332 if (prefix >= REX_OPCODE && prefix < REX_OPCODE + 16
2333 && flag_code == CODE_64BIT)
2334 {
2335 if ((i.prefix[REX_PREFIX] & prefix & REX_W)
2336 || ((i.prefix[REX_PREFIX] & (REX_R | REX_X | REX_B))
2337 && (prefix & (REX_R | REX_X | REX_B))))
2338 ret = PREFIX_EXIST;
2339 q = REX_PREFIX;
2340 }
2341 else
2342 {
2343 switch (prefix)
2344 {
2345 default:
2346 abort ();
2347
2348 case DS_PREFIX_OPCODE:
2349 ret = PREFIX_DS;
2350 /* Fall through. */
2351 case CS_PREFIX_OPCODE:
2352 case ES_PREFIX_OPCODE:
2353 case FS_PREFIX_OPCODE:
2354 case GS_PREFIX_OPCODE:
2355 case SS_PREFIX_OPCODE:
2356 q = SEG_PREFIX;
2357 break;
2358
2359 case REPNE_PREFIX_OPCODE:
2360 case REPE_PREFIX_OPCODE:
2361 q = REP_PREFIX;
2362 ret = PREFIX_REP;
2363 break;
2364
2365 case LOCK_PREFIX_OPCODE:
2366 q = LOCK_PREFIX;
2367 ret = PREFIX_LOCK;
2368 break;
2369
2370 case FWAIT_OPCODE:
2371 q = WAIT_PREFIX;
2372 break;
2373
2374 case ADDR_PREFIX_OPCODE:
2375 q = ADDR_PREFIX;
2376 break;
2377
2378 case DATA_PREFIX_OPCODE:
2379 q = DATA_PREFIX;
2380 break;
2381 }
2382 if (i.prefix[q] != 0)
2383 ret = PREFIX_EXIST;
2384 }
2385
2386 if (ret)
2387 {
2388 if (!i.prefix[q])
2389 ++i.prefixes;
2390 i.prefix[q] |= prefix;
2391 }
2392 else
2393 as_bad (_("same type of prefix used twice"));
2394
2395 return ret;
2396}
2397
2398static void
2399update_code_flag (int value, int check)
2400{
2401 PRINTF_LIKE ((*as_error));
2402
2403 flag_code = (enum flag_code) value;
2404 if (flag_code == CODE_64BIT)
2405 {
2406 cpu_arch_flags.bitfield.cpu64 = 1;
2407 cpu_arch_flags.bitfield.cpuno64 = 0;
2408 }
2409 else
2410 {
2411 cpu_arch_flags.bitfield.cpu64 = 0;
2412 cpu_arch_flags.bitfield.cpuno64 = 1;
2413 }
2414 if (value == CODE_64BIT && !cpu_arch_flags.bitfield.cpulm )
2415 {
2416 if (check)
2417 as_error = as_fatal;
2418 else
2419 as_error = as_bad;
2420 (*as_error) (_("64bit mode not supported on `%s'."),
2421 cpu_arch_name ? cpu_arch_name : default_arch);
2422 }
2423 if (value == CODE_32BIT && !cpu_arch_flags.bitfield.cpui386)
2424 {
2425 if (check)
2426 as_error = as_fatal;
2427 else
2428 as_error = as_bad;
2429 (*as_error) (_("32bit mode not supported on `%s'."),
2430 cpu_arch_name ? cpu_arch_name : default_arch);
2431 }
2432 stackop_size = '\0';
2433}
2434
2435static void
2436set_code_flag (int value)
2437{
2438 update_code_flag (value, 0);
2439}
2440
2441static void
2442set_16bit_gcc_code_flag (int new_code_flag)
2443{
2444 flag_code = (enum flag_code) new_code_flag;
2445 if (flag_code != CODE_16BIT)
2446 abort ();
2447 cpu_arch_flags.bitfield.cpu64 = 0;
2448 cpu_arch_flags.bitfield.cpuno64 = 1;
2449 stackop_size = LONG_MNEM_SUFFIX;
2450}
2451
2452static void
2453set_intel_syntax (int syntax_flag)
2454{
2455 /* Find out if register prefixing is specified. */
2456 int ask_naked_reg = 0;
2457
2458 SKIP_WHITESPACE ();
2459 if (!is_end_of_line[(unsigned char) *input_line_pointer])
2460 {
2461 char *string;
2462 int e = get_symbol_name (&string);
2463
2464 if (strcmp (string, "prefix") == 0)
2465 ask_naked_reg = 1;
2466 else if (strcmp (string, "noprefix") == 0)
2467 ask_naked_reg = -1;
2468 else
2469 as_bad (_("bad argument to syntax directive."));
2470 (void) restore_line_pointer (e);
2471 }
2472 demand_empty_rest_of_line ();
2473
2474 intel_syntax = syntax_flag;
2475
2476 if (ask_naked_reg == 0)
2477 allow_naked_reg = (intel_syntax
2478 && (bfd_get_symbol_leading_char (stdoutput) != '\0'));
2479 else
2480 allow_naked_reg = (ask_naked_reg < 0);
2481
2482 expr_set_rank (O_full_ptr, syntax_flag ? 10 : 0);
2483
2484 identifier_chars['%'] = intel_syntax && allow_naked_reg ? '%' : 0;
2485 identifier_chars['$'] = intel_syntax ? '$' : 0;
2486 register_prefix = allow_naked_reg ? "" : "%";
2487}
2488
2489static void
2490set_intel_mnemonic (int mnemonic_flag)
2491{
2492 intel_mnemonic = mnemonic_flag;
2493}
2494
2495static void
2496set_allow_index_reg (int flag)
2497{
2498 allow_index_reg = flag;
2499}
2500
2501static void
2502set_check (int what)
2503{
2504 enum check_kind *kind;
2505 const char *str;
2506
2507 if (what)
2508 {
2509 kind = &operand_check;
2510 str = "operand";
2511 }
2512 else
2513 {
2514 kind = &sse_check;
2515 str = "sse";
2516 }
2517
2518 SKIP_WHITESPACE ();
2519
2520 if (!is_end_of_line[(unsigned char) *input_line_pointer])
2521 {
2522 char *string;
2523 int e = get_symbol_name (&string);
2524
2525 if (strcmp (string, "none") == 0)
2526 *kind = check_none;
2527 else if (strcmp (string, "warning") == 0)
2528 *kind = check_warning;
2529 else if (strcmp (string, "error") == 0)
2530 *kind = check_error;
2531 else
2532 as_bad (_("bad argument to %s_check directive."), str);
2533 (void) restore_line_pointer (e);
2534 }
2535 else
2536 as_bad (_("missing argument for %s_check directive"), str);
2537
2538 demand_empty_rest_of_line ();
2539}
2540
2541static void
2542check_cpu_arch_compatible (const char *name ATTRIBUTE_UNUSED,
2543 i386_cpu_flags new_flag ATTRIBUTE_UNUSED)
2544{
2545#if defined (OBJ_ELF) || defined (OBJ_MAYBE_ELF)
2546 static const char *arch;
2547
2548 /* Intel LIOM is only supported on ELF. */
2549 if (!IS_ELF)
2550 return;
2551
2552 if (!arch)
2553 {
2554 /* Use cpu_arch_name if it is set in md_parse_option. Otherwise
2555 use default_arch. */
2556 arch = cpu_arch_name;
2557 if (!arch)
2558 arch = default_arch;
2559 }
2560
2561 /* If we are targeting Intel MCU, we must enable it. */
2562 if (get_elf_backend_data (stdoutput)->elf_machine_code != EM_IAMCU
2563 || new_flag.bitfield.cpuiamcu)
2564 return;
2565
2566 /* If we are targeting Intel L1OM, we must enable it. */
2567 if (get_elf_backend_data (stdoutput)->elf_machine_code != EM_L1OM
2568 || new_flag.bitfield.cpul1om)
2569 return;
2570
2571 /* If we are targeting Intel K1OM, we must enable it. */
2572 if (get_elf_backend_data (stdoutput)->elf_machine_code != EM_K1OM
2573 || new_flag.bitfield.cpuk1om)
2574 return;
2575
2576 as_bad (_("`%s' is not supported on `%s'"), name, arch);
2577#endif
2578}
2579
2580static void
2581set_cpu_arch (int dummy ATTRIBUTE_UNUSED)
2582{
2583 SKIP_WHITESPACE ();
2584
2585 if (!is_end_of_line[(unsigned char) *input_line_pointer])
2586 {
2587 char *string;
2588 int e = get_symbol_name (&string);
2589 unsigned int j;
2590 i386_cpu_flags flags;
2591
2592 for (j = 0; j < ARRAY_SIZE (cpu_arch); j++)
2593 {
2594 if (strcmp (string, cpu_arch[j].name) == 0)
2595 {
2596 check_cpu_arch_compatible (string, cpu_arch[j].flags);
2597
2598 if (*string != '.')
2599 {
2600 cpu_arch_name = cpu_arch[j].name;
2601 cpu_sub_arch_name = NULL;
2602 cpu_arch_flags = cpu_arch[j].flags;
2603 if (flag_code == CODE_64BIT)
2604 {
2605 cpu_arch_flags.bitfield.cpu64 = 1;
2606 cpu_arch_flags.bitfield.cpuno64 = 0;
2607 }
2608 else
2609 {
2610 cpu_arch_flags.bitfield.cpu64 = 0;
2611 cpu_arch_flags.bitfield.cpuno64 = 1;
2612 }
2613 cpu_arch_isa = cpu_arch[j].type;
2614 cpu_arch_isa_flags = cpu_arch[j].flags;
2615 if (!cpu_arch_tune_set)
2616 {
2617 cpu_arch_tune = cpu_arch_isa;
2618 cpu_arch_tune_flags = cpu_arch_isa_flags;
2619 }
2620 break;
2621 }
2622
2623 flags = cpu_flags_or (cpu_arch_flags,
2624 cpu_arch[j].flags);
2625
2626 if (!cpu_flags_equal (&flags, &cpu_arch_flags))
2627 {
2628 if (cpu_sub_arch_name)
2629 {
2630 char *name = cpu_sub_arch_name;
2631 cpu_sub_arch_name = concat (name,
2632 cpu_arch[j].name,
2633 (const char *) NULL);
2634 free (name);
2635 }
2636 else
2637 cpu_sub_arch_name = xstrdup (cpu_arch[j].name);
2638 cpu_arch_flags = flags;
2639 cpu_arch_isa_flags = flags;
2640 }
2641 (void) restore_line_pointer (e);
2642 demand_empty_rest_of_line ();
2643 return;
2644 }
2645 }
2646
2647 if (*string == '.' && j >= ARRAY_SIZE (cpu_arch))
2648 {
2649 /* Disable an ISA extension. */
2650 for (j = 0; j < ARRAY_SIZE (cpu_noarch); j++)
2651 if (strcmp (string + 1, cpu_noarch [j].name) == 0)
2652 {
2653 flags = cpu_flags_and_not (cpu_arch_flags,
2654 cpu_noarch[j].flags);
2655 if (!cpu_flags_equal (&flags, &cpu_arch_flags))
2656 {
2657 if (cpu_sub_arch_name)
2658 {
2659 char *name = cpu_sub_arch_name;
2660 cpu_sub_arch_name = concat (name, string,
2661 (const char *) NULL);
2662 free (name);
2663 }
2664 else
2665 cpu_sub_arch_name = xstrdup (string);
2666 cpu_arch_flags = flags;
2667 cpu_arch_isa_flags = flags;
2668 }
2669 (void) restore_line_pointer (e);
2670 demand_empty_rest_of_line ();
2671 return;
2672 }
2673
2674 j = ARRAY_SIZE (cpu_arch);
2675 }
2676
2677 if (j >= ARRAY_SIZE (cpu_arch))
2678 as_bad (_("no such architecture: `%s'"), string);
2679
2680 *input_line_pointer = e;
2681 }
2682 else
2683 as_bad (_("missing cpu architecture"));
2684
2685 no_cond_jump_promotion = 0;
2686 if (*input_line_pointer == ','
2687 && !is_end_of_line[(unsigned char) input_line_pointer[1]])
2688 {
2689 char *string;
2690 char e;
2691
2692 ++input_line_pointer;
2693 e = get_symbol_name (&string);
2694
2695 if (strcmp (string, "nojumps") == 0)
2696 no_cond_jump_promotion = 1;
2697 else if (strcmp (string, "jumps") == 0)
2698 ;
2699 else
2700 as_bad (_("no such architecture modifier: `%s'"), string);
2701
2702 (void) restore_line_pointer (e);
2703 }
2704
2705 demand_empty_rest_of_line ();
2706}
2707
2708enum bfd_architecture
2709i386_arch (void)
2710{
2711 if (cpu_arch_isa == PROCESSOR_L1OM)
2712 {
2713 if (OUTPUT_FLAVOR != bfd_target_elf_flavour
2714 || flag_code != CODE_64BIT)
2715 as_fatal (_("Intel L1OM is 64bit ELF only"));
2716 return bfd_arch_l1om;
2717 }
2718 else if (cpu_arch_isa == PROCESSOR_K1OM)
2719 {
2720 if (OUTPUT_FLAVOR != bfd_target_elf_flavour
2721 || flag_code != CODE_64BIT)
2722 as_fatal (_("Intel K1OM is 64bit ELF only"));
2723 return bfd_arch_k1om;
2724 }
2725 else if (cpu_arch_isa == PROCESSOR_IAMCU)
2726 {
2727 if (OUTPUT_FLAVOR != bfd_target_elf_flavour
2728 || flag_code == CODE_64BIT)
2729 as_fatal (_("Intel MCU is 32bit ELF only"));
2730 return bfd_arch_iamcu;
2731 }
2732 else
2733 return bfd_arch_i386;
2734}
2735
2736unsigned long
2737i386_mach (void)
2738{
2739 if (!strncmp (default_arch, "x86_64", 6))
2740 {
2741 if (cpu_arch_isa == PROCESSOR_L1OM)
2742 {
2743 if (OUTPUT_FLAVOR != bfd_target_elf_flavour
2744 || default_arch[6] != '\0')
2745 as_fatal (_("Intel L1OM is 64bit ELF only"));
2746 return bfd_mach_l1om;
2747 }
2748 else if (cpu_arch_isa == PROCESSOR_K1OM)
2749 {
2750 if (OUTPUT_FLAVOR != bfd_target_elf_flavour
2751 || default_arch[6] != '\0')
2752 as_fatal (_("Intel K1OM is 64bit ELF only"));
2753 return bfd_mach_k1om;
2754 }
2755 else if (default_arch[6] == '\0')
2756 return bfd_mach_x86_64;
2757 else
2758 return bfd_mach_x64_32;
2759 }
2760 else if (!strcmp (default_arch, "i386")
2761 || !strcmp (default_arch, "iamcu"))
2762 {
2763 if (cpu_arch_isa == PROCESSOR_IAMCU)
2764 {
2765 if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
2766 as_fatal (_("Intel MCU is 32bit ELF only"));
2767 return bfd_mach_i386_iamcu;
2768 }
2769 else
2770 return bfd_mach_i386_i386;
2771 }
2772 else
2773 as_fatal (_("unknown architecture"));
2774}
2775\f
2776void
2777md_begin (void)
2778{
2779 const char *hash_err;
2780
2781 /* Support pseudo prefixes like {disp32}. */
2782 lex_type ['{'] = LEX_BEGIN_NAME;
2783
2784 /* Initialize op_hash hash table. */
2785 op_hash = hash_new ();
2786
2787 {
2788 const insn_template *optab;
2789 templates *core_optab;
2790
2791 /* Setup for loop. */
2792 optab = i386_optab;
2793 core_optab = XNEW (templates);
2794 core_optab->start = optab;
2795
2796 while (1)
2797 {
2798 ++optab;
2799 if (optab->name == NULL
2800 || strcmp (optab->name, (optab - 1)->name) != 0)
2801 {
2802 /* different name --> ship out current template list;
2803 add to hash table; & begin anew. */
2804 core_optab->end = optab;
2805 hash_err = hash_insert (op_hash,
2806 (optab - 1)->name,
2807 (void *) core_optab);
2808 if (hash_err)
2809 {
2810 as_fatal (_("can't hash %s: %s"),
2811 (optab - 1)->name,
2812 hash_err);
2813 }
2814 if (optab->name == NULL)
2815 break;
2816 core_optab = XNEW (templates);
2817 core_optab->start = optab;
2818 }
2819 }
2820 }
2821
2822 /* Initialize reg_hash hash table. */
2823 reg_hash = hash_new ();
2824 {
2825 const reg_entry *regtab;
2826 unsigned int regtab_size = i386_regtab_size;
2827
2828 for (regtab = i386_regtab; regtab_size--; regtab++)
2829 {
2830 hash_err = hash_insert (reg_hash, regtab->reg_name, (void *) regtab);
2831 if (hash_err)
2832 as_fatal (_("can't hash %s: %s"),
2833 regtab->reg_name,
2834 hash_err);
2835 }
2836 }
2837
2838 /* Fill in lexical tables: mnemonic_chars, operand_chars. */
2839 {
2840 int c;
2841 char *p;
2842
2843 for (c = 0; c < 256; c++)
2844 {
2845 if (ISDIGIT (c))
2846 {
2847 digit_chars[c] = c;
2848 mnemonic_chars[c] = c;
2849 register_chars[c] = c;
2850 operand_chars[c] = c;
2851 }
2852 else if (ISLOWER (c))
2853 {
2854 mnemonic_chars[c] = c;
2855 register_chars[c] = c;
2856 operand_chars[c] = c;
2857 }
2858 else if (ISUPPER (c))
2859 {
2860 mnemonic_chars[c] = TOLOWER (c);
2861 register_chars[c] = mnemonic_chars[c];
2862 operand_chars[c] = c;
2863 }
2864 else if (c == '{' || c == '}')
2865 {
2866 mnemonic_chars[c] = c;
2867 operand_chars[c] = c;
2868 }
2869
2870 if (ISALPHA (c) || ISDIGIT (c))
2871 identifier_chars[c] = c;
2872 else if (c >= 128)
2873 {
2874 identifier_chars[c] = c;
2875 operand_chars[c] = c;
2876 }
2877 }
2878
2879#ifdef LEX_AT
2880 identifier_chars['@'] = '@';
2881#endif
2882#ifdef LEX_QM
2883 identifier_chars['?'] = '?';
2884 operand_chars['?'] = '?';
2885#endif
2886 digit_chars['-'] = '-';
2887 mnemonic_chars['_'] = '_';
2888 mnemonic_chars['-'] = '-';
2889 mnemonic_chars['.'] = '.';
2890 identifier_chars['_'] = '_';
2891 identifier_chars['.'] = '.';
2892
2893 for (p = operand_special_chars; *p != '\0'; p++)
2894 operand_chars[(unsigned char) *p] = *p;
2895 }
2896
2897 if (flag_code == CODE_64BIT)
2898 {
2899#if defined (OBJ_COFF) && defined (TE_PE)
2900 x86_dwarf2_return_column = (OUTPUT_FLAVOR == bfd_target_coff_flavour
2901 ? 32 : 16);
2902#else
2903 x86_dwarf2_return_column = 16;
2904#endif
2905 x86_cie_data_alignment = -8;
2906 }
2907 else
2908 {
2909 x86_dwarf2_return_column = 8;
2910 x86_cie_data_alignment = -4;
2911 }
2912}
2913
2914void
2915i386_print_statistics (FILE *file)
2916{
2917 hash_print_statistics (file, "i386 opcode", op_hash);
2918 hash_print_statistics (file, "i386 register", reg_hash);
2919}
2920\f
2921#ifdef DEBUG386
2922
2923/* Debugging routines for md_assemble. */
2924static void pte (insn_template *);
2925static void pt (i386_operand_type);
2926static void pe (expressionS *);
2927static void ps (symbolS *);
2928
2929static void
2930pi (char *line, i386_insn *x)
2931{
2932 unsigned int j;
2933
2934 fprintf (stdout, "%s: template ", line);
2935 pte (&x->tm);
2936 fprintf (stdout, " address: base %s index %s scale %x\n",
2937 x->base_reg ? x->base_reg->reg_name : "none",
2938 x->index_reg ? x->index_reg->reg_name : "none",
2939 x->log2_scale_factor);
2940 fprintf (stdout, " modrm: mode %x reg %x reg/mem %x\n",
2941 x->rm.mode, x->rm.reg, x->rm.regmem);
2942 fprintf (stdout, " sib: base %x index %x scale %x\n",
2943 x->sib.base, x->sib.index, x->sib.scale);
2944 fprintf (stdout, " rex: 64bit %x extX %x extY %x extZ %x\n",
2945 (x->rex & REX_W) != 0,
2946 (x->rex & REX_R) != 0,
2947 (x->rex & REX_X) != 0,
2948 (x->rex & REX_B) != 0);
2949 for (j = 0; j < x->operands; j++)
2950 {
2951 fprintf (stdout, " #%d: ", j + 1);
2952 pt (x->types[j]);
2953 fprintf (stdout, "\n");
2954 if (x->types[j].bitfield.reg
2955 || x->types[j].bitfield.regmmx
2956 || x->types[j].bitfield.regsimd
2957 || x->types[j].bitfield.sreg2
2958 || x->types[j].bitfield.sreg3
2959 || x->types[j].bitfield.control
2960 || x->types[j].bitfield.debug
2961 || x->types[j].bitfield.test)
2962 fprintf (stdout, "%s\n", x->op[j].regs->reg_name);
2963 if (operand_type_check (x->types[j], imm))
2964 pe (x->op[j].imms);
2965 if (operand_type_check (x->types[j], disp))
2966 pe (x->op[j].disps);
2967 }
2968}
2969
2970static void
2971pte (insn_template *t)
2972{
2973 unsigned int j;
2974 fprintf (stdout, " %d operands ", t->operands);
2975 fprintf (stdout, "opcode %x ", t->base_opcode);
2976 if (t->extension_opcode != None)
2977 fprintf (stdout, "ext %x ", t->extension_opcode);
2978 if (t->opcode_modifier.d)
2979 fprintf (stdout, "D");
2980 if (t->opcode_modifier.w)
2981 fprintf (stdout, "W");
2982 fprintf (stdout, "\n");
2983 for (j = 0; j < t->operands; j++)
2984 {
2985 fprintf (stdout, " #%d type ", j + 1);
2986 pt (t->operand_types[j]);
2987 fprintf (stdout, "\n");
2988 }
2989}
2990
2991static void
2992pe (expressionS *e)
2993{
2994 fprintf (stdout, " operation %d\n", e->X_op);
2995 fprintf (stdout, " add_number %ld (%lx)\n",
2996 (long) e->X_add_number, (long) e->X_add_number);
2997 if (e->X_add_symbol)
2998 {
2999 fprintf (stdout, " add_symbol ");
3000 ps (e->X_add_symbol);
3001 fprintf (stdout, "\n");
3002 }
3003 if (e->X_op_symbol)
3004 {
3005 fprintf (stdout, " op_symbol ");
3006 ps (e->X_op_symbol);
3007 fprintf (stdout, "\n");
3008 }
3009}
3010
3011static void
3012ps (symbolS *s)
3013{
3014 fprintf (stdout, "%s type %s%s",
3015 S_GET_NAME (s),
3016 S_IS_EXTERNAL (s) ? "EXTERNAL " : "",
3017 segment_name (S_GET_SEGMENT (s)));
3018}
3019
3020static struct type_name
3021 {
3022 i386_operand_type mask;
3023 const char *name;
3024 }
3025const type_names[] =
3026{
3027 { OPERAND_TYPE_REG8, "r8" },
3028 { OPERAND_TYPE_REG16, "r16" },
3029 { OPERAND_TYPE_REG32, "r32" },
3030 { OPERAND_TYPE_REG64, "r64" },
3031 { OPERAND_TYPE_IMM8, "i8" },
3032 { OPERAND_TYPE_IMM8, "i8s" },
3033 { OPERAND_TYPE_IMM16, "i16" },
3034 { OPERAND_TYPE_IMM32, "i32" },
3035 { OPERAND_TYPE_IMM32S, "i32s" },
3036 { OPERAND_TYPE_IMM64, "i64" },
3037 { OPERAND_TYPE_IMM1, "i1" },
3038 { OPERAND_TYPE_BASEINDEX, "BaseIndex" },
3039 { OPERAND_TYPE_DISP8, "d8" },
3040 { OPERAND_TYPE_DISP16, "d16" },
3041 { OPERAND_TYPE_DISP32, "d32" },
3042 { OPERAND_TYPE_DISP32S, "d32s" },
3043 { OPERAND_TYPE_DISP64, "d64" },
3044 { OPERAND_TYPE_INOUTPORTREG, "InOutPortReg" },
3045 { OPERAND_TYPE_SHIFTCOUNT, "ShiftCount" },
3046 { OPERAND_TYPE_CONTROL, "control reg" },
3047 { OPERAND_TYPE_TEST, "test reg" },
3048 { OPERAND_TYPE_DEBUG, "debug reg" },
3049 { OPERAND_TYPE_FLOATREG, "FReg" },
3050 { OPERAND_TYPE_FLOATACC, "FAcc" },
3051 { OPERAND_TYPE_SREG2, "SReg2" },
3052 { OPERAND_TYPE_SREG3, "SReg3" },
3053 { OPERAND_TYPE_ACC, "Acc" },
3054 { OPERAND_TYPE_JUMPABSOLUTE, "Jump Absolute" },
3055 { OPERAND_TYPE_REGMMX, "rMMX" },
3056 { OPERAND_TYPE_REGXMM, "rXMM" },
3057 { OPERAND_TYPE_REGYMM, "rYMM" },
3058 { OPERAND_TYPE_REGZMM, "rZMM" },
3059 { OPERAND_TYPE_REGMASK, "Mask reg" },
3060 { OPERAND_TYPE_ESSEG, "es" },
3061};
3062
3063static void
3064pt (i386_operand_type t)
3065{
3066 unsigned int j;
3067 i386_operand_type a;
3068
3069 for (j = 0; j < ARRAY_SIZE (type_names); j++)
3070 {
3071 a = operand_type_and (t, type_names[j].mask);
3072 if (!operand_type_all_zero (&a))
3073 fprintf (stdout, "%s, ", type_names[j].name);
3074 }
3075 fflush (stdout);
3076}
3077
3078#endif /* DEBUG386 */
3079\f
3080static bfd_reloc_code_real_type
3081reloc (unsigned int size,
3082 int pcrel,
3083 int sign,
3084 bfd_reloc_code_real_type other)
3085{
3086 if (other != NO_RELOC)
3087 {
3088 reloc_howto_type *rel;
3089
3090 if (size == 8)
3091 switch (other)
3092 {
3093 case BFD_RELOC_X86_64_GOT32:
3094 return BFD_RELOC_X86_64_GOT64;
3095 break;
3096 case BFD_RELOC_X86_64_GOTPLT64:
3097 return BFD_RELOC_X86_64_GOTPLT64;
3098 break;
3099 case BFD_RELOC_X86_64_PLTOFF64:
3100 return BFD_RELOC_X86_64_PLTOFF64;
3101 break;
3102 case BFD_RELOC_X86_64_GOTPC32:
3103 other = BFD_RELOC_X86_64_GOTPC64;
3104 break;
3105 case BFD_RELOC_X86_64_GOTPCREL:
3106 other = BFD_RELOC_X86_64_GOTPCREL64;
3107 break;
3108 case BFD_RELOC_X86_64_TPOFF32:
3109 other = BFD_RELOC_X86_64_TPOFF64;
3110 break;
3111 case BFD_RELOC_X86_64_DTPOFF32:
3112 other = BFD_RELOC_X86_64_DTPOFF64;
3113 break;
3114 default:
3115 break;
3116 }
3117
3118#if defined (OBJ_ELF) || defined (OBJ_MAYBE_ELF)
3119 if (other == BFD_RELOC_SIZE32)
3120 {
3121 if (size == 8)
3122 other = BFD_RELOC_SIZE64;
3123 if (pcrel)
3124 {
3125 as_bad (_("there are no pc-relative size relocations"));
3126 return NO_RELOC;
3127 }
3128 }
3129#endif
3130
3131 /* Sign-checking 4-byte relocations in 16-/32-bit code is pointless. */
3132 if (size == 4 && (flag_code != CODE_64BIT || disallow_64bit_reloc))
3133 sign = -1;
3134
3135 rel = bfd_reloc_type_lookup (stdoutput, other);
3136 if (!rel)
3137 as_bad (_("unknown relocation (%u)"), other);
3138 else if (size != bfd_get_reloc_size (rel))
3139 as_bad (_("%u-byte relocation cannot be applied to %u-byte field"),
3140 bfd_get_reloc_size (rel),
3141 size);
3142 else if (pcrel && !rel->pc_relative)
3143 as_bad (_("non-pc-relative relocation for pc-relative field"));
3144 else if ((rel->complain_on_overflow == complain_overflow_signed
3145 && !sign)
3146 || (rel->complain_on_overflow == complain_overflow_unsigned
3147 && sign > 0))
3148 as_bad (_("relocated field and relocation type differ in signedness"));
3149 else
3150 return other;
3151 return NO_RELOC;
3152 }
3153
3154 if (pcrel)
3155 {
3156 if (!sign)
3157 as_bad (_("there are no unsigned pc-relative relocations"));
3158 switch (size)
3159 {
3160 case 1: return BFD_RELOC_8_PCREL;
3161 case 2: return BFD_RELOC_16_PCREL;
3162 case 4: return BFD_RELOC_32_PCREL;
3163 case 8: return BFD_RELOC_64_PCREL;
3164 }
3165 as_bad (_("cannot do %u byte pc-relative relocation"), size);
3166 }
3167 else
3168 {
3169 if (sign > 0)
3170 switch (size)
3171 {
3172 case 4: return BFD_RELOC_X86_64_32S;
3173 }
3174 else
3175 switch (size)
3176 {
3177 case 1: return BFD_RELOC_8;
3178 case 2: return BFD_RELOC_16;
3179 case 4: return BFD_RELOC_32;
3180 case 8: return BFD_RELOC_64;
3181 }
3182 as_bad (_("cannot do %s %u byte relocation"),
3183 sign > 0 ? "signed" : "unsigned", size);
3184 }
3185
3186 return NO_RELOC;
3187}
3188
3189/* Here we decide which fixups can be adjusted to make them relative to
3190 the beginning of the section instead of the symbol. Basically we need
3191 to make sure that the dynamic relocations are done correctly, so in
3192 some cases we force the original symbol to be used. */
3193
3194int
3195tc_i386_fix_adjustable (fixS *fixP ATTRIBUTE_UNUSED)
3196{
3197#if defined (OBJ_ELF) || defined (OBJ_MAYBE_ELF)
3198 if (!IS_ELF)
3199 return 1;
3200
3201 /* Don't adjust pc-relative references to merge sections in 64-bit
3202 mode. */
3203 if (use_rela_relocations
3204 && (S_GET_SEGMENT (fixP->fx_addsy)->flags & SEC_MERGE) != 0
3205 && fixP->fx_pcrel)
3206 return 0;
3207
3208 /* The x86_64 GOTPCREL are represented as 32bit PCrel relocations
3209 and changed later by validate_fix. */
3210 if (GOT_symbol && fixP->fx_subsy == GOT_symbol
3211 && fixP->fx_r_type == BFD_RELOC_32_PCREL)
3212 return 0;
3213
3214 /* Adjust_reloc_syms doesn't know about the GOT. Need to keep symbol
3215 for size relocations. */
3216 if (fixP->fx_r_type == BFD_RELOC_SIZE32
3217 || fixP->fx_r_type == BFD_RELOC_SIZE64
3218 || fixP->fx_r_type == BFD_RELOC_386_GOTOFF
3219 || fixP->fx_r_type == BFD_RELOC_386_PLT32
3220 || fixP->fx_r_type == BFD_RELOC_386_GOT32
3221 || fixP->fx_r_type == BFD_RELOC_386_GOT32X
3222 || fixP->fx_r_type == BFD_RELOC_386_TLS_GD
3223 || fixP->fx_r_type == BFD_RELOC_386_TLS_LDM
3224 || fixP->fx_r_type == BFD_RELOC_386_TLS_LDO_32
3225 || fixP->fx_r_type == BFD_RELOC_386_TLS_IE_32
3226 || fixP->fx_r_type == BFD_RELOC_386_TLS_IE
3227 || fixP->fx_r_type == BFD_RELOC_386_TLS_GOTIE
3228 || fixP->fx_r_type == BFD_RELOC_386_TLS_LE_32
3229 || fixP->fx_r_type == BFD_RELOC_386_TLS_LE
3230 || fixP->fx_r_type == BFD_RELOC_386_TLS_GOTDESC
3231 || fixP->fx_r_type == BFD_RELOC_386_TLS_DESC_CALL
3232 || fixP->fx_r_type == BFD_RELOC_X86_64_PLT32
3233 || fixP->fx_r_type == BFD_RELOC_X86_64_GOT32
3234 || fixP->fx_r_type == BFD_RELOC_X86_64_GOTPCREL
3235 || fixP->fx_r_type == BFD_RELOC_X86_64_GOTPCRELX
3236 || fixP->fx_r_type == BFD_RELOC_X86_64_REX_GOTPCRELX
3237 || fixP->fx_r_type == BFD_RELOC_X86_64_TLSGD
3238 || fixP->fx_r_type == BFD_RELOC_X86_64_TLSLD
3239 || fixP->fx_r_type == BFD_RELOC_X86_64_DTPOFF32
3240 || fixP->fx_r_type == BFD_RELOC_X86_64_DTPOFF64
3241 || fixP->fx_r_type == BFD_RELOC_X86_64_GOTTPOFF
3242 || fixP->fx_r_type == BFD_RELOC_X86_64_TPOFF32
3243 || fixP->fx_r_type == BFD_RELOC_X86_64_TPOFF64
3244 || fixP->fx_r_type == BFD_RELOC_X86_64_GOTOFF64
3245 || fixP->fx_r_type == BFD_RELOC_X86_64_GOTPC32_TLSDESC
3246 || fixP->fx_r_type == BFD_RELOC_X86_64_TLSDESC_CALL
3247 || fixP->fx_r_type == BFD_RELOC_VTABLE_INHERIT
3248 || fixP->fx_r_type == BFD_RELOC_VTABLE_ENTRY)
3249 return 0;
3250#endif
3251 return 1;
3252}
3253
3254static int
3255intel_float_operand (const char *mnemonic)
3256{
3257 /* Note that the value returned is meaningful only for opcodes with (memory)
3258 operands, hence the code here is free to improperly handle opcodes that
3259 have no operands (for better performance and smaller code). */
3260
3261 if (mnemonic[0] != 'f')
3262 return 0; /* non-math */
3263
3264 switch (mnemonic[1])
3265 {
3266 /* fclex, fdecstp, fdisi, femms, feni, fincstp, finit, fsetpm, and
3267 the fs segment override prefix not currently handled because no
3268 call path can make opcodes without operands get here */
3269 case 'i':
3270 return 2 /* integer op */;
3271 case 'l':
3272 if (mnemonic[2] == 'd' && (mnemonic[3] == 'c' || mnemonic[3] == 'e'))
3273 return 3; /* fldcw/fldenv */
3274 break;
3275 case 'n':
3276 if (mnemonic[2] != 'o' /* fnop */)
3277 return 3; /* non-waiting control op */
3278 break;
3279 case 'r':
3280 if (mnemonic[2] == 's')
3281 return 3; /* frstor/frstpm */
3282 break;
3283 case 's':
3284 if (mnemonic[2] == 'a')
3285 return 3; /* fsave */
3286 if (mnemonic[2] == 't')
3287 {
3288 switch (mnemonic[3])
3289 {
3290 case 'c': /* fstcw */
3291 case 'd': /* fstdw */
3292 case 'e': /* fstenv */
3293 case 's': /* fsts[gw] */
3294 return 3;
3295 }
3296 }
3297 break;
3298 case 'x':
3299 if (mnemonic[2] == 'r' || mnemonic[2] == 's')
3300 return 0; /* fxsave/fxrstor are not really math ops */
3301 break;
3302 }
3303
3304 return 1;
3305}
3306
3307/* Build the VEX prefix. */
3308
3309static void
3310build_vex_prefix (const insn_template *t)
3311{
3312 unsigned int register_specifier;
3313 unsigned int implied_prefix;
3314 unsigned int vector_length;
3315
3316 /* Check register specifier. */
3317 if (i.vex.register_specifier)
3318 {
3319 register_specifier =
3320 ~register_number (i.vex.register_specifier) & 0xf;
3321 gas_assert ((i.vex.register_specifier->reg_flags & RegVRex) == 0);
3322 }
3323 else
3324 register_specifier = 0xf;
3325
3326 /* Use 2-byte VEX prefix by swapping destination and source
3327 operand. */
3328 if (i.vec_encoding != vex_encoding_vex3
3329 && i.dir_encoding == dir_encoding_default
3330 && i.operands == i.reg_operands
3331 && i.tm.opcode_modifier.vexopcode == VEX0F
3332 && i.tm.opcode_modifier.load
3333 && i.rex == REX_B)
3334 {
3335 unsigned int xchg = i.operands - 1;
3336 union i386_op temp_op;
3337 i386_operand_type temp_type;
3338
3339 temp_type = i.types[xchg];
3340 i.types[xchg] = i.types[0];
3341 i.types[0] = temp_type;
3342 temp_op = i.op[xchg];
3343 i.op[xchg] = i.op[0];
3344 i.op[0] = temp_op;
3345
3346 gas_assert (i.rm.mode == 3);
3347
3348 i.rex = REX_R;
3349 xchg = i.rm.regmem;
3350 i.rm.regmem = i.rm.reg;
3351 i.rm.reg = xchg;
3352
3353 /* Use the next insn. */
3354 i.tm = t[1];
3355 }
3356
3357 if (i.tm.opcode_modifier.vex == VEXScalar)
3358 vector_length = avxscalar;
3359 else if (i.tm.opcode_modifier.vex == VEX256)
3360 vector_length = 1;
3361 else
3362 {
3363 unsigned int op;
3364
3365 vector_length = 0;
3366 for (op = 0; op < t->operands; ++op)
3367 if (t->operand_types[op].bitfield.xmmword
3368 && t->operand_types[op].bitfield.ymmword
3369 && i.types[op].bitfield.ymmword)
3370 {
3371 vector_length = 1;
3372 break;
3373 }
3374 }
3375
3376 switch ((i.tm.base_opcode >> 8) & 0xff)
3377 {
3378 case 0:
3379 implied_prefix = 0;
3380 break;
3381 case DATA_PREFIX_OPCODE:
3382 implied_prefix = 1;
3383 break;
3384 case REPE_PREFIX_OPCODE:
3385 implied_prefix = 2;
3386 break;
3387 case REPNE_PREFIX_OPCODE:
3388 implied_prefix = 3;
3389 break;
3390 default:
3391 abort ();
3392 }
3393
3394 /* Use 2-byte VEX prefix if possible. */
3395 if (i.vec_encoding != vex_encoding_vex3
3396 && i.tm.opcode_modifier.vexopcode == VEX0F
3397 && i.tm.opcode_modifier.vexw != VEXW1
3398 && (i.rex & (REX_W | REX_X | REX_B)) == 0)
3399 {
3400 /* 2-byte VEX prefix. */
3401 unsigned int r;
3402
3403 i.vex.length = 2;
3404 i.vex.bytes[0] = 0xc5;
3405
3406 /* Check the REX.R bit. */
3407 r = (i.rex & REX_R) ? 0 : 1;
3408 i.vex.bytes[1] = (r << 7
3409 | register_specifier << 3
3410 | vector_length << 2
3411 | implied_prefix);
3412 }
3413 else
3414 {
3415 /* 3-byte VEX prefix. */
3416 unsigned int m, w;
3417
3418 i.vex.length = 3;
3419
3420 switch (i.tm.opcode_modifier.vexopcode)
3421 {
3422 case VEX0F:
3423 m = 0x1;
3424 i.vex.bytes[0] = 0xc4;
3425 break;
3426 case VEX0F38:
3427 m = 0x2;
3428 i.vex.bytes[0] = 0xc4;
3429 break;
3430 case VEX0F3A:
3431 m = 0x3;
3432 i.vex.bytes[0] = 0xc4;
3433 break;
3434 case XOP08:
3435 m = 0x8;
3436 i.vex.bytes[0] = 0x8f;
3437 break;
3438 case XOP09:
3439 m = 0x9;
3440 i.vex.bytes[0] = 0x8f;
3441 break;
3442 case XOP0A:
3443 m = 0xa;
3444 i.vex.bytes[0] = 0x8f;
3445 break;
3446 default:
3447 abort ();
3448 }
3449
3450 /* The high 3 bits of the second VEX byte are 1's compliment
3451 of RXB bits from REX. */
3452 i.vex.bytes[1] = (~i.rex & 0x7) << 5 | m;
3453
3454 /* Check the REX.W bit. */
3455 w = (i.rex & REX_W) ? 1 : 0;
3456 if (i.tm.opcode_modifier.vexw == VEXW1)
3457 w = 1;
3458
3459 i.vex.bytes[2] = (w << 7
3460 | register_specifier << 3
3461 | vector_length << 2
3462 | implied_prefix);
3463 }
3464}
3465
3466/* Build the EVEX prefix. */
3467
3468static void
3469build_evex_prefix (void)
3470{
3471 unsigned int register_specifier;
3472 unsigned int implied_prefix;
3473 unsigned int m, w;
3474 rex_byte vrex_used = 0;
3475
3476 /* Check register specifier. */
3477 if (i.vex.register_specifier)
3478 {
3479 gas_assert ((i.vrex & REX_X) == 0);
3480
3481 register_specifier = i.vex.register_specifier->reg_num;
3482 if ((i.vex.register_specifier->reg_flags & RegRex))
3483 register_specifier += 8;
3484 /* The upper 16 registers are encoded in the fourth byte of the
3485 EVEX prefix. */
3486 if (!(i.vex.register_specifier->reg_flags & RegVRex))
3487 i.vex.bytes[3] = 0x8;
3488 register_specifier = ~register_specifier & 0xf;
3489 }
3490 else
3491 {
3492 register_specifier = 0xf;
3493
3494 /* Encode upper 16 vector index register in the fourth byte of
3495 the EVEX prefix. */
3496 if (!(i.vrex & REX_X))
3497 i.vex.bytes[3] = 0x8;
3498 else
3499 vrex_used |= REX_X;
3500 }
3501
3502 switch ((i.tm.base_opcode >> 8) & 0xff)
3503 {
3504 case 0:
3505 implied_prefix = 0;
3506 break;
3507 case DATA_PREFIX_OPCODE:
3508 implied_prefix = 1;
3509 break;
3510 case REPE_PREFIX_OPCODE:
3511 implied_prefix = 2;
3512 break;
3513 case REPNE_PREFIX_OPCODE:
3514 implied_prefix = 3;
3515 break;
3516 default:
3517 abort ();
3518 }
3519
3520 /* 4 byte EVEX prefix. */
3521 i.vex.length = 4;
3522 i.vex.bytes[0] = 0x62;
3523
3524 /* mmmm bits. */
3525 switch (i.tm.opcode_modifier.vexopcode)
3526 {
3527 case VEX0F:
3528 m = 1;
3529 break;
3530 case VEX0F38:
3531 m = 2;
3532 break;
3533 case VEX0F3A:
3534 m = 3;
3535 break;
3536 default:
3537 abort ();
3538 break;
3539 }
3540
3541 /* The high 3 bits of the second EVEX byte are 1's compliment of RXB
3542 bits from REX. */
3543 i.vex.bytes[1] = (~i.rex & 0x7) << 5 | m;
3544
3545 /* The fifth bit of the second EVEX byte is 1's compliment of the
3546 REX_R bit in VREX. */
3547 if (!(i.vrex & REX_R))
3548 i.vex.bytes[1] |= 0x10;
3549 else
3550 vrex_used |= REX_R;
3551
3552 if ((i.reg_operands + i.imm_operands) == i.operands)
3553 {
3554 /* When all operands are registers, the REX_X bit in REX is not
3555 used. We reuse it to encode the upper 16 registers, which is
3556 indicated by the REX_B bit in VREX. The REX_X bit is encoded
3557 as 1's compliment. */
3558 if ((i.vrex & REX_B))
3559 {
3560 vrex_used |= REX_B;
3561 i.vex.bytes[1] &= ~0x40;
3562 }
3563 }
3564
3565 /* EVEX instructions shouldn't need the REX prefix. */
3566 i.vrex &= ~vrex_used;
3567 gas_assert (i.vrex == 0);
3568
3569 /* Check the REX.W bit. */
3570 w = (i.rex & REX_W) ? 1 : 0;
3571 if (i.tm.opcode_modifier.vexw)
3572 {
3573 if (i.tm.opcode_modifier.vexw == VEXW1)
3574 w = 1;
3575 }
3576 /* If w is not set it means we are dealing with WIG instruction. */
3577 else if (!w)
3578 {
3579 if (evexwig == evexw1)
3580 w = 1;
3581 }
3582
3583 /* Encode the U bit. */
3584 implied_prefix |= 0x4;
3585
3586 /* The third byte of the EVEX prefix. */
3587 i.vex.bytes[2] = (w << 7 | register_specifier << 3 | implied_prefix);
3588
3589 /* The fourth byte of the EVEX prefix. */
3590 /* The zeroing-masking bit. */
3591 if (i.mask && i.mask->zeroing)
3592 i.vex.bytes[3] |= 0x80;
3593
3594 /* Don't always set the broadcast bit if there is no RC. */
3595 if (!i.rounding)
3596 {
3597 /* Encode the vector length. */
3598 unsigned int vec_length;
3599
3600 switch (i.tm.opcode_modifier.evex)
3601 {
3602 case EVEXLIG: /* LL' is ignored */
3603 vec_length = evexlig << 5;
3604 break;
3605 case EVEX128:
3606 vec_length = 0 << 5;
3607 break;
3608 case EVEX256:
3609 vec_length = 1 << 5;
3610 break;
3611 case EVEX512:
3612 vec_length = 2 << 5;
3613 break;
3614 default:
3615 abort ();
3616 break;
3617 }
3618 i.vex.bytes[3] |= vec_length;
3619 /* Encode the broadcast bit. */
3620 if (i.broadcast)
3621 i.vex.bytes[3] |= 0x10;
3622 }
3623 else
3624 {
3625 if (i.rounding->type != saeonly)
3626 i.vex.bytes[3] |= 0x10 | (i.rounding->type << 5);
3627 else
3628 i.vex.bytes[3] |= 0x10 | (evexrcig << 5);
3629 }
3630
3631 if (i.mask && i.mask->mask)
3632 i.vex.bytes[3] |= i.mask->mask->reg_num;
3633}
3634
3635static void
3636process_immext (void)
3637{
3638 expressionS *exp;
3639
3640 if ((i.tm.cpu_flags.bitfield.cpusse3 || i.tm.cpu_flags.bitfield.cpusvme)
3641 && i.operands > 0)
3642 {
3643 /* MONITOR/MWAIT as well as SVME instructions have fixed operands
3644 with an opcode suffix which is coded in the same place as an
3645 8-bit immediate field would be.
3646 Here we check those operands and remove them afterwards. */
3647 unsigned int x;
3648
3649 for (x = 0; x < i.operands; x++)
3650 if (register_number (i.op[x].regs) != x)
3651 as_bad (_("can't use register '%s%s' as operand %d in '%s'."),
3652 register_prefix, i.op[x].regs->reg_name, x + 1,
3653 i.tm.name);
3654
3655 i.operands = 0;
3656 }
3657
3658 if (i.tm.cpu_flags.bitfield.cpumwaitx && i.operands > 0)
3659 {
3660 /* MONITORX/MWAITX instructions have fixed operands with an opcode
3661 suffix which is coded in the same place as an 8-bit immediate
3662 field would be.
3663 Here we check those operands and remove them afterwards. */
3664 unsigned int x;
3665
3666 if (i.operands != 3)
3667 abort();
3668
3669 for (x = 0; x < 2; x++)
3670 if (register_number (i.op[x].regs) != x)
3671 goto bad_register_operand;
3672
3673 /* Check for third operand for mwaitx/monitorx insn. */
3674 if (register_number (i.op[x].regs)
3675 != (x + (i.tm.extension_opcode == 0xfb)))
3676 {
3677bad_register_operand:
3678 as_bad (_("can't use register '%s%s' as operand %d in '%s'."),
3679 register_prefix, i.op[x].regs->reg_name, x+1,
3680 i.tm.name);
3681 }
3682
3683 i.operands = 0;
3684 }
3685
3686 /* These AMD 3DNow! and SSE2 instructions have an opcode suffix
3687 which is coded in the same place as an 8-bit immediate field
3688 would be. Here we fake an 8-bit immediate operand from the
3689 opcode suffix stored in tm.extension_opcode.
3690
3691 AVX instructions also use this encoding, for some of
3692 3 argument instructions. */
3693
3694 gas_assert (i.imm_operands <= 1
3695 && (i.operands <= 2
3696 || ((i.tm.opcode_modifier.vex
3697 || i.tm.opcode_modifier.evex)
3698 && i.operands <= 4)));
3699
3700 exp = &im_expressions[i.imm_operands++];
3701 i.op[i.operands].imms = exp;
3702 i.types[i.operands] = imm8;
3703 i.operands++;
3704 exp->X_op = O_constant;
3705 exp->X_add_number = i.tm.extension_opcode;
3706 i.tm.extension_opcode = None;
3707}
3708
3709
3710static int
3711check_hle (void)
3712{
3713 switch (i.tm.opcode_modifier.hleprefixok)
3714 {
3715 default:
3716 abort ();
3717 case HLEPrefixNone:
3718 as_bad (_("invalid instruction `%s' after `%s'"),
3719 i.tm.name, i.hle_prefix);
3720 return 0;
3721 case HLEPrefixLock:
3722 if (i.prefix[LOCK_PREFIX])
3723 return 1;
3724 as_bad (_("missing `lock' with `%s'"), i.hle_prefix);
3725 return 0;
3726 case HLEPrefixAny:
3727 return 1;
3728 case HLEPrefixRelease:
3729 if (i.prefix[HLE_PREFIX] != XRELEASE_PREFIX_OPCODE)
3730 {
3731 as_bad (_("instruction `%s' after `xacquire' not allowed"),
3732 i.tm.name);
3733 return 0;
3734 }
3735 if (i.mem_operands == 0
3736 || !operand_type_check (i.types[i.operands - 1], anymem))
3737 {
3738 as_bad (_("memory destination needed for instruction `%s'"
3739 " after `xrelease'"), i.tm.name);
3740 return 0;
3741 }
3742 return 1;
3743 }
3744}
3745
3746/* Try the shortest encoding by shortening operand size. */
3747
3748static void
3749optimize_encoding (void)
3750{
3751 int j;
3752
3753 if (optimize_for_space
3754 && i.reg_operands == 1
3755 && i.imm_operands == 1
3756 && !i.types[1].bitfield.byte
3757 && i.op[0].imms->X_op == O_constant
3758 && fits_in_imm7 (i.op[0].imms->X_add_number)
3759 && ((i.tm.base_opcode == 0xa8
3760 && i.tm.extension_opcode == None)
3761 || (i.tm.base_opcode == 0xf6
3762 && i.tm.extension_opcode == 0x0)))
3763 {
3764 /* Optimize: -Os:
3765 test $imm7, %r64/%r32/%r16 -> test $imm7, %r8
3766 */
3767 unsigned int base_regnum = i.op[1].regs->reg_num;
3768 if (flag_code == CODE_64BIT || base_regnum < 4)
3769 {
3770 i.types[1].bitfield.byte = 1;
3771 /* Ignore the suffix. */
3772 i.suffix = 0;
3773 if (base_regnum >= 4
3774 && !(i.op[1].regs->reg_flags & RegRex))
3775 {
3776 /* Handle SP, BP, SI and DI registers. */
3777 if (i.types[1].bitfield.word)
3778 j = 16;
3779 else if (i.types[1].bitfield.dword)
3780 j = 32;
3781 else
3782 j = 48;
3783 i.op[1].regs -= j;
3784 }
3785 }
3786 }
3787 else if (flag_code == CODE_64BIT
3788 && ((i.reg_operands == 1
3789 && i.imm_operands == 1
3790 && i.op[0].imms->X_op == O_constant
3791 && ((i.tm.base_opcode == 0xb0
3792 && i.tm.extension_opcode == None
3793 && fits_in_unsigned_long (i.op[0].imms->X_add_number))
3794 || (fits_in_imm31 (i.op[0].imms->X_add_number)
3795 && (((i.tm.base_opcode == 0x24
3796 || i.tm.base_opcode == 0xa8)
3797 && i.tm.extension_opcode == None)
3798 || (i.tm.base_opcode == 0x80
3799 && i.tm.extension_opcode == 0x4)
3800 || ((i.tm.base_opcode == 0xf6
3801 || i.tm.base_opcode == 0xc6)
3802 && i.tm.extension_opcode == 0x0)))))
3803 || (i.reg_operands == 2
3804 && i.op[0].regs == i.op[1].regs
3805 && ((i.tm.base_opcode == 0x30
3806 || i.tm.base_opcode == 0x28)
3807 && i.tm.extension_opcode == None)))
3808 && i.types[1].bitfield.qword)
3809 {
3810 /* Optimize: -O:
3811 andq $imm31, %r64 -> andl $imm31, %r32
3812 testq $imm31, %r64 -> testl $imm31, %r32
3813 xorq %r64, %r64 -> xorl %r32, %r32
3814 subq %r64, %r64 -> subl %r32, %r32
3815 movq $imm31, %r64 -> movl $imm31, %r32
3816 movq $imm32, %r64 -> movl $imm32, %r32
3817 */
3818 i.tm.opcode_modifier.norex64 = 1;
3819 if (i.tm.base_opcode == 0xb0 || i.tm.base_opcode == 0xc6)
3820 {
3821 /* Handle
3822 movq $imm31, %r64 -> movl $imm31, %r32
3823 movq $imm32, %r64 -> movl $imm32, %r32
3824 */
3825 i.tm.operand_types[0].bitfield.imm32 = 1;
3826 i.tm.operand_types[0].bitfield.imm32s = 0;
3827 i.tm.operand_types[0].bitfield.imm64 = 0;
3828 i.types[0].bitfield.imm32 = 1;
3829 i.types[0].bitfield.imm32s = 0;
3830 i.types[0].bitfield.imm64 = 0;
3831 i.types[1].bitfield.dword = 1;
3832 i.types[1].bitfield.qword = 0;
3833 if (i.tm.base_opcode == 0xc6)
3834 {
3835 /* Handle
3836 movq $imm31, %r64 -> movl $imm31, %r32
3837 */
3838 i.tm.base_opcode = 0xb0;
3839 i.tm.extension_opcode = None;
3840 i.tm.opcode_modifier.shortform = 1;
3841 i.tm.opcode_modifier.modrm = 0;
3842 }
3843 }
3844 }
3845 else if (optimize > 1
3846 && i.reg_operands == 3
3847 && i.op[0].regs == i.op[1].regs
3848 && !i.types[2].bitfield.xmmword
3849 && (i.tm.opcode_modifier.vex
3850 || (!i.mask
3851 && !i.rounding
3852 && i.tm.opcode_modifier.evex
3853 && cpu_arch_flags.bitfield.cpuavx512vl))
3854 && ((i.tm.base_opcode == 0x55
3855 || i.tm.base_opcode == 0x6655
3856 || i.tm.base_opcode == 0x66df
3857 || i.tm.base_opcode == 0x57
3858 || i.tm.base_opcode == 0x6657
3859 || i.tm.base_opcode == 0x66ef
3860 || i.tm.base_opcode == 0x66f8
3861 || i.tm.base_opcode == 0x66f9
3862 || i.tm.base_opcode == 0x66fa
3863 || i.tm.base_opcode == 0x66fb)
3864 && i.tm.extension_opcode == None))
3865 {
3866 /* Optimize: -O2:
3867 VOP, one of vandnps, vandnpd, vxorps, vxorpd, vpsubb, vpsubd,
3868 vpsubq and vpsubw:
3869 EVEX VOP %zmmM, %zmmM, %zmmN
3870 -> VEX VOP %xmmM, %xmmM, %xmmN (M and N < 16)
3871 -> EVEX VOP %xmmM, %xmmM, %xmmN (M || N >= 16)
3872 EVEX VOP %ymmM, %ymmM, %ymmN
3873 -> VEX VOP %xmmM, %xmmM, %xmmN (M and N < 16)
3874 -> EVEX VOP %xmmM, %xmmM, %xmmN (M || N >= 16)
3875 VEX VOP %ymmM, %ymmM, %ymmN
3876 -> VEX VOP %xmmM, %xmmM, %xmmN
3877 VOP, one of vpandn and vpxor:
3878 VEX VOP %ymmM, %ymmM, %ymmN
3879 -> VEX VOP %xmmM, %xmmM, %xmmN
3880 VOP, one of vpandnd and vpandnq:
3881 EVEX VOP %zmmM, %zmmM, %zmmN
3882 -> VEX vpandn %xmmM, %xmmM, %xmmN (M and N < 16)
3883 -> EVEX VOP %xmmM, %xmmM, %xmmN (M || N >= 16)
3884 EVEX VOP %ymmM, %ymmM, %ymmN
3885 -> VEX vpandn %xmmM, %xmmM, %xmmN (M and N < 16)
3886 -> EVEX VOP %xmmM, %xmmM, %xmmN (M || N >= 16)
3887 VOP, one of vpxord and vpxorq:
3888 EVEX VOP %zmmM, %zmmM, %zmmN
3889 -> VEX vpxor %xmmM, %xmmM, %xmmN (M and N < 16)
3890 -> EVEX VOP %xmmM, %xmmM, %xmmN (M || N >= 16)
3891 EVEX VOP %ymmM, %ymmM, %ymmN
3892 -> VEX vpxor %xmmM, %xmmM, %xmmN (M and N < 16)
3893 -> EVEX VOP %xmmM, %xmmM, %xmmN (M || N >= 16)
3894 */
3895 if (i.tm.opcode_modifier.evex)
3896 {
3897 /* If only lower 16 vector registers are used, we can use
3898 VEX encoding. */
3899 for (j = 0; j < 3; j++)
3900 if (register_number (i.op[j].regs) > 15)
3901 break;
3902
3903 if (j < 3)
3904 i.tm.opcode_modifier.evex = EVEX128;
3905 else
3906 {
3907 i.tm.opcode_modifier.vex = VEX128;
3908 i.tm.opcode_modifier.vexw = VEXW0;
3909 i.tm.opcode_modifier.evex = 0;
3910 }
3911 }
3912 else
3913 i.tm.opcode_modifier.vex = VEX128;
3914
3915 if (i.tm.opcode_modifier.vex)
3916 for (j = 0; j < 3; j++)
3917 {
3918 i.types[j].bitfield.xmmword = 1;
3919 i.types[j].bitfield.ymmword = 0;
3920 }
3921 }
3922}
3923
3924/* This is the guts of the machine-dependent assembler. LINE points to a
3925 machine dependent instruction. This function is supposed to emit
3926 the frags/bytes it assembles to. */
3927
3928void
3929md_assemble (char *line)
3930{
3931 unsigned int j;
3932 char mnemonic[MAX_MNEM_SIZE], mnem_suffix;
3933 const insn_template *t;
3934
3935 /* Initialize globals. */
3936 memset (&i, '\0', sizeof (i));
3937 for (j = 0; j < MAX_OPERANDS; j++)
3938 i.reloc[j] = NO_RELOC;
3939 memset (disp_expressions, '\0', sizeof (disp_expressions));
3940 memset (im_expressions, '\0', sizeof (im_expressions));
3941 save_stack_p = save_stack;
3942
3943 /* First parse an instruction mnemonic & call i386_operand for the operands.
3944 We assume that the scrubber has arranged it so that line[0] is the valid
3945 start of a (possibly prefixed) mnemonic. */
3946
3947 line = parse_insn (line, mnemonic);
3948 if (line == NULL)
3949 return;
3950 mnem_suffix = i.suffix;
3951
3952 line = parse_operands (line, mnemonic);
3953 this_operand = -1;
3954 xfree (i.memop1_string);
3955 i.memop1_string = NULL;
3956 if (line == NULL)
3957 return;
3958
3959 /* Now we've parsed the mnemonic into a set of templates, and have the
3960 operands at hand. */
3961
3962 /* All intel opcodes have reversed operands except for "bound" and
3963 "enter". We also don't reverse intersegment "jmp" and "call"
3964 instructions with 2 immediate operands so that the immediate segment
3965 precedes the offset, as it does when in AT&T mode. */
3966 if (intel_syntax
3967 && i.operands > 1
3968 && (strcmp (mnemonic, "bound") != 0)
3969 && (strcmp (mnemonic, "invlpga") != 0)
3970 && !(operand_type_check (i.types[0], imm)
3971 && operand_type_check (i.types[1], imm)))
3972 swap_operands ();
3973
3974 /* The order of the immediates should be reversed
3975 for 2 immediates extrq and insertq instructions */
3976 if (i.imm_operands == 2
3977 && (strcmp (mnemonic, "extrq") == 0
3978 || strcmp (mnemonic, "insertq") == 0))
3979 swap_2_operands (0, 1);
3980
3981 if (i.imm_operands)
3982 optimize_imm ();
3983
3984 /* Don't optimize displacement for movabs since it only takes 64bit
3985 displacement. */
3986 if (i.disp_operands
3987 && i.disp_encoding != disp_encoding_32bit
3988 && (flag_code != CODE_64BIT
3989 || strcmp (mnemonic, "movabs") != 0))
3990 optimize_disp ();
3991
3992 /* Next, we find a template that matches the given insn,
3993 making sure the overlap of the given operands types is consistent
3994 with the template operand types. */
3995
3996 if (!(t = match_template (mnem_suffix)))
3997 return;
3998
3999 if (sse_check != check_none
4000 && !i.tm.opcode_modifier.noavx
4001 && (i.tm.cpu_flags.bitfield.cpusse
4002 || i.tm.cpu_flags.bitfield.cpusse2
4003 || i.tm.cpu_flags.bitfield.cpusse3
4004 || i.tm.cpu_flags.bitfield.cpussse3
4005 || i.tm.cpu_flags.bitfield.cpusse4_1
4006 || i.tm.cpu_flags.bitfield.cpusse4_2))
4007 {
4008 (sse_check == check_warning
4009 ? as_warn
4010 : as_bad) (_("SSE instruction `%s' is used"), i.tm.name);
4011 }
4012
4013 /* Zap movzx and movsx suffix. The suffix has been set from
4014 "word ptr" or "byte ptr" on the source operand in Intel syntax
4015 or extracted from mnemonic in AT&T syntax. But we'll use
4016 the destination register to choose the suffix for encoding. */
4017 if ((i.tm.base_opcode & ~9) == 0x0fb6)
4018 {
4019 /* In Intel syntax, there must be a suffix. In AT&T syntax, if
4020 there is no suffix, the default will be byte extension. */
4021 if (i.reg_operands != 2
4022 && !i.suffix
4023 && intel_syntax)
4024 as_bad (_("ambiguous operand size for `%s'"), i.tm.name);
4025
4026 i.suffix = 0;
4027 }
4028
4029 if (i.tm.opcode_modifier.fwait)
4030 if (!add_prefix (FWAIT_OPCODE))
4031 return;
4032
4033 /* Check if REP prefix is OK. */
4034 if (i.rep_prefix && !i.tm.opcode_modifier.repprefixok)
4035 {
4036 as_bad (_("invalid instruction `%s' after `%s'"),
4037 i.tm.name, i.rep_prefix);
4038 return;
4039 }
4040
4041 /* Check for lock without a lockable instruction. Destination operand
4042 must be memory unless it is xchg (0x86). */
4043 if (i.prefix[LOCK_PREFIX]
4044 && (!i.tm.opcode_modifier.islockable
4045 || i.mem_operands == 0
4046 || (i.tm.base_opcode != 0x86
4047 && !operand_type_check (i.types[i.operands - 1], anymem))))
4048 {
4049 as_bad (_("expecting lockable instruction after `lock'"));
4050 return;
4051 }
4052
4053 /* Check if HLE prefix is OK. */
4054 if (i.hle_prefix && !check_hle ())
4055 return;
4056
4057 /* Check BND prefix. */
4058 if (i.bnd_prefix && !i.tm.opcode_modifier.bndprefixok)
4059 as_bad (_("expecting valid branch instruction after `bnd'"));
4060
4061 /* Check NOTRACK prefix. */
4062 if (i.notrack_prefix && !i.tm.opcode_modifier.notrackprefixok)
4063 as_bad (_("expecting indirect branch instruction after `notrack'"));
4064
4065 if (i.tm.cpu_flags.bitfield.cpumpx)
4066 {
4067 if (flag_code == CODE_64BIT && i.prefix[ADDR_PREFIX])
4068 as_bad (_("32-bit address isn't allowed in 64-bit MPX instructions."));
4069 else if (flag_code != CODE_16BIT
4070 ? i.prefix[ADDR_PREFIX]
4071 : i.mem_operands && !i.prefix[ADDR_PREFIX])
4072 as_bad (_("16-bit address isn't allowed in MPX instructions"));
4073 }
4074
4075 /* Insert BND prefix. */
4076 if (add_bnd_prefix
4077 && i.tm.opcode_modifier.bndprefixok
4078 && !i.prefix[BND_PREFIX])
4079 add_prefix (BND_PREFIX_OPCODE);
4080
4081 /* Check string instruction segment overrides. */
4082 if (i.tm.opcode_modifier.isstring && i.mem_operands != 0)
4083 {
4084 if (!check_string ())
4085 return;
4086 i.disp_operands = 0;
4087 }
4088
4089 if (optimize && !i.no_optimize && i.tm.opcode_modifier.optimize)
4090 optimize_encoding ();
4091
4092 if (!process_suffix ())
4093 return;
4094
4095 /* Update operand types. */
4096 for (j = 0; j < i.operands; j++)
4097 i.types[j] = operand_type_and (i.types[j], i.tm.operand_types[j]);
4098
4099 /* Make still unresolved immediate matches conform to size of immediate
4100 given in i.suffix. */
4101 if (!finalize_imm ())
4102 return;
4103
4104 if (i.types[0].bitfield.imm1)
4105 i.imm_operands = 0; /* kludge for shift insns. */
4106
4107 /* We only need to check those implicit registers for instructions
4108 with 3 operands or less. */
4109 if (i.operands <= 3)
4110 for (j = 0; j < i.operands; j++)
4111 if (i.types[j].bitfield.inoutportreg
4112 || i.types[j].bitfield.shiftcount
4113 || (i.types[j].bitfield.acc && !i.types[j].bitfield.xmmword))
4114 i.reg_operands--;
4115
4116 /* ImmExt should be processed after SSE2AVX. */
4117 if (!i.tm.opcode_modifier.sse2avx
4118 && i.tm.opcode_modifier.immext)
4119 process_immext ();
4120
4121 /* For insns with operands there are more diddles to do to the opcode. */
4122 if (i.operands)
4123 {
4124 if (!process_operands ())
4125 return;
4126 }
4127 else if (!quiet_warnings && i.tm.opcode_modifier.ugh)
4128 {
4129 /* UnixWare fsub no args is alias for fsubp, fadd -> faddp, etc. */
4130 as_warn (_("translating to `%sp'"), i.tm.name);
4131 }
4132
4133 if (i.tm.opcode_modifier.vex || i.tm.opcode_modifier.evex)
4134 {
4135 if (flag_code == CODE_16BIT)
4136 {
4137 as_bad (_("instruction `%s' isn't supported in 16-bit mode."),
4138 i.tm.name);
4139 return;
4140 }
4141
4142 if (i.tm.opcode_modifier.vex)
4143 build_vex_prefix (t);
4144 else
4145 build_evex_prefix ();
4146 }
4147
4148 /* Handle conversion of 'int $3' --> special int3 insn. XOP or FMA4
4149 instructions may define INT_OPCODE as well, so avoid this corner
4150 case for those instructions that use MODRM. */
4151 if (i.tm.base_opcode == INT_OPCODE
4152 && !i.tm.opcode_modifier.modrm
4153 && i.op[0].imms->X_add_number == 3)
4154 {
4155 i.tm.base_opcode = INT3_OPCODE;
4156 i.imm_operands = 0;
4157 }
4158
4159 if ((i.tm.opcode_modifier.jump
4160 || i.tm.opcode_modifier.jumpbyte
4161 || i.tm.opcode_modifier.jumpdword)
4162 && i.op[0].disps->X_op == O_constant)
4163 {
4164 /* Convert "jmp constant" (and "call constant") to a jump (call) to
4165 the absolute address given by the constant. Since ix86 jumps and
4166 calls are pc relative, we need to generate a reloc. */
4167 i.op[0].disps->X_add_symbol = &abs_symbol;
4168 i.op[0].disps->X_op = O_symbol;
4169 }
4170
4171 if (i.tm.opcode_modifier.rex64)
4172 i.rex |= REX_W;
4173
4174 /* For 8 bit registers we need an empty rex prefix. Also if the
4175 instruction already has a prefix, we need to convert old
4176 registers to new ones. */
4177
4178 if ((i.types[0].bitfield.reg && i.types[0].bitfield.byte
4179 && (i.op[0].regs->reg_flags & RegRex64) != 0)
4180 || (i.types[1].bitfield.reg && i.types[1].bitfield.byte
4181 && (i.op[1].regs->reg_flags & RegRex64) != 0)
4182 || (((i.types[0].bitfield.reg && i.types[0].bitfield.byte)
4183 || (i.types[1].bitfield.reg && i.types[1].bitfield.byte))
4184 && i.rex != 0))
4185 {
4186 int x;
4187
4188 i.rex |= REX_OPCODE;
4189 for (x = 0; x < 2; x++)
4190 {
4191 /* Look for 8 bit operand that uses old registers. */
4192 if (i.types[x].bitfield.reg && i.types[x].bitfield.byte
4193 && (i.op[x].regs->reg_flags & RegRex64) == 0)
4194 {
4195 /* In case it is "hi" register, give up. */
4196 if (i.op[x].regs->reg_num > 3)
4197 as_bad (_("can't encode register '%s%s' in an "
4198 "instruction requiring REX prefix."),
4199 register_prefix, i.op[x].regs->reg_name);
4200
4201 /* Otherwise it is equivalent to the extended register.
4202 Since the encoding doesn't change this is merely
4203 cosmetic cleanup for debug output. */
4204
4205 i.op[x].regs = i.op[x].regs + 8;
4206 }
4207 }
4208 }
4209
4210 if (i.rex == 0 && i.rex_encoding)
4211 {
4212 /* Check if we can add a REX_OPCODE byte. Look for 8 bit operand
4213 that uses legacy register. If it is "hi" register, don't add
4214 the REX_OPCODE byte. */
4215 int x;
4216 for (x = 0; x < 2; x++)
4217 if (i.types[x].bitfield.reg
4218 && i.types[x].bitfield.byte
4219 && (i.op[x].regs->reg_flags & RegRex64) == 0
4220 && i.op[x].regs->reg_num > 3)
4221 {
4222 i.rex_encoding = FALSE;
4223 break;
4224 }
4225
4226 if (i.rex_encoding)
4227 i.rex = REX_OPCODE;
4228 }
4229
4230 if (i.rex != 0)
4231 add_prefix (REX_OPCODE | i.rex);
4232
4233 /* We are ready to output the insn. */
4234 output_insn ();
4235}
4236
4237static char *
4238parse_insn (char *line, char *mnemonic)
4239{
4240 char *l = line;
4241 char *token_start = l;
4242 char *mnem_p;
4243 int supported;
4244 const insn_template *t;
4245 char *dot_p = NULL;
4246
4247 while (1)
4248 {
4249 mnem_p = mnemonic;
4250 while ((*mnem_p = mnemonic_chars[(unsigned char) *l]) != 0)
4251 {
4252 if (*mnem_p == '.')
4253 dot_p = mnem_p;
4254 mnem_p++;
4255 if (mnem_p >= mnemonic + MAX_MNEM_SIZE)
4256 {
4257 as_bad (_("no such instruction: `%s'"), token_start);
4258 return NULL;
4259 }
4260 l++;
4261 }
4262 if (!is_space_char (*l)
4263 && *l != END_OF_INSN
4264 && (intel_syntax
4265 || (*l != PREFIX_SEPARATOR
4266 && *l != ',')))
4267 {
4268 as_bad (_("invalid character %s in mnemonic"),
4269 output_invalid (*l));
4270 return NULL;
4271 }
4272 if (token_start == l)
4273 {
4274 if (!intel_syntax && *l == PREFIX_SEPARATOR)
4275 as_bad (_("expecting prefix; got nothing"));
4276 else
4277 as_bad (_("expecting mnemonic; got nothing"));
4278 return NULL;
4279 }
4280
4281 /* Look up instruction (or prefix) via hash table. */
4282 current_templates = (const templates *) hash_find (op_hash, mnemonic);
4283
4284 if (*l != END_OF_INSN
4285 && (!is_space_char (*l) || l[1] != END_OF_INSN)
4286 && current_templates
4287 && current_templates->start->opcode_modifier.isprefix)
4288 {
4289 if (!cpu_flags_check_cpu64 (current_templates->start->cpu_flags))
4290 {
4291 as_bad ((flag_code != CODE_64BIT
4292 ? _("`%s' is only supported in 64-bit mode")
4293 : _("`%s' is not supported in 64-bit mode")),
4294 current_templates->start->name);
4295 return NULL;
4296 }
4297 /* If we are in 16-bit mode, do not allow addr16 or data16.
4298 Similarly, in 32-bit mode, do not allow addr32 or data32. */
4299 if ((current_templates->start->opcode_modifier.size16
4300 || current_templates->start->opcode_modifier.size32)
4301 && flag_code != CODE_64BIT
4302 && (current_templates->start->opcode_modifier.size32
4303 ^ (flag_code == CODE_16BIT)))
4304 {
4305 as_bad (_("redundant %s prefix"),
4306 current_templates->start->name);
4307 return NULL;
4308 }
4309 if (current_templates->start->opcode_length == 0)
4310 {
4311 /* Handle pseudo prefixes. */
4312 switch (current_templates->start->base_opcode)
4313 {
4314 case 0x0:
4315 /* {disp8} */
4316 i.disp_encoding = disp_encoding_8bit;
4317 break;
4318 case 0x1:
4319 /* {disp32} */
4320 i.disp_encoding = disp_encoding_32bit;
4321 break;
4322 case 0x2:
4323 /* {load} */
4324 i.dir_encoding = dir_encoding_load;
4325 break;
4326 case 0x3:
4327 /* {store} */
4328 i.dir_encoding = dir_encoding_store;
4329 break;
4330 case 0x4:
4331 /* {vex2} */
4332 i.vec_encoding = vex_encoding_vex2;
4333 break;
4334 case 0x5:
4335 /* {vex3} */
4336 i.vec_encoding = vex_encoding_vex3;
4337 break;
4338 case 0x6:
4339 /* {evex} */
4340 i.vec_encoding = vex_encoding_evex;
4341 break;
4342 case 0x7:
4343 /* {rex} */
4344 i.rex_encoding = TRUE;
4345 break;
4346 case 0x8:
4347 /* {nooptimize} */
4348 i.no_optimize = TRUE;
4349 break;
4350 default:
4351 abort ();
4352 }
4353 }
4354 else
4355 {
4356 /* Add prefix, checking for repeated prefixes. */
4357 switch (add_prefix (current_templates->start->base_opcode))
4358 {
4359 case PREFIX_EXIST:
4360 return NULL;
4361 case PREFIX_DS:
4362 if (current_templates->start->cpu_flags.bitfield.cpuibt)
4363 i.notrack_prefix = current_templates->start->name;
4364 break;
4365 case PREFIX_REP:
4366 if (current_templates->start->cpu_flags.bitfield.cpuhle)
4367 i.hle_prefix = current_templates->start->name;
4368 else if (current_templates->start->cpu_flags.bitfield.cpumpx)
4369 i.bnd_prefix = current_templates->start->name;
4370 else
4371 i.rep_prefix = current_templates->start->name;
4372 break;
4373 default:
4374 break;
4375 }
4376 }
4377 /* Skip past PREFIX_SEPARATOR and reset token_start. */
4378 token_start = ++l;
4379 }
4380 else
4381 break;
4382 }
4383
4384 if (!current_templates)
4385 {
4386 /* Check if we should swap operand or force 32bit displacement in
4387 encoding. */
4388 if (mnem_p - 2 == dot_p && dot_p[1] == 's')
4389 i.dir_encoding = dir_encoding_store;
4390 else if (mnem_p - 3 == dot_p
4391 && dot_p[1] == 'd'
4392 && dot_p[2] == '8')
4393 i.disp_encoding = disp_encoding_8bit;
4394 else if (mnem_p - 4 == dot_p
4395 && dot_p[1] == 'd'
4396 && dot_p[2] == '3'
4397 && dot_p[3] == '2')
4398 i.disp_encoding = disp_encoding_32bit;
4399 else
4400 goto check_suffix;
4401 mnem_p = dot_p;
4402 *dot_p = '\0';
4403 current_templates = (const templates *) hash_find (op_hash, mnemonic);
4404 }
4405
4406 if (!current_templates)
4407 {
4408check_suffix:
4409 /* See if we can get a match by trimming off a suffix. */
4410 switch (mnem_p[-1])
4411 {
4412 case WORD_MNEM_SUFFIX:
4413 if (intel_syntax && (intel_float_operand (mnemonic) & 2))
4414 i.suffix = SHORT_MNEM_SUFFIX;
4415 else
4416 /* Fall through. */
4417 case BYTE_MNEM_SUFFIX:
4418 case QWORD_MNEM_SUFFIX:
4419 i.suffix = mnem_p[-1];
4420 mnem_p[-1] = '\0';
4421 current_templates = (const templates *) hash_find (op_hash,
4422 mnemonic);
4423 break;
4424 case SHORT_MNEM_SUFFIX:
4425 case LONG_MNEM_SUFFIX:
4426 if (!intel_syntax)
4427 {
4428 i.suffix = mnem_p[-1];
4429 mnem_p[-1] = '\0';
4430 current_templates = (const templates *) hash_find (op_hash,
4431 mnemonic);
4432 }
4433 break;
4434
4435 /* Intel Syntax. */
4436 case 'd':
4437 if (intel_syntax)
4438 {
4439 if (intel_float_operand (mnemonic) == 1)
4440 i.suffix = SHORT_MNEM_SUFFIX;
4441 else
4442 i.suffix = LONG_MNEM_SUFFIX;
4443 mnem_p[-1] = '\0';
4444 current_templates = (const templates *) hash_find (op_hash,
4445 mnemonic);
4446 }
4447 break;
4448 }
4449 if (!current_templates)
4450 {
4451 as_bad (_("no such instruction: `%s'"), token_start);
4452 return NULL;
4453 }
4454 }
4455
4456 if (current_templates->start->opcode_modifier.jump
4457 || current_templates->start->opcode_modifier.jumpbyte)
4458 {
4459 /* Check for a branch hint. We allow ",pt" and ",pn" for
4460 predict taken and predict not taken respectively.
4461 I'm not sure that branch hints actually do anything on loop
4462 and jcxz insns (JumpByte) for current Pentium4 chips. They
4463 may work in the future and it doesn't hurt to accept them
4464 now. */
4465 if (l[0] == ',' && l[1] == 'p')
4466 {
4467 if (l[2] == 't')
4468 {
4469 if (!add_prefix (DS_PREFIX_OPCODE))
4470 return NULL;
4471 l += 3;
4472 }
4473 else if (l[2] == 'n')
4474 {
4475 if (!add_prefix (CS_PREFIX_OPCODE))
4476 return NULL;
4477 l += 3;
4478 }
4479 }
4480 }
4481 /* Any other comma loses. */
4482 if (*l == ',')
4483 {
4484 as_bad (_("invalid character %s in mnemonic"),
4485 output_invalid (*l));
4486 return NULL;
4487 }
4488
4489 /* Check if instruction is supported on specified architecture. */
4490 supported = 0;
4491 for (t = current_templates->start; t < current_templates->end; ++t)
4492 {
4493 supported |= cpu_flags_match (t);
4494 if (supported == CPU_FLAGS_PERFECT_MATCH)
4495 goto skip;
4496 }
4497
4498 if (!(supported & CPU_FLAGS_64BIT_MATCH))
4499 {
4500 as_bad (flag_code == CODE_64BIT
4501 ? _("`%s' is not supported in 64-bit mode")
4502 : _("`%s' is only supported in 64-bit mode"),
4503 current_templates->start->name);
4504 return NULL;
4505 }
4506 if (supported != CPU_FLAGS_PERFECT_MATCH)
4507 {
4508 as_bad (_("`%s' is not supported on `%s%s'"),
4509 current_templates->start->name,
4510 cpu_arch_name ? cpu_arch_name : default_arch,
4511 cpu_sub_arch_name ? cpu_sub_arch_name : "");
4512 return NULL;
4513 }
4514
4515skip:
4516 if (!cpu_arch_flags.bitfield.cpui386
4517 && (flag_code != CODE_16BIT))
4518 {
4519 as_warn (_("use .code16 to ensure correct addressing mode"));
4520 }
4521
4522 return l;
4523}
4524
4525static char *
4526parse_operands (char *l, const char *mnemonic)
4527{
4528 char *token_start;
4529
4530 /* 1 if operand is pending after ','. */
4531 unsigned int expecting_operand = 0;
4532
4533 /* Non-zero if operand parens not balanced. */
4534 unsigned int paren_not_balanced;
4535
4536 while (*l != END_OF_INSN)
4537 {
4538 /* Skip optional white space before operand. */
4539 if (is_space_char (*l))
4540 ++l;
4541 if (!is_operand_char (*l) && *l != END_OF_INSN && *l != '"')
4542 {
4543 as_bad (_("invalid character %s before operand %d"),
4544 output_invalid (*l),
4545 i.operands + 1);
4546 return NULL;
4547 }
4548 token_start = l; /* After white space. */
4549 paren_not_balanced = 0;
4550 while (paren_not_balanced || *l != ',')
4551 {
4552 if (*l == END_OF_INSN)
4553 {
4554 if (paren_not_balanced)
4555 {
4556 if (!intel_syntax)
4557 as_bad (_("unbalanced parenthesis in operand %d."),
4558 i.operands + 1);
4559 else
4560 as_bad (_("unbalanced brackets in operand %d."),
4561 i.operands + 1);
4562 return NULL;
4563 }
4564 else
4565 break; /* we are done */
4566 }
4567 else if (!is_operand_char (*l) && !is_space_char (*l) && *l != '"')
4568 {
4569 as_bad (_("invalid character %s in operand %d"),
4570 output_invalid (*l),
4571 i.operands + 1);
4572 return NULL;
4573 }
4574 if (!intel_syntax)
4575 {
4576 if (*l == '(')
4577 ++paren_not_balanced;
4578 if (*l == ')')
4579 --paren_not_balanced;
4580 }
4581 else
4582 {
4583 if (*l == '[')
4584 ++paren_not_balanced;
4585 if (*l == ']')
4586 --paren_not_balanced;
4587 }
4588 l++;
4589 }
4590 if (l != token_start)
4591 { /* Yes, we've read in another operand. */
4592 unsigned int operand_ok;
4593 this_operand = i.operands++;
4594 if (i.operands > MAX_OPERANDS)
4595 {
4596 as_bad (_("spurious operands; (%d operands/instruction max)"),
4597 MAX_OPERANDS);
4598 return NULL;
4599 }
4600 i.types[this_operand].bitfield.unspecified = 1;
4601 /* Now parse operand adding info to 'i' as we go along. */
4602 END_STRING_AND_SAVE (l);
4603
4604 if (intel_syntax)
4605 operand_ok =
4606 i386_intel_operand (token_start,
4607 intel_float_operand (mnemonic));
4608 else
4609 operand_ok = i386_att_operand (token_start);
4610
4611 RESTORE_END_STRING (l);
4612 if (!operand_ok)
4613 return NULL;
4614 }
4615 else
4616 {
4617 if (expecting_operand)
4618 {
4619 expecting_operand_after_comma:
4620 as_bad (_("expecting operand after ','; got nothing"));
4621 return NULL;
4622 }
4623 if (*l == ',')
4624 {
4625 as_bad (_("expecting operand before ','; got nothing"));
4626 return NULL;
4627 }
4628 }
4629
4630 /* Now *l must be either ',' or END_OF_INSN. */
4631 if (*l == ',')
4632 {
4633 if (*++l == END_OF_INSN)
4634 {
4635 /* Just skip it, if it's \n complain. */
4636 goto expecting_operand_after_comma;
4637 }
4638 expecting_operand = 1;
4639 }
4640 }
4641 return l;
4642}
4643
4644static void
4645swap_2_operands (int xchg1, int xchg2)
4646{
4647 union i386_op temp_op;
4648 i386_operand_type temp_type;
4649 enum bfd_reloc_code_real temp_reloc;
4650
4651 temp_type = i.types[xchg2];
4652 i.types[xchg2] = i.types[xchg1];
4653 i.types[xchg1] = temp_type;
4654 temp_op = i.op[xchg2];
4655 i.op[xchg2] = i.op[xchg1];
4656 i.op[xchg1] = temp_op;
4657 temp_reloc = i.reloc[xchg2];
4658 i.reloc[xchg2] = i.reloc[xchg1];
4659 i.reloc[xchg1] = temp_reloc;
4660
4661 if (i.mask)
4662 {
4663 if (i.mask->operand == xchg1)
4664 i.mask->operand = xchg2;
4665 else if (i.mask->operand == xchg2)
4666 i.mask->operand = xchg1;
4667 }
4668 if (i.broadcast)
4669 {
4670 if (i.broadcast->operand == xchg1)
4671 i.broadcast->operand = xchg2;
4672 else if (i.broadcast->operand == xchg2)
4673 i.broadcast->operand = xchg1;
4674 }
4675 if (i.rounding)
4676 {
4677 if (i.rounding->operand == xchg1)
4678 i.rounding->operand = xchg2;
4679 else if (i.rounding->operand == xchg2)
4680 i.rounding->operand = xchg1;
4681 }
4682}
4683
4684static void
4685swap_operands (void)
4686{
4687 switch (i.operands)
4688 {
4689 case 5:
4690 case 4:
4691 swap_2_operands (1, i.operands - 2);
4692 /* Fall through. */
4693 case 3:
4694 case 2:
4695 swap_2_operands (0, i.operands - 1);
4696 break;
4697 default:
4698 abort ();
4699 }
4700
4701 if (i.mem_operands == 2)
4702 {
4703 const seg_entry *temp_seg;
4704 temp_seg = i.seg[0];
4705 i.seg[0] = i.seg[1];
4706 i.seg[1] = temp_seg;
4707 }
4708}
4709
4710/* Try to ensure constant immediates are represented in the smallest
4711 opcode possible. */
4712static void
4713optimize_imm (void)
4714{
4715 char guess_suffix = 0;
4716 int op;
4717
4718 if (i.suffix)
4719 guess_suffix = i.suffix;
4720 else if (i.reg_operands)
4721 {
4722 /* Figure out a suffix from the last register operand specified.
4723 We can't do this properly yet, ie. excluding InOutPortReg,
4724 but the following works for instructions with immediates.
4725 In any case, we can't set i.suffix yet. */
4726 for (op = i.operands; --op >= 0;)
4727 if (i.types[op].bitfield.reg && i.types[op].bitfield.byte)
4728 {
4729 guess_suffix = BYTE_MNEM_SUFFIX;
4730 break;
4731 }
4732 else if (i.types[op].bitfield.reg && i.types[op].bitfield.word)
4733 {
4734 guess_suffix = WORD_MNEM_SUFFIX;
4735 break;
4736 }
4737 else if (i.types[op].bitfield.reg && i.types[op].bitfield.dword)
4738 {
4739 guess_suffix = LONG_MNEM_SUFFIX;
4740 break;
4741 }
4742 else if (i.types[op].bitfield.reg && i.types[op].bitfield.qword)
4743 {
4744 guess_suffix = QWORD_MNEM_SUFFIX;
4745 break;
4746 }
4747 }
4748 else if ((flag_code == CODE_16BIT) ^ (i.prefix[DATA_PREFIX] != 0))
4749 guess_suffix = WORD_MNEM_SUFFIX;
4750
4751 for (op = i.operands; --op >= 0;)
4752 if (operand_type_check (i.types[op], imm))
4753 {
4754 switch (i.op[op].imms->X_op)
4755 {
4756 case O_constant:
4757 /* If a suffix is given, this operand may be shortened. */
4758 switch (guess_suffix)
4759 {
4760 case LONG_MNEM_SUFFIX:
4761 i.types[op].bitfield.imm32 = 1;
4762 i.types[op].bitfield.imm64 = 1;
4763 break;
4764 case WORD_MNEM_SUFFIX:
4765 i.types[op].bitfield.imm16 = 1;
4766 i.types[op].bitfield.imm32 = 1;
4767 i.types[op].bitfield.imm32s = 1;
4768 i.types[op].bitfield.imm64 = 1;
4769 break;
4770 case BYTE_MNEM_SUFFIX:
4771 i.types[op].bitfield.imm8 = 1;
4772 i.types[op].bitfield.imm8s = 1;
4773 i.types[op].bitfield.imm16 = 1;
4774 i.types[op].bitfield.imm32 = 1;
4775 i.types[op].bitfield.imm32s = 1;
4776 i.types[op].bitfield.imm64 = 1;
4777 break;
4778 }
4779
4780 /* If this operand is at most 16 bits, convert it
4781 to a signed 16 bit number before trying to see
4782 whether it will fit in an even smaller size.
4783 This allows a 16-bit operand such as $0xffe0 to
4784 be recognised as within Imm8S range. */
4785 if ((i.types[op].bitfield.imm16)
4786 && (i.op[op].imms->X_add_number & ~(offsetT) 0xffff) == 0)
4787 {
4788 i.op[op].imms->X_add_number =
4789 (((i.op[op].imms->X_add_number & 0xffff) ^ 0x8000) - 0x8000);
4790 }
4791#ifdef BFD64
4792 /* Store 32-bit immediate in 64-bit for 64-bit BFD. */
4793 if ((i.types[op].bitfield.imm32)
4794 && ((i.op[op].imms->X_add_number & ~(((offsetT) 2 << 31) - 1))
4795 == 0))
4796 {
4797 i.op[op].imms->X_add_number = ((i.op[op].imms->X_add_number
4798 ^ ((offsetT) 1 << 31))
4799 - ((offsetT) 1 << 31));
4800 }
4801#endif
4802 i.types[op]
4803 = operand_type_or (i.types[op],
4804 smallest_imm_type (i.op[op].imms->X_add_number));
4805
4806 /* We must avoid matching of Imm32 templates when 64bit
4807 only immediate is available. */
4808 if (guess_suffix == QWORD_MNEM_SUFFIX)
4809 i.types[op].bitfield.imm32 = 0;
4810 break;
4811
4812 case O_absent:
4813 case O_register:
4814 abort ();
4815
4816 /* Symbols and expressions. */
4817 default:
4818 /* Convert symbolic operand to proper sizes for matching, but don't
4819 prevent matching a set of insns that only supports sizes other
4820 than those matching the insn suffix. */
4821 {
4822 i386_operand_type mask, allowed;
4823 const insn_template *t;
4824
4825 operand_type_set (&mask, 0);
4826 operand_type_set (&allowed, 0);
4827
4828 for (t = current_templates->start;
4829 t < current_templates->end;
4830 ++t)
4831 allowed = operand_type_or (allowed,
4832 t->operand_types[op]);
4833 switch (guess_suffix)
4834 {
4835 case QWORD_MNEM_SUFFIX:
4836 mask.bitfield.imm64 = 1;
4837 mask.bitfield.imm32s = 1;
4838 break;
4839 case LONG_MNEM_SUFFIX:
4840 mask.bitfield.imm32 = 1;
4841 break;
4842 case WORD_MNEM_SUFFIX:
4843 mask.bitfield.imm16 = 1;
4844 break;
4845 case BYTE_MNEM_SUFFIX:
4846 mask.bitfield.imm8 = 1;
4847 break;
4848 default:
4849 break;
4850 }
4851 allowed = operand_type_and (mask, allowed);
4852 if (!operand_type_all_zero (&allowed))
4853 i.types[op] = operand_type_and (i.types[op], mask);
4854 }
4855 break;
4856 }
4857 }
4858}
4859
4860/* Try to use the smallest displacement type too. */
4861static void
4862optimize_disp (void)
4863{
4864 int op;
4865
4866 for (op = i.operands; --op >= 0;)
4867 if (operand_type_check (i.types[op], disp))
4868 {
4869 if (i.op[op].disps->X_op == O_constant)
4870 {
4871 offsetT op_disp = i.op[op].disps->X_add_number;
4872
4873 if (i.types[op].bitfield.disp16
4874 && (op_disp & ~(offsetT) 0xffff) == 0)
4875 {
4876 /* If this operand is at most 16 bits, convert
4877 to a signed 16 bit number and don't use 64bit
4878 displacement. */
4879 op_disp = (((op_disp & 0xffff) ^ 0x8000) - 0x8000);
4880 i.types[op].bitfield.disp64 = 0;
4881 }
4882#ifdef BFD64
4883 /* Optimize 64-bit displacement to 32-bit for 64-bit BFD. */
4884 if (i.types[op].bitfield.disp32
4885 && (op_disp & ~(((offsetT) 2 << 31) - 1)) == 0)
4886 {
4887 /* If this operand is at most 32 bits, convert
4888 to a signed 32 bit number and don't use 64bit
4889 displacement. */
4890 op_disp &= (((offsetT) 2 << 31) - 1);
4891 op_disp = (op_disp ^ ((offsetT) 1 << 31)) - ((addressT) 1 << 31);
4892 i.types[op].bitfield.disp64 = 0;
4893 }
4894#endif
4895 if (!op_disp && i.types[op].bitfield.baseindex)
4896 {
4897 i.types[op].bitfield.disp8 = 0;
4898 i.types[op].bitfield.disp16 = 0;
4899 i.types[op].bitfield.disp32 = 0;
4900 i.types[op].bitfield.disp32s = 0;
4901 i.types[op].bitfield.disp64 = 0;
4902 i.op[op].disps = 0;
4903 i.disp_operands--;
4904 }
4905 else if (flag_code == CODE_64BIT)
4906 {
4907 if (fits_in_signed_long (op_disp))
4908 {
4909 i.types[op].bitfield.disp64 = 0;
4910 i.types[op].bitfield.disp32s = 1;
4911 }
4912 if (i.prefix[ADDR_PREFIX]
4913 && fits_in_unsigned_long (op_disp))
4914 i.types[op].bitfield.disp32 = 1;
4915 }
4916 if ((i.types[op].bitfield.disp32
4917 || i.types[op].bitfield.disp32s
4918 || i.types[op].bitfield.disp16)
4919 && fits_in_disp8 (op_disp))
4920 i.types[op].bitfield.disp8 = 1;
4921 }
4922 else if (i.reloc[op] == BFD_RELOC_386_TLS_DESC_CALL
4923 || i.reloc[op] == BFD_RELOC_X86_64_TLSDESC_CALL)
4924 {
4925 fix_new_exp (frag_now, frag_more (0) - frag_now->fr_literal, 0,
4926 i.op[op].disps, 0, i.reloc[op]);
4927 i.types[op].bitfield.disp8 = 0;
4928 i.types[op].bitfield.disp16 = 0;
4929 i.types[op].bitfield.disp32 = 0;
4930 i.types[op].bitfield.disp32s = 0;
4931 i.types[op].bitfield.disp64 = 0;
4932 }
4933 else
4934 /* We only support 64bit displacement on constants. */
4935 i.types[op].bitfield.disp64 = 0;
4936 }
4937}
4938
4939/* Check if operands are valid for the instruction. */
4940
4941static int
4942check_VecOperands (const insn_template *t)
4943{
4944 unsigned int op;
4945
4946 /* Without VSIB byte, we can't have a vector register for index. */
4947 if (!t->opcode_modifier.vecsib
4948 && i.index_reg
4949 && (i.index_reg->reg_type.bitfield.xmmword
4950 || i.index_reg->reg_type.bitfield.ymmword
4951 || i.index_reg->reg_type.bitfield.zmmword))
4952 {
4953 i.error = unsupported_vector_index_register;
4954 return 1;
4955 }
4956
4957 /* Check if default mask is allowed. */
4958 if (t->opcode_modifier.nodefmask
4959 && (!i.mask || i.mask->mask->reg_num == 0))
4960 {
4961 i.error = no_default_mask;
4962 return 1;
4963 }
4964
4965 /* For VSIB byte, we need a vector register for index, and all vector
4966 registers must be distinct. */
4967 if (t->opcode_modifier.vecsib)
4968 {
4969 if (!i.index_reg
4970 || !((t->opcode_modifier.vecsib == VecSIB128
4971 && i.index_reg->reg_type.bitfield.xmmword)
4972 || (t->opcode_modifier.vecsib == VecSIB256
4973 && i.index_reg->reg_type.bitfield.ymmword)
4974 || (t->opcode_modifier.vecsib == VecSIB512
4975 && i.index_reg->reg_type.bitfield.zmmword)))
4976 {
4977 i.error = invalid_vsib_address;
4978 return 1;
4979 }
4980
4981 gas_assert (i.reg_operands == 2 || i.mask);
4982 if (i.reg_operands == 2 && !i.mask)
4983 {
4984 gas_assert (i.types[0].bitfield.regsimd);
4985 gas_assert (i.types[0].bitfield.xmmword
4986 || i.types[0].bitfield.ymmword);
4987 gas_assert (i.types[2].bitfield.regsimd);
4988 gas_assert (i.types[2].bitfield.xmmword
4989 || i.types[2].bitfield.ymmword);
4990 if (operand_check == check_none)
4991 return 0;
4992 if (register_number (i.op[0].regs)
4993 != register_number (i.index_reg)
4994 && register_number (i.op[2].regs)
4995 != register_number (i.index_reg)
4996 && register_number (i.op[0].regs)
4997 != register_number (i.op[2].regs))
4998 return 0;
4999 if (operand_check == check_error)
5000 {
5001 i.error = invalid_vector_register_set;
5002 return 1;
5003 }
5004 as_warn (_("mask, index, and destination registers should be distinct"));
5005 }
5006 else if (i.reg_operands == 1 && i.mask)
5007 {
5008 if (i.types[1].bitfield.regsimd
5009 && (i.types[1].bitfield.xmmword
5010 || i.types[1].bitfield.ymmword
5011 || i.types[1].bitfield.zmmword)
5012 && (register_number (i.op[1].regs)
5013 == register_number (i.index_reg)))
5014 {
5015 if (operand_check == check_error)
5016 {
5017 i.error = invalid_vector_register_set;
5018 return 1;
5019 }
5020 if (operand_check != check_none)
5021 as_warn (_("index and destination registers should be distinct"));
5022 }
5023 }
5024 }
5025
5026 /* Check if broadcast is supported by the instruction and is applied
5027 to the memory operand. */
5028 if (i.broadcast)
5029 {
5030 int broadcasted_opnd_size;
5031
5032 /* Check if specified broadcast is supported in this instruction,
5033 and it's applied to memory operand of DWORD or QWORD type,
5034 depending on VecESize. */
5035 if (i.broadcast->type != t->opcode_modifier.broadcast
5036 || !i.types[i.broadcast->operand].bitfield.mem
5037 || (t->opcode_modifier.vecesize == 0
5038 && !i.types[i.broadcast->operand].bitfield.dword
5039 && !i.types[i.broadcast->operand].bitfield.unspecified)
5040 || (t->opcode_modifier.vecesize == 1
5041 && !i.types[i.broadcast->operand].bitfield.qword
5042 && !i.types[i.broadcast->operand].bitfield.unspecified))
5043 goto bad_broadcast;
5044
5045 broadcasted_opnd_size = t->opcode_modifier.vecesize ? 64 : 32;
5046 if (i.broadcast->type == BROADCAST_1TO16)
5047 broadcasted_opnd_size <<= 4; /* Broadcast 1to16. */
5048 else if (i.broadcast->type == BROADCAST_1TO8)
5049 broadcasted_opnd_size <<= 3; /* Broadcast 1to8. */
5050 else if (i.broadcast->type == BROADCAST_1TO4)
5051 broadcasted_opnd_size <<= 2; /* Broadcast 1to4. */
5052 else if (i.broadcast->type == BROADCAST_1TO2)
5053 broadcasted_opnd_size <<= 1; /* Broadcast 1to2. */
5054 else
5055 goto bad_broadcast;
5056
5057 if ((broadcasted_opnd_size == 256
5058 && !t->operand_types[i.broadcast->operand].bitfield.ymmword)
5059 || (broadcasted_opnd_size == 512
5060 && !t->operand_types[i.broadcast->operand].bitfield.zmmword))
5061 {
5062 bad_broadcast:
5063 i.error = unsupported_broadcast;
5064 return 1;
5065 }
5066 }
5067 /* If broadcast is supported in this instruction, we need to check if
5068 operand of one-element size isn't specified without broadcast. */
5069 else if (t->opcode_modifier.broadcast && i.mem_operands)
5070 {
5071 /* Find memory operand. */
5072 for (op = 0; op < i.operands; op++)
5073 if (operand_type_check (i.types[op], anymem))
5074 break;
5075 gas_assert (op < i.operands);
5076 /* Check size of the memory operand. */
5077 if ((t->opcode_modifier.vecesize == 0
5078 && i.types[op].bitfield.dword)
5079 || (t->opcode_modifier.vecesize == 1
5080 && i.types[op].bitfield.qword))
5081 {
5082 i.error = broadcast_needed;
5083 return 1;
5084 }
5085 }
5086
5087 /* Check if requested masking is supported. */
5088 if (i.mask
5089 && (!t->opcode_modifier.masking
5090 || (i.mask->zeroing
5091 && t->opcode_modifier.masking == MERGING_MASKING)))
5092 {
5093 i.error = unsupported_masking;
5094 return 1;
5095 }
5096
5097 /* Check if masking is applied to dest operand. */
5098 if (i.mask && (i.mask->operand != (int) (i.operands - 1)))
5099 {
5100 i.error = mask_not_on_destination;
5101 return 1;
5102 }
5103
5104 /* Check RC/SAE. */
5105 if (i.rounding)
5106 {
5107 if ((i.rounding->type != saeonly
5108 && !t->opcode_modifier.staticrounding)
5109 || (i.rounding->type == saeonly
5110 && (t->opcode_modifier.staticrounding
5111 || !t->opcode_modifier.sae)))
5112 {
5113 i.error = unsupported_rc_sae;
5114 return 1;
5115 }
5116 /* If the instruction has several immediate operands and one of
5117 them is rounding, the rounding operand should be the last
5118 immediate operand. */
5119 if (i.imm_operands > 1
5120 && i.rounding->operand != (int) (i.imm_operands - 1))
5121 {
5122 i.error = rc_sae_operand_not_last_imm;
5123 return 1;
5124 }
5125 }
5126
5127 /* Check vector Disp8 operand. */
5128 if (t->opcode_modifier.disp8memshift
5129 && i.disp_encoding != disp_encoding_32bit)
5130 {
5131 if (i.broadcast)
5132 i.memshift = t->opcode_modifier.vecesize ? 3 : 2;
5133 else
5134 i.memshift = t->opcode_modifier.disp8memshift;
5135
5136 for (op = 0; op < i.operands; op++)
5137 if (operand_type_check (i.types[op], disp)
5138 && i.op[op].disps->X_op == O_constant)
5139 {
5140 if (fits_in_disp8 (i.op[op].disps->X_add_number))
5141 {
5142 i.types[op].bitfield.disp8 = 1;
5143 return 0;
5144 }
5145 i.types[op].bitfield.disp8 = 0;
5146 }
5147 }
5148
5149 i.memshift = 0;
5150
5151 return 0;
5152}
5153
5154/* Check if operands are valid for the instruction. Update VEX
5155 operand types. */
5156
5157static int
5158VEX_check_operands (const insn_template *t)
5159{
5160 if (i.vec_encoding == vex_encoding_evex)
5161 {
5162 /* This instruction must be encoded with EVEX prefix. */
5163 if (!t->opcode_modifier.evex)
5164 {
5165 i.error = unsupported;
5166 return 1;
5167 }
5168 return 0;
5169 }
5170
5171 if (!t->opcode_modifier.vex)
5172 {
5173 /* This instruction template doesn't have VEX prefix. */
5174 if (i.vec_encoding != vex_encoding_default)
5175 {
5176 i.error = unsupported;
5177 return 1;
5178 }
5179 return 0;
5180 }
5181
5182 /* Only check VEX_Imm4, which must be the first operand. */
5183 if (t->operand_types[0].bitfield.vec_imm4)
5184 {
5185 if (i.op[0].imms->X_op != O_constant
5186 || !fits_in_imm4 (i.op[0].imms->X_add_number))
5187 {
5188 i.error = bad_imm4;
5189 return 1;
5190 }
5191
5192 /* Turn off Imm8 so that update_imm won't complain. */
5193 i.types[0] = vec_imm4;
5194 }
5195
5196 return 0;
5197}
5198
5199static const insn_template *
5200match_template (char mnem_suffix)
5201{
5202 /* Points to template once we've found it. */
5203 const insn_template *t;
5204 i386_operand_type overlap0, overlap1, overlap2, overlap3;
5205 i386_operand_type overlap4;
5206 unsigned int found_reverse_match;
5207 i386_opcode_modifier suffix_check, mnemsuf_check;
5208 i386_operand_type operand_types [MAX_OPERANDS];
5209 int addr_prefix_disp;
5210 unsigned int j;
5211 unsigned int found_cpu_match;
5212 unsigned int check_register;
5213 enum i386_error specific_error = 0;
5214
5215#if MAX_OPERANDS != 5
5216# error "MAX_OPERANDS must be 5."
5217#endif
5218
5219 found_reverse_match = 0;
5220 addr_prefix_disp = -1;
5221
5222 memset (&suffix_check, 0, sizeof (suffix_check));
5223 if (i.suffix == BYTE_MNEM_SUFFIX)
5224 suffix_check.no_bsuf = 1;
5225 else if (i.suffix == WORD_MNEM_SUFFIX)
5226 suffix_check.no_wsuf = 1;
5227 else if (i.suffix == SHORT_MNEM_SUFFIX)
5228 suffix_check.no_ssuf = 1;
5229 else if (i.suffix == LONG_MNEM_SUFFIX)
5230 suffix_check.no_lsuf = 1;
5231 else if (i.suffix == QWORD_MNEM_SUFFIX)
5232 suffix_check.no_qsuf = 1;
5233 else if (i.suffix == LONG_DOUBLE_MNEM_SUFFIX)
5234 suffix_check.no_ldsuf = 1;
5235
5236 memset (&mnemsuf_check, 0, sizeof (mnemsuf_check));
5237 if (intel_syntax)
5238 {
5239 switch (mnem_suffix)
5240 {
5241 case BYTE_MNEM_SUFFIX: mnemsuf_check.no_bsuf = 1; break;
5242 case WORD_MNEM_SUFFIX: mnemsuf_check.no_wsuf = 1; break;
5243 case SHORT_MNEM_SUFFIX: mnemsuf_check.no_ssuf = 1; break;
5244 case LONG_MNEM_SUFFIX: mnemsuf_check.no_lsuf = 1; break;
5245 case QWORD_MNEM_SUFFIX: mnemsuf_check.no_qsuf = 1; break;
5246 }
5247 }
5248
5249 /* Must have right number of operands. */
5250 i.error = number_of_operands_mismatch;
5251
5252 for (t = current_templates->start; t < current_templates->end; t++)
5253 {
5254 addr_prefix_disp = -1;
5255
5256 if (i.operands != t->operands)
5257 continue;
5258
5259 /* Check processor support. */
5260 i.error = unsupported;
5261 found_cpu_match = (cpu_flags_match (t)
5262 == CPU_FLAGS_PERFECT_MATCH);
5263 if (!found_cpu_match)
5264 continue;
5265
5266 /* Check old gcc support. */
5267 i.error = old_gcc_only;
5268 if (!old_gcc && t->opcode_modifier.oldgcc)
5269 continue;
5270
5271 /* Check AT&T mnemonic. */
5272 i.error = unsupported_with_intel_mnemonic;
5273 if (intel_mnemonic && t->opcode_modifier.attmnemonic)
5274 continue;
5275
5276 /* Check AT&T/Intel syntax and Intel64/AMD64 ISA. */
5277 i.error = unsupported_syntax;
5278 if ((intel_syntax && t->opcode_modifier.attsyntax)
5279 || (!intel_syntax && t->opcode_modifier.intelsyntax)
5280 || (intel64 && t->opcode_modifier.amd64)
5281 || (!intel64 && t->opcode_modifier.intel64))
5282 continue;
5283
5284 /* Check the suffix, except for some instructions in intel mode. */
5285 i.error = invalid_instruction_suffix;
5286 if ((!intel_syntax || !t->opcode_modifier.ignoresize)
5287 && ((t->opcode_modifier.no_bsuf && suffix_check.no_bsuf)
5288 || (t->opcode_modifier.no_wsuf && suffix_check.no_wsuf)
5289 || (t->opcode_modifier.no_lsuf && suffix_check.no_lsuf)
5290 || (t->opcode_modifier.no_ssuf && suffix_check.no_ssuf)
5291 || (t->opcode_modifier.no_qsuf && suffix_check.no_qsuf)
5292 || (t->opcode_modifier.no_ldsuf && suffix_check.no_ldsuf)))
5293 continue;
5294 /* In Intel mode all mnemonic suffixes must be explicitly allowed. */
5295 if ((t->opcode_modifier.no_bsuf && mnemsuf_check.no_bsuf)
5296 || (t->opcode_modifier.no_wsuf && mnemsuf_check.no_wsuf)
5297 || (t->opcode_modifier.no_lsuf && mnemsuf_check.no_lsuf)
5298 || (t->opcode_modifier.no_ssuf && mnemsuf_check.no_ssuf)
5299 || (t->opcode_modifier.no_qsuf && mnemsuf_check.no_qsuf)
5300 || (t->opcode_modifier.no_ldsuf && mnemsuf_check.no_ldsuf))
5301 continue;
5302
5303 if (!operand_size_match (t))
5304 continue;
5305
5306 for (j = 0; j < MAX_OPERANDS; j++)
5307 operand_types[j] = t->operand_types[j];
5308
5309 /* In general, don't allow 64-bit operands in 32-bit mode. */
5310 if (i.suffix == QWORD_MNEM_SUFFIX
5311 && flag_code != CODE_64BIT
5312 && (intel_syntax
5313 ? (!t->opcode_modifier.ignoresize
5314 && !intel_float_operand (t->name))
5315 : intel_float_operand (t->name) != 2)
5316 && ((!operand_types[0].bitfield.regmmx
5317 && !operand_types[0].bitfield.regsimd)
5318 || (!operand_types[t->operands > 1].bitfield.regmmx
5319 && !operand_types[t->operands > 1].bitfield.regsimd))
5320 && (t->base_opcode != 0x0fc7
5321 || t->extension_opcode != 1 /* cmpxchg8b */))
5322 continue;
5323
5324 /* In general, don't allow 32-bit operands on pre-386. */
5325 else if (i.suffix == LONG_MNEM_SUFFIX
5326 && !cpu_arch_flags.bitfield.cpui386
5327 && (intel_syntax
5328 ? (!t->opcode_modifier.ignoresize
5329 && !intel_float_operand (t->name))
5330 : intel_float_operand (t->name) != 2)
5331 && ((!operand_types[0].bitfield.regmmx
5332 && !operand_types[0].bitfield.regsimd)
5333 || (!operand_types[t->operands > 1].bitfield.regmmx
5334 && !operand_types[t->operands > 1].bitfield.regsimd)))
5335 continue;
5336
5337 /* Do not verify operands when there are none. */
5338 else
5339 {
5340 if (!t->operands)
5341 /* We've found a match; break out of loop. */
5342 break;
5343 }
5344
5345 /* Address size prefix will turn Disp64/Disp32/Disp16 operand
5346 into Disp32/Disp16/Disp32 operand. */
5347 if (i.prefix[ADDR_PREFIX] != 0)
5348 {
5349 /* There should be only one Disp operand. */
5350 switch (flag_code)
5351 {
5352 case CODE_16BIT:
5353 for (j = 0; j < MAX_OPERANDS; j++)
5354 {
5355 if (operand_types[j].bitfield.disp16)
5356 {
5357 addr_prefix_disp = j;
5358 operand_types[j].bitfield.disp32 = 1;
5359 operand_types[j].bitfield.disp16 = 0;
5360 break;
5361 }
5362 }
5363 break;
5364 case CODE_32BIT:
5365 for (j = 0; j < MAX_OPERANDS; j++)
5366 {
5367 if (operand_types[j].bitfield.disp32)
5368 {
5369 addr_prefix_disp = j;
5370 operand_types[j].bitfield.disp32 = 0;
5371 operand_types[j].bitfield.disp16 = 1;
5372 break;
5373 }
5374 }
5375 break;
5376 case CODE_64BIT:
5377 for (j = 0; j < MAX_OPERANDS; j++)
5378 {
5379 if (operand_types[j].bitfield.disp64)
5380 {
5381 addr_prefix_disp = j;
5382 operand_types[j].bitfield.disp64 = 0;
5383 operand_types[j].bitfield.disp32 = 1;
5384 break;
5385 }
5386 }
5387 break;
5388 }
5389 }
5390
5391 /* Force 0x8b encoding for "mov foo@GOT, %eax". */
5392 if (i.reloc[0] == BFD_RELOC_386_GOT32 && t->base_opcode == 0xa0)
5393 continue;
5394
5395 /* We check register size if needed. */
5396 check_register = t->opcode_modifier.checkregsize;
5397 overlap0 = operand_type_and (i.types[0], operand_types[0]);
5398 switch (t->operands)
5399 {
5400 case 1:
5401 if (!operand_type_match (overlap0, i.types[0]))
5402 continue;
5403 break;
5404 case 2:
5405 /* xchg %eax, %eax is a special case. It is an alias for nop
5406 only in 32bit mode and we can use opcode 0x90. In 64bit
5407 mode, we can't use 0x90 for xchg %eax, %eax since it should
5408 zero-extend %eax to %rax. */
5409 if (flag_code == CODE_64BIT
5410 && t->base_opcode == 0x90
5411 && operand_type_equal (&i.types [0], &acc32)
5412 && operand_type_equal (&i.types [1], &acc32))
5413 continue;
5414 /* If we want store form, we reverse direction of operands. */
5415 if (i.dir_encoding == dir_encoding_store
5416 && t->opcode_modifier.d)
5417 goto check_reverse;
5418 /* Fall through. */
5419
5420 case 3:
5421 /* If we want store form, we skip the current load. */
5422 if (i.dir_encoding == dir_encoding_store
5423 && i.mem_operands == 0
5424 && t->opcode_modifier.load)
5425 continue;
5426 /* Fall through. */
5427 case 4:
5428 case 5:
5429 overlap1 = operand_type_and (i.types[1], operand_types[1]);
5430 if (!operand_type_match (overlap0, i.types[0])
5431 || !operand_type_match (overlap1, i.types[1])
5432 || (check_register
5433 && !operand_type_register_match (i.types[0],
5434 operand_types[0],
5435 i.types[1],
5436 operand_types[1])))
5437 {
5438 /* Check if other direction is valid ... */
5439 if (!t->opcode_modifier.d && !t->opcode_modifier.floatd)
5440 continue;
5441
5442check_reverse:
5443 /* Try reversing direction of operands. */
5444 overlap0 = operand_type_and (i.types[0], operand_types[1]);
5445 overlap1 = operand_type_and (i.types[1], operand_types[0]);
5446 if (!operand_type_match (overlap0, i.types[0])
5447 || !operand_type_match (overlap1, i.types[1])
5448 || (check_register
5449 && !operand_type_register_match (i.types[0],
5450 operand_types[1],
5451 i.types[1],
5452 operand_types[0])))
5453 {
5454 /* Does not match either direction. */
5455 continue;
5456 }
5457 /* found_reverse_match holds which of D or FloatDR
5458 we've found. */
5459 if (t->opcode_modifier.d)
5460 found_reverse_match = Opcode_D;
5461 else if (t->opcode_modifier.floatd)
5462 found_reverse_match = Opcode_FloatD;
5463 else
5464 found_reverse_match = 0;
5465 if (t->opcode_modifier.floatr)
5466 found_reverse_match |= Opcode_FloatR;
5467 }
5468 else
5469 {
5470 /* Found a forward 2 operand match here. */
5471 switch (t->operands)
5472 {
5473 case 5:
5474 overlap4 = operand_type_and (i.types[4],
5475 operand_types[4]);
5476 /* Fall through. */
5477 case 4:
5478 overlap3 = operand_type_and (i.types[3],
5479 operand_types[3]);
5480 /* Fall through. */
5481 case 3:
5482 overlap2 = operand_type_and (i.types[2],
5483 operand_types[2]);
5484 break;
5485 }
5486
5487 switch (t->operands)
5488 {
5489 case 5:
5490 if (!operand_type_match (overlap4, i.types[4])
5491 || !operand_type_register_match (i.types[3],
5492 operand_types[3],
5493 i.types[4],
5494 operand_types[4]))
5495 continue;
5496 /* Fall through. */
5497 case 4:
5498 if (!operand_type_match (overlap3, i.types[3])
5499 || (check_register
5500 && !operand_type_register_match (i.types[2],
5501 operand_types[2],
5502 i.types[3],
5503 operand_types[3])))
5504 continue;
5505 /* Fall through. */
5506 case 3:
5507 /* Here we make use of the fact that there are no
5508 reverse match 3 operand instructions, and all 3
5509 operand instructions only need to be checked for
5510 register consistency between operands 2 and 3. */
5511 if (!operand_type_match (overlap2, i.types[2])
5512 || (check_register
5513 && !operand_type_register_match (i.types[1],
5514 operand_types[1],
5515 i.types[2],
5516 operand_types[2])))
5517 continue;
5518 break;
5519 }
5520 }
5521 /* Found either forward/reverse 2, 3 or 4 operand match here:
5522 slip through to break. */
5523 }
5524 if (!found_cpu_match)
5525 {
5526 found_reverse_match = 0;
5527 continue;
5528 }
5529
5530 /* Check if vector and VEX operands are valid. */
5531 if (check_VecOperands (t) || VEX_check_operands (t))
5532 {
5533 specific_error = i.error;
5534 continue;
5535 }
5536
5537 /* We've found a match; break out of loop. */
5538 break;
5539 }
5540
5541 if (t == current_templates->end)
5542 {
5543 /* We found no match. */
5544 const char *err_msg;
5545 switch (specific_error ? specific_error : i.error)
5546 {
5547 default:
5548 abort ();
5549 case operand_size_mismatch:
5550 err_msg = _("operand size mismatch");
5551 break;
5552 case operand_type_mismatch:
5553 err_msg = _("operand type mismatch");
5554 break;
5555 case register_type_mismatch:
5556 err_msg = _("register type mismatch");
5557 break;
5558 case number_of_operands_mismatch:
5559 err_msg = _("number of operands mismatch");
5560 break;
5561 case invalid_instruction_suffix:
5562 err_msg = _("invalid instruction suffix");
5563 break;
5564 case bad_imm4:
5565 err_msg = _("constant doesn't fit in 4 bits");
5566 break;
5567 case old_gcc_only:
5568 err_msg = _("only supported with old gcc");
5569 break;
5570 case unsupported_with_intel_mnemonic:
5571 err_msg = _("unsupported with Intel mnemonic");
5572 break;
5573 case unsupported_syntax:
5574 err_msg = _("unsupported syntax");
5575 break;
5576 case unsupported:
5577 as_bad (_("unsupported instruction `%s'"),
5578 current_templates->start->name);
5579 return NULL;
5580 case invalid_vsib_address:
5581 err_msg = _("invalid VSIB address");
5582 break;
5583 case invalid_vector_register_set:
5584 err_msg = _("mask, index, and destination registers must be distinct");
5585 break;
5586 case unsupported_vector_index_register:
5587 err_msg = _("unsupported vector index register");
5588 break;
5589 case unsupported_broadcast:
5590 err_msg = _("unsupported broadcast");
5591 break;
5592 case broadcast_not_on_src_operand:
5593 err_msg = _("broadcast not on source memory operand");
5594 break;
5595 case broadcast_needed:
5596 err_msg = _("broadcast is needed for operand of such type");
5597 break;
5598 case unsupported_masking:
5599 err_msg = _("unsupported masking");
5600 break;
5601 case mask_not_on_destination:
5602 err_msg = _("mask not on destination operand");
5603 break;
5604 case no_default_mask:
5605 err_msg = _("default mask isn't allowed");
5606 break;
5607 case unsupported_rc_sae:
5608 err_msg = _("unsupported static rounding/sae");
5609 break;
5610 case rc_sae_operand_not_last_imm:
5611 if (intel_syntax)
5612 err_msg = _("RC/SAE operand must precede immediate operands");
5613 else
5614 err_msg = _("RC/SAE operand must follow immediate operands");
5615 break;
5616 case invalid_register_operand:
5617 err_msg = _("invalid register operand");
5618 break;
5619 }
5620 as_bad (_("%s for `%s'"), err_msg,
5621 current_templates->start->name);
5622 return NULL;
5623 }
5624
5625 if (!quiet_warnings)
5626 {
5627 if (!intel_syntax
5628 && (i.types[0].bitfield.jumpabsolute
5629 != operand_types[0].bitfield.jumpabsolute))
5630 {
5631 as_warn (_("indirect %s without `*'"), t->name);
5632 }
5633
5634 if (t->opcode_modifier.isprefix
5635 && t->opcode_modifier.ignoresize)
5636 {
5637 /* Warn them that a data or address size prefix doesn't
5638 affect assembly of the next line of code. */
5639 as_warn (_("stand-alone `%s' prefix"), t->name);
5640 }
5641 }
5642
5643 /* Copy the template we found. */
5644 i.tm = *t;
5645
5646 if (addr_prefix_disp != -1)
5647 i.tm.operand_types[addr_prefix_disp]
5648 = operand_types[addr_prefix_disp];
5649
5650 if (found_reverse_match)
5651 {
5652 /* If we found a reverse match we must alter the opcode
5653 direction bit. found_reverse_match holds bits to change
5654 (different for int & float insns). */
5655
5656 i.tm.base_opcode ^= found_reverse_match;
5657
5658 i.tm.operand_types[0] = operand_types[1];
5659 i.tm.operand_types[1] = operand_types[0];
5660 }
5661
5662 return t;
5663}
5664
5665static int
5666check_string (void)
5667{
5668 int mem_op = operand_type_check (i.types[0], anymem) ? 0 : 1;
5669 if (i.tm.operand_types[mem_op].bitfield.esseg)
5670 {
5671 if (i.seg[0] != NULL && i.seg[0] != &es)
5672 {
5673 as_bad (_("`%s' operand %d must use `%ses' segment"),
5674 i.tm.name,
5675 mem_op + 1,
5676 register_prefix);
5677 return 0;
5678 }
5679 /* There's only ever one segment override allowed per instruction.
5680 This instruction possibly has a legal segment override on the
5681 second operand, so copy the segment to where non-string
5682 instructions store it, allowing common code. */
5683 i.seg[0] = i.seg[1];
5684 }
5685 else if (i.tm.operand_types[mem_op + 1].bitfield.esseg)
5686 {
5687 if (i.seg[1] != NULL && i.seg[1] != &es)
5688 {
5689 as_bad (_("`%s' operand %d must use `%ses' segment"),
5690 i.tm.name,
5691 mem_op + 2,
5692 register_prefix);
5693 return 0;
5694 }
5695 }
5696 return 1;
5697}
5698
5699static int
5700process_suffix (void)
5701{
5702 /* If matched instruction specifies an explicit instruction mnemonic
5703 suffix, use it. */
5704 if (i.tm.opcode_modifier.size16)
5705 i.suffix = WORD_MNEM_SUFFIX;
5706 else if (i.tm.opcode_modifier.size32)
5707 i.suffix = LONG_MNEM_SUFFIX;
5708 else if (i.tm.opcode_modifier.size64)
5709 i.suffix = QWORD_MNEM_SUFFIX;
5710 else if (i.reg_operands)
5711 {
5712 /* If there's no instruction mnemonic suffix we try to invent one
5713 based on register operands. */
5714 if (!i.suffix)
5715 {
5716 /* We take i.suffix from the last register operand specified,
5717 Destination register type is more significant than source
5718 register type. crc32 in SSE4.2 prefers source register
5719 type. */
5720 if (i.tm.base_opcode == 0xf20f38f1)
5721 {
5722 if (i.types[0].bitfield.reg && i.types[0].bitfield.word)
5723 i.suffix = WORD_MNEM_SUFFIX;
5724 else if (i.types[0].bitfield.reg && i.types[0].bitfield.dword)
5725 i.suffix = LONG_MNEM_SUFFIX;
5726 else if (i.types[0].bitfield.reg && i.types[0].bitfield.qword)
5727 i.suffix = QWORD_MNEM_SUFFIX;
5728 }
5729 else if (i.tm.base_opcode == 0xf20f38f0)
5730 {
5731 if (i.types[0].bitfield.reg && i.types[0].bitfield.byte)
5732 i.suffix = BYTE_MNEM_SUFFIX;
5733 }
5734
5735 if (!i.suffix)
5736 {
5737 int op;
5738
5739 if (i.tm.base_opcode == 0xf20f38f1
5740 || i.tm.base_opcode == 0xf20f38f0)
5741 {
5742 /* We have to know the operand size for crc32. */
5743 as_bad (_("ambiguous memory operand size for `%s`"),
5744 i.tm.name);
5745 return 0;
5746 }
5747
5748 for (op = i.operands; --op >= 0;)
5749 if (!i.tm.operand_types[op].bitfield.inoutportreg
5750 && !i.tm.operand_types[op].bitfield.shiftcount)
5751 {
5752 if (i.types[op].bitfield.reg && i.types[op].bitfield.byte)
5753 {
5754 i.suffix = BYTE_MNEM_SUFFIX;
5755 break;
5756 }
5757 if (i.types[op].bitfield.reg && i.types[op].bitfield.word)
5758 {
5759 i.suffix = WORD_MNEM_SUFFIX;
5760 break;
5761 }
5762 if (i.types[op].bitfield.reg && i.types[op].bitfield.dword)
5763 {
5764 i.suffix = LONG_MNEM_SUFFIX;
5765 break;
5766 }
5767 if (i.types[op].bitfield.reg && i.types[op].bitfield.qword)
5768 {
5769 i.suffix = QWORD_MNEM_SUFFIX;
5770 break;
5771 }
5772 }
5773 }
5774 }
5775 else if (i.suffix == BYTE_MNEM_SUFFIX)
5776 {
5777 if (intel_syntax
5778 && i.tm.opcode_modifier.ignoresize
5779 && i.tm.opcode_modifier.no_bsuf)
5780 i.suffix = 0;
5781 else if (!check_byte_reg ())
5782 return 0;
5783 }
5784 else if (i.suffix == LONG_MNEM_SUFFIX)
5785 {
5786 if (intel_syntax
5787 && i.tm.opcode_modifier.ignoresize
5788 && i.tm.opcode_modifier.no_lsuf)
5789 i.suffix = 0;
5790 else if (!check_long_reg ())
5791 return 0;
5792 }
5793 else if (i.suffix == QWORD_MNEM_SUFFIX)
5794 {
5795 if (intel_syntax
5796 && i.tm.opcode_modifier.ignoresize
5797 && i.tm.opcode_modifier.no_qsuf)
5798 i.suffix = 0;
5799 else if (!check_qword_reg ())
5800 return 0;
5801 }
5802 else if (i.suffix == WORD_MNEM_SUFFIX)
5803 {
5804 if (intel_syntax
5805 && i.tm.opcode_modifier.ignoresize
5806 && i.tm.opcode_modifier.no_wsuf)
5807 i.suffix = 0;
5808 else if (!check_word_reg ())
5809 return 0;
5810 }
5811 else if (i.suffix == XMMWORD_MNEM_SUFFIX
5812 || i.suffix == YMMWORD_MNEM_SUFFIX
5813 || i.suffix == ZMMWORD_MNEM_SUFFIX)
5814 {
5815 /* Skip if the instruction has x/y/z suffix. match_template
5816 should check if it is a valid suffix. */
5817 }
5818 else if (intel_syntax && i.tm.opcode_modifier.ignoresize)
5819 /* Do nothing if the instruction is going to ignore the prefix. */
5820 ;
5821 else
5822 abort ();
5823 }
5824 else if (i.tm.opcode_modifier.defaultsize
5825 && !i.suffix
5826 /* exclude fldenv/frstor/fsave/fstenv */
5827 && i.tm.opcode_modifier.no_ssuf)
5828 {
5829 i.suffix = stackop_size;
5830 }
5831 else if (intel_syntax
5832 && !i.suffix
5833 && (i.tm.operand_types[0].bitfield.jumpabsolute
5834 || i.tm.opcode_modifier.jumpbyte
5835 || i.tm.opcode_modifier.jumpintersegment
5836 || (i.tm.base_opcode == 0x0f01 /* [ls][gi]dt */
5837 && i.tm.extension_opcode <= 3)))
5838 {
5839 switch (flag_code)
5840 {
5841 case CODE_64BIT:
5842 if (!i.tm.opcode_modifier.no_qsuf)
5843 {
5844 i.suffix = QWORD_MNEM_SUFFIX;
5845 break;
5846 }
5847 /* Fall through. */
5848 case CODE_32BIT:
5849 if (!i.tm.opcode_modifier.no_lsuf)
5850 i.suffix = LONG_MNEM_SUFFIX;
5851 break;
5852 case CODE_16BIT:
5853 if (!i.tm.opcode_modifier.no_wsuf)
5854 i.suffix = WORD_MNEM_SUFFIX;
5855 break;
5856 }
5857 }
5858
5859 if (!i.suffix)
5860 {
5861 if (!intel_syntax)
5862 {
5863 if (i.tm.opcode_modifier.w)
5864 {
5865 as_bad (_("no instruction mnemonic suffix given and "
5866 "no register operands; can't size instruction"));
5867 return 0;
5868 }
5869 }
5870 else
5871 {
5872 unsigned int suffixes;
5873
5874 suffixes = !i.tm.opcode_modifier.no_bsuf;
5875 if (!i.tm.opcode_modifier.no_wsuf)
5876 suffixes |= 1 << 1;
5877 if (!i.tm.opcode_modifier.no_lsuf)
5878 suffixes |= 1 << 2;
5879 if (!i.tm.opcode_modifier.no_ldsuf)
5880 suffixes |= 1 << 3;
5881 if (!i.tm.opcode_modifier.no_ssuf)
5882 suffixes |= 1 << 4;
5883 if (flag_code == CODE_64BIT && !i.tm.opcode_modifier.no_qsuf)
5884 suffixes |= 1 << 5;
5885
5886 /* There are more than suffix matches. */
5887 if (i.tm.opcode_modifier.w
5888 || ((suffixes & (suffixes - 1))
5889 && !i.tm.opcode_modifier.defaultsize
5890 && !i.tm.opcode_modifier.ignoresize))
5891 {
5892 as_bad (_("ambiguous operand size for `%s'"), i.tm.name);
5893 return 0;
5894 }
5895 }
5896 }
5897
5898 /* Change the opcode based on the operand size given by i.suffix;
5899 We don't need to change things for byte insns. */
5900
5901 if (i.suffix
5902 && i.suffix != BYTE_MNEM_SUFFIX
5903 && i.suffix != XMMWORD_MNEM_SUFFIX
5904 && i.suffix != YMMWORD_MNEM_SUFFIX
5905 && i.suffix != ZMMWORD_MNEM_SUFFIX)
5906 {
5907 /* It's not a byte, select word/dword operation. */
5908 if (i.tm.opcode_modifier.w)
5909 {
5910 if (i.tm.opcode_modifier.shortform)
5911 i.tm.base_opcode |= 8;
5912 else
5913 i.tm.base_opcode |= 1;
5914 }
5915
5916 /* Now select between word & dword operations via the operand
5917 size prefix, except for instructions that will ignore this
5918 prefix anyway. */
5919 if (i.tm.opcode_modifier.addrprefixop0)
5920 {
5921 /* The address size override prefix changes the size of the
5922 first operand. */
5923 if ((flag_code == CODE_32BIT
5924 && i.op->regs[0].reg_type.bitfield.word)
5925 || (flag_code != CODE_32BIT
5926 && i.op->regs[0].reg_type.bitfield.dword))
5927 if (!add_prefix (ADDR_PREFIX_OPCODE))
5928 return 0;
5929 }
5930 else if (i.suffix != QWORD_MNEM_SUFFIX
5931 && i.suffix != LONG_DOUBLE_MNEM_SUFFIX
5932 && !i.tm.opcode_modifier.ignoresize
5933 && !i.tm.opcode_modifier.floatmf
5934 && ((i.suffix == LONG_MNEM_SUFFIX) == (flag_code == CODE_16BIT)
5935 || (flag_code == CODE_64BIT
5936 && i.tm.opcode_modifier.jumpbyte)))
5937 {
5938 unsigned int prefix = DATA_PREFIX_OPCODE;
5939
5940 if (i.tm.opcode_modifier.jumpbyte) /* jcxz, loop */
5941 prefix = ADDR_PREFIX_OPCODE;
5942
5943 if (!add_prefix (prefix))
5944 return 0;
5945 }
5946
5947 /* Set mode64 for an operand. */
5948 if (i.suffix == QWORD_MNEM_SUFFIX
5949 && flag_code == CODE_64BIT
5950 && !i.tm.opcode_modifier.norex64)
5951 {
5952 /* Special case for xchg %rax,%rax. It is NOP and doesn't
5953 need rex64. cmpxchg8b is also a special case. */
5954 if (! (i.operands == 2
5955 && i.tm.base_opcode == 0x90
5956 && i.tm.extension_opcode == None
5957 && operand_type_equal (&i.types [0], &acc64)
5958 && operand_type_equal (&i.types [1], &acc64))
5959 && ! (i.operands == 1
5960 && i.tm.base_opcode == 0xfc7
5961 && i.tm.extension_opcode == 1
5962 && !operand_type_check (i.types [0], reg)
5963 && operand_type_check (i.types [0], anymem)))
5964 i.rex |= REX_W;
5965 }
5966
5967 /* Size floating point instruction. */
5968 if (i.suffix == LONG_MNEM_SUFFIX)
5969 if (i.tm.opcode_modifier.floatmf)
5970 i.tm.base_opcode ^= 4;
5971 }
5972
5973 return 1;
5974}
5975
5976static int
5977check_byte_reg (void)
5978{
5979 int op;
5980
5981 for (op = i.operands; --op >= 0;)
5982 {
5983 /* Skip non-register operands. */
5984 if (!i.types[op].bitfield.reg)
5985 continue;
5986
5987 /* If this is an eight bit register, it's OK. If it's the 16 or
5988 32 bit version of an eight bit register, we will just use the
5989 low portion, and that's OK too. */
5990 if (i.types[op].bitfield.byte)
5991 continue;
5992
5993 /* I/O port address operands are OK too. */
5994 if (i.tm.operand_types[op].bitfield.inoutportreg)
5995 continue;
5996
5997 /* crc32 doesn't generate this warning. */
5998 if (i.tm.base_opcode == 0xf20f38f0)
5999 continue;
6000
6001 if ((i.types[op].bitfield.word
6002 || i.types[op].bitfield.dword
6003 || i.types[op].bitfield.qword)
6004 && i.op[op].regs->reg_num < 4
6005 /* Prohibit these changes in 64bit mode, since the lowering
6006 would be more complicated. */
6007 && flag_code != CODE_64BIT)
6008 {
6009#if REGISTER_WARNINGS
6010 if (!quiet_warnings)
6011 as_warn (_("using `%s%s' instead of `%s%s' due to `%c' suffix"),
6012 register_prefix,
6013 (i.op[op].regs + (i.types[op].bitfield.word
6014 ? REGNAM_AL - REGNAM_AX
6015 : REGNAM_AL - REGNAM_EAX))->reg_name,
6016 register_prefix,
6017 i.op[op].regs->reg_name,
6018 i.suffix);
6019#endif
6020 continue;
6021 }
6022 /* Any other register is bad. */
6023 if (i.types[op].bitfield.reg
6024 || i.types[op].bitfield.regmmx
6025 || i.types[op].bitfield.regsimd
6026 || i.types[op].bitfield.sreg2
6027 || i.types[op].bitfield.sreg3
6028 || i.types[op].bitfield.control
6029 || i.types[op].bitfield.debug
6030 || i.types[op].bitfield.test)
6031 {
6032 as_bad (_("`%s%s' not allowed with `%s%c'"),
6033 register_prefix,
6034 i.op[op].regs->reg_name,
6035 i.tm.name,
6036 i.suffix);
6037 return 0;
6038 }
6039 }
6040 return 1;
6041}
6042
6043static int
6044check_long_reg (void)
6045{
6046 int op;
6047
6048 for (op = i.operands; --op >= 0;)
6049 /* Skip non-register operands. */
6050 if (!i.types[op].bitfield.reg)
6051 continue;
6052 /* Reject eight bit registers, except where the template requires
6053 them. (eg. movzb) */
6054 else if (i.types[op].bitfield.byte
6055 && (i.tm.operand_types[op].bitfield.reg
6056 || i.tm.operand_types[op].bitfield.acc)
6057 && (i.tm.operand_types[op].bitfield.word
6058 || i.tm.operand_types[op].bitfield.dword))
6059 {
6060 as_bad (_("`%s%s' not allowed with `%s%c'"),
6061 register_prefix,
6062 i.op[op].regs->reg_name,
6063 i.tm.name,
6064 i.suffix);
6065 return 0;
6066 }
6067 /* Warn if the e prefix on a general reg is missing. */
6068 else if ((!quiet_warnings || flag_code == CODE_64BIT)
6069 && i.types[op].bitfield.word
6070 && (i.tm.operand_types[op].bitfield.reg
6071 || i.tm.operand_types[op].bitfield.acc)
6072 && i.tm.operand_types[op].bitfield.dword)
6073 {
6074 /* Prohibit these changes in the 64bit mode, since the
6075 lowering is more complicated. */
6076 if (flag_code == CODE_64BIT)
6077 {
6078 as_bad (_("incorrect register `%s%s' used with `%c' suffix"),
6079 register_prefix, i.op[op].regs->reg_name,
6080 i.suffix);
6081 return 0;
6082 }
6083#if REGISTER_WARNINGS
6084 as_warn (_("using `%s%s' instead of `%s%s' due to `%c' suffix"),
6085 register_prefix,
6086 (i.op[op].regs + REGNAM_EAX - REGNAM_AX)->reg_name,
6087 register_prefix, i.op[op].regs->reg_name, i.suffix);
6088#endif
6089 }
6090 /* Warn if the r prefix on a general reg is present. */
6091 else if (i.types[op].bitfield.qword
6092 && (i.tm.operand_types[op].bitfield.reg
6093 || i.tm.operand_types[op].bitfield.acc)
6094 && i.tm.operand_types[op].bitfield.dword)
6095 {
6096 if (intel_syntax
6097 && i.tm.opcode_modifier.toqword
6098 && !i.types[0].bitfield.regsimd)
6099 {
6100 /* Convert to QWORD. We want REX byte. */
6101 i.suffix = QWORD_MNEM_SUFFIX;
6102 }
6103 else
6104 {
6105 as_bad (_("incorrect register `%s%s' used with `%c' suffix"),
6106 register_prefix, i.op[op].regs->reg_name,
6107 i.suffix);
6108 return 0;
6109 }
6110 }
6111 return 1;
6112}
6113
6114static int
6115check_qword_reg (void)
6116{
6117 int op;
6118
6119 for (op = i.operands; --op >= 0; )
6120 /* Skip non-register operands. */
6121 if (!i.types[op].bitfield.reg)
6122 continue;
6123 /* Reject eight bit registers, except where the template requires
6124 them. (eg. movzb) */
6125 else if (i.types[op].bitfield.byte
6126 && (i.tm.operand_types[op].bitfield.reg
6127 || i.tm.operand_types[op].bitfield.acc)
6128 && (i.tm.operand_types[op].bitfield.word
6129 || i.tm.operand_types[op].bitfield.dword))
6130 {
6131 as_bad (_("`%s%s' not allowed with `%s%c'"),
6132 register_prefix,
6133 i.op[op].regs->reg_name,
6134 i.tm.name,
6135 i.suffix);
6136 return 0;
6137 }
6138 /* Warn if the r prefix on a general reg is missing. */
6139 else if ((i.types[op].bitfield.word
6140 || i.types[op].bitfield.dword)
6141 && (i.tm.operand_types[op].bitfield.reg
6142 || i.tm.operand_types[op].bitfield.acc)
6143 && i.tm.operand_types[op].bitfield.qword)
6144 {
6145 /* Prohibit these changes in the 64bit mode, since the
6146 lowering is more complicated. */
6147 if (intel_syntax
6148 && i.tm.opcode_modifier.todword
6149 && !i.types[0].bitfield.regsimd)
6150 {
6151 /* Convert to DWORD. We don't want REX byte. */
6152 i.suffix = LONG_MNEM_SUFFIX;
6153 }
6154 else
6155 {
6156 as_bad (_("incorrect register `%s%s' used with `%c' suffix"),
6157 register_prefix, i.op[op].regs->reg_name,
6158 i.suffix);
6159 return 0;
6160 }
6161 }
6162 return 1;
6163}
6164
6165static int
6166check_word_reg (void)
6167{
6168 int op;
6169 for (op = i.operands; --op >= 0;)
6170 /* Skip non-register operands. */
6171 if (!i.types[op].bitfield.reg)
6172 continue;
6173 /* Reject eight bit registers, except where the template requires
6174 them. (eg. movzb) */
6175 else if (i.types[op].bitfield.byte
6176 && (i.tm.operand_types[op].bitfield.reg
6177 || i.tm.operand_types[op].bitfield.acc)
6178 && (i.tm.operand_types[op].bitfield.word
6179 || i.tm.operand_types[op].bitfield.dword))
6180 {
6181 as_bad (_("`%s%s' not allowed with `%s%c'"),
6182 register_prefix,
6183 i.op[op].regs->reg_name,
6184 i.tm.name,
6185 i.suffix);
6186 return 0;
6187 }
6188 /* Warn if the e or r prefix on a general reg is present. */
6189 else if ((!quiet_warnings || flag_code == CODE_64BIT)
6190 && (i.types[op].bitfield.dword
6191 || i.types[op].bitfield.qword)
6192 && (i.tm.operand_types[op].bitfield.reg
6193 || i.tm.operand_types[op].bitfield.acc)
6194 && i.tm.operand_types[op].bitfield.word)
6195 {
6196 /* Prohibit these changes in the 64bit mode, since the
6197 lowering is more complicated. */
6198 if (flag_code == CODE_64BIT)
6199 {
6200 as_bad (_("incorrect register `%s%s' used with `%c' suffix"),
6201 register_prefix, i.op[op].regs->reg_name,
6202 i.suffix);
6203 return 0;
6204 }
6205#if REGISTER_WARNINGS
6206 as_warn (_("using `%s%s' instead of `%s%s' due to `%c' suffix"),
6207 register_prefix,
6208 (i.op[op].regs + REGNAM_AX - REGNAM_EAX)->reg_name,
6209 register_prefix, i.op[op].regs->reg_name, i.suffix);
6210#endif
6211 }
6212 return 1;
6213}
6214
6215static int
6216update_imm (unsigned int j)
6217{
6218 i386_operand_type overlap = i.types[j];
6219 if ((overlap.bitfield.imm8
6220 || overlap.bitfield.imm8s
6221 || overlap.bitfield.imm16
6222 || overlap.bitfield.imm32
6223 || overlap.bitfield.imm32s
6224 || overlap.bitfield.imm64)
6225 && !operand_type_equal (&overlap, &imm8)
6226 && !operand_type_equal (&overlap, &imm8s)
6227 && !operand_type_equal (&overlap, &imm16)
6228 && !operand_type_equal (&overlap, &imm32)
6229 && !operand_type_equal (&overlap, &imm32s)
6230 && !operand_type_equal (&overlap, &imm64))
6231 {
6232 if (i.suffix)
6233 {
6234 i386_operand_type temp;
6235
6236 operand_type_set (&temp, 0);
6237 if (i.suffix == BYTE_MNEM_SUFFIX)
6238 {
6239 temp.bitfield.imm8 = overlap.bitfield.imm8;
6240 temp.bitfield.imm8s = overlap.bitfield.imm8s;
6241 }
6242 else if (i.suffix == WORD_MNEM_SUFFIX)
6243 temp.bitfield.imm16 = overlap.bitfield.imm16;
6244 else if (i.suffix == QWORD_MNEM_SUFFIX)
6245 {
6246 temp.bitfield.imm64 = overlap.bitfield.imm64;
6247 temp.bitfield.imm32s = overlap.bitfield.imm32s;
6248 }
6249 else
6250 temp.bitfield.imm32 = overlap.bitfield.imm32;
6251 overlap = temp;
6252 }
6253 else if (operand_type_equal (&overlap, &imm16_32_32s)
6254 || operand_type_equal (&overlap, &imm16_32)
6255 || operand_type_equal (&overlap, &imm16_32s))
6256 {
6257 if ((flag_code == CODE_16BIT) ^ (i.prefix[DATA_PREFIX] != 0))
6258 overlap = imm16;
6259 else
6260 overlap = imm32s;
6261 }
6262 if (!operand_type_equal (&overlap, &imm8)
6263 && !operand_type_equal (&overlap, &imm8s)
6264 && !operand_type_equal (&overlap, &imm16)
6265 && !operand_type_equal (&overlap, &imm32)
6266 && !operand_type_equal (&overlap, &imm32s)
6267 && !operand_type_equal (&overlap, &imm64))
6268 {
6269 as_bad (_("no instruction mnemonic suffix given; "
6270 "can't determine immediate size"));
6271 return 0;
6272 }
6273 }
6274 i.types[j] = overlap;
6275
6276 return 1;
6277}
6278
6279static int
6280finalize_imm (void)
6281{
6282 unsigned int j, n;
6283
6284 /* Update the first 2 immediate operands. */
6285 n = i.operands > 2 ? 2 : i.operands;
6286 if (n)
6287 {
6288 for (j = 0; j < n; j++)
6289 if (update_imm (j) == 0)
6290 return 0;
6291
6292 /* The 3rd operand can't be immediate operand. */
6293 gas_assert (operand_type_check (i.types[2], imm) == 0);
6294 }
6295
6296 return 1;
6297}
6298
6299static int
6300process_operands (void)
6301{
6302 /* Default segment register this instruction will use for memory
6303 accesses. 0 means unknown. This is only for optimizing out
6304 unnecessary segment overrides. */
6305 const seg_entry *default_seg = 0;
6306
6307 if (i.tm.opcode_modifier.sse2avx && i.tm.opcode_modifier.vexvvvv)
6308 {
6309 unsigned int dupl = i.operands;
6310 unsigned int dest = dupl - 1;
6311 unsigned int j;
6312
6313 /* The destination must be an xmm register. */
6314 gas_assert (i.reg_operands
6315 && MAX_OPERANDS > dupl
6316 && operand_type_equal (&i.types[dest], &regxmm));
6317
6318 if (i.tm.operand_types[0].bitfield.acc
6319 && i.tm.operand_types[0].bitfield.xmmword)
6320 {
6321 if (i.tm.opcode_modifier.vexsources == VEX3SOURCES)
6322 {
6323 /* Keep xmm0 for instructions with VEX prefix and 3
6324 sources. */
6325 i.tm.operand_types[0].bitfield.acc = 0;
6326 i.tm.operand_types[0].bitfield.regsimd = 1;
6327 goto duplicate;
6328 }
6329 else
6330 {
6331 /* We remove the first xmm0 and keep the number of
6332 operands unchanged, which in fact duplicates the
6333 destination. */
6334 for (j = 1; j < i.operands; j++)
6335 {
6336 i.op[j - 1] = i.op[j];
6337 i.types[j - 1] = i.types[j];
6338 i.tm.operand_types[j - 1] = i.tm.operand_types[j];
6339 }
6340 }
6341 }
6342 else if (i.tm.opcode_modifier.implicit1stxmm0)
6343 {
6344 gas_assert ((MAX_OPERANDS - 1) > dupl
6345 && (i.tm.opcode_modifier.vexsources
6346 == VEX3SOURCES));
6347
6348 /* Add the implicit xmm0 for instructions with VEX prefix
6349 and 3 sources. */
6350 for (j = i.operands; j > 0; j--)
6351 {
6352 i.op[j] = i.op[j - 1];
6353 i.types[j] = i.types[j - 1];
6354 i.tm.operand_types[j] = i.tm.operand_types[j - 1];
6355 }
6356 i.op[0].regs
6357 = (const reg_entry *) hash_find (reg_hash, "xmm0");
6358 i.types[0] = regxmm;
6359 i.tm.operand_types[0] = regxmm;
6360
6361 i.operands += 2;
6362 i.reg_operands += 2;
6363 i.tm.operands += 2;
6364
6365 dupl++;
6366 dest++;
6367 i.op[dupl] = i.op[dest];
6368 i.types[dupl] = i.types[dest];
6369 i.tm.operand_types[dupl] = i.tm.operand_types[dest];
6370 }
6371 else
6372 {
6373duplicate:
6374 i.operands++;
6375 i.reg_operands++;
6376 i.tm.operands++;
6377
6378 i.op[dupl] = i.op[dest];
6379 i.types[dupl] = i.types[dest];
6380 i.tm.operand_types[dupl] = i.tm.operand_types[dest];
6381 }
6382
6383 if (i.tm.opcode_modifier.immext)
6384 process_immext ();
6385 }
6386 else if (i.tm.operand_types[0].bitfield.acc
6387 && i.tm.operand_types[0].bitfield.xmmword)
6388 {
6389 unsigned int j;
6390
6391 for (j = 1; j < i.operands; j++)
6392 {
6393 i.op[j - 1] = i.op[j];
6394 i.types[j - 1] = i.types[j];
6395
6396 /* We need to adjust fields in i.tm since they are used by
6397 build_modrm_byte. */
6398 i.tm.operand_types [j - 1] = i.tm.operand_types [j];
6399 }
6400
6401 i.operands--;
6402 i.reg_operands--;
6403 i.tm.operands--;
6404 }
6405 else if (i.tm.opcode_modifier.implicitquadgroup)
6406 {
6407 /* The second operand must be {x,y,z}mmN, where N is a multiple of 4. */
6408 gas_assert (i.operands >= 2 && i.types[1].bitfield.regsimd);
6409 unsigned int regnum = register_number (i.op[1].regs);
6410 unsigned int first_reg_in_group = regnum & ~3;
6411 unsigned int last_reg_in_group = first_reg_in_group + 3;
6412 if (regnum != first_reg_in_group) {
6413 as_warn (_("the second source register `%s%s' implicitly denotes"
6414 " `%s%.3s%d' to `%s%.3s%d' source group in `%s'"),
6415 register_prefix, i.op[1].regs->reg_name,
6416 register_prefix, i.op[1].regs->reg_name, first_reg_in_group,
6417 register_prefix, i.op[1].regs->reg_name, last_reg_in_group,
6418 i.tm.name);
6419 }
6420 }
6421 else if (i.tm.opcode_modifier.regkludge)
6422 {
6423 /* The imul $imm, %reg instruction is converted into
6424 imul $imm, %reg, %reg, and the clr %reg instruction
6425 is converted into xor %reg, %reg. */
6426
6427 unsigned int first_reg_op;
6428
6429 if (operand_type_check (i.types[0], reg))
6430 first_reg_op = 0;
6431 else
6432 first_reg_op = 1;
6433 /* Pretend we saw the extra register operand. */
6434 gas_assert (i.reg_operands == 1
6435 && i.op[first_reg_op + 1].regs == 0);
6436 i.op[first_reg_op + 1].regs = i.op[first_reg_op].regs;
6437 i.types[first_reg_op + 1] = i.types[first_reg_op];
6438 i.operands++;
6439 i.reg_operands++;
6440 }
6441
6442 if (i.tm.opcode_modifier.shortform)
6443 {
6444 if (i.types[0].bitfield.sreg2
6445 || i.types[0].bitfield.sreg3)
6446 {
6447 if (i.tm.base_opcode == POP_SEG_SHORT
6448 && i.op[0].regs->reg_num == 1)
6449 {
6450 as_bad (_("you can't `pop %scs'"), register_prefix);
6451 return 0;
6452 }
6453 i.tm.base_opcode |= (i.op[0].regs->reg_num << 3);
6454 if ((i.op[0].regs->reg_flags & RegRex) != 0)
6455 i.rex |= REX_B;
6456 }
6457 else
6458 {
6459 /* The register or float register operand is in operand
6460 0 or 1. */
6461 unsigned int op;
6462
6463 if ((i.types[0].bitfield.reg && i.types[0].bitfield.tbyte)
6464 || operand_type_check (i.types[0], reg))
6465 op = 0;
6466 else
6467 op = 1;
6468 /* Register goes in low 3 bits of opcode. */
6469 i.tm.base_opcode |= i.op[op].regs->reg_num;
6470 if ((i.op[op].regs->reg_flags & RegRex) != 0)
6471 i.rex |= REX_B;
6472 if (!quiet_warnings && i.tm.opcode_modifier.ugh)
6473 {
6474 /* Warn about some common errors, but press on regardless.
6475 The first case can be generated by gcc (<= 2.8.1). */
6476 if (i.operands == 2)
6477 {
6478 /* Reversed arguments on faddp, fsubp, etc. */
6479 as_warn (_("translating to `%s %s%s,%s%s'"), i.tm.name,
6480 register_prefix, i.op[!intel_syntax].regs->reg_name,
6481 register_prefix, i.op[intel_syntax].regs->reg_name);
6482 }
6483 else
6484 {
6485 /* Extraneous `l' suffix on fp insn. */
6486 as_warn (_("translating to `%s %s%s'"), i.tm.name,
6487 register_prefix, i.op[0].regs->reg_name);
6488 }
6489 }
6490 }
6491 }
6492 else if (i.tm.opcode_modifier.modrm)
6493 {
6494 /* The opcode is completed (modulo i.tm.extension_opcode which
6495 must be put into the modrm byte). Now, we make the modrm and
6496 index base bytes based on all the info we've collected. */
6497
6498 default_seg = build_modrm_byte ();
6499 }
6500 else if ((i.tm.base_opcode & ~0x3) == MOV_AX_DISP32)
6501 {
6502 default_seg = &ds;
6503 }
6504 else if (i.tm.opcode_modifier.isstring)
6505 {
6506 /* For the string instructions that allow a segment override
6507 on one of their operands, the default segment is ds. */
6508 default_seg = &ds;
6509 }
6510
6511 if (i.tm.base_opcode == 0x8d /* lea */
6512 && i.seg[0]
6513 && !quiet_warnings)
6514 as_warn (_("segment override on `%s' is ineffectual"), i.tm.name);
6515
6516 /* If a segment was explicitly specified, and the specified segment
6517 is not the default, use an opcode prefix to select it. If we
6518 never figured out what the default segment is, then default_seg
6519 will be zero at this point, and the specified segment prefix will
6520 always be used. */
6521 if ((i.seg[0]) && (i.seg[0] != default_seg))
6522 {
6523 if (!add_prefix (i.seg[0]->seg_prefix))
6524 return 0;
6525 }
6526 return 1;
6527}
6528
6529static const seg_entry *
6530build_modrm_byte (void)
6531{
6532 const seg_entry *default_seg = 0;
6533 unsigned int source, dest;
6534 int vex_3_sources;
6535
6536 /* The first operand of instructions with VEX prefix and 3 sources
6537 must be VEX_Imm4. */
6538 vex_3_sources = i.tm.opcode_modifier.vexsources == VEX3SOURCES;
6539 if (vex_3_sources)
6540 {
6541 unsigned int nds, reg_slot;
6542 expressionS *exp;
6543
6544 if (i.tm.opcode_modifier.veximmext
6545 && i.tm.opcode_modifier.immext)
6546 {
6547 dest = i.operands - 2;
6548 gas_assert (dest == 3);
6549 }
6550 else
6551 dest = i.operands - 1;
6552 nds = dest - 1;
6553
6554 /* There are 2 kinds of instructions:
6555 1. 5 operands: 4 register operands or 3 register operands
6556 plus 1 memory operand plus one Vec_Imm4 operand, VexXDS, and
6557 VexW0 or VexW1. The destination must be either XMM, YMM or
6558 ZMM register.
6559 2. 4 operands: 4 register operands or 3 register operands
6560 plus 1 memory operand, VexXDS, and VexImmExt */
6561 gas_assert ((i.reg_operands == 4
6562 || (i.reg_operands == 3 && i.mem_operands == 1))
6563 && i.tm.opcode_modifier.vexvvvv == VEXXDS
6564 && (i.tm.opcode_modifier.veximmext
6565 || (i.imm_operands == 1
6566 && i.types[0].bitfield.vec_imm4
6567 && (i.tm.opcode_modifier.vexw == VEXW0
6568 || i.tm.opcode_modifier.vexw == VEXW1)
6569 && i.tm.operand_types[dest].bitfield.regsimd)));
6570
6571 if (i.imm_operands == 0)
6572 {
6573 /* When there is no immediate operand, generate an 8bit
6574 immediate operand to encode the first operand. */
6575 exp = &im_expressions[i.imm_operands++];
6576 i.op[i.operands].imms = exp;
6577 i.types[i.operands] = imm8;
6578 i.operands++;
6579 /* If VexW1 is set, the first operand is the source and
6580 the second operand is encoded in the immediate operand. */
6581 if (i.tm.opcode_modifier.vexw == VEXW1)
6582 {
6583 source = 0;
6584 reg_slot = 1;
6585 }
6586 else
6587 {
6588 source = 1;
6589 reg_slot = 0;
6590 }
6591
6592 /* FMA swaps REG and NDS. */
6593 if (i.tm.cpu_flags.bitfield.cpufma)
6594 {
6595 unsigned int tmp;
6596 tmp = reg_slot;
6597 reg_slot = nds;
6598 nds = tmp;
6599 }
6600
6601 gas_assert (i.tm.operand_types[reg_slot].bitfield.regsimd);
6602 exp->X_op = O_constant;
6603 exp->X_add_number = register_number (i.op[reg_slot].regs) << 4;
6604 gas_assert ((i.op[reg_slot].regs->reg_flags & RegVRex) == 0);
6605 }
6606 else
6607 {
6608 unsigned int imm_slot;
6609
6610 if (i.tm.opcode_modifier.vexw == VEXW0)
6611 {
6612 /* If VexW0 is set, the third operand is the source and
6613 the second operand is encoded in the immediate
6614 operand. */
6615 source = 2;
6616 reg_slot = 1;
6617 }
6618 else
6619 {
6620 /* VexW1 is set, the second operand is the source and
6621 the third operand is encoded in the immediate
6622 operand. */
6623 source = 1;
6624 reg_slot = 2;
6625 }
6626
6627 if (i.tm.opcode_modifier.immext)
6628 {
6629 /* When ImmExt is set, the immediate byte is the last
6630 operand. */
6631 imm_slot = i.operands - 1;
6632 source--;
6633 reg_slot--;
6634 }
6635 else
6636 {
6637 imm_slot = 0;
6638
6639 /* Turn on Imm8 so that output_imm will generate it. */
6640 i.types[imm_slot].bitfield.imm8 = 1;
6641 }
6642
6643 gas_assert (i.tm.operand_types[reg_slot].bitfield.regsimd);
6644 i.op[imm_slot].imms->X_add_number
6645 |= register_number (i.op[reg_slot].regs) << 4;
6646 gas_assert ((i.op[reg_slot].regs->reg_flags & RegVRex) == 0);
6647 }
6648
6649 gas_assert (i.tm.operand_types[nds].bitfield.regsimd);
6650 i.vex.register_specifier = i.op[nds].regs;
6651 }
6652 else
6653 source = dest = 0;
6654
6655 /* i.reg_operands MUST be the number of real register operands;
6656 implicit registers do not count. If there are 3 register
6657 operands, it must be a instruction with VexNDS. For a
6658 instruction with VexNDD, the destination register is encoded
6659 in VEX prefix. If there are 4 register operands, it must be
6660 a instruction with VEX prefix and 3 sources. */
6661 if (i.mem_operands == 0
6662 && ((i.reg_operands == 2
6663 && i.tm.opcode_modifier.vexvvvv <= VEXXDS)
6664 || (i.reg_operands == 3
6665 && i.tm.opcode_modifier.vexvvvv == VEXXDS)
6666 || (i.reg_operands == 4 && vex_3_sources)))
6667 {
6668 switch (i.operands)
6669 {
6670 case 2:
6671 source = 0;
6672 break;
6673 case 3:
6674 /* When there are 3 operands, one of them may be immediate,
6675 which may be the first or the last operand. Otherwise,
6676 the first operand must be shift count register (cl) or it
6677 is an instruction with VexNDS. */
6678 gas_assert (i.imm_operands == 1
6679 || (i.imm_operands == 0
6680 && (i.tm.opcode_modifier.vexvvvv == VEXXDS
6681 || i.types[0].bitfield.shiftcount)));
6682 if (operand_type_check (i.types[0], imm)
6683 || i.types[0].bitfield.shiftcount)
6684 source = 1;
6685 else
6686 source = 0;
6687 break;
6688 case 4:
6689 /* When there are 4 operands, the first two must be 8bit
6690 immediate operands. The source operand will be the 3rd
6691 one.
6692
6693 For instructions with VexNDS, if the first operand
6694 an imm8, the source operand is the 2nd one. If the last
6695 operand is imm8, the source operand is the first one. */
6696 gas_assert ((i.imm_operands == 2
6697 && i.types[0].bitfield.imm8
6698 && i.types[1].bitfield.imm8)
6699 || (i.tm.opcode_modifier.vexvvvv == VEXXDS
6700 && i.imm_operands == 1
6701 && (i.types[0].bitfield.imm8
6702 || i.types[i.operands - 1].bitfield.imm8
6703 || i.rounding)));
6704 if (i.imm_operands == 2)
6705 source = 2;
6706 else
6707 {
6708 if (i.types[0].bitfield.imm8)
6709 source = 1;
6710 else
6711 source = 0;
6712 }
6713 break;
6714 case 5:
6715 if (i.tm.opcode_modifier.evex)
6716 {
6717 /* For EVEX instructions, when there are 5 operands, the
6718 first one must be immediate operand. If the second one
6719 is immediate operand, the source operand is the 3th
6720 one. If the last one is immediate operand, the source
6721 operand is the 2nd one. */
6722 gas_assert (i.imm_operands == 2
6723 && i.tm.opcode_modifier.sae
6724 && operand_type_check (i.types[0], imm));
6725 if (operand_type_check (i.types[1], imm))
6726 source = 2;
6727 else if (operand_type_check (i.types[4], imm))
6728 source = 1;
6729 else
6730 abort ();
6731 }
6732 break;
6733 default:
6734 abort ();
6735 }
6736
6737 if (!vex_3_sources)
6738 {
6739 dest = source + 1;
6740
6741 /* RC/SAE operand could be between DEST and SRC. That happens
6742 when one operand is GPR and the other one is XMM/YMM/ZMM
6743 register. */
6744 if (i.rounding && i.rounding->operand == (int) dest)
6745 dest++;
6746
6747 if (i.tm.opcode_modifier.vexvvvv == VEXXDS)
6748 {
6749 /* For instructions with VexNDS, the register-only source
6750 operand must be a 32/64bit integer, XMM, YMM, ZMM, or mask
6751 register. It is encoded in VEX prefix. We need to
6752 clear RegMem bit before calling operand_type_equal. */
6753
6754 i386_operand_type op;
6755 unsigned int vvvv;
6756
6757 /* Check register-only source operand when two source
6758 operands are swapped. */
6759 if (!i.tm.operand_types[source].bitfield.baseindex
6760 && i.tm.operand_types[dest].bitfield.baseindex)
6761 {
6762 vvvv = source;
6763 source = dest;
6764 }
6765 else
6766 vvvv = dest;
6767
6768 op = i.tm.operand_types[vvvv];
6769 op.bitfield.regmem = 0;
6770 if ((dest + 1) >= i.operands
6771 || ((!op.bitfield.reg
6772 || (!op.bitfield.dword && !op.bitfield.qword))
6773 && !op.bitfield.regsimd
6774 && !operand_type_equal (&op, &regmask)))
6775 abort ();
6776 i.vex.register_specifier = i.op[vvvv].regs;
6777 dest++;
6778 }
6779 }
6780
6781 i.rm.mode = 3;
6782 /* One of the register operands will be encoded in the i.tm.reg
6783 field, the other in the combined i.tm.mode and i.tm.regmem
6784 fields. If no form of this instruction supports a memory
6785 destination operand, then we assume the source operand may
6786 sometimes be a memory operand and so we need to store the
6787 destination in the i.rm.reg field. */
6788 if (!i.tm.operand_types[dest].bitfield.regmem
6789 && operand_type_check (i.tm.operand_types[dest], anymem) == 0)
6790 {
6791 i.rm.reg = i.op[dest].regs->reg_num;
6792 i.rm.regmem = i.op[source].regs->reg_num;
6793 if ((i.op[dest].regs->reg_flags & RegRex) != 0)
6794 i.rex |= REX_R;
6795 if ((i.op[dest].regs->reg_flags & RegVRex) != 0)
6796 i.vrex |= REX_R;
6797 if ((i.op[source].regs->reg_flags & RegRex) != 0)
6798 i.rex |= REX_B;
6799 if ((i.op[source].regs->reg_flags & RegVRex) != 0)
6800 i.vrex |= REX_B;
6801 }
6802 else
6803 {
6804 i.rm.reg = i.op[source].regs->reg_num;
6805 i.rm.regmem = i.op[dest].regs->reg_num;
6806 if ((i.op[dest].regs->reg_flags & RegRex) != 0)
6807 i.rex |= REX_B;
6808 if ((i.op[dest].regs->reg_flags & RegVRex) != 0)
6809 i.vrex |= REX_B;
6810 if ((i.op[source].regs->reg_flags & RegRex) != 0)
6811 i.rex |= REX_R;
6812 if ((i.op[source].regs->reg_flags & RegVRex) != 0)
6813 i.vrex |= REX_R;
6814 }
6815 if (flag_code != CODE_64BIT && (i.rex & (REX_R | REX_B)))
6816 {
6817 if (!i.types[0].bitfield.control
6818 && !i.types[1].bitfield.control)
6819 abort ();
6820 i.rex &= ~(REX_R | REX_B);
6821 add_prefix (LOCK_PREFIX_OPCODE);
6822 }
6823 }
6824 else
6825 { /* If it's not 2 reg operands... */
6826 unsigned int mem;
6827
6828 if (i.mem_operands)
6829 {
6830 unsigned int fake_zero_displacement = 0;
6831 unsigned int op;
6832
6833 for (op = 0; op < i.operands; op++)
6834 if (operand_type_check (i.types[op], anymem))
6835 break;
6836 gas_assert (op < i.operands);
6837
6838 if (i.tm.opcode_modifier.vecsib)
6839 {
6840 if (i.index_reg->reg_num == RegEiz
6841 || i.index_reg->reg_num == RegRiz)
6842 abort ();
6843
6844 i.rm.regmem = ESCAPE_TO_TWO_BYTE_ADDRESSING;
6845 if (!i.base_reg)
6846 {
6847 i.sib.base = NO_BASE_REGISTER;
6848 i.sib.scale = i.log2_scale_factor;
6849 i.types[op].bitfield.disp8 = 0;
6850 i.types[op].bitfield.disp16 = 0;
6851 i.types[op].bitfield.disp64 = 0;
6852 if (flag_code != CODE_64BIT || i.prefix[ADDR_PREFIX])
6853 {
6854 /* Must be 32 bit */
6855 i.types[op].bitfield.disp32 = 1;
6856 i.types[op].bitfield.disp32s = 0;
6857 }
6858 else
6859 {
6860 i.types[op].bitfield.disp32 = 0;
6861 i.types[op].bitfield.disp32s = 1;
6862 }
6863 }
6864 i.sib.index = i.index_reg->reg_num;
6865 if ((i.index_reg->reg_flags & RegRex) != 0)
6866 i.rex |= REX_X;
6867 if ((i.index_reg->reg_flags & RegVRex) != 0)
6868 i.vrex |= REX_X;
6869 }
6870
6871 default_seg = &ds;
6872
6873 if (i.base_reg == 0)
6874 {
6875 i.rm.mode = 0;
6876 if (!i.disp_operands)
6877 fake_zero_displacement = 1;
6878 if (i.index_reg == 0)
6879 {
6880 gas_assert (!i.tm.opcode_modifier.vecsib);
6881 /* Operand is just <disp> */
6882 if (flag_code == CODE_64BIT)
6883 {
6884 /* 64bit mode overwrites the 32bit absolute
6885 addressing by RIP relative addressing and
6886 absolute addressing is encoded by one of the
6887 redundant SIB forms. */
6888 i.rm.regmem = ESCAPE_TO_TWO_BYTE_ADDRESSING;
6889 i.sib.base = NO_BASE_REGISTER;
6890 i.sib.index = NO_INDEX_REGISTER;
6891 i.types[op] = ((i.prefix[ADDR_PREFIX] == 0)
6892 ? disp32s : disp32);
6893 }
6894 else if ((flag_code == CODE_16BIT)
6895 ^ (i.prefix[ADDR_PREFIX] != 0))
6896 {
6897 i.rm.regmem = NO_BASE_REGISTER_16;
6898 i.types[op] = disp16;
6899 }
6900 else
6901 {
6902 i.rm.regmem = NO_BASE_REGISTER;
6903 i.types[op] = disp32;
6904 }
6905 }
6906 else if (!i.tm.opcode_modifier.vecsib)
6907 {
6908 /* !i.base_reg && i.index_reg */
6909 if (i.index_reg->reg_num == RegEiz
6910 || i.index_reg->reg_num == RegRiz)
6911 i.sib.index = NO_INDEX_REGISTER;
6912 else
6913 i.sib.index = i.index_reg->reg_num;
6914 i.sib.base = NO_BASE_REGISTER;
6915 i.sib.scale = i.log2_scale_factor;
6916 i.rm.regmem = ESCAPE_TO_TWO_BYTE_ADDRESSING;
6917 i.types[op].bitfield.disp8 = 0;
6918 i.types[op].bitfield.disp16 = 0;
6919 i.types[op].bitfield.disp64 = 0;
6920 if (flag_code != CODE_64BIT || i.prefix[ADDR_PREFIX])
6921 {
6922 /* Must be 32 bit */
6923 i.types[op].bitfield.disp32 = 1;
6924 i.types[op].bitfield.disp32s = 0;
6925 }
6926 else
6927 {
6928 i.types[op].bitfield.disp32 = 0;
6929 i.types[op].bitfield.disp32s = 1;
6930 }
6931 if ((i.index_reg->reg_flags & RegRex) != 0)
6932 i.rex |= REX_X;
6933 }
6934 }
6935 /* RIP addressing for 64bit mode. */
6936 else if (i.base_reg->reg_num == RegRip ||
6937 i.base_reg->reg_num == RegEip)
6938 {
6939 gas_assert (!i.tm.opcode_modifier.vecsib);
6940 i.rm.regmem = NO_BASE_REGISTER;
6941 i.types[op].bitfield.disp8 = 0;
6942 i.types[op].bitfield.disp16 = 0;
6943 i.types[op].bitfield.disp32 = 0;
6944 i.types[op].bitfield.disp32s = 1;
6945 i.types[op].bitfield.disp64 = 0;
6946 i.flags[op] |= Operand_PCrel;
6947 if (! i.disp_operands)
6948 fake_zero_displacement = 1;
6949 }
6950 else if (i.base_reg->reg_type.bitfield.word)
6951 {
6952 gas_assert (!i.tm.opcode_modifier.vecsib);
6953 switch (i.base_reg->reg_num)
6954 {
6955 case 3: /* (%bx) */
6956 if (i.index_reg == 0)
6957 i.rm.regmem = 7;
6958 else /* (%bx,%si) -> 0, or (%bx,%di) -> 1 */
6959 i.rm.regmem = i.index_reg->reg_num - 6;
6960 break;
6961 case 5: /* (%bp) */
6962 default_seg = &ss;
6963 if (i.index_reg == 0)
6964 {
6965 i.rm.regmem = 6;
6966 if (operand_type_check (i.types[op], disp) == 0)
6967 {
6968 /* fake (%bp) into 0(%bp) */
6969 i.types[op].bitfield.disp8 = 1;
6970 fake_zero_displacement = 1;
6971 }
6972 }
6973 else /* (%bp,%si) -> 2, or (%bp,%di) -> 3 */
6974 i.rm.regmem = i.index_reg->reg_num - 6 + 2;
6975 break;
6976 default: /* (%si) -> 4 or (%di) -> 5 */
6977 i.rm.regmem = i.base_reg->reg_num - 6 + 4;
6978 }
6979 i.rm.mode = mode_from_disp_size (i.types[op]);
6980 }
6981 else /* i.base_reg and 32/64 bit mode */
6982 {
6983 if (flag_code == CODE_64BIT
6984 && operand_type_check (i.types[op], disp))
6985 {
6986 i386_operand_type temp;
6987 operand_type_set (&temp, 0);
6988 temp.bitfield.disp8 = i.types[op].bitfield.disp8;
6989 i.types[op] = temp;
6990 if (i.prefix[ADDR_PREFIX] == 0)
6991 i.types[op].bitfield.disp32s = 1;
6992 else
6993 i.types[op].bitfield.disp32 = 1;
6994 }
6995
6996 if (!i.tm.opcode_modifier.vecsib)
6997 i.rm.regmem = i.base_reg->reg_num;
6998 if ((i.base_reg->reg_flags & RegRex) != 0)
6999 i.rex |= REX_B;
7000 i.sib.base = i.base_reg->reg_num;
7001 /* x86-64 ignores REX prefix bit here to avoid decoder
7002 complications. */
7003 if (!(i.base_reg->reg_flags & RegRex)
7004 && (i.base_reg->reg_num == EBP_REG_NUM
7005 || i.base_reg->reg_num == ESP_REG_NUM))
7006 default_seg = &ss;
7007 if (i.base_reg->reg_num == 5 && i.disp_operands == 0)
7008 {
7009 fake_zero_displacement = 1;
7010 i.types[op].bitfield.disp8 = 1;
7011 }
7012 i.sib.scale = i.log2_scale_factor;
7013 if (i.index_reg == 0)
7014 {
7015 gas_assert (!i.tm.opcode_modifier.vecsib);
7016 /* <disp>(%esp) becomes two byte modrm with no index
7017 register. We've already stored the code for esp
7018 in i.rm.regmem ie. ESCAPE_TO_TWO_BYTE_ADDRESSING.
7019 Any base register besides %esp will not use the
7020 extra modrm byte. */
7021 i.sib.index = NO_INDEX_REGISTER;
7022 }
7023 else if (!i.tm.opcode_modifier.vecsib)
7024 {
7025 if (i.index_reg->reg_num == RegEiz
7026 || i.index_reg->reg_num == RegRiz)
7027 i.sib.index = NO_INDEX_REGISTER;
7028 else
7029 i.sib.index = i.index_reg->reg_num;
7030 i.rm.regmem = ESCAPE_TO_TWO_BYTE_ADDRESSING;
7031 if ((i.index_reg->reg_flags & RegRex) != 0)
7032 i.rex |= REX_X;
7033 }
7034
7035 if (i.disp_operands
7036 && (i.reloc[op] == BFD_RELOC_386_TLS_DESC_CALL
7037 || i.reloc[op] == BFD_RELOC_X86_64_TLSDESC_CALL))
7038 i.rm.mode = 0;
7039 else
7040 {
7041 if (!fake_zero_displacement
7042 && !i.disp_operands
7043 && i.disp_encoding)
7044 {
7045 fake_zero_displacement = 1;
7046 if (i.disp_encoding == disp_encoding_8bit)
7047 i.types[op].bitfield.disp8 = 1;
7048 else
7049 i.types[op].bitfield.disp32 = 1;
7050 }
7051 i.rm.mode = mode_from_disp_size (i.types[op]);
7052 }
7053 }
7054
7055 if (fake_zero_displacement)
7056 {
7057 /* Fakes a zero displacement assuming that i.types[op]
7058 holds the correct displacement size. */
7059 expressionS *exp;
7060
7061 gas_assert (i.op[op].disps == 0);
7062 exp = &disp_expressions[i.disp_operands++];
7063 i.op[op].disps = exp;
7064 exp->X_op = O_constant;
7065 exp->X_add_number = 0;
7066 exp->X_add_symbol = (symbolS *) 0;
7067 exp->X_op_symbol = (symbolS *) 0;
7068 }
7069
7070 mem = op;
7071 }
7072 else
7073 mem = ~0;
7074
7075 if (i.tm.opcode_modifier.vexsources == XOP2SOURCES)
7076 {
7077 if (operand_type_check (i.types[0], imm))
7078 i.vex.register_specifier = NULL;
7079 else
7080 {
7081 /* VEX.vvvv encodes one of the sources when the first
7082 operand is not an immediate. */
7083 if (i.tm.opcode_modifier.vexw == VEXW0)
7084 i.vex.register_specifier = i.op[0].regs;
7085 else
7086 i.vex.register_specifier = i.op[1].regs;
7087 }
7088
7089 /* Destination is a XMM register encoded in the ModRM.reg
7090 and VEX.R bit. */
7091 i.rm.reg = i.op[2].regs->reg_num;
7092 if ((i.op[2].regs->reg_flags & RegRex) != 0)
7093 i.rex |= REX_R;
7094
7095 /* ModRM.rm and VEX.B encodes the other source. */
7096 if (!i.mem_operands)
7097 {
7098 i.rm.mode = 3;
7099
7100 if (i.tm.opcode_modifier.vexw == VEXW0)
7101 i.rm.regmem = i.op[1].regs->reg_num;
7102 else
7103 i.rm.regmem = i.op[0].regs->reg_num;
7104
7105 if ((i.op[1].regs->reg_flags & RegRex) != 0)
7106 i.rex |= REX_B;
7107 }
7108 }
7109 else if (i.tm.opcode_modifier.vexvvvv == VEXLWP)
7110 {
7111 i.vex.register_specifier = i.op[2].regs;
7112 if (!i.mem_operands)
7113 {
7114 i.rm.mode = 3;
7115 i.rm.regmem = i.op[1].regs->reg_num;
7116 if ((i.op[1].regs->reg_flags & RegRex) != 0)
7117 i.rex |= REX_B;
7118 }
7119 }
7120 /* Fill in i.rm.reg or i.rm.regmem field with register operand
7121 (if any) based on i.tm.extension_opcode. Again, we must be
7122 careful to make sure that segment/control/debug/test/MMX
7123 registers are coded into the i.rm.reg field. */
7124 else if (i.reg_operands)
7125 {
7126 unsigned int op;
7127 unsigned int vex_reg = ~0;
7128
7129 for (op = 0; op < i.operands; op++)
7130 if (i.types[op].bitfield.reg
7131 || i.types[op].bitfield.regmmx
7132 || i.types[op].bitfield.regsimd
7133 || i.types[op].bitfield.regbnd
7134 || i.types[op].bitfield.regmask
7135 || i.types[op].bitfield.sreg2
7136 || i.types[op].bitfield.sreg3
7137 || i.types[op].bitfield.control
7138 || i.types[op].bitfield.debug
7139 || i.types[op].bitfield.test)
7140 break;
7141
7142 if (vex_3_sources)
7143 op = dest;
7144 else if (i.tm.opcode_modifier.vexvvvv == VEXXDS)
7145 {
7146 /* For instructions with VexNDS, the register-only
7147 source operand is encoded in VEX prefix. */
7148 gas_assert (mem != (unsigned int) ~0);
7149
7150 if (op > mem)
7151 {
7152 vex_reg = op++;
7153 gas_assert (op < i.operands);
7154 }
7155 else
7156 {
7157 /* Check register-only source operand when two source
7158 operands are swapped. */
7159 if (!i.tm.operand_types[op].bitfield.baseindex
7160 && i.tm.operand_types[op + 1].bitfield.baseindex)
7161 {
7162 vex_reg = op;
7163 op += 2;
7164 gas_assert (mem == (vex_reg + 1)
7165 && op < i.operands);
7166 }
7167 else
7168 {
7169 vex_reg = op + 1;
7170 gas_assert (vex_reg < i.operands);
7171 }
7172 }
7173 }
7174 else if (i.tm.opcode_modifier.vexvvvv == VEXNDD)
7175 {
7176 /* For instructions with VexNDD, the register destination
7177 is encoded in VEX prefix. */
7178 if (i.mem_operands == 0)
7179 {
7180 /* There is no memory operand. */
7181 gas_assert ((op + 2) == i.operands);
7182 vex_reg = op + 1;
7183 }
7184 else
7185 {
7186 /* There are only 2 operands. */
7187 gas_assert (op < 2 && i.operands == 2);
7188 vex_reg = 1;
7189 }
7190 }
7191 else
7192 gas_assert (op < i.operands);
7193
7194 if (vex_reg != (unsigned int) ~0)
7195 {
7196 i386_operand_type *type = &i.tm.operand_types[vex_reg];
7197
7198 if ((!type->bitfield.reg
7199 || (!type->bitfield.dword && !type->bitfield.qword))
7200 && !type->bitfield.regsimd
7201 && !operand_type_equal (type, &regmask))
7202 abort ();
7203
7204 i.vex.register_specifier = i.op[vex_reg].regs;
7205 }
7206
7207 /* Don't set OP operand twice. */
7208 if (vex_reg != op)
7209 {
7210 /* If there is an extension opcode to put here, the
7211 register number must be put into the regmem field. */
7212 if (i.tm.extension_opcode != None)
7213 {
7214 i.rm.regmem = i.op[op].regs->reg_num;
7215 if ((i.op[op].regs->reg_flags & RegRex) != 0)
7216 i.rex |= REX_B;
7217 if ((i.op[op].regs->reg_flags & RegVRex) != 0)
7218 i.vrex |= REX_B;
7219 }
7220 else
7221 {
7222 i.rm.reg = i.op[op].regs->reg_num;
7223 if ((i.op[op].regs->reg_flags & RegRex) != 0)
7224 i.rex |= REX_R;
7225 if ((i.op[op].regs->reg_flags & RegVRex) != 0)
7226 i.vrex |= REX_R;
7227 }
7228 }
7229
7230 /* Now, if no memory operand has set i.rm.mode = 0, 1, 2 we
7231 must set it to 3 to indicate this is a register operand
7232 in the regmem field. */
7233 if (!i.mem_operands)
7234 i.rm.mode = 3;
7235 }
7236
7237 /* Fill in i.rm.reg field with extension opcode (if any). */
7238 if (i.tm.extension_opcode != None)
7239 i.rm.reg = i.tm.extension_opcode;
7240 }
7241 return default_seg;
7242}
7243
7244static void
7245output_branch (void)
7246{
7247 char *p;
7248 int size;
7249 int code16;
7250 int prefix;
7251 relax_substateT subtype;
7252 symbolS *sym;
7253 offsetT off;
7254
7255 code16 = flag_code == CODE_16BIT ? CODE16 : 0;
7256 size = i.disp_encoding == disp_encoding_32bit ? BIG : SMALL;
7257
7258 prefix = 0;
7259 if (i.prefix[DATA_PREFIX] != 0)
7260 {
7261 prefix = 1;
7262 i.prefixes -= 1;
7263 code16 ^= CODE16;
7264 }
7265 /* Pentium4 branch hints. */
7266 if (i.prefix[SEG_PREFIX] == CS_PREFIX_OPCODE /* not taken */
7267 || i.prefix[SEG_PREFIX] == DS_PREFIX_OPCODE /* taken */)
7268 {
7269 prefix++;
7270 i.prefixes--;
7271 }
7272 if (i.prefix[REX_PREFIX] != 0)
7273 {
7274 prefix++;
7275 i.prefixes--;
7276 }
7277
7278 /* BND prefixed jump. */
7279 if (i.prefix[BND_PREFIX] != 0)
7280 {
7281 FRAG_APPEND_1_CHAR (i.prefix[BND_PREFIX]);
7282 i.prefixes -= 1;
7283 }
7284
7285 if (i.prefixes != 0 && !intel_syntax)
7286 as_warn (_("skipping prefixes on this instruction"));
7287
7288 /* It's always a symbol; End frag & setup for relax.
7289 Make sure there is enough room in this frag for the largest
7290 instruction we may generate in md_convert_frag. This is 2
7291 bytes for the opcode and room for the prefix and largest
7292 displacement. */
7293 frag_grow (prefix + 2 + 4);
7294 /* Prefix and 1 opcode byte go in fr_fix. */
7295 p = frag_more (prefix + 1);
7296 if (i.prefix[DATA_PREFIX] != 0)
7297 *p++ = DATA_PREFIX_OPCODE;
7298 if (i.prefix[SEG_PREFIX] == CS_PREFIX_OPCODE
7299 || i.prefix[SEG_PREFIX] == DS_PREFIX_OPCODE)
7300 *p++ = i.prefix[SEG_PREFIX];
7301 if (i.prefix[REX_PREFIX] != 0)
7302 *p++ = i.prefix[REX_PREFIX];
7303 *p = i.tm.base_opcode;
7304
7305 if ((unsigned char) *p == JUMP_PC_RELATIVE)
7306 subtype = ENCODE_RELAX_STATE (UNCOND_JUMP, size);
7307 else if (cpu_arch_flags.bitfield.cpui386)
7308 subtype = ENCODE_RELAX_STATE (COND_JUMP, size);
7309 else
7310 subtype = ENCODE_RELAX_STATE (COND_JUMP86, size);
7311 subtype |= code16;
7312
7313 sym = i.op[0].disps->X_add_symbol;
7314 off = i.op[0].disps->X_add_number;
7315
7316 if (i.op[0].disps->X_op != O_constant
7317 && i.op[0].disps->X_op != O_symbol)
7318 {
7319 /* Handle complex expressions. */
7320 sym = make_expr_symbol (i.op[0].disps);
7321 off = 0;
7322 }
7323
7324 /* 1 possible extra opcode + 4 byte displacement go in var part.
7325 Pass reloc in fr_var. */
7326 frag_var (rs_machine_dependent, 5, i.reloc[0], subtype, sym, off, p);
7327}
7328
7329#if defined (OBJ_ELF) || defined (OBJ_MAYBE_ELF)
7330/* Return TRUE iff PLT32 relocation should be used for branching to
7331 symbol S. */
7332
7333static bfd_boolean
7334need_plt32_p (symbolS *s)
7335{
7336 /* PLT32 relocation is ELF only. */
7337 if (!IS_ELF)
7338 return FALSE;
7339
7340 /* Since there is no need to prepare for PLT branch on x86-64, we
7341 can generate R_X86_64_PLT32, instead of R_X86_64_PC32, which can
7342 be used as a marker for 32-bit PC-relative branches. */
7343 if (!object_64bit)
7344 return FALSE;
7345
7346 /* Weak or undefined symbol need PLT32 relocation. */
7347 if (S_IS_WEAK (s) || !S_IS_DEFINED (s))
7348 return TRUE;
7349
7350 /* Non-global symbol doesn't need PLT32 relocation. */
7351 if (! S_IS_EXTERNAL (s))
7352 return FALSE;
7353
7354 /* Other global symbols need PLT32 relocation. NB: Symbol with
7355 non-default visibilities are treated as normal global symbol
7356 so that PLT32 relocation can be used as a marker for 32-bit
7357 PC-relative branches. It is useful for linker relaxation. */
7358 return TRUE;
7359}
7360#endif
7361
7362static void
7363output_jump (void)
7364{
7365 char *p;
7366 int size;
7367 fixS *fixP;
7368 bfd_reloc_code_real_type jump_reloc = i.reloc[0];
7369
7370 if (i.tm.opcode_modifier.jumpbyte)
7371 {
7372 /* This is a loop or jecxz type instruction. */
7373 size = 1;
7374 if (i.prefix[ADDR_PREFIX] != 0)
7375 {
7376 FRAG_APPEND_1_CHAR (ADDR_PREFIX_OPCODE);
7377 i.prefixes -= 1;
7378 }
7379 /* Pentium4 branch hints. */
7380 if (i.prefix[SEG_PREFIX] == CS_PREFIX_OPCODE /* not taken */
7381 || i.prefix[SEG_PREFIX] == DS_PREFIX_OPCODE /* taken */)
7382 {
7383 FRAG_APPEND_1_CHAR (i.prefix[SEG_PREFIX]);
7384 i.prefixes--;
7385 }
7386 }
7387 else
7388 {
7389 int code16;
7390
7391 code16 = 0;
7392 if (flag_code == CODE_16BIT)
7393 code16 = CODE16;
7394
7395 if (i.prefix[DATA_PREFIX] != 0)
7396 {
7397 FRAG_APPEND_1_CHAR (DATA_PREFIX_OPCODE);
7398 i.prefixes -= 1;
7399 code16 ^= CODE16;
7400 }
7401
7402 size = 4;
7403 if (code16)
7404 size = 2;
7405 }
7406
7407 if (i.prefix[REX_PREFIX] != 0)
7408 {
7409 FRAG_APPEND_1_CHAR (i.prefix[REX_PREFIX]);
7410 i.prefixes -= 1;
7411 }
7412
7413 /* BND prefixed jump. */
7414 if (i.prefix[BND_PREFIX] != 0)
7415 {
7416 FRAG_APPEND_1_CHAR (i.prefix[BND_PREFIX]);
7417 i.prefixes -= 1;
7418 }
7419
7420 if (i.prefixes != 0 && !intel_syntax)
7421 as_warn (_("skipping prefixes on this instruction"));
7422
7423 p = frag_more (i.tm.opcode_length + size);
7424 switch (i.tm.opcode_length)
7425 {
7426 case 2:
7427 *p++ = i.tm.base_opcode >> 8;
7428 /* Fall through. */
7429 case 1:
7430 *p++ = i.tm.base_opcode;
7431 break;
7432 default:
7433 abort ();
7434 }
7435
7436#if defined (OBJ_ELF) || defined (OBJ_MAYBE_ELF)
7437 if (size == 4
7438 && jump_reloc == NO_RELOC
7439 && need_plt32_p (i.op[0].disps->X_add_symbol))
7440 jump_reloc = BFD_RELOC_X86_64_PLT32;
7441#endif
7442
7443 jump_reloc = reloc (size, 1, 1, jump_reloc);
7444
7445 fixP = fix_new_exp (frag_now, p - frag_now->fr_literal, size,
7446 i.op[0].disps, 1, jump_reloc);
7447
7448 /* All jumps handled here are signed, but don't use a signed limit
7449 check for 32 and 16 bit jumps as we want to allow wrap around at
7450 4G and 64k respectively. */
7451 if (size == 1)
7452 fixP->fx_signed = 1;
7453}
7454
7455static void
7456output_interseg_jump (void)
7457{
7458 char *p;
7459 int size;
7460 int prefix;
7461 int code16;
7462
7463 code16 = 0;
7464 if (flag_code == CODE_16BIT)
7465 code16 = CODE16;
7466
7467 prefix = 0;
7468 if (i.prefix[DATA_PREFIX] != 0)
7469 {
7470 prefix = 1;
7471 i.prefixes -= 1;
7472 code16 ^= CODE16;
7473 }
7474 if (i.prefix[REX_PREFIX] != 0)
7475 {
7476 prefix++;
7477 i.prefixes -= 1;
7478 }
7479
7480 size = 4;
7481 if (code16)
7482 size = 2;
7483
7484 if (i.prefixes != 0 && !intel_syntax)
7485 as_warn (_("skipping prefixes on this instruction"));
7486
7487 /* 1 opcode; 2 segment; offset */
7488 p = frag_more (prefix + 1 + 2 + size);
7489
7490 if (i.prefix[DATA_PREFIX] != 0)
7491 *p++ = DATA_PREFIX_OPCODE;
7492
7493 if (i.prefix[REX_PREFIX] != 0)
7494 *p++ = i.prefix[REX_PREFIX];
7495
7496 *p++ = i.tm.base_opcode;
7497 if (i.op[1].imms->X_op == O_constant)
7498 {
7499 offsetT n = i.op[1].imms->X_add_number;
7500
7501 if (size == 2
7502 && !fits_in_unsigned_word (n)
7503 && !fits_in_signed_word (n))
7504 {
7505 as_bad (_("16-bit jump out of range"));
7506 return;
7507 }
7508 md_number_to_chars (p, n, size);
7509 }
7510 else
7511 fix_new_exp (frag_now, p - frag_now->fr_literal, size,
7512 i.op[1].imms, 0, reloc (size, 0, 0, i.reloc[1]));
7513 if (i.op[0].imms->X_op != O_constant)
7514 as_bad (_("can't handle non absolute segment in `%s'"),
7515 i.tm.name);
7516 md_number_to_chars (p + size, (valueT) i.op[0].imms->X_add_number, 2);
7517}
7518
7519static void
7520output_insn (void)
7521{
7522 fragS *insn_start_frag;
7523 offsetT insn_start_off;
7524
7525 /* Tie dwarf2 debug info to the address at the start of the insn.
7526 We can't do this after the insn has been output as the current
7527 frag may have been closed off. eg. by frag_var. */
7528 dwarf2_emit_insn (0);
7529
7530 insn_start_frag = frag_now;
7531 insn_start_off = frag_now_fix ();
7532
7533 /* Output jumps. */
7534 if (i.tm.opcode_modifier.jump)
7535 output_branch ();
7536 else if (i.tm.opcode_modifier.jumpbyte
7537 || i.tm.opcode_modifier.jumpdword)
7538 output_jump ();
7539 else if (i.tm.opcode_modifier.jumpintersegment)
7540 output_interseg_jump ();
7541 else
7542 {
7543 /* Output normal instructions here. */
7544 char *p;
7545 unsigned char *q;
7546 unsigned int j;
7547 unsigned int prefix;
7548
7549 if (avoid_fence
7550 && i.tm.base_opcode == 0xfae
7551 && i.operands == 1
7552 && i.imm_operands == 1
7553 && (i.op[0].imms->X_add_number == 0xe8
7554 || i.op[0].imms->X_add_number == 0xf0
7555 || i.op[0].imms->X_add_number == 0xf8))
7556 {
7557 /* Encode lfence, mfence, and sfence as
7558 f0 83 04 24 00 lock addl $0x0, (%{re}sp). */
7559 offsetT val = 0x240483f0ULL;
7560 p = frag_more (5);
7561 md_number_to_chars (p, val, 5);
7562 return;
7563 }
7564
7565 /* Some processors fail on LOCK prefix. This options makes
7566 assembler ignore LOCK prefix and serves as a workaround. */
7567 if (omit_lock_prefix)
7568 {
7569 if (i.tm.base_opcode == LOCK_PREFIX_OPCODE)
7570 return;
7571 i.prefix[LOCK_PREFIX] = 0;
7572 }
7573
7574 /* Since the VEX/EVEX prefix contains the implicit prefix, we
7575 don't need the explicit prefix. */
7576 if (!i.tm.opcode_modifier.vex && !i.tm.opcode_modifier.evex)
7577 {
7578 switch (i.tm.opcode_length)
7579 {
7580 case 3:
7581 if (i.tm.base_opcode & 0xff000000)
7582 {
7583 prefix = (i.tm.base_opcode >> 24) & 0xff;
7584 goto check_prefix;
7585 }
7586 break;
7587 case 2:
7588 if ((i.tm.base_opcode & 0xff0000) != 0)
7589 {
7590 prefix = (i.tm.base_opcode >> 16) & 0xff;
7591 if (i.tm.cpu_flags.bitfield.cpupadlock)
7592 {
7593check_prefix:
7594 if (prefix != REPE_PREFIX_OPCODE
7595 || (i.prefix[REP_PREFIX]
7596 != REPE_PREFIX_OPCODE))
7597 add_prefix (prefix);
7598 }
7599 else
7600 add_prefix (prefix);
7601 }
7602 break;
7603 case 1:
7604 break;
7605 case 0:
7606 /* Check for pseudo prefixes. */
7607 as_bad_where (insn_start_frag->fr_file,
7608 insn_start_frag->fr_line,
7609 _("pseudo prefix without instruction"));
7610 return;
7611 default:
7612 abort ();
7613 }
7614
7615#if defined (OBJ_MAYBE_ELF) || defined (OBJ_ELF)
7616 /* For x32, add a dummy REX_OPCODE prefix for mov/add with
7617 R_X86_64_GOTTPOFF relocation so that linker can safely
7618 perform IE->LE optimization. */
7619 if (x86_elf_abi == X86_64_X32_ABI
7620 && i.operands == 2
7621 && i.reloc[0] == BFD_RELOC_X86_64_GOTTPOFF
7622 && i.prefix[REX_PREFIX] == 0)
7623 add_prefix (REX_OPCODE);
7624#endif
7625
7626 /* The prefix bytes. */
7627 for (j = ARRAY_SIZE (i.prefix), q = i.prefix; j > 0; j--, q++)
7628 if (*q)
7629 FRAG_APPEND_1_CHAR (*q);
7630 }
7631 else
7632 {
7633 for (j = 0, q = i.prefix; j < ARRAY_SIZE (i.prefix); j++, q++)
7634 if (*q)
7635 switch (j)
7636 {
7637 case REX_PREFIX:
7638 /* REX byte is encoded in VEX prefix. */
7639 break;
7640 case SEG_PREFIX:
7641 case ADDR_PREFIX:
7642 FRAG_APPEND_1_CHAR (*q);
7643 break;
7644 default:
7645 /* There should be no other prefixes for instructions
7646 with VEX prefix. */
7647 abort ();
7648 }
7649
7650 /* For EVEX instructions i.vrex should become 0 after
7651 build_evex_prefix. For VEX instructions upper 16 registers
7652 aren't available, so VREX should be 0. */
7653 if (i.vrex)
7654 abort ();
7655 /* Now the VEX prefix. */
7656 p = frag_more (i.vex.length);
7657 for (j = 0; j < i.vex.length; j++)
7658 p[j] = i.vex.bytes[j];
7659 }
7660
7661 /* Now the opcode; be careful about word order here! */
7662 if (i.tm.opcode_length == 1)
7663 {
7664 FRAG_APPEND_1_CHAR (i.tm.base_opcode);
7665 }
7666 else
7667 {
7668 switch (i.tm.opcode_length)
7669 {
7670 case 4:
7671 p = frag_more (4);
7672 *p++ = (i.tm.base_opcode >> 24) & 0xff;
7673 *p++ = (i.tm.base_opcode >> 16) & 0xff;
7674 break;
7675 case 3:
7676 p = frag_more (3);
7677 *p++ = (i.tm.base_opcode >> 16) & 0xff;
7678 break;
7679 case 2:
7680 p = frag_more (2);
7681 break;
7682 default:
7683 abort ();
7684 break;
7685 }
7686
7687 /* Put out high byte first: can't use md_number_to_chars! */
7688 *p++ = (i.tm.base_opcode >> 8) & 0xff;
7689 *p = i.tm.base_opcode & 0xff;
7690 }
7691
7692 /* Now the modrm byte and sib byte (if present). */
7693 if (i.tm.opcode_modifier.modrm)
7694 {
7695 FRAG_APPEND_1_CHAR ((i.rm.regmem << 0
7696 | i.rm.reg << 3
7697 | i.rm.mode << 6));
7698 /* If i.rm.regmem == ESP (4)
7699 && i.rm.mode != (Register mode)
7700 && not 16 bit
7701 ==> need second modrm byte. */
7702 if (i.rm.regmem == ESCAPE_TO_TWO_BYTE_ADDRESSING
7703 && i.rm.mode != 3
7704 && !(i.base_reg && i.base_reg->reg_type.bitfield.word))
7705 FRAG_APPEND_1_CHAR ((i.sib.base << 0
7706 | i.sib.index << 3
7707 | i.sib.scale << 6));
7708 }
7709
7710 if (i.disp_operands)
7711 output_disp (insn_start_frag, insn_start_off);
7712
7713 if (i.imm_operands)
7714 output_imm (insn_start_frag, insn_start_off);
7715 }
7716
7717#ifdef DEBUG386
7718 if (flag_debug)
7719 {
7720 pi ("" /*line*/, &i);
7721 }
7722#endif /* DEBUG386 */
7723}
7724
7725/* Return the size of the displacement operand N. */
7726
7727static int
7728disp_size (unsigned int n)
7729{
7730 int size = 4;
7731
7732 if (i.types[n].bitfield.disp64)
7733 size = 8;
7734 else if (i.types[n].bitfield.disp8)
7735 size = 1;
7736 else if (i.types[n].bitfield.disp16)
7737 size = 2;
7738 return size;
7739}
7740
7741/* Return the size of the immediate operand N. */
7742
7743static int
7744imm_size (unsigned int n)
7745{
7746 int size = 4;
7747 if (i.types[n].bitfield.imm64)
7748 size = 8;
7749 else if (i.types[n].bitfield.imm8 || i.types[n].bitfield.imm8s)
7750 size = 1;
7751 else if (i.types[n].bitfield.imm16)
7752 size = 2;
7753 return size;
7754}
7755
7756static void
7757output_disp (fragS *insn_start_frag, offsetT insn_start_off)
7758{
7759 char *p;
7760 unsigned int n;
7761
7762 for (n = 0; n < i.operands; n++)
7763 {
7764 if (operand_type_check (i.types[n], disp))
7765 {
7766 if (i.op[n].disps->X_op == O_constant)
7767 {
7768 int size = disp_size (n);
7769 offsetT val = i.op[n].disps->X_add_number;
7770
7771 val = offset_in_range (val >> i.memshift, size);
7772 p = frag_more (size);
7773 md_number_to_chars (p, val, size);
7774 }
7775 else
7776 {
7777 enum bfd_reloc_code_real reloc_type;
7778 int size = disp_size (n);
7779 int sign = i.types[n].bitfield.disp32s;
7780 int pcrel = (i.flags[n] & Operand_PCrel) != 0;
7781 fixS *fixP;
7782
7783 /* We can't have 8 bit displacement here. */
7784 gas_assert (!i.types[n].bitfield.disp8);
7785
7786 /* The PC relative address is computed relative
7787 to the instruction boundary, so in case immediate
7788 fields follows, we need to adjust the value. */
7789 if (pcrel && i.imm_operands)
7790 {
7791 unsigned int n1;
7792 int sz = 0;
7793
7794 for (n1 = 0; n1 < i.operands; n1++)
7795 if (operand_type_check (i.types[n1], imm))
7796 {
7797 /* Only one immediate is allowed for PC
7798 relative address. */
7799 gas_assert (sz == 0);
7800 sz = imm_size (n1);
7801 i.op[n].disps->X_add_number -= sz;
7802 }
7803 /* We should find the immediate. */
7804 gas_assert (sz != 0);
7805 }
7806
7807 p = frag_more (size);
7808 reloc_type = reloc (size, pcrel, sign, i.reloc[n]);
7809 if (GOT_symbol
7810 && GOT_symbol == i.op[n].disps->X_add_symbol
7811 && (((reloc_type == BFD_RELOC_32
7812 || reloc_type == BFD_RELOC_X86_64_32S
7813 || (reloc_type == BFD_RELOC_64
7814 && object_64bit))
7815 && (i.op[n].disps->X_op == O_symbol
7816 || (i.op[n].disps->X_op == O_add
7817 && ((symbol_get_value_expression
7818 (i.op[n].disps->X_op_symbol)->X_op)
7819 == O_subtract))))
7820 || reloc_type == BFD_RELOC_32_PCREL))
7821 {
7822 offsetT add;
7823
7824 if (insn_start_frag == frag_now)
7825 add = (p - frag_now->fr_literal) - insn_start_off;
7826 else
7827 {
7828 fragS *fr;
7829
7830 add = insn_start_frag->fr_fix - insn_start_off;
7831 for (fr = insn_start_frag->fr_next;
7832 fr && fr != frag_now; fr = fr->fr_next)
7833 add += fr->fr_fix;
7834 add += p - frag_now->fr_literal;
7835 }
7836
7837 if (!object_64bit)
7838 {
7839 reloc_type = BFD_RELOC_386_GOTPC;
7840 i.op[n].imms->X_add_number += add;
7841 }
7842 else if (reloc_type == BFD_RELOC_64)
7843 reloc_type = BFD_RELOC_X86_64_GOTPC64;
7844 else
7845 /* Don't do the adjustment for x86-64, as there
7846 the pcrel addressing is relative to the _next_
7847 insn, and that is taken care of in other code. */
7848 reloc_type = BFD_RELOC_X86_64_GOTPC32;
7849 }
7850 fixP = fix_new_exp (frag_now, p - frag_now->fr_literal,
7851 size, i.op[n].disps, pcrel,
7852 reloc_type);
7853 /* Check for "call/jmp *mem", "mov mem, %reg",
7854 "test %reg, mem" and "binop mem, %reg" where binop
7855 is one of adc, add, and, cmp, or, sbb, sub, xor
7856 instructions. Always generate R_386_GOT32X for
7857 "sym*GOT" operand in 32-bit mode. */
7858 if ((generate_relax_relocations
7859 || (!object_64bit
7860 && i.rm.mode == 0
7861 && i.rm.regmem == 5))
7862 && (i.rm.mode == 2
7863 || (i.rm.mode == 0 && i.rm.regmem == 5))
7864 && ((i.operands == 1
7865 && i.tm.base_opcode == 0xff
7866 && (i.rm.reg == 2 || i.rm.reg == 4))
7867 || (i.operands == 2
7868 && (i.tm.base_opcode == 0x8b
7869 || i.tm.base_opcode == 0x85
7870 || (i.tm.base_opcode & 0xc7) == 0x03))))
7871 {
7872 if (object_64bit)
7873 {
7874 fixP->fx_tcbit = i.rex != 0;
7875 if (i.base_reg
7876 && (i.base_reg->reg_num == RegRip
7877 || i.base_reg->reg_num == RegEip))
7878 fixP->fx_tcbit2 = 1;
7879 }
7880 else
7881 fixP->fx_tcbit2 = 1;
7882 }
7883 }
7884 }
7885 }
7886}
7887
7888static void
7889output_imm (fragS *insn_start_frag, offsetT insn_start_off)
7890{
7891 char *p;
7892 unsigned int n;
7893
7894 for (n = 0; n < i.operands; n++)
7895 {
7896 /* Skip SAE/RC Imm operand in EVEX. They are already handled. */
7897 if (i.rounding && (int) n == i.rounding->operand)
7898 continue;
7899
7900 if (operand_type_check (i.types[n], imm))
7901 {
7902 if (i.op[n].imms->X_op == O_constant)
7903 {
7904 int size = imm_size (n);
7905 offsetT val;
7906
7907 val = offset_in_range (i.op[n].imms->X_add_number,
7908 size);
7909 p = frag_more (size);
7910 md_number_to_chars (p, val, size);
7911 }
7912 else
7913 {
7914 /* Not absolute_section.
7915 Need a 32-bit fixup (don't support 8bit
7916 non-absolute imms). Try to support other
7917 sizes ... */
7918 enum bfd_reloc_code_real reloc_type;
7919 int size = imm_size (n);
7920 int sign;
7921
7922 if (i.types[n].bitfield.imm32s
7923 && (i.suffix == QWORD_MNEM_SUFFIX
7924 || (!i.suffix && i.tm.opcode_modifier.no_lsuf)))
7925 sign = 1;
7926 else
7927 sign = 0;
7928
7929 p = frag_more (size);
7930 reloc_type = reloc (size, 0, sign, i.reloc[n]);
7931
7932 /* This is tough to explain. We end up with this one if we
7933 * have operands that look like
7934 * "_GLOBAL_OFFSET_TABLE_+[.-.L284]". The goal here is to
7935 * obtain the absolute address of the GOT, and it is strongly
7936 * preferable from a performance point of view to avoid using
7937 * a runtime relocation for this. The actual sequence of
7938 * instructions often look something like:
7939 *
7940 * call .L66
7941 * .L66:
7942 * popl %ebx
7943 * addl $_GLOBAL_OFFSET_TABLE_+[.-.L66],%ebx
7944 *
7945 * The call and pop essentially return the absolute address
7946 * of the label .L66 and store it in %ebx. The linker itself
7947 * will ultimately change the first operand of the addl so
7948 * that %ebx points to the GOT, but to keep things simple, the
7949 * .o file must have this operand set so that it generates not
7950 * the absolute address of .L66, but the absolute address of
7951 * itself. This allows the linker itself simply treat a GOTPC
7952 * relocation as asking for a pcrel offset to the GOT to be
7953 * added in, and the addend of the relocation is stored in the
7954 * operand field for the instruction itself.
7955 *
7956 * Our job here is to fix the operand so that it would add
7957 * the correct offset so that %ebx would point to itself. The
7958 * thing that is tricky is that .-.L66 will point to the
7959 * beginning of the instruction, so we need to further modify
7960 * the operand so that it will point to itself. There are
7961 * other cases where you have something like:
7962 *
7963 * .long $_GLOBAL_OFFSET_TABLE_+[.-.L66]
7964 *
7965 * and here no correction would be required. Internally in
7966 * the assembler we treat operands of this form as not being
7967 * pcrel since the '.' is explicitly mentioned, and I wonder
7968 * whether it would simplify matters to do it this way. Who
7969 * knows. In earlier versions of the PIC patches, the
7970 * pcrel_adjust field was used to store the correction, but
7971 * since the expression is not pcrel, I felt it would be
7972 * confusing to do it this way. */
7973
7974 if ((reloc_type == BFD_RELOC_32
7975 || reloc_type == BFD_RELOC_X86_64_32S
7976 || reloc_type == BFD_RELOC_64)
7977 && GOT_symbol
7978 && GOT_symbol == i.op[n].imms->X_add_symbol
7979 && (i.op[n].imms->X_op == O_symbol
7980 || (i.op[n].imms->X_op == O_add
7981 && ((symbol_get_value_expression
7982 (i.op[n].imms->X_op_symbol)->X_op)
7983 == O_subtract))))
7984 {
7985 offsetT add;
7986
7987 if (insn_start_frag == frag_now)
7988 add = (p - frag_now->fr_literal) - insn_start_off;
7989 else
7990 {
7991 fragS *fr;
7992
7993 add = insn_start_frag->fr_fix - insn_start_off;
7994 for (fr = insn_start_frag->fr_next;
7995 fr && fr != frag_now; fr = fr->fr_next)
7996 add += fr->fr_fix;
7997 add += p - frag_now->fr_literal;
7998 }
7999
8000 if (!object_64bit)
8001 reloc_type = BFD_RELOC_386_GOTPC;
8002 else if (size == 4)
8003 reloc_type = BFD_RELOC_X86_64_GOTPC32;
8004 else if (size == 8)
8005 reloc_type = BFD_RELOC_X86_64_GOTPC64;
8006 i.op[n].imms->X_add_number += add;
8007 }
8008 fix_new_exp (frag_now, p - frag_now->fr_literal, size,
8009 i.op[n].imms, 0, reloc_type);
8010 }
8011 }
8012 }
8013}
8014\f
8015/* x86_cons_fix_new is called via the expression parsing code when a
8016 reloc is needed. We use this hook to get the correct .got reloc. */
8017static int cons_sign = -1;
8018
8019void
8020x86_cons_fix_new (fragS *frag, unsigned int off, unsigned int len,
8021 expressionS *exp, bfd_reloc_code_real_type r)
8022{
8023 r = reloc (len, 0, cons_sign, r);
8024
8025#ifdef TE_PE
8026 if (exp->X_op == O_secrel)
8027 {
8028 exp->X_op = O_symbol;
8029 r = BFD_RELOC_32_SECREL;
8030 }
8031#endif
8032
8033 fix_new_exp (frag, off, len, exp, 0, r);
8034}
8035
8036/* Export the ABI address size for use by TC_ADDRESS_BYTES for the
8037 purpose of the `.dc.a' internal pseudo-op. */
8038
8039int
8040x86_address_bytes (void)
8041{
8042 if ((stdoutput->arch_info->mach & bfd_mach_x64_32))
8043 return 4;
8044 return stdoutput->arch_info->bits_per_address / 8;
8045}
8046
8047#if !(defined (OBJ_ELF) || defined (OBJ_MAYBE_ELF) || defined (OBJ_MACH_O)) \
8048 || defined (LEX_AT)
8049# define lex_got(reloc, adjust, types) NULL
8050#else
8051/* Parse operands of the form
8052 <symbol>@GOTOFF+<nnn>
8053 and similar .plt or .got references.
8054
8055 If we find one, set up the correct relocation in RELOC and copy the
8056 input string, minus the `@GOTOFF' into a malloc'd buffer for
8057 parsing by the calling routine. Return this buffer, and if ADJUST
8058 is non-null set it to the length of the string we removed from the
8059 input line. Otherwise return NULL. */
8060static char *
8061lex_got (enum bfd_reloc_code_real *rel,
8062 int *adjust,
8063 i386_operand_type *types)
8064{
8065 /* Some of the relocations depend on the size of what field is to
8066 be relocated. But in our callers i386_immediate and i386_displacement
8067 we don't yet know the operand size (this will be set by insn
8068 matching). Hence we record the word32 relocation here,
8069 and adjust the reloc according to the real size in reloc(). */
8070 static const struct {
8071 const char *str;
8072 int len;
8073 const enum bfd_reloc_code_real rel[2];
8074 const i386_operand_type types64;
8075 } gotrel[] = {
8076#if defined (OBJ_ELF) || defined (OBJ_MAYBE_ELF)
8077 { STRING_COMMA_LEN ("SIZE"), { BFD_RELOC_SIZE32,
8078 BFD_RELOC_SIZE32 },
8079 OPERAND_TYPE_IMM32_64 },
8080#endif
8081 { STRING_COMMA_LEN ("PLTOFF"), { _dummy_first_bfd_reloc_code_real,
8082 BFD_RELOC_X86_64_PLTOFF64 },
8083 OPERAND_TYPE_IMM64 },
8084 { STRING_COMMA_LEN ("PLT"), { BFD_RELOC_386_PLT32,
8085 BFD_RELOC_X86_64_PLT32 },
8086 OPERAND_TYPE_IMM32_32S_DISP32 },
8087 { STRING_COMMA_LEN ("GOTPLT"), { _dummy_first_bfd_reloc_code_real,
8088 BFD_RELOC_X86_64_GOTPLT64 },
8089 OPERAND_TYPE_IMM64_DISP64 },
8090 { STRING_COMMA_LEN ("GOTOFF"), { BFD_RELOC_386_GOTOFF,
8091 BFD_RELOC_X86_64_GOTOFF64 },
8092 OPERAND_TYPE_IMM64_DISP64 },
8093 { STRING_COMMA_LEN ("GOTPCREL"), { _dummy_first_bfd_reloc_code_real,
8094 BFD_RELOC_X86_64_GOTPCREL },
8095 OPERAND_TYPE_IMM32_32S_DISP32 },
8096 { STRING_COMMA_LEN ("TLSGD"), { BFD_RELOC_386_TLS_GD,
8097 BFD_RELOC_X86_64_TLSGD },
8098 OPERAND_TYPE_IMM32_32S_DISP32 },
8099 { STRING_COMMA_LEN ("TLSLDM"), { BFD_RELOC_386_TLS_LDM,
8100 _dummy_first_bfd_reloc_code_real },
8101 OPERAND_TYPE_NONE },
8102 { STRING_COMMA_LEN ("TLSLD"), { _dummy_first_bfd_reloc_code_real,
8103 BFD_RELOC_X86_64_TLSLD },
8104 OPERAND_TYPE_IMM32_32S_DISP32 },
8105 { STRING_COMMA_LEN ("GOTTPOFF"), { BFD_RELOC_386_TLS_IE_32,
8106 BFD_RELOC_X86_64_GOTTPOFF },
8107 OPERAND_TYPE_IMM32_32S_DISP32 },
8108 { STRING_COMMA_LEN ("TPOFF"), { BFD_RELOC_386_TLS_LE_32,
8109 BFD_RELOC_X86_64_TPOFF32 },
8110 OPERAND_TYPE_IMM32_32S_64_DISP32_64 },
8111 { STRING_COMMA_LEN ("NTPOFF"), { BFD_RELOC_386_TLS_LE,
8112 _dummy_first_bfd_reloc_code_real },
8113 OPERAND_TYPE_NONE },
8114 { STRING_COMMA_LEN ("DTPOFF"), { BFD_RELOC_386_TLS_LDO_32,
8115 BFD_RELOC_X86_64_DTPOFF32 },
8116 OPERAND_TYPE_IMM32_32S_64_DISP32_64 },
8117 { STRING_COMMA_LEN ("GOTNTPOFF"),{ BFD_RELOC_386_TLS_GOTIE,
8118 _dummy_first_bfd_reloc_code_real },
8119 OPERAND_TYPE_NONE },
8120 { STRING_COMMA_LEN ("INDNTPOFF"),{ BFD_RELOC_386_TLS_IE,
8121 _dummy_first_bfd_reloc_code_real },
8122 OPERAND_TYPE_NONE },
8123 { STRING_COMMA_LEN ("GOT"), { BFD_RELOC_386_GOT32,
8124 BFD_RELOC_X86_64_GOT32 },
8125 OPERAND_TYPE_IMM32_32S_64_DISP32 },
8126 { STRING_COMMA_LEN ("TLSDESC"), { BFD_RELOC_386_TLS_GOTDESC,
8127 BFD_RELOC_X86_64_GOTPC32_TLSDESC },
8128 OPERAND_TYPE_IMM32_32S_DISP32 },
8129 { STRING_COMMA_LEN ("TLSCALL"), { BFD_RELOC_386_TLS_DESC_CALL,
8130 BFD_RELOC_X86_64_TLSDESC_CALL },
8131 OPERAND_TYPE_IMM32_32S_DISP32 },
8132 };
8133 char *cp;
8134 unsigned int j;
8135
8136#if defined (OBJ_MAYBE_ELF)
8137 if (!IS_ELF)
8138 return NULL;
8139#endif
8140
8141 for (cp = input_line_pointer; *cp != '@'; cp++)
8142 if (is_end_of_line[(unsigned char) *cp] || *cp == ',')
8143 return NULL;
8144
8145 for (j = 0; j < ARRAY_SIZE (gotrel); j++)
8146 {
8147 int len = gotrel[j].len;
8148 if (strncasecmp (cp + 1, gotrel[j].str, len) == 0)
8149 {
8150 if (gotrel[j].rel[object_64bit] != 0)
8151 {
8152 int first, second;
8153 char *tmpbuf, *past_reloc;
8154
8155 *rel = gotrel[j].rel[object_64bit];
8156
8157 if (types)
8158 {
8159 if (flag_code != CODE_64BIT)
8160 {
8161 types->bitfield.imm32 = 1;
8162 types->bitfield.disp32 = 1;
8163 }
8164 else
8165 *types = gotrel[j].types64;
8166 }
8167
8168 if (j != 0 && GOT_symbol == NULL)
8169 GOT_symbol = symbol_find_or_make (GLOBAL_OFFSET_TABLE_NAME);
8170
8171 /* The length of the first part of our input line. */
8172 first = cp - input_line_pointer;
8173
8174 /* The second part goes from after the reloc token until
8175 (and including) an end_of_line char or comma. */
8176 past_reloc = cp + 1 + len;
8177 cp = past_reloc;
8178 while (!is_end_of_line[(unsigned char) *cp] && *cp != ',')
8179 ++cp;
8180 second = cp + 1 - past_reloc;
8181
8182 /* Allocate and copy string. The trailing NUL shouldn't
8183 be necessary, but be safe. */
8184 tmpbuf = XNEWVEC (char, first + second + 2);
8185 memcpy (tmpbuf, input_line_pointer, first);
8186 if (second != 0 && *past_reloc != ' ')
8187 /* Replace the relocation token with ' ', so that
8188 errors like foo@GOTOFF1 will be detected. */
8189 tmpbuf[first++] = ' ';
8190 else
8191 /* Increment length by 1 if the relocation token is
8192 removed. */
8193 len++;
8194 if (adjust)
8195 *adjust = len;
8196 memcpy (tmpbuf + first, past_reloc, second);
8197 tmpbuf[first + second] = '\0';
8198 return tmpbuf;
8199 }
8200
8201 as_bad (_("@%s reloc is not supported with %d-bit output format"),
8202 gotrel[j].str, 1 << (5 + object_64bit));
8203 return NULL;
8204 }
8205 }
8206
8207 /* Might be a symbol version string. Don't as_bad here. */
8208 return NULL;
8209}
8210#endif
8211
8212#ifdef TE_PE
8213#ifdef lex_got
8214#undef lex_got
8215#endif
8216/* Parse operands of the form
8217 <symbol>@SECREL32+<nnn>
8218
8219 If we find one, set up the correct relocation in RELOC and copy the
8220 input string, minus the `@SECREL32' into a malloc'd buffer for
8221 parsing by the calling routine. Return this buffer, and if ADJUST
8222 is non-null set it to the length of the string we removed from the
8223 input line. Otherwise return NULL.
8224
8225 This function is copied from the ELF version above adjusted for PE targets. */
8226
8227static char *
8228lex_got (enum bfd_reloc_code_real *rel ATTRIBUTE_UNUSED,
8229 int *adjust ATTRIBUTE_UNUSED,
8230 i386_operand_type *types)
8231{
8232 static const struct
8233 {
8234 const char *str;
8235 int len;
8236 const enum bfd_reloc_code_real rel[2];
8237 const i386_operand_type types64;
8238 }
8239 gotrel[] =
8240 {
8241 { STRING_COMMA_LEN ("SECREL32"), { BFD_RELOC_32_SECREL,
8242 BFD_RELOC_32_SECREL },
8243 OPERAND_TYPE_IMM32_32S_64_DISP32_64 },
8244 };
8245
8246 char *cp;
8247 unsigned j;
8248
8249 for (cp = input_line_pointer; *cp != '@'; cp++)
8250 if (is_end_of_line[(unsigned char) *cp] || *cp == ',')
8251 return NULL;
8252
8253 for (j = 0; j < ARRAY_SIZE (gotrel); j++)
8254 {
8255 int len = gotrel[j].len;
8256
8257 if (strncasecmp (cp + 1, gotrel[j].str, len) == 0)
8258 {
8259 if (gotrel[j].rel[object_64bit] != 0)
8260 {
8261 int first, second;
8262 char *tmpbuf, *past_reloc;
8263
8264 *rel = gotrel[j].rel[object_64bit];
8265 if (adjust)
8266 *adjust = len;
8267
8268 if (types)
8269 {
8270 if (flag_code != CODE_64BIT)
8271 {
8272 types->bitfield.imm32 = 1;
8273 types->bitfield.disp32 = 1;
8274 }
8275 else
8276 *types = gotrel[j].types64;
8277 }
8278
8279 /* The length of the first part of our input line. */
8280 first = cp - input_line_pointer;
8281
8282 /* The second part goes from after the reloc token until
8283 (and including) an end_of_line char or comma. */
8284 past_reloc = cp + 1 + len;
8285 cp = past_reloc;
8286 while (!is_end_of_line[(unsigned char) *cp] && *cp != ',')
8287 ++cp;
8288 second = cp + 1 - past_reloc;
8289
8290 /* Allocate and copy string. The trailing NUL shouldn't
8291 be necessary, but be safe. */
8292 tmpbuf = XNEWVEC (char, first + second + 2);
8293 memcpy (tmpbuf, input_line_pointer, first);
8294 if (second != 0 && *past_reloc != ' ')
8295 /* Replace the relocation token with ' ', so that
8296 errors like foo@SECLREL321 will be detected. */
8297 tmpbuf[first++] = ' ';
8298 memcpy (tmpbuf + first, past_reloc, second);
8299 tmpbuf[first + second] = '\0';
8300 return tmpbuf;
8301 }
8302
8303 as_bad (_("@%s reloc is not supported with %d-bit output format"),
8304 gotrel[j].str, 1 << (5 + object_64bit));
8305 return NULL;
8306 }
8307 }
8308
8309 /* Might be a symbol version string. Don't as_bad here. */
8310 return NULL;
8311}
8312
8313#endif /* TE_PE */
8314
8315bfd_reloc_code_real_type
8316x86_cons (expressionS *exp, int size)
8317{
8318 bfd_reloc_code_real_type got_reloc = NO_RELOC;
8319
8320 intel_syntax = -intel_syntax;
8321
8322 exp->X_md = 0;
8323 if (size == 4 || (object_64bit && size == 8))
8324 {
8325 /* Handle @GOTOFF and the like in an expression. */
8326 char *save;
8327 char *gotfree_input_line;
8328 int adjust = 0;
8329
8330 save = input_line_pointer;
8331 gotfree_input_line = lex_got (&got_reloc, &adjust, NULL);
8332 if (gotfree_input_line)
8333 input_line_pointer = gotfree_input_line;
8334
8335 expression (exp);
8336
8337 if (gotfree_input_line)
8338 {
8339 /* expression () has merrily parsed up to the end of line,
8340 or a comma - in the wrong buffer. Transfer how far
8341 input_line_pointer has moved to the right buffer. */
8342 input_line_pointer = (save
8343 + (input_line_pointer - gotfree_input_line)
8344 + adjust);
8345 free (gotfree_input_line);
8346 if (exp->X_op == O_constant
8347 || exp->X_op == O_absent
8348 || exp->X_op == O_illegal
8349 || exp->X_op == O_register
8350 || exp->X_op == O_big)
8351 {
8352 char c = *input_line_pointer;
8353 *input_line_pointer = 0;
8354 as_bad (_("missing or invalid expression `%s'"), save);
8355 *input_line_pointer = c;
8356 }
8357 }
8358 }
8359 else
8360 expression (exp);
8361
8362 intel_syntax = -intel_syntax;
8363
8364 if (intel_syntax)
8365 i386_intel_simplify (exp);
8366
8367 return got_reloc;
8368}
8369
8370static void
8371signed_cons (int size)
8372{
8373 if (flag_code == CODE_64BIT)
8374 cons_sign = 1;
8375 cons (size);
8376 cons_sign = -1;
8377}
8378
8379#ifdef TE_PE
8380static void
8381pe_directive_secrel (int dummy ATTRIBUTE_UNUSED)
8382{
8383 expressionS exp;
8384
8385 do
8386 {
8387 expression (&exp);
8388 if (exp.X_op == O_symbol)
8389 exp.X_op = O_secrel;
8390
8391 emit_expr (&exp, 4);
8392 }
8393 while (*input_line_pointer++ == ',');
8394
8395 input_line_pointer--;
8396 demand_empty_rest_of_line ();
8397}
8398#endif
8399
8400/* Handle Vector operations. */
8401
8402static char *
8403check_VecOperations (char *op_string, char *op_end)
8404{
8405 const reg_entry *mask;
8406 const char *saved;
8407 char *end_op;
8408
8409 while (*op_string
8410 && (op_end == NULL || op_string < op_end))
8411 {
8412 saved = op_string;
8413 if (*op_string == '{')
8414 {
8415 op_string++;
8416
8417 /* Check broadcasts. */
8418 if (strncmp (op_string, "1to", 3) == 0)
8419 {
8420 int bcst_type;
8421
8422 if (i.broadcast)
8423 goto duplicated_vec_op;
8424
8425 op_string += 3;
8426 if (*op_string == '8')
8427 bcst_type = BROADCAST_1TO8;
8428 else if (*op_string == '4')
8429 bcst_type = BROADCAST_1TO4;
8430 else if (*op_string == '2')
8431 bcst_type = BROADCAST_1TO2;
8432 else if (*op_string == '1'
8433 && *(op_string+1) == '6')
8434 {
8435 bcst_type = BROADCAST_1TO16;
8436 op_string++;
8437 }
8438 else
8439 {
8440 as_bad (_("Unsupported broadcast: `%s'"), saved);
8441 return NULL;
8442 }
8443 op_string++;
8444
8445 broadcast_op.type = bcst_type;
8446 broadcast_op.operand = this_operand;
8447 i.broadcast = &broadcast_op;
8448 }
8449 /* Check masking operation. */
8450 else if ((mask = parse_register (op_string, &end_op)) != NULL)
8451 {
8452 /* k0 can't be used for write mask. */
8453 if (!mask->reg_type.bitfield.regmask || mask->reg_num == 0)
8454 {
8455 as_bad (_("`%s%s' can't be used for write mask"),
8456 register_prefix, mask->reg_name);
8457 return NULL;
8458 }
8459
8460 if (!i.mask)
8461 {
8462 mask_op.mask = mask;
8463 mask_op.zeroing = 0;
8464 mask_op.operand = this_operand;
8465 i.mask = &mask_op;
8466 }
8467 else
8468 {
8469 if (i.mask->mask)
8470 goto duplicated_vec_op;
8471
8472 i.mask->mask = mask;
8473
8474 /* Only "{z}" is allowed here. No need to check
8475 zeroing mask explicitly. */
8476 if (i.mask->operand != this_operand)
8477 {
8478 as_bad (_("invalid write mask `%s'"), saved);
8479 return NULL;
8480 }
8481 }
8482
8483 op_string = end_op;
8484 }
8485 /* Check zeroing-flag for masking operation. */
8486 else if (*op_string == 'z')
8487 {
8488 if (!i.mask)
8489 {
8490 mask_op.mask = NULL;
8491 mask_op.zeroing = 1;
8492 mask_op.operand = this_operand;
8493 i.mask = &mask_op;
8494 }
8495 else
8496 {
8497 if (i.mask->zeroing)
8498 {
8499 duplicated_vec_op:
8500 as_bad (_("duplicated `%s'"), saved);
8501 return NULL;
8502 }
8503
8504 i.mask->zeroing = 1;
8505
8506 /* Only "{%k}" is allowed here. No need to check mask
8507 register explicitly. */
8508 if (i.mask->operand != this_operand)
8509 {
8510 as_bad (_("invalid zeroing-masking `%s'"),
8511 saved);
8512 return NULL;
8513 }
8514 }
8515
8516 op_string++;
8517 }
8518 else
8519 goto unknown_vec_op;
8520
8521 if (*op_string != '}')
8522 {
8523 as_bad (_("missing `}' in `%s'"), saved);
8524 return NULL;
8525 }
8526 op_string++;
8527 continue;
8528 }
8529 unknown_vec_op:
8530 /* We don't know this one. */
8531 as_bad (_("unknown vector operation: `%s'"), saved);
8532 return NULL;
8533 }
8534
8535 if (i.mask && i.mask->zeroing && !i.mask->mask)
8536 {
8537 as_bad (_("zeroing-masking only allowed with write mask"));
8538 return NULL;
8539 }
8540
8541 return op_string;
8542}
8543
8544static int
8545i386_immediate (char *imm_start)
8546{
8547 char *save_input_line_pointer;
8548 char *gotfree_input_line;
8549 segT exp_seg = 0;
8550 expressionS *exp;
8551 i386_operand_type types;
8552
8553 operand_type_set (&types, ~0);
8554
8555 if (i.imm_operands == MAX_IMMEDIATE_OPERANDS)
8556 {
8557 as_bad (_("at most %d immediate operands are allowed"),
8558 MAX_IMMEDIATE_OPERANDS);
8559 return 0;
8560 }
8561
8562 exp = &im_expressions[i.imm_operands++];
8563 i.op[this_operand].imms = exp;
8564
8565 if (is_space_char (*imm_start))
8566 ++imm_start;
8567
8568 save_input_line_pointer = input_line_pointer;
8569 input_line_pointer = imm_start;
8570
8571 gotfree_input_line = lex_got (&i.reloc[this_operand], NULL, &types);
8572 if (gotfree_input_line)
8573 input_line_pointer = gotfree_input_line;
8574
8575 exp_seg = expression (exp);
8576
8577 SKIP_WHITESPACE ();
8578
8579 /* Handle vector operations. */
8580 if (*input_line_pointer == '{')
8581 {
8582 input_line_pointer = check_VecOperations (input_line_pointer,
8583 NULL);
8584 if (input_line_pointer == NULL)
8585 return 0;
8586 }
8587
8588 if (*input_line_pointer)
8589 as_bad (_("junk `%s' after expression"), input_line_pointer);
8590
8591 input_line_pointer = save_input_line_pointer;
8592 if (gotfree_input_line)
8593 {
8594 free (gotfree_input_line);
8595
8596 if (exp->X_op == O_constant || exp->X_op == O_register)
8597 exp->X_op = O_illegal;
8598 }
8599
8600 return i386_finalize_immediate (exp_seg, exp, types, imm_start);
8601}
8602
8603static int
8604i386_finalize_immediate (segT exp_seg ATTRIBUTE_UNUSED, expressionS *exp,
8605 i386_operand_type types, const char *imm_start)
8606{
8607 if (exp->X_op == O_absent || exp->X_op == O_illegal || exp->X_op == O_big)
8608 {
8609 if (imm_start)
8610 as_bad (_("missing or invalid immediate expression `%s'"),
8611 imm_start);
8612 return 0;
8613 }
8614 else if (exp->X_op == O_constant)
8615 {
8616 /* Size it properly later. */
8617 i.types[this_operand].bitfield.imm64 = 1;
8618 /* If not 64bit, sign extend val. */
8619 if (flag_code != CODE_64BIT
8620 && (exp->X_add_number & ~(((addressT) 2 << 31) - 1)) == 0)
8621 exp->X_add_number
8622 = (exp->X_add_number ^ ((addressT) 1 << 31)) - ((addressT) 1 << 31);
8623 }
8624#if (defined (OBJ_AOUT) || defined (OBJ_MAYBE_AOUT))
8625 else if (OUTPUT_FLAVOR == bfd_target_aout_flavour
8626 && exp_seg != absolute_section
8627 && exp_seg != text_section
8628 && exp_seg != data_section
8629 && exp_seg != bss_section
8630 && exp_seg != undefined_section
8631 && !bfd_is_com_section (exp_seg))
8632 {
8633 as_bad (_("unimplemented segment %s in operand"), exp_seg->name);
8634 return 0;
8635 }
8636#endif
8637 else if (!intel_syntax && exp_seg == reg_section)
8638 {
8639 if (imm_start)
8640 as_bad (_("illegal immediate register operand %s"), imm_start);
8641 return 0;
8642 }
8643 else
8644 {
8645 /* This is an address. The size of the address will be
8646 determined later, depending on destination register,
8647 suffix, or the default for the section. */
8648 i.types[this_operand].bitfield.imm8 = 1;
8649 i.types[this_operand].bitfield.imm16 = 1;
8650 i.types[this_operand].bitfield.imm32 = 1;
8651 i.types[this_operand].bitfield.imm32s = 1;
8652 i.types[this_operand].bitfield.imm64 = 1;
8653 i.types[this_operand] = operand_type_and (i.types[this_operand],
8654 types);
8655 }
8656
8657 return 1;
8658}
8659
8660static char *
8661i386_scale (char *scale)
8662{
8663 offsetT val;
8664 char *save = input_line_pointer;
8665
8666 input_line_pointer = scale;
8667 val = get_absolute_expression ();
8668
8669 switch (val)
8670 {
8671 case 1:
8672 i.log2_scale_factor = 0;
8673 break;
8674 case 2:
8675 i.log2_scale_factor = 1;
8676 break;
8677 case 4:
8678 i.log2_scale_factor = 2;
8679 break;
8680 case 8:
8681 i.log2_scale_factor = 3;
8682 break;
8683 default:
8684 {
8685 char sep = *input_line_pointer;
8686
8687 *input_line_pointer = '\0';
8688 as_bad (_("expecting scale factor of 1, 2, 4, or 8: got `%s'"),
8689 scale);
8690 *input_line_pointer = sep;
8691 input_line_pointer = save;
8692 return NULL;
8693 }
8694 }
8695 if (i.log2_scale_factor != 0 && i.index_reg == 0)
8696 {
8697 as_warn (_("scale factor of %d without an index register"),
8698 1 << i.log2_scale_factor);
8699 i.log2_scale_factor = 0;
8700 }
8701 scale = input_line_pointer;
8702 input_line_pointer = save;
8703 return scale;
8704}
8705
8706static int
8707i386_displacement (char *disp_start, char *disp_end)
8708{
8709 expressionS *exp;
8710 segT exp_seg = 0;
8711 char *save_input_line_pointer;
8712 char *gotfree_input_line;
8713 int override;
8714 i386_operand_type bigdisp, types = anydisp;
8715 int ret;
8716
8717 if (i.disp_operands == MAX_MEMORY_OPERANDS)
8718 {
8719 as_bad (_("at most %d displacement operands are allowed"),
8720 MAX_MEMORY_OPERANDS);
8721 return 0;
8722 }
8723
8724 operand_type_set (&bigdisp, 0);
8725 if ((i.types[this_operand].bitfield.jumpabsolute)
8726 || (!current_templates->start->opcode_modifier.jump
8727 && !current_templates->start->opcode_modifier.jumpdword))
8728 {
8729 bigdisp.bitfield.disp32 = 1;
8730 override = (i.prefix[ADDR_PREFIX] != 0);
8731 if (flag_code == CODE_64BIT)
8732 {
8733 if (!override)
8734 {
8735 bigdisp.bitfield.disp32s = 1;
8736 bigdisp.bitfield.disp64 = 1;
8737 }
8738 }
8739 else if ((flag_code == CODE_16BIT) ^ override)
8740 {
8741 bigdisp.bitfield.disp32 = 0;
8742 bigdisp.bitfield.disp16 = 1;
8743 }
8744 }
8745 else
8746 {
8747 /* For PC-relative branches, the width of the displacement
8748 is dependent upon data size, not address size. */
8749 override = (i.prefix[DATA_PREFIX] != 0);
8750 if (flag_code == CODE_64BIT)
8751 {
8752 if (override || i.suffix == WORD_MNEM_SUFFIX)
8753 bigdisp.bitfield.disp16 = 1;
8754 else
8755 {
8756 bigdisp.bitfield.disp32 = 1;
8757 bigdisp.bitfield.disp32s = 1;
8758 }
8759 }
8760 else
8761 {
8762 if (!override)
8763 override = (i.suffix == (flag_code != CODE_16BIT
8764 ? WORD_MNEM_SUFFIX
8765 : LONG_MNEM_SUFFIX));
8766 bigdisp.bitfield.disp32 = 1;
8767 if ((flag_code == CODE_16BIT) ^ override)
8768 {
8769 bigdisp.bitfield.disp32 = 0;
8770 bigdisp.bitfield.disp16 = 1;
8771 }
8772 }
8773 }
8774 i.types[this_operand] = operand_type_or (i.types[this_operand],
8775 bigdisp);
8776
8777 exp = &disp_expressions[i.disp_operands];
8778 i.op[this_operand].disps = exp;
8779 i.disp_operands++;
8780 save_input_line_pointer = input_line_pointer;
8781 input_line_pointer = disp_start;
8782 END_STRING_AND_SAVE (disp_end);
8783
8784#ifndef GCC_ASM_O_HACK
8785#define GCC_ASM_O_HACK 0
8786#endif
8787#if GCC_ASM_O_HACK
8788 END_STRING_AND_SAVE (disp_end + 1);
8789 if (i.types[this_operand].bitfield.baseIndex
8790 && displacement_string_end[-1] == '+')
8791 {
8792 /* This hack is to avoid a warning when using the "o"
8793 constraint within gcc asm statements.
8794 For instance:
8795
8796 #define _set_tssldt_desc(n,addr,limit,type) \
8797 __asm__ __volatile__ ( \
8798 "movw %w2,%0\n\t" \
8799 "movw %w1,2+%0\n\t" \
8800 "rorl $16,%1\n\t" \
8801 "movb %b1,4+%0\n\t" \
8802 "movb %4,5+%0\n\t" \
8803 "movb $0,6+%0\n\t" \
8804 "movb %h1,7+%0\n\t" \
8805 "rorl $16,%1" \
8806 : "=o"(*(n)) : "q" (addr), "ri"(limit), "i"(type))
8807
8808 This works great except that the output assembler ends
8809 up looking a bit weird if it turns out that there is
8810 no offset. You end up producing code that looks like:
8811
8812 #APP
8813 movw $235,(%eax)
8814 movw %dx,2+(%eax)
8815 rorl $16,%edx
8816 movb %dl,4+(%eax)
8817 movb $137,5+(%eax)
8818 movb $0,6+(%eax)
8819 movb %dh,7+(%eax)
8820 rorl $16,%edx
8821 #NO_APP
8822
8823 So here we provide the missing zero. */
8824
8825 *displacement_string_end = '0';
8826 }
8827#endif
8828 gotfree_input_line = lex_got (&i.reloc[this_operand], NULL, &types);
8829 if (gotfree_input_line)
8830 input_line_pointer = gotfree_input_line;
8831
8832 exp_seg = expression (exp);
8833
8834 SKIP_WHITESPACE ();
8835 if (*input_line_pointer)
8836 as_bad (_("junk `%s' after expression"), input_line_pointer);
8837#if GCC_ASM_O_HACK
8838 RESTORE_END_STRING (disp_end + 1);
8839#endif
8840 input_line_pointer = save_input_line_pointer;
8841 if (gotfree_input_line)
8842 {
8843 free (gotfree_input_line);
8844
8845 if (exp->X_op == O_constant || exp->X_op == O_register)
8846 exp->X_op = O_illegal;
8847 }
8848
8849 ret = i386_finalize_displacement (exp_seg, exp, types, disp_start);
8850
8851 RESTORE_END_STRING (disp_end);
8852
8853 return ret;
8854}
8855
8856static int
8857i386_finalize_displacement (segT exp_seg ATTRIBUTE_UNUSED, expressionS *exp,
8858 i386_operand_type types, const char *disp_start)
8859{
8860 i386_operand_type bigdisp;
8861 int ret = 1;
8862
8863 /* We do this to make sure that the section symbol is in
8864 the symbol table. We will ultimately change the relocation
8865 to be relative to the beginning of the section. */
8866 if (i.reloc[this_operand] == BFD_RELOC_386_GOTOFF
8867 || i.reloc[this_operand] == BFD_RELOC_X86_64_GOTPCREL
8868 || i.reloc[this_operand] == BFD_RELOC_X86_64_GOTOFF64)
8869 {
8870 if (exp->X_op != O_symbol)
8871 goto inv_disp;
8872
8873 if (S_IS_LOCAL (exp->X_add_symbol)
8874 && S_GET_SEGMENT (exp->X_add_symbol) != undefined_section
8875 && S_GET_SEGMENT (exp->X_add_symbol) != expr_section)
8876 section_symbol (S_GET_SEGMENT (exp->X_add_symbol));
8877 exp->X_op = O_subtract;
8878 exp->X_op_symbol = GOT_symbol;
8879 if (i.reloc[this_operand] == BFD_RELOC_X86_64_GOTPCREL)
8880 i.reloc[this_operand] = BFD_RELOC_32_PCREL;
8881 else if (i.reloc[this_operand] == BFD_RELOC_X86_64_GOTOFF64)
8882 i.reloc[this_operand] = BFD_RELOC_64;
8883 else
8884 i.reloc[this_operand] = BFD_RELOC_32;
8885 }
8886
8887 else if (exp->X_op == O_absent
8888 || exp->X_op == O_illegal
8889 || exp->X_op == O_big)
8890 {
8891 inv_disp:
8892 as_bad (_("missing or invalid displacement expression `%s'"),
8893 disp_start);
8894 ret = 0;
8895 }
8896
8897 else if (flag_code == CODE_64BIT
8898 && !i.prefix[ADDR_PREFIX]
8899 && exp->X_op == O_constant)
8900 {
8901 /* Since displacement is signed extended to 64bit, don't allow
8902 disp32 and turn off disp32s if they are out of range. */
8903 i.types[this_operand].bitfield.disp32 = 0;
8904 if (!fits_in_signed_long (exp->X_add_number))
8905 {
8906 i.types[this_operand].bitfield.disp32s = 0;
8907 if (i.types[this_operand].bitfield.baseindex)
8908 {
8909 as_bad (_("0x%lx out range of signed 32bit displacement"),
8910 (long) exp->X_add_number);
8911 ret = 0;
8912 }
8913 }
8914 }
8915
8916#if (defined (OBJ_AOUT) || defined (OBJ_MAYBE_AOUT))
8917 else if (exp->X_op != O_constant
8918 && OUTPUT_FLAVOR == bfd_target_aout_flavour
8919 && exp_seg != absolute_section
8920 && exp_seg != text_section
8921 && exp_seg != data_section
8922 && exp_seg != bss_section
8923 && exp_seg != undefined_section
8924 && !bfd_is_com_section (exp_seg))
8925 {
8926 as_bad (_("unimplemented segment %s in operand"), exp_seg->name);
8927 ret = 0;
8928 }
8929#endif
8930
8931 /* Check if this is a displacement only operand. */
8932 bigdisp = i.types[this_operand];
8933 bigdisp.bitfield.disp8 = 0;
8934 bigdisp.bitfield.disp16 = 0;
8935 bigdisp.bitfield.disp32 = 0;
8936 bigdisp.bitfield.disp32s = 0;
8937 bigdisp.bitfield.disp64 = 0;
8938 if (operand_type_all_zero (&bigdisp))
8939 i.types[this_operand] = operand_type_and (i.types[this_operand],
8940 types);
8941
8942 return ret;
8943}
8944
8945/* Return the active addressing mode, taking address override and
8946 registers forming the address into consideration. Update the
8947 address override prefix if necessary. */
8948
8949static enum flag_code
8950i386_addressing_mode (void)
8951{
8952 enum flag_code addr_mode;
8953
8954 if (i.prefix[ADDR_PREFIX])
8955 addr_mode = flag_code == CODE_32BIT ? CODE_16BIT : CODE_32BIT;
8956 else
8957 {
8958 addr_mode = flag_code;
8959
8960#if INFER_ADDR_PREFIX
8961 if (i.mem_operands == 0)
8962 {
8963 /* Infer address prefix from the first memory operand. */
8964 const reg_entry *addr_reg = i.base_reg;
8965
8966 if (addr_reg == NULL)
8967 addr_reg = i.index_reg;
8968
8969 if (addr_reg)
8970 {
8971 if (addr_reg->reg_num == RegEip
8972 || addr_reg->reg_num == RegEiz
8973 || addr_reg->reg_type.bitfield.dword)
8974 addr_mode = CODE_32BIT;
8975 else if (flag_code != CODE_64BIT
8976 && addr_reg->reg_type.bitfield.word)
8977 addr_mode = CODE_16BIT;
8978
8979 if (addr_mode != flag_code)
8980 {
8981 i.prefix[ADDR_PREFIX] = ADDR_PREFIX_OPCODE;
8982 i.prefixes += 1;
8983 /* Change the size of any displacement too. At most one
8984 of Disp16 or Disp32 is set.
8985 FIXME. There doesn't seem to be any real need for
8986 separate Disp16 and Disp32 flags. The same goes for
8987 Imm16 and Imm32. Removing them would probably clean
8988 up the code quite a lot. */
8989 if (flag_code != CODE_64BIT
8990 && (i.types[this_operand].bitfield.disp16
8991 || i.types[this_operand].bitfield.disp32))
8992 i.types[this_operand]
8993 = operand_type_xor (i.types[this_operand], disp16_32);
8994 }
8995 }
8996 }
8997#endif
8998 }
8999
9000 return addr_mode;
9001}
9002
9003/* Make sure the memory operand we've been dealt is valid.
9004 Return 1 on success, 0 on a failure. */
9005
9006static int
9007i386_index_check (const char *operand_string)
9008{
9009 const char *kind = "base/index";
9010 enum flag_code addr_mode = i386_addressing_mode ();
9011
9012 if (current_templates->start->opcode_modifier.isstring
9013 && !current_templates->start->opcode_modifier.immext
9014 && (current_templates->end[-1].opcode_modifier.isstring
9015 || i.mem_operands))
9016 {
9017 /* Memory operands of string insns are special in that they only allow
9018 a single register (rDI, rSI, or rBX) as their memory address. */
9019 const reg_entry *expected_reg;
9020 static const char *di_si[][2] =
9021 {
9022 { "esi", "edi" },
9023 { "si", "di" },
9024 { "rsi", "rdi" }
9025 };
9026 static const char *bx[] = { "ebx", "bx", "rbx" };
9027
9028 kind = "string address";
9029
9030 if (current_templates->start->opcode_modifier.repprefixok)
9031 {
9032 i386_operand_type type = current_templates->end[-1].operand_types[0];
9033
9034 if (!type.bitfield.baseindex
9035 || ((!i.mem_operands != !intel_syntax)
9036 && current_templates->end[-1].operand_types[1]
9037 .bitfield.baseindex))
9038 type = current_templates->end[-1].operand_types[1];
9039 expected_reg = hash_find (reg_hash,
9040 di_si[addr_mode][type.bitfield.esseg]);
9041
9042 }
9043 else
9044 expected_reg = hash_find (reg_hash, bx[addr_mode]);
9045
9046 if (i.base_reg != expected_reg
9047 || i.index_reg
9048 || operand_type_check (i.types[this_operand], disp))
9049 {
9050 /* The second memory operand must have the same size as
9051 the first one. */
9052 if (i.mem_operands
9053 && i.base_reg
9054 && !((addr_mode == CODE_64BIT
9055 && i.base_reg->reg_type.bitfield.qword)
9056 || (addr_mode == CODE_32BIT
9057 ? i.base_reg->reg_type.bitfield.dword
9058 : i.base_reg->reg_type.bitfield.word)))
9059 goto bad_address;
9060
9061 as_warn (_("`%s' is not valid here (expected `%c%s%s%c')"),
9062 operand_string,
9063 intel_syntax ? '[' : '(',
9064 register_prefix,
9065 expected_reg->reg_name,
9066 intel_syntax ? ']' : ')');
9067 return 1;
9068 }
9069 else
9070 return 1;
9071
9072bad_address:
9073 as_bad (_("`%s' is not a valid %s expression"),
9074 operand_string, kind);
9075 return 0;
9076 }
9077 else
9078 {
9079 if (addr_mode != CODE_16BIT)
9080 {
9081 /* 32-bit/64-bit checks. */
9082 if ((i.base_reg
9083 && (addr_mode == CODE_64BIT
9084 ? !i.base_reg->reg_type.bitfield.qword
9085 : !i.base_reg->reg_type.bitfield.dword)
9086 && (i.index_reg
9087 || (i.base_reg->reg_num
9088 != (addr_mode == CODE_64BIT ? RegRip : RegEip))))
9089 || (i.index_reg
9090 && !i.index_reg->reg_type.bitfield.xmmword
9091 && !i.index_reg->reg_type.bitfield.ymmword
9092 && !i.index_reg->reg_type.bitfield.zmmword
9093 && ((addr_mode == CODE_64BIT
9094 ? !(i.index_reg->reg_type.bitfield.qword
9095 || i.index_reg->reg_num == RegRiz)
9096 : !(i.index_reg->reg_type.bitfield.dword
9097 || i.index_reg->reg_num == RegEiz))
9098 || !i.index_reg->reg_type.bitfield.baseindex)))
9099 goto bad_address;
9100
9101 /* bndmk, bndldx, and bndstx have special restrictions. */
9102 if (current_templates->start->base_opcode == 0xf30f1b
9103 || (current_templates->start->base_opcode & ~1) == 0x0f1a)
9104 {
9105 /* They cannot use RIP-relative addressing. */
9106 if (i.base_reg && i.base_reg->reg_num == RegRip)
9107 {
9108 as_bad (_("`%s' cannot be used here"), operand_string);
9109 return 0;
9110 }
9111
9112 /* bndldx and bndstx ignore their scale factor. */
9113 if (current_templates->start->base_opcode != 0xf30f1b
9114 && i.log2_scale_factor)
9115 as_warn (_("register scaling is being ignored here"));
9116 }
9117 }
9118 else
9119 {
9120 /* 16-bit checks. */
9121 if ((i.base_reg
9122 && (!i.base_reg->reg_type.bitfield.word
9123 || !i.base_reg->reg_type.bitfield.baseindex))
9124 || (i.index_reg
9125 && (!i.index_reg->reg_type.bitfield.word
9126 || !i.index_reg->reg_type.bitfield.baseindex
9127 || !(i.base_reg
9128 && i.base_reg->reg_num < 6
9129 && i.index_reg->reg_num >= 6
9130 && i.log2_scale_factor == 0))))
9131 goto bad_address;
9132 }
9133 }
9134 return 1;
9135}
9136
9137/* Handle vector immediates. */
9138
9139static int
9140RC_SAE_immediate (const char *imm_start)
9141{
9142 unsigned int match_found, j;
9143 const char *pstr = imm_start;
9144 expressionS *exp;
9145
9146 if (*pstr != '{')
9147 return 0;
9148
9149 pstr++;
9150 match_found = 0;
9151 for (j = 0; j < ARRAY_SIZE (RC_NamesTable); j++)
9152 {
9153 if (!strncmp (pstr, RC_NamesTable[j].name, RC_NamesTable[j].len))
9154 {
9155 if (!i.rounding)
9156 {
9157 rc_op.type = RC_NamesTable[j].type;
9158 rc_op.operand = this_operand;
9159 i.rounding = &rc_op;
9160 }
9161 else
9162 {
9163 as_bad (_("duplicated `%s'"), imm_start);
9164 return 0;
9165 }
9166 pstr += RC_NamesTable[j].len;
9167 match_found = 1;
9168 break;
9169 }
9170 }
9171 if (!match_found)
9172 return 0;
9173
9174 if (*pstr++ != '}')
9175 {
9176 as_bad (_("Missing '}': '%s'"), imm_start);
9177 return 0;
9178 }
9179 /* RC/SAE immediate string should contain nothing more. */;
9180 if (*pstr != 0)
9181 {
9182 as_bad (_("Junk after '}': '%s'"), imm_start);
9183 return 0;
9184 }
9185
9186 exp = &im_expressions[i.imm_operands++];
9187 i.op[this_operand].imms = exp;
9188
9189 exp->X_op = O_constant;
9190 exp->X_add_number = 0;
9191 exp->X_add_symbol = (symbolS *) 0;
9192 exp->X_op_symbol = (symbolS *) 0;
9193
9194 i.types[this_operand].bitfield.imm8 = 1;
9195 return 1;
9196}
9197
9198/* Only string instructions can have a second memory operand, so
9199 reduce current_templates to just those if it contains any. */
9200static int
9201maybe_adjust_templates (void)
9202{
9203 const insn_template *t;
9204
9205 gas_assert (i.mem_operands == 1);
9206
9207 for (t = current_templates->start; t < current_templates->end; ++t)
9208 if (t->opcode_modifier.isstring)
9209 break;
9210
9211 if (t < current_templates->end)
9212 {
9213 static templates aux_templates;
9214 bfd_boolean recheck;
9215
9216 aux_templates.start = t;
9217 for (; t < current_templates->end; ++t)
9218 if (!t->opcode_modifier.isstring)
9219 break;
9220 aux_templates.end = t;
9221
9222 /* Determine whether to re-check the first memory operand. */
9223 recheck = (aux_templates.start != current_templates->start
9224 || t != current_templates->end);
9225
9226 current_templates = &aux_templates;
9227
9228 if (recheck)
9229 {
9230 i.mem_operands = 0;
9231 if (i.memop1_string != NULL
9232 && i386_index_check (i.memop1_string) == 0)
9233 return 0;
9234 i.mem_operands = 1;
9235 }
9236 }
9237
9238 return 1;
9239}
9240
9241/* Parse OPERAND_STRING into the i386_insn structure I. Returns zero
9242 on error. */
9243
9244static int
9245i386_att_operand (char *operand_string)
9246{
9247 const reg_entry *r;
9248 char *end_op;
9249 char *op_string = operand_string;
9250
9251 if (is_space_char (*op_string))
9252 ++op_string;
9253
9254 /* We check for an absolute prefix (differentiating,
9255 for example, 'jmp pc_relative_label' from 'jmp *absolute_label'. */
9256 if (*op_string == ABSOLUTE_PREFIX)
9257 {
9258 ++op_string;
9259 if (is_space_char (*op_string))
9260 ++op_string;
9261 i.types[this_operand].bitfield.jumpabsolute = 1;
9262 }
9263
9264 /* Check if operand is a register. */
9265 if ((r = parse_register (op_string, &end_op)) != NULL)
9266 {
9267 i386_operand_type temp;
9268
9269 /* Check for a segment override by searching for ':' after a
9270 segment register. */
9271 op_string = end_op;
9272 if (is_space_char (*op_string))
9273 ++op_string;
9274 if (*op_string == ':'
9275 && (r->reg_type.bitfield.sreg2
9276 || r->reg_type.bitfield.sreg3))
9277 {
9278 switch (r->reg_num)
9279 {
9280 case 0:
9281 i.seg[i.mem_operands] = &es;
9282 break;
9283 case 1:
9284 i.seg[i.mem_operands] = &cs;
9285 break;
9286 case 2:
9287 i.seg[i.mem_operands] = &ss;
9288 break;
9289 case 3:
9290 i.seg[i.mem_operands] = &ds;
9291 break;
9292 case 4:
9293 i.seg[i.mem_operands] = &fs;
9294 break;
9295 case 5:
9296 i.seg[i.mem_operands] = &gs;
9297 break;
9298 }
9299
9300 /* Skip the ':' and whitespace. */
9301 ++op_string;
9302 if (is_space_char (*op_string))
9303 ++op_string;
9304
9305 if (!is_digit_char (*op_string)
9306 && !is_identifier_char (*op_string)
9307 && *op_string != '('
9308 && *op_string != ABSOLUTE_PREFIX)
9309 {
9310 as_bad (_("bad memory operand `%s'"), op_string);
9311 return 0;
9312 }
9313 /* Handle case of %es:*foo. */
9314 if (*op_string == ABSOLUTE_PREFIX)
9315 {
9316 ++op_string;
9317 if (is_space_char (*op_string))
9318 ++op_string;
9319 i.types[this_operand].bitfield.jumpabsolute = 1;
9320 }
9321 goto do_memory_reference;
9322 }
9323
9324 /* Handle vector operations. */
9325 if (*op_string == '{')
9326 {
9327 op_string = check_VecOperations (op_string, NULL);
9328 if (op_string == NULL)
9329 return 0;
9330 }
9331
9332 if (*op_string)
9333 {
9334 as_bad (_("junk `%s' after register"), op_string);
9335 return 0;
9336 }
9337 temp = r->reg_type;
9338 temp.bitfield.baseindex = 0;
9339 i.types[this_operand] = operand_type_or (i.types[this_operand],
9340 temp);
9341 i.types[this_operand].bitfield.unspecified = 0;
9342 i.op[this_operand].regs = r;
9343 i.reg_operands++;
9344 }
9345 else if (*op_string == REGISTER_PREFIX)
9346 {
9347 as_bad (_("bad register name `%s'"), op_string);
9348 return 0;
9349 }
9350 else if (*op_string == IMMEDIATE_PREFIX)
9351 {
9352 ++op_string;
9353 if (i.types[this_operand].bitfield.jumpabsolute)
9354 {
9355 as_bad (_("immediate operand illegal with absolute jump"));
9356 return 0;
9357 }
9358 if (!i386_immediate (op_string))
9359 return 0;
9360 }
9361 else if (RC_SAE_immediate (operand_string))
9362 {
9363 /* If it is a RC or SAE immediate, do nothing. */
9364 ;
9365 }
9366 else if (is_digit_char (*op_string)
9367 || is_identifier_char (*op_string)
9368 || *op_string == '"'
9369 || *op_string == '(')
9370 {
9371 /* This is a memory reference of some sort. */
9372 char *base_string;
9373
9374 /* Start and end of displacement string expression (if found). */
9375 char *displacement_string_start;
9376 char *displacement_string_end;
9377 char *vop_start;
9378
9379 do_memory_reference:
9380 if (i.mem_operands == 1 && !maybe_adjust_templates ())
9381 return 0;
9382 if ((i.mem_operands == 1
9383 && !current_templates->start->opcode_modifier.isstring)
9384 || i.mem_operands == 2)
9385 {
9386 as_bad (_("too many memory references for `%s'"),
9387 current_templates->start->name);
9388 return 0;
9389 }
9390
9391 /* Check for base index form. We detect the base index form by
9392 looking for an ')' at the end of the operand, searching
9393 for the '(' matching it, and finding a REGISTER_PREFIX or ','
9394 after the '('. */
9395 base_string = op_string + strlen (op_string);
9396
9397 /* Handle vector operations. */
9398 vop_start = strchr (op_string, '{');
9399 if (vop_start && vop_start < base_string)
9400 {
9401 if (check_VecOperations (vop_start, base_string) == NULL)
9402 return 0;
9403 base_string = vop_start;
9404 }
9405
9406 --base_string;
9407 if (is_space_char (*base_string))
9408 --base_string;
9409
9410 /* If we only have a displacement, set-up for it to be parsed later. */
9411 displacement_string_start = op_string;
9412 displacement_string_end = base_string + 1;
9413
9414 if (*base_string == ')')
9415 {
9416 char *temp_string;
9417 unsigned int parens_balanced = 1;
9418 /* We've already checked that the number of left & right ()'s are
9419 equal, so this loop will not be infinite. */
9420 do
9421 {
9422 base_string--;
9423 if (*base_string == ')')
9424 parens_balanced++;
9425 if (*base_string == '(')
9426 parens_balanced--;
9427 }
9428 while (parens_balanced);
9429
9430 temp_string = base_string;
9431
9432 /* Skip past '(' and whitespace. */
9433 ++base_string;
9434 if (is_space_char (*base_string))
9435 ++base_string;
9436
9437 if (*base_string == ','
9438 || ((i.base_reg = parse_register (base_string, &end_op))
9439 != NULL))
9440 {
9441 displacement_string_end = temp_string;
9442
9443 i.types[this_operand].bitfield.baseindex = 1;
9444
9445 if (i.base_reg)
9446 {
9447 base_string = end_op;
9448 if (is_space_char (*base_string))
9449 ++base_string;
9450 }
9451
9452 /* There may be an index reg or scale factor here. */
9453 if (*base_string == ',')
9454 {
9455 ++base_string;
9456 if (is_space_char (*base_string))
9457 ++base_string;
9458
9459 if ((i.index_reg = parse_register (base_string, &end_op))
9460 != NULL)
9461 {
9462 base_string = end_op;
9463 if (is_space_char (*base_string))
9464 ++base_string;
9465 if (*base_string == ',')
9466 {
9467 ++base_string;
9468 if (is_space_char (*base_string))
9469 ++base_string;
9470 }
9471 else if (*base_string != ')')
9472 {
9473 as_bad (_("expecting `,' or `)' "
9474 "after index register in `%s'"),
9475 operand_string);
9476 return 0;
9477 }
9478 }
9479 else if (*base_string == REGISTER_PREFIX)
9480 {
9481 end_op = strchr (base_string, ',');
9482 if (end_op)
9483 *end_op = '\0';
9484 as_bad (_("bad register name `%s'"), base_string);
9485 return 0;
9486 }
9487
9488 /* Check for scale factor. */
9489 if (*base_string != ')')
9490 {
9491 char *end_scale = i386_scale (base_string);
9492
9493 if (!end_scale)
9494 return 0;
9495
9496 base_string = end_scale;
9497 if (is_space_char (*base_string))
9498 ++base_string;
9499 if (*base_string != ')')
9500 {
9501 as_bad (_("expecting `)' "
9502 "after scale factor in `%s'"),
9503 operand_string);
9504 return 0;
9505 }
9506 }
9507 else if (!i.index_reg)
9508 {
9509 as_bad (_("expecting index register or scale factor "
9510 "after `,'; got '%c'"),
9511 *base_string);
9512 return 0;
9513 }
9514 }
9515 else if (*base_string != ')')
9516 {
9517 as_bad (_("expecting `,' or `)' "
9518 "after base register in `%s'"),
9519 operand_string);
9520 return 0;
9521 }
9522 }
9523 else if (*base_string == REGISTER_PREFIX)
9524 {
9525 end_op = strchr (base_string, ',');
9526 if (end_op)
9527 *end_op = '\0';
9528 as_bad (_("bad register name `%s'"), base_string);
9529 return 0;
9530 }
9531 }
9532
9533 /* If there's an expression beginning the operand, parse it,
9534 assuming displacement_string_start and
9535 displacement_string_end are meaningful. */
9536 if (displacement_string_start != displacement_string_end)
9537 {
9538 if (!i386_displacement (displacement_string_start,
9539 displacement_string_end))
9540 return 0;
9541 }
9542
9543 /* Special case for (%dx) while doing input/output op. */
9544 if (i.base_reg
9545 && operand_type_equal (&i.base_reg->reg_type,
9546 &reg16_inoutportreg)
9547 && i.index_reg == 0
9548 && i.log2_scale_factor == 0
9549 && i.seg[i.mem_operands] == 0
9550 && !operand_type_check (i.types[this_operand], disp))
9551 {
9552 i.types[this_operand] = inoutportreg;
9553 return 1;
9554 }
9555
9556 if (i386_index_check (operand_string) == 0)
9557 return 0;
9558 i.types[this_operand].bitfield.mem = 1;
9559 if (i.mem_operands == 0)
9560 i.memop1_string = xstrdup (operand_string);
9561 i.mem_operands++;
9562 }
9563 else
9564 {
9565 /* It's not a memory operand; argh! */
9566 as_bad (_("invalid char %s beginning operand %d `%s'"),
9567 output_invalid (*op_string),
9568 this_operand + 1,
9569 op_string);
9570 return 0;
9571 }
9572 return 1; /* Normal return. */
9573}
9574\f
9575/* Calculate the maximum variable size (i.e., excluding fr_fix)
9576 that an rs_machine_dependent frag may reach. */
9577
9578unsigned int
9579i386_frag_max_var (fragS *frag)
9580{
9581 /* The only relaxable frags are for jumps.
9582 Unconditional jumps can grow by 4 bytes and others by 5 bytes. */
9583 gas_assert (frag->fr_type == rs_machine_dependent);
9584 return TYPE_FROM_RELAX_STATE (frag->fr_subtype) == UNCOND_JUMP ? 4 : 5;
9585}
9586
9587#if defined (OBJ_ELF) || defined (OBJ_MAYBE_ELF)
9588static int
9589elf_symbol_resolved_in_segment_p (symbolS *fr_symbol, offsetT fr_var)
9590{
9591 /* STT_GNU_IFUNC symbol must go through PLT. */
9592 if ((symbol_get_bfdsym (fr_symbol)->flags
9593 & BSF_GNU_INDIRECT_FUNCTION) != 0)
9594 return 0;
9595
9596 if (!S_IS_EXTERNAL (fr_symbol))
9597 /* Symbol may be weak or local. */
9598 return !S_IS_WEAK (fr_symbol);
9599
9600 /* Global symbols with non-default visibility can't be preempted. */
9601 if (ELF_ST_VISIBILITY (S_GET_OTHER (fr_symbol)) != STV_DEFAULT)
9602 return 1;
9603
9604 if (fr_var != NO_RELOC)
9605 switch ((enum bfd_reloc_code_real) fr_var)
9606 {
9607 case BFD_RELOC_386_PLT32:
9608 case BFD_RELOC_X86_64_PLT32:
9609 /* Symbol with PLT relocation may be preempted. */
9610 return 0;
9611 default:
9612 abort ();
9613 }
9614
9615 /* Global symbols with default visibility in a shared library may be
9616 preempted by another definition. */
9617 return !shared;
9618}
9619#endif
9620
9621/* md_estimate_size_before_relax()
9622
9623 Called just before relax() for rs_machine_dependent frags. The x86
9624 assembler uses these frags to handle variable size jump
9625 instructions.
9626
9627 Any symbol that is now undefined will not become defined.
9628 Return the correct fr_subtype in the frag.
9629 Return the initial "guess for variable size of frag" to caller.
9630 The guess is actually the growth beyond the fixed part. Whatever
9631 we do to grow the fixed or variable part contributes to our
9632 returned value. */
9633
9634int
9635md_estimate_size_before_relax (fragS *fragP, segT segment)
9636{
9637 /* We've already got fragP->fr_subtype right; all we have to do is
9638 check for un-relaxable symbols. On an ELF system, we can't relax
9639 an externally visible symbol, because it may be overridden by a
9640 shared library. */
9641 if (S_GET_SEGMENT (fragP->fr_symbol) != segment
9642#if defined (OBJ_ELF) || defined (OBJ_MAYBE_ELF)
9643 || (IS_ELF
9644 && !elf_symbol_resolved_in_segment_p (fragP->fr_symbol,
9645 fragP->fr_var))
9646#endif
9647#if defined (OBJ_COFF) && defined (TE_PE)
9648 || (OUTPUT_FLAVOR == bfd_target_coff_flavour
9649 && S_IS_WEAK (fragP->fr_symbol))
9650#endif
9651 )
9652 {
9653 /* Symbol is undefined in this segment, or we need to keep a
9654 reloc so that weak symbols can be overridden. */
9655 int size = (fragP->fr_subtype & CODE16) ? 2 : 4;
9656 enum bfd_reloc_code_real reloc_type;
9657 unsigned char *opcode;
9658 int old_fr_fix;
9659
9660 if (fragP->fr_var != NO_RELOC)
9661 reloc_type = (enum bfd_reloc_code_real) fragP->fr_var;
9662 else if (size == 2)
9663 reloc_type = BFD_RELOC_16_PCREL;
9664#if defined (OBJ_ELF) || defined (OBJ_MAYBE_ELF)
9665 else if (need_plt32_p (fragP->fr_symbol))
9666 reloc_type = BFD_RELOC_X86_64_PLT32;
9667#endif
9668 else
9669 reloc_type = BFD_RELOC_32_PCREL;
9670
9671 old_fr_fix = fragP->fr_fix;
9672 opcode = (unsigned char *) fragP->fr_opcode;
9673
9674 switch (TYPE_FROM_RELAX_STATE (fragP->fr_subtype))
9675 {
9676 case UNCOND_JUMP:
9677 /* Make jmp (0xeb) a (d)word displacement jump. */
9678 opcode[0] = 0xe9;
9679 fragP->fr_fix += size;
9680 fix_new (fragP, old_fr_fix, size,
9681 fragP->fr_symbol,
9682 fragP->fr_offset, 1,
9683 reloc_type);
9684 break;
9685
9686 case COND_JUMP86:
9687 if (size == 2
9688 && (!no_cond_jump_promotion || fragP->fr_var != NO_RELOC))
9689 {
9690 /* Negate the condition, and branch past an
9691 unconditional jump. */
9692 opcode[0] ^= 1;
9693 opcode[1] = 3;
9694 /* Insert an unconditional jump. */
9695 opcode[2] = 0xe9;
9696 /* We added two extra opcode bytes, and have a two byte
9697 offset. */
9698 fragP->fr_fix += 2 + 2;
9699 fix_new (fragP, old_fr_fix + 2, 2,
9700 fragP->fr_symbol,
9701 fragP->fr_offset, 1,
9702 reloc_type);
9703 break;
9704 }
9705 /* Fall through. */
9706
9707 case COND_JUMP:
9708 if (no_cond_jump_promotion && fragP->fr_var == NO_RELOC)
9709 {
9710 fixS *fixP;
9711
9712 fragP->fr_fix += 1;
9713 fixP = fix_new (fragP, old_fr_fix, 1,
9714 fragP->fr_symbol,
9715 fragP->fr_offset, 1,
9716 BFD_RELOC_8_PCREL);
9717 fixP->fx_signed = 1;
9718 break;
9719 }
9720
9721 /* This changes the byte-displacement jump 0x7N
9722 to the (d)word-displacement jump 0x0f,0x8N. */
9723 opcode[1] = opcode[0] + 0x10;
9724 opcode[0] = TWO_BYTE_OPCODE_ESCAPE;
9725 /* We've added an opcode byte. */
9726 fragP->fr_fix += 1 + size;
9727 fix_new (fragP, old_fr_fix + 1, size,
9728 fragP->fr_symbol,
9729 fragP->fr_offset, 1,
9730 reloc_type);
9731 break;
9732
9733 default:
9734 BAD_CASE (fragP->fr_subtype);
9735 break;
9736 }
9737 frag_wane (fragP);
9738 return fragP->fr_fix - old_fr_fix;
9739 }
9740
9741 /* Guess size depending on current relax state. Initially the relax
9742 state will correspond to a short jump and we return 1, because
9743 the variable part of the frag (the branch offset) is one byte
9744 long. However, we can relax a section more than once and in that
9745 case we must either set fr_subtype back to the unrelaxed state,
9746 or return the value for the appropriate branch. */
9747 return md_relax_table[fragP->fr_subtype].rlx_length;
9748}
9749
9750/* Called after relax() is finished.
9751
9752 In: Address of frag.
9753 fr_type == rs_machine_dependent.
9754 fr_subtype is what the address relaxed to.
9755
9756 Out: Any fixSs and constants are set up.
9757 Caller will turn frag into a ".space 0". */
9758
9759void
9760md_convert_frag (bfd *abfd ATTRIBUTE_UNUSED, segT sec ATTRIBUTE_UNUSED,
9761 fragS *fragP)
9762{
9763 unsigned char *opcode;
9764 unsigned char *where_to_put_displacement = NULL;
9765 offsetT target_address;
9766 offsetT opcode_address;
9767 unsigned int extension = 0;
9768 offsetT displacement_from_opcode_start;
9769
9770 opcode = (unsigned char *) fragP->fr_opcode;
9771
9772 /* Address we want to reach in file space. */
9773 target_address = S_GET_VALUE (fragP->fr_symbol) + fragP->fr_offset;
9774
9775 /* Address opcode resides at in file space. */
9776 opcode_address = fragP->fr_address + fragP->fr_fix;
9777
9778 /* Displacement from opcode start to fill into instruction. */
9779 displacement_from_opcode_start = target_address - opcode_address;
9780
9781 if ((fragP->fr_subtype & BIG) == 0)
9782 {
9783 /* Don't have to change opcode. */
9784 extension = 1; /* 1 opcode + 1 displacement */
9785 where_to_put_displacement = &opcode[1];
9786 }
9787 else
9788 {
9789 if (no_cond_jump_promotion
9790 && TYPE_FROM_RELAX_STATE (fragP->fr_subtype) != UNCOND_JUMP)
9791 as_warn_where (fragP->fr_file, fragP->fr_line,
9792 _("long jump required"));
9793
9794 switch (fragP->fr_subtype)
9795 {
9796 case ENCODE_RELAX_STATE (UNCOND_JUMP, BIG):
9797 extension = 4; /* 1 opcode + 4 displacement */
9798 opcode[0] = 0xe9;
9799 where_to_put_displacement = &opcode[1];
9800 break;
9801
9802 case ENCODE_RELAX_STATE (UNCOND_JUMP, BIG16):
9803 extension = 2; /* 1 opcode + 2 displacement */
9804 opcode[0] = 0xe9;
9805 where_to_put_displacement = &opcode[1];
9806 break;
9807
9808 case ENCODE_RELAX_STATE (COND_JUMP, BIG):
9809 case ENCODE_RELAX_STATE (COND_JUMP86, BIG):
9810 extension = 5; /* 2 opcode + 4 displacement */
9811 opcode[1] = opcode[0] + 0x10;
9812 opcode[0] = TWO_BYTE_OPCODE_ESCAPE;
9813 where_to_put_displacement = &opcode[2];
9814 break;
9815
9816 case ENCODE_RELAX_STATE (COND_JUMP, BIG16):
9817 extension = 3; /* 2 opcode + 2 displacement */
9818 opcode[1] = opcode[0] + 0x10;
9819 opcode[0] = TWO_BYTE_OPCODE_ESCAPE;
9820 where_to_put_displacement = &opcode[2];
9821 break;
9822
9823 case ENCODE_RELAX_STATE (COND_JUMP86, BIG16):
9824 extension = 4;
9825 opcode[0] ^= 1;
9826 opcode[1] = 3;
9827 opcode[2] = 0xe9;
9828 where_to_put_displacement = &opcode[3];
9829 break;
9830
9831 default:
9832 BAD_CASE (fragP->fr_subtype);
9833 break;
9834 }
9835 }
9836
9837 /* If size if less then four we are sure that the operand fits,
9838 but if it's 4, then it could be that the displacement is larger
9839 then -/+ 2GB. */
9840 if (DISP_SIZE_FROM_RELAX_STATE (fragP->fr_subtype) == 4
9841 && object_64bit
9842 && ((addressT) (displacement_from_opcode_start - extension
9843 + ((addressT) 1 << 31))
9844 > (((addressT) 2 << 31) - 1)))
9845 {
9846 as_bad_where (fragP->fr_file, fragP->fr_line,
9847 _("jump target out of range"));
9848 /* Make us emit 0. */
9849 displacement_from_opcode_start = extension;
9850 }
9851 /* Now put displacement after opcode. */
9852 md_number_to_chars ((char *) where_to_put_displacement,
9853 (valueT) (displacement_from_opcode_start - extension),
9854 DISP_SIZE_FROM_RELAX_STATE (fragP->fr_subtype));
9855 fragP->fr_fix += extension;
9856}
9857\f
9858/* Apply a fixup (fixP) to segment data, once it has been determined
9859 by our caller that we have all the info we need to fix it up.
9860
9861 Parameter valP is the pointer to the value of the bits.
9862
9863 On the 386, immediates, displacements, and data pointers are all in
9864 the same (little-endian) format, so we don't need to care about which
9865 we are handling. */
9866
9867void
9868md_apply_fix (fixS *fixP, valueT *valP, segT seg ATTRIBUTE_UNUSED)
9869{
9870 char *p = fixP->fx_where + fixP->fx_frag->fr_literal;
9871 valueT value = *valP;
9872
9873#if !defined (TE_Mach)
9874 if (fixP->fx_pcrel)
9875 {
9876 switch (fixP->fx_r_type)
9877 {
9878 default:
9879 break;
9880
9881 case BFD_RELOC_64:
9882 fixP->fx_r_type = BFD_RELOC_64_PCREL;
9883 break;
9884 case BFD_RELOC_32:
9885 case BFD_RELOC_X86_64_32S:
9886 fixP->fx_r_type = BFD_RELOC_32_PCREL;
9887 break;
9888 case BFD_RELOC_16:
9889 fixP->fx_r_type = BFD_RELOC_16_PCREL;
9890 break;
9891 case BFD_RELOC_8:
9892 fixP->fx_r_type = BFD_RELOC_8_PCREL;
9893 break;
9894 }
9895 }
9896
9897 if (fixP->fx_addsy != NULL
9898 && (fixP->fx_r_type == BFD_RELOC_32_PCREL
9899 || fixP->fx_r_type == BFD_RELOC_64_PCREL
9900 || fixP->fx_r_type == BFD_RELOC_16_PCREL
9901 || fixP->fx_r_type == BFD_RELOC_8_PCREL)
9902 && !use_rela_relocations)
9903 {
9904 /* This is a hack. There should be a better way to handle this.
9905 This covers for the fact that bfd_install_relocation will
9906 subtract the current location (for partial_inplace, PC relative
9907 relocations); see more below. */
9908#ifndef OBJ_AOUT
9909 if (IS_ELF
9910#ifdef TE_PE
9911 || OUTPUT_FLAVOR == bfd_target_coff_flavour
9912#endif
9913 )
9914 value += fixP->fx_where + fixP->fx_frag->fr_address;
9915#endif
9916#if defined (OBJ_ELF) || defined (OBJ_MAYBE_ELF)
9917 if (IS_ELF)
9918 {
9919 segT sym_seg = S_GET_SEGMENT (fixP->fx_addsy);
9920
9921 if ((sym_seg == seg
9922 || (symbol_section_p (fixP->fx_addsy)
9923 && sym_seg != absolute_section))
9924 && !generic_force_reloc (fixP))
9925 {
9926 /* Yes, we add the values in twice. This is because
9927 bfd_install_relocation subtracts them out again. I think
9928 bfd_install_relocation is broken, but I don't dare change
9929 it. FIXME. */
9930 value += fixP->fx_where + fixP->fx_frag->fr_address;
9931 }
9932 }
9933#endif
9934#if defined (OBJ_COFF) && defined (TE_PE)
9935 /* For some reason, the PE format does not store a
9936 section address offset for a PC relative symbol. */
9937 if (S_GET_SEGMENT (fixP->fx_addsy) != seg
9938 || S_IS_WEAK (fixP->fx_addsy))
9939 value += md_pcrel_from (fixP);
9940#endif
9941 }
9942#if defined (OBJ_COFF) && defined (TE_PE)
9943 if (fixP->fx_addsy != NULL
9944 && S_IS_WEAK (fixP->fx_addsy)
9945 /* PR 16858: Do not modify weak function references. */
9946 && ! fixP->fx_pcrel)
9947 {
9948#if !defined (TE_PEP)
9949 /* For x86 PE weak function symbols are neither PC-relative
9950 nor do they set S_IS_FUNCTION. So the only reliable way
9951 to detect them is to check the flags of their containing
9952 section. */
9953 if (S_GET_SEGMENT (fixP->fx_addsy) != NULL
9954 && S_GET_SEGMENT (fixP->fx_addsy)->flags & SEC_CODE)
9955 ;
9956 else
9957#endif
9958 value -= S_GET_VALUE (fixP->fx_addsy);
9959 }
9960#endif
9961
9962 /* Fix a few things - the dynamic linker expects certain values here,
9963 and we must not disappoint it. */
9964#if defined (OBJ_ELF) || defined (OBJ_MAYBE_ELF)
9965 if (IS_ELF && fixP->fx_addsy)
9966 switch (fixP->fx_r_type)
9967 {
9968 case BFD_RELOC_386_PLT32:
9969 case BFD_RELOC_X86_64_PLT32:
9970 /* Make the jump instruction point to the address of the operand. At
9971 runtime we merely add the offset to the actual PLT entry. */
9972 value = -4;
9973 break;
9974
9975 case BFD_RELOC_386_TLS_GD:
9976 case BFD_RELOC_386_TLS_LDM:
9977 case BFD_RELOC_386_TLS_IE_32:
9978 case BFD_RELOC_386_TLS_IE:
9979 case BFD_RELOC_386_TLS_GOTIE:
9980 case BFD_RELOC_386_TLS_GOTDESC:
9981 case BFD_RELOC_X86_64_TLSGD:
9982 case BFD_RELOC_X86_64_TLSLD:
9983 case BFD_RELOC_X86_64_GOTTPOFF:
9984 case BFD_RELOC_X86_64_GOTPC32_TLSDESC:
9985 value = 0; /* Fully resolved at runtime. No addend. */
9986 /* Fallthrough */
9987 case BFD_RELOC_386_TLS_LE:
9988 case BFD_RELOC_386_TLS_LDO_32:
9989 case BFD_RELOC_386_TLS_LE_32:
9990 case BFD_RELOC_X86_64_DTPOFF32:
9991 case BFD_RELOC_X86_64_DTPOFF64:
9992 case BFD_RELOC_X86_64_TPOFF32:
9993 case BFD_RELOC_X86_64_TPOFF64:
9994 S_SET_THREAD_LOCAL (fixP->fx_addsy);
9995 break;
9996
9997 case BFD_RELOC_386_TLS_DESC_CALL:
9998 case BFD_RELOC_X86_64_TLSDESC_CALL:
9999 value = 0; /* Fully resolved at runtime. No addend. */
10000 S_SET_THREAD_LOCAL (fixP->fx_addsy);
10001 fixP->fx_done = 0;
10002 return;
10003
10004 case BFD_RELOC_VTABLE_INHERIT:
10005 case BFD_RELOC_VTABLE_ENTRY:
10006 fixP->fx_done = 0;
10007 return;
10008
10009 default:
10010 break;
10011 }
10012#endif /* defined (OBJ_ELF) || defined (OBJ_MAYBE_ELF) */
10013 *valP = value;
10014#endif /* !defined (TE_Mach) */
10015
10016 /* Are we finished with this relocation now? */
10017 if (fixP->fx_addsy == NULL)
10018 fixP->fx_done = 1;
10019#if defined (OBJ_COFF) && defined (TE_PE)
10020 else if (fixP->fx_addsy != NULL && S_IS_WEAK (fixP->fx_addsy))
10021 {
10022 fixP->fx_done = 0;
10023 /* Remember value for tc_gen_reloc. */
10024 fixP->fx_addnumber = value;
10025 /* Clear out the frag for now. */
10026 value = 0;
10027 }
10028#endif
10029 else if (use_rela_relocations)
10030 {
10031 fixP->fx_no_overflow = 1;
10032 /* Remember value for tc_gen_reloc. */
10033 fixP->fx_addnumber = value;
10034 value = 0;
10035 }
10036
10037 md_number_to_chars (p, value, fixP->fx_size);
10038}
10039\f
10040const char *
10041md_atof (int type, char *litP, int *sizeP)
10042{
10043 /* This outputs the LITTLENUMs in REVERSE order;
10044 in accord with the bigendian 386. */
10045 return ieee_md_atof (type, litP, sizeP, FALSE);
10046}
10047\f
10048static char output_invalid_buf[sizeof (unsigned char) * 2 + 6];
10049
10050static char *
10051output_invalid (int c)
10052{
10053 if (ISPRINT (c))
10054 snprintf (output_invalid_buf, sizeof (output_invalid_buf),
10055 "'%c'", c);
10056 else
10057 snprintf (output_invalid_buf, sizeof (output_invalid_buf),
10058 "(0x%x)", (unsigned char) c);
10059 return output_invalid_buf;
10060}
10061
10062/* REG_STRING starts *before* REGISTER_PREFIX. */
10063
10064static const reg_entry *
10065parse_real_register (char *reg_string, char **end_op)
10066{
10067 char *s = reg_string;
10068 char *p;
10069 char reg_name_given[MAX_REG_NAME_SIZE + 1];
10070 const reg_entry *r;
10071
10072 /* Skip possible REGISTER_PREFIX and possible whitespace. */
10073 if (*s == REGISTER_PREFIX)
10074 ++s;
10075
10076 if (is_space_char (*s))
10077 ++s;
10078
10079 p = reg_name_given;
10080 while ((*p++ = register_chars[(unsigned char) *s]) != '\0')
10081 {
10082 if (p >= reg_name_given + MAX_REG_NAME_SIZE)
10083 return (const reg_entry *) NULL;
10084 s++;
10085 }
10086
10087 /* For naked regs, make sure that we are not dealing with an identifier.
10088 This prevents confusing an identifier like `eax_var' with register
10089 `eax'. */
10090 if (allow_naked_reg && identifier_chars[(unsigned char) *s])
10091 return (const reg_entry *) NULL;
10092
10093 *end_op = s;
10094
10095 r = (const reg_entry *) hash_find (reg_hash, reg_name_given);
10096
10097 /* Handle floating point regs, allowing spaces in the (i) part. */
10098 if (r == i386_regtab /* %st is first entry of table */)
10099 {
10100 if (is_space_char (*s))
10101 ++s;
10102 if (*s == '(')
10103 {
10104 ++s;
10105 if (is_space_char (*s))
10106 ++s;
10107 if (*s >= '0' && *s <= '7')
10108 {
10109 int fpr = *s - '0';
10110 ++s;
10111 if (is_space_char (*s))
10112 ++s;
10113 if (*s == ')')
10114 {
10115 *end_op = s + 1;
10116 r = (const reg_entry *) hash_find (reg_hash, "st(0)");
10117 know (r);
10118 return r + fpr;
10119 }
10120 }
10121 /* We have "%st(" then garbage. */
10122 return (const reg_entry *) NULL;
10123 }
10124 }
10125
10126 if (r == NULL || allow_pseudo_reg)
10127 return r;
10128
10129 if (operand_type_all_zero (&r->reg_type))
10130 return (const reg_entry *) NULL;
10131
10132 if ((r->reg_type.bitfield.dword
10133 || r->reg_type.bitfield.sreg3
10134 || r->reg_type.bitfield.control
10135 || r->reg_type.bitfield.debug
10136 || r->reg_type.bitfield.test)
10137 && !cpu_arch_flags.bitfield.cpui386)
10138 return (const reg_entry *) NULL;
10139
10140 if (r->reg_type.bitfield.tbyte
10141 && !cpu_arch_flags.bitfield.cpu8087
10142 && !cpu_arch_flags.bitfield.cpu287
10143 && !cpu_arch_flags.bitfield.cpu387)
10144 return (const reg_entry *) NULL;
10145
10146 if (r->reg_type.bitfield.regmmx && !cpu_arch_flags.bitfield.cpuregmmx)
10147 return (const reg_entry *) NULL;
10148
10149 if (r->reg_type.bitfield.xmmword && !cpu_arch_flags.bitfield.cpuregxmm)
10150 return (const reg_entry *) NULL;
10151
10152 if (r->reg_type.bitfield.ymmword && !cpu_arch_flags.bitfield.cpuregymm)
10153 return (const reg_entry *) NULL;
10154
10155 if (r->reg_type.bitfield.zmmword && !cpu_arch_flags.bitfield.cpuregzmm)
10156 return (const reg_entry *) NULL;
10157
10158 if (r->reg_type.bitfield.regmask
10159 && !cpu_arch_flags.bitfield.cpuregmask)
10160 return (const reg_entry *) NULL;
10161
10162 /* Don't allow fake index register unless allow_index_reg isn't 0. */
10163 if (!allow_index_reg
10164 && (r->reg_num == RegEiz || r->reg_num == RegRiz))
10165 return (const reg_entry *) NULL;
10166
10167 /* Upper 16 vector register is only available with VREX in 64bit
10168 mode. */
10169 if ((r->reg_flags & RegVRex))
10170 {
10171 if (i.vec_encoding == vex_encoding_default)
10172 i.vec_encoding = vex_encoding_evex;
10173
10174 if (!cpu_arch_flags.bitfield.cpuvrex
10175 || i.vec_encoding != vex_encoding_evex
10176 || flag_code != CODE_64BIT)
10177 return (const reg_entry *) NULL;
10178 }
10179
10180 if (((r->reg_flags & (RegRex64 | RegRex))
10181 || r->reg_type.bitfield.qword)
10182 && (!cpu_arch_flags.bitfield.cpulm
10183 || !operand_type_equal (&r->reg_type, &control))
10184 && flag_code != CODE_64BIT)
10185 return (const reg_entry *) NULL;
10186
10187 if (r->reg_type.bitfield.sreg3 && r->reg_num == RegFlat && !intel_syntax)
10188 return (const reg_entry *) NULL;
10189
10190 return r;
10191}
10192
10193/* REG_STRING starts *before* REGISTER_PREFIX. */
10194
10195static const reg_entry *
10196parse_register (char *reg_string, char **end_op)
10197{
10198 const reg_entry *r;
10199
10200 if (*reg_string == REGISTER_PREFIX || allow_naked_reg)
10201 r = parse_real_register (reg_string, end_op);
10202 else
10203 r = NULL;
10204 if (!r)
10205 {
10206 char *save = input_line_pointer;
10207 char c;
10208 symbolS *symbolP;
10209
10210 input_line_pointer = reg_string;
10211 c = get_symbol_name (&reg_string);
10212 symbolP = symbol_find (reg_string);
10213 if (symbolP && S_GET_SEGMENT (symbolP) == reg_section)
10214 {
10215 const expressionS *e = symbol_get_value_expression (symbolP);
10216
10217 know (e->X_op == O_register);
10218 know (e->X_add_number >= 0
10219 && (valueT) e->X_add_number < i386_regtab_size);
10220 r = i386_regtab + e->X_add_number;
10221 if ((r->reg_flags & RegVRex))
10222 i.vec_encoding = vex_encoding_evex;
10223 *end_op = input_line_pointer;
10224 }
10225 *input_line_pointer = c;
10226 input_line_pointer = save;
10227 }
10228 return r;
10229}
10230
10231int
10232i386_parse_name (char *name, expressionS *e, char *nextcharP)
10233{
10234 const reg_entry *r;
10235 char *end = input_line_pointer;
10236
10237 *end = *nextcharP;
10238 r = parse_register (name, &input_line_pointer);
10239 if (r && end <= input_line_pointer)
10240 {
10241 *nextcharP = *input_line_pointer;
10242 *input_line_pointer = 0;
10243 e->X_op = O_register;
10244 e->X_add_number = r - i386_regtab;
10245 return 1;
10246 }
10247 input_line_pointer = end;
10248 *end = 0;
10249 return intel_syntax ? i386_intel_parse_name (name, e) : 0;
10250}
10251
10252void
10253md_operand (expressionS *e)
10254{
10255 char *end;
10256 const reg_entry *r;
10257
10258 switch (*input_line_pointer)
10259 {
10260 case REGISTER_PREFIX:
10261 r = parse_real_register (input_line_pointer, &end);
10262 if (r)
10263 {
10264 e->X_op = O_register;
10265 e->X_add_number = r - i386_regtab;
10266 input_line_pointer = end;
10267 }
10268 break;
10269
10270 case '[':
10271 gas_assert (intel_syntax);
10272 end = input_line_pointer++;
10273 expression (e);
10274 if (*input_line_pointer == ']')
10275 {
10276 ++input_line_pointer;
10277 e->X_op_symbol = make_expr_symbol (e);
10278 e->X_add_symbol = NULL;
10279 e->X_add_number = 0;
10280 e->X_op = O_index;
10281 }
10282 else
10283 {
10284 e->X_op = O_absent;
10285 input_line_pointer = end;
10286 }
10287 break;
10288 }
10289}
10290
10291\f
10292#if defined (OBJ_ELF) || defined (OBJ_MAYBE_ELF)
10293const char *md_shortopts = "kVQ:sqnO::";
10294#else
10295const char *md_shortopts = "qnO::";
10296#endif
10297
10298#define OPTION_32 (OPTION_MD_BASE + 0)
10299#define OPTION_64 (OPTION_MD_BASE + 1)
10300#define OPTION_DIVIDE (OPTION_MD_BASE + 2)
10301#define OPTION_MARCH (OPTION_MD_BASE + 3)
10302#define OPTION_MTUNE (OPTION_MD_BASE + 4)
10303#define OPTION_MMNEMONIC (OPTION_MD_BASE + 5)
10304#define OPTION_MSYNTAX (OPTION_MD_BASE + 6)
10305#define OPTION_MINDEX_REG (OPTION_MD_BASE + 7)
10306#define OPTION_MNAKED_REG (OPTION_MD_BASE + 8)
10307#define OPTION_MOLD_GCC (OPTION_MD_BASE + 9)
10308#define OPTION_MSSE2AVX (OPTION_MD_BASE + 10)
10309#define OPTION_MSSE_CHECK (OPTION_MD_BASE + 11)
10310#define OPTION_MOPERAND_CHECK (OPTION_MD_BASE + 12)
10311#define OPTION_MAVXSCALAR (OPTION_MD_BASE + 13)
10312#define OPTION_X32 (OPTION_MD_BASE + 14)
10313#define OPTION_MADD_BND_PREFIX (OPTION_MD_BASE + 15)
10314#define OPTION_MEVEXLIG (OPTION_MD_BASE + 16)
10315#define OPTION_MEVEXWIG (OPTION_MD_BASE + 17)
10316#define OPTION_MBIG_OBJ (OPTION_MD_BASE + 18)
10317#define OPTION_MOMIT_LOCK_PREFIX (OPTION_MD_BASE + 19)
10318#define OPTION_MEVEXRCIG (OPTION_MD_BASE + 20)
10319#define OPTION_MSHARED (OPTION_MD_BASE + 21)
10320#define OPTION_MAMD64 (OPTION_MD_BASE + 22)
10321#define OPTION_MINTEL64 (OPTION_MD_BASE + 23)
10322#define OPTION_MFENCE_AS_LOCK_ADD (OPTION_MD_BASE + 24)
10323#define OPTION_MRELAX_RELOCATIONS (OPTION_MD_BASE + 25)
10324
10325struct option md_longopts[] =
10326{
10327 {"32", no_argument, NULL, OPTION_32},
10328#if (defined (OBJ_ELF) || defined (OBJ_MAYBE_ELF) \
10329 || defined (TE_PE) || defined (TE_PEP) || defined (OBJ_MACH_O))
10330 {"64", no_argument, NULL, OPTION_64},
10331#endif
10332#if defined (OBJ_ELF) || defined (OBJ_MAYBE_ELF)
10333 {"x32", no_argument, NULL, OPTION_X32},
10334 {"mshared", no_argument, NULL, OPTION_MSHARED},
10335#endif
10336 {"divide", no_argument, NULL, OPTION_DIVIDE},
10337 {"march", required_argument, NULL, OPTION_MARCH},
10338 {"mtune", required_argument, NULL, OPTION_MTUNE},
10339 {"mmnemonic", required_argument, NULL, OPTION_MMNEMONIC},
10340 {"msyntax", required_argument, NULL, OPTION_MSYNTAX},
10341 {"mindex-reg", no_argument, NULL, OPTION_MINDEX_REG},
10342 {"mnaked-reg", no_argument, NULL, OPTION_MNAKED_REG},
10343 {"mold-gcc", no_argument, NULL, OPTION_MOLD_GCC},
10344 {"msse2avx", no_argument, NULL, OPTION_MSSE2AVX},
10345 {"msse-check", required_argument, NULL, OPTION_MSSE_CHECK},
10346 {"moperand-check", required_argument, NULL, OPTION_MOPERAND_CHECK},
10347 {"mavxscalar", required_argument, NULL, OPTION_MAVXSCALAR},
10348 {"madd-bnd-prefix", no_argument, NULL, OPTION_MADD_BND_PREFIX},
10349 {"mevexlig", required_argument, NULL, OPTION_MEVEXLIG},
10350 {"mevexwig", required_argument, NULL, OPTION_MEVEXWIG},
10351# if defined (TE_PE) || defined (TE_PEP)
10352 {"mbig-obj", no_argument, NULL, OPTION_MBIG_OBJ},
10353#endif
10354 {"momit-lock-prefix", required_argument, NULL, OPTION_MOMIT_LOCK_PREFIX},
10355 {"mfence-as-lock-add", required_argument, NULL, OPTION_MFENCE_AS_LOCK_ADD},
10356 {"mrelax-relocations", required_argument, NULL, OPTION_MRELAX_RELOCATIONS},
10357 {"mevexrcig", required_argument, NULL, OPTION_MEVEXRCIG},
10358 {"mamd64", no_argument, NULL, OPTION_MAMD64},
10359 {"mintel64", no_argument, NULL, OPTION_MINTEL64},
10360 {NULL, no_argument, NULL, 0}
10361};
10362size_t md_longopts_size = sizeof (md_longopts);
10363
10364int
10365md_parse_option (int c, const char *arg)
10366{
10367 unsigned int j;
10368 char *arch, *next, *saved;
10369
10370 switch (c)
10371 {
10372 case 'n':
10373 optimize_align_code = 0;
10374 break;
10375
10376 case 'q':
10377 quiet_warnings = 1;
10378 break;
10379
10380#if defined (OBJ_ELF) || defined (OBJ_MAYBE_ELF)
10381 /* -Qy, -Qn: SVR4 arguments controlling whether a .comment section
10382 should be emitted or not. FIXME: Not implemented. */
10383 case 'Q':
10384 break;
10385
10386 /* -V: SVR4 argument to print version ID. */
10387 case 'V':
10388 print_version_id ();
10389 break;
10390
10391 /* -k: Ignore for FreeBSD compatibility. */
10392 case 'k':
10393 break;
10394
10395 case 's':
10396 /* -s: On i386 Solaris, this tells the native assembler to use
10397 .stab instead of .stab.excl. We always use .stab anyhow. */
10398 break;
10399
10400 case OPTION_MSHARED:
10401 shared = 1;
10402 break;
10403#endif
10404#if (defined (OBJ_ELF) || defined (OBJ_MAYBE_ELF) \
10405 || defined (TE_PE) || defined (TE_PEP) || defined (OBJ_MACH_O))
10406 case OPTION_64:
10407 {
10408 const char **list, **l;
10409
10410 list = bfd_target_list ();
10411 for (l = list; *l != NULL; l++)
10412 if (CONST_STRNEQ (*l, "elf64-x86-64")
10413 || strcmp (*l, "coff-x86-64") == 0
10414 || strcmp (*l, "pe-x86-64") == 0
10415 || strcmp (*l, "pei-x86-64") == 0
10416 || strcmp (*l, "mach-o-x86-64") == 0)
10417 {
10418 default_arch = "x86_64";
10419 break;
10420 }
10421 if (*l == NULL)
10422 as_fatal (_("no compiled in support for x86_64"));
10423 free (list);
10424 }
10425 break;
10426#endif
10427
10428#if defined (OBJ_ELF) || defined (OBJ_MAYBE_ELF)
10429 case OPTION_X32:
10430 if (IS_ELF)
10431 {
10432 const char **list, **l;
10433
10434 list = bfd_target_list ();
10435 for (l = list; *l != NULL; l++)
10436 if (CONST_STRNEQ (*l, "elf32-x86-64"))
10437 {
10438 default_arch = "x86_64:32";
10439 break;
10440 }
10441 if (*l == NULL)
10442 as_fatal (_("no compiled in support for 32bit x86_64"));
10443 free (list);
10444 }
10445 else
10446 as_fatal (_("32bit x86_64 is only supported for ELF"));
10447 break;
10448#endif
10449
10450 case OPTION_32:
10451 default_arch = "i386";
10452 break;
10453
10454 case OPTION_DIVIDE:
10455#ifdef SVR4_COMMENT_CHARS
10456 {
10457 char *n, *t;
10458 const char *s;
10459
10460 n = XNEWVEC (char, strlen (i386_comment_chars) + 1);
10461 t = n;
10462 for (s = i386_comment_chars; *s != '\0'; s++)
10463 if (*s != '/')
10464 *t++ = *s;
10465 *t = '\0';
10466 i386_comment_chars = n;
10467 }
10468#endif
10469 break;
10470
10471 case OPTION_MARCH:
10472 saved = xstrdup (arg);
10473 arch = saved;
10474 /* Allow -march=+nosse. */
10475 if (*arch == '+')
10476 arch++;
10477 do
10478 {
10479 if (*arch == '.')
10480 as_fatal (_("invalid -march= option: `%s'"), arg);
10481 next = strchr (arch, '+');
10482 if (next)
10483 *next++ = '\0';
10484 for (j = 0; j < ARRAY_SIZE (cpu_arch); j++)
10485 {
10486 if (strcmp (arch, cpu_arch [j].name) == 0)
10487 {
10488 /* Processor. */
10489 if (! cpu_arch[j].flags.bitfield.cpui386)
10490 continue;
10491
10492 cpu_arch_name = cpu_arch[j].name;
10493 cpu_sub_arch_name = NULL;
10494 cpu_arch_flags = cpu_arch[j].flags;
10495 cpu_arch_isa = cpu_arch[j].type;
10496 cpu_arch_isa_flags = cpu_arch[j].flags;
10497 if (!cpu_arch_tune_set)
10498 {
10499 cpu_arch_tune = cpu_arch_isa;
10500 cpu_arch_tune_flags = cpu_arch_isa_flags;
10501 }
10502 break;
10503 }
10504 else if (*cpu_arch [j].name == '.'
10505 && strcmp (arch, cpu_arch [j].name + 1) == 0)
10506 {
10507 /* ISA extension. */
10508 i386_cpu_flags flags;
10509
10510 flags = cpu_flags_or (cpu_arch_flags,
10511 cpu_arch[j].flags);
10512
10513 if (!cpu_flags_equal (&flags, &cpu_arch_flags))
10514 {
10515 if (cpu_sub_arch_name)
10516 {
10517 char *name = cpu_sub_arch_name;
10518 cpu_sub_arch_name = concat (name,
10519 cpu_arch[j].name,
10520 (const char *) NULL);
10521 free (name);
10522 }
10523 else
10524 cpu_sub_arch_name = xstrdup (cpu_arch[j].name);
10525 cpu_arch_flags = flags;
10526 cpu_arch_isa_flags = flags;
10527 }
10528 break;
10529 }
10530 }
10531
10532 if (j >= ARRAY_SIZE (cpu_arch))
10533 {
10534 /* Disable an ISA extension. */
10535 for (j = 0; j < ARRAY_SIZE (cpu_noarch); j++)
10536 if (strcmp (arch, cpu_noarch [j].name) == 0)
10537 {
10538 i386_cpu_flags flags;
10539
10540 flags = cpu_flags_and_not (cpu_arch_flags,
10541 cpu_noarch[j].flags);
10542 if (!cpu_flags_equal (&flags, &cpu_arch_flags))
10543 {
10544 if (cpu_sub_arch_name)
10545 {
10546 char *name = cpu_sub_arch_name;
10547 cpu_sub_arch_name = concat (arch,
10548 (const char *) NULL);
10549 free (name);
10550 }
10551 else
10552 cpu_sub_arch_name = xstrdup (arch);
10553 cpu_arch_flags = flags;
10554 cpu_arch_isa_flags = flags;
10555 }
10556 break;
10557 }
10558
10559 if (j >= ARRAY_SIZE (cpu_noarch))
10560 j = ARRAY_SIZE (cpu_arch);
10561 }
10562
10563 if (j >= ARRAY_SIZE (cpu_arch))
10564 as_fatal (_("invalid -march= option: `%s'"), arg);
10565
10566 arch = next;
10567 }
10568 while (next != NULL);
10569 free (saved);
10570 break;
10571
10572 case OPTION_MTUNE:
10573 if (*arg == '.')
10574 as_fatal (_("invalid -mtune= option: `%s'"), arg);
10575 for (j = 0; j < ARRAY_SIZE (cpu_arch); j++)
10576 {
10577 if (strcmp (arg, cpu_arch [j].name) == 0)
10578 {
10579 cpu_arch_tune_set = 1;
10580 cpu_arch_tune = cpu_arch [j].type;
10581 cpu_arch_tune_flags = cpu_arch[j].flags;
10582 break;
10583 }
10584 }
10585 if (j >= ARRAY_SIZE (cpu_arch))
10586 as_fatal (_("invalid -mtune= option: `%s'"), arg);
10587 break;
10588
10589 case OPTION_MMNEMONIC:
10590 if (strcasecmp (arg, "att") == 0)
10591 intel_mnemonic = 0;
10592 else if (strcasecmp (arg, "intel") == 0)
10593 intel_mnemonic = 1;
10594 else
10595 as_fatal (_("invalid -mmnemonic= option: `%s'"), arg);
10596 break;
10597
10598 case OPTION_MSYNTAX:
10599 if (strcasecmp (arg, "att") == 0)
10600 intel_syntax = 0;
10601 else if (strcasecmp (arg, "intel") == 0)
10602 intel_syntax = 1;
10603 else
10604 as_fatal (_("invalid -msyntax= option: `%s'"), arg);
10605 break;
10606
10607 case OPTION_MINDEX_REG:
10608 allow_index_reg = 1;
10609 break;
10610
10611 case OPTION_MNAKED_REG:
10612 allow_naked_reg = 1;
10613 break;
10614
10615 case OPTION_MOLD_GCC:
10616 old_gcc = 1;
10617 break;
10618
10619 case OPTION_MSSE2AVX:
10620 sse2avx = 1;
10621 break;
10622
10623 case OPTION_MSSE_CHECK:
10624 if (strcasecmp (arg, "error") == 0)
10625 sse_check = check_error;
10626 else if (strcasecmp (arg, "warning") == 0)
10627 sse_check = check_warning;
10628 else if (strcasecmp (arg, "none") == 0)
10629 sse_check = check_none;
10630 else
10631 as_fatal (_("invalid -msse-check= option: `%s'"), arg);
10632 break;
10633
10634 case OPTION_MOPERAND_CHECK:
10635 if (strcasecmp (arg, "error") == 0)
10636 operand_check = check_error;
10637 else if (strcasecmp (arg, "warning") == 0)
10638 operand_check = check_warning;
10639 else if (strcasecmp (arg, "none") == 0)
10640 operand_check = check_none;
10641 else
10642 as_fatal (_("invalid -moperand-check= option: `%s'"), arg);
10643 break;
10644
10645 case OPTION_MAVXSCALAR:
10646 if (strcasecmp (arg, "128") == 0)
10647 avxscalar = vex128;
10648 else if (strcasecmp (arg, "256") == 0)
10649 avxscalar = vex256;
10650 else
10651 as_fatal (_("invalid -mavxscalar= option: `%s'"), arg);
10652 break;
10653
10654 case OPTION_MADD_BND_PREFIX:
10655 add_bnd_prefix = 1;
10656 break;
10657
10658 case OPTION_MEVEXLIG:
10659 if (strcmp (arg, "128") == 0)
10660 evexlig = evexl128;
10661 else if (strcmp (arg, "256") == 0)
10662 evexlig = evexl256;
10663 else if (strcmp (arg, "512") == 0)
10664 evexlig = evexl512;
10665 else
10666 as_fatal (_("invalid -mevexlig= option: `%s'"), arg);
10667 break;
10668
10669 case OPTION_MEVEXRCIG:
10670 if (strcmp (arg, "rne") == 0)
10671 evexrcig = rne;
10672 else if (strcmp (arg, "rd") == 0)
10673 evexrcig = rd;
10674 else if (strcmp (arg, "ru") == 0)
10675 evexrcig = ru;
10676 else if (strcmp (arg, "rz") == 0)
10677 evexrcig = rz;
10678 else
10679 as_fatal (_("invalid -mevexrcig= option: `%s'"), arg);
10680 break;
10681
10682 case OPTION_MEVEXWIG:
10683 if (strcmp (arg, "0") == 0)
10684 evexwig = evexw0;
10685 else if (strcmp (arg, "1") == 0)
10686 evexwig = evexw1;
10687 else
10688 as_fatal (_("invalid -mevexwig= option: `%s'"), arg);
10689 break;
10690
10691# if defined (TE_PE) || defined (TE_PEP)
10692 case OPTION_MBIG_OBJ:
10693 use_big_obj = 1;
10694 break;
10695#endif
10696
10697 case OPTION_MOMIT_LOCK_PREFIX:
10698 if (strcasecmp (arg, "yes") == 0)
10699 omit_lock_prefix = 1;
10700 else if (strcasecmp (arg, "no") == 0)
10701 omit_lock_prefix = 0;
10702 else
10703 as_fatal (_("invalid -momit-lock-prefix= option: `%s'"), arg);
10704 break;
10705
10706 case OPTION_MFENCE_AS_LOCK_ADD:
10707 if (strcasecmp (arg, "yes") == 0)
10708 avoid_fence = 1;
10709 else if (strcasecmp (arg, "no") == 0)
10710 avoid_fence = 0;
10711 else
10712 as_fatal (_("invalid -mfence-as-lock-add= option: `%s'"), arg);
10713 break;
10714
10715 case OPTION_MRELAX_RELOCATIONS:
10716 if (strcasecmp (arg, "yes") == 0)
10717 generate_relax_relocations = 1;
10718 else if (strcasecmp (arg, "no") == 0)
10719 generate_relax_relocations = 0;
10720 else
10721 as_fatal (_("invalid -mrelax-relocations= option: `%s'"), arg);
10722 break;
10723
10724 case OPTION_MAMD64:
10725 intel64 = 0;
10726 break;
10727
10728 case OPTION_MINTEL64:
10729 intel64 = 1;
10730 break;
10731
10732 case 'O':
10733 if (arg == NULL)
10734 {
10735 optimize = 1;
10736 /* Turn off -Os. */
10737 optimize_for_space = 0;
10738 }
10739 else if (*arg == 's')
10740 {
10741 optimize_for_space = 1;
10742 /* Turn on all encoding optimizations. */
10743 optimize = -1;
10744 }
10745 else
10746 {
10747 optimize = atoi (arg);
10748 /* Turn off -Os. */
10749 optimize_for_space = 0;
10750 }
10751 break;
10752
10753 default:
10754 return 0;
10755 }
10756 return 1;
10757}
10758
10759#define MESSAGE_TEMPLATE \
10760" "
10761
10762static char *
10763output_message (FILE *stream, char *p, char *message, char *start,
10764 int *left_p, const char *name, int len)
10765{
10766 int size = sizeof (MESSAGE_TEMPLATE);
10767 int left = *left_p;
10768
10769 /* Reserve 2 spaces for ", " or ",\0" */
10770 left -= len + 2;
10771
10772 /* Check if there is any room. */
10773 if (left >= 0)
10774 {
10775 if (p != start)
10776 {
10777 *p++ = ',';
10778 *p++ = ' ';
10779 }
10780 p = mempcpy (p, name, len);
10781 }
10782 else
10783 {
10784 /* Output the current message now and start a new one. */
10785 *p++ = ',';
10786 *p = '\0';
10787 fprintf (stream, "%s\n", message);
10788 p = start;
10789 left = size - (start - message) - len - 2;
10790
10791 gas_assert (left >= 0);
10792
10793 p = mempcpy (p, name, len);
10794 }
10795
10796 *left_p = left;
10797 return p;
10798}
10799
10800static void
10801show_arch (FILE *stream, int ext, int check)
10802{
10803 static char message[] = MESSAGE_TEMPLATE;
10804 char *start = message + 27;
10805 char *p;
10806 int size = sizeof (MESSAGE_TEMPLATE);
10807 int left;
10808 const char *name;
10809 int len;
10810 unsigned int j;
10811
10812 p = start;
10813 left = size - (start - message);
10814 for (j = 0; j < ARRAY_SIZE (cpu_arch); j++)
10815 {
10816 /* Should it be skipped? */
10817 if (cpu_arch [j].skip)
10818 continue;
10819
10820 name = cpu_arch [j].name;
10821 len = cpu_arch [j].len;
10822 if (*name == '.')
10823 {
10824 /* It is an extension. Skip if we aren't asked to show it. */
10825 if (ext)
10826 {
10827 name++;
10828 len--;
10829 }
10830 else
10831 continue;
10832 }
10833 else if (ext)
10834 {
10835 /* It is an processor. Skip if we show only extension. */
10836 continue;
10837 }
10838 else if (check && ! cpu_arch[j].flags.bitfield.cpui386)
10839 {
10840 /* It is an impossible processor - skip. */
10841 continue;
10842 }
10843
10844 p = output_message (stream, p, message, start, &left, name, len);
10845 }
10846
10847 /* Display disabled extensions. */
10848 if (ext)
10849 for (j = 0; j < ARRAY_SIZE (cpu_noarch); j++)
10850 {
10851 name = cpu_noarch [j].name;
10852 len = cpu_noarch [j].len;
10853 p = output_message (stream, p, message, start, &left, name,
10854 len);
10855 }
10856
10857 *p = '\0';
10858 fprintf (stream, "%s\n", message);
10859}
10860
10861void
10862md_show_usage (FILE *stream)
10863{
10864#if defined (OBJ_ELF) || defined (OBJ_MAYBE_ELF)
10865 fprintf (stream, _("\
10866 -Q ignored\n\
10867 -V print assembler version number\n\
10868 -k ignored\n"));
10869#endif
10870 fprintf (stream, _("\
10871 -n Do not optimize code alignment\n\
10872 -q quieten some warnings\n"));
10873#if defined (OBJ_ELF) || defined (OBJ_MAYBE_ELF)
10874 fprintf (stream, _("\
10875 -s ignored\n"));
10876#endif
10877#if (defined (OBJ_ELF) || defined (OBJ_MAYBE_ELF) \
10878 || defined (TE_PE) || defined (TE_PEP))
10879 fprintf (stream, _("\
10880 --32/--64/--x32 generate 32bit/64bit/x32 code\n"));
10881#endif
10882#ifdef SVR4_COMMENT_CHARS
10883 fprintf (stream, _("\
10884 --divide do not treat `/' as a comment character\n"));
10885#else
10886 fprintf (stream, _("\
10887 --divide ignored\n"));
10888#endif
10889 fprintf (stream, _("\
10890 -march=CPU[,+EXTENSION...]\n\
10891 generate code for CPU and EXTENSION, CPU is one of:\n"));
10892 show_arch (stream, 0, 1);
10893 fprintf (stream, _("\
10894 EXTENSION is combination of:\n"));
10895 show_arch (stream, 1, 0);
10896 fprintf (stream, _("\
10897 -mtune=CPU optimize for CPU, CPU is one of:\n"));
10898 show_arch (stream, 0, 0);
10899 fprintf (stream, _("\
10900 -msse2avx encode SSE instructions with VEX prefix\n"));
10901 fprintf (stream, _("\
10902 -msse-check=[none|error|warning]\n\
10903 check SSE instructions\n"));
10904 fprintf (stream, _("\
10905 -moperand-check=[none|error|warning]\n\
10906 check operand combinations for validity\n"));
10907 fprintf (stream, _("\
10908 -mavxscalar=[128|256] encode scalar AVX instructions with specific vector\n\
10909 length\n"));
10910 fprintf (stream, _("\
10911 -mevexlig=[128|256|512] encode scalar EVEX instructions with specific vector\n\
10912 length\n"));
10913 fprintf (stream, _("\
10914 -mevexwig=[0|1] encode EVEX instructions with specific EVEX.W value\n\
10915 for EVEX.W bit ignored instructions\n"));
10916 fprintf (stream, _("\
10917 -mevexrcig=[rne|rd|ru|rz]\n\
10918 encode EVEX instructions with specific EVEX.RC value\n\
10919 for SAE-only ignored instructions\n"));
10920 fprintf (stream, _("\
10921 -mmnemonic=[att|intel] use AT&T/Intel mnemonic\n"));
10922 fprintf (stream, _("\
10923 -msyntax=[att|intel] use AT&T/Intel syntax\n"));
10924 fprintf (stream, _("\
10925 -mindex-reg support pseudo index registers\n"));
10926 fprintf (stream, _("\
10927 -mnaked-reg don't require `%%' prefix for registers\n"));
10928 fprintf (stream, _("\
10929 -mold-gcc support old (<= 2.8.1) versions of gcc\n"));
10930 fprintf (stream, _("\
10931 -madd-bnd-prefix add BND prefix for all valid branches\n"));
10932 fprintf (stream, _("\
10933 -mshared disable branch optimization for shared code\n"));
10934# if defined (TE_PE) || defined (TE_PEP)
10935 fprintf (stream, _("\
10936 -mbig-obj generate big object files\n"));
10937#endif
10938 fprintf (stream, _("\
10939 -momit-lock-prefix=[no|yes]\n\
10940 strip all lock prefixes\n"));
10941 fprintf (stream, _("\
10942 -mfence-as-lock-add=[no|yes]\n\
10943 encode lfence, mfence and sfence as\n\
10944 lock addl $0x0, (%%{re}sp)\n"));
10945 fprintf (stream, _("\
10946 -mrelax-relocations=[no|yes]\n\
10947 generate relax relocations\n"));
10948 fprintf (stream, _("\
10949 -mamd64 accept only AMD64 ISA\n"));
10950 fprintf (stream, _("\
10951 -mintel64 accept only Intel64 ISA\n"));
10952}
10953
10954#if ((defined (OBJ_MAYBE_COFF) && defined (OBJ_MAYBE_AOUT)) \
10955 || defined (OBJ_ELF) || defined (OBJ_MAYBE_ELF) \
10956 || defined (TE_PE) || defined (TE_PEP) || defined (OBJ_MACH_O))
10957
10958/* Pick the target format to use. */
10959
10960const char *
10961i386_target_format (void)
10962{
10963 if (!strncmp (default_arch, "x86_64", 6))
10964 {
10965 update_code_flag (CODE_64BIT, 1);
10966 if (default_arch[6] == '\0')
10967 x86_elf_abi = X86_64_ABI;
10968 else
10969 x86_elf_abi = X86_64_X32_ABI;
10970 }
10971 else if (!strcmp (default_arch, "i386"))
10972 update_code_flag (CODE_32BIT, 1);
10973 else if (!strcmp (default_arch, "iamcu"))
10974 {
10975 update_code_flag (CODE_32BIT, 1);
10976 if (cpu_arch_isa == PROCESSOR_UNKNOWN)
10977 {
10978 static const i386_cpu_flags iamcu_flags = CPU_IAMCU_FLAGS;
10979 cpu_arch_name = "iamcu";
10980 cpu_sub_arch_name = NULL;
10981 cpu_arch_flags = iamcu_flags;
10982 cpu_arch_isa = PROCESSOR_IAMCU;
10983 cpu_arch_isa_flags = iamcu_flags;
10984 if (!cpu_arch_tune_set)
10985 {
10986 cpu_arch_tune = cpu_arch_isa;
10987 cpu_arch_tune_flags = cpu_arch_isa_flags;
10988 }
10989 }
10990 else if (cpu_arch_isa != PROCESSOR_IAMCU)
10991 as_fatal (_("Intel MCU doesn't support `%s' architecture"),
10992 cpu_arch_name);
10993 }
10994 else
10995 as_fatal (_("unknown architecture"));
10996
10997 if (cpu_flags_all_zero (&cpu_arch_isa_flags))
10998 cpu_arch_isa_flags = cpu_arch[flag_code == CODE_64BIT].flags;
10999 if (cpu_flags_all_zero (&cpu_arch_tune_flags))
11000 cpu_arch_tune_flags = cpu_arch[flag_code == CODE_64BIT].flags;
11001
11002 switch (OUTPUT_FLAVOR)
11003 {
11004#if defined (OBJ_MAYBE_AOUT) || defined (OBJ_AOUT)
11005 case bfd_target_aout_flavour:
11006 return AOUT_TARGET_FORMAT;
11007#endif
11008#if defined (OBJ_MAYBE_COFF) || defined (OBJ_COFF)
11009# if defined (TE_PE) || defined (TE_PEP)
11010 case bfd_target_coff_flavour:
11011 if (flag_code == CODE_64BIT)
11012 return use_big_obj ? "pe-bigobj-x86-64" : "pe-x86-64";
11013 else
11014 return "pe-i386";
11015# elif defined (TE_GO32)
11016 case bfd_target_coff_flavour:
11017 return "coff-go32";
11018# else
11019 case bfd_target_coff_flavour:
11020 return "coff-i386";
11021# endif
11022#endif
11023#if defined (OBJ_MAYBE_ELF) || defined (OBJ_ELF)
11024 case bfd_target_elf_flavour:
11025 {
11026 const char *format;
11027
11028 switch (x86_elf_abi)
11029 {
11030 default:
11031 format = ELF_TARGET_FORMAT;
11032 break;
11033 case X86_64_ABI:
11034 use_rela_relocations = 1;
11035 object_64bit = 1;
11036 format = ELF_TARGET_FORMAT64;
11037 break;
11038 case X86_64_X32_ABI:
11039 use_rela_relocations = 1;
11040 object_64bit = 1;
11041 disallow_64bit_reloc = 1;
11042 format = ELF_TARGET_FORMAT32;
11043 break;
11044 }
11045 if (cpu_arch_isa == PROCESSOR_L1OM)
11046 {
11047 if (x86_elf_abi != X86_64_ABI)
11048 as_fatal (_("Intel L1OM is 64bit only"));
11049 return ELF_TARGET_L1OM_FORMAT;
11050 }
11051 else if (cpu_arch_isa == PROCESSOR_K1OM)
11052 {
11053 if (x86_elf_abi != X86_64_ABI)
11054 as_fatal (_("Intel K1OM is 64bit only"));
11055 return ELF_TARGET_K1OM_FORMAT;
11056 }
11057 else if (cpu_arch_isa == PROCESSOR_IAMCU)
11058 {
11059 if (x86_elf_abi != I386_ABI)
11060 as_fatal (_("Intel MCU is 32bit only"));
11061 return ELF_TARGET_IAMCU_FORMAT;
11062 }
11063 else
11064 return format;
11065 }
11066#endif
11067#if defined (OBJ_MACH_O)
11068 case bfd_target_mach_o_flavour:
11069 if (flag_code == CODE_64BIT)
11070 {
11071 use_rela_relocations = 1;
11072 object_64bit = 1;
11073 return "mach-o-x86-64";
11074 }
11075 else
11076 return "mach-o-i386";
11077#endif
11078 default:
11079 abort ();
11080 return NULL;
11081 }
11082}
11083
11084#endif /* OBJ_MAYBE_ more than one */
11085\f
11086symbolS *
11087md_undefined_symbol (char *name)
11088{
11089 if (name[0] == GLOBAL_OFFSET_TABLE_NAME[0]
11090 && name[1] == GLOBAL_OFFSET_TABLE_NAME[1]
11091 && name[2] == GLOBAL_OFFSET_TABLE_NAME[2]
11092 && strcmp (name, GLOBAL_OFFSET_TABLE_NAME) == 0)
11093 {
11094 if (!GOT_symbol)
11095 {
11096 if (symbol_find (name))
11097 as_bad (_("GOT already in symbol table"));
11098 GOT_symbol = symbol_new (name, undefined_section,
11099 (valueT) 0, &zero_address_frag);
11100 };
11101 return GOT_symbol;
11102 }
11103 return 0;
11104}
11105
11106/* Round up a section size to the appropriate boundary. */
11107
11108valueT
11109md_section_align (segT segment ATTRIBUTE_UNUSED, valueT size)
11110{
11111#if (defined (OBJ_AOUT) || defined (OBJ_MAYBE_AOUT))
11112 if (OUTPUT_FLAVOR == bfd_target_aout_flavour)
11113 {
11114 /* For a.out, force the section size to be aligned. If we don't do
11115 this, BFD will align it for us, but it will not write out the
11116 final bytes of the section. This may be a bug in BFD, but it is
11117 easier to fix it here since that is how the other a.out targets
11118 work. */
11119 int align;
11120
11121 align = bfd_get_section_alignment (stdoutput, segment);
11122 size = ((size + (1 << align) - 1) & (-((valueT) 1 << align)));
11123 }
11124#endif
11125
11126 return size;
11127}
11128
11129/* On the i386, PC-relative offsets are relative to the start of the
11130 next instruction. That is, the address of the offset, plus its
11131 size, since the offset is always the last part of the insn. */
11132
11133long
11134md_pcrel_from (fixS *fixP)
11135{
11136 return fixP->fx_size + fixP->fx_where + fixP->fx_frag->fr_address;
11137}
11138
11139#ifndef I386COFF
11140
11141static void
11142s_bss (int ignore ATTRIBUTE_UNUSED)
11143{
11144 int temp;
11145
11146#if defined (OBJ_ELF) || defined (OBJ_MAYBE_ELF)
11147 if (IS_ELF)
11148 obj_elf_section_change_hook ();
11149#endif
11150 temp = get_absolute_expression ();
11151 subseg_set (bss_section, (subsegT) temp);
11152 demand_empty_rest_of_line ();
11153}
11154
11155#endif
11156
11157void
11158i386_validate_fix (fixS *fixp)
11159{
11160 if (fixp->fx_subsy)
11161 {
11162 if (fixp->fx_subsy == GOT_symbol)
11163 {
11164 if (fixp->fx_r_type == BFD_RELOC_32_PCREL)
11165 {
11166 if (!object_64bit)
11167 abort ();
11168#if defined (OBJ_ELF) || defined (OBJ_MAYBE_ELF)
11169 if (fixp->fx_tcbit2)
11170 fixp->fx_r_type = (fixp->fx_tcbit
11171 ? BFD_RELOC_X86_64_REX_GOTPCRELX
11172 : BFD_RELOC_X86_64_GOTPCRELX);
11173 else
11174#endif
11175 fixp->fx_r_type = BFD_RELOC_X86_64_GOTPCREL;
11176 }
11177 else
11178 {
11179 if (!object_64bit)
11180 fixp->fx_r_type = BFD_RELOC_386_GOTOFF;
11181 else
11182 fixp->fx_r_type = BFD_RELOC_X86_64_GOTOFF64;
11183 }
11184 fixp->fx_subsy = 0;
11185 }
11186 }
11187#if defined (OBJ_ELF) || defined (OBJ_MAYBE_ELF)
11188 else if (!object_64bit)
11189 {
11190 if (fixp->fx_r_type == BFD_RELOC_386_GOT32
11191 && fixp->fx_tcbit2)
11192 fixp->fx_r_type = BFD_RELOC_386_GOT32X;
11193 }
11194#endif
11195}
11196
11197arelent *
11198tc_gen_reloc (asection *section ATTRIBUTE_UNUSED, fixS *fixp)
11199{
11200 arelent *rel;
11201 bfd_reloc_code_real_type code;
11202
11203 switch (fixp->fx_r_type)
11204 {
11205#if defined (OBJ_ELF) || defined (OBJ_MAYBE_ELF)
11206 case BFD_RELOC_SIZE32:
11207 case BFD_RELOC_SIZE64:
11208 if (S_IS_DEFINED (fixp->fx_addsy)
11209 && !S_IS_EXTERNAL (fixp->fx_addsy))
11210 {
11211 /* Resolve size relocation against local symbol to size of
11212 the symbol plus addend. */
11213 valueT value = S_GET_SIZE (fixp->fx_addsy) + fixp->fx_offset;
11214 if (fixp->fx_r_type == BFD_RELOC_SIZE32
11215 && !fits_in_unsigned_long (value))
11216 as_bad_where (fixp->fx_file, fixp->fx_line,
11217 _("symbol size computation overflow"));
11218 fixp->fx_addsy = NULL;
11219 fixp->fx_subsy = NULL;
11220 md_apply_fix (fixp, (valueT *) &value, NULL);
11221 return NULL;
11222 }
11223#endif
11224 /* Fall through. */
11225
11226 case BFD_RELOC_X86_64_PLT32:
11227 case BFD_RELOC_X86_64_GOT32:
11228 case BFD_RELOC_X86_64_GOTPCREL:
11229 case BFD_RELOC_X86_64_GOTPCRELX:
11230 case BFD_RELOC_X86_64_REX_GOTPCRELX:
11231 case BFD_RELOC_386_PLT32:
11232 case BFD_RELOC_386_GOT32:
11233 case BFD_RELOC_386_GOT32X:
11234 case BFD_RELOC_386_GOTOFF:
11235 case BFD_RELOC_386_GOTPC:
11236 case BFD_RELOC_386_TLS_GD:
11237 case BFD_RELOC_386_TLS_LDM:
11238 case BFD_RELOC_386_TLS_LDO_32:
11239 case BFD_RELOC_386_TLS_IE_32:
11240 case BFD_RELOC_386_TLS_IE:
11241 case BFD_RELOC_386_TLS_GOTIE:
11242 case BFD_RELOC_386_TLS_LE_32:
11243 case BFD_RELOC_386_TLS_LE:
11244 case BFD_RELOC_386_TLS_GOTDESC:
11245 case BFD_RELOC_386_TLS_DESC_CALL:
11246 case BFD_RELOC_X86_64_TLSGD:
11247 case BFD_RELOC_X86_64_TLSLD:
11248 case BFD_RELOC_X86_64_DTPOFF32:
11249 case BFD_RELOC_X86_64_DTPOFF64:
11250 case BFD_RELOC_X86_64_GOTTPOFF:
11251 case BFD_RELOC_X86_64_TPOFF32:
11252 case BFD_RELOC_X86_64_TPOFF64:
11253 case BFD_RELOC_X86_64_GOTOFF64:
11254 case BFD_RELOC_X86_64_GOTPC32:
11255 case BFD_RELOC_X86_64_GOT64:
11256 case BFD_RELOC_X86_64_GOTPCREL64:
11257 case BFD_RELOC_X86_64_GOTPC64:
11258 case BFD_RELOC_X86_64_GOTPLT64:
11259 case BFD_RELOC_X86_64_PLTOFF64:
11260 case BFD_RELOC_X86_64_GOTPC32_TLSDESC:
11261 case BFD_RELOC_X86_64_TLSDESC_CALL:
11262 case BFD_RELOC_RVA:
11263 case BFD_RELOC_VTABLE_ENTRY:
11264 case BFD_RELOC_VTABLE_INHERIT:
11265#ifdef TE_PE
11266 case BFD_RELOC_32_SECREL:
11267#endif
11268 code = fixp->fx_r_type;
11269 break;
11270 case BFD_RELOC_X86_64_32S:
11271 if (!fixp->fx_pcrel)
11272 {
11273 /* Don't turn BFD_RELOC_X86_64_32S into BFD_RELOC_32. */
11274 code = fixp->fx_r_type;
11275 break;
11276 }
11277 /* Fall through. */
11278 default:
11279 if (fixp->fx_pcrel)
11280 {
11281 switch (fixp->fx_size)
11282 {
11283 default:
11284 as_bad_where (fixp->fx_file, fixp->fx_line,
11285 _("can not do %d byte pc-relative relocation"),
11286 fixp->fx_size);
11287 code = BFD_RELOC_32_PCREL;
11288 break;
11289 case 1: code = BFD_RELOC_8_PCREL; break;
11290 case 2: code = BFD_RELOC_16_PCREL; break;
11291 case 4: code = BFD_RELOC_32_PCREL; break;
11292#ifdef BFD64
11293 case 8: code = BFD_RELOC_64_PCREL; break;
11294#endif
11295 }
11296 }
11297 else
11298 {
11299 switch (fixp->fx_size)
11300 {
11301 default:
11302 as_bad_where (fixp->fx_file, fixp->fx_line,
11303 _("can not do %d byte relocation"),
11304 fixp->fx_size);
11305 code = BFD_RELOC_32;
11306 break;
11307 case 1: code = BFD_RELOC_8; break;
11308 case 2: code = BFD_RELOC_16; break;
11309 case 4: code = BFD_RELOC_32; break;
11310#ifdef BFD64
11311 case 8: code = BFD_RELOC_64; break;
11312#endif
11313 }
11314 }
11315 break;
11316 }
11317
11318 if ((code == BFD_RELOC_32
11319 || code == BFD_RELOC_32_PCREL
11320 || code == BFD_RELOC_X86_64_32S)
11321 && GOT_symbol
11322 && fixp->fx_addsy == GOT_symbol)
11323 {
11324 if (!object_64bit)
11325 code = BFD_RELOC_386_GOTPC;
11326 else
11327 code = BFD_RELOC_X86_64_GOTPC32;
11328 }
11329 if ((code == BFD_RELOC_64 || code == BFD_RELOC_64_PCREL)
11330 && GOT_symbol
11331 && fixp->fx_addsy == GOT_symbol)
11332 {
11333 code = BFD_RELOC_X86_64_GOTPC64;
11334 }
11335
11336 rel = XNEW (arelent);
11337 rel->sym_ptr_ptr = XNEW (asymbol *);
11338 *rel->sym_ptr_ptr = symbol_get_bfdsym (fixp->fx_addsy);
11339
11340 rel->address = fixp->fx_frag->fr_address + fixp->fx_where;
11341
11342 if (!use_rela_relocations)
11343 {
11344 /* HACK: Since i386 ELF uses Rel instead of Rela, encode the
11345 vtable entry to be used in the relocation's section offset. */
11346 if (fixp->fx_r_type == BFD_RELOC_VTABLE_ENTRY)
11347 rel->address = fixp->fx_offset;
11348#if defined (OBJ_COFF) && defined (TE_PE)
11349 else if (fixp->fx_addsy && S_IS_WEAK (fixp->fx_addsy))
11350 rel->addend = fixp->fx_addnumber - (S_GET_VALUE (fixp->fx_addsy) * 2);
11351 else
11352#endif
11353 rel->addend = 0;
11354 }
11355 /* Use the rela in 64bit mode. */
11356 else
11357 {
11358 if (disallow_64bit_reloc)
11359 switch (code)
11360 {
11361 case BFD_RELOC_X86_64_DTPOFF64:
11362 case BFD_RELOC_X86_64_TPOFF64:
11363 case BFD_RELOC_64_PCREL:
11364 case BFD_RELOC_X86_64_GOTOFF64:
11365 case BFD_RELOC_X86_64_GOT64:
11366 case BFD_RELOC_X86_64_GOTPCREL64:
11367 case BFD_RELOC_X86_64_GOTPC64:
11368 case BFD_RELOC_X86_64_GOTPLT64:
11369 case BFD_RELOC_X86_64_PLTOFF64:
11370 as_bad_where (fixp->fx_file, fixp->fx_line,
11371 _("cannot represent relocation type %s in x32 mode"),
11372 bfd_get_reloc_code_name (code));
11373 break;
11374 default:
11375 break;
11376 }
11377
11378 if (!fixp->fx_pcrel)
11379 rel->addend = fixp->fx_offset;
11380 else
11381 switch (code)
11382 {
11383 case BFD_RELOC_X86_64_PLT32:
11384 case BFD_RELOC_X86_64_GOT32:
11385 case BFD_RELOC_X86_64_GOTPCREL:
11386 case BFD_RELOC_X86_64_GOTPCRELX:
11387 case BFD_RELOC_X86_64_REX_GOTPCRELX:
11388 case BFD_RELOC_X86_64_TLSGD:
11389 case BFD_RELOC_X86_64_TLSLD:
11390 case BFD_RELOC_X86_64_GOTTPOFF:
11391 case BFD_RELOC_X86_64_GOTPC32_TLSDESC:
11392 case BFD_RELOC_X86_64_TLSDESC_CALL:
11393 rel->addend = fixp->fx_offset - fixp->fx_size;
11394 break;
11395 default:
11396 rel->addend = (section->vma
11397 - fixp->fx_size
11398 + fixp->fx_addnumber
11399 + md_pcrel_from (fixp));
11400 break;
11401 }
11402 }
11403
11404 rel->howto = bfd_reloc_type_lookup (stdoutput, code);
11405 if (rel->howto == NULL)
11406 {
11407 as_bad_where (fixp->fx_file, fixp->fx_line,
11408 _("cannot represent relocation type %s"),
11409 bfd_get_reloc_code_name (code));
11410 /* Set howto to a garbage value so that we can keep going. */
11411 rel->howto = bfd_reloc_type_lookup (stdoutput, BFD_RELOC_32);
11412 gas_assert (rel->howto != NULL);
11413 }
11414
11415 return rel;
11416}
11417
11418#include "tc-i386-intel.c"
11419
11420void
11421tc_x86_parse_to_dw2regnum (expressionS *exp)
11422{
11423 int saved_naked_reg;
11424 char saved_register_dot;
11425
11426 saved_naked_reg = allow_naked_reg;
11427 allow_naked_reg = 1;
11428 saved_register_dot = register_chars['.'];
11429 register_chars['.'] = '.';
11430 allow_pseudo_reg = 1;
11431 expression_and_evaluate (exp);
11432 allow_pseudo_reg = 0;
11433 register_chars['.'] = saved_register_dot;
11434 allow_naked_reg = saved_naked_reg;
11435
11436 if (exp->X_op == O_register && exp->X_add_number >= 0)
11437 {
11438 if ((addressT) exp->X_add_number < i386_regtab_size)
11439 {
11440 exp->X_op = O_constant;
11441 exp->X_add_number = i386_regtab[exp->X_add_number]
11442 .dw2_regnum[flag_code >> 1];
11443 }
11444 else
11445 exp->X_op = O_illegal;
11446 }
11447}
11448
11449void
11450tc_x86_frame_initial_instructions (void)
11451{
11452 static unsigned int sp_regno[2];
11453
11454 if (!sp_regno[flag_code >> 1])
11455 {
11456 char *saved_input = input_line_pointer;
11457 char sp[][4] = {"esp", "rsp"};
11458 expressionS exp;
11459
11460 input_line_pointer = sp[flag_code >> 1];
11461 tc_x86_parse_to_dw2regnum (&exp);
11462 gas_assert (exp.X_op == O_constant);
11463 sp_regno[flag_code >> 1] = exp.X_add_number;
11464 input_line_pointer = saved_input;
11465 }
11466
11467 cfi_add_CFA_def_cfa (sp_regno[flag_code >> 1], -x86_cie_data_alignment);
11468 cfi_add_CFA_offset (x86_dwarf2_return_column, x86_cie_data_alignment);
11469}
11470
11471int
11472x86_dwarf2_addr_size (void)
11473{
11474#if defined (OBJ_MAYBE_ELF) || defined (OBJ_ELF)
11475 if (x86_elf_abi == X86_64_X32_ABI)
11476 return 4;
11477#endif
11478 return bfd_arch_bits_per_address (stdoutput) / 8;
11479}
11480
11481int
11482i386_elf_section_type (const char *str, size_t len)
11483{
11484 if (flag_code == CODE_64BIT
11485 && len == sizeof ("unwind") - 1
11486 && strncmp (str, "unwind", 6) == 0)
11487 return SHT_X86_64_UNWIND;
11488
11489 return -1;
11490}
11491
11492#ifdef TE_SOLARIS
11493void
11494i386_solaris_fix_up_eh_frame (segT sec)
11495{
11496 if (flag_code == CODE_64BIT)
11497 elf_section_type (sec) = SHT_X86_64_UNWIND;
11498}
11499#endif
11500
11501#ifdef TE_PE
11502void
11503tc_pe_dwarf2_emit_offset (symbolS *symbol, unsigned int size)
11504{
11505 expressionS exp;
11506
11507 exp.X_op = O_secrel;
11508 exp.X_add_symbol = symbol;
11509 exp.X_add_number = 0;
11510 emit_expr (&exp, size);
11511}
11512#endif
11513
11514#if defined (OBJ_ELF) || defined (OBJ_MAYBE_ELF)
11515/* For ELF on x86-64, add support for SHF_X86_64_LARGE. */
11516
11517bfd_vma
11518x86_64_section_letter (int letter, const char **ptr_msg)
11519{
11520 if (flag_code == CODE_64BIT)
11521 {
11522 if (letter == 'l')
11523 return SHF_X86_64_LARGE;
11524
11525 *ptr_msg = _("bad .section directive: want a,l,w,x,M,S,G,T in string");
11526 }
11527 else
11528 *ptr_msg = _("bad .section directive: want a,w,x,M,S,G,T in string");
11529 return -1;
11530}
11531
11532bfd_vma
11533x86_64_section_word (char *str, size_t len)
11534{
11535 if (len == 5 && flag_code == CODE_64BIT && CONST_STRNEQ (str, "large"))
11536 return SHF_X86_64_LARGE;
11537
11538 return -1;
11539}
11540
11541static void
11542handle_large_common (int small ATTRIBUTE_UNUSED)
11543{
11544 if (flag_code != CODE_64BIT)
11545 {
11546 s_comm_internal (0, elf_common_parse);
11547 as_warn (_(".largecomm supported only in 64bit mode, producing .comm"));
11548 }
11549 else
11550 {
11551 static segT lbss_section;
11552 asection *saved_com_section_ptr = elf_com_section_ptr;
11553 asection *saved_bss_section = bss_section;
11554
11555 if (lbss_section == NULL)
11556 {
11557 flagword applicable;
11558 segT seg = now_seg;
11559 subsegT subseg = now_subseg;
11560
11561 /* The .lbss section is for local .largecomm symbols. */
11562 lbss_section = subseg_new (".lbss", 0);
11563 applicable = bfd_applicable_section_flags (stdoutput);
11564 bfd_set_section_flags (stdoutput, lbss_section,
11565 applicable & SEC_ALLOC);
11566 seg_info (lbss_section)->bss = 1;
11567
11568 subseg_set (seg, subseg);
11569 }
11570
11571 elf_com_section_ptr = &_bfd_elf_large_com_section;
11572 bss_section = lbss_section;
11573
11574 s_comm_internal (0, elf_common_parse);
11575
11576 elf_com_section_ptr = saved_com_section_ptr;
11577 bss_section = saved_bss_section;
11578 }
11579}
11580#endif /* OBJ_ELF || OBJ_MAYBE_ELF */
This page took 0.059401 seconds and 4 git commands to generate.