1 /* tc-mips.c -- assemble code for a MIPS chip.
2 Copyright 1993, 1994, 1995, 1996, 1997, 1998, 1999, 2000, 2001, 2002,
3 2003, 2004 Free Software Foundation, Inc.
4 Contributed by the OSF and Ralph Campbell.
5 Written by Keith Knowles and Ralph Campbell, working independently.
6 Modified for ECOFF and R4000 support by Ian Lance Taylor of Cygnus
9 This file is part of GAS.
11 GAS is free software; you can redistribute it and/or modify
12 it under the terms of the GNU General Public License as published by
13 the Free Software Foundation; either version 2, or (at your option)
16 GAS is distributed in the hope that it will be useful,
17 but WITHOUT ANY WARRANTY; without even the implied warranty of
18 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
19 GNU General Public License for more details.
21 You should have received a copy of the GNU General Public License
22 along with GAS; see the file COPYING. If not, write to the Free
23 Software Foundation, 59 Temple Place - Suite 330, Boston, MA
29 #include "safe-ctype.h"
33 #include "opcode/mips.h"
35 #include "dwarf2dbg.h"
38 #define DBG(x) printf x
44 /* Clean up namespace so we can include obj-elf.h too. */
45 static int mips_output_flavor (void);
46 static int mips_output_flavor (void) { return OUTPUT_FLAVOR; }
47 #undef OBJ_PROCESS_STAB
54 #undef obj_frob_file_after_relocs
55 #undef obj_frob_symbol
57 #undef obj_sec_sym_ok_for_reloc
58 #undef OBJ_COPY_SYMBOL_ATTRIBUTES
61 /* Fix any of them that we actually care about. */
63 #define OUTPUT_FLAVOR mips_output_flavor()
70 #ifndef ECOFF_DEBUGGING
71 #define NO_ECOFF_DEBUGGING
72 #define ECOFF_DEBUGGING 0
75 int mips_flag_mdebug = -1;
77 /* Control generation of .pdr sections. Off by default on IRIX: the native
78 linker doesn't know about and discards them, but relocations against them
79 remain, leading to rld crashes. */
81 int mips_flag_pdr = FALSE;
83 int mips_flag_pdr = TRUE;
88 #if defined (OBJ_ELF) || defined (OBJ_MAYBE_ELF)
89 static char *mips_regmask_frag;
95 #define PIC_CALL_REG 25
103 #define ILLEGAL_REG (32)
105 /* Allow override of standard little-endian ECOFF format. */
107 #ifndef ECOFF_LITTLE_FORMAT
108 #define ECOFF_LITTLE_FORMAT "ecoff-littlemips"
111 extern int target_big_endian;
113 /* The name of the readonly data section. */
114 #define RDATA_SECTION_NAME (OUTPUT_FLAVOR == bfd_target_aout_flavour \
116 : OUTPUT_FLAVOR == bfd_target_ecoff_flavour \
118 : OUTPUT_FLAVOR == bfd_target_coff_flavour \
120 : OUTPUT_FLAVOR == bfd_target_elf_flavour \
124 /* The ABI to use. */
135 /* MIPS ABI we are using for this output file. */
136 static enum mips_abi_level mips_abi = NO_ABI;
138 /* Whether or not we have code that can call pic code. */
139 int mips_abicalls = FALSE;
141 /* This is the set of options which may be modified by the .set
142 pseudo-op. We use a struct so that .set push and .set pop are more
145 struct mips_set_options
147 /* MIPS ISA (Instruction Set Architecture) level. This is set to -1
148 if it has not been initialized. Changed by `.set mipsN', and the
149 -mipsN command line option, and the default CPU. */
151 /* Enabled Application Specific Extensions (ASEs). These are set to -1
152 if they have not been initialized. Changed by `.set <asename>', by
153 command line options, and based on the default architecture. */
156 /* Whether we are assembling for the mips16 processor. 0 if we are
157 not, 1 if we are, and -1 if the value has not been initialized.
158 Changed by `.set mips16' and `.set nomips16', and the -mips16 and
159 -nomips16 command line options, and the default CPU. */
161 /* Non-zero if we should not reorder instructions. Changed by `.set
162 reorder' and `.set noreorder'. */
164 /* Non-zero if we should not permit the $at ($1) register to be used
165 in instructions. Changed by `.set at' and `.set noat'. */
167 /* Non-zero if we should warn when a macro instruction expands into
168 more than one machine instruction. Changed by `.set nomacro' and
170 int warn_about_macros;
171 /* Non-zero if we should not move instructions. Changed by `.set
172 move', `.set volatile', `.set nomove', and `.set novolatile'. */
174 /* Non-zero if we should not optimize branches by moving the target
175 of the branch into the delay slot. Actually, we don't perform
176 this optimization anyhow. Changed by `.set bopt' and `.set
179 /* Non-zero if we should not autoextend mips16 instructions.
180 Changed by `.set autoextend' and `.set noautoextend'. */
182 /* Restrict general purpose registers and floating point registers
183 to 32 bit. This is initially determined when -mgp32 or -mfp32
184 is passed but can changed if the assembler code uses .set mipsN. */
187 /* MIPS architecture (CPU) type. Changed by .set arch=FOO, the -march
188 command line option, and the default CPU. */
192 /* True if -mgp32 was passed. */
193 static int file_mips_gp32 = -1;
195 /* True if -mfp32 was passed. */
196 static int file_mips_fp32 = -1;
198 /* This is the struct we use to hold the current set of options. Note
199 that we must set the isa field to ISA_UNKNOWN and the ASE fields to
200 -1 to indicate that they have not been initialized. */
202 static struct mips_set_options mips_opts =
204 ISA_UNKNOWN, -1, -1, -1, 0, 0, 0, 0, 0, 0, 0, 0, CPU_UNKNOWN
207 /* These variables are filled in with the masks of registers used.
208 The object format code reads them and puts them in the appropriate
210 unsigned long mips_gprmask;
211 unsigned long mips_cprmask[4];
213 /* MIPS ISA we are using for this output file. */
214 static int file_mips_isa = ISA_UNKNOWN;
216 /* True if -mips16 was passed or implied by arguments passed on the
217 command line (e.g., by -march). */
218 static int file_ase_mips16;
220 /* True if -mips3d was passed or implied by arguments passed on the
221 command line (e.g., by -march). */
222 static int file_ase_mips3d;
224 /* True if -mdmx was passed or implied by arguments passed on the
225 command line (e.g., by -march). */
226 static int file_ase_mdmx;
228 /* The argument of the -march= flag. The architecture we are assembling. */
229 static int file_mips_arch = CPU_UNKNOWN;
230 static const char *mips_arch_string;
232 /* The argument of the -mtune= flag. The architecture for which we
234 static int mips_tune = CPU_UNKNOWN;
235 static const char *mips_tune_string;
237 /* True when generating 32-bit code for a 64-bit processor. */
238 static int mips_32bitmode = 0;
240 /* True if the given ABI requires 32-bit registers. */
241 #define ABI_NEEDS_32BIT_REGS(ABI) ((ABI) == O32_ABI)
243 /* Likewise 64-bit registers. */
244 #define ABI_NEEDS_64BIT_REGS(ABI) \
246 || (ABI) == N64_ABI \
249 /* Return true if ISA supports 64 bit gp register instructions. */
250 #define ISA_HAS_64BIT_REGS(ISA) ( \
252 || (ISA) == ISA_MIPS4 \
253 || (ISA) == ISA_MIPS5 \
254 || (ISA) == ISA_MIPS64 \
255 || (ISA) == ISA_MIPS64R2 \
258 /* Return true if ISA supports 64-bit right rotate (dror et al.)
260 #define ISA_HAS_DROR(ISA) ( \
261 (ISA) == ISA_MIPS64R2 \
264 /* Return true if ISA supports 32-bit right rotate (ror et al.)
266 #define ISA_HAS_ROR(ISA) ( \
267 (ISA) == ISA_MIPS32R2 \
268 || (ISA) == ISA_MIPS64R2 \
271 #define HAVE_32BIT_GPRS \
272 (mips_opts.gp32 || ! ISA_HAS_64BIT_REGS (mips_opts.isa))
274 #define HAVE_32BIT_FPRS \
275 (mips_opts.fp32 || ! ISA_HAS_64BIT_REGS (mips_opts.isa))
277 #define HAVE_64BIT_GPRS (! HAVE_32BIT_GPRS)
278 #define HAVE_64BIT_FPRS (! HAVE_32BIT_FPRS)
280 #define HAVE_NEWABI (mips_abi == N32_ABI || mips_abi == N64_ABI)
282 #define HAVE_64BIT_OBJECTS (mips_abi == N64_ABI)
284 /* We can only have 64bit addresses if the object file format
286 #define HAVE_32BIT_ADDRESSES \
288 || ((bfd_arch_bits_per_address (stdoutput) == 32 \
289 || ! HAVE_64BIT_OBJECTS) \
290 && mips_pic != EMBEDDED_PIC))
292 #define HAVE_64BIT_ADDRESSES (! HAVE_32BIT_ADDRESSES)
294 /* Addresses are loaded in different ways, depending on the address size
295 in use. The n32 ABI Documentation also mandates the use of additions
296 with overflow checking, but existing implementations don't follow it. */
297 #define ADDRESS_ADD_INSN \
298 (HAVE_32BIT_ADDRESSES ? "addu" : "daddu")
300 #define ADDRESS_ADDI_INSN \
301 (HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu")
303 #define ADDRESS_LOAD_INSN \
304 (HAVE_32BIT_ADDRESSES ? "lw" : "ld")
306 #define ADDRESS_STORE_INSN \
307 (HAVE_32BIT_ADDRESSES ? "sw" : "sd")
309 /* Return true if the given CPU supports the MIPS16 ASE. */
310 #define CPU_HAS_MIPS16(cpu) \
311 (strncmp (TARGET_CPU, "mips16", sizeof ("mips16") - 1) == 0 \
312 || strncmp (TARGET_CANONICAL, "mips-lsi-elf", sizeof ("mips-lsi-elf") - 1) == 0)
314 /* Return true if the given CPU supports the MIPS3D ASE. */
315 #define CPU_HAS_MIPS3D(cpu) ((cpu) == CPU_SB1 \
318 /* Return true if the given CPU supports the MDMX ASE. */
319 #define CPU_HAS_MDMX(cpu) (FALSE \
322 /* True if CPU has a dror instruction. */
323 #define CPU_HAS_DROR(CPU) ((CPU) == CPU_VR5400 || (CPU) == CPU_VR5500)
325 /* True if CPU has a ror instruction. */
326 #define CPU_HAS_ROR(CPU) CPU_HAS_DROR (CPU)
328 /* Whether the processor uses hardware interlocks to protect
329 reads from the HI and LO registers, and thus does not
330 require nops to be inserted. */
332 #define hilo_interlocks (mips_opts.arch == CPU_R4010 \
333 || mips_opts.arch == CPU_VR5500 \
334 || mips_opts.arch == CPU_RM7000 \
335 || mips_opts.arch == CPU_SB1 \
338 /* Whether the processor uses hardware interlocks to protect reads
339 from the GPRs after they are loaded from memory, and thus does not
340 require nops to be inserted. This applies to instructions marked
341 INSN_LOAD_MEMORY_DELAY. These nops are only required at MIPS ISA
343 #define gpr_interlocks \
344 (mips_opts.isa != ISA_MIPS1 \
345 || mips_opts.arch == CPU_VR5400 \
346 || mips_opts.arch == CPU_VR5500 \
347 || mips_opts.arch == CPU_R3900)
349 /* Whether the processor uses hardware interlocks to avoid delays
350 required by coprocessor instructions, and thus does not require
351 nops to be inserted. This applies to instructions marked
352 INSN_LOAD_COPROC_DELAY, INSN_COPROC_MOVE_DELAY, and to delays
353 between instructions marked INSN_WRITE_COND_CODE and ones marked
354 INSN_READ_COND_CODE. These nops are only required at MIPS ISA
355 levels I, II, and III. */
356 /* Itbl support may require additional care here. */
357 #define cop_interlocks \
358 ((mips_opts.isa != ISA_MIPS1 \
359 && mips_opts.isa != ISA_MIPS2 \
360 && mips_opts.isa != ISA_MIPS3) \
361 || mips_opts.arch == CPU_R4300 \
362 || mips_opts.arch == CPU_VR5400 \
363 || mips_opts.arch == CPU_VR5500 \
364 || mips_opts.arch == CPU_SB1 \
367 /* Whether the processor uses hardware interlocks to protect reads
368 from coprocessor registers after they are loaded from memory, and
369 thus does not require nops to be inserted. This applies to
370 instructions marked INSN_COPROC_MEMORY_DELAY. These nops are only
371 requires at MIPS ISA level I. */
372 #define cop_mem_interlocks (mips_opts.isa != ISA_MIPS1)
374 /* Is this a mfhi or mflo instruction? */
375 #define MF_HILO_INSN(PINFO) \
376 ((PINFO & INSN_READ_HI) || (PINFO & INSN_READ_LO))
378 /* MIPS PIC level. */
380 enum mips_pic_level mips_pic;
382 /* 1 if we should generate 32 bit offsets from the $gp register in
383 SVR4_PIC mode. Currently has no meaning in other modes. */
384 static int mips_big_got = 0;
386 /* 1 if trap instructions should used for overflow rather than break
388 static int mips_trap = 0;
390 /* 1 if double width floating point constants should not be constructed
391 by assembling two single width halves into two single width floating
392 point registers which just happen to alias the double width destination
393 register. On some architectures this aliasing can be disabled by a bit
394 in the status register, and the setting of this bit cannot be determined
395 automatically at assemble time. */
396 static int mips_disable_float_construction;
398 /* Non-zero if any .set noreorder directives were used. */
400 static int mips_any_noreorder;
402 /* Non-zero if nops should be inserted when the register referenced in
403 an mfhi/mflo instruction is read in the next two instructions. */
404 static int mips_7000_hilo_fix;
406 /* The size of the small data section. */
407 static unsigned int g_switch_value = 8;
408 /* Whether the -G option was used. */
409 static int g_switch_seen = 0;
414 /* If we can determine in advance that GP optimization won't be
415 possible, we can skip the relaxation stuff that tries to produce
416 GP-relative references. This makes delay slot optimization work
419 This function can only provide a guess, but it seems to work for
420 gcc output. It needs to guess right for gcc, otherwise gcc
421 will put what it thinks is a GP-relative instruction in a branch
424 I don't know if a fix is needed for the SVR4_PIC mode. I've only
425 fixed it for the non-PIC mode. KR 95/04/07 */
426 static int nopic_need_relax (symbolS *, int);
428 /* handle of the OPCODE hash table */
429 static struct hash_control *op_hash = NULL;
431 /* The opcode hash table we use for the mips16. */
432 static struct hash_control *mips16_op_hash = NULL;
434 /* This array holds the chars that always start a comment. If the
435 pre-processor is disabled, these aren't very useful */
436 const char comment_chars[] = "#";
438 /* This array holds the chars that only start a comment at the beginning of
439 a line. If the line seems to have the form '# 123 filename'
440 .line and .file directives will appear in the pre-processed output */
441 /* Note that input_file.c hand checks for '#' at the beginning of the
442 first line of the input file. This is because the compiler outputs
443 #NO_APP at the beginning of its output. */
444 /* Also note that C style comments are always supported. */
445 const char line_comment_chars[] = "#";
447 /* This array holds machine specific line separator characters. */
448 const char line_separator_chars[] = ";";
450 /* Chars that can be used to separate mant from exp in floating point nums */
451 const char EXP_CHARS[] = "eE";
453 /* Chars that mean this number is a floating point constant */
456 const char FLT_CHARS[] = "rRsSfFdDxXpP";
458 /* Also be aware that MAXIMUM_NUMBER_OF_CHARS_FOR_FLOAT may have to be
459 changed in read.c . Ideally it shouldn't have to know about it at all,
460 but nothing is ideal around here.
463 static char *insn_error;
465 static int auto_align = 1;
467 /* When outputting SVR4 PIC code, the assembler needs to know the
468 offset in the stack frame from which to restore the $gp register.
469 This is set by the .cprestore pseudo-op, and saved in this
471 static offsetT mips_cprestore_offset = -1;
473 /* Similar for NewABI PIC code, where $gp is callee-saved. NewABI has some
474 more optimizations, it can use a register value instead of a memory-saved
475 offset and even an other register than $gp as global pointer. */
476 static offsetT mips_cpreturn_offset = -1;
477 static int mips_cpreturn_register = -1;
478 static int mips_gp_register = GP;
479 static int mips_gprel_offset = 0;
481 /* Whether mips_cprestore_offset has been set in the current function
482 (or whether it has already been warned about, if not). */
483 static int mips_cprestore_valid = 0;
485 /* This is the register which holds the stack frame, as set by the
486 .frame pseudo-op. This is needed to implement .cprestore. */
487 static int mips_frame_reg = SP;
489 /* Whether mips_frame_reg has been set in the current function
490 (or whether it has already been warned about, if not). */
491 static int mips_frame_reg_valid = 0;
493 /* To output NOP instructions correctly, we need to keep information
494 about the previous two instructions. */
496 /* Whether we are optimizing. The default value of 2 means to remove
497 unneeded NOPs and swap branch instructions when possible. A value
498 of 1 means to not swap branches. A value of 0 means to always
500 static int mips_optimize = 2;
502 /* Debugging level. -g sets this to 2. -gN sets this to N. -g0 is
503 equivalent to seeing no -g option at all. */
504 static int mips_debug = 0;
506 /* The previous instruction. */
507 static struct mips_cl_insn prev_insn;
509 /* The instruction before prev_insn. */
510 static struct mips_cl_insn prev_prev_insn;
512 /* If we don't want information for prev_insn or prev_prev_insn, we
513 point the insn_mo field at this dummy integer. */
514 static const struct mips_opcode dummy_opcode = { NULL, NULL, 0, 0, 0, 0 };
516 /* Non-zero if prev_insn is valid. */
517 static int prev_insn_valid;
519 /* The frag for the previous instruction. */
520 static struct frag *prev_insn_frag;
522 /* The offset into prev_insn_frag for the previous instruction. */
523 static long prev_insn_where;
525 /* The reloc type for the previous instruction, if any. */
526 static bfd_reloc_code_real_type prev_insn_reloc_type[3];
528 /* The reloc for the previous instruction, if any. */
529 static fixS *prev_insn_fixp[3];
531 /* Non-zero if the previous instruction was in a delay slot. */
532 static int prev_insn_is_delay_slot;
534 /* Non-zero if the previous instruction was in a .set noreorder. */
535 static int prev_insn_unreordered;
537 /* Non-zero if the previous instruction uses an extend opcode (if
539 static int prev_insn_extended;
541 /* Non-zero if the previous previous instruction was in a .set
543 static int prev_prev_insn_unreordered;
545 /* If this is set, it points to a frag holding nop instructions which
546 were inserted before the start of a noreorder section. If those
547 nops turn out to be unnecessary, the size of the frag can be
549 static fragS *prev_nop_frag;
551 /* The number of nop instructions we created in prev_nop_frag. */
552 static int prev_nop_frag_holds;
554 /* The number of nop instructions that we know we need in
556 static int prev_nop_frag_required;
558 /* The number of instructions we've seen since prev_nop_frag. */
559 static int prev_nop_frag_since;
561 /* For ECOFF and ELF, relocations against symbols are done in two
562 parts, with a HI relocation and a LO relocation. Each relocation
563 has only 16 bits of space to store an addend. This means that in
564 order for the linker to handle carries correctly, it must be able
565 to locate both the HI and the LO relocation. This means that the
566 relocations must appear in order in the relocation table.
568 In order to implement this, we keep track of each unmatched HI
569 relocation. We then sort them so that they immediately precede the
570 corresponding LO relocation. */
575 struct mips_hi_fixup *next;
578 /* The section this fixup is in. */
582 /* The list of unmatched HI relocs. */
584 static struct mips_hi_fixup *mips_hi_fixup_list;
586 /* The frag containing the last explicit relocation operator.
587 Null if explicit relocations have not been used. */
589 static fragS *prev_reloc_op_frag;
591 /* Map normal MIPS register numbers to mips16 register numbers. */
593 #define X ILLEGAL_REG
594 static const int mips32_to_16_reg_map[] =
596 X, X, 2, 3, 4, 5, 6, 7,
597 X, X, X, X, X, X, X, X,
598 0, 1, X, X, X, X, X, X,
599 X, X, X, X, X, X, X, X
603 /* Map mips16 register numbers to normal MIPS register numbers. */
605 static const unsigned int mips16_to_32_reg_map[] =
607 16, 17, 2, 3, 4, 5, 6, 7
610 static int mips_fix_4122_bugs;
612 /* We don't relax branches by default, since this causes us to expand
613 `la .l2 - .l1' if there's a branch between .l1 and .l2, because we
614 fail to compute the offset before expanding the macro to the most
615 efficient expansion. */
617 static int mips_relax_branch;
619 /* The expansion of many macros depends on the type of symbol that
620 they refer to. For example, when generating position-dependent code,
621 a macro that refers to a symbol may have two different expansions,
622 one which uses GP-relative addresses and one which uses absolute
623 addresses. When generating SVR4-style PIC, a macro may have
624 different expansions for local and global symbols.
626 We handle these situations by generating both sequences and putting
627 them in variant frags. In position-dependent code, the first sequence
628 will be the GP-relative one and the second sequence will be the
629 absolute one. In SVR4 PIC, the first sequence will be for global
630 symbols and the second will be for local symbols.
632 The frag's "subtype" is RELAX_ENCODE (FIRST, SECOND), where FIRST and
633 SECOND are the lengths of the two sequences in bytes. These fields
634 can be extracted using RELAX_FIRST() and RELAX_SECOND(). In addition,
635 the subtype has the following flags:
638 Set if it has been decided that we should use the second
639 sequence instead of the first.
642 Set in the first variant frag if the macro's second implementation
643 is longer than its first. This refers to the macro as a whole,
644 not an individual relaxation.
647 Set in the first variant frag if the macro appeared in a .set nomacro
648 block and if one alternative requires a warning but the other does not.
651 Like RELAX_NOMACRO, but indicates that the macro appears in a branch
654 The frag's "opcode" points to the first fixup for relaxable code.
656 Relaxable macros are generated using a sequence such as:
658 relax_start (SYMBOL);
659 ... generate first expansion ...
661 ... generate second expansion ...
664 The code and fixups for the unwanted alternative are discarded
665 by md_convert_frag. */
666 #define RELAX_ENCODE(FIRST, SECOND) (((FIRST) << 8) | (SECOND))
668 #define RELAX_FIRST(X) (((X) >> 8) & 0xff)
669 #define RELAX_SECOND(X) ((X) & 0xff)
670 #define RELAX_USE_SECOND 0x10000
671 #define RELAX_SECOND_LONGER 0x20000
672 #define RELAX_NOMACRO 0x40000
673 #define RELAX_DELAY_SLOT 0x80000
675 /* Branch without likely bit. If label is out of range, we turn:
677 beq reg1, reg2, label
687 with the following opcode replacements:
694 bltzal <-> bgezal (with jal label instead of j label)
696 Even though keeping the delay slot instruction in the delay slot of
697 the branch would be more efficient, it would be very tricky to do
698 correctly, because we'd have to introduce a variable frag *after*
699 the delay slot instruction, and expand that instead. Let's do it
700 the easy way for now, even if the branch-not-taken case now costs
701 one additional instruction. Out-of-range branches are not supposed
702 to be common, anyway.
704 Branch likely. If label is out of range, we turn:
706 beql reg1, reg2, label
707 delay slot (annulled if branch not taken)
716 delay slot (executed only if branch taken)
719 It would be possible to generate a shorter sequence by losing the
720 likely bit, generating something like:
725 delay slot (executed only if branch taken)
737 bltzall -> bgezal (with jal label instead of j label)
738 bgezall -> bltzal (ditto)
741 but it's not clear that it would actually improve performance. */
742 #define RELAX_BRANCH_ENCODE(uncond, likely, link, toofar) \
745 | ((toofar) ? 1 : 0) \
747 | ((likely) ? 4 : 0) \
748 | ((uncond) ? 8 : 0)))
749 #define RELAX_BRANCH_P(i) (((i) & 0xf0000000) == 0xc0000000)
750 #define RELAX_BRANCH_UNCOND(i) (((i) & 8) != 0)
751 #define RELAX_BRANCH_LIKELY(i) (((i) & 4) != 0)
752 #define RELAX_BRANCH_LINK(i) (((i) & 2) != 0)
753 #define RELAX_BRANCH_TOOFAR(i) (((i) & 1) != 0)
755 /* For mips16 code, we use an entirely different form of relaxation.
756 mips16 supports two versions of most instructions which take
757 immediate values: a small one which takes some small value, and a
758 larger one which takes a 16 bit value. Since branches also follow
759 this pattern, relaxing these values is required.
761 We can assemble both mips16 and normal MIPS code in a single
762 object. Therefore, we need to support this type of relaxation at
763 the same time that we support the relaxation described above. We
764 use the high bit of the subtype field to distinguish these cases.
766 The information we store for this type of relaxation is the
767 argument code found in the opcode file for this relocation, whether
768 the user explicitly requested a small or extended form, and whether
769 the relocation is in a jump or jal delay slot. That tells us the
770 size of the value, and how it should be stored. We also store
771 whether the fragment is considered to be extended or not. We also
772 store whether this is known to be a branch to a different section,
773 whether we have tried to relax this frag yet, and whether we have
774 ever extended a PC relative fragment because of a shift count. */
775 #define RELAX_MIPS16_ENCODE(type, small, ext, dslot, jal_dslot) \
778 | ((small) ? 0x100 : 0) \
779 | ((ext) ? 0x200 : 0) \
780 | ((dslot) ? 0x400 : 0) \
781 | ((jal_dslot) ? 0x800 : 0))
782 #define RELAX_MIPS16_P(i) (((i) & 0xc0000000) == 0x80000000)
783 #define RELAX_MIPS16_TYPE(i) ((i) & 0xff)
784 #define RELAX_MIPS16_USER_SMALL(i) (((i) & 0x100) != 0)
785 #define RELAX_MIPS16_USER_EXT(i) (((i) & 0x200) != 0)
786 #define RELAX_MIPS16_DSLOT(i) (((i) & 0x400) != 0)
787 #define RELAX_MIPS16_JAL_DSLOT(i) (((i) & 0x800) != 0)
788 #define RELAX_MIPS16_EXTENDED(i) (((i) & 0x1000) != 0)
789 #define RELAX_MIPS16_MARK_EXTENDED(i) ((i) | 0x1000)
790 #define RELAX_MIPS16_CLEAR_EXTENDED(i) ((i) &~ 0x1000)
791 #define RELAX_MIPS16_LONG_BRANCH(i) (((i) & 0x2000) != 0)
792 #define RELAX_MIPS16_MARK_LONG_BRANCH(i) ((i) | 0x2000)
793 #define RELAX_MIPS16_CLEAR_LONG_BRANCH(i) ((i) &~ 0x2000)
795 /* Is the given value a sign-extended 32-bit value? */
796 #define IS_SEXT_32BIT_NUM(x) \
797 (((x) &~ (offsetT) 0x7fffffff) == 0 \
798 || (((x) &~ (offsetT) 0x7fffffff) == ~ (offsetT) 0x7fffffff))
800 /* Is the given value a sign-extended 16-bit value? */
801 #define IS_SEXT_16BIT_NUM(x) \
802 (((x) &~ (offsetT) 0x7fff) == 0 \
803 || (((x) &~ (offsetT) 0x7fff) == ~ (offsetT) 0x7fff))
806 /* Global variables used when generating relaxable macros. See the
807 comment above RELAX_ENCODE for more details about how relaxation
810 /* 0 if we're not emitting a relaxable macro.
811 1 if we're emitting the first of the two relaxation alternatives.
812 2 if we're emitting the second alternative. */
815 /* The first relaxable fixup in the current frag. (In other words,
816 the first fixup that refers to relaxable code.) */
819 /* sizes[0] says how many bytes of the first alternative are stored in
820 the current frag. Likewise sizes[1] for the second alternative. */
821 unsigned int sizes[2];
823 /* The symbol on which the choice of sequence depends. */
827 /* Global variables used to decide whether a macro needs a warning. */
829 /* True if the macro is in a branch delay slot. */
830 bfd_boolean delay_slot_p;
832 /* For relaxable macros, sizes[0] is the length of the first alternative
833 in bytes and sizes[1] is the length of the second alternative.
834 For non-relaxable macros, both elements give the length of the
836 unsigned int sizes[2];
838 /* The first variant frag for this macro. */
840 } mips_macro_warning;
842 /* Prototypes for static functions. */
844 #define internalError() \
845 as_fatal (_("internal Error, line %d, %s"), __LINE__, __FILE__)
847 enum mips_regclass { MIPS_GR_REG, MIPS_FP_REG, MIPS16_REG };
849 static void append_insn
850 (struct mips_cl_insn *ip, expressionS *p, bfd_reloc_code_real_type *r);
851 static void mips_no_prev_insn (int);
852 static void mips16_macro_build
853 (expressionS *, const char *, const char *, va_list);
854 static void load_register (int, expressionS *, int);
855 static void macro_start (void);
856 static void macro_end (void);
857 static void macro (struct mips_cl_insn * ip);
858 static void mips16_macro (struct mips_cl_insn * ip);
859 #ifdef LOSING_COMPILER
860 static void macro2 (struct mips_cl_insn * ip);
862 static void mips_ip (char *str, struct mips_cl_insn * ip);
863 static void mips16_ip (char *str, struct mips_cl_insn * ip);
864 static void mips16_immed
865 (char *, unsigned int, int, offsetT, bfd_boolean, bfd_boolean, bfd_boolean,
866 unsigned long *, bfd_boolean *, unsigned short *);
867 static size_t my_getSmallExpression
868 (expressionS *, bfd_reloc_code_real_type *, char *);
869 static void my_getExpression (expressionS *, char *);
870 static void s_align (int);
871 static void s_change_sec (int);
872 static void s_change_section (int);
873 static void s_cons (int);
874 static void s_float_cons (int);
875 static void s_mips_globl (int);
876 static void s_option (int);
877 static void s_mipsset (int);
878 static void s_abicalls (int);
879 static void s_cpload (int);
880 static void s_cpsetup (int);
881 static void s_cplocal (int);
882 static void s_cprestore (int);
883 static void s_cpreturn (int);
884 static void s_gpvalue (int);
885 static void s_gpword (int);
886 static void s_gpdword (int);
887 static void s_cpadd (int);
888 static void s_insn (int);
889 static void md_obj_begin (void);
890 static void md_obj_end (void);
891 static void s_mips_ent (int);
892 static void s_mips_end (int);
893 static void s_mips_frame (int);
894 static void s_mips_mask (int reg_type);
895 static void s_mips_stab (int);
896 static void s_mips_weakext (int);
897 static void s_mips_file (int);
898 static void s_mips_loc (int);
899 static bfd_boolean pic_need_relax (symbolS *, asection *);
900 static int relaxed_branch_length (fragS *, asection *, int);
901 static int validate_mips_insn (const struct mips_opcode *);
903 /* Table and functions used to map between CPU/ISA names, and
904 ISA levels, and CPU numbers. */
908 const char *name; /* CPU or ISA name. */
909 int is_isa; /* Is this an ISA? (If 0, a CPU.) */
910 int isa; /* ISA level. */
911 int cpu; /* CPU number (default CPU if ISA). */
914 static const struct mips_cpu_info *mips_parse_cpu (const char *, const char *);
915 static const struct mips_cpu_info *mips_cpu_info_from_isa (int);
916 static const struct mips_cpu_info *mips_cpu_info_from_arch (int);
920 The following pseudo-ops from the Kane and Heinrich MIPS book
921 should be defined here, but are currently unsupported: .alias,
922 .galive, .gjaldef, .gjrlive, .livereg, .noalias.
924 The following pseudo-ops from the Kane and Heinrich MIPS book are
925 specific to the type of debugging information being generated, and
926 should be defined by the object format: .aent, .begin, .bend,
927 .bgnb, .end, .endb, .ent, .fmask, .frame, .loc, .mask, .verstamp,
930 The following pseudo-ops from the Kane and Heinrich MIPS book are
931 not MIPS CPU specific, but are also not specific to the object file
932 format. This file is probably the best place to define them, but
933 they are not currently supported: .asm0, .endr, .lab, .repeat,
936 static const pseudo_typeS mips_pseudo_table[] =
938 /* MIPS specific pseudo-ops. */
939 {"option", s_option, 0},
940 {"set", s_mipsset, 0},
941 {"rdata", s_change_sec, 'r'},
942 {"sdata", s_change_sec, 's'},
943 {"livereg", s_ignore, 0},
944 {"abicalls", s_abicalls, 0},
945 {"cpload", s_cpload, 0},
946 {"cpsetup", s_cpsetup, 0},
947 {"cplocal", s_cplocal, 0},
948 {"cprestore", s_cprestore, 0},
949 {"cpreturn", s_cpreturn, 0},
950 {"gpvalue", s_gpvalue, 0},
951 {"gpword", s_gpword, 0},
952 {"gpdword", s_gpdword, 0},
953 {"cpadd", s_cpadd, 0},
956 /* Relatively generic pseudo-ops that happen to be used on MIPS
958 {"asciiz", stringer, 1},
959 {"bss", s_change_sec, 'b'},
962 {"dword", s_cons, 3},
963 {"weakext", s_mips_weakext, 0},
965 /* These pseudo-ops are defined in read.c, but must be overridden
966 here for one reason or another. */
967 {"align", s_align, 0},
969 {"data", s_change_sec, 'd'},
970 {"double", s_float_cons, 'd'},
971 {"float", s_float_cons, 'f'},
972 {"globl", s_mips_globl, 0},
973 {"global", s_mips_globl, 0},
974 {"hword", s_cons, 1},
979 {"section", s_change_section, 0},
980 {"short", s_cons, 1},
981 {"single", s_float_cons, 'f'},
982 {"stabn", s_mips_stab, 'n'},
983 {"text", s_change_sec, 't'},
986 { "extern", ecoff_directive_extern, 0},
991 static const pseudo_typeS mips_nonecoff_pseudo_table[] =
993 /* These pseudo-ops should be defined by the object file format.
994 However, a.out doesn't support them, so we have versions here. */
995 {"aent", s_mips_ent, 1},
996 {"bgnb", s_ignore, 0},
997 {"end", s_mips_end, 0},
998 {"endb", s_ignore, 0},
999 {"ent", s_mips_ent, 0},
1000 {"file", s_mips_file, 0},
1001 {"fmask", s_mips_mask, 'F'},
1002 {"frame", s_mips_frame, 0},
1003 {"loc", s_mips_loc, 0},
1004 {"mask", s_mips_mask, 'R'},
1005 {"verstamp", s_ignore, 0},
1009 extern void pop_insert (const pseudo_typeS *);
1012 mips_pop_insert (void)
1014 pop_insert (mips_pseudo_table);
1015 if (! ECOFF_DEBUGGING)
1016 pop_insert (mips_nonecoff_pseudo_table);
1019 /* Symbols labelling the current insn. */
1021 struct insn_label_list
1023 struct insn_label_list *next;
1027 static struct insn_label_list *insn_labels;
1028 static struct insn_label_list *free_insn_labels;
1030 static void mips_clear_insn_labels (void);
1033 mips_clear_insn_labels (void)
1035 register struct insn_label_list **pl;
1037 for (pl = &free_insn_labels; *pl != NULL; pl = &(*pl)->next)
1043 static char *expr_end;
1045 /* Expressions which appear in instructions. These are set by
1048 static expressionS imm_expr;
1049 static expressionS imm2_expr;
1050 static expressionS offset_expr;
1052 /* Relocs associated with imm_expr and offset_expr. */
1054 static bfd_reloc_code_real_type imm_reloc[3]
1055 = {BFD_RELOC_UNUSED, BFD_RELOC_UNUSED, BFD_RELOC_UNUSED};
1056 static bfd_reloc_code_real_type offset_reloc[3]
1057 = {BFD_RELOC_UNUSED, BFD_RELOC_UNUSED, BFD_RELOC_UNUSED};
1059 /* These are set by mips16_ip if an explicit extension is used. */
1061 static bfd_boolean mips16_small, mips16_ext;
1064 /* The pdr segment for per procedure frame/regmask info. Not used for
1067 static segT pdr_seg;
1070 /* The default target format to use. */
1073 mips_target_format (void)
1075 switch (OUTPUT_FLAVOR)
1077 case bfd_target_aout_flavour:
1078 return target_big_endian ? "a.out-mips-big" : "a.out-mips-little";
1079 case bfd_target_ecoff_flavour:
1080 return target_big_endian ? "ecoff-bigmips" : ECOFF_LITTLE_FORMAT;
1081 case bfd_target_coff_flavour:
1083 case bfd_target_elf_flavour:
1085 /* This is traditional mips. */
1086 return (target_big_endian
1087 ? (HAVE_64BIT_OBJECTS
1088 ? "elf64-tradbigmips"
1090 ? "elf32-ntradbigmips" : "elf32-tradbigmips"))
1091 : (HAVE_64BIT_OBJECTS
1092 ? "elf64-tradlittlemips"
1094 ? "elf32-ntradlittlemips" : "elf32-tradlittlemips")));
1096 return (target_big_endian
1097 ? (HAVE_64BIT_OBJECTS
1100 ? "elf32-nbigmips" : "elf32-bigmips"))
1101 : (HAVE_64BIT_OBJECTS
1102 ? "elf64-littlemips"
1104 ? "elf32-nlittlemips" : "elf32-littlemips")));
1112 /* This function is called once, at assembler startup time. It should
1113 set up all the tables, etc. that the MD part of the assembler will need. */
1118 register const char *retval = NULL;
1122 if (! bfd_set_arch_mach (stdoutput, bfd_arch_mips, file_mips_arch))
1123 as_warn (_("Could not set architecture and machine"));
1125 op_hash = hash_new ();
1127 for (i = 0; i < NUMOPCODES;)
1129 const char *name = mips_opcodes[i].name;
1131 retval = hash_insert (op_hash, name, (void *) &mips_opcodes[i]);
1134 fprintf (stderr, _("internal error: can't hash `%s': %s\n"),
1135 mips_opcodes[i].name, retval);
1136 /* Probably a memory allocation problem? Give up now. */
1137 as_fatal (_("Broken assembler. No assembly attempted."));
1141 if (mips_opcodes[i].pinfo != INSN_MACRO)
1143 if (!validate_mips_insn (&mips_opcodes[i]))
1148 while ((i < NUMOPCODES) && !strcmp (mips_opcodes[i].name, name));
1151 mips16_op_hash = hash_new ();
1154 while (i < bfd_mips16_num_opcodes)
1156 const char *name = mips16_opcodes[i].name;
1158 retval = hash_insert (mips16_op_hash, name, (void *) &mips16_opcodes[i]);
1160 as_fatal (_("internal: can't hash `%s': %s"),
1161 mips16_opcodes[i].name, retval);
1164 if (mips16_opcodes[i].pinfo != INSN_MACRO
1165 && ((mips16_opcodes[i].match & mips16_opcodes[i].mask)
1166 != mips16_opcodes[i].match))
1168 fprintf (stderr, _("internal error: bad mips16 opcode: %s %s\n"),
1169 mips16_opcodes[i].name, mips16_opcodes[i].args);
1174 while (i < bfd_mips16_num_opcodes
1175 && strcmp (mips16_opcodes[i].name, name) == 0);
1179 as_fatal (_("Broken assembler. No assembly attempted."));
1181 /* We add all the general register names to the symbol table. This
1182 helps us detect invalid uses of them. */
1183 for (i = 0; i < 32; i++)
1187 sprintf (buf, "$%d", i);
1188 symbol_table_insert (symbol_new (buf, reg_section, i,
1189 &zero_address_frag));
1191 symbol_table_insert (symbol_new ("$ra", reg_section, RA,
1192 &zero_address_frag));
1193 symbol_table_insert (symbol_new ("$fp", reg_section, FP,
1194 &zero_address_frag));
1195 symbol_table_insert (symbol_new ("$sp", reg_section, SP,
1196 &zero_address_frag));
1197 symbol_table_insert (symbol_new ("$gp", reg_section, GP,
1198 &zero_address_frag));
1199 symbol_table_insert (symbol_new ("$at", reg_section, AT,
1200 &zero_address_frag));
1201 symbol_table_insert (symbol_new ("$kt0", reg_section, KT0,
1202 &zero_address_frag));
1203 symbol_table_insert (symbol_new ("$kt1", reg_section, KT1,
1204 &zero_address_frag));
1205 symbol_table_insert (symbol_new ("$zero", reg_section, ZERO,
1206 &zero_address_frag));
1207 symbol_table_insert (symbol_new ("$pc", reg_section, -1,
1208 &zero_address_frag));
1210 /* If we don't add these register names to the symbol table, they
1211 may end up being added as regular symbols by operand(), and then
1212 make it to the object file as undefined in case they're not
1213 regarded as local symbols. They're local in o32, since `$' is a
1214 local symbol prefix, but not in n32 or n64. */
1215 for (i = 0; i < 8; i++)
1219 sprintf (buf, "$fcc%i", i);
1220 symbol_table_insert (symbol_new (buf, reg_section, -1,
1221 &zero_address_frag));
1224 mips_no_prev_insn (FALSE);
1227 mips_cprmask[0] = 0;
1228 mips_cprmask[1] = 0;
1229 mips_cprmask[2] = 0;
1230 mips_cprmask[3] = 0;
1232 /* set the default alignment for the text section (2**2) */
1233 record_alignment (text_section, 2);
1235 if (USE_GLOBAL_POINTER_OPT)
1236 bfd_set_gp_size (stdoutput, g_switch_value);
1238 if (OUTPUT_FLAVOR == bfd_target_elf_flavour)
1240 /* On a native system, sections must be aligned to 16 byte
1241 boundaries. When configured for an embedded ELF target, we
1243 if (strcmp (TARGET_OS, "elf") != 0)
1245 (void) bfd_set_section_alignment (stdoutput, text_section, 4);
1246 (void) bfd_set_section_alignment (stdoutput, data_section, 4);
1247 (void) bfd_set_section_alignment (stdoutput, bss_section, 4);
1250 /* Create a .reginfo section for register masks and a .mdebug
1251 section for debugging information. */
1259 subseg = now_subseg;
1261 /* The ABI says this section should be loaded so that the
1262 running program can access it. However, we don't load it
1263 if we are configured for an embedded target */
1264 flags = SEC_READONLY | SEC_DATA;
1265 if (strcmp (TARGET_OS, "elf") != 0)
1266 flags |= SEC_ALLOC | SEC_LOAD;
1268 if (mips_abi != N64_ABI)
1270 sec = subseg_new (".reginfo", (subsegT) 0);
1272 bfd_set_section_flags (stdoutput, sec, flags);
1273 bfd_set_section_alignment (stdoutput, sec, HAVE_NEWABI ? 3 : 2);
1276 mips_regmask_frag = frag_more (sizeof (Elf32_External_RegInfo));
1281 /* The 64-bit ABI uses a .MIPS.options section rather than
1282 .reginfo section. */
1283 sec = subseg_new (".MIPS.options", (subsegT) 0);
1284 bfd_set_section_flags (stdoutput, sec, flags);
1285 bfd_set_section_alignment (stdoutput, sec, 3);
1288 /* Set up the option header. */
1290 Elf_Internal_Options opthdr;
1293 opthdr.kind = ODK_REGINFO;
1294 opthdr.size = (sizeof (Elf_External_Options)
1295 + sizeof (Elf64_External_RegInfo));
1298 f = frag_more (sizeof (Elf_External_Options));
1299 bfd_mips_elf_swap_options_out (stdoutput, &opthdr,
1300 (Elf_External_Options *) f);
1302 mips_regmask_frag = frag_more (sizeof (Elf64_External_RegInfo));
1307 if (ECOFF_DEBUGGING)
1309 sec = subseg_new (".mdebug", (subsegT) 0);
1310 (void) bfd_set_section_flags (stdoutput, sec,
1311 SEC_HAS_CONTENTS | SEC_READONLY);
1312 (void) bfd_set_section_alignment (stdoutput, sec, 2);
1315 else if (OUTPUT_FLAVOR == bfd_target_elf_flavour && mips_flag_pdr)
1317 pdr_seg = subseg_new (".pdr", (subsegT) 0);
1318 (void) bfd_set_section_flags (stdoutput, pdr_seg,
1319 SEC_READONLY | SEC_RELOC
1321 (void) bfd_set_section_alignment (stdoutput, pdr_seg, 2);
1325 subseg_set (seg, subseg);
1329 if (! ECOFF_DEBUGGING)
1336 if (! ECOFF_DEBUGGING)
1341 md_assemble (char *str)
1343 struct mips_cl_insn insn;
1344 bfd_reloc_code_real_type unused_reloc[3]
1345 = {BFD_RELOC_UNUSED, BFD_RELOC_UNUSED, BFD_RELOC_UNUSED};
1347 imm_expr.X_op = O_absent;
1348 imm2_expr.X_op = O_absent;
1349 offset_expr.X_op = O_absent;
1350 imm_reloc[0] = BFD_RELOC_UNUSED;
1351 imm_reloc[1] = BFD_RELOC_UNUSED;
1352 imm_reloc[2] = BFD_RELOC_UNUSED;
1353 offset_reloc[0] = BFD_RELOC_UNUSED;
1354 offset_reloc[1] = BFD_RELOC_UNUSED;
1355 offset_reloc[2] = BFD_RELOC_UNUSED;
1357 if (mips_opts.mips16)
1358 mips16_ip (str, &insn);
1361 mips_ip (str, &insn);
1362 DBG ((_("returned from mips_ip(%s) insn_opcode = 0x%x\n"),
1363 str, insn.insn_opcode));
1368 as_bad ("%s `%s'", insn_error, str);
1372 if (insn.insn_mo->pinfo == INSN_MACRO)
1375 if (mips_opts.mips16)
1376 mips16_macro (&insn);
1383 if (imm_expr.X_op != O_absent)
1384 append_insn (&insn, &imm_expr, imm_reloc);
1385 else if (offset_expr.X_op != O_absent)
1386 append_insn (&insn, &offset_expr, offset_reloc);
1388 append_insn (&insn, NULL, unused_reloc);
1392 /* Return true if the given relocation might need a matching %lo().
1393 Note that R_MIPS_GOT16 relocations only need a matching %lo() when
1394 applied to local symbols. */
1396 static inline bfd_boolean
1397 reloc_needs_lo_p (bfd_reloc_code_real_type reloc)
1399 return (reloc == BFD_RELOC_HI16_S
1400 || reloc == BFD_RELOC_MIPS_GOT16);
1403 /* Return true if the given fixup is followed by a matching R_MIPS_LO16
1406 static inline bfd_boolean
1407 fixup_has_matching_lo_p (fixS *fixp)
1409 return (fixp->fx_next != NULL
1410 && fixp->fx_next->fx_r_type == BFD_RELOC_LO16
1411 && fixp->fx_addsy == fixp->fx_next->fx_addsy
1412 && fixp->fx_offset == fixp->fx_next->fx_offset);
1415 /* See whether instruction IP reads register REG. CLASS is the type
1419 insn_uses_reg (struct mips_cl_insn *ip, unsigned int reg,
1420 enum mips_regclass class)
1422 if (class == MIPS16_REG)
1424 assert (mips_opts.mips16);
1425 reg = mips16_to_32_reg_map[reg];
1426 class = MIPS_GR_REG;
1429 /* Don't report on general register ZERO, since it never changes. */
1430 if (class == MIPS_GR_REG && reg == ZERO)
1433 if (class == MIPS_FP_REG)
1435 assert (! mips_opts.mips16);
1436 /* If we are called with either $f0 or $f1, we must check $f0.
1437 This is not optimal, because it will introduce an unnecessary
1438 NOP between "lwc1 $f0" and "swc1 $f1". To fix this we would
1439 need to distinguish reading both $f0 and $f1 or just one of
1440 them. Note that we don't have to check the other way,
1441 because there is no instruction that sets both $f0 and $f1
1442 and requires a delay. */
1443 if ((ip->insn_mo->pinfo & INSN_READ_FPR_S)
1444 && ((((ip->insn_opcode >> OP_SH_FS) & OP_MASK_FS) &~(unsigned)1)
1445 == (reg &~ (unsigned) 1)))
1447 if ((ip->insn_mo->pinfo & INSN_READ_FPR_T)
1448 && ((((ip->insn_opcode >> OP_SH_FT) & OP_MASK_FT) &~(unsigned)1)
1449 == (reg &~ (unsigned) 1)))
1452 else if (! mips_opts.mips16)
1454 if ((ip->insn_mo->pinfo & INSN_READ_GPR_S)
1455 && ((ip->insn_opcode >> OP_SH_RS) & OP_MASK_RS) == reg)
1457 if ((ip->insn_mo->pinfo & INSN_READ_GPR_T)
1458 && ((ip->insn_opcode >> OP_SH_RT) & OP_MASK_RT) == reg)
1463 if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_X)
1464 && (mips16_to_32_reg_map[((ip->insn_opcode >> MIPS16OP_SH_RX)
1465 & MIPS16OP_MASK_RX)]
1468 if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_Y)
1469 && (mips16_to_32_reg_map[((ip->insn_opcode >> MIPS16OP_SH_RY)
1470 & MIPS16OP_MASK_RY)]
1473 if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_Z)
1474 && (mips16_to_32_reg_map[((ip->insn_opcode >> MIPS16OP_SH_MOVE32Z)
1475 & MIPS16OP_MASK_MOVE32Z)]
1478 if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_T) && reg == TREG)
1480 if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_SP) && reg == SP)
1482 if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_31) && reg == RA)
1484 if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_GPR_X)
1485 && ((ip->insn_opcode >> MIPS16OP_SH_REGR32)
1486 & MIPS16OP_MASK_REGR32) == reg)
1493 /* This function returns true if modifying a register requires a
1497 reg_needs_delay (unsigned int reg)
1499 unsigned long prev_pinfo;
1501 prev_pinfo = prev_insn.insn_mo->pinfo;
1502 if (! mips_opts.noreorder
1503 && (((prev_pinfo & INSN_LOAD_MEMORY_DELAY)
1504 && ! gpr_interlocks)
1505 || ((prev_pinfo & INSN_LOAD_COPROC_DELAY)
1506 && ! cop_interlocks)))
1508 /* A load from a coprocessor or from memory. All load delays
1509 delay the use of general register rt for one instruction. */
1510 /* Itbl support may require additional care here. */
1511 know (prev_pinfo & INSN_WRITE_GPR_T);
1512 if (reg == ((prev_insn.insn_opcode >> OP_SH_RT) & OP_MASK_RT))
1519 /* Mark instruction labels in mips16 mode. This permits the linker to
1520 handle them specially, such as generating jalx instructions when
1521 needed. We also make them odd for the duration of the assembly, in
1522 order to generate the right sort of code. We will make them even
1523 in the adjust_symtab routine, while leaving them marked. This is
1524 convenient for the debugger and the disassembler. The linker knows
1525 to make them odd again. */
1528 mips16_mark_labels (void)
1530 if (mips_opts.mips16)
1532 struct insn_label_list *l;
1535 for (l = insn_labels; l != NULL; l = l->next)
1538 if (OUTPUT_FLAVOR == bfd_target_elf_flavour)
1539 S_SET_OTHER (l->label, STO_MIPS16);
1541 val = S_GET_VALUE (l->label);
1543 S_SET_VALUE (l->label, val + 1);
1548 /* End the current frag. Make it a variant frag and record the
1552 relax_close_frag (void)
1554 mips_macro_warning.first_frag = frag_now;
1555 frag_var (rs_machine_dependent, 0, 0,
1556 RELAX_ENCODE (mips_relax.sizes[0], mips_relax.sizes[1]),
1557 mips_relax.symbol, 0, (char *) mips_relax.first_fixup);
1559 memset (&mips_relax.sizes, 0, sizeof (mips_relax.sizes));
1560 mips_relax.first_fixup = 0;
1563 /* Start a new relaxation sequence whose expansion depends on SYMBOL.
1564 See the comment above RELAX_ENCODE for more details. */
1567 relax_start (symbolS *symbol)
1569 assert (mips_relax.sequence == 0);
1570 mips_relax.sequence = 1;
1571 mips_relax.symbol = symbol;
1574 /* Start generating the second version of a relaxable sequence.
1575 See the comment above RELAX_ENCODE for more details. */
1580 assert (mips_relax.sequence == 1);
1581 mips_relax.sequence = 2;
1584 /* End the current relaxable sequence. */
1589 assert (mips_relax.sequence == 2);
1590 relax_close_frag ();
1591 mips_relax.sequence = 0;
1594 /* Output an instruction. IP is the instruction information.
1595 ADDRESS_EXPR is an operand of the instruction to be used with
1599 append_insn (struct mips_cl_insn *ip, expressionS *address_expr,
1600 bfd_reloc_code_real_type *reloc_type)
1602 register unsigned long prev_pinfo, pinfo;
1606 relax_stateT prev_insn_frag_type = 0;
1607 bfd_boolean relaxed_branch = FALSE;
1608 bfd_boolean force_new_frag = FALSE;
1610 /* Mark instruction labels in mips16 mode. */
1611 mips16_mark_labels ();
1613 prev_pinfo = prev_insn.insn_mo->pinfo;
1614 pinfo = ip->insn_mo->pinfo;
1616 if (mips_relax.sequence != 2
1617 && (!mips_opts.noreorder || prev_nop_frag != NULL))
1621 /* If the previous insn required any delay slots, see if we need
1622 to insert a NOP or two. There are eight kinds of possible
1623 hazards, of which an instruction can have at most one type.
1624 (1) a load from memory delay
1625 (2) a load from a coprocessor delay
1626 (3) an unconditional branch delay
1627 (4) a conditional branch delay
1628 (5) a move to coprocessor register delay
1629 (6) a load coprocessor register from memory delay
1630 (7) a coprocessor condition code delay
1631 (8) a HI/LO special register delay
1633 There are a lot of optimizations we could do that we don't.
1634 In particular, we do not, in general, reorder instructions.
1635 If you use gcc with optimization, it will reorder
1636 instructions and generally do much more optimization then we
1637 do here; repeating all that work in the assembler would only
1638 benefit hand written assembly code, and does not seem worth
1641 /* This is how a NOP is emitted. */
1642 #define emit_nop() \
1644 ? md_number_to_chars (frag_more (2), 0x6500, 2) \
1645 : md_number_to_chars (frag_more (4), 0, 4))
1647 /* The previous insn might require a delay slot, depending upon
1648 the contents of the current insn. */
1649 if (! mips_opts.mips16
1650 && (((prev_pinfo & INSN_LOAD_MEMORY_DELAY)
1651 && ! gpr_interlocks)
1652 || ((prev_pinfo & INSN_LOAD_COPROC_DELAY)
1653 && ! cop_interlocks)))
1655 /* A load from a coprocessor or from memory. All load
1656 delays delay the use of general register rt for one
1658 /* Itbl support may require additional care here. */
1659 know (prev_pinfo & INSN_WRITE_GPR_T);
1660 if (mips_optimize == 0
1661 || insn_uses_reg (ip,
1662 ((prev_insn.insn_opcode >> OP_SH_RT)
1667 else if (! mips_opts.mips16
1668 && (((prev_pinfo & INSN_COPROC_MOVE_DELAY)
1669 && ! cop_interlocks)
1670 || ((prev_pinfo & INSN_COPROC_MEMORY_DELAY)
1671 && ! cop_mem_interlocks)))
1673 /* A generic coprocessor delay. The previous instruction
1674 modified a coprocessor general or control register. If
1675 it modified a control register, we need to avoid any
1676 coprocessor instruction (this is probably not always
1677 required, but it sometimes is). If it modified a general
1678 register, we avoid using that register.
1680 This case is not handled very well. There is no special
1681 knowledge of CP0 handling, and the coprocessors other
1682 than the floating point unit are not distinguished at
1684 /* Itbl support may require additional care here. FIXME!
1685 Need to modify this to include knowledge about
1686 user specified delays! */
1687 if (prev_pinfo & INSN_WRITE_FPR_T)
1689 if (mips_optimize == 0
1690 || insn_uses_reg (ip,
1691 ((prev_insn.insn_opcode >> OP_SH_FT)
1696 else if (prev_pinfo & INSN_WRITE_FPR_S)
1698 if (mips_optimize == 0
1699 || insn_uses_reg (ip,
1700 ((prev_insn.insn_opcode >> OP_SH_FS)
1707 /* We don't know exactly what the previous instruction
1708 does. If the current instruction uses a coprocessor
1709 register, we must insert a NOP. If previous
1710 instruction may set the condition codes, and the
1711 current instruction uses them, we must insert two
1713 /* Itbl support may require additional care here. */
1714 if (mips_optimize == 0
1715 || ((prev_pinfo & INSN_WRITE_COND_CODE)
1716 && (pinfo & INSN_READ_COND_CODE)))
1718 else if (pinfo & INSN_COP)
1722 else if (! mips_opts.mips16
1723 && (prev_pinfo & INSN_WRITE_COND_CODE)
1724 && ! cop_interlocks)
1726 /* The previous instruction sets the coprocessor condition
1727 codes, but does not require a general coprocessor delay
1728 (this means it is a floating point comparison
1729 instruction). If this instruction uses the condition
1730 codes, we need to insert a single NOP. */
1731 /* Itbl support may require additional care here. */
1732 if (mips_optimize == 0
1733 || (pinfo & INSN_READ_COND_CODE))
1737 /* If we're fixing up mfhi/mflo for the r7000 and the
1738 previous insn was an mfhi/mflo and the current insn
1739 reads the register that the mfhi/mflo wrote to, then
1742 else if (mips_7000_hilo_fix
1743 && MF_HILO_INSN (prev_pinfo)
1744 && insn_uses_reg (ip, ((prev_insn.insn_opcode >> OP_SH_RD)
1751 /* If we're fixing up mfhi/mflo for the r7000 and the
1752 2nd previous insn was an mfhi/mflo and the current insn
1753 reads the register that the mfhi/mflo wrote to, then
1756 else if (mips_7000_hilo_fix
1757 && MF_HILO_INSN (prev_prev_insn.insn_opcode)
1758 && insn_uses_reg (ip, ((prev_prev_insn.insn_opcode >> OP_SH_RD)
1766 else if (prev_pinfo & INSN_READ_LO)
1768 /* The previous instruction reads the LO register; if the
1769 current instruction writes to the LO register, we must
1770 insert two NOPS. Some newer processors have interlocks.
1771 Also the tx39's multiply instructions can be executed
1772 immediately after a read from HI/LO (without the delay),
1773 though the tx39's divide insns still do require the
1775 if (! (hilo_interlocks
1776 || (mips_opts.arch == CPU_R3900 && (pinfo & INSN_MULT)))
1777 && (mips_optimize == 0
1778 || (pinfo & INSN_WRITE_LO)))
1780 /* Most mips16 branch insns don't have a delay slot.
1781 If a read from LO is immediately followed by a branch
1782 to a write to LO we have a read followed by a write
1783 less than 2 insns away. We assume the target of
1784 a branch might be a write to LO, and insert a nop
1785 between a read and an immediately following branch. */
1786 else if (mips_opts.mips16
1787 && (mips_optimize == 0
1788 || (pinfo & MIPS16_INSN_BRANCH)))
1791 else if (prev_insn.insn_mo->pinfo & INSN_READ_HI)
1793 /* The previous instruction reads the HI register; if the
1794 current instruction writes to the HI register, we must
1795 insert a NOP. Some newer processors have interlocks.
1796 Also the note tx39's multiply above. */
1797 if (! (hilo_interlocks
1798 || (mips_opts.arch == CPU_R3900 && (pinfo & INSN_MULT)))
1799 && (mips_optimize == 0
1800 || (pinfo & INSN_WRITE_HI)))
1802 /* Most mips16 branch insns don't have a delay slot.
1803 If a read from HI is immediately followed by a branch
1804 to a write to HI we have a read followed by a write
1805 less than 2 insns away. We assume the target of
1806 a branch might be a write to HI, and insert a nop
1807 between a read and an immediately following branch. */
1808 else if (mips_opts.mips16
1809 && (mips_optimize == 0
1810 || (pinfo & MIPS16_INSN_BRANCH)))
1814 /* If the previous instruction was in a noreorder section, then
1815 we don't want to insert the nop after all. */
1816 /* Itbl support may require additional care here. */
1817 if (prev_insn_unreordered)
1820 /* There are two cases which require two intervening
1821 instructions: 1) setting the condition codes using a move to
1822 coprocessor instruction which requires a general coprocessor
1823 delay and then reading the condition codes 2) reading the HI
1824 or LO register and then writing to it (except on processors
1825 which have interlocks). If we are not already emitting a NOP
1826 instruction, we must check for these cases compared to the
1827 instruction previous to the previous instruction. */
1828 if ((! mips_opts.mips16
1829 && (prev_prev_insn.insn_mo->pinfo & INSN_COPROC_MOVE_DELAY)
1830 && (prev_prev_insn.insn_mo->pinfo & INSN_WRITE_COND_CODE)
1831 && (pinfo & INSN_READ_COND_CODE)
1832 && ! cop_interlocks)
1833 || ((prev_prev_insn.insn_mo->pinfo & INSN_READ_LO)
1834 && (pinfo & INSN_WRITE_LO)
1835 && ! (hilo_interlocks
1836 || (mips_opts.arch == CPU_R3900 && (pinfo & INSN_MULT))))
1837 || ((prev_prev_insn.insn_mo->pinfo & INSN_READ_HI)
1838 && (pinfo & INSN_WRITE_HI)
1839 && ! (hilo_interlocks
1840 || (mips_opts.arch == CPU_R3900 && (pinfo & INSN_MULT)))))
1845 if (prev_prev_insn_unreordered)
1848 if (prev_prev_nop && nops == 0)
1851 if (mips_fix_4122_bugs && prev_insn.insn_mo->name)
1853 /* We're out of bits in pinfo, so we must resort to string
1854 ops here. Shortcuts are selected based on opcodes being
1855 limited to the VR4122 instruction set. */
1857 const char *pn = prev_insn.insn_mo->name;
1858 const char *tn = ip->insn_mo->name;
1859 if (strncmp(pn, "macc", 4) == 0
1860 || strncmp(pn, "dmacc", 5) == 0)
1862 /* Errata 21 - [D]DIV[U] after [D]MACC */
1863 if (strstr (tn, "div"))
1868 /* Errata 23 - Continuous DMULT[U]/DMACC instructions */
1869 if (pn[0] == 'd' /* dmacc */
1870 && (strncmp(tn, "dmult", 5) == 0
1871 || strncmp(tn, "dmacc", 5) == 0))
1876 /* Errata 24 - MT{LO,HI} after [D]MACC */
1877 if (strcmp (tn, "mtlo") == 0
1878 || strcmp (tn, "mthi") == 0)
1884 else if (strncmp(pn, "dmult", 5) == 0
1885 && (strncmp(tn, "dmult", 5) == 0
1886 || strncmp(tn, "dmacc", 5) == 0))
1888 /* Here is the rest of errata 23. */
1891 if (nops < min_nops)
1895 /* If we are being given a nop instruction, don't bother with
1896 one of the nops we would otherwise output. This will only
1897 happen when a nop instruction is used with mips_optimize set
1900 && ! mips_opts.noreorder
1901 && ip->insn_opcode == (unsigned) (mips_opts.mips16 ? 0x6500 : 0))
1904 /* Now emit the right number of NOP instructions. */
1905 if (nops > 0 && ! mips_opts.noreorder)
1908 unsigned long old_frag_offset;
1910 struct insn_label_list *l;
1912 old_frag = frag_now;
1913 old_frag_offset = frag_now_fix ();
1915 for (i = 0; i < nops; i++)
1920 listing_prev_line ();
1921 /* We may be at the start of a variant frag. In case we
1922 are, make sure there is enough space for the frag
1923 after the frags created by listing_prev_line. The
1924 argument to frag_grow here must be at least as large
1925 as the argument to all other calls to frag_grow in
1926 this file. We don't have to worry about being in the
1927 middle of a variant frag, because the variants insert
1928 all needed nop instructions themselves. */
1932 for (l = insn_labels; l != NULL; l = l->next)
1936 assert (S_GET_SEGMENT (l->label) == now_seg);
1937 symbol_set_frag (l->label, frag_now);
1938 val = (valueT) frag_now_fix ();
1939 /* mips16 text labels are stored as odd. */
1940 if (mips_opts.mips16)
1942 S_SET_VALUE (l->label, val);
1945 #ifndef NO_ECOFF_DEBUGGING
1946 if (ECOFF_DEBUGGING)
1947 ecoff_fix_loc (old_frag, old_frag_offset);
1950 else if (prev_nop_frag != NULL)
1952 /* We have a frag holding nops we may be able to remove. If
1953 we don't need any nops, we can decrease the size of
1954 prev_nop_frag by the size of one instruction. If we do
1955 need some nops, we count them in prev_nops_required. */
1956 if (prev_nop_frag_since == 0)
1960 prev_nop_frag->fr_fix -= mips_opts.mips16 ? 2 : 4;
1961 --prev_nop_frag_holds;
1964 prev_nop_frag_required += nops;
1968 if (prev_prev_nop == 0)
1970 prev_nop_frag->fr_fix -= mips_opts.mips16 ? 2 : 4;
1971 --prev_nop_frag_holds;
1974 ++prev_nop_frag_required;
1977 if (prev_nop_frag_holds <= prev_nop_frag_required)
1978 prev_nop_frag = NULL;
1980 ++prev_nop_frag_since;
1982 /* Sanity check: by the time we reach the second instruction
1983 after prev_nop_frag, we should have used up all the nops
1984 one way or another. */
1985 assert (prev_nop_frag_since <= 1 || prev_nop_frag == NULL);
1989 /* Record the frag type before frag_var. */
1991 prev_insn_frag_type = prev_insn_frag->fr_type;
1994 && *reloc_type == BFD_RELOC_16_PCREL_S2
1995 && (pinfo & INSN_UNCOND_BRANCH_DELAY || pinfo & INSN_COND_BRANCH_DELAY
1996 || pinfo & INSN_COND_BRANCH_LIKELY)
1997 && mips_relax_branch
1998 /* Don't try branch relaxation within .set nomacro, or within
1999 .set noat if we use $at for PIC computations. If it turns
2000 out that the branch was out-of-range, we'll get an error. */
2001 && !mips_opts.warn_about_macros
2002 && !(mips_opts.noat && mips_pic != NO_PIC)
2003 && !mips_opts.mips16)
2005 relaxed_branch = TRUE;
2006 f = frag_var (rs_machine_dependent,
2007 relaxed_branch_length
2009 (pinfo & INSN_UNCOND_BRANCH_DELAY) ? -1
2010 : (pinfo & INSN_COND_BRANCH_LIKELY) ? 1 : 0), 4,
2012 (pinfo & INSN_UNCOND_BRANCH_DELAY,
2013 pinfo & INSN_COND_BRANCH_LIKELY,
2014 pinfo & INSN_WRITE_GPR_31,
2016 address_expr->X_add_symbol,
2017 address_expr->X_add_number,
2019 *reloc_type = BFD_RELOC_UNUSED;
2021 else if (*reloc_type > BFD_RELOC_UNUSED)
2023 /* We need to set up a variant frag. */
2024 assert (mips_opts.mips16 && address_expr != NULL);
2025 f = frag_var (rs_machine_dependent, 4, 0,
2026 RELAX_MIPS16_ENCODE (*reloc_type - BFD_RELOC_UNUSED,
2027 mips16_small, mips16_ext,
2029 & INSN_UNCOND_BRANCH_DELAY),
2030 (*prev_insn_reloc_type
2031 == BFD_RELOC_MIPS16_JMP)),
2032 make_expr_symbol (address_expr), 0, NULL);
2034 else if (mips_opts.mips16
2036 && *reloc_type != BFD_RELOC_MIPS16_JMP)
2038 /* Make sure there is enough room to swap this instruction with
2039 a following jump instruction. */
2045 if (mips_opts.mips16
2046 && mips_opts.noreorder
2047 && (prev_pinfo & INSN_UNCOND_BRANCH_DELAY) != 0)
2048 as_warn (_("extended instruction in delay slot"));
2050 if (mips_relax.sequence)
2052 /* If we've reached the end of this frag, turn it into a variant
2053 frag and record the information for the instructions we've
2055 if (frag_room () < 4)
2056 relax_close_frag ();
2057 mips_relax.sizes[mips_relax.sequence - 1] += 4;
2060 if (mips_relax.sequence != 2)
2061 mips_macro_warning.sizes[0] += 4;
2062 if (mips_relax.sequence != 1)
2063 mips_macro_warning.sizes[1] += 4;
2068 fixp[0] = fixp[1] = fixp[2] = NULL;
2069 if (address_expr != NULL && *reloc_type < BFD_RELOC_UNUSED)
2071 if (address_expr->X_op == O_constant)
2075 switch (*reloc_type)
2078 ip->insn_opcode |= address_expr->X_add_number;
2081 case BFD_RELOC_MIPS_HIGHEST:
2082 tmp = (address_expr->X_add_number
2083 + ((valueT) 0x8000 << 32) + 0x80008000) >> 16;
2085 ip->insn_opcode |= (tmp >> 16) & 0xffff;
2088 case BFD_RELOC_MIPS_HIGHER:
2089 tmp = (address_expr->X_add_number + 0x80008000) >> 16;
2090 ip->insn_opcode |= (tmp >> 16) & 0xffff;
2093 case BFD_RELOC_HI16_S:
2094 ip->insn_opcode |= ((address_expr->X_add_number + 0x8000)
2098 case BFD_RELOC_HI16:
2099 ip->insn_opcode |= (address_expr->X_add_number >> 16) & 0xffff;
2102 case BFD_RELOC_LO16:
2103 case BFD_RELOC_MIPS_GOT_DISP:
2104 ip->insn_opcode |= address_expr->X_add_number & 0xffff;
2107 case BFD_RELOC_MIPS_JMP:
2108 if ((address_expr->X_add_number & 3) != 0)
2109 as_bad (_("jump to misaligned address (0x%lx)"),
2110 (unsigned long) address_expr->X_add_number);
2111 if (address_expr->X_add_number & ~0xfffffff)
2112 as_bad (_("jump address range overflow (0x%lx)"),
2113 (unsigned long) address_expr->X_add_number);
2114 ip->insn_opcode |= (address_expr->X_add_number >> 2) & 0x3ffffff;
2117 case BFD_RELOC_MIPS16_JMP:
2118 if ((address_expr->X_add_number & 3) != 0)
2119 as_bad (_("jump to misaligned address (0x%lx)"),
2120 (unsigned long) address_expr->X_add_number);
2121 if (address_expr->X_add_number & ~0xfffffff)
2122 as_bad (_("jump address range overflow (0x%lx)"),
2123 (unsigned long) address_expr->X_add_number);
2125 (((address_expr->X_add_number & 0x7c0000) << 3)
2126 | ((address_expr->X_add_number & 0xf800000) >> 7)
2127 | ((address_expr->X_add_number & 0x3fffc) >> 2));
2130 case BFD_RELOC_16_PCREL_S2:
2140 reloc_howto_type *howto;
2143 /* In a compound relocation, it is the final (outermost)
2144 operator that determines the relocated field. */
2145 for (i = 1; i < 3; i++)
2146 if (reloc_type[i] == BFD_RELOC_UNUSED)
2149 howto = bfd_reloc_type_lookup (stdoutput, reloc_type[i - 1]);
2150 fixp[0] = fix_new_exp (frag_now, f - frag_now->fr_literal,
2151 bfd_get_reloc_size(howto),
2153 reloc_type[0] == BFD_RELOC_16_PCREL_S2,
2156 /* These relocations can have an addend that won't fit in
2157 4 octets for 64bit assembly. */
2159 && ! howto->partial_inplace
2160 && (reloc_type[0] == BFD_RELOC_16
2161 || reloc_type[0] == BFD_RELOC_32
2162 || reloc_type[0] == BFD_RELOC_MIPS_JMP
2163 || reloc_type[0] == BFD_RELOC_HI16_S
2164 || reloc_type[0] == BFD_RELOC_LO16
2165 || reloc_type[0] == BFD_RELOC_GPREL16
2166 || reloc_type[0] == BFD_RELOC_MIPS_LITERAL
2167 || reloc_type[0] == BFD_RELOC_GPREL32
2168 || reloc_type[0] == BFD_RELOC_64
2169 || reloc_type[0] == BFD_RELOC_CTOR
2170 || reloc_type[0] == BFD_RELOC_MIPS_SUB
2171 || reloc_type[0] == BFD_RELOC_MIPS_HIGHEST
2172 || reloc_type[0] == BFD_RELOC_MIPS_HIGHER
2173 || reloc_type[0] == BFD_RELOC_MIPS_SCN_DISP
2174 || reloc_type[0] == BFD_RELOC_MIPS_REL16
2175 || reloc_type[0] == BFD_RELOC_MIPS_RELGOT))
2176 fixp[0]->fx_no_overflow = 1;
2178 if (mips_relax.sequence)
2180 if (mips_relax.first_fixup == 0)
2181 mips_relax.first_fixup = fixp[0];
2183 else if (reloc_needs_lo_p (*reloc_type))
2185 struct mips_hi_fixup *hi_fixup;
2187 /* Reuse the last entry if it already has a matching %lo. */
2188 hi_fixup = mips_hi_fixup_list;
2190 || !fixup_has_matching_lo_p (hi_fixup->fixp))
2192 hi_fixup = ((struct mips_hi_fixup *)
2193 xmalloc (sizeof (struct mips_hi_fixup)));
2194 hi_fixup->next = mips_hi_fixup_list;
2195 mips_hi_fixup_list = hi_fixup;
2197 hi_fixup->fixp = fixp[0];
2198 hi_fixup->seg = now_seg;
2201 /* Add fixups for the second and third relocations, if given.
2202 Note that the ABI allows the second relocation to be
2203 against RSS_UNDEF, RSS_GP, RSS_GP0 or RSS_LOC. At the
2204 moment we only use RSS_UNDEF, but we could add support
2205 for the others if it ever becomes necessary. */
2206 for (i = 1; i < 3; i++)
2207 if (reloc_type[i] != BFD_RELOC_UNUSED)
2209 address_expr->X_op = O_absent;
2210 address_expr->X_add_symbol = 0;
2211 address_expr->X_add_number = 0;
2213 fixp[i] = fix_new_exp (frag_now, fixp[0]->fx_where,
2214 fixp[0]->fx_size, address_expr,
2215 FALSE, reloc_type[i]);
2220 if (! mips_opts.mips16)
2222 md_number_to_chars (f, ip->insn_opcode, 4);
2224 dwarf2_emit_insn (4);
2227 else if (*reloc_type == BFD_RELOC_MIPS16_JMP)
2229 md_number_to_chars (f, ip->insn_opcode >> 16, 2);
2230 md_number_to_chars (f + 2, ip->insn_opcode & 0xffff, 2);
2232 dwarf2_emit_insn (4);
2239 md_number_to_chars (f, 0xf000 | ip->extend, 2);
2242 md_number_to_chars (f, ip->insn_opcode, 2);
2244 dwarf2_emit_insn (ip->use_extend ? 4 : 2);
2248 /* Update the register mask information. */
2249 if (! mips_opts.mips16)
2251 if (pinfo & INSN_WRITE_GPR_D)
2252 mips_gprmask |= 1 << ((ip->insn_opcode >> OP_SH_RD) & OP_MASK_RD);
2253 if ((pinfo & (INSN_WRITE_GPR_T | INSN_READ_GPR_T)) != 0)
2254 mips_gprmask |= 1 << ((ip->insn_opcode >> OP_SH_RT) & OP_MASK_RT);
2255 if (pinfo & INSN_READ_GPR_S)
2256 mips_gprmask |= 1 << ((ip->insn_opcode >> OP_SH_RS) & OP_MASK_RS);
2257 if (pinfo & INSN_WRITE_GPR_31)
2258 mips_gprmask |= 1 << RA;
2259 if (pinfo & INSN_WRITE_FPR_D)
2260 mips_cprmask[1] |= 1 << ((ip->insn_opcode >> OP_SH_FD) & OP_MASK_FD);
2261 if ((pinfo & (INSN_WRITE_FPR_S | INSN_READ_FPR_S)) != 0)
2262 mips_cprmask[1] |= 1 << ((ip->insn_opcode >> OP_SH_FS) & OP_MASK_FS);
2263 if ((pinfo & (INSN_WRITE_FPR_T | INSN_READ_FPR_T)) != 0)
2264 mips_cprmask[1] |= 1 << ((ip->insn_opcode >> OP_SH_FT) & OP_MASK_FT);
2265 if ((pinfo & INSN_READ_FPR_R) != 0)
2266 mips_cprmask[1] |= 1 << ((ip->insn_opcode >> OP_SH_FR) & OP_MASK_FR);
2267 if (pinfo & INSN_COP)
2269 /* We don't keep enough information to sort these cases out.
2270 The itbl support does keep this information however, although
2271 we currently don't support itbl fprmats as part of the cop
2272 instruction. May want to add this support in the future. */
2274 /* Never set the bit for $0, which is always zero. */
2275 mips_gprmask &= ~1 << 0;
2279 if (pinfo & (MIPS16_INSN_WRITE_X | MIPS16_INSN_READ_X))
2280 mips_gprmask |= 1 << ((ip->insn_opcode >> MIPS16OP_SH_RX)
2281 & MIPS16OP_MASK_RX);
2282 if (pinfo & (MIPS16_INSN_WRITE_Y | MIPS16_INSN_READ_Y))
2283 mips_gprmask |= 1 << ((ip->insn_opcode >> MIPS16OP_SH_RY)
2284 & MIPS16OP_MASK_RY);
2285 if (pinfo & MIPS16_INSN_WRITE_Z)
2286 mips_gprmask |= 1 << ((ip->insn_opcode >> MIPS16OP_SH_RZ)
2287 & MIPS16OP_MASK_RZ);
2288 if (pinfo & (MIPS16_INSN_WRITE_T | MIPS16_INSN_READ_T))
2289 mips_gprmask |= 1 << TREG;
2290 if (pinfo & (MIPS16_INSN_WRITE_SP | MIPS16_INSN_READ_SP))
2291 mips_gprmask |= 1 << SP;
2292 if (pinfo & (MIPS16_INSN_WRITE_31 | MIPS16_INSN_READ_31))
2293 mips_gprmask |= 1 << RA;
2294 if (pinfo & MIPS16_INSN_WRITE_GPR_Y)
2295 mips_gprmask |= 1 << MIPS16OP_EXTRACT_REG32R (ip->insn_opcode);
2296 if (pinfo & MIPS16_INSN_READ_Z)
2297 mips_gprmask |= 1 << ((ip->insn_opcode >> MIPS16OP_SH_MOVE32Z)
2298 & MIPS16OP_MASK_MOVE32Z);
2299 if (pinfo & MIPS16_INSN_READ_GPR_X)
2300 mips_gprmask |= 1 << ((ip->insn_opcode >> MIPS16OP_SH_REGR32)
2301 & MIPS16OP_MASK_REGR32);
2304 if (mips_relax.sequence != 2 && !mips_opts.noreorder)
2306 /* Filling the branch delay slot is more complex. We try to
2307 switch the branch with the previous instruction, which we can
2308 do if the previous instruction does not set up a condition
2309 that the branch tests and if the branch is not itself the
2310 target of any branch. */
2311 if ((pinfo & INSN_UNCOND_BRANCH_DELAY)
2312 || (pinfo & INSN_COND_BRANCH_DELAY))
2314 if (mips_optimize < 2
2315 /* If we have seen .set volatile or .set nomove, don't
2317 || mips_opts.nomove != 0
2318 /* If we had to emit any NOP instructions, then we
2319 already know we can not swap. */
2321 /* If we don't even know the previous insn, we can not
2323 || ! prev_insn_valid
2324 /* If the previous insn is already in a branch delay
2325 slot, then we can not swap. */
2326 || prev_insn_is_delay_slot
2327 /* If the previous previous insn was in a .set
2328 noreorder, we can't swap. Actually, the MIPS
2329 assembler will swap in this situation. However, gcc
2330 configured -with-gnu-as will generate code like
2336 in which we can not swap the bne and INSN. If gcc is
2337 not configured -with-gnu-as, it does not output the
2338 .set pseudo-ops. We don't have to check
2339 prev_insn_unreordered, because prev_insn_valid will
2340 be 0 in that case. We don't want to use
2341 prev_prev_insn_valid, because we do want to be able
2342 to swap at the start of a function. */
2343 || prev_prev_insn_unreordered
2344 /* If the branch is itself the target of a branch, we
2345 can not swap. We cheat on this; all we check for is
2346 whether there is a label on this instruction. If
2347 there are any branches to anything other than a
2348 label, users must use .set noreorder. */
2349 || insn_labels != NULL
2350 /* If the previous instruction is in a variant frag
2351 other than this branch's one, we cannot do the swap.
2352 This does not apply to the mips16, which uses variant
2353 frags for different purposes. */
2354 || (! mips_opts.mips16
2355 && prev_insn_frag_type == rs_machine_dependent)
2356 /* If the branch reads the condition codes, we don't
2357 even try to swap, because in the sequence
2362 we can not swap, and I don't feel like handling that
2364 || (! mips_opts.mips16
2365 && (pinfo & INSN_READ_COND_CODE)
2366 && ! cop_interlocks)
2367 /* We can not swap with an instruction that requires a
2368 delay slot, because the target of the branch might
2369 interfere with that instruction. */
2370 || (! mips_opts.mips16
2372 /* Itbl support may require additional care here. */
2373 & (INSN_LOAD_COPROC_DELAY
2374 | INSN_COPROC_MOVE_DELAY
2375 | INSN_WRITE_COND_CODE))
2376 && ! cop_interlocks)
2377 || (! (hilo_interlocks
2378 || (mips_opts.arch == CPU_R3900 && (pinfo & INSN_MULT)))
2382 || (! mips_opts.mips16
2383 && (prev_pinfo & INSN_LOAD_MEMORY_DELAY)
2384 && ! gpr_interlocks)
2385 || (! mips_opts.mips16
2386 /* Itbl support may require additional care here. */
2387 && (prev_pinfo & INSN_COPROC_MEMORY_DELAY)
2388 && ! cop_mem_interlocks)
2389 /* We can not swap with a branch instruction. */
2391 & (INSN_UNCOND_BRANCH_DELAY
2392 | INSN_COND_BRANCH_DELAY
2393 | INSN_COND_BRANCH_LIKELY))
2394 /* We do not swap with a trap instruction, since it
2395 complicates trap handlers to have the trap
2396 instruction be in a delay slot. */
2397 || (prev_pinfo & INSN_TRAP)
2398 /* If the branch reads a register that the previous
2399 instruction sets, we can not swap. */
2400 || (! mips_opts.mips16
2401 && (prev_pinfo & INSN_WRITE_GPR_T)
2402 && insn_uses_reg (ip,
2403 ((prev_insn.insn_opcode >> OP_SH_RT)
2406 || (! mips_opts.mips16
2407 && (prev_pinfo & INSN_WRITE_GPR_D)
2408 && insn_uses_reg (ip,
2409 ((prev_insn.insn_opcode >> OP_SH_RD)
2412 || (mips_opts.mips16
2413 && (((prev_pinfo & MIPS16_INSN_WRITE_X)
2414 && insn_uses_reg (ip,
2415 ((prev_insn.insn_opcode
2417 & MIPS16OP_MASK_RX),
2419 || ((prev_pinfo & MIPS16_INSN_WRITE_Y)
2420 && insn_uses_reg (ip,
2421 ((prev_insn.insn_opcode
2423 & MIPS16OP_MASK_RY),
2425 || ((prev_pinfo & MIPS16_INSN_WRITE_Z)
2426 && insn_uses_reg (ip,
2427 ((prev_insn.insn_opcode
2429 & MIPS16OP_MASK_RZ),
2431 || ((prev_pinfo & MIPS16_INSN_WRITE_T)
2432 && insn_uses_reg (ip, TREG, MIPS_GR_REG))
2433 || ((prev_pinfo & MIPS16_INSN_WRITE_31)
2434 && insn_uses_reg (ip, RA, MIPS_GR_REG))
2435 || ((prev_pinfo & MIPS16_INSN_WRITE_GPR_Y)
2436 && insn_uses_reg (ip,
2437 MIPS16OP_EXTRACT_REG32R (prev_insn.
2440 /* If the branch writes a register that the previous
2441 instruction sets, we can not swap (we know that
2442 branches write only to RD or to $31). */
2443 || (! mips_opts.mips16
2444 && (prev_pinfo & INSN_WRITE_GPR_T)
2445 && (((pinfo & INSN_WRITE_GPR_D)
2446 && (((prev_insn.insn_opcode >> OP_SH_RT) & OP_MASK_RT)
2447 == ((ip->insn_opcode >> OP_SH_RD) & OP_MASK_RD)))
2448 || ((pinfo & INSN_WRITE_GPR_31)
2449 && (((prev_insn.insn_opcode >> OP_SH_RT)
2452 || (! mips_opts.mips16
2453 && (prev_pinfo & INSN_WRITE_GPR_D)
2454 && (((pinfo & INSN_WRITE_GPR_D)
2455 && (((prev_insn.insn_opcode >> OP_SH_RD) & OP_MASK_RD)
2456 == ((ip->insn_opcode >> OP_SH_RD) & OP_MASK_RD)))
2457 || ((pinfo & INSN_WRITE_GPR_31)
2458 && (((prev_insn.insn_opcode >> OP_SH_RD)
2461 || (mips_opts.mips16
2462 && (pinfo & MIPS16_INSN_WRITE_31)
2463 && ((prev_pinfo & MIPS16_INSN_WRITE_31)
2464 || ((prev_pinfo & MIPS16_INSN_WRITE_GPR_Y)
2465 && (MIPS16OP_EXTRACT_REG32R (prev_insn.insn_opcode)
2467 /* If the branch writes a register that the previous
2468 instruction reads, we can not swap (we know that
2469 branches only write to RD or to $31). */
2470 || (! mips_opts.mips16
2471 && (pinfo & INSN_WRITE_GPR_D)
2472 && insn_uses_reg (&prev_insn,
2473 ((ip->insn_opcode >> OP_SH_RD)
2476 || (! mips_opts.mips16
2477 && (pinfo & INSN_WRITE_GPR_31)
2478 && insn_uses_reg (&prev_insn, RA, MIPS_GR_REG))
2479 || (mips_opts.mips16
2480 && (pinfo & MIPS16_INSN_WRITE_31)
2481 && insn_uses_reg (&prev_insn, RA, MIPS_GR_REG))
2482 /* If we are generating embedded PIC code, the branch
2483 might be expanded into a sequence which uses $at, so
2484 we can't swap with an instruction which reads it. */
2485 || (mips_pic == EMBEDDED_PIC
2486 && insn_uses_reg (&prev_insn, AT, MIPS_GR_REG))
2487 /* If the previous previous instruction has a load
2488 delay, and sets a register that the branch reads, we
2490 || (! mips_opts.mips16
2491 /* Itbl support may require additional care here. */
2492 && (((prev_prev_insn.insn_mo->pinfo & INSN_LOAD_COPROC_DELAY)
2493 && ! cop_interlocks)
2494 || ((prev_prev_insn.insn_mo->pinfo
2495 & INSN_LOAD_MEMORY_DELAY)
2496 && ! gpr_interlocks))
2497 && insn_uses_reg (ip,
2498 ((prev_prev_insn.insn_opcode >> OP_SH_RT)
2501 /* If one instruction sets a condition code and the
2502 other one uses a condition code, we can not swap. */
2503 || ((pinfo & INSN_READ_COND_CODE)
2504 && (prev_pinfo & INSN_WRITE_COND_CODE))
2505 || ((pinfo & INSN_WRITE_COND_CODE)
2506 && (prev_pinfo & INSN_READ_COND_CODE))
2507 /* If the previous instruction uses the PC, we can not
2509 || (mips_opts.mips16
2510 && (prev_pinfo & MIPS16_INSN_READ_PC))
2511 /* If the previous instruction was extended, we can not
2513 || (mips_opts.mips16 && prev_insn_extended)
2514 /* If the previous instruction had a fixup in mips16
2515 mode, we can not swap. This normally means that the
2516 previous instruction was a 4 byte branch anyhow. */
2517 || (mips_opts.mips16 && prev_insn_fixp[0])
2518 /* If the previous instruction is a sync, sync.l, or
2519 sync.p, we can not swap. */
2520 || (prev_pinfo & INSN_SYNC))
2522 /* We could do even better for unconditional branches to
2523 portions of this object file; we could pick up the
2524 instruction at the destination, put it in the delay
2525 slot, and bump the destination address. */
2527 /* Update the previous insn information. */
2528 prev_prev_insn = *ip;
2529 prev_insn.insn_mo = &dummy_opcode;
2533 /* It looks like we can actually do the swap. */
2534 if (! mips_opts.mips16)
2539 prev_f = prev_insn_frag->fr_literal + prev_insn_where;
2540 if (!relaxed_branch)
2542 /* If this is not a relaxed branch, then just
2543 swap the instructions. */
2544 memcpy (temp, prev_f, 4);
2545 memcpy (prev_f, f, 4);
2546 memcpy (f, temp, 4);
2550 /* If this is a relaxed branch, then we move the
2551 instruction to be placed in the delay slot to
2552 the current frag, shrinking the fixed part of
2553 the originating frag. If the branch occupies
2554 the tail of the latter, we move it backwards,
2555 into the space freed by the moved instruction. */
2557 memcpy (f, prev_f, 4);
2558 prev_insn_frag->fr_fix -= 4;
2559 if (prev_insn_frag->fr_type == rs_machine_dependent)
2560 memmove (prev_f, prev_f + 4, prev_insn_frag->fr_var);
2563 if (prev_insn_fixp[0])
2565 prev_insn_fixp[0]->fx_frag = frag_now;
2566 prev_insn_fixp[0]->fx_where = f - frag_now->fr_literal;
2568 if (prev_insn_fixp[1])
2570 prev_insn_fixp[1]->fx_frag = frag_now;
2571 prev_insn_fixp[1]->fx_where = f - frag_now->fr_literal;
2573 if (prev_insn_fixp[2])
2575 prev_insn_fixp[2]->fx_frag = frag_now;
2576 prev_insn_fixp[2]->fx_where = f - frag_now->fr_literal;
2578 if (prev_insn_fixp[0] && HAVE_NEWABI
2579 && prev_insn_frag != frag_now
2580 && (prev_insn_fixp[0]->fx_r_type
2581 == BFD_RELOC_MIPS_GOT_DISP
2582 || (prev_insn_fixp[0]->fx_r_type
2583 == BFD_RELOC_MIPS_CALL16)))
2585 /* To avoid confusion in tc_gen_reloc, we must
2586 ensure that this does not become a variant
2588 force_new_frag = TRUE;
2591 if (!relaxed_branch)
2595 fixp[0]->fx_frag = prev_insn_frag;
2596 fixp[0]->fx_where = prev_insn_where;
2600 fixp[1]->fx_frag = prev_insn_frag;
2601 fixp[1]->fx_where = prev_insn_where;
2605 fixp[2]->fx_frag = prev_insn_frag;
2606 fixp[2]->fx_where = prev_insn_where;
2609 else if (prev_insn_frag->fr_type == rs_machine_dependent)
2612 fixp[0]->fx_where -= 4;
2614 fixp[1]->fx_where -= 4;
2616 fixp[2]->fx_where -= 4;
2624 assert (prev_insn_fixp[0] == NULL);
2625 assert (prev_insn_fixp[1] == NULL);
2626 assert (prev_insn_fixp[2] == NULL);
2627 prev_f = prev_insn_frag->fr_literal + prev_insn_where;
2628 memcpy (temp, prev_f, 2);
2629 memcpy (prev_f, f, 2);
2630 if (*reloc_type != BFD_RELOC_MIPS16_JMP)
2632 assert (*reloc_type == BFD_RELOC_UNUSED);
2633 memcpy (f, temp, 2);
2637 memcpy (f, f + 2, 2);
2638 memcpy (f + 2, temp, 2);
2642 fixp[0]->fx_frag = prev_insn_frag;
2643 fixp[0]->fx_where = prev_insn_where;
2647 fixp[1]->fx_frag = prev_insn_frag;
2648 fixp[1]->fx_where = prev_insn_where;
2652 fixp[2]->fx_frag = prev_insn_frag;
2653 fixp[2]->fx_where = prev_insn_where;
2657 /* Update the previous insn information; leave prev_insn
2659 prev_prev_insn = *ip;
2661 prev_insn_is_delay_slot = 1;
2663 /* If that was an unconditional branch, forget the previous
2664 insn information. */
2665 if (pinfo & INSN_UNCOND_BRANCH_DELAY)
2667 prev_prev_insn.insn_mo = &dummy_opcode;
2668 prev_insn.insn_mo = &dummy_opcode;
2671 prev_insn_fixp[0] = NULL;
2672 prev_insn_fixp[1] = NULL;
2673 prev_insn_fixp[2] = NULL;
2674 prev_insn_reloc_type[0] = BFD_RELOC_UNUSED;
2675 prev_insn_reloc_type[1] = BFD_RELOC_UNUSED;
2676 prev_insn_reloc_type[2] = BFD_RELOC_UNUSED;
2677 prev_insn_extended = 0;
2679 else if (pinfo & INSN_COND_BRANCH_LIKELY)
2681 /* We don't yet optimize a branch likely. What we should do
2682 is look at the target, copy the instruction found there
2683 into the delay slot, and increment the branch to jump to
2684 the next instruction. */
2686 /* Update the previous insn information. */
2687 prev_prev_insn = *ip;
2688 prev_insn.insn_mo = &dummy_opcode;
2689 prev_insn_fixp[0] = NULL;
2690 prev_insn_fixp[1] = NULL;
2691 prev_insn_fixp[2] = NULL;
2692 prev_insn_reloc_type[0] = BFD_RELOC_UNUSED;
2693 prev_insn_reloc_type[1] = BFD_RELOC_UNUSED;
2694 prev_insn_reloc_type[2] = BFD_RELOC_UNUSED;
2695 prev_insn_extended = 0;
2699 /* Update the previous insn information. */
2701 prev_prev_insn.insn_mo = &dummy_opcode;
2703 prev_prev_insn = prev_insn;
2706 /* Any time we see a branch, we always fill the delay slot
2707 immediately; since this insn is not a branch, we know it
2708 is not in a delay slot. */
2709 prev_insn_is_delay_slot = 0;
2711 prev_insn_fixp[0] = fixp[0];
2712 prev_insn_fixp[1] = fixp[1];
2713 prev_insn_fixp[2] = fixp[2];
2714 prev_insn_reloc_type[0] = reloc_type[0];
2715 prev_insn_reloc_type[1] = reloc_type[1];
2716 prev_insn_reloc_type[2] = reloc_type[2];
2717 if (mips_opts.mips16)
2718 prev_insn_extended = (ip->use_extend
2719 || *reloc_type > BFD_RELOC_UNUSED);
2722 prev_prev_insn_unreordered = prev_insn_unreordered;
2723 prev_insn_unreordered = 0;
2724 prev_insn_frag = frag_now;
2725 prev_insn_where = f - frag_now->fr_literal;
2726 prev_insn_valid = 1;
2728 else if (mips_relax.sequence != 2)
2730 /* We need to record a bit of information even when we are not
2731 reordering, in order to determine the base address for mips16
2732 PC relative relocs. */
2733 prev_prev_insn = prev_insn;
2735 prev_insn_reloc_type[0] = reloc_type[0];
2736 prev_insn_reloc_type[1] = reloc_type[1];
2737 prev_insn_reloc_type[2] = reloc_type[2];
2738 prev_prev_insn_unreordered = prev_insn_unreordered;
2739 prev_insn_unreordered = 1;
2742 /* We just output an insn, so the next one doesn't have a label. */
2743 mips_clear_insn_labels ();
2746 /* This function forgets that there was any previous instruction or
2747 label. If PRESERVE is non-zero, it remembers enough information to
2748 know whether nops are needed before a noreorder section. */
2751 mips_no_prev_insn (int preserve)
2755 prev_insn.insn_mo = &dummy_opcode;
2756 prev_prev_insn.insn_mo = &dummy_opcode;
2757 prev_nop_frag = NULL;
2758 prev_nop_frag_holds = 0;
2759 prev_nop_frag_required = 0;
2760 prev_nop_frag_since = 0;
2762 prev_insn_valid = 0;
2763 prev_insn_is_delay_slot = 0;
2764 prev_insn_unreordered = 0;
2765 prev_insn_extended = 0;
2766 prev_insn_reloc_type[0] = BFD_RELOC_UNUSED;
2767 prev_insn_reloc_type[1] = BFD_RELOC_UNUSED;
2768 prev_insn_reloc_type[2] = BFD_RELOC_UNUSED;
2769 prev_prev_insn_unreordered = 0;
2770 mips_clear_insn_labels ();
2773 /* This function must be called whenever we turn on noreorder or emit
2774 something other than instructions. It inserts any NOPS which might
2775 be needed by the previous instruction, and clears the information
2776 kept for the previous instructions. The INSNS parameter is true if
2777 instructions are to follow. */
2780 mips_emit_delays (bfd_boolean insns)
2782 if (! mips_opts.noreorder)
2787 if ((! mips_opts.mips16
2788 && ((prev_insn.insn_mo->pinfo
2789 & (INSN_LOAD_COPROC_DELAY
2790 | INSN_COPROC_MOVE_DELAY
2791 | INSN_WRITE_COND_CODE))
2792 && ! cop_interlocks))
2793 || (! hilo_interlocks
2794 && (prev_insn.insn_mo->pinfo
2797 || (! mips_opts.mips16
2798 && (prev_insn.insn_mo->pinfo & INSN_LOAD_MEMORY_DELAY)
2799 && ! gpr_interlocks)
2800 || (! mips_opts.mips16
2801 && (prev_insn.insn_mo->pinfo & INSN_COPROC_MEMORY_DELAY)
2802 && ! cop_mem_interlocks))
2804 /* Itbl support may require additional care here. */
2806 if ((! mips_opts.mips16
2807 && ((prev_insn.insn_mo->pinfo & INSN_WRITE_COND_CODE)
2808 && ! cop_interlocks))
2809 || (! hilo_interlocks
2810 && ((prev_insn.insn_mo->pinfo & INSN_READ_HI)
2811 || (prev_insn.insn_mo->pinfo & INSN_READ_LO))))
2814 if (prev_insn_unreordered)
2817 else if ((! mips_opts.mips16
2818 && ((prev_prev_insn.insn_mo->pinfo & INSN_WRITE_COND_CODE)
2819 && ! cop_interlocks))
2820 || (! hilo_interlocks
2821 && ((prev_prev_insn.insn_mo->pinfo & INSN_READ_HI)
2822 || (prev_prev_insn.insn_mo->pinfo & INSN_READ_LO))))
2824 /* Itbl support may require additional care here. */
2825 if (! prev_prev_insn_unreordered)
2829 if (mips_fix_4122_bugs && prev_insn.insn_mo->name)
2832 const char *pn = prev_insn.insn_mo->name;
2833 if (strncmp(pn, "macc", 4) == 0
2834 || strncmp(pn, "dmacc", 5) == 0
2835 || strncmp(pn, "dmult", 5) == 0)
2839 if (nops < min_nops)
2845 struct insn_label_list *l;
2849 /* Record the frag which holds the nop instructions, so
2850 that we can remove them if we don't need them. */
2851 frag_grow (mips_opts.mips16 ? nops * 2 : nops * 4);
2852 prev_nop_frag = frag_now;
2853 prev_nop_frag_holds = nops;
2854 prev_nop_frag_required = 0;
2855 prev_nop_frag_since = 0;
2858 for (; nops > 0; --nops)
2863 /* Move on to a new frag, so that it is safe to simply
2864 decrease the size of prev_nop_frag. */
2865 frag_wane (frag_now);
2869 for (l = insn_labels; l != NULL; l = l->next)
2873 assert (S_GET_SEGMENT (l->label) == now_seg);
2874 symbol_set_frag (l->label, frag_now);
2875 val = (valueT) frag_now_fix ();
2876 /* mips16 text labels are stored as odd. */
2877 if (mips_opts.mips16)
2879 S_SET_VALUE (l->label, val);
2884 /* Mark instruction labels in mips16 mode. */
2886 mips16_mark_labels ();
2888 mips_no_prev_insn (insns);
2891 /* Set up global variables for the start of a new macro. */
2896 memset (&mips_macro_warning.sizes, 0, sizeof (mips_macro_warning.sizes));
2897 mips_macro_warning.delay_slot_p = (mips_opts.noreorder
2898 && (prev_insn.insn_mo->pinfo
2899 & (INSN_UNCOND_BRANCH_DELAY
2900 | INSN_COND_BRANCH_DELAY
2901 | INSN_COND_BRANCH_LIKELY)) != 0);
2904 /* Given that a macro is longer than 4 bytes, return the appropriate warning
2905 for it. Return null if no warning is needed. SUBTYPE is a bitmask of
2906 RELAX_DELAY_SLOT and RELAX_NOMACRO. */
2909 macro_warning (relax_substateT subtype)
2911 if (subtype & RELAX_DELAY_SLOT)
2912 return _("Macro instruction expanded into multiple instructions"
2913 " in a branch delay slot");
2914 else if (subtype & RELAX_NOMACRO)
2915 return _("Macro instruction expanded into multiple instructions");
2920 /* Finish up a macro. Emit warnings as appropriate. */
2925 if (mips_macro_warning.sizes[0] > 4 || mips_macro_warning.sizes[1] > 4)
2927 relax_substateT subtype;
2929 /* Set up the relaxation warning flags. */
2931 if (mips_macro_warning.sizes[1] > mips_macro_warning.sizes[0])
2932 subtype |= RELAX_SECOND_LONGER;
2933 if (mips_opts.warn_about_macros)
2934 subtype |= RELAX_NOMACRO;
2935 if (mips_macro_warning.delay_slot_p)
2936 subtype |= RELAX_DELAY_SLOT;
2938 if (mips_macro_warning.sizes[0] > 4 && mips_macro_warning.sizes[1] > 4)
2940 /* Either the macro has a single implementation or both
2941 implementations are longer than 4 bytes. Emit the
2943 const char *msg = macro_warning (subtype);
2949 /* One implementation might need a warning but the other
2950 definitely doesn't. */
2951 mips_macro_warning.first_frag->fr_subtype |= subtype;
2956 /* Build an instruction created by a macro expansion. This is passed
2957 a pointer to the count of instructions created so far, an
2958 expression, the name of the instruction to build, an operand format
2959 string, and corresponding arguments. */
2962 macro_build (expressionS *ep, const char *name, const char *fmt, ...)
2964 struct mips_cl_insn insn;
2965 bfd_reloc_code_real_type r[3];
2968 va_start (args, fmt);
2970 if (mips_opts.mips16)
2972 mips16_macro_build (ep, name, fmt, args);
2977 r[0] = BFD_RELOC_UNUSED;
2978 r[1] = BFD_RELOC_UNUSED;
2979 r[2] = BFD_RELOC_UNUSED;
2980 insn.insn_mo = (struct mips_opcode *) hash_find (op_hash, name);
2981 assert (insn.insn_mo);
2982 assert (strcmp (name, insn.insn_mo->name) == 0);
2984 /* Search until we get a match for NAME. */
2987 /* It is assumed here that macros will never generate
2988 MDMX or MIPS-3D instructions. */
2989 if (strcmp (fmt, insn.insn_mo->args) == 0
2990 && insn.insn_mo->pinfo != INSN_MACRO
2991 && OPCODE_IS_MEMBER (insn.insn_mo,
2993 | (file_ase_mips16 ? INSN_MIPS16 : 0)),
2995 && (mips_opts.arch != CPU_R4650 || (insn.insn_mo->pinfo & FP_D) == 0))
2999 assert (insn.insn_mo->name);
3000 assert (strcmp (name, insn.insn_mo->name) == 0);
3003 insn.insn_opcode = insn.insn_mo->match;
3021 insn.insn_opcode |= (va_arg (args, int)
3022 & OP_MASK_SHAMT) << OP_SH_SHAMT;
3027 /* Note that in the macro case, these arguments are already
3028 in MSB form. (When handling the instruction in the
3029 non-macro case, these arguments are sizes from which
3030 MSB values must be calculated.) */
3031 insn.insn_opcode |= (va_arg (args, int)
3032 & OP_MASK_INSMSB) << OP_SH_INSMSB;
3038 /* Note that in the macro case, these arguments are already
3039 in MSBD form. (When handling the instruction in the
3040 non-macro case, these arguments are sizes from which
3041 MSBD values must be calculated.) */
3042 insn.insn_opcode |= (va_arg (args, int)
3043 & OP_MASK_EXTMSBD) << OP_SH_EXTMSBD;
3054 insn.insn_opcode |= va_arg (args, int) << OP_SH_RT;
3058 insn.insn_opcode |= va_arg (args, int) << OP_SH_CODE;
3063 insn.insn_opcode |= va_arg (args, int) << OP_SH_FT;
3069 insn.insn_opcode |= va_arg (args, int) << OP_SH_RD;
3074 int tmp = va_arg (args, int);
3076 insn.insn_opcode |= tmp << OP_SH_RT;
3077 insn.insn_opcode |= tmp << OP_SH_RD;
3083 insn.insn_opcode |= va_arg (args, int) << OP_SH_FS;
3090 insn.insn_opcode |= va_arg (args, int) << OP_SH_SHAMT;
3094 insn.insn_opcode |= va_arg (args, int) << OP_SH_FD;
3098 insn.insn_opcode |= va_arg (args, int) << OP_SH_CODE20;
3102 insn.insn_opcode |= va_arg (args, int) << OP_SH_CODE19;
3106 insn.insn_opcode |= va_arg (args, int) << OP_SH_CODE2;
3113 insn.insn_opcode |= va_arg (args, int) << OP_SH_RS;
3119 *r = (bfd_reloc_code_real_type) va_arg (args, int);
3120 assert (*r == BFD_RELOC_GPREL16
3121 || *r == BFD_RELOC_MIPS_LITERAL
3122 || *r == BFD_RELOC_MIPS_HIGHER
3123 || *r == BFD_RELOC_HI16_S
3124 || *r == BFD_RELOC_LO16
3125 || *r == BFD_RELOC_MIPS_GOT16
3126 || *r == BFD_RELOC_MIPS_CALL16
3127 || *r == BFD_RELOC_MIPS_GOT_DISP
3128 || *r == BFD_RELOC_MIPS_GOT_PAGE
3129 || *r == BFD_RELOC_MIPS_GOT_OFST
3130 || *r == BFD_RELOC_MIPS_GOT_LO16
3131 || *r == BFD_RELOC_MIPS_CALL_LO16
3132 || (ep->X_op == O_subtract
3133 && *r == BFD_RELOC_PCREL_LO16));
3137 *r = (bfd_reloc_code_real_type) va_arg (args, int);
3139 && (ep->X_op == O_constant
3140 || (ep->X_op == O_symbol
3141 && (*r == BFD_RELOC_MIPS_HIGHEST
3142 || *r == BFD_RELOC_HI16_S
3143 || *r == BFD_RELOC_HI16
3144 || *r == BFD_RELOC_GPREL16
3145 || *r == BFD_RELOC_MIPS_GOT_HI16
3146 || *r == BFD_RELOC_MIPS_CALL_HI16))
3147 || (ep->X_op == O_subtract
3148 && *r == BFD_RELOC_PCREL_HI16_S)));
3152 assert (ep != NULL);
3154 * This allows macro() to pass an immediate expression for
3155 * creating short branches without creating a symbol.
3156 * Note that the expression still might come from the assembly
3157 * input, in which case the value is not checked for range nor
3158 * is a relocation entry generated (yuck).
3160 if (ep->X_op == O_constant)
3162 insn.insn_opcode |= (ep->X_add_number >> 2) & 0xffff;
3166 *r = BFD_RELOC_16_PCREL_S2;
3170 assert (ep != NULL);
3171 *r = BFD_RELOC_MIPS_JMP;
3175 insn.insn_opcode |= va_arg (args, unsigned long);
3184 assert (*r == BFD_RELOC_UNUSED ? ep == NULL : ep != NULL);
3186 append_insn (&insn, ep, r);
3190 mips16_macro_build (expressionS *ep, const char *name, const char *fmt,
3193 struct mips_cl_insn insn;
3194 bfd_reloc_code_real_type r[3]
3195 = {BFD_RELOC_UNUSED, BFD_RELOC_UNUSED, BFD_RELOC_UNUSED};
3197 insn.insn_mo = (struct mips_opcode *) hash_find (mips16_op_hash, name);
3198 assert (insn.insn_mo);
3199 assert (strcmp (name, insn.insn_mo->name) == 0);
3201 while (strcmp (fmt, insn.insn_mo->args) != 0
3202 || insn.insn_mo->pinfo == INSN_MACRO)
3205 assert (insn.insn_mo->name);
3206 assert (strcmp (name, insn.insn_mo->name) == 0);
3209 insn.insn_opcode = insn.insn_mo->match;
3210 insn.use_extend = FALSE;
3229 insn.insn_opcode |= va_arg (args, int) << MIPS16OP_SH_RY;
3234 insn.insn_opcode |= va_arg (args, int) << MIPS16OP_SH_RX;
3238 insn.insn_opcode |= va_arg (args, int) << MIPS16OP_SH_RZ;
3242 insn.insn_opcode |= va_arg (args, int) << MIPS16OP_SH_MOVE32Z;
3252 insn.insn_opcode |= va_arg (args, int) << MIPS16OP_SH_REGR32;
3259 regno = va_arg (args, int);
3260 regno = ((regno & 7) << 2) | ((regno & 0x18) >> 3);
3261 insn.insn_opcode |= regno << MIPS16OP_SH_REG32R;
3282 assert (ep != NULL);
3284 if (ep->X_op != O_constant)
3285 *r = (int) BFD_RELOC_UNUSED + c;
3288 mips16_immed (NULL, 0, c, ep->X_add_number, FALSE, FALSE,
3289 FALSE, &insn.insn_opcode, &insn.use_extend,
3292 *r = BFD_RELOC_UNUSED;
3298 insn.insn_opcode |= va_arg (args, int) << MIPS16OP_SH_IMM6;
3305 assert (*r == BFD_RELOC_UNUSED ? ep == NULL : ep != NULL);
3307 append_insn (&insn, ep, r);
3311 * Generate a "jalr" instruction with a relocation hint to the called
3312 * function. This occurs in NewABI PIC code.
3315 macro_build_jalr (expressionS *ep)
3324 macro_build (NULL, "jalr", "d,s", RA, PIC_CALL_REG);
3326 fix_new_exp (frag_now, f - frag_now->fr_literal,
3327 4, ep, FALSE, BFD_RELOC_MIPS_JALR);
3331 * Generate a "lui" instruction.
3334 macro_build_lui (expressionS *ep, int regnum)
3336 expressionS high_expr;
3337 struct mips_cl_insn insn;
3338 bfd_reloc_code_real_type r[3]
3339 = {BFD_RELOC_UNUSED, BFD_RELOC_UNUSED, BFD_RELOC_UNUSED};
3340 const char *name = "lui";
3341 const char *fmt = "t,u";
3343 assert (! mips_opts.mips16);
3347 if (high_expr.X_op == O_constant)
3349 /* we can compute the instruction now without a relocation entry */
3350 high_expr.X_add_number = ((high_expr.X_add_number + 0x8000)
3352 *r = BFD_RELOC_UNUSED;
3356 assert (ep->X_op == O_symbol);
3357 /* _gp_disp is a special case, used from s_cpload. */
3358 assert (mips_pic == NO_PIC
3360 && strcmp (S_GET_NAME (ep->X_add_symbol), "_gp_disp") == 0));
3361 *r = BFD_RELOC_HI16_S;
3364 insn.insn_mo = (struct mips_opcode *) hash_find (op_hash, name);
3365 assert (insn.insn_mo);
3366 assert (strcmp (name, insn.insn_mo->name) == 0);
3367 assert (strcmp (fmt, insn.insn_mo->args) == 0);
3369 insn.insn_opcode = insn.insn_mo->match | (regnum << OP_SH_RT);
3370 if (*r == BFD_RELOC_UNUSED)
3372 insn.insn_opcode |= high_expr.X_add_number;
3373 append_insn (&insn, NULL, r);
3376 append_insn (&insn, &high_expr, r);
3379 /* Generate a sequence of instructions to do a load or store from a constant
3380 offset off of a base register (breg) into/from a target register (treg),
3381 using AT if necessary. */
3383 macro_build_ldst_constoffset (expressionS *ep, const char *op,
3384 int treg, int breg, int dbl)
3386 assert (ep->X_op == O_constant);
3388 /* Sign-extending 32-bit constants makes their handling easier. */
3389 if (! dbl && ! ((ep->X_add_number & ~((bfd_vma) 0x7fffffff))
3390 == ~((bfd_vma) 0x7fffffff)))
3392 if (ep->X_add_number & ~((bfd_vma) 0xffffffff))
3393 as_bad (_("constant too large"));
3395 ep->X_add_number = (((ep->X_add_number & 0xffffffff) ^ 0x80000000)
3399 /* Right now, this routine can only handle signed 32-bit constants. */
3400 if (! IS_SEXT_32BIT_NUM(ep->X_add_number + 0x8000))
3401 as_warn (_("operand overflow"));
3403 if (IS_SEXT_16BIT_NUM(ep->X_add_number))
3405 /* Signed 16-bit offset will fit in the op. Easy! */
3406 macro_build (ep, op, "t,o(b)", treg, BFD_RELOC_LO16, breg);
3410 /* 32-bit offset, need multiple instructions and AT, like:
3411 lui $tempreg,const_hi (BFD_RELOC_HI16_S)
3412 addu $tempreg,$tempreg,$breg
3413 <op> $treg,const_lo($tempreg) (BFD_RELOC_LO16)
3414 to handle the complete offset. */
3415 macro_build_lui (ep, AT);
3416 macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", AT, AT, breg);
3417 macro_build (ep, op, "t,o(b)", treg, BFD_RELOC_LO16, AT);
3420 as_warn (_("Macro used $at after \".set noat\""));
3425 * Generates code to set the $at register to true (one)
3426 * if reg is less than the immediate expression.
3429 set_at (int reg, int unsignedp)
3431 if (imm_expr.X_op == O_constant
3432 && imm_expr.X_add_number >= -0x8000
3433 && imm_expr.X_add_number < 0x8000)
3434 macro_build (&imm_expr, unsignedp ? "sltiu" : "slti", "t,r,j",
3435 AT, reg, BFD_RELOC_LO16);
3438 load_register (AT, &imm_expr, HAVE_64BIT_GPRS);
3439 macro_build (NULL, unsignedp ? "sltu" : "slt", "d,v,t", AT, reg, AT);
3444 normalize_constant_expr (expressionS *ex)
3446 if (ex->X_op == O_constant && HAVE_32BIT_GPRS)
3447 ex->X_add_number = (((ex->X_add_number & 0xffffffff) ^ 0x80000000)
3451 /* Warn if an expression is not a constant. */
3454 check_absolute_expr (struct mips_cl_insn *ip, expressionS *ex)
3456 if (ex->X_op == O_big)
3457 as_bad (_("unsupported large constant"));
3458 else if (ex->X_op != O_constant)
3459 as_bad (_("Instruction %s requires absolute expression"), ip->insn_mo->name);
3461 normalize_constant_expr (ex);
3464 /* Count the leading zeroes by performing a binary chop. This is a
3465 bulky bit of source, but performance is a LOT better for the
3466 majority of values than a simple loop to count the bits:
3467 for (lcnt = 0; (lcnt < 32); lcnt++)
3468 if ((v) & (1 << (31 - lcnt)))
3470 However it is not code size friendly, and the gain will drop a bit
3471 on certain cached systems.
3473 #define COUNT_TOP_ZEROES(v) \
3474 (((v) & ~0xffff) == 0 \
3475 ? ((v) & ~0xff) == 0 \
3476 ? ((v) & ~0xf) == 0 \
3477 ? ((v) & ~0x3) == 0 \
3478 ? ((v) & ~0x1) == 0 \
3483 : ((v) & ~0x7) == 0 \
3486 : ((v) & ~0x3f) == 0 \
3487 ? ((v) & ~0x1f) == 0 \
3490 : ((v) & ~0x7f) == 0 \
3493 : ((v) & ~0xfff) == 0 \
3494 ? ((v) & ~0x3ff) == 0 \
3495 ? ((v) & ~0x1ff) == 0 \
3498 : ((v) & ~0x7ff) == 0 \
3501 : ((v) & ~0x3fff) == 0 \
3502 ? ((v) & ~0x1fff) == 0 \
3505 : ((v) & ~0x7fff) == 0 \
3508 : ((v) & ~0xffffff) == 0 \
3509 ? ((v) & ~0xfffff) == 0 \
3510 ? ((v) & ~0x3ffff) == 0 \
3511 ? ((v) & ~0x1ffff) == 0 \
3514 : ((v) & ~0x7ffff) == 0 \
3517 : ((v) & ~0x3fffff) == 0 \
3518 ? ((v) & ~0x1fffff) == 0 \
3521 : ((v) & ~0x7fffff) == 0 \
3524 : ((v) & ~0xfffffff) == 0 \
3525 ? ((v) & ~0x3ffffff) == 0 \
3526 ? ((v) & ~0x1ffffff) == 0 \
3529 : ((v) & ~0x7ffffff) == 0 \
3532 : ((v) & ~0x3fffffff) == 0 \
3533 ? ((v) & ~0x1fffffff) == 0 \
3536 : ((v) & ~0x7fffffff) == 0 \
3541 * This routine generates the least number of instructions necessary to load
3542 * an absolute expression value into a register.
3545 load_register (int reg, expressionS *ep, int dbl)
3548 expressionS hi32, lo32;
3550 if (ep->X_op != O_big)
3552 assert (ep->X_op == O_constant);
3554 /* Sign-extending 32-bit constants makes their handling easier. */
3555 if (! dbl && ! ((ep->X_add_number & ~((bfd_vma) 0x7fffffff))
3556 == ~((bfd_vma) 0x7fffffff)))
3558 if (ep->X_add_number & ~((bfd_vma) 0xffffffff))
3559 as_bad (_("constant too large"));
3561 ep->X_add_number = (((ep->X_add_number & 0xffffffff) ^ 0x80000000)
3565 if (IS_SEXT_16BIT_NUM (ep->X_add_number))
3567 /* We can handle 16 bit signed values with an addiu to
3568 $zero. No need to ever use daddiu here, since $zero and
3569 the result are always correct in 32 bit mode. */
3570 macro_build (ep, "addiu", "t,r,j", reg, 0, BFD_RELOC_LO16);
3573 else if (ep->X_add_number >= 0 && ep->X_add_number < 0x10000)
3575 /* We can handle 16 bit unsigned values with an ori to
3577 macro_build (ep, "ori", "t,r,i", reg, 0, BFD_RELOC_LO16);
3580 else if ((IS_SEXT_32BIT_NUM (ep->X_add_number)))
3582 /* 32 bit values require an lui. */
3583 macro_build (ep, "lui", "t,u", reg, BFD_RELOC_HI16);
3584 if ((ep->X_add_number & 0xffff) != 0)
3585 macro_build (ep, "ori", "t,r,i", reg, reg, BFD_RELOC_LO16);
3590 /* The value is larger than 32 bits. */
3592 if (HAVE_32BIT_GPRS)
3594 as_bad (_("Number (0x%lx) larger than 32 bits"),
3595 (unsigned long) ep->X_add_number);
3596 macro_build (ep, "addiu", "t,r,j", reg, 0, BFD_RELOC_LO16);
3600 if (ep->X_op != O_big)
3603 hi32.X_add_number = (valueT) hi32.X_add_number >> 16;
3604 hi32.X_add_number = (valueT) hi32.X_add_number >> 16;
3605 hi32.X_add_number &= 0xffffffff;
3607 lo32.X_add_number &= 0xffffffff;
3611 assert (ep->X_add_number > 2);
3612 if (ep->X_add_number == 3)
3613 generic_bignum[3] = 0;
3614 else if (ep->X_add_number > 4)
3615 as_bad (_("Number larger than 64 bits"));
3616 lo32.X_op = O_constant;
3617 lo32.X_add_number = generic_bignum[0] + (generic_bignum[1] << 16);
3618 hi32.X_op = O_constant;
3619 hi32.X_add_number = generic_bignum[2] + (generic_bignum[3] << 16);
3622 if (hi32.X_add_number == 0)
3627 unsigned long hi, lo;
3629 if (hi32.X_add_number == (offsetT) 0xffffffff)
3631 if ((lo32.X_add_number & 0xffff8000) == 0xffff8000)
3633 macro_build (&lo32, "addiu", "t,r,j", reg, 0, BFD_RELOC_LO16);
3636 if (lo32.X_add_number & 0x80000000)
3638 macro_build (&lo32, "lui", "t,u", reg, BFD_RELOC_HI16);
3639 if (lo32.X_add_number & 0xffff)
3640 macro_build (&lo32, "ori", "t,r,i", reg, reg, BFD_RELOC_LO16);
3645 /* Check for 16bit shifted constant. We know that hi32 is
3646 non-zero, so start the mask on the first bit of the hi32
3651 unsigned long himask, lomask;
3655 himask = 0xffff >> (32 - shift);
3656 lomask = (0xffff << shift) & 0xffffffff;
3660 himask = 0xffff << (shift - 32);
3663 if ((hi32.X_add_number & ~(offsetT) himask) == 0
3664 && (lo32.X_add_number & ~(offsetT) lomask) == 0)
3668 tmp.X_op = O_constant;
3670 tmp.X_add_number = ((hi32.X_add_number << (32 - shift))
3671 | (lo32.X_add_number >> shift));
3673 tmp.X_add_number = hi32.X_add_number >> (shift - 32);
3674 macro_build (&tmp, "ori", "t,r,i", reg, 0, BFD_RELOC_LO16);
3675 macro_build (NULL, (shift >= 32) ? "dsll32" : "dsll", "d,w,<",
3676 reg, reg, (shift >= 32) ? shift - 32 : shift);
3681 while (shift <= (64 - 16));
3683 /* Find the bit number of the lowest one bit, and store the
3684 shifted value in hi/lo. */
3685 hi = (unsigned long) (hi32.X_add_number & 0xffffffff);
3686 lo = (unsigned long) (lo32.X_add_number & 0xffffffff);
3690 while ((lo & 1) == 0)
3695 lo |= (hi & (((unsigned long) 1 << bit) - 1)) << (32 - bit);
3701 while ((hi & 1) == 0)
3710 /* Optimize if the shifted value is a (power of 2) - 1. */
3711 if ((hi == 0 && ((lo + 1) & lo) == 0)
3712 || (lo == 0xffffffff && ((hi + 1) & hi) == 0))
3714 shift = COUNT_TOP_ZEROES ((unsigned int) hi32.X_add_number);
3719 /* This instruction will set the register to be all
3721 tmp.X_op = O_constant;
3722 tmp.X_add_number = (offsetT) -1;
3723 macro_build (&tmp, "addiu", "t,r,j", reg, 0, BFD_RELOC_LO16);
3727 macro_build (NULL, (bit >= 32) ? "dsll32" : "dsll", "d,w,<",
3728 reg, reg, (bit >= 32) ? bit - 32 : bit);
3730 macro_build (NULL, (shift >= 32) ? "dsrl32" : "dsrl", "d,w,<",
3731 reg, reg, (shift >= 32) ? shift - 32 : shift);
3736 /* Sign extend hi32 before calling load_register, because we can
3737 generally get better code when we load a sign extended value. */
3738 if ((hi32.X_add_number & 0x80000000) != 0)
3739 hi32.X_add_number |= ~(offsetT) 0xffffffff;
3740 load_register (reg, &hi32, 0);
3743 if ((lo32.X_add_number & 0xffff0000) == 0)
3747 macro_build (NULL, "dsll32", "d,w,<", reg, freg, 0);
3755 if ((freg == 0) && (lo32.X_add_number == (offsetT) 0xffffffff))
3757 macro_build (&lo32, "lui", "t,u", reg, BFD_RELOC_HI16);
3758 macro_build (NULL, "dsrl32", "d,w,<", reg, reg, 0);
3764 macro_build (NULL, "dsll", "d,w,<", reg, freg, 16);
3768 mid16.X_add_number >>= 16;
3769 macro_build (&mid16, "ori", "t,r,i", reg, freg, BFD_RELOC_LO16);
3770 macro_build (NULL, "dsll", "d,w,<", reg, reg, 16);
3773 if ((lo32.X_add_number & 0xffff) != 0)
3774 macro_build (&lo32, "ori", "t,r,i", reg, freg, BFD_RELOC_LO16);
3777 /* Load an address into a register. */
3780 load_address (int reg, expressionS *ep, int *used_at)
3782 if (ep->X_op != O_constant
3783 && ep->X_op != O_symbol)
3785 as_bad (_("expression too complex"));
3786 ep->X_op = O_constant;
3789 if (ep->X_op == O_constant)
3791 load_register (reg, ep, HAVE_64BIT_ADDRESSES);
3795 if (mips_pic == NO_PIC)
3797 /* If this is a reference to a GP relative symbol, we want
3798 addiu $reg,$gp,<sym> (BFD_RELOC_GPREL16)
3800 lui $reg,<sym> (BFD_RELOC_HI16_S)
3801 addiu $reg,$reg,<sym> (BFD_RELOC_LO16)
3802 If we have an addend, we always use the latter form.
3804 With 64bit address space and a usable $at we want
3805 lui $reg,<sym> (BFD_RELOC_MIPS_HIGHEST)
3806 lui $at,<sym> (BFD_RELOC_HI16_S)
3807 daddiu $reg,<sym> (BFD_RELOC_MIPS_HIGHER)
3808 daddiu $at,<sym> (BFD_RELOC_LO16)
3812 If $at is already in use, we use a path which is suboptimal
3813 on superscalar processors.
3814 lui $reg,<sym> (BFD_RELOC_MIPS_HIGHEST)
3815 daddiu $reg,<sym> (BFD_RELOC_MIPS_HIGHER)
3817 daddiu $reg,<sym> (BFD_RELOC_HI16_S)
3819 daddiu $reg,<sym> (BFD_RELOC_LO16)
3821 if (HAVE_64BIT_ADDRESSES)
3823 /* ??? We don't provide a GP-relative alternative for these macros.
3824 It used not to be possible with the original relaxation code,
3825 but it could be done now. */
3827 if (*used_at == 0 && ! mips_opts.noat)
3829 macro_build (ep, "lui", "t,u", reg, BFD_RELOC_MIPS_HIGHEST);
3830 macro_build (ep, "lui", "t,u", AT, BFD_RELOC_HI16_S);
3831 macro_build (ep, "daddiu", "t,r,j", reg, reg,
3832 BFD_RELOC_MIPS_HIGHER);
3833 macro_build (ep, "daddiu", "t,r,j", AT, AT, BFD_RELOC_LO16);
3834 macro_build (NULL, "dsll32", "d,w,<", reg, reg, 0);
3835 macro_build (NULL, "daddu", "d,v,t", reg, reg, AT);
3840 macro_build (ep, "lui", "t,u", reg, BFD_RELOC_MIPS_HIGHEST);
3841 macro_build (ep, "daddiu", "t,r,j", reg, reg,
3842 BFD_RELOC_MIPS_HIGHER);
3843 macro_build (NULL, "dsll", "d,w,<", reg, reg, 16);
3844 macro_build (ep, "daddiu", "t,r,j", reg, reg, BFD_RELOC_HI16_S);
3845 macro_build (NULL, "dsll", "d,w,<", reg, reg, 16);
3846 macro_build (ep, "daddiu", "t,r,j", reg, reg, BFD_RELOC_LO16);
3851 if ((valueT) ep->X_add_number <= MAX_GPREL_OFFSET
3852 && ! nopic_need_relax (ep->X_add_symbol, 1))
3854 relax_start (ep->X_add_symbol);
3855 macro_build (ep, ADDRESS_ADDI_INSN, "t,r,j", reg,
3856 mips_gp_register, BFD_RELOC_GPREL16);
3859 macro_build_lui (ep, reg);
3860 macro_build (ep, ADDRESS_ADDI_INSN, "t,r,j",
3861 reg, reg, BFD_RELOC_LO16);
3862 if (mips_relax.sequence)
3866 else if (mips_pic == SVR4_PIC && ! mips_big_got)
3870 /* If this is a reference to an external symbol, we want
3871 lw $reg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
3873 lw $reg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
3875 addiu $reg,$reg,<sym> (BFD_RELOC_LO16)
3876 If there is a constant, it must be added in after.
3878 If we have NewABI, we want
3879 lw $reg,<sym+cst>($gp) (BFD_RELOC_MIPS_GOT_DISP)
3880 unless we're referencing a global symbol with a non-zero
3881 offset, in which case cst must be added separately. */
3884 if (ep->X_add_number)
3886 ex.X_add_number = ep->X_add_number;
3887 ep->X_add_number = 0;
3888 relax_start (ep->X_add_symbol);
3889 macro_build (ep, ADDRESS_LOAD_INSN, "t,o(b)", reg,
3890 BFD_RELOC_MIPS_GOT_DISP, mips_gp_register);
3891 if (ex.X_add_number < -0x8000 || ex.X_add_number >= 0x8000)
3892 as_bad (_("PIC code offset overflow (max 16 signed bits)"));
3893 ex.X_op = O_constant;
3894 macro_build (&ex, ADDRESS_ADDI_INSN, "t,r,j",
3895 reg, reg, BFD_RELOC_LO16);
3896 ep->X_add_number = ex.X_add_number;
3899 macro_build (ep, ADDRESS_LOAD_INSN, "t,o(b)", reg,
3900 BFD_RELOC_MIPS_GOT_DISP, mips_gp_register);
3901 if (mips_relax.sequence)
3906 ex.X_add_number = ep->X_add_number;
3907 ep->X_add_number = 0;
3908 macro_build (ep, ADDRESS_LOAD_INSN, "t,o(b)", reg,
3909 BFD_RELOC_MIPS_GOT16, mips_gp_register);
3910 macro_build (NULL, "nop", "");
3911 relax_start (ep->X_add_symbol);
3913 macro_build (ep, ADDRESS_ADDI_INSN, "t,r,j", reg, reg,
3917 if (ex.X_add_number != 0)
3919 if (ex.X_add_number < -0x8000 || ex.X_add_number >= 0x8000)
3920 as_bad (_("PIC code offset overflow (max 16 signed bits)"));
3921 ex.X_op = O_constant;
3922 macro_build (&ex, ADDRESS_ADDI_INSN, "t,r,j",
3923 reg, reg, BFD_RELOC_LO16);
3927 else if (mips_pic == SVR4_PIC)
3931 /* This is the large GOT case. If this is a reference to an
3932 external symbol, we want
3933 lui $reg,<sym> (BFD_RELOC_MIPS_GOT_HI16)
3935 lw $reg,<sym>($reg) (BFD_RELOC_MIPS_GOT_LO16)
3937 Otherwise, for a reference to a local symbol in old ABI, we want
3938 lw $reg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
3940 addiu $reg,$reg,<sym> (BFD_RELOC_LO16)
3941 If there is a constant, it must be added in after.
3943 In the NewABI, for local symbols, with or without offsets, we want:
3944 lw $reg,<sym>($gp) (BFD_RELOC_MIPS_GOT_PAGE)
3945 addiu $reg,$reg,<sym> (BFD_RELOC_MIPS_GOT_OFST)
3949 ex.X_add_number = ep->X_add_number;
3950 ep->X_add_number = 0;
3951 relax_start (ep->X_add_symbol);
3952 macro_build (ep, "lui", "t,u", reg, BFD_RELOC_MIPS_GOT_HI16);
3953 macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
3954 reg, reg, mips_gp_register);
3955 macro_build (ep, ADDRESS_LOAD_INSN, "t,o(b)",
3956 reg, BFD_RELOC_MIPS_GOT_LO16, reg);
3957 if (ex.X_add_number < -0x8000 || ex.X_add_number >= 0x8000)
3958 as_bad (_("PIC code offset overflow (max 16 signed bits)"));
3959 else if (ex.X_add_number)
3961 ex.X_op = O_constant;
3962 macro_build (&ex, ADDRESS_ADDI_INSN, "t,r,j", reg, reg,
3966 ep->X_add_number = ex.X_add_number;
3968 macro_build (ep, ADDRESS_LOAD_INSN, "t,o(b)", reg,
3969 BFD_RELOC_MIPS_GOT_PAGE, mips_gp_register);
3970 macro_build (ep, ADDRESS_ADDI_INSN, "t,r,j", reg, reg,
3971 BFD_RELOC_MIPS_GOT_OFST);
3976 ex.X_add_number = ep->X_add_number;
3977 ep->X_add_number = 0;
3978 relax_start (ep->X_add_symbol);
3979 macro_build (ep, "lui", "t,u", reg, BFD_RELOC_MIPS_GOT_HI16);
3980 macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
3981 reg, reg, mips_gp_register);
3982 macro_build (ep, ADDRESS_LOAD_INSN, "t,o(b)",
3983 reg, BFD_RELOC_MIPS_GOT_LO16, reg);
3985 if (reg_needs_delay (mips_gp_register))
3987 /* We need a nop before loading from $gp. This special
3988 check is required because the lui which starts the main
3989 instruction stream does not refer to $gp, and so will not
3990 insert the nop which may be required. */
3991 macro_build (NULL, "nop", "");
3993 macro_build (ep, ADDRESS_LOAD_INSN, "t,o(b)", reg,
3994 BFD_RELOC_MIPS_GOT16, mips_gp_register);
3995 macro_build (NULL, "nop", "");
3996 macro_build (ep, ADDRESS_ADDI_INSN, "t,r,j", reg, reg,
4000 if (ex.X_add_number != 0)
4002 if (ex.X_add_number < -0x8000 || ex.X_add_number >= 0x8000)
4003 as_bad (_("PIC code offset overflow (max 16 signed bits)"));
4004 ex.X_op = O_constant;
4005 macro_build (&ex, ADDRESS_ADDI_INSN, "t,r,j", reg, reg,
4010 else if (mips_pic == EMBEDDED_PIC)
4013 addiu $reg,$gp,<sym> (BFD_RELOC_GPREL16)
4015 macro_build (ep, ADDRESS_ADDI_INSN, "t,r,j",
4016 reg, mips_gp_register, BFD_RELOC_GPREL16);
4022 /* Move the contents of register SOURCE into register DEST. */
4025 move_register (int dest, int source)
4027 macro_build (NULL, HAVE_32BIT_GPRS ? "addu" : "daddu", "d,v,t",
4031 /* Emit an SVR4 PIC sequence to load address LOCAL into DEST, where
4032 LOCAL is the sum of a symbol and a 16-bit displacement. The two
4035 Global symbol Local sybmol
4036 ------------- ------------
4037 lw DEST,%got(SYMBOL) lw DEST,%got(SYMBOL + OFFSET)
4039 addiu DEST,DEST,OFFSET addiu DEST,DEST,%lo(SYMBOL + OFFSET)
4041 load_got_offset emits the first instruction and add_got_offset
4042 emits the second. */
4045 load_got_offset (int dest, expressionS *local)
4050 global.X_add_number = 0;
4052 relax_start (local->X_add_symbol);
4053 macro_build (&global, ADDRESS_LOAD_INSN, "t,o(b)", dest,
4054 BFD_RELOC_MIPS_GOT16, mips_gp_register);
4056 macro_build (local, ADDRESS_LOAD_INSN, "t,o(b)", dest,
4057 BFD_RELOC_MIPS_GOT16, mips_gp_register);
4062 add_got_offset (int dest, expressionS *local)
4066 global.X_op = O_constant;
4067 global.X_op_symbol = NULL;
4068 global.X_add_symbol = NULL;
4069 global.X_add_number = local->X_add_number;
4071 relax_start (local->X_add_symbol);
4072 macro_build (&global, ADDRESS_ADDI_INSN, "t,r,j",
4073 dest, dest, BFD_RELOC_LO16);
4075 macro_build (local, ADDRESS_ADDI_INSN, "t,r,j", dest, dest, BFD_RELOC_LO16);
4081 * This routine implements the seemingly endless macro or synthesized
4082 * instructions and addressing modes in the mips assembly language. Many
4083 * of these macros are simple and are similar to each other. These could
4084 * probably be handled by some kind of table or grammar approach instead of
4085 * this verbose method. Others are not simple macros but are more like
4086 * optimizing code generation.
4087 * One interesting optimization is when several store macros appear
4088 * consecutively that would load AT with the upper half of the same address.
4089 * The ensuing load upper instructions are ommited. This implies some kind
4090 * of global optimization. We currently only optimize within a single macro.
4091 * For many of the load and store macros if the address is specified as a
4092 * constant expression in the first 64k of memory (ie ld $2,0x4000c) we
4093 * first load register 'at' with zero and use it as the base register. The
4094 * mips assembler simply uses register $zero. Just one tiny optimization
4098 macro (struct mips_cl_insn *ip)
4100 register int treg, sreg, dreg, breg;
4116 bfd_reloc_code_real_type r;
4117 int hold_mips_optimize;
4119 assert (! mips_opts.mips16);
4121 treg = (ip->insn_opcode >> 16) & 0x1f;
4122 dreg = (ip->insn_opcode >> 11) & 0x1f;
4123 sreg = breg = (ip->insn_opcode >> 21) & 0x1f;
4124 mask = ip->insn_mo->mask;
4126 expr1.X_op = O_constant;
4127 expr1.X_op_symbol = NULL;
4128 expr1.X_add_symbol = NULL;
4129 expr1.X_add_number = 1;
4141 mips_emit_delays (TRUE);
4142 ++mips_opts.noreorder;
4143 mips_any_noreorder = 1;
4145 expr1.X_add_number = 8;
4146 macro_build (&expr1, "bgez", "s,p", sreg);
4148 macro_build (NULL, "nop", "", 0);
4150 move_register (dreg, sreg);
4151 macro_build (NULL, dbl ? "dsub" : "sub", "d,v,t", dreg, 0, sreg);
4153 --mips_opts.noreorder;
4174 if (imm_expr.X_op == O_constant
4175 && imm_expr.X_add_number >= -0x8000
4176 && imm_expr.X_add_number < 0x8000)
4178 macro_build (&imm_expr, s, "t,r,j", treg, sreg, BFD_RELOC_LO16);
4181 load_register (AT, &imm_expr, dbl);
4182 macro_build (NULL, s2, "d,v,t", treg, sreg, AT);
4201 if (imm_expr.X_op == O_constant
4202 && imm_expr.X_add_number >= 0
4203 && imm_expr.X_add_number < 0x10000)
4205 if (mask != M_NOR_I)
4206 macro_build (&imm_expr, s, "t,r,i", treg, sreg, BFD_RELOC_LO16);
4209 macro_build (&imm_expr, "ori", "t,r,i",
4210 treg, sreg, BFD_RELOC_LO16);
4211 macro_build (NULL, "nor", "d,v,t", treg, treg, 0);
4216 load_register (AT, &imm_expr, HAVE_64BIT_GPRS);
4217 macro_build (NULL, s2, "d,v,t", treg, sreg, AT);
4234 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
4236 macro_build (&offset_expr, s, "s,t,p", sreg, 0);
4239 load_register (AT, &imm_expr, HAVE_64BIT_GPRS);
4240 macro_build (&offset_expr, s, "s,t,p", sreg, AT);
4248 macro_build (&offset_expr, likely ? "bgezl" : "bgez", "s,p", sreg);
4253 macro_build (&offset_expr, likely ? "blezl" : "blez", "s,p", treg);
4256 macro_build (NULL, "slt", "d,v,t", AT, sreg, treg);
4257 macro_build (&offset_expr, likely ? "beql" : "beq", "s,t,p", AT, 0);
4263 /* check for > max integer */
4264 maxnum = 0x7fffffff;
4265 if (HAVE_64BIT_GPRS && sizeof (maxnum) > 4)
4272 if (imm_expr.X_op == O_constant
4273 && imm_expr.X_add_number >= maxnum
4274 && (HAVE_32BIT_GPRS || sizeof (maxnum) > 4))
4277 /* result is always false */
4279 macro_build (NULL, "nop", "", 0);
4281 macro_build (&offset_expr, "bnel", "s,t,p", 0, 0);
4284 if (imm_expr.X_op != O_constant)
4285 as_bad (_("Unsupported large constant"));
4286 ++imm_expr.X_add_number;
4290 if (mask == M_BGEL_I)
4292 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
4294 macro_build (&offset_expr, likely ? "bgezl" : "bgez", "s,p", sreg);
4297 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 1)
4299 macro_build (&offset_expr, likely ? "bgtzl" : "bgtz", "s,p", sreg);
4302 maxnum = 0x7fffffff;
4303 if (HAVE_64BIT_GPRS && sizeof (maxnum) > 4)
4310 maxnum = - maxnum - 1;
4311 if (imm_expr.X_op == O_constant
4312 && imm_expr.X_add_number <= maxnum
4313 && (HAVE_32BIT_GPRS || sizeof (maxnum) > 4))
4316 /* result is always true */
4317 as_warn (_("Branch %s is always true"), ip->insn_mo->name);
4318 macro_build (&offset_expr, "b", "p");
4322 macro_build (&offset_expr, likely ? "beql" : "beq", "s,t,p", AT, 0);
4332 macro_build (&offset_expr, likely ? "beql" : "beq",
4336 macro_build (NULL, "sltu", "d,v,t", AT, sreg, treg);
4337 macro_build (&offset_expr, likely ? "beql" : "beq", "s,t,p", AT, 0);
4345 && imm_expr.X_op == O_constant
4346 && imm_expr.X_add_number == (offsetT) 0xffffffff))
4348 if (imm_expr.X_op != O_constant)
4349 as_bad (_("Unsupported large constant"));
4350 ++imm_expr.X_add_number;
4354 if (mask == M_BGEUL_I)
4356 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
4358 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 1)
4360 macro_build (&offset_expr, likely ? "bnel" : "bne",
4365 macro_build (&offset_expr, likely ? "beql" : "beq", "s,t,p", AT, 0);
4373 macro_build (&offset_expr, likely ? "bgtzl" : "bgtz", "s,p", sreg);
4378 macro_build (&offset_expr, likely ? "bltzl" : "bltz", "s,p", treg);
4381 macro_build (NULL, "slt", "d,v,t", AT, treg, sreg);
4382 macro_build (&offset_expr, likely ? "bnel" : "bne", "s,t,p", AT, 0);
4390 macro_build (&offset_expr, likely ? "bnel" : "bne",
4396 macro_build (NULL, "sltu", "d,v,t", AT, treg, sreg);
4397 macro_build (&offset_expr, likely ? "bnel" : "bne", "s,t,p", AT, 0);
4405 macro_build (&offset_expr, likely ? "blezl" : "blez", "s,p", sreg);
4410 macro_build (&offset_expr, likely ? "bgezl" : "bgez", "s,p", treg);
4413 macro_build (NULL, "slt", "d,v,t", AT, treg, sreg);
4414 macro_build (&offset_expr, likely ? "beql" : "beq", "s,t,p", AT, 0);
4420 maxnum = 0x7fffffff;
4421 if (HAVE_64BIT_GPRS && sizeof (maxnum) > 4)
4428 if (imm_expr.X_op == O_constant
4429 && imm_expr.X_add_number >= maxnum
4430 && (HAVE_32BIT_GPRS || sizeof (maxnum) > 4))
4432 if (imm_expr.X_op != O_constant)
4433 as_bad (_("Unsupported large constant"));
4434 ++imm_expr.X_add_number;
4438 if (mask == M_BLTL_I)
4440 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
4442 macro_build (&offset_expr, likely ? "bltzl" : "bltz", "s,p", sreg);
4445 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 1)
4447 macro_build (&offset_expr, likely ? "blezl" : "blez", "s,p", sreg);
4451 macro_build (&offset_expr, likely ? "bnel" : "bne", "s,t,p", AT, 0);
4459 macro_build (&offset_expr, likely ? "beql" : "beq",
4465 macro_build (NULL, "sltu", "d,v,t", AT, treg, sreg);
4466 macro_build (&offset_expr, likely ? "beql" : "beq", "s,t,p", AT, 0);
4474 && imm_expr.X_op == O_constant
4475 && imm_expr.X_add_number == (offsetT) 0xffffffff))
4477 if (imm_expr.X_op != O_constant)
4478 as_bad (_("Unsupported large constant"));
4479 ++imm_expr.X_add_number;
4483 if (mask == M_BLTUL_I)
4485 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
4487 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 1)
4489 macro_build (&offset_expr, likely ? "beql" : "beq",
4494 macro_build (&offset_expr, likely ? "bnel" : "bne", "s,t,p", AT, 0);
4502 macro_build (&offset_expr, likely ? "bltzl" : "bltz", "s,p", sreg);
4507 macro_build (&offset_expr, likely ? "bgtzl" : "bgtz", "s,p", treg);
4510 macro_build (NULL, "slt", "d,v,t", AT, sreg, treg);
4511 macro_build (&offset_expr, likely ? "bnel" : "bne", "s,t,p", AT, 0);
4521 macro_build (&offset_expr, likely ? "bnel" : "bne",
4525 macro_build (NULL, "sltu", "d,v,t", AT, sreg, treg);
4526 macro_build (&offset_expr, likely ? "bnel" : "bne", "s,t,p", AT, 0);
4534 if (imm_expr.X_op != O_constant || imm2_expr.X_op != O_constant)
4536 as_bad (_("Unsupported large constant"));
4541 pos = (unsigned long) imm_expr.X_add_number;
4542 size = (unsigned long) imm2_expr.X_add_number;
4547 as_bad (_("Improper position (%lu)"), pos);
4550 if (size == 0 || size > 64
4551 || (pos + size - 1) > 63)
4553 as_bad (_("Improper extract size (%lu, position %lu)"),
4558 if (size <= 32 && pos < 32)
4563 else if (size <= 32)
4573 macro_build ((expressionS *) NULL, s, fmt, treg, sreg, pos, size - 1);
4582 if (imm_expr.X_op != O_constant || imm2_expr.X_op != O_constant)
4584 as_bad (_("Unsupported large constant"));
4589 pos = (unsigned long) imm_expr.X_add_number;
4590 size = (unsigned long) imm2_expr.X_add_number;
4595 as_bad (_("Improper position (%lu)"), pos);
4598 if (size == 0 || size > 64
4599 || (pos + size - 1) > 63)
4601 as_bad (_("Improper insert size (%lu, position %lu)"),
4606 if (pos < 32 && (pos + size - 1) < 32)
4621 macro_build ((expressionS *) NULL, s, fmt, treg, sreg, pos,
4638 as_warn (_("Divide by zero."));
4640 macro_build (NULL, "teq", "s,t,q", 0, 0, 7);
4642 macro_build (NULL, "break", "c", 7);
4646 mips_emit_delays (TRUE);
4647 ++mips_opts.noreorder;
4648 mips_any_noreorder = 1;
4651 macro_build (NULL, "teq", "s,t,q", treg, 0, 7);
4652 macro_build (NULL, dbl ? "ddiv" : "div", "z,s,t", sreg, treg);
4656 expr1.X_add_number = 8;
4657 macro_build (&expr1, "bne", "s,t,p", treg, 0);
4658 macro_build (NULL, dbl ? "ddiv" : "div", "z,s,t", sreg, treg);
4659 macro_build (NULL, "break", "c", 7);
4661 expr1.X_add_number = -1;
4662 macro_build (&expr1, dbl ? "daddiu" : "addiu", "t,r,j", AT, 0,
4664 expr1.X_add_number = mips_trap ? (dbl ? 12 : 8) : (dbl ? 20 : 16);
4665 macro_build (&expr1, "bne", "s,t,p", treg, AT);
4668 expr1.X_add_number = 1;
4669 macro_build (&expr1, "daddiu", "t,r,j", AT, 0, BFD_RELOC_LO16);
4670 macro_build (NULL, "dsll32", "d,w,<", AT, AT, 31);
4674 expr1.X_add_number = 0x80000000;
4675 macro_build (&expr1, "lui", "t,u", AT, BFD_RELOC_HI16);
4679 macro_build (NULL, "teq", "s,t,q", sreg, AT, 6);
4680 /* We want to close the noreorder block as soon as possible, so
4681 that later insns are available for delay slot filling. */
4682 --mips_opts.noreorder;
4686 expr1.X_add_number = 8;
4687 macro_build (&expr1, "bne", "s,t,p", sreg, AT);
4688 macro_build (NULL, "nop", "", 0);
4690 /* We want to close the noreorder block as soon as possible, so
4691 that later insns are available for delay slot filling. */
4692 --mips_opts.noreorder;
4694 macro_build (NULL, "break", "c", 6);
4696 macro_build (NULL, s, "d", dreg);
4735 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
4737 as_warn (_("Divide by zero."));
4739 macro_build (NULL, "teq", "s,t,q", 0, 0, 7);
4741 macro_build (NULL, "break", "c", 7);
4744 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 1)
4746 if (strcmp (s2, "mflo") == 0)
4747 move_register (dreg, sreg);
4749 move_register (dreg, 0);
4752 if (imm_expr.X_op == O_constant
4753 && imm_expr.X_add_number == -1
4754 && s[strlen (s) - 1] != 'u')
4756 if (strcmp (s2, "mflo") == 0)
4758 macro_build (NULL, dbl ? "dneg" : "neg", "d,w", dreg, sreg);
4761 move_register (dreg, 0);
4765 load_register (AT, &imm_expr, dbl);
4766 macro_build (NULL, s, "z,s,t", sreg, AT);
4767 macro_build (NULL, s2, "d", dreg);
4786 mips_emit_delays (TRUE);
4787 ++mips_opts.noreorder;
4788 mips_any_noreorder = 1;
4791 macro_build (NULL, "teq", "s,t,q", treg, 0, 7);
4792 macro_build (NULL, s, "z,s,t", sreg, treg);
4793 /* We want to close the noreorder block as soon as possible, so
4794 that later insns are available for delay slot filling. */
4795 --mips_opts.noreorder;
4799 expr1.X_add_number = 8;
4800 macro_build (&expr1, "bne", "s,t,p", treg, 0);
4801 macro_build (NULL, s, "z,s,t", sreg, treg);
4803 /* We want to close the noreorder block as soon as possible, so
4804 that later insns are available for delay slot filling. */
4805 --mips_opts.noreorder;
4806 macro_build (NULL, "break", "c", 7);
4808 macro_build (NULL, s2, "d", dreg);
4820 /* Load the address of a symbol into a register. If breg is not
4821 zero, we then add a base register to it. */
4823 if (dbl && HAVE_32BIT_GPRS)
4824 as_warn (_("dla used to load 32-bit register"));
4826 if (! dbl && HAVE_64BIT_OBJECTS)
4827 as_warn (_("la used to load 64-bit address"));
4829 if (offset_expr.X_op == O_constant
4830 && offset_expr.X_add_number >= -0x8000
4831 && offset_expr.X_add_number < 0x8000)
4833 macro_build (&offset_expr,
4834 (dbl || HAVE_64BIT_ADDRESSES) ? "daddiu" : "addiu",
4835 "t,r,j", treg, sreg, BFD_RELOC_LO16);
4850 /* When generating embedded PIC code, we permit expressions of
4853 la $treg,foo-bar($breg)
4854 where bar is an address in the current section. These are used
4855 when getting the addresses of functions. We don't permit
4856 X_add_number to be non-zero, because if the symbol is
4857 external the relaxing code needs to know that any addend is
4858 purely the offset to X_op_symbol. */
4859 if (mips_pic == EMBEDDED_PIC
4860 && offset_expr.X_op == O_subtract
4861 && (symbol_constant_p (offset_expr.X_op_symbol)
4862 ? S_GET_SEGMENT (offset_expr.X_op_symbol) == now_seg
4863 : (symbol_equated_p (offset_expr.X_op_symbol)
4865 (symbol_get_value_expression (offset_expr.X_op_symbol)
4868 && (offset_expr.X_add_number == 0
4869 || OUTPUT_FLAVOR == bfd_target_elf_flavour))
4875 macro_build (&offset_expr, "lui", "t,u",
4876 tempreg, BFD_RELOC_PCREL_HI16_S);
4880 macro_build (&offset_expr, "lui", "t,u",
4881 tempreg, BFD_RELOC_PCREL_HI16_S);
4883 (dbl || HAVE_64BIT_ADDRESSES) ? "daddu" : "addu",
4884 "d,v,t", tempreg, tempreg, breg);
4886 macro_build (&offset_expr,
4887 (dbl || HAVE_64BIT_ADDRESSES) ? "daddiu" : "addiu",
4888 "t,r,j", treg, tempreg, BFD_RELOC_PCREL_LO16);
4894 if (offset_expr.X_op != O_symbol
4895 && offset_expr.X_op != O_constant)
4897 as_bad (_("expression too complex"));
4898 offset_expr.X_op = O_constant;
4901 if (offset_expr.X_op == O_constant)
4902 load_register (tempreg, &offset_expr,
4903 ((mips_pic == EMBEDDED_PIC || mips_pic == NO_PIC)
4904 ? (dbl || HAVE_64BIT_ADDRESSES)
4905 : HAVE_64BIT_ADDRESSES));
4906 else if (mips_pic == NO_PIC)
4908 /* If this is a reference to a GP relative symbol, we want
4909 addiu $tempreg,$gp,<sym> (BFD_RELOC_GPREL16)
4911 lui $tempreg,<sym> (BFD_RELOC_HI16_S)
4912 addiu $tempreg,$tempreg,<sym> (BFD_RELOC_LO16)
4913 If we have a constant, we need two instructions anyhow,
4914 so we may as well always use the latter form.
4916 With 64bit address space and a usable $at we want
4917 lui $tempreg,<sym> (BFD_RELOC_MIPS_HIGHEST)
4918 lui $at,<sym> (BFD_RELOC_HI16_S)
4919 daddiu $tempreg,<sym> (BFD_RELOC_MIPS_HIGHER)
4920 daddiu $at,<sym> (BFD_RELOC_LO16)
4922 daddu $tempreg,$tempreg,$at
4924 If $at is already in use, we use a path which is suboptimal
4925 on superscalar processors.
4926 lui $tempreg,<sym> (BFD_RELOC_MIPS_HIGHEST)
4927 daddiu $tempreg,<sym> (BFD_RELOC_MIPS_HIGHER)
4929 daddiu $tempreg,<sym> (BFD_RELOC_HI16_S)
4931 daddiu $tempreg,<sym> (BFD_RELOC_LO16)
4933 if (HAVE_64BIT_ADDRESSES)
4935 /* ??? We don't provide a GP-relative alternative for
4936 these macros. It used not to be possible with the
4937 original relaxation code, but it could be done now. */
4939 if (used_at == 0 && ! mips_opts.noat)
4941 macro_build (&offset_expr, "lui", "t,u",
4942 tempreg, BFD_RELOC_MIPS_HIGHEST);
4943 macro_build (&offset_expr, "lui", "t,u",
4944 AT, BFD_RELOC_HI16_S);
4945 macro_build (&offset_expr, "daddiu", "t,r,j",
4946 tempreg, tempreg, BFD_RELOC_MIPS_HIGHER);
4947 macro_build (&offset_expr, "daddiu", "t,r,j",
4948 AT, AT, BFD_RELOC_LO16);
4949 macro_build (NULL, "dsll32", "d,w,<", tempreg, tempreg, 0);
4950 macro_build (NULL, "daddu", "d,v,t", tempreg, tempreg, AT);
4955 macro_build (&offset_expr, "lui", "t,u",
4956 tempreg, BFD_RELOC_MIPS_HIGHEST);
4957 macro_build (&offset_expr, "daddiu", "t,r,j",
4958 tempreg, tempreg, BFD_RELOC_MIPS_HIGHER);
4959 macro_build (NULL, "dsll", "d,w,<", tempreg, tempreg, 16);
4960 macro_build (&offset_expr, "daddiu", "t,r,j",
4961 tempreg, tempreg, BFD_RELOC_HI16_S);
4962 macro_build (NULL, "dsll", "d,w,<", tempreg, tempreg, 16);
4963 macro_build (&offset_expr, "daddiu", "t,r,j",
4964 tempreg, tempreg, BFD_RELOC_LO16);
4969 if ((valueT) offset_expr.X_add_number <= MAX_GPREL_OFFSET
4970 && ! nopic_need_relax (offset_expr.X_add_symbol, 1))
4972 relax_start (offset_expr.X_add_symbol);
4973 macro_build (&offset_expr, ADDRESS_ADDI_INSN, "t,r,j",
4974 tempreg, mips_gp_register, BFD_RELOC_GPREL16);
4977 macro_build_lui (&offset_expr, tempreg);
4978 macro_build (&offset_expr, ADDRESS_ADDI_INSN, "t,r,j",
4979 tempreg, tempreg, BFD_RELOC_LO16);
4980 if (mips_relax.sequence)
4984 else if (mips_pic == SVR4_PIC && ! mips_big_got && ! HAVE_NEWABI)
4986 int lw_reloc_type = (int) BFD_RELOC_MIPS_GOT16;
4988 /* If this is a reference to an external symbol, and there
4989 is no constant, we want
4990 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
4991 or for lca or if tempreg is PIC_CALL_REG
4992 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_CALL16)
4993 For a local symbol, we want
4994 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
4996 addiu $tempreg,$tempreg,<sym> (BFD_RELOC_LO16)
4998 If we have a small constant, and this is a reference to
4999 an external symbol, we want
5000 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
5002 addiu $tempreg,$tempreg,<constant>
5003 For a local symbol, we want the same instruction
5004 sequence, but we output a BFD_RELOC_LO16 reloc on the
5007 If we have a large constant, and this is a reference to
5008 an external symbol, we want
5009 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
5010 lui $at,<hiconstant>
5011 addiu $at,$at,<loconstant>
5012 addu $tempreg,$tempreg,$at
5013 For a local symbol, we want the same instruction
5014 sequence, but we output a BFD_RELOC_LO16 reloc on the
5018 if (offset_expr.X_add_number == 0)
5020 if (breg == 0 && (call || tempreg == PIC_CALL_REG))
5021 lw_reloc_type = (int) BFD_RELOC_MIPS_CALL16;
5023 relax_start (offset_expr.X_add_symbol);
5024 macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)", tempreg,
5025 lw_reloc_type, mips_gp_register);
5028 /* We're going to put in an addu instruction using
5029 tempreg, so we may as well insert the nop right
5031 macro_build (NULL, "nop", "");
5034 macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)",
5035 tempreg, BFD_RELOC_MIPS_GOT16, mips_gp_register);
5036 macro_build (NULL, "nop", "");
5037 macro_build (&offset_expr, ADDRESS_ADDI_INSN, "t,r,j",
5038 tempreg, tempreg, BFD_RELOC_LO16);
5040 /* FIXME: If breg == 0, and the next instruction uses
5041 $tempreg, then if this variant case is used an extra
5042 nop will be generated. */
5044 else if (offset_expr.X_add_number >= -0x8000
5045 && offset_expr.X_add_number < 0x8000)
5047 load_got_offset (tempreg, &offset_expr);
5048 macro_build (NULL, "nop", "");
5049 add_got_offset (tempreg, &offset_expr);
5053 expr1.X_add_number = offset_expr.X_add_number;
5054 offset_expr.X_add_number =
5055 ((offset_expr.X_add_number + 0x8000) & 0xffff) - 0x8000;
5056 load_got_offset (tempreg, &offset_expr);
5057 /* If we are going to add in a base register, and the
5058 target register and the base register are the same,
5059 then we are using AT as a temporary register. Since
5060 we want to load the constant into AT, we add our
5061 current AT (from the global offset table) and the
5062 register into the register now, and pretend we were
5063 not using a base register. */
5066 macro_build (NULL, "nop", "");
5067 macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
5073 /* Set mips_optimize around the lui instruction to avoid
5074 inserting an unnecessary nop after the lw. */
5075 hold_mips_optimize = mips_optimize;
5077 macro_build_lui (&expr1, AT);
5078 mips_optimize = hold_mips_optimize;
5080 add_got_offset (AT, &offset_expr);
5081 macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
5082 tempreg, tempreg, AT);
5086 else if (mips_pic == SVR4_PIC && ! mips_big_got && HAVE_NEWABI)
5088 int add_breg_early = 0;
5090 /* If this is a reference to an external, and there is no
5091 constant, or local symbol (*), with or without a
5093 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT_DISP)
5094 or for lca or if tempreg is PIC_CALL_REG
5095 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_CALL16)
5097 If we have a small constant, and this is a reference to
5098 an external symbol, we want
5099 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT_DISP)
5100 addiu $tempreg,$tempreg,<constant>
5102 If we have a large constant, and this is a reference to
5103 an external symbol, we want
5104 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT_DISP)
5105 lui $at,<hiconstant>
5106 addiu $at,$at,<loconstant>
5107 addu $tempreg,$tempreg,$at
5109 (*) Other assemblers seem to prefer GOT_PAGE/GOT_OFST for
5110 local symbols, even though it introduces an additional
5113 if (offset_expr.X_add_number)
5115 expr1.X_add_number = offset_expr.X_add_number;
5116 offset_expr.X_add_number = 0;
5118 relax_start (offset_expr.X_add_symbol);
5119 macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)", tempreg,
5120 BFD_RELOC_MIPS_GOT_DISP, mips_gp_register);
5122 if (expr1.X_add_number >= -0x8000
5123 && expr1.X_add_number < 0x8000)
5125 macro_build (&expr1, ADDRESS_ADDI_INSN, "t,r,j",
5126 tempreg, tempreg, BFD_RELOC_LO16);
5128 else if (IS_SEXT_32BIT_NUM (expr1.X_add_number + 0x8000))
5132 /* If we are going to add in a base register, and the
5133 target register and the base register are the same,
5134 then we are using AT as a temporary register. Since
5135 we want to load the constant into AT, we add our
5136 current AT (from the global offset table) and the
5137 register into the register now, and pretend we were
5138 not using a base register. */
5143 assert (tempreg == AT);
5144 macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
5150 macro_build_lui (&expr1, AT);
5151 macro_build (&expr1, ADDRESS_ADDI_INSN, "t,r,j",
5152 AT, AT, BFD_RELOC_LO16);
5153 macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
5159 as_bad (_("PIC code offset overflow (max 32 signed bits)"));
5162 offset_expr.X_add_number = expr1.X_add_number;
5164 macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)", tempreg,
5165 BFD_RELOC_MIPS_GOT_DISP, mips_gp_register);
5168 macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
5169 treg, tempreg, breg);
5175 else if (breg == 0 && (call || tempreg == PIC_CALL_REG))
5177 relax_start (offset_expr.X_add_symbol);
5178 macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)", tempreg,
5179 BFD_RELOC_MIPS_CALL16, mips_gp_register);
5181 macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)", tempreg,
5182 BFD_RELOC_MIPS_GOT_DISP, mips_gp_register);
5187 macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)", tempreg,
5188 BFD_RELOC_MIPS_GOT_DISP, mips_gp_register);
5191 else if (mips_pic == SVR4_PIC && ! HAVE_NEWABI)
5194 int lui_reloc_type = (int) BFD_RELOC_MIPS_GOT_HI16;
5195 int lw_reloc_type = (int) BFD_RELOC_MIPS_GOT_LO16;
5196 int local_reloc_type = (int) BFD_RELOC_MIPS_GOT16;
5198 /* This is the large GOT case. If this is a reference to an
5199 external symbol, and there is no constant, we want
5200 lui $tempreg,<sym> (BFD_RELOC_MIPS_GOT_HI16)
5201 addu $tempreg,$tempreg,$gp
5202 lw $tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_LO16)
5203 or for lca or if tempreg is PIC_CALL_REG
5204 lui $tempreg,<sym> (BFD_RELOC_MIPS_CALL_HI16)
5205 addu $tempreg,$tempreg,$gp
5206 lw $tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_CALL_LO16)
5207 For a local symbol, we want
5208 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
5210 addiu $tempreg,$tempreg,<sym> (BFD_RELOC_LO16)
5212 If we have a small constant, and this is a reference to
5213 an external symbol, we want
5214 lui $tempreg,<sym> (BFD_RELOC_MIPS_GOT_HI16)
5215 addu $tempreg,$tempreg,$gp
5216 lw $tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_LO16)
5218 addiu $tempreg,$tempreg,<constant>
5219 For a local symbol, we want
5220 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
5222 addiu $tempreg,$tempreg,<constant> (BFD_RELOC_LO16)
5224 If we have a large constant, and this is a reference to
5225 an external symbol, we want
5226 lui $tempreg,<sym> (BFD_RELOC_MIPS_GOT_HI16)
5227 addu $tempreg,$tempreg,$gp
5228 lw $tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_LO16)
5229 lui $at,<hiconstant>
5230 addiu $at,$at,<loconstant>
5231 addu $tempreg,$tempreg,$at
5232 For a local symbol, we want
5233 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
5234 lui $at,<hiconstant>
5235 addiu $at,$at,<loconstant> (BFD_RELOC_LO16)
5236 addu $tempreg,$tempreg,$at
5239 expr1.X_add_number = offset_expr.X_add_number;
5240 offset_expr.X_add_number = 0;
5241 relax_start (offset_expr.X_add_symbol);
5242 gpdelay = reg_needs_delay (mips_gp_register);
5243 if (expr1.X_add_number == 0 && breg == 0
5244 && (call || tempreg == PIC_CALL_REG))
5246 lui_reloc_type = (int) BFD_RELOC_MIPS_CALL_HI16;
5247 lw_reloc_type = (int) BFD_RELOC_MIPS_CALL_LO16;
5249 macro_build (&offset_expr, "lui", "t,u", tempreg, lui_reloc_type);
5250 macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
5251 tempreg, tempreg, mips_gp_register);
5252 macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)",
5253 tempreg, lw_reloc_type, tempreg);
5254 if (expr1.X_add_number == 0)
5258 /* We're going to put in an addu instruction using
5259 tempreg, so we may as well insert the nop right
5261 macro_build (NULL, "nop", "");
5264 else if (expr1.X_add_number >= -0x8000
5265 && expr1.X_add_number < 0x8000)
5267 macro_build (NULL, "nop", "");
5268 macro_build (&expr1, ADDRESS_ADDI_INSN, "t,r,j",
5269 tempreg, tempreg, BFD_RELOC_LO16);
5275 /* If we are going to add in a base register, and the
5276 target register and the base register are the same,
5277 then we are using AT as a temporary register. Since
5278 we want to load the constant into AT, we add our
5279 current AT (from the global offset table) and the
5280 register into the register now, and pretend we were
5281 not using a base register. */
5286 assert (tempreg == AT);
5287 macro_build (NULL, "nop", "");
5288 macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
5293 /* Set mips_optimize around the lui instruction to avoid
5294 inserting an unnecessary nop after the lw. */
5295 hold_mips_optimize = mips_optimize;
5297 macro_build_lui (&expr1, AT);
5298 mips_optimize = hold_mips_optimize;
5300 macro_build (&expr1, ADDRESS_ADDI_INSN, "t,r,j",
5301 AT, AT, BFD_RELOC_LO16);
5302 macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", dreg, dreg, AT);
5306 offset_expr.X_add_number =
5307 ((expr1.X_add_number + 0x8000) & 0xffff) - 0x8000;
5312 /* This is needed because this instruction uses $gp, but
5313 the first instruction on the main stream does not. */
5314 macro_build (NULL, "nop", "");
5317 macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)", tempreg,
5318 local_reloc_type, mips_gp_register);
5319 if (expr1.X_add_number >= -0x8000
5320 && expr1.X_add_number < 0x8000)
5322 macro_build (NULL, "nop", "");
5323 macro_build (&offset_expr, ADDRESS_ADDI_INSN, "t,r,j",
5324 tempreg, tempreg, BFD_RELOC_LO16);
5325 /* FIXME: If add_number is 0, and there was no base
5326 register, the external symbol case ended with a load,
5327 so if the symbol turns out to not be external, and
5328 the next instruction uses tempreg, an unnecessary nop
5329 will be inserted. */
5335 /* We must add in the base register now, as in the
5336 external symbol case. */
5337 assert (tempreg == AT);
5338 macro_build (NULL, "nop", "");
5339 macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
5342 /* We set breg to 0 because we have arranged to add
5343 it in in both cases. */
5347 macro_build_lui (&expr1, AT);
5348 macro_build (&offset_expr, ADDRESS_ADDI_INSN, "t,r,j",
5349 AT, AT, BFD_RELOC_LO16);
5350 macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
5351 tempreg, tempreg, AT);
5355 else if (mips_pic == SVR4_PIC && HAVE_NEWABI)
5357 int lui_reloc_type = (int) BFD_RELOC_MIPS_GOT_HI16;
5358 int lw_reloc_type = (int) BFD_RELOC_MIPS_GOT_LO16;
5359 int add_breg_early = 0;
5361 /* This is the large GOT case. If this is a reference to an
5362 external symbol, and there is no constant, we want
5363 lui $tempreg,<sym> (BFD_RELOC_MIPS_GOT_HI16)
5364 add $tempreg,$tempreg,$gp
5365 lw $tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_LO16)
5366 or for lca or if tempreg is PIC_CALL_REG
5367 lui $tempreg,<sym> (BFD_RELOC_MIPS_CALL_HI16)
5368 add $tempreg,$tempreg,$gp
5369 lw $tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_CALL_LO16)
5371 If we have a small constant, and this is a reference to
5372 an external symbol, we want
5373 lui $tempreg,<sym> (BFD_RELOC_MIPS_GOT_HI16)
5374 add $tempreg,$tempreg,$gp
5375 lw $tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_LO16)
5376 addi $tempreg,$tempreg,<constant>
5378 If we have a large constant, and this is a reference to
5379 an external symbol, we want
5380 lui $tempreg,<sym> (BFD_RELOC_MIPS_GOT_HI16)
5381 addu $tempreg,$tempreg,$gp
5382 lw $tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_LO16)
5383 lui $at,<hiconstant>
5384 addi $at,$at,<loconstant>
5385 add $tempreg,$tempreg,$at
5387 If we have NewABI, and we know it's a local symbol, we want
5388 lw $reg,<sym>($gp) (BFD_RELOC_MIPS_GOT_PAGE)
5389 addiu $reg,$reg,<sym> (BFD_RELOC_MIPS_GOT_OFST)
5390 otherwise we have to resort to GOT_HI16/GOT_LO16. */
5392 relax_start (offset_expr.X_add_symbol);
5394 expr1.X_add_number = offset_expr.X_add_number;
5395 offset_expr.X_add_number = 0;
5397 if (expr1.X_add_number == 0 && breg == 0
5398 && (call || tempreg == PIC_CALL_REG))
5400 lui_reloc_type = (int) BFD_RELOC_MIPS_CALL_HI16;
5401 lw_reloc_type = (int) BFD_RELOC_MIPS_CALL_LO16;
5403 macro_build (&offset_expr, "lui", "t,u", tempreg, lui_reloc_type);
5404 macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
5405 tempreg, tempreg, mips_gp_register);
5406 macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)",
5407 tempreg, lw_reloc_type, tempreg);
5409 if (expr1.X_add_number == 0)
5411 else if (expr1.X_add_number >= -0x8000
5412 && expr1.X_add_number < 0x8000)
5414 macro_build (&expr1, ADDRESS_ADDI_INSN, "t,r,j",
5415 tempreg, tempreg, BFD_RELOC_LO16);
5417 else if (IS_SEXT_32BIT_NUM (expr1.X_add_number + 0x8000))
5421 /* If we are going to add in a base register, and the
5422 target register and the base register are the same,
5423 then we are using AT as a temporary register. Since
5424 we want to load the constant into AT, we add our
5425 current AT (from the global offset table) and the
5426 register into the register now, and pretend we were
5427 not using a base register. */
5432 assert (tempreg == AT);
5433 macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
5439 /* Set mips_optimize around the lui instruction to avoid
5440 inserting an unnecessary nop after the lw. */
5441 macro_build_lui (&expr1, AT);
5442 macro_build (&expr1, ADDRESS_ADDI_INSN, "t,r,j",
5443 AT, AT, BFD_RELOC_LO16);
5444 macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", dreg, dreg, AT);
5449 as_bad (_("PIC code offset overflow (max 32 signed bits)"));
5452 offset_expr.X_add_number = expr1.X_add_number;
5453 macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)", tempreg,
5454 BFD_RELOC_MIPS_GOT_PAGE, mips_gp_register);
5455 macro_build (&offset_expr, ADDRESS_ADDI_INSN, "t,r,j", tempreg,
5456 tempreg, BFD_RELOC_MIPS_GOT_OFST);
5459 macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
5460 treg, tempreg, breg);
5466 else if (mips_pic == EMBEDDED_PIC)
5469 addiu $tempreg,$gp,<sym> (BFD_RELOC_GPREL16)
5471 macro_build (&offset_expr, ADDRESS_ADDI_INSN, "t,r,j", tempreg,
5472 mips_gp_register, BFD_RELOC_GPREL16);
5481 if (mips_pic == EMBEDDED_PIC || mips_pic == NO_PIC)
5482 s = (dbl || HAVE_64BIT_ADDRESSES) ? "daddu" : "addu";
5484 s = ADDRESS_ADD_INSN;
5486 macro_build (NULL, s, "d,v,t", treg, tempreg, breg);
5495 /* The j instruction may not be used in PIC code, since it
5496 requires an absolute address. We convert it to a b
5498 if (mips_pic == NO_PIC)
5499 macro_build (&offset_expr, "j", "a");
5501 macro_build (&offset_expr, "b", "p");
5504 /* The jal instructions must be handled as macros because when
5505 generating PIC code they expand to multi-instruction
5506 sequences. Normally they are simple instructions. */
5511 if (mips_pic == NO_PIC
5512 || mips_pic == EMBEDDED_PIC)
5513 macro_build (NULL, "jalr", "d,s", dreg, sreg);
5514 else if (mips_pic == SVR4_PIC)
5516 if (sreg != PIC_CALL_REG)
5517 as_warn (_("MIPS PIC call to register other than $25"));
5519 macro_build (NULL, "jalr", "d,s", dreg, sreg);
5522 if (mips_cprestore_offset < 0)
5523 as_warn (_("No .cprestore pseudo-op used in PIC code"));
5526 if (! mips_frame_reg_valid)
5528 as_warn (_("No .frame pseudo-op used in PIC code"));
5529 /* Quiet this warning. */
5530 mips_frame_reg_valid = 1;
5532 if (! mips_cprestore_valid)
5534 as_warn (_("No .cprestore pseudo-op used in PIC code"));
5535 /* Quiet this warning. */
5536 mips_cprestore_valid = 1;
5538 expr1.X_add_number = mips_cprestore_offset;
5539 macro_build_ldst_constoffset (&expr1, ADDRESS_LOAD_INSN,
5542 HAVE_64BIT_ADDRESSES);
5552 if (mips_pic == NO_PIC)
5553 macro_build (&offset_expr, "jal", "a");
5554 else if (mips_pic == SVR4_PIC)
5556 /* If this is a reference to an external symbol, and we are
5557 using a small GOT, we want
5558 lw $25,<sym>($gp) (BFD_RELOC_MIPS_CALL16)
5562 lw $gp,cprestore($sp)
5563 The cprestore value is set using the .cprestore
5564 pseudo-op. If we are using a big GOT, we want
5565 lui $25,<sym> (BFD_RELOC_MIPS_CALL_HI16)
5567 lw $25,<sym>($25) (BFD_RELOC_MIPS_CALL_LO16)
5571 lw $gp,cprestore($sp)
5572 If the symbol is not external, we want
5573 lw $25,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
5575 addiu $25,$25,<sym> (BFD_RELOC_LO16)
5578 lw $gp,cprestore($sp)
5580 For NewABI, we use the same CALL16 or CALL_HI16/CALL_LO16
5581 sequences above, minus nops, unless the symbol is local,
5582 which enables us to use GOT_PAGE/GOT_OFST (big got) or
5588 relax_start (offset_expr.X_add_symbol);
5589 macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)",
5590 PIC_CALL_REG, BFD_RELOC_MIPS_CALL16,
5593 macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)",
5594 PIC_CALL_REG, BFD_RELOC_MIPS_GOT_DISP,
5600 relax_start (offset_expr.X_add_symbol);
5601 macro_build (&offset_expr, "lui", "t,u", PIC_CALL_REG,
5602 BFD_RELOC_MIPS_CALL_HI16);
5603 macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", PIC_CALL_REG,
5604 PIC_CALL_REG, mips_gp_register);
5605 macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)",
5606 PIC_CALL_REG, BFD_RELOC_MIPS_CALL_LO16,
5609 macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)",
5610 PIC_CALL_REG, BFD_RELOC_MIPS_GOT_PAGE,
5612 macro_build (&offset_expr, ADDRESS_ADDI_INSN, "t,r,j",
5613 PIC_CALL_REG, PIC_CALL_REG,
5614 BFD_RELOC_MIPS_GOT_OFST);
5618 macro_build_jalr (&offset_expr);
5622 relax_start (offset_expr.X_add_symbol);
5625 macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)",
5626 PIC_CALL_REG, BFD_RELOC_MIPS_CALL16,
5628 macro_build (NULL, "nop", "");
5635 gpdelay = reg_needs_delay (mips_gp_register);
5636 macro_build (&offset_expr, "lui", "t,u", PIC_CALL_REG,
5637 BFD_RELOC_MIPS_CALL_HI16);
5638 macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", PIC_CALL_REG,
5639 PIC_CALL_REG, mips_gp_register);
5640 macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)",
5641 PIC_CALL_REG, BFD_RELOC_MIPS_CALL_LO16,
5643 macro_build (NULL, "nop", "");
5646 macro_build (NULL, "nop", "");
5648 macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)",
5649 PIC_CALL_REG, BFD_RELOC_MIPS_GOT16,
5651 macro_build (NULL, "nop", "");
5652 macro_build (&offset_expr, ADDRESS_ADDI_INSN, "t,r,j",
5653 PIC_CALL_REG, PIC_CALL_REG, BFD_RELOC_LO16);
5655 macro_build_jalr (&offset_expr);
5657 if (mips_cprestore_offset < 0)
5658 as_warn (_("No .cprestore pseudo-op used in PIC code"));
5661 if (! mips_frame_reg_valid)
5663 as_warn (_("No .frame pseudo-op used in PIC code"));
5664 /* Quiet this warning. */
5665 mips_frame_reg_valid = 1;
5667 if (! mips_cprestore_valid)
5669 as_warn (_("No .cprestore pseudo-op used in PIC code"));
5670 /* Quiet this warning. */
5671 mips_cprestore_valid = 1;
5673 if (mips_opts.noreorder)
5674 macro_build (NULL, "nop", "");
5675 expr1.X_add_number = mips_cprestore_offset;
5676 macro_build_ldst_constoffset (&expr1, ADDRESS_LOAD_INSN,
5679 HAVE_64BIT_ADDRESSES);
5683 else if (mips_pic == EMBEDDED_PIC)
5685 macro_build (&offset_expr, "bal", "p");
5686 /* The linker may expand the call to a longer sequence which
5687 uses $at, so we must break rather than return. */
5712 /* Itbl support may require additional care here. */
5717 /* Itbl support may require additional care here. */
5722 /* Itbl support may require additional care here. */
5727 /* Itbl support may require additional care here. */
5739 if (mips_opts.arch == CPU_R4650)
5741 as_bad (_("opcode not supported on this processor"));
5745 /* Itbl support may require additional care here. */
5750 /* Itbl support may require additional care here. */
5755 /* Itbl support may require additional care here. */
5775 if (breg == treg || coproc || lr)
5797 /* Itbl support may require additional care here. */
5802 /* Itbl support may require additional care here. */
5807 /* Itbl support may require additional care here. */
5812 /* Itbl support may require additional care here. */
5828 if (mips_opts.arch == CPU_R4650)
5830 as_bad (_("opcode not supported on this processor"));
5835 /* Itbl support may require additional care here. */
5839 /* Itbl support may require additional care here. */
5844 /* Itbl support may require additional care here. */
5856 /* Itbl support may require additional care here. */
5857 if (mask == M_LWC1_AB
5858 || mask == M_SWC1_AB
5859 || mask == M_LDC1_AB
5860 || mask == M_SDC1_AB
5869 /* Sign-extending 32-bit constants makes their handling easier.
5870 The HAVE_64BIT_GPRS... part is due to the linux kernel hack
5872 if ((! HAVE_64BIT_ADDRESSES
5873 && (! HAVE_64BIT_GPRS && offset_expr.X_op == O_constant))
5874 && (offset_expr.X_op == O_constant)
5875 && ! ((offset_expr.X_add_number & ~((bfd_vma) 0x7fffffff))
5876 == ~((bfd_vma) 0x7fffffff)))
5878 if (offset_expr.X_add_number & ~((bfd_vma) 0xffffffff))
5879 as_bad (_("constant too large"));
5881 offset_expr.X_add_number = (((offset_expr.X_add_number & 0xffffffff)
5882 ^ 0x80000000) - 0x80000000);
5885 /* For embedded PIC, we allow loads where the offset is calculated
5886 by subtracting a symbol in the current segment from an unknown
5887 symbol, relative to a base register, e.g.:
5888 <op> $treg, <sym>-<localsym>($breg)
5889 This is used by the compiler for switch statements. */
5890 if (mips_pic == EMBEDDED_PIC
5891 && offset_expr.X_op == O_subtract
5892 && (symbol_constant_p (offset_expr.X_op_symbol)
5893 ? S_GET_SEGMENT (offset_expr.X_op_symbol) == now_seg
5894 : (symbol_equated_p (offset_expr.X_op_symbol)
5896 (symbol_get_value_expression (offset_expr.X_op_symbol)
5900 && (offset_expr.X_add_number == 0
5901 || OUTPUT_FLAVOR == bfd_target_elf_flavour))
5903 /* For this case, we output the instructions:
5904 lui $tempreg,<sym> (BFD_RELOC_PCREL_HI16_S)
5905 addiu $tempreg,$tempreg,$breg
5906 <op> $treg,<sym>($tempreg) (BFD_RELOC_PCREL_LO16)
5907 If the relocation would fit entirely in 16 bits, it would be
5909 <op> $treg,<sym>($breg) (BFD_RELOC_PCREL_LO16)
5910 instead, but that seems quite difficult. */
5911 macro_build (&offset_expr, "lui", "t,u", tempreg,
5912 BFD_RELOC_PCREL_HI16_S);
5914 ((bfd_arch_bits_per_address (stdoutput) == 32
5915 || ! ISA_HAS_64BIT_REGS (mips_opts.isa))
5916 ? "addu" : "daddu"),
5917 "d,v,t", tempreg, tempreg, breg);
5918 macro_build (&offset_expr, s, fmt, treg,
5919 BFD_RELOC_PCREL_LO16, tempreg);
5925 if (offset_expr.X_op != O_constant
5926 && offset_expr.X_op != O_symbol)
5928 as_bad (_("expression too complex"));
5929 offset_expr.X_op = O_constant;
5932 /* A constant expression in PIC code can be handled just as it
5933 is in non PIC code. */
5934 if (mips_pic == NO_PIC
5935 || offset_expr.X_op == O_constant)
5937 /* If this is a reference to a GP relative symbol, and there
5938 is no base register, we want
5939 <op> $treg,<sym>($gp) (BFD_RELOC_GPREL16)
5940 Otherwise, if there is no base register, we want
5941 lui $tempreg,<sym> (BFD_RELOC_HI16_S)
5942 <op> $treg,<sym>($tempreg) (BFD_RELOC_LO16)
5943 If we have a constant, we need two instructions anyhow,
5944 so we always use the latter form.
5946 If we have a base register, and this is a reference to a
5947 GP relative symbol, we want
5948 addu $tempreg,$breg,$gp
5949 <op> $treg,<sym>($tempreg) (BFD_RELOC_GPREL16)
5951 lui $tempreg,<sym> (BFD_RELOC_HI16_S)
5952 addu $tempreg,$tempreg,$breg
5953 <op> $treg,<sym>($tempreg) (BFD_RELOC_LO16)
5954 With a constant we always use the latter case.
5956 With 64bit address space and no base register and $at usable,
5958 lui $tempreg,<sym> (BFD_RELOC_MIPS_HIGHEST)
5959 lui $at,<sym> (BFD_RELOC_HI16_S)
5960 daddiu $tempreg,<sym> (BFD_RELOC_MIPS_HIGHER)
5963 <op> $treg,<sym>($tempreg) (BFD_RELOC_LO16)
5964 If we have a base register, we want
5965 lui $tempreg,<sym> (BFD_RELOC_MIPS_HIGHEST)
5966 lui $at,<sym> (BFD_RELOC_HI16_S)
5967 daddiu $tempreg,<sym> (BFD_RELOC_MIPS_HIGHER)
5971 <op> $treg,<sym>($tempreg) (BFD_RELOC_LO16)
5973 Without $at we can't generate the optimal path for superscalar
5974 processors here since this would require two temporary registers.
5975 lui $tempreg,<sym> (BFD_RELOC_MIPS_HIGHEST)
5976 daddiu $tempreg,<sym> (BFD_RELOC_MIPS_HIGHER)
5978 daddiu $tempreg,<sym> (BFD_RELOC_HI16_S)
5980 <op> $treg,<sym>($tempreg) (BFD_RELOC_LO16)
5981 If we have a base register, we want
5982 lui $tempreg,<sym> (BFD_RELOC_MIPS_HIGHEST)
5983 daddiu $tempreg,<sym> (BFD_RELOC_MIPS_HIGHER)
5985 daddiu $tempreg,<sym> (BFD_RELOC_HI16_S)
5987 daddu $tempreg,$tempreg,$breg
5988 <op> $treg,<sym>($tempreg) (BFD_RELOC_LO16)
5990 If we have 64-bit addresses, as an optimization, for
5991 addresses which are 32-bit constants (e.g. kseg0/kseg1
5992 addresses) we fall back to the 32-bit address generation
5993 mechanism since it is more efficient. Note that due to
5994 the signed offset used by memory operations, the 32-bit
5995 range is shifted down by 32768 here. This code should
5996 probably attempt to generate 64-bit constants more
5997 efficiently in general.
5999 As an extension for architectures with 64-bit registers,
6000 we don't truncate 64-bit addresses given as literal
6001 constants down to 32 bits, to support existing practice
6002 in the mips64 Linux (the kernel), that compiles source
6003 files with -mabi=64, assembling them as o32 or n32 (with
6004 -Wa,-32 or -Wa,-n32). This is not beautiful, but since
6005 the whole kernel is loaded into a memory region that is
6006 addressable with sign-extended 32-bit addresses, it is
6007 wasteful to compute the upper 32 bits of every
6008 non-literal address, that takes more space and time.
6009 Some day this should probably be implemented as an
6010 assembler option, such that the kernel doesn't have to
6011 use such ugly hacks, even though it will still have to
6012 end up converting the binary to ELF32 for a number of
6013 platforms whose boot loaders don't support ELF64
6015 if ((HAVE_64BIT_ADDRESSES
6016 && ! (offset_expr.X_op == O_constant
6017 && IS_SEXT_32BIT_NUM (offset_expr.X_add_number + 0x8000)))
6019 && offset_expr.X_op == O_constant
6020 && ! IS_SEXT_32BIT_NUM (offset_expr.X_add_number + 0x8000)))
6022 /* ??? We don't provide a GP-relative alternative for
6023 these macros. It used not to be possible with the
6024 original relaxation code, but it could be done now. */
6026 if (used_at == 0 && ! mips_opts.noat)
6028 macro_build (&offset_expr, "lui", "t,u", tempreg,
6029 BFD_RELOC_MIPS_HIGHEST);
6030 macro_build (&offset_expr, "lui", "t,u", AT,
6032 macro_build (&offset_expr, "daddiu", "t,r,j", tempreg,
6033 tempreg, BFD_RELOC_MIPS_HIGHER);
6035 macro_build (NULL, "daddu", "d,v,t", AT, AT, breg);
6036 macro_build (NULL, "dsll32", "d,w,<", tempreg, tempreg, 0);
6037 macro_build (NULL, "daddu", "d,v,t", tempreg, tempreg, AT);
6038 macro_build (&offset_expr, s, fmt, treg, BFD_RELOC_LO16,
6044 macro_build (&offset_expr, "lui", "t,u", tempreg,
6045 BFD_RELOC_MIPS_HIGHEST);
6046 macro_build (&offset_expr, "daddiu", "t,r,j", tempreg,
6047 tempreg, BFD_RELOC_MIPS_HIGHER);
6048 macro_build (NULL, "dsll", "d,w,<", tempreg, tempreg, 16);
6049 macro_build (&offset_expr, "daddiu", "t,r,j", tempreg,
6050 tempreg, BFD_RELOC_HI16_S);
6051 macro_build (NULL, "dsll", "d,w,<", tempreg, tempreg, 16);
6053 macro_build (NULL, "daddu", "d,v,t",
6054 tempreg, tempreg, breg);
6055 macro_build (&offset_expr, s, fmt, treg,
6056 BFD_RELOC_LO16, tempreg);
6062 if (offset_expr.X_op == O_constant
6063 && ! IS_SEXT_32BIT_NUM (offset_expr.X_add_number + 0x8000))
6064 as_bad (_("load/store address overflow (max 32 bits)"));
6068 if ((valueT) offset_expr.X_add_number <= MAX_GPREL_OFFSET
6069 && ! nopic_need_relax (offset_expr.X_add_symbol, 1))
6071 relax_start (offset_expr.X_add_symbol);
6072 macro_build (&offset_expr, s, fmt, treg, BFD_RELOC_GPREL16,
6077 macro_build_lui (&offset_expr, tempreg);
6078 macro_build (&offset_expr, s, fmt, treg,
6079 BFD_RELOC_LO16, tempreg);
6080 if (mips_relax.sequence)
6085 if ((valueT) offset_expr.X_add_number <= MAX_GPREL_OFFSET
6086 && ! nopic_need_relax (offset_expr.X_add_symbol, 1))
6088 relax_start (offset_expr.X_add_symbol);
6089 macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
6090 tempreg, breg, mips_gp_register);
6091 macro_build (&offset_expr, s, fmt, treg,
6092 BFD_RELOC_GPREL16, tempreg);
6095 macro_build_lui (&offset_expr, tempreg);
6096 macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
6097 tempreg, tempreg, breg);
6098 macro_build (&offset_expr, s, fmt, treg,
6099 BFD_RELOC_LO16, tempreg);
6100 if (mips_relax.sequence)
6104 else if (mips_pic == SVR4_PIC && ! mips_big_got)
6106 int lw_reloc_type = (int) BFD_RELOC_MIPS_GOT16;
6108 /* If this is a reference to an external symbol, we want
6109 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
6111 <op> $treg,0($tempreg)
6113 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
6115 addiu $tempreg,$tempreg,<sym> (BFD_RELOC_LO16)
6116 <op> $treg,0($tempreg)
6119 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT_PAGE)
6120 <op> $treg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_OFST)
6122 If there is a base register, we add it to $tempreg before
6123 the <op>. If there is a constant, we stick it in the
6124 <op> instruction. We don't handle constants larger than
6125 16 bits, because we have no way to load the upper 16 bits
6126 (actually, we could handle them for the subset of cases
6127 in which we are not using $at). */
6128 assert (offset_expr.X_op == O_symbol);
6131 macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)", tempreg,
6132 BFD_RELOC_MIPS_GOT_PAGE, mips_gp_register);
6134 macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
6135 tempreg, tempreg, breg);
6136 macro_build (&offset_expr, s, fmt, treg,
6137 BFD_RELOC_MIPS_GOT_OFST, tempreg);
6144 expr1.X_add_number = offset_expr.X_add_number;
6145 offset_expr.X_add_number = 0;
6146 if (expr1.X_add_number < -0x8000
6147 || expr1.X_add_number >= 0x8000)
6148 as_bad (_("PIC code offset overflow (max 16 signed bits)"));
6149 macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)", tempreg,
6150 lw_reloc_type, mips_gp_register);
6151 macro_build (NULL, "nop", "");
6152 relax_start (offset_expr.X_add_symbol);
6154 macro_build (&offset_expr, ADDRESS_ADDI_INSN, "t,r,j", tempreg,
6155 tempreg, BFD_RELOC_LO16);
6158 macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
6159 tempreg, tempreg, breg);
6160 macro_build (&expr1, s, fmt, treg, BFD_RELOC_LO16, tempreg);
6162 else if (mips_pic == SVR4_PIC && ! HAVE_NEWABI)
6166 /* If this is a reference to an external symbol, we want
6167 lui $tempreg,<sym> (BFD_RELOC_MIPS_GOT_HI16)
6168 addu $tempreg,$tempreg,$gp
6169 lw $tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_LO16)
6170 <op> $treg,0($tempreg)
6172 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
6174 addiu $tempreg,$tempreg,<sym> (BFD_RELOC_LO16)
6175 <op> $treg,0($tempreg)
6176 If there is a base register, we add it to $tempreg before
6177 the <op>. If there is a constant, we stick it in the
6178 <op> instruction. We don't handle constants larger than
6179 16 bits, because we have no way to load the upper 16 bits
6180 (actually, we could handle them for the subset of cases
6181 in which we are not using $at). */
6182 assert (offset_expr.X_op == O_symbol);
6183 expr1.X_add_number = offset_expr.X_add_number;
6184 offset_expr.X_add_number = 0;
6185 if (expr1.X_add_number < -0x8000
6186 || expr1.X_add_number >= 0x8000)
6187 as_bad (_("PIC code offset overflow (max 16 signed bits)"));
6188 gpdelay = reg_needs_delay (mips_gp_register);
6189 relax_start (offset_expr.X_add_symbol);
6190 macro_build (&offset_expr, "lui", "t,u", tempreg,
6191 BFD_RELOC_MIPS_GOT_HI16);
6192 macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", tempreg, tempreg,
6194 macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)", tempreg,
6195 BFD_RELOC_MIPS_GOT_LO16, tempreg);
6198 macro_build (NULL, "nop", "");
6199 macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)", tempreg,
6200 BFD_RELOC_MIPS_GOT16, mips_gp_register);
6201 macro_build (NULL, "nop", "");
6202 macro_build (&offset_expr, ADDRESS_ADDI_INSN, "t,r,j", tempreg,
6203 tempreg, BFD_RELOC_LO16);
6207 macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
6208 tempreg, tempreg, breg);
6209 macro_build (&expr1, s, fmt, treg, BFD_RELOC_LO16, tempreg);
6211 else if (mips_pic == SVR4_PIC && HAVE_NEWABI)
6213 /* If this is a reference to an external symbol, we want
6214 lui $tempreg,<sym> (BFD_RELOC_MIPS_GOT_HI16)
6215 add $tempreg,$tempreg,$gp
6216 lw $tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_LO16)
6217 <op> $treg,<ofst>($tempreg)
6218 Otherwise, for local symbols, we want:
6219 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT_PAGE)
6220 <op> $treg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_OFST) */
6221 assert (offset_expr.X_op == O_symbol);
6222 expr1.X_add_number = offset_expr.X_add_number;
6223 offset_expr.X_add_number = 0;
6224 if (expr1.X_add_number < -0x8000
6225 || expr1.X_add_number >= 0x8000)
6226 as_bad (_("PIC code offset overflow (max 16 signed bits)"));
6227 relax_start (offset_expr.X_add_symbol);
6228 macro_build (&offset_expr, "lui", "t,u", tempreg,
6229 BFD_RELOC_MIPS_GOT_HI16);
6230 macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", tempreg, tempreg,
6232 macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)", tempreg,
6233 BFD_RELOC_MIPS_GOT_LO16, tempreg);
6235 macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
6236 tempreg, tempreg, breg);
6237 macro_build (&expr1, s, fmt, treg, BFD_RELOC_LO16, tempreg);
6240 offset_expr.X_add_number = expr1.X_add_number;
6241 macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)", tempreg,
6242 BFD_RELOC_MIPS_GOT_PAGE, mips_gp_register);
6244 macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
6245 tempreg, tempreg, breg);
6246 macro_build (&offset_expr, s, fmt, treg,
6247 BFD_RELOC_MIPS_GOT_OFST, tempreg);
6250 else if (mips_pic == EMBEDDED_PIC)
6252 /* If there is no base register, we want
6253 <op> $treg,<sym>($gp) (BFD_RELOC_GPREL16)
6254 If there is a base register, we want
6255 addu $tempreg,$breg,$gp
6256 <op> $treg,<sym>($tempreg) (BFD_RELOC_GPREL16)
6258 assert (offset_expr.X_op == O_symbol);
6261 macro_build (&offset_expr, s, fmt, treg, BFD_RELOC_GPREL16,
6267 macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
6268 tempreg, breg, mips_gp_register);
6269 macro_build (&offset_expr, s, fmt, treg,
6270 BFD_RELOC_GPREL16, tempreg);
6283 load_register (treg, &imm_expr, 0);
6287 load_register (treg, &imm_expr, 1);
6291 if (imm_expr.X_op == O_constant)
6293 load_register (AT, &imm_expr, 0);
6294 macro_build (NULL, "mtc1", "t,G", AT, treg);
6299 assert (offset_expr.X_op == O_symbol
6300 && strcmp (segment_name (S_GET_SEGMENT
6301 (offset_expr.X_add_symbol)),
6303 && offset_expr.X_add_number == 0);
6304 macro_build (&offset_expr, "lwc1", "T,o(b)", treg,
6305 BFD_RELOC_MIPS_LITERAL, mips_gp_register);
6310 /* Check if we have a constant in IMM_EXPR. If the GPRs are 64 bits
6311 wide, IMM_EXPR is the entire value. Otherwise IMM_EXPR is the high
6312 order 32 bits of the value and the low order 32 bits are either
6313 zero or in OFFSET_EXPR. */
6314 if (imm_expr.X_op == O_constant || imm_expr.X_op == O_big)
6316 if (HAVE_64BIT_GPRS)
6317 load_register (treg, &imm_expr, 1);
6322 if (target_big_endian)
6334 load_register (hreg, &imm_expr, 0);
6337 if (offset_expr.X_op == O_absent)
6338 move_register (lreg, 0);
6341 assert (offset_expr.X_op == O_constant);
6342 load_register (lreg, &offset_expr, 0);
6349 /* We know that sym is in the .rdata section. First we get the
6350 upper 16 bits of the address. */
6351 if (mips_pic == NO_PIC)
6353 macro_build_lui (&offset_expr, AT);
6355 else if (mips_pic == SVR4_PIC)
6357 macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)", AT,
6358 BFD_RELOC_MIPS_GOT16, mips_gp_register);
6360 else if (mips_pic == EMBEDDED_PIC)
6362 /* For embedded PIC we pick up the entire address off $gp in
6363 a single instruction. */
6364 macro_build (&offset_expr, ADDRESS_ADDI_INSN, "t,r,j", AT,
6365 mips_gp_register, BFD_RELOC_GPREL16);
6366 offset_expr.X_op = O_constant;
6367 offset_expr.X_add_number = 0;
6372 /* Now we load the register(s). */
6373 if (HAVE_64BIT_GPRS)
6374 macro_build (&offset_expr, "ld", "t,o(b)", treg, BFD_RELOC_LO16, AT);
6377 macro_build (&offset_expr, "lw", "t,o(b)", treg, BFD_RELOC_LO16, AT);
6380 /* FIXME: How in the world do we deal with the possible
6382 offset_expr.X_add_number += 4;
6383 macro_build (&offset_expr, "lw", "t,o(b)",
6384 treg + 1, BFD_RELOC_LO16, AT);
6390 /* Check if we have a constant in IMM_EXPR. If the FPRs are 64 bits
6391 wide, IMM_EXPR is the entire value and the GPRs are known to be 64
6392 bits wide as well. Otherwise IMM_EXPR is the high order 32 bits of
6393 the value and the low order 32 bits are either zero or in
6395 if (imm_expr.X_op == O_constant || imm_expr.X_op == O_big)
6397 load_register (AT, &imm_expr, HAVE_64BIT_FPRS);
6398 if (HAVE_64BIT_FPRS)
6400 assert (HAVE_64BIT_GPRS);
6401 macro_build (NULL, "dmtc1", "t,S", AT, treg);
6405 macro_build (NULL, "mtc1", "t,G", AT, treg + 1);
6406 if (offset_expr.X_op == O_absent)
6407 macro_build (NULL, "mtc1", "t,G", 0, treg);
6410 assert (offset_expr.X_op == O_constant);
6411 load_register (AT, &offset_expr, 0);
6412 macro_build (NULL, "mtc1", "t,G", AT, treg);
6418 assert (offset_expr.X_op == O_symbol
6419 && offset_expr.X_add_number == 0);
6420 s = segment_name (S_GET_SEGMENT (offset_expr.X_add_symbol));
6421 if (strcmp (s, ".lit8") == 0)
6423 if (mips_opts.isa != ISA_MIPS1)
6425 macro_build (&offset_expr, "ldc1", "T,o(b)", treg,
6426 BFD_RELOC_MIPS_LITERAL, mips_gp_register);
6429 breg = mips_gp_register;
6430 r = BFD_RELOC_MIPS_LITERAL;
6435 assert (strcmp (s, RDATA_SECTION_NAME) == 0);
6436 if (mips_pic == SVR4_PIC)
6437 macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)", AT,
6438 BFD_RELOC_MIPS_GOT16, mips_gp_register);
6441 /* FIXME: This won't work for a 64 bit address. */
6442 macro_build_lui (&offset_expr, AT);
6445 if (mips_opts.isa != ISA_MIPS1)
6447 macro_build (&offset_expr, "ldc1", "T,o(b)",
6448 treg, BFD_RELOC_LO16, AT);
6457 if (mips_opts.arch == CPU_R4650)
6459 as_bad (_("opcode not supported on this processor"));
6462 /* Even on a big endian machine $fn comes before $fn+1. We have
6463 to adjust when loading from memory. */
6466 assert (mips_opts.isa == ISA_MIPS1);
6467 macro_build (&offset_expr, "lwc1", "T,o(b)",
6468 target_big_endian ? treg + 1 : treg, r, breg);
6469 /* FIXME: A possible overflow which I don't know how to deal
6471 offset_expr.X_add_number += 4;
6472 macro_build (&offset_expr, "lwc1", "T,o(b)",
6473 target_big_endian ? treg : treg + 1, r, breg);
6481 * The MIPS assembler seems to check for X_add_number not
6482 * being double aligned and generating:
6485 * addiu at,at,%lo(foo+1)
6488 * But, the resulting address is the same after relocation so why
6489 * generate the extra instruction?
6491 if (mips_opts.arch == CPU_R4650)
6493 as_bad (_("opcode not supported on this processor"));
6496 /* Itbl support may require additional care here. */
6498 if (mips_opts.isa != ISA_MIPS1)
6509 if (mips_opts.arch == CPU_R4650)
6511 as_bad (_("opcode not supported on this processor"));
6515 if (mips_opts.isa != ISA_MIPS1)
6523 /* Itbl support may require additional care here. */
6528 if (HAVE_64BIT_GPRS)
6539 if (HAVE_64BIT_GPRS)
6549 /* We do _not_ bother to allow embedded PIC (symbol-local_symbol)
6550 loads for the case of doing a pair of loads to simulate an 'ld'.
6551 This is not currently done by the compiler, and assembly coders
6552 writing embedded-pic code can cope. */
6554 if (offset_expr.X_op != O_symbol
6555 && offset_expr.X_op != O_constant)
6557 as_bad (_("expression too complex"));
6558 offset_expr.X_op = O_constant;
6561 /* Even on a big endian machine $fn comes before $fn+1. We have
6562 to adjust when loading from memory. We set coproc if we must
6563 load $fn+1 first. */
6564 /* Itbl support may require additional care here. */
6565 if (! target_big_endian)
6568 if (mips_pic == NO_PIC
6569 || offset_expr.X_op == O_constant)
6571 /* If this is a reference to a GP relative symbol, we want
6572 <op> $treg,<sym>($gp) (BFD_RELOC_GPREL16)
6573 <op> $treg+1,<sym>+4($gp) (BFD_RELOC_GPREL16)
6574 If we have a base register, we use this
6576 <op> $treg,<sym>($at) (BFD_RELOC_GPREL16)
6577 <op> $treg+1,<sym>+4($at) (BFD_RELOC_GPREL16)
6578 If this is not a GP relative symbol, we want
6579 lui $at,<sym> (BFD_RELOC_HI16_S)
6580 <op> $treg,<sym>($at) (BFD_RELOC_LO16)
6581 <op> $treg+1,<sym>+4($at) (BFD_RELOC_LO16)
6582 If there is a base register, we add it to $at after the
6583 lui instruction. If there is a constant, we always use
6585 if ((valueT) offset_expr.X_add_number > MAX_GPREL_OFFSET
6586 || nopic_need_relax (offset_expr.X_add_symbol, 1))
6590 relax_start (offset_expr.X_add_symbol);
6593 tempreg = mips_gp_register;
6598 macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
6599 AT, breg, mips_gp_register);
6604 /* Itbl support may require additional care here. */
6605 macro_build (&offset_expr, s, fmt, coproc ? treg + 1 : treg,
6606 BFD_RELOC_GPREL16, tempreg);
6607 offset_expr.X_add_number += 4;
6609 /* Set mips_optimize to 2 to avoid inserting an
6611 hold_mips_optimize = mips_optimize;
6613 /* Itbl support may require additional care here. */
6614 macro_build (&offset_expr, s, fmt, coproc ? treg : treg + 1,
6615 BFD_RELOC_GPREL16, tempreg);
6616 mips_optimize = hold_mips_optimize;
6620 /* We just generated two relocs. When tc_gen_reloc
6621 handles this case, it will skip the first reloc and
6622 handle the second. The second reloc already has an
6623 extra addend of 4, which we added above. We must
6624 subtract it out, and then subtract another 4 to make
6625 the first reloc come out right. The second reloc
6626 will come out right because we are going to add 4 to
6627 offset_expr when we build its instruction below.
6629 If we have a symbol, then we don't want to include
6630 the offset, because it will wind up being included
6631 when we generate the reloc. */
6633 if (offset_expr.X_op == O_constant)
6634 offset_expr.X_add_number -= 8;
6637 offset_expr.X_add_number = -4;
6638 offset_expr.X_op = O_constant;
6641 macro_build_lui (&offset_expr, AT);
6643 macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", AT, breg, AT);
6644 /* Itbl support may require additional care here. */
6645 macro_build (&offset_expr, s, fmt, coproc ? treg + 1 : treg,
6646 BFD_RELOC_LO16, AT);
6647 /* FIXME: How do we handle overflow here? */
6648 offset_expr.X_add_number += 4;
6649 /* Itbl support may require additional care here. */
6650 macro_build (&offset_expr, s, fmt, coproc ? treg : treg + 1,
6651 BFD_RELOC_LO16, AT);
6652 if (mips_relax.sequence)
6655 else if (mips_pic == SVR4_PIC && ! mips_big_got)
6657 /* If this is a reference to an external symbol, we want
6658 lw $at,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
6663 lw $at,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
6665 <op> $treg,<sym>($at) (BFD_RELOC_LO16)
6666 <op> $treg+1,<sym>+4($at) (BFD_RELOC_LO16)
6667 If there is a base register we add it to $at before the
6668 lwc1 instructions. If there is a constant we include it
6669 in the lwc1 instructions. */
6671 expr1.X_add_number = offset_expr.X_add_number;
6672 if (expr1.X_add_number < -0x8000
6673 || expr1.X_add_number >= 0x8000 - 4)
6674 as_bad (_("PIC code offset overflow (max 16 signed bits)"));
6675 load_got_offset (AT, &offset_expr);
6676 macro_build (NULL, "nop", "");
6678 macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", AT, breg, AT);
6680 /* Set mips_optimize to 2 to avoid inserting an undesired
6682 hold_mips_optimize = mips_optimize;
6685 /* Itbl support may require additional care here. */
6686 relax_start (offset_expr.X_add_symbol);
6687 macro_build (&expr1, s, fmt, coproc ? treg + 1 : treg,
6688 BFD_RELOC_LO16, AT);
6689 expr1.X_add_number += 4;
6690 macro_build (&expr1, s, fmt, coproc ? treg : treg + 1,
6691 BFD_RELOC_LO16, AT);
6693 macro_build (&offset_expr, s, fmt, coproc ? treg + 1 : treg,
6694 BFD_RELOC_LO16, AT);
6695 offset_expr.X_add_number += 4;
6696 macro_build (&offset_expr, s, fmt, coproc ? treg : treg + 1,
6697 BFD_RELOC_LO16, AT);
6700 mips_optimize = hold_mips_optimize;
6702 else if (mips_pic == SVR4_PIC)
6706 /* If this is a reference to an external symbol, we want
6707 lui $at,<sym> (BFD_RELOC_MIPS_GOT_HI16)
6709 lw $at,<sym>($at) (BFD_RELOC_MIPS_GOT_LO16)
6714 lw $at,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
6716 <op> $treg,<sym>($at) (BFD_RELOC_LO16)
6717 <op> $treg+1,<sym>+4($at) (BFD_RELOC_LO16)
6718 If there is a base register we add it to $at before the
6719 lwc1 instructions. If there is a constant we include it
6720 in the lwc1 instructions. */
6722 expr1.X_add_number = offset_expr.X_add_number;
6723 offset_expr.X_add_number = 0;
6724 if (expr1.X_add_number < -0x8000
6725 || expr1.X_add_number >= 0x8000 - 4)
6726 as_bad (_("PIC code offset overflow (max 16 signed bits)"));
6727 gpdelay = reg_needs_delay (mips_gp_register);
6728 relax_start (offset_expr.X_add_symbol);
6729 macro_build (&offset_expr, "lui", "t,u",
6730 AT, BFD_RELOC_MIPS_GOT_HI16);
6731 macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
6732 AT, AT, mips_gp_register);
6733 macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)",
6734 AT, BFD_RELOC_MIPS_GOT_LO16, AT);
6735 macro_build (NULL, "nop", "");
6737 macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", AT, breg, AT);
6738 /* Itbl support may require additional care here. */
6739 macro_build (&expr1, s, fmt, coproc ? treg + 1 : treg,
6740 BFD_RELOC_LO16, AT);
6741 expr1.X_add_number += 4;
6743 /* Set mips_optimize to 2 to avoid inserting an undesired
6745 hold_mips_optimize = mips_optimize;
6747 /* Itbl support may require additional care here. */
6748 macro_build (&expr1, s, fmt, coproc ? treg : treg + 1,
6749 BFD_RELOC_LO16, AT);
6750 mips_optimize = hold_mips_optimize;
6751 expr1.X_add_number -= 4;
6754 offset_expr.X_add_number = expr1.X_add_number;
6756 macro_build (NULL, "nop", "");
6757 macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)", AT,
6758 BFD_RELOC_MIPS_GOT16, mips_gp_register);
6759 macro_build (NULL, "nop", "");
6761 macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", AT, breg, AT);
6762 /* Itbl support may require additional care here. */
6763 macro_build (&offset_expr, s, fmt, coproc ? treg + 1 : treg,
6764 BFD_RELOC_LO16, AT);
6765 offset_expr.X_add_number += 4;
6767 /* Set mips_optimize to 2 to avoid inserting an undesired
6769 hold_mips_optimize = mips_optimize;
6771 /* Itbl support may require additional care here. */
6772 macro_build (&offset_expr, s, fmt, coproc ? treg : treg + 1,
6773 BFD_RELOC_LO16, AT);
6774 mips_optimize = hold_mips_optimize;
6777 else if (mips_pic == EMBEDDED_PIC)
6779 /* If there is no base register, we use
6780 <op> $treg,<sym>($gp) (BFD_RELOC_GPREL16)
6781 <op> $treg+1,<sym>+4($gp) (BFD_RELOC_GPREL16)
6782 If we have a base register, we use
6784 <op> $treg,<sym>($at) (BFD_RELOC_GPREL16)
6785 <op> $treg+1,<sym>+4($at) (BFD_RELOC_GPREL16)
6789 tempreg = mips_gp_register;
6794 macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
6795 AT, breg, mips_gp_register);
6800 /* Itbl support may require additional care here. */
6801 macro_build (&offset_expr, s, fmt, coproc ? treg + 1 : treg,
6802 BFD_RELOC_GPREL16, tempreg);
6803 offset_expr.X_add_number += 4;
6804 /* Itbl support may require additional care here. */
6805 macro_build (&offset_expr, s, fmt, coproc ? treg : treg + 1,
6806 BFD_RELOC_GPREL16, tempreg);
6822 assert (HAVE_32BIT_ADDRESSES);
6823 macro_build (&offset_expr, s, "t,o(b)", treg, BFD_RELOC_LO16, breg);
6824 offset_expr.X_add_number += 4;
6825 macro_build (&offset_expr, s, "t,o(b)", treg + 1, BFD_RELOC_LO16, breg);
6828 /* New code added to support COPZ instructions.
6829 This code builds table entries out of the macros in mip_opcodes.
6830 R4000 uses interlocks to handle coproc delays.
6831 Other chips (like the R3000) require nops to be inserted for delays.
6833 FIXME: Currently, we require that the user handle delays.
6834 In order to fill delay slots for non-interlocked chips,
6835 we must have a way to specify delays based on the coprocessor.
6836 Eg. 4 cycles if load coproc reg from memory, 1 if in cache, etc.
6837 What are the side-effects of the cop instruction?
6838 What cache support might we have and what are its effects?
6839 Both coprocessor & memory require delays. how long???
6840 What registers are read/set/modified?
6842 If an itbl is provided to interpret cop instructions,
6843 this knowledge can be encoded in the itbl spec. */
6857 /* For now we just do C (same as Cz). The parameter will be
6858 stored in insn_opcode by mips_ip. */
6859 macro_build (NULL, s, "C", ip->insn_opcode);
6863 move_register (dreg, sreg);
6866 #ifdef LOSING_COMPILER
6868 /* Try and see if this is a new itbl instruction.
6869 This code builds table entries out of the macros in mip_opcodes.
6870 FIXME: For now we just assemble the expression and pass it's
6871 value along as a 32-bit immediate.
6872 We may want to have the assembler assemble this value,
6873 so that we gain the assembler's knowledge of delay slots,
6875 Would it be more efficient to use mask (id) here? */
6876 if (itbl_have_entries
6877 && (immed_expr = itbl_assemble (ip->insn_mo->name, "")))
6879 s = ip->insn_mo->name;
6881 coproc = ITBL_DECODE_PNUM (immed_expr);;
6882 macro_build (&immed_expr, s, "C");
6889 as_warn (_("Macro used $at after \".set noat\""));
6893 macro2 (struct mips_cl_insn *ip)
6895 register int treg, sreg, dreg, breg;
6910 bfd_reloc_code_real_type r;
6912 treg = (ip->insn_opcode >> 16) & 0x1f;
6913 dreg = (ip->insn_opcode >> 11) & 0x1f;
6914 sreg = breg = (ip->insn_opcode >> 21) & 0x1f;
6915 mask = ip->insn_mo->mask;
6917 expr1.X_op = O_constant;
6918 expr1.X_op_symbol = NULL;
6919 expr1.X_add_symbol = NULL;
6920 expr1.X_add_number = 1;
6924 #endif /* LOSING_COMPILER */
6929 macro_build (NULL, dbl ? "dmultu" : "multu", "s,t", sreg, treg);
6930 macro_build (NULL, "mflo", "d", dreg);
6936 /* The MIPS assembler some times generates shifts and adds. I'm
6937 not trying to be that fancy. GCC should do this for us
6939 load_register (AT, &imm_expr, dbl);
6940 macro_build (NULL, dbl ? "dmult" : "mult", "s,t", sreg, AT);
6941 macro_build (NULL, "mflo", "d", dreg);
6954 mips_emit_delays (TRUE);
6955 ++mips_opts.noreorder;
6956 mips_any_noreorder = 1;
6958 load_register (AT, &imm_expr, dbl);
6959 macro_build (NULL, dbl ? "dmult" : "mult", "s,t", sreg, imm ? AT : treg);
6960 macro_build (NULL, "mflo", "d", dreg);
6961 macro_build (NULL, dbl ? "dsra32" : "sra", "d,w,<", dreg, dreg, RA);
6962 macro_build (NULL, "mfhi", "d", AT);
6964 macro_build (NULL, "tne", "s,t,q", dreg, AT, 6);
6967 expr1.X_add_number = 8;
6968 macro_build (&expr1, "beq", "s,t,p", dreg, AT);
6969 macro_build (NULL, "nop", "", 0);
6970 macro_build (NULL, "break", "c", 6);
6972 --mips_opts.noreorder;
6973 macro_build (NULL, "mflo", "d", dreg);
6986 mips_emit_delays (TRUE);
6987 ++mips_opts.noreorder;
6988 mips_any_noreorder = 1;
6990 load_register (AT, &imm_expr, dbl);
6991 macro_build (NULL, dbl ? "dmultu" : "multu", "s,t",
6992 sreg, imm ? AT : treg);
6993 macro_build (NULL, "mfhi", "d", AT);
6994 macro_build (NULL, "mflo", "d", dreg);
6996 macro_build (NULL, "tne", "s,t,q", AT, 0, 6);
6999 expr1.X_add_number = 8;
7000 macro_build (&expr1, "beq", "s,t,p", AT, 0);
7001 macro_build (NULL, "nop", "", 0);
7002 macro_build (NULL, "break", "c", 6);
7004 --mips_opts.noreorder;
7008 if (ISA_HAS_DROR (mips_opts.isa) || CPU_HAS_DROR (mips_opts.arch))
7020 macro_build (NULL, "dnegu", "d,w", tempreg, treg);
7021 macro_build (NULL, "drorv", "d,t,s", dreg, sreg, tempreg);
7026 macro_build (NULL, "dsubu", "d,v,t", AT, 0, treg);
7027 macro_build (NULL, "dsrlv", "d,t,s", AT, sreg, AT);
7028 macro_build (NULL, "dsllv", "d,t,s", dreg, sreg, treg);
7029 macro_build (NULL, "or", "d,v,t", dreg, dreg, AT);
7033 if (ISA_HAS_ROR (mips_opts.isa) || CPU_HAS_ROR (mips_opts.arch))
7045 macro_build (NULL, "negu", "d,w", tempreg, treg);
7046 macro_build (NULL, "rorv", "d,t,s", dreg, sreg, tempreg);
7051 macro_build (NULL, "subu", "d,v,t", AT, 0, treg);
7052 macro_build (NULL, "srlv", "d,t,s", AT, sreg, AT);
7053 macro_build (NULL, "sllv", "d,t,s", dreg, sreg, treg);
7054 macro_build (NULL, "or", "d,v,t", dreg, dreg, AT);
7062 if (imm_expr.X_op != O_constant)
7063 as_bad (_("Improper rotate count"));
7064 rot = imm_expr.X_add_number & 0x3f;
7065 if (ISA_HAS_DROR (mips_opts.isa) || CPU_HAS_DROR (mips_opts.arch))
7067 rot = (64 - rot) & 0x3f;
7069 macro_build (NULL, "dror32", "d,w,<", dreg, sreg, rot - 32);
7071 macro_build (NULL, "dror", "d,w,<", dreg, sreg, rot);
7076 macro_build (NULL, "dsrl", "d,w,<", dreg, sreg, 0);
7079 l = (rot < 0x20) ? "dsll" : "dsll32";
7080 r = ((0x40 - rot) < 0x20) ? "dsrl" : "dsrl32";
7082 macro_build (NULL, l, "d,w,<", AT, sreg, rot);
7083 macro_build (NULL, r, "d,w,<", dreg, sreg, (0x20 - rot) & 0x1f);
7084 macro_build (NULL, "or", "d,v,t", dreg, dreg, AT);
7092 if (imm_expr.X_op != O_constant)
7093 as_bad (_("Improper rotate count"));
7094 rot = imm_expr.X_add_number & 0x1f;
7095 if (ISA_HAS_ROR (mips_opts.isa) || CPU_HAS_ROR (mips_opts.arch))
7097 macro_build (NULL, "ror", "d,w,<", dreg, sreg, (32 - rot) & 0x1f);
7102 macro_build (NULL, "srl", "d,w,<", dreg, sreg, 0);
7105 macro_build (NULL, "sll", "d,w,<", AT, sreg, rot);
7106 macro_build (NULL, "srl", "d,w,<", dreg, sreg, (0x20 - rot) & 0x1f);
7107 macro_build (NULL, "or", "d,v,t", dreg, dreg, AT);
7112 if (ISA_HAS_DROR (mips_opts.isa) || CPU_HAS_DROR (mips_opts.arch))
7114 macro_build (NULL, "drorv", "d,t,s", dreg, sreg, treg);
7117 macro_build (NULL, "dsubu", "d,v,t", AT, 0, treg);
7118 macro_build (NULL, "dsllv", "d,t,s", AT, sreg, AT);
7119 macro_build (NULL, "dsrlv", "d,t,s", dreg, sreg, treg);
7120 macro_build (NULL, "or", "d,v,t", dreg, dreg, AT);
7124 if (ISA_HAS_ROR (mips_opts.isa) || CPU_HAS_ROR (mips_opts.arch))
7126 macro_build (NULL, "rorv", "d,t,s", dreg, sreg, treg);
7129 macro_build (NULL, "subu", "d,v,t", AT, 0, treg);
7130 macro_build (NULL, "sllv", "d,t,s", AT, sreg, AT);
7131 macro_build (NULL, "srlv", "d,t,s", dreg, sreg, treg);
7132 macro_build (NULL, "or", "d,v,t", dreg, dreg, AT);
7140 if (imm_expr.X_op != O_constant)
7141 as_bad (_("Improper rotate count"));
7142 rot = imm_expr.X_add_number & 0x3f;
7143 if (ISA_HAS_DROR (mips_opts.isa) || CPU_HAS_DROR (mips_opts.arch))
7146 macro_build (NULL, "dror32", "d,w,<", dreg, sreg, rot - 32);
7148 macro_build (NULL, "dror", "d,w,<", dreg, sreg, rot);
7153 macro_build (NULL, "dsrl", "d,w,<", dreg, sreg, 0);
7156 r = (rot < 0x20) ? "dsrl" : "dsrl32";
7157 l = ((0x40 - rot) < 0x20) ? "dsll" : "dsll32";
7159 macro_build (NULL, r, "d,w,<", AT, sreg, rot);
7160 macro_build (NULL, l, "d,w,<", dreg, sreg, (0x20 - rot) & 0x1f);
7161 macro_build (NULL, "or", "d,v,t", dreg, dreg, AT);
7169 if (imm_expr.X_op != O_constant)
7170 as_bad (_("Improper rotate count"));
7171 rot = imm_expr.X_add_number & 0x1f;
7172 if (ISA_HAS_ROR (mips_opts.isa) || CPU_HAS_ROR (mips_opts.arch))
7174 macro_build (NULL, "ror", "d,w,<", dreg, sreg, rot);
7179 macro_build (NULL, "srl", "d,w,<", dreg, sreg, 0);
7182 macro_build (NULL, "srl", "d,w,<", AT, sreg, rot);
7183 macro_build (NULL, "sll", "d,w,<", dreg, sreg, (0x20 - rot) & 0x1f);
7184 macro_build (NULL, "or", "d,v,t", dreg, dreg, AT);
7189 if (mips_opts.arch == CPU_R4650)
7191 as_bad (_("opcode not supported on this processor"));
7194 assert (mips_opts.isa == ISA_MIPS1);
7195 /* Even on a big endian machine $fn comes before $fn+1. We have
7196 to adjust when storing to memory. */
7197 macro_build (&offset_expr, "swc1", "T,o(b)",
7198 target_big_endian ? treg + 1 : treg, BFD_RELOC_LO16, breg);
7199 offset_expr.X_add_number += 4;
7200 macro_build (&offset_expr, "swc1", "T,o(b)",
7201 target_big_endian ? treg : treg + 1, BFD_RELOC_LO16, breg);
7206 macro_build (&expr1, "sltiu", "t,r,j", dreg, treg, BFD_RELOC_LO16);
7208 macro_build (&expr1, "sltiu", "t,r,j", dreg, sreg, BFD_RELOC_LO16);
7211 macro_build (NULL, "xor", "d,v,t", dreg, sreg, treg);
7212 macro_build (&expr1, "sltiu", "t,r,j", dreg, dreg, BFD_RELOC_LO16);
7217 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
7219 macro_build (&expr1, "sltiu", "t,r,j", dreg, sreg, BFD_RELOC_LO16);
7224 as_warn (_("Instruction %s: result is always false"),
7226 move_register (dreg, 0);
7229 if (imm_expr.X_op == O_constant
7230 && imm_expr.X_add_number >= 0
7231 && imm_expr.X_add_number < 0x10000)
7233 macro_build (&imm_expr, "xori", "t,r,i", dreg, sreg, BFD_RELOC_LO16);
7236 else if (imm_expr.X_op == O_constant
7237 && imm_expr.X_add_number > -0x8000
7238 && imm_expr.X_add_number < 0)
7240 imm_expr.X_add_number = -imm_expr.X_add_number;
7241 macro_build (&imm_expr, HAVE_32BIT_GPRS ? "addiu" : "daddiu",
7242 "t,r,j", dreg, sreg, BFD_RELOC_LO16);
7247 load_register (AT, &imm_expr, HAVE_64BIT_GPRS);
7248 macro_build (NULL, "xor", "d,v,t", dreg, sreg, AT);
7251 macro_build (&expr1, "sltiu", "t,r,j", dreg, dreg, BFD_RELOC_LO16);
7256 case M_SGE: /* sreg >= treg <==> not (sreg < treg) */
7262 macro_build (NULL, s, "d,v,t", dreg, sreg, treg);
7263 macro_build (&expr1, "xori", "t,r,i", dreg, dreg, BFD_RELOC_LO16);
7266 case M_SGE_I: /* sreg >= I <==> not (sreg < I) */
7268 if (imm_expr.X_op == O_constant
7269 && imm_expr.X_add_number >= -0x8000
7270 && imm_expr.X_add_number < 0x8000)
7272 macro_build (&imm_expr, mask == M_SGE_I ? "slti" : "sltiu", "t,r,j",
7273 dreg, sreg, BFD_RELOC_LO16);
7278 load_register (AT, &imm_expr, HAVE_64BIT_GPRS);
7279 macro_build (NULL, mask == M_SGE_I ? "slt" : "sltu", "d,v,t",
7283 macro_build (&expr1, "xori", "t,r,i", dreg, dreg, BFD_RELOC_LO16);
7288 case M_SGT: /* sreg > treg <==> treg < sreg */
7294 macro_build (NULL, s, "d,v,t", dreg, treg, sreg);
7297 case M_SGT_I: /* sreg > I <==> I < sreg */
7303 load_register (AT, &imm_expr, HAVE_64BIT_GPRS);
7304 macro_build (NULL, s, "d,v,t", dreg, AT, sreg);
7307 case M_SLE: /* sreg <= treg <==> treg >= sreg <==> not (treg < sreg) */
7313 macro_build (NULL, s, "d,v,t", dreg, treg, sreg);
7314 macro_build (&expr1, "xori", "t,r,i", dreg, dreg, BFD_RELOC_LO16);
7317 case M_SLE_I: /* sreg <= I <==> I >= sreg <==> not (I < sreg) */
7323 load_register (AT, &imm_expr, HAVE_64BIT_GPRS);
7324 macro_build (NULL, s, "d,v,t", dreg, AT, sreg);
7325 macro_build (&expr1, "xori", "t,r,i", dreg, dreg, BFD_RELOC_LO16);
7329 if (imm_expr.X_op == O_constant
7330 && imm_expr.X_add_number >= -0x8000
7331 && imm_expr.X_add_number < 0x8000)
7333 macro_build (&imm_expr, "slti", "t,r,j", dreg, sreg, BFD_RELOC_LO16);
7336 load_register (AT, &imm_expr, HAVE_64BIT_GPRS);
7337 macro_build (NULL, "slt", "d,v,t", dreg, sreg, AT);
7341 if (imm_expr.X_op == O_constant
7342 && imm_expr.X_add_number >= -0x8000
7343 && imm_expr.X_add_number < 0x8000)
7345 macro_build (&imm_expr, "sltiu", "t,r,j", dreg, sreg,
7349 load_register (AT, &imm_expr, HAVE_64BIT_GPRS);
7350 macro_build (NULL, "sltu", "d,v,t", dreg, sreg, AT);
7355 macro_build (NULL, "sltu", "d,v,t", dreg, 0, treg);
7357 macro_build (NULL, "sltu", "d,v,t", dreg, 0, sreg);
7360 macro_build (NULL, "xor", "d,v,t", dreg, sreg, treg);
7361 macro_build (NULL, "sltu", "d,v,t", dreg, 0, dreg);
7366 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
7368 macro_build (NULL, "sltu", "d,v,t", dreg, 0, sreg);
7373 as_warn (_("Instruction %s: result is always true"),
7375 macro_build (&expr1, HAVE_32BIT_GPRS ? "addiu" : "daddiu", "t,r,j",
7376 dreg, 0, BFD_RELOC_LO16);
7379 if (imm_expr.X_op == O_constant
7380 && imm_expr.X_add_number >= 0
7381 && imm_expr.X_add_number < 0x10000)
7383 macro_build (&imm_expr, "xori", "t,r,i", dreg, sreg, BFD_RELOC_LO16);
7386 else if (imm_expr.X_op == O_constant
7387 && imm_expr.X_add_number > -0x8000
7388 && imm_expr.X_add_number < 0)
7390 imm_expr.X_add_number = -imm_expr.X_add_number;
7391 macro_build (&imm_expr, HAVE_32BIT_GPRS ? "addiu" : "daddiu",
7392 "t,r,j", dreg, sreg, BFD_RELOC_LO16);
7397 load_register (AT, &imm_expr, HAVE_64BIT_GPRS);
7398 macro_build (NULL, "xor", "d,v,t", dreg, sreg, AT);
7401 macro_build (NULL, "sltu", "d,v,t", dreg, 0, dreg);
7409 if (imm_expr.X_op == O_constant
7410 && imm_expr.X_add_number > -0x8000
7411 && imm_expr.X_add_number <= 0x8000)
7413 imm_expr.X_add_number = -imm_expr.X_add_number;
7414 macro_build (&imm_expr, dbl ? "daddi" : "addi", "t,r,j",
7415 dreg, sreg, BFD_RELOC_LO16);
7418 load_register (AT, &imm_expr, dbl);
7419 macro_build (NULL, dbl ? "dsub" : "sub", "d,v,t", dreg, sreg, AT);
7425 if (imm_expr.X_op == O_constant
7426 && imm_expr.X_add_number > -0x8000
7427 && imm_expr.X_add_number <= 0x8000)
7429 imm_expr.X_add_number = -imm_expr.X_add_number;
7430 macro_build (&imm_expr, dbl ? "daddiu" : "addiu", "t,r,j",
7431 dreg, sreg, BFD_RELOC_LO16);
7434 load_register (AT, &imm_expr, dbl);
7435 macro_build (NULL, dbl ? "dsubu" : "subu", "d,v,t", dreg, sreg, AT);
7456 load_register (AT, &imm_expr, HAVE_64BIT_GPRS);
7457 macro_build (NULL, s, "s,t", sreg, AT);
7462 assert (mips_opts.isa == ISA_MIPS1);
7463 sreg = (ip->insn_opcode >> 11) & 0x1f; /* floating reg */
7464 dreg = (ip->insn_opcode >> 06) & 0x1f; /* floating reg */
7467 * Is the double cfc1 instruction a bug in the mips assembler;
7468 * or is there a reason for it?
7470 mips_emit_delays (TRUE);
7471 ++mips_opts.noreorder;
7472 mips_any_noreorder = 1;
7473 macro_build (NULL, "cfc1", "t,G", treg, RA);
7474 macro_build (NULL, "cfc1", "t,G", treg, RA);
7475 macro_build (NULL, "nop", "");
7476 expr1.X_add_number = 3;
7477 macro_build (&expr1, "ori", "t,r,i", AT, treg, BFD_RELOC_LO16);
7478 expr1.X_add_number = 2;
7479 macro_build (&expr1, "xori", "t,r,i", AT, AT, BFD_RELOC_LO16);
7480 macro_build (NULL, "ctc1", "t,G", AT, RA);
7481 macro_build (NULL, "nop", "");
7482 macro_build (NULL, mask == M_TRUNCWD ? "cvt.w.d" : "cvt.w.s", "D,S",
7484 macro_build (NULL, "ctc1", "t,G", treg, RA);
7485 macro_build (NULL, "nop", "");
7486 --mips_opts.noreorder;
7495 if (offset_expr.X_add_number >= 0x7fff)
7496 as_bad (_("operand overflow"));
7497 if (! target_big_endian)
7498 ++offset_expr.X_add_number;
7499 macro_build (&offset_expr, s, "t,o(b)", AT, BFD_RELOC_LO16, breg);
7500 if (! target_big_endian)
7501 --offset_expr.X_add_number;
7503 ++offset_expr.X_add_number;
7504 macro_build (&offset_expr, "lbu", "t,o(b)", treg, BFD_RELOC_LO16, breg);
7505 macro_build (NULL, "sll", "d,w,<", AT, AT, 8);
7506 macro_build (NULL, "or", "d,v,t", treg, treg, AT);
7519 if (offset_expr.X_add_number >= 0x8000 - off)
7520 as_bad (_("operand overflow"));
7525 if (! target_big_endian)
7526 offset_expr.X_add_number += off;
7527 macro_build (&offset_expr, s, "t,o(b)", tempreg, BFD_RELOC_LO16, breg);
7528 if (! target_big_endian)
7529 offset_expr.X_add_number -= off;
7531 offset_expr.X_add_number += off;
7532 macro_build (&offset_expr, s2, "t,o(b)", tempreg, BFD_RELOC_LO16, breg);
7534 /* If necessary, move the result in tempreg the final destination. */
7535 if (treg == tempreg)
7537 /* Protect second load's delay slot. */
7538 if (!gpr_interlocks)
7539 macro_build (NULL, "nop", "");
7540 move_register (treg, tempreg);
7554 load_address (AT, &offset_expr, &used_at);
7556 macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", AT, AT, breg);
7557 if (! target_big_endian)
7558 expr1.X_add_number = off;
7560 expr1.X_add_number = 0;
7561 macro_build (&expr1, s, "t,o(b)", treg, BFD_RELOC_LO16, AT);
7562 if (! target_big_endian)
7563 expr1.X_add_number = 0;
7565 expr1.X_add_number = off;
7566 macro_build (&expr1, s2, "t,o(b)", treg, BFD_RELOC_LO16, AT);
7572 load_address (AT, &offset_expr, &used_at);
7574 macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", AT, AT, breg);
7575 if (target_big_endian)
7576 expr1.X_add_number = 0;
7577 macro_build (&expr1, mask == M_ULH_A ? "lb" : "lbu", "t,o(b)",
7578 treg, BFD_RELOC_LO16, AT);
7579 if (target_big_endian)
7580 expr1.X_add_number = 1;
7582 expr1.X_add_number = 0;
7583 macro_build (&expr1, "lbu", "t,o(b)", AT, BFD_RELOC_LO16, AT);
7584 macro_build (NULL, "sll", "d,w,<", treg, treg, 8);
7585 macro_build (NULL, "or", "d,v,t", treg, treg, AT);
7589 if (offset_expr.X_add_number >= 0x7fff)
7590 as_bad (_("operand overflow"));
7591 if (target_big_endian)
7592 ++offset_expr.X_add_number;
7593 macro_build (&offset_expr, "sb", "t,o(b)", treg, BFD_RELOC_LO16, breg);
7594 macro_build (NULL, "srl", "d,w,<", AT, treg, 8);
7595 if (target_big_endian)
7596 --offset_expr.X_add_number;
7598 ++offset_expr.X_add_number;
7599 macro_build (&offset_expr, "sb", "t,o(b)", AT, BFD_RELOC_LO16, breg);
7612 if (offset_expr.X_add_number >= 0x8000 - off)
7613 as_bad (_("operand overflow"));
7614 if (! target_big_endian)
7615 offset_expr.X_add_number += off;
7616 macro_build (&offset_expr, s, "t,o(b)", treg, BFD_RELOC_LO16, breg);
7617 if (! target_big_endian)
7618 offset_expr.X_add_number -= off;
7620 offset_expr.X_add_number += off;
7621 macro_build (&offset_expr, s2, "t,o(b)", treg, BFD_RELOC_LO16, breg);
7635 load_address (AT, &offset_expr, &used_at);
7637 macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", AT, AT, breg);
7638 if (! target_big_endian)
7639 expr1.X_add_number = off;
7641 expr1.X_add_number = 0;
7642 macro_build (&expr1, s, "t,o(b)", treg, BFD_RELOC_LO16, AT);
7643 if (! target_big_endian)
7644 expr1.X_add_number = 0;
7646 expr1.X_add_number = off;
7647 macro_build (&expr1, s2, "t,o(b)", treg, BFD_RELOC_LO16, AT);
7652 load_address (AT, &offset_expr, &used_at);
7654 macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", AT, AT, breg);
7655 if (! target_big_endian)
7656 expr1.X_add_number = 0;
7657 macro_build (&expr1, "sb", "t,o(b)", treg, BFD_RELOC_LO16, AT);
7658 macro_build (NULL, "srl", "d,w,<", treg, treg, 8);
7659 if (! target_big_endian)
7660 expr1.X_add_number = 1;
7662 expr1.X_add_number = 0;
7663 macro_build (&expr1, "sb", "t,o(b)", treg, BFD_RELOC_LO16, AT);
7664 if (! target_big_endian)
7665 expr1.X_add_number = 0;
7667 expr1.X_add_number = 1;
7668 macro_build (&expr1, "lbu", "t,o(b)", AT, BFD_RELOC_LO16, AT);
7669 macro_build (NULL, "sll", "d,w,<", treg, treg, 8);
7670 macro_build (NULL, "or", "d,v,t", treg, treg, AT);
7674 /* FIXME: Check if this is one of the itbl macros, since they
7675 are added dynamically. */
7676 as_bad (_("Macro %s not implemented yet"), ip->insn_mo->name);
7680 as_warn (_("Macro used $at after \".set noat\""));
7683 /* Implement macros in mips16 mode. */
7686 mips16_macro (struct mips_cl_insn *ip)
7689 int xreg, yreg, zreg, tmp;
7692 const char *s, *s2, *s3;
7694 mask = ip->insn_mo->mask;
7696 xreg = (ip->insn_opcode >> MIPS16OP_SH_RX) & MIPS16OP_MASK_RX;
7697 yreg = (ip->insn_opcode >> MIPS16OP_SH_RY) & MIPS16OP_MASK_RY;
7698 zreg = (ip->insn_opcode >> MIPS16OP_SH_RZ) & MIPS16OP_MASK_RZ;
7700 expr1.X_op = O_constant;
7701 expr1.X_op_symbol = NULL;
7702 expr1.X_add_symbol = NULL;
7703 expr1.X_add_number = 1;
7722 mips_emit_delays (TRUE);
7723 ++mips_opts.noreorder;
7724 mips_any_noreorder = 1;
7725 macro_build (NULL, dbl ? "ddiv" : "div", "0,x,y", xreg, yreg);
7726 expr1.X_add_number = 2;
7727 macro_build (&expr1, "bnez", "x,p", yreg);
7728 macro_build (NULL, "break", "6", 7);
7730 /* FIXME: The normal code checks for of -1 / -0x80000000 here,
7731 since that causes an overflow. We should do that as well,
7732 but I don't see how to do the comparisons without a temporary
7734 --mips_opts.noreorder;
7735 macro_build (NULL, s, "x", zreg);
7754 mips_emit_delays (TRUE);
7755 ++mips_opts.noreorder;
7756 mips_any_noreorder = 1;
7757 macro_build (NULL, s, "0,x,y", xreg, yreg);
7758 expr1.X_add_number = 2;
7759 macro_build (&expr1, "bnez", "x,p", yreg);
7760 macro_build (NULL, "break", "6", 7);
7761 --mips_opts.noreorder;
7762 macro_build (NULL, s2, "x", zreg);
7768 macro_build (NULL, dbl ? "dmultu" : "multu", "x,y", xreg, yreg);
7769 macro_build (NULL, "mflo", "x", zreg);
7777 if (imm_expr.X_op != O_constant)
7778 as_bad (_("Unsupported large constant"));
7779 imm_expr.X_add_number = -imm_expr.X_add_number;
7780 macro_build (&imm_expr, dbl ? "daddiu" : "addiu", "y,x,4", yreg, xreg);
7784 if (imm_expr.X_op != O_constant)
7785 as_bad (_("Unsupported large constant"));
7786 imm_expr.X_add_number = -imm_expr.X_add_number;
7787 macro_build (&imm_expr, "addiu", "x,k", xreg);
7791 if (imm_expr.X_op != O_constant)
7792 as_bad (_("Unsupported large constant"));
7793 imm_expr.X_add_number = -imm_expr.X_add_number;
7794 macro_build (&imm_expr, "daddiu", "y,j", yreg);
7816 goto do_reverse_branch;
7820 goto do_reverse_branch;
7832 goto do_reverse_branch;
7843 macro_build (NULL, s, "x,y", xreg, yreg);
7844 macro_build (&offset_expr, s2, "p");
7871 goto do_addone_branch_i;
7876 goto do_addone_branch_i;
7891 goto do_addone_branch_i;
7898 if (imm_expr.X_op != O_constant)
7899 as_bad (_("Unsupported large constant"));
7900 ++imm_expr.X_add_number;
7903 macro_build (&imm_expr, s, s3, xreg);
7904 macro_build (&offset_expr, s2, "p");
7908 expr1.X_add_number = 0;
7909 macro_build (&expr1, "slti", "x,8", yreg);
7911 move_register (xreg, yreg);
7912 expr1.X_add_number = 2;
7913 macro_build (&expr1, "bteqz", "p");
7914 macro_build (NULL, "neg", "x,w", xreg, xreg);
7918 /* For consistency checking, verify that all bits are specified either
7919 by the match/mask part of the instruction definition, or by the
7922 validate_mips_insn (const struct mips_opcode *opc)
7924 const char *p = opc->args;
7926 unsigned long used_bits = opc->mask;
7928 if ((used_bits & opc->match) != opc->match)
7930 as_bad (_("internal: bad mips opcode (mask error): %s %s"),
7931 opc->name, opc->args);
7934 #define USE_BITS(mask,shift) (used_bits |= ((mask) << (shift)))
7944 case 'A': USE_BITS (OP_MASK_SHAMT, OP_SH_SHAMT); break;
7945 case 'B': USE_BITS (OP_MASK_INSMSB, OP_SH_INSMSB); break;
7946 case 'C': USE_BITS (OP_MASK_EXTMSBD, OP_SH_EXTMSBD); break;
7947 case 'D': USE_BITS (OP_MASK_RD, OP_SH_RD);
7948 USE_BITS (OP_MASK_SEL, OP_SH_SEL); break;
7949 case 'E': USE_BITS (OP_MASK_SHAMT, OP_SH_SHAMT); break;
7950 case 'F': USE_BITS (OP_MASK_INSMSB, OP_SH_INSMSB); break;
7951 case 'G': USE_BITS (OP_MASK_EXTMSBD, OP_SH_EXTMSBD); break;
7952 case 'H': USE_BITS (OP_MASK_EXTMSBD, OP_SH_EXTMSBD); break;
7955 as_bad (_("internal: bad mips opcode (unknown extension operand type `+%c'): %s %s"),
7956 c, opc->name, opc->args);
7960 case '<': USE_BITS (OP_MASK_SHAMT, OP_SH_SHAMT); break;
7961 case '>': USE_BITS (OP_MASK_SHAMT, OP_SH_SHAMT); break;
7963 case 'B': USE_BITS (OP_MASK_CODE20, OP_SH_CODE20); break;
7964 case 'C': USE_BITS (OP_MASK_COPZ, OP_SH_COPZ); break;
7965 case 'D': USE_BITS (OP_MASK_FD, OP_SH_FD); break;
7966 case 'E': USE_BITS (OP_MASK_RT, OP_SH_RT); break;
7968 case 'G': USE_BITS (OP_MASK_RD, OP_SH_RD); break;
7969 case 'H': USE_BITS (OP_MASK_SEL, OP_SH_SEL); break;
7971 case 'J': USE_BITS (OP_MASK_CODE19, OP_SH_CODE19); break;
7972 case 'K': USE_BITS (OP_MASK_RD, OP_SH_RD); break;
7974 case 'M': USE_BITS (OP_MASK_CCC, OP_SH_CCC); break;
7975 case 'N': USE_BITS (OP_MASK_BCC, OP_SH_BCC); break;
7976 case 'O': USE_BITS (OP_MASK_ALN, OP_SH_ALN); break;
7977 case 'Q': USE_BITS (OP_MASK_VSEL, OP_SH_VSEL);
7978 USE_BITS (OP_MASK_FT, OP_SH_FT); break;
7979 case 'R': USE_BITS (OP_MASK_FR, OP_SH_FR); break;
7980 case 'S': USE_BITS (OP_MASK_FS, OP_SH_FS); break;
7981 case 'T': USE_BITS (OP_MASK_FT, OP_SH_FT); break;
7982 case 'V': USE_BITS (OP_MASK_FS, OP_SH_FS); break;
7983 case 'W': USE_BITS (OP_MASK_FT, OP_SH_FT); break;
7984 case 'X': USE_BITS (OP_MASK_FD, OP_SH_FD); break;
7985 case 'Y': USE_BITS (OP_MASK_FS, OP_SH_FS); break;
7986 case 'Z': USE_BITS (OP_MASK_FT, OP_SH_FT); break;
7987 case 'a': USE_BITS (OP_MASK_TARGET, OP_SH_TARGET); break;
7988 case 'b': USE_BITS (OP_MASK_RS, OP_SH_RS); break;
7989 case 'c': USE_BITS (OP_MASK_CODE, OP_SH_CODE); break;
7990 case 'd': USE_BITS (OP_MASK_RD, OP_SH_RD); break;
7992 case 'h': USE_BITS (OP_MASK_PREFX, OP_SH_PREFX); break;
7993 case 'i': USE_BITS (OP_MASK_IMMEDIATE, OP_SH_IMMEDIATE); break;
7994 case 'j': USE_BITS (OP_MASK_DELTA, OP_SH_DELTA); break;
7995 case 'k': USE_BITS (OP_MASK_CACHE, OP_SH_CACHE); break;
7997 case 'o': USE_BITS (OP_MASK_DELTA, OP_SH_DELTA); break;
7998 case 'p': USE_BITS (OP_MASK_DELTA, OP_SH_DELTA); break;
7999 case 'q': USE_BITS (OP_MASK_CODE2, OP_SH_CODE2); break;
8000 case 'r': USE_BITS (OP_MASK_RS, OP_SH_RS); break;
8001 case 's': USE_BITS (OP_MASK_RS, OP_SH_RS); break;
8002 case 't': USE_BITS (OP_MASK_RT, OP_SH_RT); break;
8003 case 'u': USE_BITS (OP_MASK_IMMEDIATE, OP_SH_IMMEDIATE); break;
8004 case 'v': USE_BITS (OP_MASK_RS, OP_SH_RS); break;
8005 case 'w': USE_BITS (OP_MASK_RT, OP_SH_RT); break;
8008 case 'P': USE_BITS (OP_MASK_PERFREG, OP_SH_PERFREG); break;
8009 case 'U': USE_BITS (OP_MASK_RD, OP_SH_RD);
8010 USE_BITS (OP_MASK_RT, OP_SH_RT); break;
8011 case 'e': USE_BITS (OP_MASK_VECBYTE, OP_SH_VECBYTE); break;
8012 case '%': USE_BITS (OP_MASK_VECALIGN, OP_SH_VECALIGN); break;
8016 as_bad (_("internal: bad mips opcode (unknown operand type `%c'): %s %s"),
8017 c, opc->name, opc->args);
8021 if (used_bits != 0xffffffff)
8023 as_bad (_("internal: bad mips opcode (bits 0x%lx undefined): %s %s"),
8024 ~used_bits & 0xffffffff, opc->name, opc->args);
8030 /* This routine assembles an instruction into its binary format. As a
8031 side effect, it sets one of the global variables imm_reloc or
8032 offset_reloc to the type of relocation to do if one of the operands
8033 is an address expression. */
8036 mips_ip (char *str, struct mips_cl_insn *ip)
8041 struct mips_opcode *insn;
8044 unsigned int lastregno = 0;
8045 unsigned int lastpos = 0;
8046 unsigned int limlo, limhi;
8052 /* If the instruction contains a '.', we first try to match an instruction
8053 including the '.'. Then we try again without the '.'. */
8055 for (s = str; *s != '\0' && !ISSPACE (*s); ++s)
8058 /* If we stopped on whitespace, then replace the whitespace with null for
8059 the call to hash_find. Save the character we replaced just in case we
8060 have to re-parse the instruction. */
8067 insn = (struct mips_opcode *) hash_find (op_hash, str);
8069 /* If we didn't find the instruction in the opcode table, try again, but
8070 this time with just the instruction up to, but not including the
8074 /* Restore the character we overwrite above (if any). */
8078 /* Scan up to the first '.' or whitespace. */
8080 *s != '\0' && *s != '.' && !ISSPACE (*s);
8084 /* If we did not find a '.', then we can quit now. */
8087 insn_error = "unrecognized opcode";
8091 /* Lookup the instruction in the hash table. */
8093 if ((insn = (struct mips_opcode *) hash_find (op_hash, str)) == NULL)
8095 insn_error = "unrecognized opcode";
8105 assert (strcmp (insn->name, str) == 0);
8107 if (OPCODE_IS_MEMBER (insn,
8109 | (file_ase_mips16 ? INSN_MIPS16 : 0)
8110 | (mips_opts.ase_mdmx ? INSN_MDMX : 0)
8111 | (mips_opts.ase_mips3d ? INSN_MIPS3D : 0)),
8117 if (insn->pinfo != INSN_MACRO)
8119 if (mips_opts.arch == CPU_R4650 && (insn->pinfo & FP_D) != 0)
8125 if (insn + 1 < &mips_opcodes[NUMOPCODES]
8126 && strcmp (insn->name, insn[1].name) == 0)
8135 static char buf[100];
8137 _("opcode not supported on this processor: %s (%s)"),
8138 mips_cpu_info_from_arch (mips_opts.arch)->name,
8139 mips_cpu_info_from_isa (mips_opts.isa)->name);
8149 ip->insn_opcode = insn->match;
8151 for (args = insn->args;; ++args)
8155 s += strspn (s, " \t");
8159 case '\0': /* end of args */
8172 ip->insn_opcode |= lastregno << OP_SH_RS;
8176 ip->insn_opcode |= lastregno << OP_SH_RT;
8180 ip->insn_opcode |= lastregno << OP_SH_FT;
8184 ip->insn_opcode |= lastregno << OP_SH_FS;
8190 /* Handle optional base register.
8191 Either the base register is omitted or
8192 we must have a left paren. */
8193 /* This is dependent on the next operand specifier
8194 is a base register specification. */
8195 assert (args[1] == 'b' || args[1] == '5'
8196 || args[1] == '-' || args[1] == '4');
8200 case ')': /* these must match exactly */
8207 case '+': /* Opcode extension character. */
8210 case 'A': /* ins/ext position, becomes LSB. */
8219 my_getExpression (&imm_expr, s);
8220 check_absolute_expr (ip, &imm_expr);
8221 if ((unsigned long) imm_expr.X_add_number < limlo
8222 || (unsigned long) imm_expr.X_add_number > limhi)
8224 as_bad (_("Improper position (%lu)"),
8225 (unsigned long) imm_expr.X_add_number);
8226 imm_expr.X_add_number = limlo;
8228 lastpos = imm_expr.X_add_number;
8229 ip->insn_opcode |= (imm_expr.X_add_number
8230 & OP_MASK_SHAMT) << OP_SH_SHAMT;
8231 imm_expr.X_op = O_absent;
8235 case 'B': /* ins size, becomes MSB. */
8244 my_getExpression (&imm_expr, s);
8245 check_absolute_expr (ip, &imm_expr);
8246 /* Check for negative input so that small negative numbers
8247 will not succeed incorrectly. The checks against
8248 (pos+size) transitively check "size" itself,
8249 assuming that "pos" is reasonable. */
8250 if ((long) imm_expr.X_add_number < 0
8251 || ((unsigned long) imm_expr.X_add_number
8253 || ((unsigned long) imm_expr.X_add_number
8256 as_bad (_("Improper insert size (%lu, position %lu)"),
8257 (unsigned long) imm_expr.X_add_number,
8258 (unsigned long) lastpos);
8259 imm_expr.X_add_number = limlo - lastpos;
8261 ip->insn_opcode |= ((lastpos + imm_expr.X_add_number - 1)
8262 & OP_MASK_INSMSB) << OP_SH_INSMSB;
8263 imm_expr.X_op = O_absent;
8267 case 'C': /* ext size, becomes MSBD. */
8280 my_getExpression (&imm_expr, s);
8281 check_absolute_expr (ip, &imm_expr);
8282 /* Check for negative input so that small negative numbers
8283 will not succeed incorrectly. The checks against
8284 (pos+size) transitively check "size" itself,
8285 assuming that "pos" is reasonable. */
8286 if ((long) imm_expr.X_add_number < 0
8287 || ((unsigned long) imm_expr.X_add_number
8289 || ((unsigned long) imm_expr.X_add_number
8292 as_bad (_("Improper extract size (%lu, position %lu)"),
8293 (unsigned long) imm_expr.X_add_number,
8294 (unsigned long) lastpos);
8295 imm_expr.X_add_number = limlo - lastpos;
8297 ip->insn_opcode |= ((imm_expr.X_add_number - 1)
8298 & OP_MASK_EXTMSBD) << OP_SH_EXTMSBD;
8299 imm_expr.X_op = O_absent;
8304 /* +D is for disassembly only; never match. */
8308 /* "+I" is like "I", except that imm2_expr is used. */
8309 my_getExpression (&imm2_expr, s);
8310 if (imm2_expr.X_op != O_big
8311 && imm2_expr.X_op != O_constant)
8312 insn_error = _("absolute expression required");
8313 normalize_constant_expr (&imm2_expr);
8318 as_bad (_("internal: bad mips opcode (unknown extension operand type `+%c'): %s %s"),
8319 *args, insn->name, insn->args);
8320 /* Further processing is fruitless. */
8325 case '<': /* must be at least one digit */
8327 * According to the manual, if the shift amount is greater
8328 * than 31 or less than 0, then the shift amount should be
8329 * mod 32. In reality the mips assembler issues an error.
8330 * We issue a warning and mask out all but the low 5 bits.
8332 my_getExpression (&imm_expr, s);
8333 check_absolute_expr (ip, &imm_expr);
8334 if ((unsigned long) imm_expr.X_add_number > 31)
8336 as_warn (_("Improper shift amount (%lu)"),
8337 (unsigned long) imm_expr.X_add_number);
8338 imm_expr.X_add_number &= OP_MASK_SHAMT;
8340 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_SHAMT;
8341 imm_expr.X_op = O_absent;
8345 case '>': /* shift amount minus 32 */
8346 my_getExpression (&imm_expr, s);
8347 check_absolute_expr (ip, &imm_expr);
8348 if ((unsigned long) imm_expr.X_add_number < 32
8349 || (unsigned long) imm_expr.X_add_number > 63)
8351 ip->insn_opcode |= (imm_expr.X_add_number - 32) << OP_SH_SHAMT;
8352 imm_expr.X_op = O_absent;
8356 case 'k': /* cache code */
8357 case 'h': /* prefx code */
8358 my_getExpression (&imm_expr, s);
8359 check_absolute_expr (ip, &imm_expr);
8360 if ((unsigned long) imm_expr.X_add_number > 31)
8362 as_warn (_("Invalid value for `%s' (%lu)"),
8364 (unsigned long) imm_expr.X_add_number);
8365 imm_expr.X_add_number &= 0x1f;
8368 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_CACHE;
8370 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_PREFX;
8371 imm_expr.X_op = O_absent;
8375 case 'c': /* break code */
8376 my_getExpression (&imm_expr, s);
8377 check_absolute_expr (ip, &imm_expr);
8378 if ((unsigned long) imm_expr.X_add_number > 1023)
8380 as_warn (_("Illegal break code (%lu)"),
8381 (unsigned long) imm_expr.X_add_number);
8382 imm_expr.X_add_number &= OP_MASK_CODE;
8384 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_CODE;
8385 imm_expr.X_op = O_absent;
8389 case 'q': /* lower break code */
8390 my_getExpression (&imm_expr, s);
8391 check_absolute_expr (ip, &imm_expr);
8392 if ((unsigned long) imm_expr.X_add_number > 1023)
8394 as_warn (_("Illegal lower break code (%lu)"),
8395 (unsigned long) imm_expr.X_add_number);
8396 imm_expr.X_add_number &= OP_MASK_CODE2;
8398 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_CODE2;
8399 imm_expr.X_op = O_absent;
8403 case 'B': /* 20-bit syscall/break code. */
8404 my_getExpression (&imm_expr, s);
8405 check_absolute_expr (ip, &imm_expr);
8406 if ((unsigned long) imm_expr.X_add_number > OP_MASK_CODE20)
8407 as_warn (_("Illegal 20-bit code (%lu)"),
8408 (unsigned long) imm_expr.X_add_number);
8409 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_CODE20;
8410 imm_expr.X_op = O_absent;
8414 case 'C': /* Coprocessor code */
8415 my_getExpression (&imm_expr, s);
8416 check_absolute_expr (ip, &imm_expr);
8417 if ((unsigned long) imm_expr.X_add_number >= (1 << 25))
8419 as_warn (_("Coproccesor code > 25 bits (%lu)"),
8420 (unsigned long) imm_expr.X_add_number);
8421 imm_expr.X_add_number &= ((1 << 25) - 1);
8423 ip->insn_opcode |= imm_expr.X_add_number;
8424 imm_expr.X_op = O_absent;
8428 case 'J': /* 19-bit wait code. */
8429 my_getExpression (&imm_expr, s);
8430 check_absolute_expr (ip, &imm_expr);
8431 if ((unsigned long) imm_expr.X_add_number > OP_MASK_CODE19)
8432 as_warn (_("Illegal 19-bit code (%lu)"),
8433 (unsigned long) imm_expr.X_add_number);
8434 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_CODE19;
8435 imm_expr.X_op = O_absent;
8439 case 'P': /* Performance register */
8440 my_getExpression (&imm_expr, s);
8441 check_absolute_expr (ip, &imm_expr);
8442 if (imm_expr.X_add_number != 0 && imm_expr.X_add_number != 1)
8444 as_warn (_("Invalid performance register (%lu)"),
8445 (unsigned long) imm_expr.X_add_number);
8446 imm_expr.X_add_number &= OP_MASK_PERFREG;
8448 ip->insn_opcode |= (imm_expr.X_add_number << OP_SH_PERFREG);
8449 imm_expr.X_op = O_absent;
8453 case 'b': /* base register */
8454 case 'd': /* destination register */
8455 case 's': /* source register */
8456 case 't': /* target register */
8457 case 'r': /* both target and source */
8458 case 'v': /* both dest and source */
8459 case 'w': /* both dest and target */
8460 case 'E': /* coprocessor target register */
8461 case 'G': /* coprocessor destination register */
8462 case 'K': /* 'rdhwr' destination register */
8463 case 'x': /* ignore register name */
8464 case 'z': /* must be zero register */
8465 case 'U': /* destination register (clo/clz). */
8480 while (ISDIGIT (*s));
8482 as_bad (_("Invalid register number (%d)"), regno);
8484 else if (*args == 'E' || *args == 'G' || *args == 'K')
8488 if (s[1] == 'r' && s[2] == 'a')
8493 else if (s[1] == 'f' && s[2] == 'p')
8498 else if (s[1] == 's' && s[2] == 'p')
8503 else if (s[1] == 'g' && s[2] == 'p')
8508 else if (s[1] == 'a' && s[2] == 't')
8513 else if (s[1] == 'k' && s[2] == 't' && s[3] == '0')
8518 else if (s[1] == 'k' && s[2] == 't' && s[3] == '1')
8523 else if (s[1] == 'z' && s[2] == 'e' && s[3] == 'r' && s[4] == 'o')
8528 else if (itbl_have_entries)
8533 p = s + 1; /* advance past '$' */
8534 n = itbl_get_field (&p); /* n is name */
8536 /* See if this is a register defined in an
8538 if (itbl_get_reg_val (n, &r))
8540 /* Get_field advances to the start of
8541 the next field, so we need to back
8542 rack to the end of the last field. */
8546 s = strchr (s, '\0');
8560 as_warn (_("Used $at without \".set noat\""));
8566 if (c == 'r' || c == 'v' || c == 'w')
8573 /* 'z' only matches $0. */
8574 if (c == 'z' && regno != 0)
8577 /* Now that we have assembled one operand, we use the args string
8578 * to figure out where it goes in the instruction. */
8585 ip->insn_opcode |= regno << OP_SH_RS;
8590 ip->insn_opcode |= regno << OP_SH_RD;
8593 ip->insn_opcode |= regno << OP_SH_RD;
8594 ip->insn_opcode |= regno << OP_SH_RT;
8599 ip->insn_opcode |= regno << OP_SH_RT;
8602 /* This case exists because on the r3000 trunc
8603 expands into a macro which requires a gp
8604 register. On the r6000 or r4000 it is
8605 assembled into a single instruction which
8606 ignores the register. Thus the insn version
8607 is MIPS_ISA2 and uses 'x', and the macro
8608 version is MIPS_ISA1 and uses 't'. */
8611 /* This case is for the div instruction, which
8612 acts differently if the destination argument
8613 is $0. This only matches $0, and is checked
8614 outside the switch. */
8617 /* Itbl operand; not yet implemented. FIXME ?? */
8619 /* What about all other operands like 'i', which
8620 can be specified in the opcode table? */
8630 ip->insn_opcode |= lastregno << OP_SH_RS;
8633 ip->insn_opcode |= lastregno << OP_SH_RT;
8638 case 'O': /* MDMX alignment immediate constant. */
8639 my_getExpression (&imm_expr, s);
8640 check_absolute_expr (ip, &imm_expr);
8641 if ((unsigned long) imm_expr.X_add_number > OP_MASK_ALN)
8643 as_warn ("Improper align amount (%ld), using low bits",
8644 (long) imm_expr.X_add_number);
8645 imm_expr.X_add_number &= OP_MASK_ALN;
8647 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_ALN;
8648 imm_expr.X_op = O_absent;
8652 case 'Q': /* MDMX vector, element sel, or const. */
8655 /* MDMX Immediate. */
8656 my_getExpression (&imm_expr, s);
8657 check_absolute_expr (ip, &imm_expr);
8658 if ((unsigned long) imm_expr.X_add_number > OP_MASK_FT)
8660 as_warn (_("Invalid MDMX Immediate (%ld)"),
8661 (long) imm_expr.X_add_number);
8662 imm_expr.X_add_number &= OP_MASK_FT;
8664 imm_expr.X_add_number &= OP_MASK_FT;
8665 if (ip->insn_opcode & (OP_MASK_VSEL << OP_SH_VSEL))
8666 ip->insn_opcode |= MDMX_FMTSEL_IMM_QH << OP_SH_VSEL;
8668 ip->insn_opcode |= MDMX_FMTSEL_IMM_OB << OP_SH_VSEL;
8669 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_FT;
8670 imm_expr.X_op = O_absent;
8674 /* Not MDMX Immediate. Fall through. */
8675 case 'X': /* MDMX destination register. */
8676 case 'Y': /* MDMX source register. */
8677 case 'Z': /* MDMX target register. */
8679 case 'D': /* floating point destination register */
8680 case 'S': /* floating point source register */
8681 case 'T': /* floating point target register */
8682 case 'R': /* floating point source register */
8686 /* Accept $fN for FP and MDMX register numbers, and in
8687 addition accept $vN for MDMX register numbers. */
8688 if ((s[0] == '$' && s[1] == 'f' && ISDIGIT (s[2]))
8689 || (is_mdmx != 0 && s[0] == '$' && s[1] == 'v'
8700 while (ISDIGIT (*s));
8703 as_bad (_("Invalid float register number (%d)"), regno);
8705 if ((regno & 1) != 0
8707 && ! (strcmp (str, "mtc1") == 0
8708 || strcmp (str, "mfc1") == 0
8709 || strcmp (str, "lwc1") == 0
8710 || strcmp (str, "swc1") == 0
8711 || strcmp (str, "l.s") == 0
8712 || strcmp (str, "s.s") == 0))
8713 as_warn (_("Float register should be even, was %d"),
8721 if (c == 'V' || c == 'W')
8732 ip->insn_opcode |= regno << OP_SH_FD;
8737 ip->insn_opcode |= regno << OP_SH_FS;
8740 /* This is like 'Z', but also needs to fix the MDMX
8741 vector/scalar select bits. Note that the
8742 scalar immediate case is handled above. */
8745 int is_qh = (ip->insn_opcode & (1 << OP_SH_VSEL));
8746 int max_el = (is_qh ? 3 : 7);
8748 my_getExpression(&imm_expr, s);
8749 check_absolute_expr (ip, &imm_expr);
8751 if (imm_expr.X_add_number > max_el)
8752 as_bad(_("Bad element selector %ld"),
8753 (long) imm_expr.X_add_number);
8754 imm_expr.X_add_number &= max_el;
8755 ip->insn_opcode |= (imm_expr.X_add_number
8759 as_warn(_("Expecting ']' found '%s'"), s);
8765 if (ip->insn_opcode & (OP_MASK_VSEL << OP_SH_VSEL))
8766 ip->insn_opcode |= (MDMX_FMTSEL_VEC_QH
8769 ip->insn_opcode |= (MDMX_FMTSEL_VEC_OB <<
8776 ip->insn_opcode |= regno << OP_SH_FT;
8779 ip->insn_opcode |= regno << OP_SH_FR;
8789 ip->insn_opcode |= lastregno << OP_SH_FS;
8792 ip->insn_opcode |= lastregno << OP_SH_FT;
8798 my_getExpression (&imm_expr, s);
8799 if (imm_expr.X_op != O_big
8800 && imm_expr.X_op != O_constant)
8801 insn_error = _("absolute expression required");
8802 normalize_constant_expr (&imm_expr);
8807 my_getExpression (&offset_expr, s);
8808 *imm_reloc = BFD_RELOC_32;
8821 unsigned char temp[8];
8823 unsigned int length;
8828 /* These only appear as the last operand in an
8829 instruction, and every instruction that accepts
8830 them in any variant accepts them in all variants.
8831 This means we don't have to worry about backing out
8832 any changes if the instruction does not match.
8834 The difference between them is the size of the
8835 floating point constant and where it goes. For 'F'
8836 and 'L' the constant is 64 bits; for 'f' and 'l' it
8837 is 32 bits. Where the constant is placed is based
8838 on how the MIPS assembler does things:
8841 f -- immediate value
8844 The .lit4 and .lit8 sections are only used if
8845 permitted by the -G argument.
8847 When generating embedded PIC code, we use the
8848 .lit8 section but not the .lit4 section (we can do
8849 .lit4 inline easily; we need to put .lit8
8850 somewhere in the data segment, and using .lit8
8851 permits the linker to eventually combine identical
8854 The code below needs to know whether the target register
8855 is 32 or 64 bits wide. It relies on the fact 'f' and
8856 'F' are used with GPR-based instructions and 'l' and
8857 'L' are used with FPR-based instructions. */
8859 f64 = *args == 'F' || *args == 'L';
8860 using_gprs = *args == 'F' || *args == 'f';
8862 save_in = input_line_pointer;
8863 input_line_pointer = s;
8864 err = md_atof (f64 ? 'd' : 'f', (char *) temp, &len);
8866 s = input_line_pointer;
8867 input_line_pointer = save_in;
8868 if (err != NULL && *err != '\0')
8870 as_bad (_("Bad floating point constant: %s"), err);
8871 memset (temp, '\0', sizeof temp);
8872 length = f64 ? 8 : 4;
8875 assert (length == (unsigned) (f64 ? 8 : 4));
8879 && (! USE_GLOBAL_POINTER_OPT
8880 || mips_pic == EMBEDDED_PIC
8881 || g_switch_value < 4
8882 || (temp[0] == 0 && temp[1] == 0)
8883 || (temp[2] == 0 && temp[3] == 0))))
8885 imm_expr.X_op = O_constant;
8886 if (! target_big_endian)
8887 imm_expr.X_add_number = bfd_getl32 (temp);
8889 imm_expr.X_add_number = bfd_getb32 (temp);
8892 && ! mips_disable_float_construction
8893 /* Constants can only be constructed in GPRs and
8894 copied to FPRs if the GPRs are at least as wide
8895 as the FPRs. Force the constant into memory if
8896 we are using 64-bit FPRs but the GPRs are only
8899 || ! (HAVE_64BIT_FPRS && HAVE_32BIT_GPRS))
8900 && ((temp[0] == 0 && temp[1] == 0)
8901 || (temp[2] == 0 && temp[3] == 0))
8902 && ((temp[4] == 0 && temp[5] == 0)
8903 || (temp[6] == 0 && temp[7] == 0)))
8905 /* The value is simple enough to load with a couple of
8906 instructions. If using 32-bit registers, set
8907 imm_expr to the high order 32 bits and offset_expr to
8908 the low order 32 bits. Otherwise, set imm_expr to
8909 the entire 64 bit constant. */
8910 if (using_gprs ? HAVE_32BIT_GPRS : HAVE_32BIT_FPRS)
8912 imm_expr.X_op = O_constant;
8913 offset_expr.X_op = O_constant;
8914 if (! target_big_endian)
8916 imm_expr.X_add_number = bfd_getl32 (temp + 4);
8917 offset_expr.X_add_number = bfd_getl32 (temp);
8921 imm_expr.X_add_number = bfd_getb32 (temp);
8922 offset_expr.X_add_number = bfd_getb32 (temp + 4);
8924 if (offset_expr.X_add_number == 0)
8925 offset_expr.X_op = O_absent;
8927 else if (sizeof (imm_expr.X_add_number) > 4)
8929 imm_expr.X_op = O_constant;
8930 if (! target_big_endian)
8931 imm_expr.X_add_number = bfd_getl64 (temp);
8933 imm_expr.X_add_number = bfd_getb64 (temp);
8937 imm_expr.X_op = O_big;
8938 imm_expr.X_add_number = 4;
8939 if (! target_big_endian)
8941 generic_bignum[0] = bfd_getl16 (temp);
8942 generic_bignum[1] = bfd_getl16 (temp + 2);
8943 generic_bignum[2] = bfd_getl16 (temp + 4);
8944 generic_bignum[3] = bfd_getl16 (temp + 6);
8948 generic_bignum[0] = bfd_getb16 (temp + 6);
8949 generic_bignum[1] = bfd_getb16 (temp + 4);
8950 generic_bignum[2] = bfd_getb16 (temp + 2);
8951 generic_bignum[3] = bfd_getb16 (temp);
8957 const char *newname;
8960 /* Switch to the right section. */
8962 subseg = now_subseg;
8965 default: /* unused default case avoids warnings. */
8967 newname = RDATA_SECTION_NAME;
8968 if ((USE_GLOBAL_POINTER_OPT && g_switch_value >= 8)
8969 || mips_pic == EMBEDDED_PIC)
8973 if (mips_pic == EMBEDDED_PIC)
8976 newname = RDATA_SECTION_NAME;
8979 assert (!USE_GLOBAL_POINTER_OPT
8980 || g_switch_value >= 4);
8984 new_seg = subseg_new (newname, (subsegT) 0);
8985 if (OUTPUT_FLAVOR == bfd_target_elf_flavour)
8986 bfd_set_section_flags (stdoutput, new_seg,
8991 frag_align (*args == 'l' ? 2 : 3, 0, 0);
8992 if (OUTPUT_FLAVOR == bfd_target_elf_flavour
8993 && strcmp (TARGET_OS, "elf") != 0)
8994 record_alignment (new_seg, 4);
8996 record_alignment (new_seg, *args == 'l' ? 2 : 3);
8998 as_bad (_("Can't use floating point insn in this section"));
9000 /* Set the argument to the current address in the
9002 offset_expr.X_op = O_symbol;
9003 offset_expr.X_add_symbol =
9004 symbol_new ("L0\001", now_seg,
9005 (valueT) frag_now_fix (), frag_now);
9006 offset_expr.X_add_number = 0;
9008 /* Put the floating point number into the section. */
9009 p = frag_more ((int) length);
9010 memcpy (p, temp, length);
9012 /* Switch back to the original section. */
9013 subseg_set (seg, subseg);
9018 case 'i': /* 16 bit unsigned immediate */
9019 case 'j': /* 16 bit signed immediate */
9020 *imm_reloc = BFD_RELOC_LO16;
9021 if (my_getSmallExpression (&imm_expr, imm_reloc, s) == 0)
9024 offsetT minval, maxval;
9026 more = (insn + 1 < &mips_opcodes[NUMOPCODES]
9027 && strcmp (insn->name, insn[1].name) == 0);
9029 /* If the expression was written as an unsigned number,
9030 only treat it as signed if there are no more
9034 && sizeof (imm_expr.X_add_number) <= 4
9035 && imm_expr.X_op == O_constant
9036 && imm_expr.X_add_number < 0
9037 && imm_expr.X_unsigned
9041 /* For compatibility with older assemblers, we accept
9042 0x8000-0xffff as signed 16-bit numbers when only
9043 signed numbers are allowed. */
9045 minval = 0, maxval = 0xffff;
9047 minval = -0x8000, maxval = 0x7fff;
9049 minval = -0x8000, maxval = 0xffff;
9051 if (imm_expr.X_op != O_constant
9052 || imm_expr.X_add_number < minval
9053 || imm_expr.X_add_number > maxval)
9057 if (imm_expr.X_op == O_constant
9058 || imm_expr.X_op == O_big)
9059 as_bad (_("expression out of range"));
9065 case 'o': /* 16 bit offset */
9066 /* Check whether there is only a single bracketed expression
9067 left. If so, it must be the base register and the
9068 constant must be zero. */
9069 if (*s == '(' && strchr (s + 1, '(') == 0)
9071 offset_expr.X_op = O_constant;
9072 offset_expr.X_add_number = 0;
9076 /* If this value won't fit into a 16 bit offset, then go
9077 find a macro that will generate the 32 bit offset
9079 if (my_getSmallExpression (&offset_expr, offset_reloc, s) == 0
9080 && (offset_expr.X_op != O_constant
9081 || offset_expr.X_add_number >= 0x8000
9082 || offset_expr.X_add_number < -0x8000))
9088 case 'p': /* pc relative offset */
9089 *offset_reloc = BFD_RELOC_16_PCREL_S2;
9090 my_getExpression (&offset_expr, s);
9094 case 'u': /* upper 16 bits */
9095 if (my_getSmallExpression (&imm_expr, imm_reloc, s) == 0
9096 && imm_expr.X_op == O_constant
9097 && (imm_expr.X_add_number < 0
9098 || imm_expr.X_add_number >= 0x10000))
9099 as_bad (_("lui expression not in range 0..65535"));
9103 case 'a': /* 26 bit address */
9104 my_getExpression (&offset_expr, s);
9106 *offset_reloc = BFD_RELOC_MIPS_JMP;
9109 case 'N': /* 3 bit branch condition code */
9110 case 'M': /* 3 bit compare condition code */
9111 if (strncmp (s, "$fcc", 4) != 0)
9121 while (ISDIGIT (*s));
9123 as_bad (_("Invalid condition code register $fcc%d"), regno);
9124 if ((strcmp(str + strlen(str) - 3, ".ps") == 0
9125 || strcmp(str + strlen(str) - 5, "any2f") == 0
9126 || strcmp(str + strlen(str) - 5, "any2t") == 0)
9127 && (regno & 1) != 0)
9128 as_warn(_("Condition code register should be even for %s, was %d"),
9130 if ((strcmp(str + strlen(str) - 5, "any4f") == 0
9131 || strcmp(str + strlen(str) - 5, "any4t") == 0)
9132 && (regno & 3) != 0)
9133 as_warn(_("Condition code register should be 0 or 4 for %s, was %d"),
9136 ip->insn_opcode |= regno << OP_SH_BCC;
9138 ip->insn_opcode |= regno << OP_SH_CCC;
9142 if (s[0] == '0' && (s[1] == 'x' || s[1] == 'X'))
9153 while (ISDIGIT (*s));
9156 c = 8; /* Invalid sel value. */
9159 as_bad (_("invalid coprocessor sub-selection value (0-7)"));
9160 ip->insn_opcode |= c;
9164 /* Must be at least one digit. */
9165 my_getExpression (&imm_expr, s);
9166 check_absolute_expr (ip, &imm_expr);
9168 if ((unsigned long) imm_expr.X_add_number
9169 > (unsigned long) OP_MASK_VECBYTE)
9171 as_bad (_("bad byte vector index (%ld)"),
9172 (long) imm_expr.X_add_number);
9173 imm_expr.X_add_number = 0;
9176 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_VECBYTE;
9177 imm_expr.X_op = O_absent;
9182 my_getExpression (&imm_expr, s);
9183 check_absolute_expr (ip, &imm_expr);
9185 if ((unsigned long) imm_expr.X_add_number
9186 > (unsigned long) OP_MASK_VECALIGN)
9188 as_bad (_("bad byte vector index (%ld)"),
9189 (long) imm_expr.X_add_number);
9190 imm_expr.X_add_number = 0;
9193 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_VECALIGN;
9194 imm_expr.X_op = O_absent;
9199 as_bad (_("bad char = '%c'\n"), *args);
9204 /* Args don't match. */
9205 if (insn + 1 < &mips_opcodes[NUMOPCODES] &&
9206 !strcmp (insn->name, insn[1].name))
9210 insn_error = _("illegal operands");
9215 insn_error = _("illegal operands");
9220 /* This routine assembles an instruction into its binary format when
9221 assembling for the mips16. As a side effect, it sets one of the
9222 global variables imm_reloc or offset_reloc to the type of
9223 relocation to do if one of the operands is an address expression.
9224 It also sets mips16_small and mips16_ext if the user explicitly
9225 requested a small or extended instruction. */
9228 mips16_ip (char *str, struct mips_cl_insn *ip)
9232 struct mips_opcode *insn;
9235 unsigned int lastregno = 0;
9240 mips16_small = FALSE;
9243 for (s = str; ISLOWER (*s); ++s)
9255 if (s[1] == 't' && s[2] == ' ')
9258 mips16_small = TRUE;
9262 else if (s[1] == 'e' && s[2] == ' ')
9271 insn_error = _("unknown opcode");
9275 if (mips_opts.noautoextend && ! mips16_ext)
9276 mips16_small = TRUE;
9278 if ((insn = (struct mips_opcode *) hash_find (mips16_op_hash, str)) == NULL)
9280 insn_error = _("unrecognized opcode");
9287 assert (strcmp (insn->name, str) == 0);
9290 ip->insn_opcode = insn->match;
9291 ip->use_extend = FALSE;
9292 imm_expr.X_op = O_absent;
9293 imm_reloc[0] = BFD_RELOC_UNUSED;
9294 imm_reloc[1] = BFD_RELOC_UNUSED;
9295 imm_reloc[2] = BFD_RELOC_UNUSED;
9296 imm2_expr.X_op = O_absent;
9297 offset_expr.X_op = O_absent;
9298 offset_reloc[0] = BFD_RELOC_UNUSED;
9299 offset_reloc[1] = BFD_RELOC_UNUSED;
9300 offset_reloc[2] = BFD_RELOC_UNUSED;
9301 for (args = insn->args; 1; ++args)
9308 /* In this switch statement we call break if we did not find
9309 a match, continue if we did find a match, or return if we
9318 /* Stuff the immediate value in now, if we can. */
9319 if (imm_expr.X_op == O_constant
9320 && *imm_reloc > BFD_RELOC_UNUSED
9321 && insn->pinfo != INSN_MACRO)
9323 mips16_immed (NULL, 0, *imm_reloc - BFD_RELOC_UNUSED,
9324 imm_expr.X_add_number, TRUE, mips16_small,
9325 mips16_ext, &ip->insn_opcode,
9326 &ip->use_extend, &ip->extend);
9327 imm_expr.X_op = O_absent;
9328 *imm_reloc = BFD_RELOC_UNUSED;
9342 ip->insn_opcode |= lastregno << MIPS16OP_SH_RX;
9345 ip->insn_opcode |= lastregno << MIPS16OP_SH_RY;
9361 ip->insn_opcode |= lastregno << MIPS16OP_SH_RX;
9363 ip->insn_opcode |= lastregno << MIPS16OP_SH_RY;
9390 while (ISDIGIT (*s));
9393 as_bad (_("invalid register number (%d)"), regno);
9399 if (s[1] == 'r' && s[2] == 'a')
9404 else if (s[1] == 'f' && s[2] == 'p')
9409 else if (s[1] == 's' && s[2] == 'p')
9414 else if (s[1] == 'g' && s[2] == 'p')
9419 else if (s[1] == 'a' && s[2] == 't')
9424 else if (s[1] == 'k' && s[2] == 't' && s[3] == '0')
9429 else if (s[1] == 'k' && s[2] == 't' && s[3] == '1')
9434 else if (s[1] == 'z' && s[2] == 'e' && s[3] == 'r' && s[4] == 'o')
9447 if (c == 'v' || c == 'w')
9449 regno = mips16_to_32_reg_map[lastregno];
9463 regno = mips32_to_16_reg_map[regno];
9468 regno = ILLEGAL_REG;
9473 regno = ILLEGAL_REG;
9478 regno = ILLEGAL_REG;
9483 if (regno == AT && ! mips_opts.noat)
9484 as_warn (_("used $at without \".set noat\""));
9491 if (regno == ILLEGAL_REG)
9498 ip->insn_opcode |= regno << MIPS16OP_SH_RX;
9502 ip->insn_opcode |= regno << MIPS16OP_SH_RY;
9505 ip->insn_opcode |= regno << MIPS16OP_SH_RZ;
9508 ip->insn_opcode |= regno << MIPS16OP_SH_MOVE32Z;
9514 ip->insn_opcode |= regno << MIPS16OP_SH_REGR32;
9517 regno = ((regno & 7) << 2) | ((regno & 0x18) >> 3);
9518 ip->insn_opcode |= regno << MIPS16OP_SH_REG32R;
9528 if (strncmp (s, "$pc", 3) == 0)
9552 && strncmp (s + 1, "gprel(", sizeof "gprel(" - 1) == 0)
9554 /* This is %gprel(SYMBOL). We need to read SYMBOL,
9555 and generate the appropriate reloc. If the text
9556 inside %gprel is not a symbol name with an
9557 optional offset, then we generate a normal reloc
9558 and will probably fail later. */
9559 my_getExpression (&imm_expr, s + sizeof "%gprel" - 1);
9560 if (imm_expr.X_op == O_symbol)
9563 *imm_reloc = BFD_RELOC_MIPS16_GPREL;
9565 ip->use_extend = TRUE;
9572 /* Just pick up a normal expression. */
9573 my_getExpression (&imm_expr, s);
9576 if (imm_expr.X_op == O_register)
9578 /* What we thought was an expression turned out to
9581 if (s[0] == '(' && args[1] == '(')
9583 /* It looks like the expression was omitted
9584 before a register indirection, which means
9585 that the expression is implicitly zero. We
9586 still set up imm_expr, so that we handle
9587 explicit extensions correctly. */
9588 imm_expr.X_op = O_constant;
9589 imm_expr.X_add_number = 0;
9590 *imm_reloc = (int) BFD_RELOC_UNUSED + c;
9597 /* We need to relax this instruction. */
9598 *imm_reloc = (int) BFD_RELOC_UNUSED + c;
9607 /* We use offset_reloc rather than imm_reloc for the PC
9608 relative operands. This lets macros with both
9609 immediate and address operands work correctly. */
9610 my_getExpression (&offset_expr, s);
9612 if (offset_expr.X_op == O_register)
9615 /* We need to relax this instruction. */
9616 *offset_reloc = (int) BFD_RELOC_UNUSED + c;
9620 case '6': /* break code */
9621 my_getExpression (&imm_expr, s);
9622 check_absolute_expr (ip, &imm_expr);
9623 if ((unsigned long) imm_expr.X_add_number > 63)
9625 as_warn (_("Invalid value for `%s' (%lu)"),
9627 (unsigned long) imm_expr.X_add_number);
9628 imm_expr.X_add_number &= 0x3f;
9630 ip->insn_opcode |= imm_expr.X_add_number << MIPS16OP_SH_IMM6;
9631 imm_expr.X_op = O_absent;
9635 case 'a': /* 26 bit address */
9636 my_getExpression (&offset_expr, s);
9638 *offset_reloc = BFD_RELOC_MIPS16_JMP;
9639 ip->insn_opcode <<= 16;
9642 case 'l': /* register list for entry macro */
9643 case 'L': /* register list for exit macro */
9653 int freg, reg1, reg2;
9655 while (*s == ' ' || *s == ',')
9659 as_bad (_("can't parse register list"));
9671 while (ISDIGIT (*s))
9693 as_bad (_("invalid register list"));
9698 while (ISDIGIT (*s))
9705 if (freg && reg1 == 0 && reg2 == 0 && c == 'L')
9710 else if (freg && reg1 == 0 && reg2 == 1 && c == 'L')
9715 else if (reg1 == 4 && reg2 >= 4 && reg2 <= 7 && c != 'L')
9716 mask |= (reg2 - 3) << 3;
9717 else if (reg1 == 16 && reg2 >= 16 && reg2 <= 17)
9718 mask |= (reg2 - 15) << 1;
9719 else if (reg1 == RA && reg2 == RA)
9723 as_bad (_("invalid register list"));
9727 /* The mask is filled in in the opcode table for the
9728 benefit of the disassembler. We remove it before
9729 applying the actual mask. */
9730 ip->insn_opcode &= ~ ((7 << 3) << MIPS16OP_SH_IMM6);
9731 ip->insn_opcode |= mask << MIPS16OP_SH_IMM6;
9735 case 'e': /* extend code */
9736 my_getExpression (&imm_expr, s);
9737 check_absolute_expr (ip, &imm_expr);
9738 if ((unsigned long) imm_expr.X_add_number > 0x7ff)
9740 as_warn (_("Invalid value for `%s' (%lu)"),
9742 (unsigned long) imm_expr.X_add_number);
9743 imm_expr.X_add_number &= 0x7ff;
9745 ip->insn_opcode |= imm_expr.X_add_number;
9746 imm_expr.X_op = O_absent;
9756 /* Args don't match. */
9757 if (insn + 1 < &mips16_opcodes[bfd_mips16_num_opcodes] &&
9758 strcmp (insn->name, insn[1].name) == 0)
9765 insn_error = _("illegal operands");
9771 /* This structure holds information we know about a mips16 immediate
9774 struct mips16_immed_operand
9776 /* The type code used in the argument string in the opcode table. */
9778 /* The number of bits in the short form of the opcode. */
9780 /* The number of bits in the extended form of the opcode. */
9782 /* The amount by which the short form is shifted when it is used;
9783 for example, the sw instruction has a shift count of 2. */
9785 /* The amount by which the short form is shifted when it is stored
9786 into the instruction code. */
9788 /* Non-zero if the short form is unsigned. */
9790 /* Non-zero if the extended form is unsigned. */
9792 /* Non-zero if the value is PC relative. */
9796 /* The mips16 immediate operand types. */
9798 static const struct mips16_immed_operand mips16_immed_operands[] =
9800 { '<', 3, 5, 0, MIPS16OP_SH_RZ, 1, 1, 0 },
9801 { '>', 3, 5, 0, MIPS16OP_SH_RX, 1, 1, 0 },
9802 { '[', 3, 6, 0, MIPS16OP_SH_RZ, 1, 1, 0 },
9803 { ']', 3, 6, 0, MIPS16OP_SH_RX, 1, 1, 0 },
9804 { '4', 4, 15, 0, MIPS16OP_SH_IMM4, 0, 0, 0 },
9805 { '5', 5, 16, 0, MIPS16OP_SH_IMM5, 1, 0, 0 },
9806 { 'H', 5, 16, 1, MIPS16OP_SH_IMM5, 1, 0, 0 },
9807 { 'W', 5, 16, 2, MIPS16OP_SH_IMM5, 1, 0, 0 },
9808 { 'D', 5, 16, 3, MIPS16OP_SH_IMM5, 1, 0, 0 },
9809 { 'j', 5, 16, 0, MIPS16OP_SH_IMM5, 0, 0, 0 },
9810 { '8', 8, 16, 0, MIPS16OP_SH_IMM8, 1, 0, 0 },
9811 { 'V', 8, 16, 2, MIPS16OP_SH_IMM8, 1, 0, 0 },
9812 { 'C', 8, 16, 3, MIPS16OP_SH_IMM8, 1, 0, 0 },
9813 { 'U', 8, 16, 0, MIPS16OP_SH_IMM8, 1, 1, 0 },
9814 { 'k', 8, 16, 0, MIPS16OP_SH_IMM8, 0, 0, 0 },
9815 { 'K', 8, 16, 3, MIPS16OP_SH_IMM8, 0, 0, 0 },
9816 { 'p', 8, 16, 0, MIPS16OP_SH_IMM8, 0, 0, 1 },
9817 { 'q', 11, 16, 0, MIPS16OP_SH_IMM8, 0, 0, 1 },
9818 { 'A', 8, 16, 2, MIPS16OP_SH_IMM8, 1, 0, 1 },
9819 { 'B', 5, 16, 3, MIPS16OP_SH_IMM5, 1, 0, 1 },
9820 { 'E', 5, 16, 2, MIPS16OP_SH_IMM5, 1, 0, 1 }
9823 #define MIPS16_NUM_IMMED \
9824 (sizeof mips16_immed_operands / sizeof mips16_immed_operands[0])
9826 /* Handle a mips16 instruction with an immediate value. This or's the
9827 small immediate value into *INSN. It sets *USE_EXTEND to indicate
9828 whether an extended value is needed; if one is needed, it sets
9829 *EXTEND to the value. The argument type is TYPE. The value is VAL.
9830 If SMALL is true, an unextended opcode was explicitly requested.
9831 If EXT is true, an extended opcode was explicitly requested. If
9832 WARN is true, warn if EXT does not match reality. */
9835 mips16_immed (char *file, unsigned int line, int type, offsetT val,
9836 bfd_boolean warn, bfd_boolean small, bfd_boolean ext,
9837 unsigned long *insn, bfd_boolean *use_extend,
9838 unsigned short *extend)
9840 register const struct mips16_immed_operand *op;
9841 int mintiny, maxtiny;
9842 bfd_boolean needext;
9844 op = mips16_immed_operands;
9845 while (op->type != type)
9848 assert (op < mips16_immed_operands + MIPS16_NUM_IMMED);
9853 if (type == '<' || type == '>' || type == '[' || type == ']')
9856 maxtiny = 1 << op->nbits;
9861 maxtiny = (1 << op->nbits) - 1;
9866 mintiny = - (1 << (op->nbits - 1));
9867 maxtiny = (1 << (op->nbits - 1)) - 1;
9870 /* Branch offsets have an implicit 0 in the lowest bit. */
9871 if (type == 'p' || type == 'q')
9874 if ((val & ((1 << op->shift) - 1)) != 0
9875 || val < (mintiny << op->shift)
9876 || val > (maxtiny << op->shift))
9881 if (warn && ext && ! needext)
9882 as_warn_where (file, line,
9883 _("extended operand requested but not required"));
9884 if (small && needext)
9885 as_bad_where (file, line, _("invalid unextended operand value"));
9887 if (small || (! ext && ! needext))
9891 *use_extend = FALSE;
9892 insnval = ((val >> op->shift) & ((1 << op->nbits) - 1));
9893 insnval <<= op->op_shift;
9898 long minext, maxext;
9904 maxext = (1 << op->extbits) - 1;
9908 minext = - (1 << (op->extbits - 1));
9909 maxext = (1 << (op->extbits - 1)) - 1;
9911 if (val < minext || val > maxext)
9912 as_bad_where (file, line,
9913 _("operand value out of range for instruction"));
9916 if (op->extbits == 16)
9918 extval = ((val >> 11) & 0x1f) | (val & 0x7e0);
9921 else if (op->extbits == 15)
9923 extval = ((val >> 11) & 0xf) | (val & 0x7f0);
9928 extval = ((val & 0x1f) << 6) | (val & 0x20);
9932 *extend = (unsigned short) extval;
9937 static const struct percent_op_match
9940 bfd_reloc_code_real_type reloc;
9943 {"%lo", BFD_RELOC_LO16},
9945 {"%call_hi", BFD_RELOC_MIPS_CALL_HI16},
9946 {"%call_lo", BFD_RELOC_MIPS_CALL_LO16},
9947 {"%call16", BFD_RELOC_MIPS_CALL16},
9948 {"%got_disp", BFD_RELOC_MIPS_GOT_DISP},
9949 {"%got_page", BFD_RELOC_MIPS_GOT_PAGE},
9950 {"%got_ofst", BFD_RELOC_MIPS_GOT_OFST},
9951 {"%got_hi", BFD_RELOC_MIPS_GOT_HI16},
9952 {"%got_lo", BFD_RELOC_MIPS_GOT_LO16},
9953 {"%got", BFD_RELOC_MIPS_GOT16},
9954 {"%gp_rel", BFD_RELOC_GPREL16},
9955 {"%half", BFD_RELOC_16},
9956 {"%highest", BFD_RELOC_MIPS_HIGHEST},
9957 {"%higher", BFD_RELOC_MIPS_HIGHER},
9958 {"%neg", BFD_RELOC_MIPS_SUB},
9960 {"%hi", BFD_RELOC_HI16_S}
9964 /* Return true if *STR points to a relocation operator. When returning true,
9965 move *STR over the operator and store its relocation code in *RELOC.
9966 Leave both *STR and *RELOC alone when returning false. */
9969 parse_relocation (char **str, bfd_reloc_code_real_type *reloc)
9973 for (i = 0; i < ARRAY_SIZE (percent_op); i++)
9974 if (strncasecmp (*str, percent_op[i].str, strlen (percent_op[i].str)) == 0)
9976 *str += strlen (percent_op[i].str);
9977 *reloc = percent_op[i].reloc;
9979 /* Check whether the output BFD supports this relocation.
9980 If not, issue an error and fall back on something safe. */
9981 if (!bfd_reloc_type_lookup (stdoutput, percent_op[i].reloc))
9983 as_bad ("relocation %s isn't supported by the current ABI",
9985 *reloc = BFD_RELOC_LO16;
9993 /* Parse string STR as a 16-bit relocatable operand. Store the
9994 expression in *EP and the relocations in the array starting
9995 at RELOC. Return the number of relocation operators used.
9997 On exit, EXPR_END points to the first character after the expression.
9998 If no relocation operators are used, RELOC[0] is set to BFD_RELOC_LO16. */
10001 my_getSmallExpression (expressionS *ep, bfd_reloc_code_real_type *reloc,
10004 bfd_reloc_code_real_type reversed_reloc[3];
10005 size_t reloc_index, i;
10006 int crux_depth, str_depth;
10009 /* Search for the start of the main expression, recoding relocations
10010 in REVERSED_RELOC. End the loop with CRUX pointing to the start
10011 of the main expression and with CRUX_DEPTH containing the number
10012 of open brackets at that point. */
10019 crux_depth = str_depth;
10021 /* Skip over whitespace and brackets, keeping count of the number
10023 while (*str == ' ' || *str == '\t' || *str == '(')
10028 && reloc_index < (HAVE_NEWABI ? 3 : 1)
10029 && parse_relocation (&str, &reversed_reloc[reloc_index]));
10031 my_getExpression (ep, crux);
10034 /* Match every open bracket. */
10035 while (crux_depth > 0 && (*str == ')' || *str == ' ' || *str == '\t'))
10039 if (crux_depth > 0)
10040 as_bad ("unclosed '('");
10044 if (reloc_index == 0)
10045 reloc[0] = BFD_RELOC_LO16;
10048 prev_reloc_op_frag = frag_now;
10049 for (i = 0; i < reloc_index; i++)
10050 reloc[i] = reversed_reloc[reloc_index - 1 - i];
10053 return reloc_index;
10057 my_getExpression (expressionS *ep, char *str)
10062 save_in = input_line_pointer;
10063 input_line_pointer = str;
10065 expr_end = input_line_pointer;
10066 input_line_pointer = save_in;
10068 /* If we are in mips16 mode, and this is an expression based on `.',
10069 then we bump the value of the symbol by 1 since that is how other
10070 text symbols are handled. We don't bother to handle complex
10071 expressions, just `.' plus or minus a constant. */
10072 if (mips_opts.mips16
10073 && ep->X_op == O_symbol
10074 && strcmp (S_GET_NAME (ep->X_add_symbol), FAKE_LABEL_NAME) == 0
10075 && S_GET_SEGMENT (ep->X_add_symbol) == now_seg
10076 && symbol_get_frag (ep->X_add_symbol) == frag_now
10077 && symbol_constant_p (ep->X_add_symbol)
10078 && (val = S_GET_VALUE (ep->X_add_symbol)) == frag_now_fix ())
10079 S_SET_VALUE (ep->X_add_symbol, val + 1);
10082 /* Turn a string in input_line_pointer into a floating point constant
10083 of type TYPE, and store the appropriate bytes in *LITP. The number
10084 of LITTLENUMS emitted is stored in *SIZEP. An error message is
10085 returned, or NULL on OK. */
10088 md_atof (int type, char *litP, int *sizeP)
10091 LITTLENUM_TYPE words[4];
10107 return _("bad call to md_atof");
10110 t = atof_ieee (input_line_pointer, type, words);
10112 input_line_pointer = t;
10116 if (! target_big_endian)
10118 for (i = prec - 1; i >= 0; i--)
10120 md_number_to_chars (litP, words[i], 2);
10126 for (i = 0; i < prec; i++)
10128 md_number_to_chars (litP, words[i], 2);
10137 md_number_to_chars (char *buf, valueT val, int n)
10139 if (target_big_endian)
10140 number_to_chars_bigendian (buf, val, n);
10142 number_to_chars_littleendian (buf, val, n);
10146 static int support_64bit_objects(void)
10148 const char **list, **l;
10151 list = bfd_target_list ();
10152 for (l = list; *l != NULL; l++)
10154 /* This is traditional mips */
10155 if (strcmp (*l, "elf64-tradbigmips") == 0
10156 || strcmp (*l, "elf64-tradlittlemips") == 0)
10158 if (strcmp (*l, "elf64-bigmips") == 0
10159 || strcmp (*l, "elf64-littlemips") == 0)
10162 yes = (*l != NULL);
10166 #endif /* OBJ_ELF */
10168 const char *md_shortopts = "O::g::G:";
10170 struct option md_longopts[] =
10172 /* Options which specify architecture. */
10173 #define OPTION_ARCH_BASE (OPTION_MD_BASE)
10174 #define OPTION_MARCH (OPTION_ARCH_BASE + 0)
10175 {"march", required_argument, NULL, OPTION_MARCH},
10176 #define OPTION_MTUNE (OPTION_ARCH_BASE + 1)
10177 {"mtune", required_argument, NULL, OPTION_MTUNE},
10178 #define OPTION_MIPS1 (OPTION_ARCH_BASE + 2)
10179 {"mips0", no_argument, NULL, OPTION_MIPS1},
10180 {"mips1", no_argument, NULL, OPTION_MIPS1},
10181 #define OPTION_MIPS2 (OPTION_ARCH_BASE + 3)
10182 {"mips2", no_argument, NULL, OPTION_MIPS2},
10183 #define OPTION_MIPS3 (OPTION_ARCH_BASE + 4)
10184 {"mips3", no_argument, NULL, OPTION_MIPS3},
10185 #define OPTION_MIPS4 (OPTION_ARCH_BASE + 5)
10186 {"mips4", no_argument, NULL, OPTION_MIPS4},
10187 #define OPTION_MIPS5 (OPTION_ARCH_BASE + 6)
10188 {"mips5", no_argument, NULL, OPTION_MIPS5},
10189 #define OPTION_MIPS32 (OPTION_ARCH_BASE + 7)
10190 {"mips32", no_argument, NULL, OPTION_MIPS32},
10191 #define OPTION_MIPS64 (OPTION_ARCH_BASE + 8)
10192 {"mips64", no_argument, NULL, OPTION_MIPS64},
10193 #define OPTION_MIPS32R2 (OPTION_ARCH_BASE + 9)
10194 {"mips32r2", no_argument, NULL, OPTION_MIPS32R2},
10195 #define OPTION_MIPS64R2 (OPTION_ARCH_BASE + 10)
10196 {"mips64r2", no_argument, NULL, OPTION_MIPS64R2},
10198 /* Options which specify Application Specific Extensions (ASEs). */
10199 #define OPTION_ASE_BASE (OPTION_ARCH_BASE + 11)
10200 #define OPTION_MIPS16 (OPTION_ASE_BASE + 0)
10201 {"mips16", no_argument, NULL, OPTION_MIPS16},
10202 #define OPTION_NO_MIPS16 (OPTION_ASE_BASE + 1)
10203 {"no-mips16", no_argument, NULL, OPTION_NO_MIPS16},
10204 #define OPTION_MIPS3D (OPTION_ASE_BASE + 2)
10205 {"mips3d", no_argument, NULL, OPTION_MIPS3D},
10206 #define OPTION_NO_MIPS3D (OPTION_ASE_BASE + 3)
10207 {"no-mips3d", no_argument, NULL, OPTION_NO_MIPS3D},
10208 #define OPTION_MDMX (OPTION_ASE_BASE + 4)
10209 {"mdmx", no_argument, NULL, OPTION_MDMX},
10210 #define OPTION_NO_MDMX (OPTION_ASE_BASE + 5)
10211 {"no-mdmx", no_argument, NULL, OPTION_NO_MDMX},
10213 /* Old-style architecture options. Don't add more of these. */
10214 #define OPTION_COMPAT_ARCH_BASE (OPTION_ASE_BASE + 6)
10215 #define OPTION_M4650 (OPTION_COMPAT_ARCH_BASE + 0)
10216 {"m4650", no_argument, NULL, OPTION_M4650},
10217 #define OPTION_NO_M4650 (OPTION_COMPAT_ARCH_BASE + 1)
10218 {"no-m4650", no_argument, NULL, OPTION_NO_M4650},
10219 #define OPTION_M4010 (OPTION_COMPAT_ARCH_BASE + 2)
10220 {"m4010", no_argument, NULL, OPTION_M4010},
10221 #define OPTION_NO_M4010 (OPTION_COMPAT_ARCH_BASE + 3)
10222 {"no-m4010", no_argument, NULL, OPTION_NO_M4010},
10223 #define OPTION_M4100 (OPTION_COMPAT_ARCH_BASE + 4)
10224 {"m4100", no_argument, NULL, OPTION_M4100},
10225 #define OPTION_NO_M4100 (OPTION_COMPAT_ARCH_BASE + 5)
10226 {"no-m4100", no_argument, NULL, OPTION_NO_M4100},
10227 #define OPTION_M3900 (OPTION_COMPAT_ARCH_BASE + 6)
10228 {"m3900", no_argument, NULL, OPTION_M3900},
10229 #define OPTION_NO_M3900 (OPTION_COMPAT_ARCH_BASE + 7)
10230 {"no-m3900", no_argument, NULL, OPTION_NO_M3900},
10232 /* Options which enable bug fixes. */
10233 #define OPTION_FIX_BASE (OPTION_COMPAT_ARCH_BASE + 8)
10234 #define OPTION_M7000_HILO_FIX (OPTION_FIX_BASE + 0)
10235 {"mfix7000", no_argument, NULL, OPTION_M7000_HILO_FIX},
10236 #define OPTION_MNO_7000_HILO_FIX (OPTION_FIX_BASE + 1)
10237 {"no-fix-7000", no_argument, NULL, OPTION_MNO_7000_HILO_FIX},
10238 {"mno-fix7000", no_argument, NULL, OPTION_MNO_7000_HILO_FIX},
10239 #define OPTION_FIX_VR4122 (OPTION_FIX_BASE + 2)
10240 #define OPTION_NO_FIX_VR4122 (OPTION_FIX_BASE + 3)
10241 {"mfix-vr4122-bugs", no_argument, NULL, OPTION_FIX_VR4122},
10242 {"no-mfix-vr4122-bugs", no_argument, NULL, OPTION_NO_FIX_VR4122},
10244 /* Miscellaneous options. */
10245 #define OPTION_MISC_BASE (OPTION_FIX_BASE + 4)
10246 #define OPTION_MEMBEDDED_PIC (OPTION_MISC_BASE + 0)
10247 {"membedded-pic", no_argument, NULL, OPTION_MEMBEDDED_PIC},
10248 #define OPTION_TRAP (OPTION_MISC_BASE + 1)
10249 {"trap", no_argument, NULL, OPTION_TRAP},
10250 {"no-break", no_argument, NULL, OPTION_TRAP},
10251 #define OPTION_BREAK (OPTION_MISC_BASE + 2)
10252 {"break", no_argument, NULL, OPTION_BREAK},
10253 {"no-trap", no_argument, NULL, OPTION_BREAK},
10254 #define OPTION_EB (OPTION_MISC_BASE + 3)
10255 {"EB", no_argument, NULL, OPTION_EB},
10256 #define OPTION_EL (OPTION_MISC_BASE + 4)
10257 {"EL", no_argument, NULL, OPTION_EL},
10258 #define OPTION_FP32 (OPTION_MISC_BASE + 5)
10259 {"mfp32", no_argument, NULL, OPTION_FP32},
10260 #define OPTION_GP32 (OPTION_MISC_BASE + 6)
10261 {"mgp32", no_argument, NULL, OPTION_GP32},
10262 #define OPTION_CONSTRUCT_FLOATS (OPTION_MISC_BASE + 7)
10263 {"construct-floats", no_argument, NULL, OPTION_CONSTRUCT_FLOATS},
10264 #define OPTION_NO_CONSTRUCT_FLOATS (OPTION_MISC_BASE + 8)
10265 {"no-construct-floats", no_argument, NULL, OPTION_NO_CONSTRUCT_FLOATS},
10266 #define OPTION_FP64 (OPTION_MISC_BASE + 9)
10267 {"mfp64", no_argument, NULL, OPTION_FP64},
10268 #define OPTION_GP64 (OPTION_MISC_BASE + 10)
10269 {"mgp64", no_argument, NULL, OPTION_GP64},
10270 #define OPTION_RELAX_BRANCH (OPTION_MISC_BASE + 11)
10271 #define OPTION_NO_RELAX_BRANCH (OPTION_MISC_BASE + 12)
10272 {"relax-branch", no_argument, NULL, OPTION_RELAX_BRANCH},
10273 {"no-relax-branch", no_argument, NULL, OPTION_NO_RELAX_BRANCH},
10275 /* ELF-specific options. */
10277 #define OPTION_ELF_BASE (OPTION_MISC_BASE + 13)
10278 #define OPTION_CALL_SHARED (OPTION_ELF_BASE + 0)
10279 {"KPIC", no_argument, NULL, OPTION_CALL_SHARED},
10280 {"call_shared", no_argument, NULL, OPTION_CALL_SHARED},
10281 #define OPTION_NON_SHARED (OPTION_ELF_BASE + 1)
10282 {"non_shared", no_argument, NULL, OPTION_NON_SHARED},
10283 #define OPTION_XGOT (OPTION_ELF_BASE + 2)
10284 {"xgot", no_argument, NULL, OPTION_XGOT},
10285 #define OPTION_MABI (OPTION_ELF_BASE + 3)
10286 {"mabi", required_argument, NULL, OPTION_MABI},
10287 #define OPTION_32 (OPTION_ELF_BASE + 4)
10288 {"32", no_argument, NULL, OPTION_32},
10289 #define OPTION_N32 (OPTION_ELF_BASE + 5)
10290 {"n32", no_argument, NULL, OPTION_N32},
10291 #define OPTION_64 (OPTION_ELF_BASE + 6)
10292 {"64", no_argument, NULL, OPTION_64},
10293 #define OPTION_MDEBUG (OPTION_ELF_BASE + 7)
10294 {"mdebug", no_argument, NULL, OPTION_MDEBUG},
10295 #define OPTION_NO_MDEBUG (OPTION_ELF_BASE + 8)
10296 {"no-mdebug", no_argument, NULL, OPTION_NO_MDEBUG},
10297 #define OPTION_PDR (OPTION_ELF_BASE + 9)
10298 {"mpdr", no_argument, NULL, OPTION_PDR},
10299 #define OPTION_NO_PDR (OPTION_ELF_BASE + 10)
10300 {"mno-pdr", no_argument, NULL, OPTION_NO_PDR},
10301 #endif /* OBJ_ELF */
10303 {NULL, no_argument, NULL, 0}
10305 size_t md_longopts_size = sizeof (md_longopts);
10307 /* Set STRING_PTR (either &mips_arch_string or &mips_tune_string) to
10308 NEW_VALUE. Warn if another value was already specified. Note:
10309 we have to defer parsing the -march and -mtune arguments in order
10310 to handle 'from-abi' correctly, since the ABI might be specified
10311 in a later argument. */
10314 mips_set_option_string (const char **string_ptr, const char *new_value)
10316 if (*string_ptr != 0 && strcasecmp (*string_ptr, new_value) != 0)
10317 as_warn (_("A different %s was already specified, is now %s"),
10318 string_ptr == &mips_arch_string ? "-march" : "-mtune",
10321 *string_ptr = new_value;
10325 md_parse_option (int c, char *arg)
10329 case OPTION_CONSTRUCT_FLOATS:
10330 mips_disable_float_construction = 0;
10333 case OPTION_NO_CONSTRUCT_FLOATS:
10334 mips_disable_float_construction = 1;
10346 target_big_endian = 1;
10350 target_big_endian = 0;
10354 if (arg && arg[1] == '0')
10364 mips_debug = atoi (arg);
10365 /* When the MIPS assembler sees -g or -g2, it does not do
10366 optimizations which limit full symbolic debugging. We take
10367 that to be equivalent to -O0. */
10368 if (mips_debug == 2)
10373 file_mips_isa = ISA_MIPS1;
10377 file_mips_isa = ISA_MIPS2;
10381 file_mips_isa = ISA_MIPS3;
10385 file_mips_isa = ISA_MIPS4;
10389 file_mips_isa = ISA_MIPS5;
10392 case OPTION_MIPS32:
10393 file_mips_isa = ISA_MIPS32;
10396 case OPTION_MIPS32R2:
10397 file_mips_isa = ISA_MIPS32R2;
10400 case OPTION_MIPS64R2:
10401 file_mips_isa = ISA_MIPS64R2;
10404 case OPTION_MIPS64:
10405 file_mips_isa = ISA_MIPS64;
10409 mips_set_option_string (&mips_tune_string, arg);
10413 mips_set_option_string (&mips_arch_string, arg);
10417 mips_set_option_string (&mips_arch_string, "4650");
10418 mips_set_option_string (&mips_tune_string, "4650");
10421 case OPTION_NO_M4650:
10425 mips_set_option_string (&mips_arch_string, "4010");
10426 mips_set_option_string (&mips_tune_string, "4010");
10429 case OPTION_NO_M4010:
10433 mips_set_option_string (&mips_arch_string, "4100");
10434 mips_set_option_string (&mips_tune_string, "4100");
10437 case OPTION_NO_M4100:
10441 mips_set_option_string (&mips_arch_string, "3900");
10442 mips_set_option_string (&mips_tune_string, "3900");
10445 case OPTION_NO_M3900:
10449 mips_opts.ase_mdmx = 1;
10452 case OPTION_NO_MDMX:
10453 mips_opts.ase_mdmx = 0;
10456 case OPTION_MIPS16:
10457 mips_opts.mips16 = 1;
10458 mips_no_prev_insn (FALSE);
10461 case OPTION_NO_MIPS16:
10462 mips_opts.mips16 = 0;
10463 mips_no_prev_insn (FALSE);
10466 case OPTION_MIPS3D:
10467 mips_opts.ase_mips3d = 1;
10470 case OPTION_NO_MIPS3D:
10471 mips_opts.ase_mips3d = 0;
10474 case OPTION_MEMBEDDED_PIC:
10475 mips_pic = EMBEDDED_PIC;
10476 if (USE_GLOBAL_POINTER_OPT && g_switch_seen)
10478 as_bad (_("-G may not be used with embedded PIC code"));
10481 g_switch_value = 0x7fffffff;
10484 case OPTION_FIX_VR4122:
10485 mips_fix_4122_bugs = 1;
10488 case OPTION_NO_FIX_VR4122:
10489 mips_fix_4122_bugs = 0;
10492 case OPTION_RELAX_BRANCH:
10493 mips_relax_branch = 1;
10496 case OPTION_NO_RELAX_BRANCH:
10497 mips_relax_branch = 0;
10501 /* When generating ELF code, we permit -KPIC and -call_shared to
10502 select SVR4_PIC, and -non_shared to select no PIC. This is
10503 intended to be compatible with Irix 5. */
10504 case OPTION_CALL_SHARED:
10505 if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
10507 as_bad (_("-call_shared is supported only for ELF format"));
10510 mips_pic = SVR4_PIC;
10511 mips_abicalls = TRUE;
10512 if (g_switch_seen && g_switch_value != 0)
10514 as_bad (_("-G may not be used with SVR4 PIC code"));
10517 g_switch_value = 0;
10520 case OPTION_NON_SHARED:
10521 if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
10523 as_bad (_("-non_shared is supported only for ELF format"));
10527 mips_abicalls = FALSE;
10530 /* The -xgot option tells the assembler to use 32 offsets when
10531 accessing the got in SVR4_PIC mode. It is for Irix
10536 #endif /* OBJ_ELF */
10539 if (! USE_GLOBAL_POINTER_OPT)
10541 as_bad (_("-G is not supported for this configuration"));
10544 else if (mips_pic == SVR4_PIC || mips_pic == EMBEDDED_PIC)
10546 as_bad (_("-G may not be used with SVR4 or embedded PIC code"));
10550 g_switch_value = atoi (arg);
10555 /* The -32, -n32 and -64 options are shortcuts for -mabi=32, -mabi=n32
10558 if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
10560 as_bad (_("-32 is supported for ELF format only"));
10563 mips_abi = O32_ABI;
10567 if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
10569 as_bad (_("-n32 is supported for ELF format only"));
10572 mips_abi = N32_ABI;
10576 if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
10578 as_bad (_("-64 is supported for ELF format only"));
10581 mips_abi = N64_ABI;
10582 if (! support_64bit_objects())
10583 as_fatal (_("No compiled in support for 64 bit object file format"));
10585 #endif /* OBJ_ELF */
10588 file_mips_gp32 = 1;
10592 file_mips_gp32 = 0;
10596 file_mips_fp32 = 1;
10600 file_mips_fp32 = 0;
10605 if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
10607 as_bad (_("-mabi is supported for ELF format only"));
10610 if (strcmp (arg, "32") == 0)
10611 mips_abi = O32_ABI;
10612 else if (strcmp (arg, "o64") == 0)
10613 mips_abi = O64_ABI;
10614 else if (strcmp (arg, "n32") == 0)
10615 mips_abi = N32_ABI;
10616 else if (strcmp (arg, "64") == 0)
10618 mips_abi = N64_ABI;
10619 if (! support_64bit_objects())
10620 as_fatal (_("No compiled in support for 64 bit object file "
10623 else if (strcmp (arg, "eabi") == 0)
10624 mips_abi = EABI_ABI;
10627 as_fatal (_("invalid abi -mabi=%s"), arg);
10631 #endif /* OBJ_ELF */
10633 case OPTION_M7000_HILO_FIX:
10634 mips_7000_hilo_fix = TRUE;
10637 case OPTION_MNO_7000_HILO_FIX:
10638 mips_7000_hilo_fix = FALSE;
10642 case OPTION_MDEBUG:
10643 mips_flag_mdebug = TRUE;
10646 case OPTION_NO_MDEBUG:
10647 mips_flag_mdebug = FALSE;
10651 mips_flag_pdr = TRUE;
10654 case OPTION_NO_PDR:
10655 mips_flag_pdr = FALSE;
10657 #endif /* OBJ_ELF */
10666 /* Set up globals to generate code for the ISA or processor
10667 described by INFO. */
10670 mips_set_architecture (const struct mips_cpu_info *info)
10674 file_mips_arch = info->cpu;
10675 mips_opts.arch = info->cpu;
10676 mips_opts.isa = info->isa;
10681 /* Likewise for tuning. */
10684 mips_set_tune (const struct mips_cpu_info *info)
10687 mips_tune = info->cpu;
10692 mips_after_parse_args (void)
10694 const struct mips_cpu_info *arch_info = 0;
10695 const struct mips_cpu_info *tune_info = 0;
10697 /* GP relative stuff not working for PE */
10698 if (strncmp (TARGET_OS, "pe", 2) == 0
10699 && g_switch_value != 0)
10702 as_bad (_("-G not supported in this configuration."));
10703 g_switch_value = 0;
10706 if (mips_abi == NO_ABI)
10707 mips_abi = MIPS_DEFAULT_ABI;
10709 /* The following code determines the architecture and register size.
10710 Similar code was added to GCC 3.3 (see override_options() in
10711 config/mips/mips.c). The GAS and GCC code should be kept in sync
10712 as much as possible. */
10714 if (mips_arch_string != 0)
10715 arch_info = mips_parse_cpu ("-march", mips_arch_string);
10717 if (file_mips_isa != ISA_UNKNOWN)
10719 /* Handle -mipsN. At this point, file_mips_isa contains the
10720 ISA level specified by -mipsN, while arch_info->isa contains
10721 the -march selection (if any). */
10722 if (arch_info != 0)
10724 /* -march takes precedence over -mipsN, since it is more descriptive.
10725 There's no harm in specifying both as long as the ISA levels
10727 if (file_mips_isa != arch_info->isa)
10728 as_bad (_("-%s conflicts with the other architecture options, which imply -%s"),
10729 mips_cpu_info_from_isa (file_mips_isa)->name,
10730 mips_cpu_info_from_isa (arch_info->isa)->name);
10733 arch_info = mips_cpu_info_from_isa (file_mips_isa);
10736 if (arch_info == 0)
10737 arch_info = mips_parse_cpu ("default CPU", MIPS_CPU_STRING_DEFAULT);
10739 if (ABI_NEEDS_64BIT_REGS (mips_abi) && !ISA_HAS_64BIT_REGS (arch_info->isa))
10740 as_bad ("-march=%s is not compatible with the selected ABI",
10743 mips_set_architecture (arch_info);
10745 /* Optimize for file_mips_arch, unless -mtune selects a different processor. */
10746 if (mips_tune_string != 0)
10747 tune_info = mips_parse_cpu ("-mtune", mips_tune_string);
10749 if (tune_info == 0)
10750 mips_set_tune (arch_info);
10752 mips_set_tune (tune_info);
10754 if (file_mips_gp32 >= 0)
10756 /* The user specified the size of the integer registers. Make sure
10757 it agrees with the ABI and ISA. */
10758 if (file_mips_gp32 == 0 && !ISA_HAS_64BIT_REGS (mips_opts.isa))
10759 as_bad (_("-mgp64 used with a 32-bit processor"));
10760 else if (file_mips_gp32 == 1 && ABI_NEEDS_64BIT_REGS (mips_abi))
10761 as_bad (_("-mgp32 used with a 64-bit ABI"));
10762 else if (file_mips_gp32 == 0 && ABI_NEEDS_32BIT_REGS (mips_abi))
10763 as_bad (_("-mgp64 used with a 32-bit ABI"));
10767 /* Infer the integer register size from the ABI and processor.
10768 Restrict ourselves to 32-bit registers if that's all the
10769 processor has, or if the ABI cannot handle 64-bit registers. */
10770 file_mips_gp32 = (ABI_NEEDS_32BIT_REGS (mips_abi)
10771 || !ISA_HAS_64BIT_REGS (mips_opts.isa));
10774 /* ??? GAS treats single-float processors as though they had 64-bit
10775 float registers (although it complains when double-precision
10776 instructions are used). As things stand, saying they have 32-bit
10777 registers would lead to spurious "register must be even" messages.
10778 So here we assume float registers are always the same size as
10779 integer ones, unless the user says otherwise. */
10780 if (file_mips_fp32 < 0)
10781 file_mips_fp32 = file_mips_gp32;
10783 /* End of GCC-shared inference code. */
10785 /* This flag is set when we have a 64-bit capable CPU but use only
10786 32-bit wide registers. Note that EABI does not use it. */
10787 if (ISA_HAS_64BIT_REGS (mips_opts.isa)
10788 && ((mips_abi == NO_ABI && file_mips_gp32 == 1)
10789 || mips_abi == O32_ABI))
10790 mips_32bitmode = 1;
10792 if (mips_opts.isa == ISA_MIPS1 && mips_trap)
10793 as_bad (_("trap exception not supported at ISA 1"));
10795 /* If the selected architecture includes support for ASEs, enable
10796 generation of code for them. */
10797 if (mips_opts.mips16 == -1)
10798 mips_opts.mips16 = (CPU_HAS_MIPS16 (file_mips_arch)) ? 1 : 0;
10799 if (mips_opts.ase_mips3d == -1)
10800 mips_opts.ase_mips3d = (CPU_HAS_MIPS3D (file_mips_arch)) ? 1 : 0;
10801 if (mips_opts.ase_mdmx == -1)
10802 mips_opts.ase_mdmx = (CPU_HAS_MDMX (file_mips_arch)) ? 1 : 0;
10804 file_mips_isa = mips_opts.isa;
10805 file_ase_mips16 = mips_opts.mips16;
10806 file_ase_mips3d = mips_opts.ase_mips3d;
10807 file_ase_mdmx = mips_opts.ase_mdmx;
10808 mips_opts.gp32 = file_mips_gp32;
10809 mips_opts.fp32 = file_mips_fp32;
10811 if (mips_flag_mdebug < 0)
10813 #ifdef OBJ_MAYBE_ECOFF
10814 if (OUTPUT_FLAVOR == bfd_target_ecoff_flavour)
10815 mips_flag_mdebug = 1;
10817 #endif /* OBJ_MAYBE_ECOFF */
10818 mips_flag_mdebug = 0;
10823 mips_init_after_args (void)
10825 /* initialize opcodes */
10826 bfd_mips_num_opcodes = bfd_mips_num_builtin_opcodes;
10827 mips_opcodes = (struct mips_opcode *) mips_builtin_opcodes;
10831 md_pcrel_from (fixS *fixP)
10833 valueT addr = fixP->fx_where + fixP->fx_frag->fr_address;
10834 switch (fixP->fx_r_type)
10836 case BFD_RELOC_16_PCREL_S2:
10837 case BFD_RELOC_MIPS_JMP:
10838 /* Return the address of the delay slot. */
10845 /* This is called before the symbol table is processed. In order to
10846 work with gcc when using mips-tfile, we must keep all local labels.
10847 However, in other cases, we want to discard them. If we were
10848 called with -g, but we didn't see any debugging information, it may
10849 mean that gcc is smuggling debugging information through to
10850 mips-tfile, in which case we must generate all local labels. */
10853 mips_frob_file_before_adjust (void)
10855 #ifndef NO_ECOFF_DEBUGGING
10856 if (ECOFF_DEBUGGING
10858 && ! ecoff_debugging_seen)
10859 flag_keep_locals = 1;
10863 /* Sort any unmatched HI16_S relocs so that they immediately precede
10864 the corresponding LO reloc. This is called before md_apply_fix3 and
10865 tc_gen_reloc. Unmatched HI16_S relocs can only be generated by
10866 explicit use of the %hi modifier. */
10869 mips_frob_file (void)
10871 struct mips_hi_fixup *l;
10873 for (l = mips_hi_fixup_list; l != NULL; l = l->next)
10875 segment_info_type *seginfo;
10878 assert (reloc_needs_lo_p (l->fixp->fx_r_type));
10880 /* If a GOT16 relocation turns out to be against a global symbol,
10881 there isn't supposed to be a matching LO. */
10882 if (l->fixp->fx_r_type == BFD_RELOC_MIPS_GOT16
10883 && !pic_need_relax (l->fixp->fx_addsy, l->seg))
10886 /* Check quickly whether the next fixup happens to be a matching %lo. */
10887 if (fixup_has_matching_lo_p (l->fixp))
10890 /* Look through the fixups for this segment for a matching %lo.
10891 When we find one, move the %hi just in front of it. We do
10892 this in two passes. In the first pass, we try to find a
10893 unique %lo. In the second pass, we permit multiple %hi
10894 relocs for a single %lo (this is a GNU extension). */
10895 seginfo = seg_info (l->seg);
10896 for (pass = 0; pass < 2; pass++)
10901 for (f = seginfo->fix_root; f != NULL; f = f->fx_next)
10903 /* Check whether this is a %lo fixup which matches l->fixp. */
10904 if (f->fx_r_type == BFD_RELOC_LO16
10905 && f->fx_addsy == l->fixp->fx_addsy
10906 && f->fx_offset == l->fixp->fx_offset
10909 || !reloc_needs_lo_p (prev->fx_r_type)
10910 || !fixup_has_matching_lo_p (prev)))
10914 /* Move l->fixp before f. */
10915 for (pf = &seginfo->fix_root;
10917 pf = &(*pf)->fx_next)
10918 assert (*pf != NULL);
10920 *pf = l->fixp->fx_next;
10922 l->fixp->fx_next = f;
10924 seginfo->fix_root = l->fixp;
10926 prev->fx_next = l->fixp;
10937 #if 0 /* GCC code motion plus incomplete dead code elimination
10938 can leave a %hi without a %lo. */
10940 as_warn_where (l->fixp->fx_file, l->fixp->fx_line,
10941 _("Unmatched %%hi reloc"));
10947 /* When generating embedded PIC code we need to use a special
10948 relocation to represent the difference of two symbols in the .text
10949 section (switch tables use a difference of this sort). See
10950 include/coff/mips.h for details. This macro checks whether this
10951 fixup requires the special reloc. */
10952 #define SWITCH_TABLE(fixp) \
10953 ((fixp)->fx_r_type == BFD_RELOC_32 \
10954 && OUTPUT_FLAVOR != bfd_target_elf_flavour \
10955 && (fixp)->fx_addsy != NULL \
10956 && (fixp)->fx_subsy != NULL \
10957 && S_GET_SEGMENT ((fixp)->fx_addsy) == text_section \
10958 && S_GET_SEGMENT ((fixp)->fx_subsy) == text_section)
10960 /* When generating embedded PIC code we must keep all PC relative
10961 relocations, in case the linker has to relax a call. We also need
10962 to keep relocations for switch table entries.
10964 We may have combined relocations without symbols in the N32/N64 ABI.
10965 We have to prevent gas from dropping them. */
10968 mips_force_relocation (fixS *fixp)
10970 if (generic_force_reloc (fixp))
10974 && S_GET_SEGMENT (fixp->fx_addsy) == bfd_abs_section_ptr
10975 && (fixp->fx_r_type == BFD_RELOC_MIPS_SUB
10976 || fixp->fx_r_type == BFD_RELOC_HI16_S
10977 || fixp->fx_r_type == BFD_RELOC_LO16))
10980 return (mips_pic == EMBEDDED_PIC
10982 || SWITCH_TABLE (fixp)
10983 || fixp->fx_r_type == BFD_RELOC_PCREL_HI16_S
10984 || fixp->fx_r_type == BFD_RELOC_PCREL_LO16));
10987 /* This hook is called before a fix is simplified. We don't really
10988 decide whether to skip a fix here. Rather, we turn global symbols
10989 used as branch targets into local symbols, such that they undergo
10990 simplification. We can only do this if the symbol is defined and
10991 it is in the same section as the branch. If this doesn't hold, we
10992 emit a better error message than just saying the relocation is not
10993 valid for the selected object format.
10995 FIXP is the fix-up we're going to try to simplify, SEG is the
10996 segment in which the fix up occurs. The return value should be
10997 non-zero to indicate the fix-up is valid for further
10998 simplifications. */
11001 mips_validate_fix (struct fix *fixP, asection *seg)
11003 /* There's a lot of discussion on whether it should be possible to
11004 use R_MIPS_PC16 to represent branch relocations. The outcome
11005 seems to be that it can, but gas/bfd are very broken in creating
11006 RELA relocations for this, so for now we only accept branches to
11007 symbols in the same section. Anything else is of dubious value,
11008 since there's no guarantee that at link time the symbol would be
11009 in range. Even for branches to local symbols this is arguably
11010 wrong, since it we assume the symbol is not going to be
11011 overridden, which should be possible per ELF library semantics,
11012 but then, there isn't a dynamic relocation that could be used to
11013 this effect, and the target would likely be out of range as well.
11015 Unfortunately, it seems that there is too much code out there
11016 that relies on branches to symbols that are global to be resolved
11017 as if they were local, like the IRIX tools do, so we do it as
11018 well, but with a warning so that people are reminded to fix their
11019 code. If we ever get back to using R_MIPS_PC16 for branch
11020 targets, this entire block should go away (and probably the
11021 whole function). */
11023 if (fixP->fx_r_type == BFD_RELOC_16_PCREL_S2
11024 && (((OUTPUT_FLAVOR == bfd_target_ecoff_flavour
11025 || OUTPUT_FLAVOR == bfd_target_elf_flavour)
11026 && mips_pic != EMBEDDED_PIC)
11027 || bfd_reloc_type_lookup (stdoutput, BFD_RELOC_16_PCREL_S2) == NULL)
11030 if (! S_IS_DEFINED (fixP->fx_addsy))
11032 as_bad_where (fixP->fx_file, fixP->fx_line,
11033 _("Cannot branch to undefined symbol."));
11034 /* Avoid any further errors about this fixup. */
11037 else if (S_GET_SEGMENT (fixP->fx_addsy) != seg)
11039 as_bad_where (fixP->fx_file, fixP->fx_line,
11040 _("Cannot branch to symbol in another section."));
11043 else if (S_IS_EXTERNAL (fixP->fx_addsy))
11045 symbolS *sym = fixP->fx_addsy;
11047 if (mips_pic == SVR4_PIC)
11048 as_warn_where (fixP->fx_file, fixP->fx_line,
11049 _("Pretending global symbol used as branch target is local."));
11051 fixP->fx_addsy = symbol_create (S_GET_NAME (sym),
11052 S_GET_SEGMENT (sym),
11054 symbol_get_frag (sym));
11055 copy_symbol_attributes (fixP->fx_addsy, sym);
11056 S_CLEAR_EXTERNAL (fixP->fx_addsy);
11057 assert (symbol_resolved_p (sym));
11058 symbol_mark_resolved (fixP->fx_addsy);
11065 /* Apply a fixup to the object file. */
11068 md_apply_fix3 (fixS *fixP, valueT *valP, segT seg ATTRIBUTE_UNUSED)
11072 static int previous_fx_r_type = 0;
11073 reloc_howto_type *howto;
11075 /* We ignore generic BFD relocations we don't know about. */
11076 howto = bfd_reloc_type_lookup (stdoutput, fixP->fx_r_type);
11080 assert (fixP->fx_size == 4
11081 || fixP->fx_r_type == BFD_RELOC_16
11082 || fixP->fx_r_type == BFD_RELOC_64
11083 || fixP->fx_r_type == BFD_RELOC_CTOR
11084 || fixP->fx_r_type == BFD_RELOC_MIPS_SUB
11085 || fixP->fx_r_type == BFD_RELOC_VTABLE_INHERIT
11086 || fixP->fx_r_type == BFD_RELOC_VTABLE_ENTRY);
11088 buf = (bfd_byte *) (fixP->fx_frag->fr_literal + fixP->fx_where);
11090 /* We are not done if this is a composite relocation to set up gp. */
11091 if (fixP->fx_addsy == NULL && ! fixP->fx_pcrel
11092 && !(fixP->fx_r_type == BFD_RELOC_MIPS_SUB
11093 || (fixP->fx_r_type == BFD_RELOC_64
11094 && (previous_fx_r_type == BFD_RELOC_GPREL32
11095 || previous_fx_r_type == BFD_RELOC_GPREL16))
11096 || (previous_fx_r_type == BFD_RELOC_MIPS_SUB
11097 && (fixP->fx_r_type == BFD_RELOC_HI16_S
11098 || fixP->fx_r_type == BFD_RELOC_LO16))))
11100 previous_fx_r_type = fixP->fx_r_type;
11102 switch (fixP->fx_r_type)
11104 case BFD_RELOC_MIPS_JMP:
11105 case BFD_RELOC_MIPS_SHIFT5:
11106 case BFD_RELOC_MIPS_SHIFT6:
11107 case BFD_RELOC_MIPS_GOT_DISP:
11108 case BFD_RELOC_MIPS_GOT_PAGE:
11109 case BFD_RELOC_MIPS_GOT_OFST:
11110 case BFD_RELOC_MIPS_SUB:
11111 case BFD_RELOC_MIPS_INSERT_A:
11112 case BFD_RELOC_MIPS_INSERT_B:
11113 case BFD_RELOC_MIPS_DELETE:
11114 case BFD_RELOC_MIPS_HIGHEST:
11115 case BFD_RELOC_MIPS_HIGHER:
11116 case BFD_RELOC_MIPS_SCN_DISP:
11117 case BFD_RELOC_MIPS_REL16:
11118 case BFD_RELOC_MIPS_RELGOT:
11119 case BFD_RELOC_MIPS_JALR:
11120 case BFD_RELOC_HI16:
11121 case BFD_RELOC_HI16_S:
11122 case BFD_RELOC_GPREL16:
11123 case BFD_RELOC_MIPS_LITERAL:
11124 case BFD_RELOC_MIPS_CALL16:
11125 case BFD_RELOC_MIPS_GOT16:
11126 case BFD_RELOC_GPREL32:
11127 case BFD_RELOC_MIPS_GOT_HI16:
11128 case BFD_RELOC_MIPS_GOT_LO16:
11129 case BFD_RELOC_MIPS_CALL_HI16:
11130 case BFD_RELOC_MIPS_CALL_LO16:
11131 case BFD_RELOC_MIPS16_GPREL:
11132 if (fixP->fx_pcrel)
11133 as_bad_where (fixP->fx_file, fixP->fx_line,
11134 _("Invalid PC relative reloc"));
11135 /* Nothing needed to do. The value comes from the reloc entry */
11138 case BFD_RELOC_MIPS16_JMP:
11139 /* We currently always generate a reloc against a symbol, which
11140 means that we don't want an addend even if the symbol is
11145 case BFD_RELOC_PCREL_HI16_S:
11146 /* The addend for this is tricky if it is internal, so we just
11147 do everything here rather than in bfd_install_relocation. */
11148 if (OUTPUT_FLAVOR == bfd_target_elf_flavour && !fixP->fx_done)
11151 && (symbol_get_bfdsym (fixP->fx_addsy)->flags & BSF_SECTION_SYM) == 0)
11153 /* For an external symbol adjust by the address to make it
11154 pcrel_offset. We use the address of the RELLO reloc
11155 which follows this one. */
11156 *valP += (fixP->fx_next->fx_frag->fr_address
11157 + fixP->fx_next->fx_where);
11159 *valP = ((*valP + 0x8000) >> 16) & 0xffff;
11160 if (target_big_endian)
11162 md_number_to_chars (buf, *valP, 2);
11165 case BFD_RELOC_PCREL_LO16:
11166 /* The addend for this is tricky if it is internal, so we just
11167 do everything here rather than in bfd_install_relocation. */
11168 if (OUTPUT_FLAVOR == bfd_target_elf_flavour && !fixP->fx_done)
11171 && (symbol_get_bfdsym (fixP->fx_addsy)->flags & BSF_SECTION_SYM) == 0)
11172 *valP += fixP->fx_frag->fr_address + fixP->fx_where;
11173 if (target_big_endian)
11175 md_number_to_chars (buf, *valP, 2);
11179 /* This is handled like BFD_RELOC_32, but we output a sign
11180 extended value if we are only 32 bits. */
11182 || (mips_pic == EMBEDDED_PIC && SWITCH_TABLE (fixP)))
11184 if (8 <= sizeof (valueT))
11185 md_number_to_chars (buf, *valP, 8);
11190 if ((*valP & 0x80000000) != 0)
11194 md_number_to_chars ((char *)(buf + target_big_endian ? 4 : 0),
11196 md_number_to_chars ((char *)(buf + target_big_endian ? 0 : 4),
11202 case BFD_RELOC_RVA:
11204 /* If we are deleting this reloc entry, we must fill in the
11205 value now. This can happen if we have a .word which is not
11206 resolved when it appears but is later defined. We also need
11207 to fill in the value if this is an embedded PIC switch table
11210 || (mips_pic == EMBEDDED_PIC && SWITCH_TABLE (fixP)))
11211 md_number_to_chars (buf, *valP, 4);
11215 /* If we are deleting this reloc entry, we must fill in the
11217 assert (fixP->fx_size == 2);
11219 md_number_to_chars (buf, *valP, 2);
11222 case BFD_RELOC_LO16:
11223 /* When handling an embedded PIC switch statement, we can wind
11224 up deleting a LO16 reloc. See the 'o' case in mips_ip. */
11227 if (*valP + 0x8000 > 0xffff)
11228 as_bad_where (fixP->fx_file, fixP->fx_line,
11229 _("relocation overflow"));
11230 if (target_big_endian)
11232 md_number_to_chars (buf, *valP, 2);
11236 case BFD_RELOC_16_PCREL_S2:
11237 if ((*valP & 0x3) != 0)
11238 as_bad_where (fixP->fx_file, fixP->fx_line,
11239 _("Branch to odd address (%lx)"), (long) *valP);
11242 * We need to save the bits in the instruction since fixup_segment()
11243 * might be deleting the relocation entry (i.e., a branch within
11244 * the current segment).
11246 if (! fixP->fx_done)
11249 /* update old instruction data */
11250 if (target_big_endian)
11251 insn = (buf[0] << 24) | (buf[1] << 16) | (buf[2] << 8) | buf[3];
11253 insn = (buf[3] << 24) | (buf[2] << 16) | (buf[1] << 8) | buf[0];
11255 if (*valP + 0x20000 <= 0x3ffff)
11257 insn |= (*valP >> 2) & 0xffff;
11258 md_number_to_chars (buf, insn, 4);
11260 else if (mips_pic == NO_PIC
11262 && fixP->fx_frag->fr_address >= text_section->vma
11263 && (fixP->fx_frag->fr_address
11264 < text_section->vma + text_section->_raw_size)
11265 && ((insn & 0xffff0000) == 0x10000000 /* beq $0,$0 */
11266 || (insn & 0xffff0000) == 0x04010000 /* bgez $0 */
11267 || (insn & 0xffff0000) == 0x04110000)) /* bgezal $0 */
11269 /* The branch offset is too large. If this is an
11270 unconditional branch, and we are not generating PIC code,
11271 we can convert it to an absolute jump instruction. */
11272 if ((insn & 0xffff0000) == 0x04110000) /* bgezal $0 */
11273 insn = 0x0c000000; /* jal */
11275 insn = 0x08000000; /* j */
11276 fixP->fx_r_type = BFD_RELOC_MIPS_JMP;
11278 fixP->fx_addsy = section_symbol (text_section);
11279 *valP += md_pcrel_from (fixP);
11280 md_number_to_chars (buf, insn, 4);
11284 /* If we got here, we have branch-relaxation disabled,
11285 and there's nothing we can do to fix this instruction
11286 without turning it into a longer sequence. */
11287 as_bad_where (fixP->fx_file, fixP->fx_line,
11288 _("Branch out of range"));
11292 case BFD_RELOC_VTABLE_INHERIT:
11295 && !S_IS_DEFINED (fixP->fx_addsy)
11296 && !S_IS_WEAK (fixP->fx_addsy))
11297 S_SET_WEAK (fixP->fx_addsy);
11300 case BFD_RELOC_VTABLE_ENTRY:
11308 /* Remember value for tc_gen_reloc. */
11309 fixP->fx_addnumber = *valP;
11314 printInsn (unsigned long oc)
11316 const struct mips_opcode *p;
11317 int treg, sreg, dreg, shamt;
11322 for (i = 0; i < NUMOPCODES; ++i)
11324 p = &mips_opcodes[i];
11325 if (((oc & p->mask) == p->match) && (p->pinfo != INSN_MACRO))
11327 printf ("%08lx %s\t", oc, p->name);
11328 treg = (oc >> 16) & 0x1f;
11329 sreg = (oc >> 21) & 0x1f;
11330 dreg = (oc >> 11) & 0x1f;
11331 shamt = (oc >> 6) & 0x1f;
11333 for (args = p->args;; ++args)
11344 printf ("%c", *args);
11348 assert (treg == sreg);
11349 printf ("$%d,$%d", treg, sreg);
11354 printf ("$%d", dreg);
11359 printf ("$%d", treg);
11363 printf ("0x%x", treg);
11368 printf ("$%d", sreg);
11372 printf ("0x%08lx", oc & 0x1ffffff);
11379 printf ("%d", imm);
11384 printf ("$%d", shamt);
11395 printf (_("%08lx UNDEFINED\n"), oc);
11406 name = input_line_pointer;
11407 c = get_symbol_end ();
11408 p = (symbolS *) symbol_find_or_make (name);
11409 *input_line_pointer = c;
11413 /* Align the current frag to a given power of two. The MIPS assembler
11414 also automatically adjusts any preceding label. */
11417 mips_align (int to, int fill, symbolS *label)
11419 mips_emit_delays (FALSE);
11420 frag_align (to, fill, 0);
11421 record_alignment (now_seg, to);
11424 assert (S_GET_SEGMENT (label) == now_seg);
11425 symbol_set_frag (label, frag_now);
11426 S_SET_VALUE (label, (valueT) frag_now_fix ());
11430 /* Align to a given power of two. .align 0 turns off the automatic
11431 alignment used by the data creating pseudo-ops. */
11434 s_align (int x ATTRIBUTE_UNUSED)
11437 register long temp_fill;
11438 long max_alignment = 15;
11442 o Note that the assembler pulls down any immediately preceding label
11443 to the aligned address.
11444 o It's not documented but auto alignment is reinstated by
11445 a .align pseudo instruction.
11446 o Note also that after auto alignment is turned off the mips assembler
11447 issues an error on attempt to assemble an improperly aligned data item.
11452 temp = get_absolute_expression ();
11453 if (temp > max_alignment)
11454 as_bad (_("Alignment too large: %d. assumed."), temp = max_alignment);
11457 as_warn (_("Alignment negative: 0 assumed."));
11460 if (*input_line_pointer == ',')
11462 ++input_line_pointer;
11463 temp_fill = get_absolute_expression ();
11470 mips_align (temp, (int) temp_fill,
11471 insn_labels != NULL ? insn_labels->label : NULL);
11478 demand_empty_rest_of_line ();
11482 mips_flush_pending_output (void)
11484 mips_emit_delays (FALSE);
11485 mips_clear_insn_labels ();
11489 s_change_sec (int sec)
11493 /* When generating embedded PIC code, we only use the .text, .lit8,
11494 .sdata and .sbss sections. We change the .data and .rdata
11495 pseudo-ops to use .sdata. */
11496 if (mips_pic == EMBEDDED_PIC
11497 && (sec == 'd' || sec == 'r'))
11501 /* The ELF backend needs to know that we are changing sections, so
11502 that .previous works correctly. We could do something like check
11503 for an obj_section_change_hook macro, but that might be confusing
11504 as it would not be appropriate to use it in the section changing
11505 functions in read.c, since obj-elf.c intercepts those. FIXME:
11506 This should be cleaner, somehow. */
11507 obj_elf_section_change_hook ();
11510 mips_emit_delays (FALSE);
11520 subseg_set (bss_section, (subsegT) get_absolute_expression ());
11521 demand_empty_rest_of_line ();
11525 if (USE_GLOBAL_POINTER_OPT)
11527 seg = subseg_new (RDATA_SECTION_NAME,
11528 (subsegT) get_absolute_expression ());
11529 if (OUTPUT_FLAVOR == bfd_target_elf_flavour)
11531 bfd_set_section_flags (stdoutput, seg,
11537 if (strcmp (TARGET_OS, "elf") != 0)
11538 record_alignment (seg, 4);
11540 demand_empty_rest_of_line ();
11544 as_bad (_("No read only data section in this object file format"));
11545 demand_empty_rest_of_line ();
11551 if (USE_GLOBAL_POINTER_OPT)
11553 seg = subseg_new (".sdata", (subsegT) get_absolute_expression ());
11554 if (OUTPUT_FLAVOR == bfd_target_elf_flavour)
11556 bfd_set_section_flags (stdoutput, seg,
11557 SEC_ALLOC | SEC_LOAD | SEC_RELOC
11559 if (strcmp (TARGET_OS, "elf") != 0)
11560 record_alignment (seg, 4);
11562 demand_empty_rest_of_line ();
11567 as_bad (_("Global pointers not supported; recompile -G 0"));
11568 demand_empty_rest_of_line ();
11577 s_change_section (int ignore ATTRIBUTE_UNUSED)
11580 char *section_name;
11585 int section_entry_size;
11586 int section_alignment;
11588 if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
11591 section_name = input_line_pointer;
11592 c = get_symbol_end ();
11594 next_c = *(input_line_pointer + 1);
11596 /* Do we have .section Name<,"flags">? */
11597 if (c != ',' || (c == ',' && next_c == '"'))
11599 /* just after name is now '\0'. */
11600 *input_line_pointer = c;
11601 input_line_pointer = section_name;
11602 obj_elf_section (ignore);
11605 input_line_pointer++;
11607 /* Do we have .section Name<,type><,flag><,entry_size><,alignment> */
11609 section_type = get_absolute_expression ();
11612 if (*input_line_pointer++ == ',')
11613 section_flag = get_absolute_expression ();
11616 if (*input_line_pointer++ == ',')
11617 section_entry_size = get_absolute_expression ();
11619 section_entry_size = 0;
11620 if (*input_line_pointer++ == ',')
11621 section_alignment = get_absolute_expression ();
11623 section_alignment = 0;
11625 section_name = xstrdup (section_name);
11627 /* When using the generic form of .section (as implemented by obj-elf.c),
11628 there's no way to set the section type to SHT_MIPS_DWARF. Users have
11629 traditionally had to fall back on the more common @progbits instead.
11631 There's nothing really harmful in this, since bfd will correct
11632 SHT_PROGBITS to SHT_MIPS_DWARF before writing out the file. But it
11633 means that, for backwards compatibiltiy, the special_section entries
11634 for dwarf sections must use SHT_PROGBITS rather than SHT_MIPS_DWARF.
11636 Even so, we shouldn't force users of the MIPS .section syntax to
11637 incorrectly label the sections as SHT_PROGBITS. The best compromise
11638 seems to be to map SHT_MIPS_DWARF to SHT_PROGBITS before calling the
11639 generic type-checking code. */
11640 if (section_type == SHT_MIPS_DWARF)
11641 section_type = SHT_PROGBITS;
11643 obj_elf_change_section (section_name, section_type, section_flag,
11644 section_entry_size, 0, 0, 0);
11646 if (now_seg->name != section_name)
11647 free (section_name);
11648 #endif /* OBJ_ELF */
11652 mips_enable_auto_align (void)
11658 s_cons (int log_size)
11662 label = insn_labels != NULL ? insn_labels->label : NULL;
11663 mips_emit_delays (FALSE);
11664 if (log_size > 0 && auto_align)
11665 mips_align (log_size, 0, label);
11666 mips_clear_insn_labels ();
11667 cons (1 << log_size);
11671 s_float_cons (int type)
11675 label = insn_labels != NULL ? insn_labels->label : NULL;
11677 mips_emit_delays (FALSE);
11682 mips_align (3, 0, label);
11684 mips_align (2, 0, label);
11687 mips_clear_insn_labels ();
11692 /* Handle .globl. We need to override it because on Irix 5 you are
11695 where foo is an undefined symbol, to mean that foo should be
11696 considered to be the address of a function. */
11699 s_mips_globl (int x ATTRIBUTE_UNUSED)
11706 name = input_line_pointer;
11707 c = get_symbol_end ();
11708 symbolP = symbol_find_or_make (name);
11709 *input_line_pointer = c;
11710 SKIP_WHITESPACE ();
11712 /* On Irix 5, every global symbol that is not explicitly labelled as
11713 being a function is apparently labelled as being an object. */
11716 if (! is_end_of_line[(unsigned char) *input_line_pointer])
11721 secname = input_line_pointer;
11722 c = get_symbol_end ();
11723 sec = bfd_get_section_by_name (stdoutput, secname);
11725 as_bad (_("%s: no such section"), secname);
11726 *input_line_pointer = c;
11728 if (sec != NULL && (sec->flags & SEC_CODE) != 0)
11729 flag = BSF_FUNCTION;
11732 symbol_get_bfdsym (symbolP)->flags |= flag;
11734 S_SET_EXTERNAL (symbolP);
11735 demand_empty_rest_of_line ();
11739 s_option (int x ATTRIBUTE_UNUSED)
11744 opt = input_line_pointer;
11745 c = get_symbol_end ();
11749 /* FIXME: What does this mean? */
11751 else if (strncmp (opt, "pic", 3) == 0)
11755 i = atoi (opt + 3);
11760 mips_pic = SVR4_PIC;
11761 mips_abicalls = TRUE;
11764 as_bad (_(".option pic%d not supported"), i);
11766 if (USE_GLOBAL_POINTER_OPT && mips_pic == SVR4_PIC)
11768 if (g_switch_seen && g_switch_value != 0)
11769 as_warn (_("-G may not be used with SVR4 PIC code"));
11770 g_switch_value = 0;
11771 bfd_set_gp_size (stdoutput, 0);
11775 as_warn (_("Unrecognized option \"%s\""), opt);
11777 *input_line_pointer = c;
11778 demand_empty_rest_of_line ();
11781 /* This structure is used to hold a stack of .set values. */
11783 struct mips_option_stack
11785 struct mips_option_stack *next;
11786 struct mips_set_options options;
11789 static struct mips_option_stack *mips_opts_stack;
11791 /* Handle the .set pseudo-op. */
11794 s_mipsset (int x ATTRIBUTE_UNUSED)
11796 char *name = input_line_pointer, ch;
11798 while (!is_end_of_line[(unsigned char) *input_line_pointer])
11799 ++input_line_pointer;
11800 ch = *input_line_pointer;
11801 *input_line_pointer = '\0';
11803 if (strcmp (name, "reorder") == 0)
11805 if (mips_opts.noreorder && prev_nop_frag != NULL)
11807 /* If we still have pending nops, we can discard them. The
11808 usual nop handling will insert any that are still
11810 prev_nop_frag->fr_fix -= (prev_nop_frag_holds
11811 * (mips_opts.mips16 ? 2 : 4));
11812 prev_nop_frag = NULL;
11814 mips_opts.noreorder = 0;
11816 else if (strcmp (name, "noreorder") == 0)
11818 mips_emit_delays (TRUE);
11819 mips_opts.noreorder = 1;
11820 mips_any_noreorder = 1;
11822 else if (strcmp (name, "at") == 0)
11824 mips_opts.noat = 0;
11826 else if (strcmp (name, "noat") == 0)
11828 mips_opts.noat = 1;
11830 else if (strcmp (name, "macro") == 0)
11832 mips_opts.warn_about_macros = 0;
11834 else if (strcmp (name, "nomacro") == 0)
11836 if (mips_opts.noreorder == 0)
11837 as_bad (_("`noreorder' must be set before `nomacro'"));
11838 mips_opts.warn_about_macros = 1;
11840 else if (strcmp (name, "move") == 0 || strcmp (name, "novolatile") == 0)
11842 mips_opts.nomove = 0;
11844 else if (strcmp (name, "nomove") == 0 || strcmp (name, "volatile") == 0)
11846 mips_opts.nomove = 1;
11848 else if (strcmp (name, "bopt") == 0)
11850 mips_opts.nobopt = 0;
11852 else if (strcmp (name, "nobopt") == 0)
11854 mips_opts.nobopt = 1;
11856 else if (strcmp (name, "mips16") == 0
11857 || strcmp (name, "MIPS-16") == 0)
11858 mips_opts.mips16 = 1;
11859 else if (strcmp (name, "nomips16") == 0
11860 || strcmp (name, "noMIPS-16") == 0)
11861 mips_opts.mips16 = 0;
11862 else if (strcmp (name, "mips3d") == 0)
11863 mips_opts.ase_mips3d = 1;
11864 else if (strcmp (name, "nomips3d") == 0)
11865 mips_opts.ase_mips3d = 0;
11866 else if (strcmp (name, "mdmx") == 0)
11867 mips_opts.ase_mdmx = 1;
11868 else if (strcmp (name, "nomdmx") == 0)
11869 mips_opts.ase_mdmx = 0;
11870 else if (strncmp (name, "mips", 4) == 0 || strncmp (name, "arch=", 5) == 0)
11874 /* Permit the user to change the ISA and architecture on the fly.
11875 Needless to say, misuse can cause serious problems. */
11876 if (strcmp (name, "mips0") == 0)
11879 mips_opts.isa = file_mips_isa;
11881 else if (strcmp (name, "mips1") == 0)
11882 mips_opts.isa = ISA_MIPS1;
11883 else if (strcmp (name, "mips2") == 0)
11884 mips_opts.isa = ISA_MIPS2;
11885 else if (strcmp (name, "mips3") == 0)
11886 mips_opts.isa = ISA_MIPS3;
11887 else if (strcmp (name, "mips4") == 0)
11888 mips_opts.isa = ISA_MIPS4;
11889 else if (strcmp (name, "mips5") == 0)
11890 mips_opts.isa = ISA_MIPS5;
11891 else if (strcmp (name, "mips32") == 0)
11892 mips_opts.isa = ISA_MIPS32;
11893 else if (strcmp (name, "mips32r2") == 0)
11894 mips_opts.isa = ISA_MIPS32R2;
11895 else if (strcmp (name, "mips64") == 0)
11896 mips_opts.isa = ISA_MIPS64;
11897 else if (strcmp (name, "mips64r2") == 0)
11898 mips_opts.isa = ISA_MIPS64R2;
11899 else if (strcmp (name, "arch=default") == 0)
11902 mips_opts.arch = file_mips_arch;
11903 mips_opts.isa = file_mips_isa;
11905 else if (strncmp (name, "arch=", 5) == 0)
11907 const struct mips_cpu_info *p;
11909 p = mips_parse_cpu("internal use", name + 5);
11911 as_bad (_("unknown architecture %s"), name + 5);
11914 mips_opts.arch = p->cpu;
11915 mips_opts.isa = p->isa;
11919 as_bad (_("unknown ISA level %s"), name + 4);
11921 switch (mips_opts.isa)
11929 mips_opts.gp32 = 1;
11930 mips_opts.fp32 = 1;
11937 mips_opts.gp32 = 0;
11938 mips_opts.fp32 = 0;
11941 as_bad (_("unknown ISA level %s"), name + 4);
11946 mips_opts.gp32 = file_mips_gp32;
11947 mips_opts.fp32 = file_mips_fp32;
11950 else if (strcmp (name, "autoextend") == 0)
11951 mips_opts.noautoextend = 0;
11952 else if (strcmp (name, "noautoextend") == 0)
11953 mips_opts.noautoextend = 1;
11954 else if (strcmp (name, "push") == 0)
11956 struct mips_option_stack *s;
11958 s = (struct mips_option_stack *) xmalloc (sizeof *s);
11959 s->next = mips_opts_stack;
11960 s->options = mips_opts;
11961 mips_opts_stack = s;
11963 else if (strcmp (name, "pop") == 0)
11965 struct mips_option_stack *s;
11967 s = mips_opts_stack;
11969 as_bad (_(".set pop with no .set push"));
11972 /* If we're changing the reorder mode we need to handle
11973 delay slots correctly. */
11974 if (s->options.noreorder && ! mips_opts.noreorder)
11975 mips_emit_delays (TRUE);
11976 else if (! s->options.noreorder && mips_opts.noreorder)
11978 if (prev_nop_frag != NULL)
11980 prev_nop_frag->fr_fix -= (prev_nop_frag_holds
11981 * (mips_opts.mips16 ? 2 : 4));
11982 prev_nop_frag = NULL;
11986 mips_opts = s->options;
11987 mips_opts_stack = s->next;
11993 as_warn (_("Tried to set unrecognized symbol: %s\n"), name);
11995 *input_line_pointer = ch;
11996 demand_empty_rest_of_line ();
11999 /* Handle the .abicalls pseudo-op. I believe this is equivalent to
12000 .option pic2. It means to generate SVR4 PIC calls. */
12003 s_abicalls (int ignore ATTRIBUTE_UNUSED)
12005 mips_pic = SVR4_PIC;
12006 mips_abicalls = TRUE;
12007 if (USE_GLOBAL_POINTER_OPT)
12009 if (g_switch_seen && g_switch_value != 0)
12010 as_warn (_("-G may not be used with SVR4 PIC code"));
12011 g_switch_value = 0;
12013 bfd_set_gp_size (stdoutput, 0);
12014 demand_empty_rest_of_line ();
12017 /* Handle the .cpload pseudo-op. This is used when generating SVR4
12018 PIC code. It sets the $gp register for the function based on the
12019 function address, which is in the register named in the argument.
12020 This uses a relocation against _gp_disp, which is handled specially
12021 by the linker. The result is:
12022 lui $gp,%hi(_gp_disp)
12023 addiu $gp,$gp,%lo(_gp_disp)
12024 addu $gp,$gp,.cpload argument
12025 The .cpload argument is normally $25 == $t9. */
12028 s_cpload (int ignore ATTRIBUTE_UNUSED)
12032 /* If we are not generating SVR4 PIC code, or if this is NewABI code,
12033 .cpload is ignored. */
12034 if (mips_pic != SVR4_PIC || HAVE_NEWABI)
12040 /* .cpload should be in a .set noreorder section. */
12041 if (mips_opts.noreorder == 0)
12042 as_warn (_(".cpload not in noreorder section"));
12044 ex.X_op = O_symbol;
12045 ex.X_add_symbol = symbol_find_or_make ("_gp_disp");
12046 ex.X_op_symbol = NULL;
12047 ex.X_add_number = 0;
12049 /* In ELF, this symbol is implicitly an STT_OBJECT symbol. */
12050 symbol_get_bfdsym (ex.X_add_symbol)->flags |= BSF_OBJECT;
12053 macro_build_lui (&ex, mips_gp_register);
12054 macro_build (&ex, "addiu", "t,r,j", mips_gp_register,
12055 mips_gp_register, BFD_RELOC_LO16);
12056 macro_build (NULL, "addu", "d,v,t", mips_gp_register,
12057 mips_gp_register, tc_get_register (0));
12060 demand_empty_rest_of_line ();
12063 /* Handle the .cpsetup pseudo-op defined for NewABI PIC code. The syntax is:
12064 .cpsetup $reg1, offset|$reg2, label
12066 If offset is given, this results in:
12067 sd $gp, offset($sp)
12068 lui $gp, %hi(%neg(%gp_rel(label)))
12069 addiu $gp, $gp, %lo(%neg(%gp_rel(label)))
12070 daddu $gp, $gp, $reg1
12072 If $reg2 is given, this results in:
12073 daddu $reg2, $gp, $0
12074 lui $gp, %hi(%neg(%gp_rel(label)))
12075 addiu $gp, $gp, %lo(%neg(%gp_rel(label)))
12076 daddu $gp, $gp, $reg1
12077 $reg1 is normally $25 == $t9. */
12079 s_cpsetup (int ignore ATTRIBUTE_UNUSED)
12081 expressionS ex_off;
12082 expressionS ex_sym;
12086 /* If we are not generating SVR4 PIC code, .cpsetup is ignored.
12087 We also need NewABI support. */
12088 if (mips_pic != SVR4_PIC || ! HAVE_NEWABI)
12094 reg1 = tc_get_register (0);
12095 SKIP_WHITESPACE ();
12096 if (*input_line_pointer != ',')
12098 as_bad (_("missing argument separator ',' for .cpsetup"));
12102 ++input_line_pointer;
12103 SKIP_WHITESPACE ();
12104 if (*input_line_pointer == '$')
12106 mips_cpreturn_register = tc_get_register (0);
12107 mips_cpreturn_offset = -1;
12111 mips_cpreturn_offset = get_absolute_expression ();
12112 mips_cpreturn_register = -1;
12114 SKIP_WHITESPACE ();
12115 if (*input_line_pointer != ',')
12117 as_bad (_("missing argument separator ',' for .cpsetup"));
12121 ++input_line_pointer;
12122 SKIP_WHITESPACE ();
12123 expression (&ex_sym);
12126 if (mips_cpreturn_register == -1)
12128 ex_off.X_op = O_constant;
12129 ex_off.X_add_symbol = NULL;
12130 ex_off.X_op_symbol = NULL;
12131 ex_off.X_add_number = mips_cpreturn_offset;
12133 macro_build (&ex_off, "sd", "t,o(b)", mips_gp_register,
12134 BFD_RELOC_LO16, SP);
12137 macro_build (NULL, "daddu", "d,v,t", mips_cpreturn_register,
12138 mips_gp_register, 0);
12140 /* Ensure there's room for the next two instructions, so that `f'
12141 doesn't end up with an address in the wrong frag. */
12144 macro_build (&ex_sym, "lui", "t,u", mips_gp_register, BFD_RELOC_GPREL16);
12145 fix_new (frag_now, f - frag_now->fr_literal,
12146 8, NULL, 0, 0, BFD_RELOC_MIPS_SUB);
12147 fix_new (frag_now, f - frag_now->fr_literal,
12148 4, NULL, 0, 0, BFD_RELOC_HI16_S);
12151 macro_build (&ex_sym, "addiu", "t,r,j", mips_gp_register,
12152 mips_gp_register, BFD_RELOC_GPREL16);
12153 fix_new (frag_now, f - frag_now->fr_literal,
12154 8, NULL, 0, 0, BFD_RELOC_MIPS_SUB);
12155 fix_new (frag_now, f - frag_now->fr_literal,
12156 4, NULL, 0, 0, BFD_RELOC_LO16);
12158 macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", mips_gp_register,
12159 mips_gp_register, reg1);
12162 demand_empty_rest_of_line ();
12166 s_cplocal (int ignore ATTRIBUTE_UNUSED)
12168 /* If we are not generating SVR4 PIC code, or if this is not NewABI code,
12169 .cplocal is ignored. */
12170 if (mips_pic != SVR4_PIC || ! HAVE_NEWABI)
12176 mips_gp_register = tc_get_register (0);
12177 demand_empty_rest_of_line ();
12180 /* Handle the .cprestore pseudo-op. This stores $gp into a given
12181 offset from $sp. The offset is remembered, and after making a PIC
12182 call $gp is restored from that location. */
12185 s_cprestore (int ignore ATTRIBUTE_UNUSED)
12189 /* If we are not generating SVR4 PIC code, or if this is NewABI code,
12190 .cprestore is ignored. */
12191 if (mips_pic != SVR4_PIC || HAVE_NEWABI)
12197 mips_cprestore_offset = get_absolute_expression ();
12198 mips_cprestore_valid = 1;
12200 ex.X_op = O_constant;
12201 ex.X_add_symbol = NULL;
12202 ex.X_op_symbol = NULL;
12203 ex.X_add_number = mips_cprestore_offset;
12206 macro_build_ldst_constoffset (&ex, ADDRESS_STORE_INSN, mips_gp_register,
12207 SP, HAVE_64BIT_ADDRESSES);
12210 demand_empty_rest_of_line ();
12213 /* Handle the .cpreturn pseudo-op defined for NewABI PIC code. If an offset
12214 was given in the preceding .cpsetup, it results in:
12215 ld $gp, offset($sp)
12217 If a register $reg2 was given there, it results in:
12218 daddu $gp, $reg2, $0
12221 s_cpreturn (int ignore ATTRIBUTE_UNUSED)
12225 /* If we are not generating SVR4 PIC code, .cpreturn is ignored.
12226 We also need NewABI support. */
12227 if (mips_pic != SVR4_PIC || ! HAVE_NEWABI)
12234 if (mips_cpreturn_register == -1)
12236 ex.X_op = O_constant;
12237 ex.X_add_symbol = NULL;
12238 ex.X_op_symbol = NULL;
12239 ex.X_add_number = mips_cpreturn_offset;
12241 macro_build (&ex, "ld", "t,o(b)", mips_gp_register, BFD_RELOC_LO16, SP);
12244 macro_build (NULL, "daddu", "d,v,t", mips_gp_register,
12245 mips_cpreturn_register, 0);
12248 demand_empty_rest_of_line ();
12251 /* Handle the .gpvalue pseudo-op. This is used when generating NewABI PIC
12252 code. It sets the offset to use in gp_rel relocations. */
12255 s_gpvalue (int ignore ATTRIBUTE_UNUSED)
12257 /* If we are not generating SVR4 PIC code, .gpvalue is ignored.
12258 We also need NewABI support. */
12259 if (mips_pic != SVR4_PIC || ! HAVE_NEWABI)
12265 mips_gprel_offset = get_absolute_expression ();
12267 demand_empty_rest_of_line ();
12270 /* Handle the .gpword pseudo-op. This is used when generating PIC
12271 code. It generates a 32 bit GP relative reloc. */
12274 s_gpword (int ignore ATTRIBUTE_UNUSED)
12280 /* When not generating PIC code, this is treated as .word. */
12281 if (mips_pic != SVR4_PIC)
12287 label = insn_labels != NULL ? insn_labels->label : NULL;
12288 mips_emit_delays (TRUE);
12290 mips_align (2, 0, label);
12291 mips_clear_insn_labels ();
12295 if (ex.X_op != O_symbol || ex.X_add_number != 0)
12297 as_bad (_("Unsupported use of .gpword"));
12298 ignore_rest_of_line ();
12302 md_number_to_chars (p, 0, 4);
12303 fix_new_exp (frag_now, p - frag_now->fr_literal, 4, &ex, FALSE,
12304 BFD_RELOC_GPREL32);
12306 demand_empty_rest_of_line ();
12310 s_gpdword (int ignore ATTRIBUTE_UNUSED)
12316 /* When not generating PIC code, this is treated as .dword. */
12317 if (mips_pic != SVR4_PIC)
12323 label = insn_labels != NULL ? insn_labels->label : NULL;
12324 mips_emit_delays (TRUE);
12326 mips_align (3, 0, label);
12327 mips_clear_insn_labels ();
12331 if (ex.X_op != O_symbol || ex.X_add_number != 0)
12333 as_bad (_("Unsupported use of .gpdword"));
12334 ignore_rest_of_line ();
12338 md_number_to_chars (p, 0, 8);
12339 fix_new_exp (frag_now, p - frag_now->fr_literal, 4, &ex, FALSE,
12340 BFD_RELOC_GPREL32);
12342 /* GPREL32 composed with 64 gives a 64-bit GP offset. */
12343 ex.X_op = O_absent;
12344 ex.X_add_symbol = 0;
12345 ex.X_add_number = 0;
12346 fix_new_exp (frag_now, p - frag_now->fr_literal, 8, &ex, FALSE,
12349 demand_empty_rest_of_line ();
12352 /* Handle the .cpadd pseudo-op. This is used when dealing with switch
12353 tables in SVR4 PIC code. */
12356 s_cpadd (int ignore ATTRIBUTE_UNUSED)
12360 /* This is ignored when not generating SVR4 PIC code. */
12361 if (mips_pic != SVR4_PIC)
12367 /* Add $gp to the register named as an argument. */
12369 reg = tc_get_register (0);
12370 macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", reg, reg, mips_gp_register);
12373 demand_empty_rest_of_line ();
12376 /* Handle the .insn pseudo-op. This marks instruction labels in
12377 mips16 mode. This permits the linker to handle them specially,
12378 such as generating jalx instructions when needed. We also make
12379 them odd for the duration of the assembly, in order to generate the
12380 right sort of code. We will make them even in the adjust_symtab
12381 routine, while leaving them marked. This is convenient for the
12382 debugger and the disassembler. The linker knows to make them odd
12386 s_insn (int ignore ATTRIBUTE_UNUSED)
12388 mips16_mark_labels ();
12390 demand_empty_rest_of_line ();
12393 /* Handle a .stabn directive. We need these in order to mark a label
12394 as being a mips16 text label correctly. Sometimes the compiler
12395 will emit a label, followed by a .stabn, and then switch sections.
12396 If the label and .stabn are in mips16 mode, then the label is
12397 really a mips16 text label. */
12400 s_mips_stab (int type)
12403 mips16_mark_labels ();
12408 /* Handle the .weakext pseudo-op as defined in Kane and Heinrich.
12412 s_mips_weakext (int ignore ATTRIBUTE_UNUSED)
12419 name = input_line_pointer;
12420 c = get_symbol_end ();
12421 symbolP = symbol_find_or_make (name);
12422 S_SET_WEAK (symbolP);
12423 *input_line_pointer = c;
12425 SKIP_WHITESPACE ();
12427 if (! is_end_of_line[(unsigned char) *input_line_pointer])
12429 if (S_IS_DEFINED (symbolP))
12431 as_bad ("ignoring attempt to redefine symbol %s",
12432 S_GET_NAME (symbolP));
12433 ignore_rest_of_line ();
12437 if (*input_line_pointer == ',')
12439 ++input_line_pointer;
12440 SKIP_WHITESPACE ();
12444 if (exp.X_op != O_symbol)
12446 as_bad ("bad .weakext directive");
12447 ignore_rest_of_line ();
12450 symbol_set_value_expression (symbolP, &exp);
12453 demand_empty_rest_of_line ();
12456 /* Parse a register string into a number. Called from the ECOFF code
12457 to parse .frame. The argument is non-zero if this is the frame
12458 register, so that we can record it in mips_frame_reg. */
12461 tc_get_register (int frame)
12465 SKIP_WHITESPACE ();
12466 if (*input_line_pointer++ != '$')
12468 as_warn (_("expected `$'"));
12471 else if (ISDIGIT (*input_line_pointer))
12473 reg = get_absolute_expression ();
12474 if (reg < 0 || reg >= 32)
12476 as_warn (_("Bad register number"));
12482 if (strncmp (input_line_pointer, "ra", 2) == 0)
12485 input_line_pointer += 2;
12487 else if (strncmp (input_line_pointer, "fp", 2) == 0)
12490 input_line_pointer += 2;
12492 else if (strncmp (input_line_pointer, "sp", 2) == 0)
12495 input_line_pointer += 2;
12497 else if (strncmp (input_line_pointer, "gp", 2) == 0)
12500 input_line_pointer += 2;
12502 else if (strncmp (input_line_pointer, "at", 2) == 0)
12505 input_line_pointer += 2;
12507 else if (strncmp (input_line_pointer, "kt0", 3) == 0)
12510 input_line_pointer += 3;
12512 else if (strncmp (input_line_pointer, "kt1", 3) == 0)
12515 input_line_pointer += 3;
12517 else if (strncmp (input_line_pointer, "zero", 4) == 0)
12520 input_line_pointer += 4;
12524 as_warn (_("Unrecognized register name"));
12526 while (ISALNUM(*input_line_pointer))
12527 input_line_pointer++;
12532 mips_frame_reg = reg != 0 ? reg : SP;
12533 mips_frame_reg_valid = 1;
12534 mips_cprestore_valid = 0;
12540 md_section_align (asection *seg, valueT addr)
12542 int align = bfd_get_section_alignment (stdoutput, seg);
12545 /* We don't need to align ELF sections to the full alignment.
12546 However, Irix 5 may prefer that we align them at least to a 16
12547 byte boundary. We don't bother to align the sections if we are
12548 targeted for an embedded system. */
12549 if (strcmp (TARGET_OS, "elf") == 0)
12555 return ((addr + (1 << align) - 1) & (-1 << align));
12558 /* Utility routine, called from above as well. If called while the
12559 input file is still being read, it's only an approximation. (For
12560 example, a symbol may later become defined which appeared to be
12561 undefined earlier.) */
12564 nopic_need_relax (symbolS *sym, int before_relaxing)
12569 if (USE_GLOBAL_POINTER_OPT && g_switch_value > 0)
12571 const char *symname;
12574 /* Find out whether this symbol can be referenced off the $gp
12575 register. It can be if it is smaller than the -G size or if
12576 it is in the .sdata or .sbss section. Certain symbols can
12577 not be referenced off the $gp, although it appears as though
12579 symname = S_GET_NAME (sym);
12580 if (symname != (const char *) NULL
12581 && (strcmp (symname, "eprol") == 0
12582 || strcmp (symname, "etext") == 0
12583 || strcmp (symname, "_gp") == 0
12584 || strcmp (symname, "edata") == 0
12585 || strcmp (symname, "_fbss") == 0
12586 || strcmp (symname, "_fdata") == 0
12587 || strcmp (symname, "_ftext") == 0
12588 || strcmp (symname, "end") == 0
12589 || strcmp (symname, "_gp_disp") == 0))
12591 else if ((! S_IS_DEFINED (sym) || S_IS_COMMON (sym))
12593 #ifndef NO_ECOFF_DEBUGGING
12594 || (symbol_get_obj (sym)->ecoff_extern_size != 0
12595 && (symbol_get_obj (sym)->ecoff_extern_size
12596 <= g_switch_value))
12598 /* We must defer this decision until after the whole
12599 file has been read, since there might be a .extern
12600 after the first use of this symbol. */
12601 || (before_relaxing
12602 #ifndef NO_ECOFF_DEBUGGING
12603 && symbol_get_obj (sym)->ecoff_extern_size == 0
12605 && S_GET_VALUE (sym) == 0)
12606 || (S_GET_VALUE (sym) != 0
12607 && S_GET_VALUE (sym) <= g_switch_value)))
12611 const char *segname;
12613 segname = segment_name (S_GET_SEGMENT (sym));
12614 assert (strcmp (segname, ".lit8") != 0
12615 && strcmp (segname, ".lit4") != 0);
12616 change = (strcmp (segname, ".sdata") != 0
12617 && strcmp (segname, ".sbss") != 0
12618 && strncmp (segname, ".sdata.", 7) != 0
12619 && strncmp (segname, ".gnu.linkonce.s.", 16) != 0);
12624 /* We are not optimizing for the $gp register. */
12629 /* Return true if the given symbol should be considered local for SVR4 PIC. */
12632 pic_need_relax (symbolS *sym, asection *segtype)
12635 bfd_boolean linkonce;
12637 /* Handle the case of a symbol equated to another symbol. */
12638 while (symbol_equated_reloc_p (sym))
12642 /* It's possible to get a loop here in a badly written
12644 n = symbol_get_value_expression (sym)->X_add_symbol;
12650 symsec = S_GET_SEGMENT (sym);
12652 /* duplicate the test for LINK_ONCE sections as in adjust_reloc_syms */
12654 if (symsec != segtype && ! S_IS_LOCAL (sym))
12656 if ((bfd_get_section_flags (stdoutput, symsec) & SEC_LINK_ONCE)
12660 /* The GNU toolchain uses an extension for ELF: a section
12661 beginning with the magic string .gnu.linkonce is a linkonce
12663 if (strncmp (segment_name (symsec), ".gnu.linkonce",
12664 sizeof ".gnu.linkonce" - 1) == 0)
12668 /* This must duplicate the test in adjust_reloc_syms. */
12669 return (symsec != &bfd_und_section
12670 && symsec != &bfd_abs_section
12671 && ! bfd_is_com_section (symsec)
12674 /* A global or weak symbol is treated as external. */
12675 && (OUTPUT_FLAVOR != bfd_target_elf_flavour
12676 || (! S_IS_WEAK (sym)
12677 && (! S_IS_EXTERNAL (sym)
12678 || mips_pic == EMBEDDED_PIC)))
12684 /* Given a mips16 variant frag FRAGP, return non-zero if it needs an
12685 extended opcode. SEC is the section the frag is in. */
12688 mips16_extended_frag (fragS *fragp, asection *sec, long stretch)
12691 register const struct mips16_immed_operand *op;
12693 int mintiny, maxtiny;
12697 if (RELAX_MIPS16_USER_SMALL (fragp->fr_subtype))
12699 if (RELAX_MIPS16_USER_EXT (fragp->fr_subtype))
12702 type = RELAX_MIPS16_TYPE (fragp->fr_subtype);
12703 op = mips16_immed_operands;
12704 while (op->type != type)
12707 assert (op < mips16_immed_operands + MIPS16_NUM_IMMED);
12712 if (type == '<' || type == '>' || type == '[' || type == ']')
12715 maxtiny = 1 << op->nbits;
12720 maxtiny = (1 << op->nbits) - 1;
12725 mintiny = - (1 << (op->nbits - 1));
12726 maxtiny = (1 << (op->nbits - 1)) - 1;
12729 sym_frag = symbol_get_frag (fragp->fr_symbol);
12730 val = S_GET_VALUE (fragp->fr_symbol);
12731 symsec = S_GET_SEGMENT (fragp->fr_symbol);
12737 /* We won't have the section when we are called from
12738 mips_relax_frag. However, we will always have been called
12739 from md_estimate_size_before_relax first. If this is a
12740 branch to a different section, we mark it as such. If SEC is
12741 NULL, and the frag is not marked, then it must be a branch to
12742 the same section. */
12745 if (RELAX_MIPS16_LONG_BRANCH (fragp->fr_subtype))
12750 /* Must have been called from md_estimate_size_before_relax. */
12753 fragp->fr_subtype =
12754 RELAX_MIPS16_MARK_LONG_BRANCH (fragp->fr_subtype);
12756 /* FIXME: We should support this, and let the linker
12757 catch branches and loads that are out of range. */
12758 as_bad_where (fragp->fr_file, fragp->fr_line,
12759 _("unsupported PC relative reference to different section"));
12763 if (fragp != sym_frag && sym_frag->fr_address == 0)
12764 /* Assume non-extended on the first relaxation pass.
12765 The address we have calculated will be bogus if this is
12766 a forward branch to another frag, as the forward frag
12767 will have fr_address == 0. */
12771 /* In this case, we know for sure that the symbol fragment is in
12772 the same section. If the relax_marker of the symbol fragment
12773 differs from the relax_marker of this fragment, we have not
12774 yet adjusted the symbol fragment fr_address. We want to add
12775 in STRETCH in order to get a better estimate of the address.
12776 This particularly matters because of the shift bits. */
12778 && sym_frag->relax_marker != fragp->relax_marker)
12782 /* Adjust stretch for any alignment frag. Note that if have
12783 been expanding the earlier code, the symbol may be
12784 defined in what appears to be an earlier frag. FIXME:
12785 This doesn't handle the fr_subtype field, which specifies
12786 a maximum number of bytes to skip when doing an
12788 for (f = fragp; f != NULL && f != sym_frag; f = f->fr_next)
12790 if (f->fr_type == rs_align || f->fr_type == rs_align_code)
12793 stretch = - ((- stretch)
12794 & ~ ((1 << (int) f->fr_offset) - 1));
12796 stretch &= ~ ((1 << (int) f->fr_offset) - 1);
12805 addr = fragp->fr_address + fragp->fr_fix;
12807 /* The base address rules are complicated. The base address of
12808 a branch is the following instruction. The base address of a
12809 PC relative load or add is the instruction itself, but if it
12810 is in a delay slot (in which case it can not be extended) use
12811 the address of the instruction whose delay slot it is in. */
12812 if (type == 'p' || type == 'q')
12816 /* If we are currently assuming that this frag should be
12817 extended, then, the current address is two bytes
12819 if (RELAX_MIPS16_EXTENDED (fragp->fr_subtype))
12822 /* Ignore the low bit in the target, since it will be set
12823 for a text label. */
12824 if ((val & 1) != 0)
12827 else if (RELAX_MIPS16_JAL_DSLOT (fragp->fr_subtype))
12829 else if (RELAX_MIPS16_DSLOT (fragp->fr_subtype))
12832 val -= addr & ~ ((1 << op->shift) - 1);
12834 /* Branch offsets have an implicit 0 in the lowest bit. */
12835 if (type == 'p' || type == 'q')
12838 /* If any of the shifted bits are set, we must use an extended
12839 opcode. If the address depends on the size of this
12840 instruction, this can lead to a loop, so we arrange to always
12841 use an extended opcode. We only check this when we are in
12842 the main relaxation loop, when SEC is NULL. */
12843 if ((val & ((1 << op->shift) - 1)) != 0 && sec == NULL)
12845 fragp->fr_subtype =
12846 RELAX_MIPS16_MARK_LONG_BRANCH (fragp->fr_subtype);
12850 /* If we are about to mark a frag as extended because the value
12851 is precisely maxtiny + 1, then there is a chance of an
12852 infinite loop as in the following code:
12857 In this case when the la is extended, foo is 0x3fc bytes
12858 away, so the la can be shrunk, but then foo is 0x400 away, so
12859 the la must be extended. To avoid this loop, we mark the
12860 frag as extended if it was small, and is about to become
12861 extended with a value of maxtiny + 1. */
12862 if (val == ((maxtiny + 1) << op->shift)
12863 && ! RELAX_MIPS16_EXTENDED (fragp->fr_subtype)
12866 fragp->fr_subtype =
12867 RELAX_MIPS16_MARK_LONG_BRANCH (fragp->fr_subtype);
12871 else if (symsec != absolute_section && sec != NULL)
12872 as_bad_where (fragp->fr_file, fragp->fr_line, _("unsupported relocation"));
12874 if ((val & ((1 << op->shift) - 1)) != 0
12875 || val < (mintiny << op->shift)
12876 || val > (maxtiny << op->shift))
12882 /* Compute the length of a branch sequence, and adjust the
12883 RELAX_BRANCH_TOOFAR bit accordingly. If FRAGP is NULL, the
12884 worst-case length is computed, with UPDATE being used to indicate
12885 whether an unconditional (-1), branch-likely (+1) or regular (0)
12886 branch is to be computed. */
12888 relaxed_branch_length (fragS *fragp, asection *sec, int update)
12890 bfd_boolean toofar;
12894 && S_IS_DEFINED (fragp->fr_symbol)
12895 && sec == S_GET_SEGMENT (fragp->fr_symbol))
12900 val = S_GET_VALUE (fragp->fr_symbol) + fragp->fr_offset;
12902 addr = fragp->fr_address + fragp->fr_fix + 4;
12906 toofar = val < - (0x8000 << 2) || val >= (0x8000 << 2);
12909 /* If the symbol is not defined or it's in a different segment,
12910 assume the user knows what's going on and emit a short
12916 if (fragp && update && toofar != RELAX_BRANCH_TOOFAR (fragp->fr_subtype))
12918 = RELAX_BRANCH_ENCODE (RELAX_BRANCH_UNCOND (fragp->fr_subtype),
12919 RELAX_BRANCH_LIKELY (fragp->fr_subtype),
12920 RELAX_BRANCH_LINK (fragp->fr_subtype),
12926 if (fragp ? RELAX_BRANCH_LIKELY (fragp->fr_subtype) : (update > 0))
12929 if (mips_pic != NO_PIC)
12931 /* Additional space for PIC loading of target address. */
12933 if (mips_opts.isa == ISA_MIPS1)
12934 /* Additional space for $at-stabilizing nop. */
12938 /* If branch is conditional. */
12939 if (fragp ? !RELAX_BRANCH_UNCOND (fragp->fr_subtype) : (update >= 0))
12946 /* Estimate the size of a frag before relaxing. Unless this is the
12947 mips16, we are not really relaxing here, and the final size is
12948 encoded in the subtype information. For the mips16, we have to
12949 decide whether we are using an extended opcode or not. */
12952 md_estimate_size_before_relax (fragS *fragp, asection *segtype)
12956 if (RELAX_BRANCH_P (fragp->fr_subtype))
12959 fragp->fr_var = relaxed_branch_length (fragp, segtype, FALSE);
12961 return fragp->fr_var;
12964 if (RELAX_MIPS16_P (fragp->fr_subtype))
12965 /* We don't want to modify the EXTENDED bit here; it might get us
12966 into infinite loops. We change it only in mips_relax_frag(). */
12967 return (RELAX_MIPS16_EXTENDED (fragp->fr_subtype) ? 4 : 2);
12969 if (mips_pic == NO_PIC)
12970 change = nopic_need_relax (fragp->fr_symbol, 0);
12971 else if (mips_pic == SVR4_PIC)
12972 change = pic_need_relax (fragp->fr_symbol, segtype);
12978 fragp->fr_subtype |= RELAX_USE_SECOND;
12979 return -RELAX_FIRST (fragp->fr_subtype);
12982 return -RELAX_SECOND (fragp->fr_subtype);
12985 /* This is called to see whether a reloc against a defined symbol
12986 should be converted into a reloc against a section. Don't adjust
12987 MIPS16 jump relocations, so we don't have to worry about the format
12988 of the offset in the .o file. Don't adjust relocations against
12989 mips16 symbols, so that the linker can find them if it needs to set
12993 mips_fix_adjustable (fixS *fixp)
12995 if (fixp->fx_r_type == BFD_RELOC_MIPS16_JMP)
12998 if (fixp->fx_r_type == BFD_RELOC_VTABLE_INHERIT
12999 || fixp->fx_r_type == BFD_RELOC_VTABLE_ENTRY)
13002 if (fixp->fx_addsy == NULL)
13006 if (OUTPUT_FLAVOR == bfd_target_elf_flavour
13007 && S_GET_OTHER (fixp->fx_addsy) == STO_MIPS16
13008 && fixp->fx_subsy == NULL)
13015 /* Translate internal representation of relocation info to BFD target
13019 tc_gen_reloc (asection *section ATTRIBUTE_UNUSED, fixS *fixp)
13021 static arelent *retval[4];
13023 bfd_reloc_code_real_type code;
13025 memset (retval, 0, sizeof(retval));
13026 reloc = retval[0] = (arelent *) xcalloc (1, sizeof (arelent));
13027 reloc->sym_ptr_ptr = (asymbol **) xmalloc (sizeof (asymbol *));
13028 *reloc->sym_ptr_ptr = symbol_get_bfdsym (fixp->fx_addsy);
13029 reloc->address = fixp->fx_frag->fr_address + fixp->fx_where;
13031 if (mips_pic == EMBEDDED_PIC
13032 && SWITCH_TABLE (fixp))
13034 /* For a switch table entry we use a special reloc. The addend
13035 is actually the difference between the reloc address and the
13037 reloc->addend = reloc->address - S_GET_VALUE (fixp->fx_subsy);
13038 if (OUTPUT_FLAVOR != bfd_target_ecoff_flavour)
13039 as_fatal (_("Double check fx_r_type in tc-mips.c:tc_gen_reloc"));
13040 fixp->fx_r_type = BFD_RELOC_GPREL32;
13042 else if (fixp->fx_pcrel)
13044 bfd_vma pcrel_address;
13046 /* Set PCREL_ADDRESS to this relocation's "PC". The PC for high
13047 high-part relocs is the address of the low-part reloc. */
13048 if (fixp->fx_r_type == BFD_RELOC_PCREL_HI16_S)
13050 assert (fixp->fx_next != NULL
13051 && fixp->fx_next->fx_r_type == BFD_RELOC_PCREL_LO16);
13052 pcrel_address = (fixp->fx_next->fx_where
13053 + fixp->fx_next->fx_frag->fr_address);
13056 pcrel_address = reloc->address;
13058 if (OUTPUT_FLAVOR == bfd_target_elf_flavour)
13060 /* At this point, fx_addnumber is "symbol offset - pcrel_address".
13061 Relocations want only the symbol offset. */
13062 reloc->addend = fixp->fx_addnumber + pcrel_address;
13064 else if (fixp->fx_r_type == BFD_RELOC_PCREL_LO16
13065 || fixp->fx_r_type == BFD_RELOC_PCREL_HI16_S)
13067 /* We use a special addend for an internal RELLO or RELHI reloc. */
13068 if (symbol_section_p (fixp->fx_addsy))
13069 reloc->addend = pcrel_address - S_GET_VALUE (fixp->fx_subsy);
13071 reloc->addend = fixp->fx_addnumber + pcrel_address;
13075 if (OUTPUT_FLAVOR != bfd_target_aout_flavour)
13076 /* A gruesome hack which is a result of the gruesome gas reloc
13078 reloc->addend = pcrel_address;
13080 reloc->addend = -pcrel_address;
13084 reloc->addend = fixp->fx_addnumber;
13086 /* Since the old MIPS ELF ABI uses Rel instead of Rela, encode the vtable
13087 entry to be used in the relocation's section offset. */
13088 if (! HAVE_NEWABI && fixp->fx_r_type == BFD_RELOC_VTABLE_ENTRY)
13090 reloc->address = reloc->addend;
13094 /* Since DIFF_EXPR_OK is defined in tc-mips.h, it is possible that
13095 fixup_segment converted a non-PC relative reloc into a PC
13096 relative reloc. In such a case, we need to convert the reloc
13098 code = fixp->fx_r_type;
13099 if (fixp->fx_pcrel)
13104 code = BFD_RELOC_8_PCREL;
13107 code = BFD_RELOC_16_PCREL;
13110 code = BFD_RELOC_32_PCREL;
13113 code = BFD_RELOC_64_PCREL;
13115 case BFD_RELOC_8_PCREL:
13116 case BFD_RELOC_16_PCREL:
13117 case BFD_RELOC_32_PCREL:
13118 case BFD_RELOC_64_PCREL:
13119 case BFD_RELOC_16_PCREL_S2:
13120 case BFD_RELOC_PCREL_HI16_S:
13121 case BFD_RELOC_PCREL_LO16:
13124 as_bad_where (fixp->fx_file, fixp->fx_line,
13125 _("Cannot make %s relocation PC relative"),
13126 bfd_get_reloc_code_name (code));
13130 /* To support a PC relative reloc when generating embedded PIC code
13131 for ECOFF, we use a Cygnus extension. We check for that here to
13132 make sure that we don't let such a reloc escape normally. */
13133 if ((OUTPUT_FLAVOR == bfd_target_ecoff_flavour
13134 || OUTPUT_FLAVOR == bfd_target_elf_flavour)
13135 && code == BFD_RELOC_16_PCREL_S2
13136 && mips_pic != EMBEDDED_PIC)
13137 reloc->howto = NULL;
13139 reloc->howto = bfd_reloc_type_lookup (stdoutput, code);
13141 if (reloc->howto == NULL)
13143 as_bad_where (fixp->fx_file, fixp->fx_line,
13144 _("Can not represent %s relocation in this object file format"),
13145 bfd_get_reloc_code_name (code));
13152 /* Relax a machine dependent frag. This returns the amount by which
13153 the current size of the frag should change. */
13156 mips_relax_frag (asection *sec, fragS *fragp, long stretch)
13158 if (RELAX_BRANCH_P (fragp->fr_subtype))
13160 offsetT old_var = fragp->fr_var;
13162 fragp->fr_var = relaxed_branch_length (fragp, sec, TRUE);
13164 return fragp->fr_var - old_var;
13167 if (! RELAX_MIPS16_P (fragp->fr_subtype))
13170 if (mips16_extended_frag (fragp, NULL, stretch))
13172 if (RELAX_MIPS16_EXTENDED (fragp->fr_subtype))
13174 fragp->fr_subtype = RELAX_MIPS16_MARK_EXTENDED (fragp->fr_subtype);
13179 if (! RELAX_MIPS16_EXTENDED (fragp->fr_subtype))
13181 fragp->fr_subtype = RELAX_MIPS16_CLEAR_EXTENDED (fragp->fr_subtype);
13188 /* Convert a machine dependent frag. */
13191 md_convert_frag (bfd *abfd ATTRIBUTE_UNUSED, segT asec, fragS *fragp)
13193 if (RELAX_BRANCH_P (fragp->fr_subtype))
13196 unsigned long insn;
13200 buf = (bfd_byte *)fragp->fr_literal + fragp->fr_fix;
13202 if (target_big_endian)
13203 insn = bfd_getb32 (buf);
13205 insn = bfd_getl32 (buf);
13207 if (!RELAX_BRANCH_TOOFAR (fragp->fr_subtype))
13209 /* We generate a fixup instead of applying it right now
13210 because, if there are linker relaxations, we're going to
13211 need the relocations. */
13212 exp.X_op = O_symbol;
13213 exp.X_add_symbol = fragp->fr_symbol;
13214 exp.X_add_number = fragp->fr_offset;
13216 fixp = fix_new_exp (fragp, buf - (bfd_byte *)fragp->fr_literal,
13218 BFD_RELOC_16_PCREL_S2);
13219 fixp->fx_file = fragp->fr_file;
13220 fixp->fx_line = fragp->fr_line;
13222 md_number_to_chars (buf, insn, 4);
13229 as_warn_where (fragp->fr_file, fragp->fr_line,
13230 _("relaxed out-of-range branch into a jump"));
13232 if (RELAX_BRANCH_UNCOND (fragp->fr_subtype))
13235 if (!RELAX_BRANCH_LIKELY (fragp->fr_subtype))
13237 /* Reverse the branch. */
13238 switch ((insn >> 28) & 0xf)
13241 /* bc[0-3][tf]l? and bc1any[24][ft] instructions can
13242 have the condition reversed by tweaking a single
13243 bit, and their opcodes all have 0x4???????. */
13244 assert ((insn & 0xf1000000) == 0x41000000);
13245 insn ^= 0x00010000;
13249 /* bltz 0x04000000 bgez 0x04010000
13250 bltzal 0x04100000 bgezal 0x04110000 */
13251 assert ((insn & 0xfc0e0000) == 0x04000000);
13252 insn ^= 0x00010000;
13256 /* beq 0x10000000 bne 0x14000000
13257 blez 0x18000000 bgtz 0x1c000000 */
13258 insn ^= 0x04000000;
13266 if (RELAX_BRANCH_LINK (fragp->fr_subtype))
13268 /* Clear the and-link bit. */
13269 assert ((insn & 0xfc1c0000) == 0x04100000);
13271 /* bltzal 0x04100000 bgezal 0x04110000
13272 bltzall 0x04120000 bgezall 0x04130000 */
13273 insn &= ~0x00100000;
13276 /* Branch over the branch (if the branch was likely) or the
13277 full jump (not likely case). Compute the offset from the
13278 current instruction to branch to. */
13279 if (RELAX_BRANCH_LIKELY (fragp->fr_subtype))
13283 /* How many bytes in instructions we've already emitted? */
13284 i = buf - (bfd_byte *)fragp->fr_literal - fragp->fr_fix;
13285 /* How many bytes in instructions from here to the end? */
13286 i = fragp->fr_var - i;
13288 /* Convert to instruction count. */
13290 /* Branch counts from the next instruction. */
13293 /* Branch over the jump. */
13294 md_number_to_chars (buf, insn, 4);
13298 md_number_to_chars (buf, 0, 4);
13301 if (RELAX_BRANCH_LIKELY (fragp->fr_subtype))
13303 /* beql $0, $0, 2f */
13305 /* Compute the PC offset from the current instruction to
13306 the end of the variable frag. */
13307 /* How many bytes in instructions we've already emitted? */
13308 i = buf - (bfd_byte *)fragp->fr_literal - fragp->fr_fix;
13309 /* How many bytes in instructions from here to the end? */
13310 i = fragp->fr_var - i;
13311 /* Convert to instruction count. */
13313 /* Don't decrement i, because we want to branch over the
13317 md_number_to_chars (buf, insn, 4);
13320 md_number_to_chars (buf, 0, 4);
13325 if (mips_pic == NO_PIC)
13328 insn = (RELAX_BRANCH_LINK (fragp->fr_subtype)
13329 ? 0x0c000000 : 0x08000000);
13330 exp.X_op = O_symbol;
13331 exp.X_add_symbol = fragp->fr_symbol;
13332 exp.X_add_number = fragp->fr_offset;
13334 fixp = fix_new_exp (fragp, buf - (bfd_byte *)fragp->fr_literal,
13335 4, &exp, 0, BFD_RELOC_MIPS_JMP);
13336 fixp->fx_file = fragp->fr_file;
13337 fixp->fx_line = fragp->fr_line;
13339 md_number_to_chars (buf, insn, 4);
13344 /* lw/ld $at, <sym>($gp) R_MIPS_GOT16 */
13345 insn = HAVE_64BIT_ADDRESSES ? 0xdf810000 : 0x8f810000;
13346 exp.X_op = O_symbol;
13347 exp.X_add_symbol = fragp->fr_symbol;
13348 exp.X_add_number = fragp->fr_offset;
13350 if (fragp->fr_offset)
13352 exp.X_add_symbol = make_expr_symbol (&exp);
13353 exp.X_add_number = 0;
13356 fixp = fix_new_exp (fragp, buf - (bfd_byte *)fragp->fr_literal,
13357 4, &exp, 0, BFD_RELOC_MIPS_GOT16);
13358 fixp->fx_file = fragp->fr_file;
13359 fixp->fx_line = fragp->fr_line;
13361 md_number_to_chars (buf, insn, 4);
13364 if (mips_opts.isa == ISA_MIPS1)
13367 md_number_to_chars (buf, 0, 4);
13371 /* d/addiu $at, $at, <sym> R_MIPS_LO16 */
13372 insn = HAVE_64BIT_ADDRESSES ? 0x64210000 : 0x24210000;
13374 fixp = fix_new_exp (fragp, buf - (bfd_byte *)fragp->fr_literal,
13375 4, &exp, 0, BFD_RELOC_LO16);
13376 fixp->fx_file = fragp->fr_file;
13377 fixp->fx_line = fragp->fr_line;
13379 md_number_to_chars (buf, insn, 4);
13383 if (RELAX_BRANCH_LINK (fragp->fr_subtype))
13388 md_number_to_chars (buf, insn, 4);
13393 assert (buf == (bfd_byte *)fragp->fr_literal
13394 + fragp->fr_fix + fragp->fr_var);
13396 fragp->fr_fix += fragp->fr_var;
13401 if (RELAX_MIPS16_P (fragp->fr_subtype))
13404 register const struct mips16_immed_operand *op;
13405 bfd_boolean small, ext;
13408 unsigned long insn;
13409 bfd_boolean use_extend;
13410 unsigned short extend;
13412 type = RELAX_MIPS16_TYPE (fragp->fr_subtype);
13413 op = mips16_immed_operands;
13414 while (op->type != type)
13417 if (RELAX_MIPS16_EXTENDED (fragp->fr_subtype))
13428 resolve_symbol_value (fragp->fr_symbol);
13429 val = S_GET_VALUE (fragp->fr_symbol);
13434 addr = fragp->fr_address + fragp->fr_fix;
13436 /* The rules for the base address of a PC relative reloc are
13437 complicated; see mips16_extended_frag. */
13438 if (type == 'p' || type == 'q')
13443 /* Ignore the low bit in the target, since it will be
13444 set for a text label. */
13445 if ((val & 1) != 0)
13448 else if (RELAX_MIPS16_JAL_DSLOT (fragp->fr_subtype))
13450 else if (RELAX_MIPS16_DSLOT (fragp->fr_subtype))
13453 addr &= ~ (addressT) ((1 << op->shift) - 1);
13456 /* Make sure the section winds up with the alignment we have
13459 record_alignment (asec, op->shift);
13463 && (RELAX_MIPS16_JAL_DSLOT (fragp->fr_subtype)
13464 || RELAX_MIPS16_DSLOT (fragp->fr_subtype)))
13465 as_warn_where (fragp->fr_file, fragp->fr_line,
13466 _("extended instruction in delay slot"));
13468 buf = (bfd_byte *) (fragp->fr_literal + fragp->fr_fix);
13470 if (target_big_endian)
13471 insn = bfd_getb16 (buf);
13473 insn = bfd_getl16 (buf);
13475 mips16_immed (fragp->fr_file, fragp->fr_line, type, val,
13476 RELAX_MIPS16_USER_EXT (fragp->fr_subtype),
13477 small, ext, &insn, &use_extend, &extend);
13481 md_number_to_chars (buf, 0xf000 | extend, 2);
13482 fragp->fr_fix += 2;
13486 md_number_to_chars (buf, insn, 2);
13487 fragp->fr_fix += 2;
13495 first = RELAX_FIRST (fragp->fr_subtype);
13496 second = RELAX_SECOND (fragp->fr_subtype);
13497 fixp = (fixS *) fragp->fr_opcode;
13499 /* Possibly emit a warning if we've chosen the longer option. */
13500 if (((fragp->fr_subtype & RELAX_USE_SECOND) != 0)
13501 == ((fragp->fr_subtype & RELAX_SECOND_LONGER) != 0))
13503 const char *msg = macro_warning (fragp->fr_subtype);
13505 as_warn_where (fragp->fr_file, fragp->fr_line, msg);
13508 /* Go through all the fixups for the first sequence. Disable them
13509 (by marking them as done) if we're going to use the second
13510 sequence instead. */
13512 && fixp->fx_frag == fragp
13513 && fixp->fx_where < fragp->fr_fix - second)
13515 if (fragp->fr_subtype & RELAX_USE_SECOND)
13517 fixp = fixp->fx_next;
13520 /* Go through the fixups for the second sequence. Disable them if
13521 we're going to use the first sequence, otherwise adjust their
13522 addresses to account for the relaxation. */
13523 while (fixp && fixp->fx_frag == fragp)
13525 if (fragp->fr_subtype & RELAX_USE_SECOND)
13526 fixp->fx_where -= first;
13529 fixp = fixp->fx_next;
13532 /* Now modify the frag contents. */
13533 if (fragp->fr_subtype & RELAX_USE_SECOND)
13537 start = fragp->fr_literal + fragp->fr_fix - first - second;
13538 memmove (start, start + first, second);
13539 fragp->fr_fix -= first;
13542 fragp->fr_fix -= second;
13548 /* This function is called after the relocs have been generated.
13549 We've been storing mips16 text labels as odd. Here we convert them
13550 back to even for the convenience of the debugger. */
13553 mips_frob_file_after_relocs (void)
13556 unsigned int count, i;
13558 if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
13561 syms = bfd_get_outsymbols (stdoutput);
13562 count = bfd_get_symcount (stdoutput);
13563 for (i = 0; i < count; i++, syms++)
13565 if (elf_symbol (*syms)->internal_elf_sym.st_other == STO_MIPS16
13566 && ((*syms)->value & 1) != 0)
13568 (*syms)->value &= ~1;
13569 /* If the symbol has an odd size, it was probably computed
13570 incorrectly, so adjust that as well. */
13571 if ((elf_symbol (*syms)->internal_elf_sym.st_size & 1) != 0)
13572 ++elf_symbol (*syms)->internal_elf_sym.st_size;
13579 /* This function is called whenever a label is defined. It is used
13580 when handling branch delays; if a branch has a label, we assume we
13581 can not move it. */
13584 mips_define_label (symbolS *sym)
13586 struct insn_label_list *l;
13588 if (free_insn_labels == NULL)
13589 l = (struct insn_label_list *) xmalloc (sizeof *l);
13592 l = free_insn_labels;
13593 free_insn_labels = l->next;
13597 l->next = insn_labels;
13601 #if defined (OBJ_ELF) || defined (OBJ_MAYBE_ELF)
13603 /* Some special processing for a MIPS ELF file. */
13606 mips_elf_final_processing (void)
13608 /* Write out the register information. */
13609 if (mips_abi != N64_ABI)
13613 s.ri_gprmask = mips_gprmask;
13614 s.ri_cprmask[0] = mips_cprmask[0];
13615 s.ri_cprmask[1] = mips_cprmask[1];
13616 s.ri_cprmask[2] = mips_cprmask[2];
13617 s.ri_cprmask[3] = mips_cprmask[3];
13618 /* The gp_value field is set by the MIPS ELF backend. */
13620 bfd_mips_elf32_swap_reginfo_out (stdoutput, &s,
13621 ((Elf32_External_RegInfo *)
13622 mips_regmask_frag));
13626 Elf64_Internal_RegInfo s;
13628 s.ri_gprmask = mips_gprmask;
13630 s.ri_cprmask[0] = mips_cprmask[0];
13631 s.ri_cprmask[1] = mips_cprmask[1];
13632 s.ri_cprmask[2] = mips_cprmask[2];
13633 s.ri_cprmask[3] = mips_cprmask[3];
13634 /* The gp_value field is set by the MIPS ELF backend. */
13636 bfd_mips_elf64_swap_reginfo_out (stdoutput, &s,
13637 ((Elf64_External_RegInfo *)
13638 mips_regmask_frag));
13641 /* Set the MIPS ELF flag bits. FIXME: There should probably be some
13642 sort of BFD interface for this. */
13643 if (mips_any_noreorder)
13644 elf_elfheader (stdoutput)->e_flags |= EF_MIPS_NOREORDER;
13645 if (mips_pic != NO_PIC)
13647 elf_elfheader (stdoutput)->e_flags |= EF_MIPS_PIC;
13648 elf_elfheader (stdoutput)->e_flags |= EF_MIPS_CPIC;
13651 elf_elfheader (stdoutput)->e_flags |= EF_MIPS_CPIC;
13653 /* Set MIPS ELF flags for ASEs. */
13654 if (file_ase_mips16)
13655 elf_elfheader (stdoutput)->e_flags |= EF_MIPS_ARCH_ASE_M16;
13656 #if 0 /* XXX FIXME */
13657 if (file_ase_mips3d)
13658 elf_elfheader (stdoutput)->e_flags |= ???;
13661 elf_elfheader (stdoutput)->e_flags |= EF_MIPS_ARCH_ASE_MDMX;
13663 /* Set the MIPS ELF ABI flags. */
13664 if (mips_abi == O32_ABI && USE_E_MIPS_ABI_O32)
13665 elf_elfheader (stdoutput)->e_flags |= E_MIPS_ABI_O32;
13666 else if (mips_abi == O64_ABI)
13667 elf_elfheader (stdoutput)->e_flags |= E_MIPS_ABI_O64;
13668 else if (mips_abi == EABI_ABI)
13670 if (!file_mips_gp32)
13671 elf_elfheader (stdoutput)->e_flags |= E_MIPS_ABI_EABI64;
13673 elf_elfheader (stdoutput)->e_flags |= E_MIPS_ABI_EABI32;
13675 else if (mips_abi == N32_ABI)
13676 elf_elfheader (stdoutput)->e_flags |= EF_MIPS_ABI2;
13678 /* Nothing to do for N64_ABI. */
13680 if (mips_32bitmode)
13681 elf_elfheader (stdoutput)->e_flags |= EF_MIPS_32BITMODE;
13684 #endif /* OBJ_ELF || OBJ_MAYBE_ELF */
13686 typedef struct proc {
13688 unsigned long reg_mask;
13689 unsigned long reg_offset;
13690 unsigned long fpreg_mask;
13691 unsigned long fpreg_offset;
13692 unsigned long frame_offset;
13693 unsigned long frame_reg;
13694 unsigned long pc_reg;
13697 static procS cur_proc;
13698 static procS *cur_proc_ptr;
13699 static int numprocs;
13701 /* Fill in an rs_align_code fragment. */
13704 mips_handle_align (fragS *fragp)
13706 if (fragp->fr_type != rs_align_code)
13709 if (mips_opts.mips16)
13711 static const unsigned char be_nop[] = { 0x65, 0x00 };
13712 static const unsigned char le_nop[] = { 0x00, 0x65 };
13717 bytes = fragp->fr_next->fr_address - fragp->fr_address - fragp->fr_fix;
13718 p = fragp->fr_literal + fragp->fr_fix;
13726 memcpy (p, (target_big_endian ? be_nop : le_nop), 2);
13730 /* For mips32, a nop is a zero, which we trivially get by doing nothing. */
13734 md_obj_begin (void)
13741 /* check for premature end, nesting errors, etc */
13743 as_warn (_("missing .end at end of assembly"));
13752 if (*input_line_pointer == '-')
13754 ++input_line_pointer;
13757 if (!ISDIGIT (*input_line_pointer))
13758 as_bad (_("expected simple number"));
13759 if (input_line_pointer[0] == '0')
13761 if (input_line_pointer[1] == 'x')
13763 input_line_pointer += 2;
13764 while (ISXDIGIT (*input_line_pointer))
13767 val |= hex_value (*input_line_pointer++);
13769 return negative ? -val : val;
13773 ++input_line_pointer;
13774 while (ISDIGIT (*input_line_pointer))
13777 val |= *input_line_pointer++ - '0';
13779 return negative ? -val : val;
13782 if (!ISDIGIT (*input_line_pointer))
13784 printf (_(" *input_line_pointer == '%c' 0x%02x\n"),
13785 *input_line_pointer, *input_line_pointer);
13786 as_warn (_("invalid number"));
13789 while (ISDIGIT (*input_line_pointer))
13792 val += *input_line_pointer++ - '0';
13794 return negative ? -val : val;
13797 /* The .file directive; just like the usual .file directive, but there
13798 is an initial number which is the ECOFF file index. In the non-ECOFF
13799 case .file implies DWARF-2. */
13802 s_mips_file (int x ATTRIBUTE_UNUSED)
13804 static int first_file_directive = 0;
13806 if (ECOFF_DEBUGGING)
13815 filename = dwarf2_directive_file (0);
13817 /* Versions of GCC up to 3.1 start files with a ".file"
13818 directive even for stabs output. Make sure that this
13819 ".file" is handled. Note that you need a version of GCC
13820 after 3.1 in order to support DWARF-2 on MIPS. */
13821 if (filename != NULL && ! first_file_directive)
13823 (void) new_logical_line (filename, -1);
13824 s_app_file_string (filename);
13826 first_file_directive = 1;
13830 /* The .loc directive, implying DWARF-2. */
13833 s_mips_loc (int x ATTRIBUTE_UNUSED)
13835 if (!ECOFF_DEBUGGING)
13836 dwarf2_directive_loc (0);
13839 /* The .end directive. */
13842 s_mips_end (int x ATTRIBUTE_UNUSED)
13846 /* Following functions need their own .frame and .cprestore directives. */
13847 mips_frame_reg_valid = 0;
13848 mips_cprestore_valid = 0;
13850 if (!is_end_of_line[(unsigned char) *input_line_pointer])
13853 demand_empty_rest_of_line ();
13858 if ((bfd_get_section_flags (stdoutput, now_seg) & SEC_CODE) == 0)
13859 as_warn (_(".end not in text section"));
13863 as_warn (_(".end directive without a preceding .ent directive."));
13864 demand_empty_rest_of_line ();
13870 assert (S_GET_NAME (p));
13871 if (strcmp (S_GET_NAME (p), S_GET_NAME (cur_proc_ptr->isym)))
13872 as_warn (_(".end symbol does not match .ent symbol."));
13874 if (debug_type == DEBUG_STABS)
13875 stabs_generate_asm_endfunc (S_GET_NAME (p),
13879 as_warn (_(".end directive missing or unknown symbol"));
13882 /* Generate a .pdr section. */
13883 if (OUTPUT_FLAVOR == bfd_target_elf_flavour && ! ECOFF_DEBUGGING
13886 segT saved_seg = now_seg;
13887 subsegT saved_subseg = now_subseg;
13892 dot = frag_now_fix ();
13894 #ifdef md_flush_pending_output
13895 md_flush_pending_output ();
13899 subseg_set (pdr_seg, 0);
13901 /* Write the symbol. */
13902 exp.X_op = O_symbol;
13903 exp.X_add_symbol = p;
13904 exp.X_add_number = 0;
13905 emit_expr (&exp, 4);
13907 fragp = frag_more (7 * 4);
13909 md_number_to_chars (fragp, cur_proc_ptr->reg_mask, 4);
13910 md_number_to_chars (fragp + 4, cur_proc_ptr->reg_offset, 4);
13911 md_number_to_chars (fragp + 8, cur_proc_ptr->fpreg_mask, 4);
13912 md_number_to_chars (fragp + 12, cur_proc_ptr->fpreg_offset, 4);
13913 md_number_to_chars (fragp + 16, cur_proc_ptr->frame_offset, 4);
13914 md_number_to_chars (fragp + 20, cur_proc_ptr->frame_reg, 4);
13915 md_number_to_chars (fragp + 24, cur_proc_ptr->pc_reg, 4);
13917 subseg_set (saved_seg, saved_subseg);
13919 #endif /* OBJ_ELF */
13921 cur_proc_ptr = NULL;
13924 /* The .aent and .ent directives. */
13927 s_mips_ent (int aent)
13931 symbolP = get_symbol ();
13932 if (*input_line_pointer == ',')
13933 ++input_line_pointer;
13934 SKIP_WHITESPACE ();
13935 if (ISDIGIT (*input_line_pointer)
13936 || *input_line_pointer == '-')
13939 if ((bfd_get_section_flags (stdoutput, now_seg) & SEC_CODE) == 0)
13940 as_warn (_(".ent or .aent not in text section."));
13942 if (!aent && cur_proc_ptr)
13943 as_warn (_("missing .end"));
13947 /* This function needs its own .frame and .cprestore directives. */
13948 mips_frame_reg_valid = 0;
13949 mips_cprestore_valid = 0;
13951 cur_proc_ptr = &cur_proc;
13952 memset (cur_proc_ptr, '\0', sizeof (procS));
13954 cur_proc_ptr->isym = symbolP;
13956 symbol_get_bfdsym (symbolP)->flags |= BSF_FUNCTION;
13960 if (debug_type == DEBUG_STABS)
13961 stabs_generate_asm_func (S_GET_NAME (symbolP),
13962 S_GET_NAME (symbolP));
13965 demand_empty_rest_of_line ();
13968 /* The .frame directive. If the mdebug section is present (IRIX 5 native)
13969 then ecoff.c (ecoff_directive_frame) is used. For embedded targets,
13970 s_mips_frame is used so that we can set the PDR information correctly.
13971 We can't use the ecoff routines because they make reference to the ecoff
13972 symbol table (in the mdebug section). */
13975 s_mips_frame (int ignore ATTRIBUTE_UNUSED)
13978 if (OUTPUT_FLAVOR == bfd_target_elf_flavour && ! ECOFF_DEBUGGING)
13982 if (cur_proc_ptr == (procS *) NULL)
13984 as_warn (_(".frame outside of .ent"));
13985 demand_empty_rest_of_line ();
13989 cur_proc_ptr->frame_reg = tc_get_register (1);
13991 SKIP_WHITESPACE ();
13992 if (*input_line_pointer++ != ','
13993 || get_absolute_expression_and_terminator (&val) != ',')
13995 as_warn (_("Bad .frame directive"));
13996 --input_line_pointer;
13997 demand_empty_rest_of_line ();
14001 cur_proc_ptr->frame_offset = val;
14002 cur_proc_ptr->pc_reg = tc_get_register (0);
14004 demand_empty_rest_of_line ();
14007 #endif /* OBJ_ELF */
14011 /* The .fmask and .mask directives. If the mdebug section is present
14012 (IRIX 5 native) then ecoff.c (ecoff_directive_mask) is used. For
14013 embedded targets, s_mips_mask is used so that we can set the PDR
14014 information correctly. We can't use the ecoff routines because they
14015 make reference to the ecoff symbol table (in the mdebug section). */
14018 s_mips_mask (int reg_type)
14021 if (OUTPUT_FLAVOR == bfd_target_elf_flavour && ! ECOFF_DEBUGGING)
14025 if (cur_proc_ptr == (procS *) NULL)
14027 as_warn (_(".mask/.fmask outside of .ent"));
14028 demand_empty_rest_of_line ();
14032 if (get_absolute_expression_and_terminator (&mask) != ',')
14034 as_warn (_("Bad .mask/.fmask directive"));
14035 --input_line_pointer;
14036 demand_empty_rest_of_line ();
14040 off = get_absolute_expression ();
14042 if (reg_type == 'F')
14044 cur_proc_ptr->fpreg_mask = mask;
14045 cur_proc_ptr->fpreg_offset = off;
14049 cur_proc_ptr->reg_mask = mask;
14050 cur_proc_ptr->reg_offset = off;
14053 demand_empty_rest_of_line ();
14056 #endif /* OBJ_ELF */
14057 s_ignore (reg_type);
14060 /* The .loc directive. */
14070 assert (now_seg == text_section);
14072 lineno = get_number ();
14073 addroff = frag_now_fix ();
14075 symbolP = symbol_new ("", N_SLINE, addroff, frag_now);
14076 S_SET_TYPE (symbolP, N_SLINE);
14077 S_SET_OTHER (symbolP, 0);
14078 S_SET_DESC (symbolP, lineno);
14079 symbolP->sy_segment = now_seg;
14083 /* A table describing all the processors gas knows about. Names are
14084 matched in the order listed.
14086 To ease comparison, please keep this table in the same order as
14087 gcc's mips_cpu_info_table[]. */
14088 static const struct mips_cpu_info mips_cpu_info_table[] =
14090 /* Entries for generic ISAs */
14091 { "mips1", 1, ISA_MIPS1, CPU_R3000 },
14092 { "mips2", 1, ISA_MIPS2, CPU_R6000 },
14093 { "mips3", 1, ISA_MIPS3, CPU_R4000 },
14094 { "mips4", 1, ISA_MIPS4, CPU_R8000 },
14095 { "mips5", 1, ISA_MIPS5, CPU_MIPS5 },
14096 { "mips32", 1, ISA_MIPS32, CPU_MIPS32 },
14097 { "mips32r2", 1, ISA_MIPS32R2, CPU_MIPS32R2 },
14098 { "mips64", 1, ISA_MIPS64, CPU_MIPS64 },
14099 { "mips64r2", 1, ISA_MIPS64R2, CPU_MIPS64R2 },
14102 { "r3000", 0, ISA_MIPS1, CPU_R3000 },
14103 { "r2000", 0, ISA_MIPS1, CPU_R3000 },
14104 { "r3900", 0, ISA_MIPS1, CPU_R3900 },
14107 { "r6000", 0, ISA_MIPS2, CPU_R6000 },
14110 { "r4000", 0, ISA_MIPS3, CPU_R4000 },
14111 { "r4010", 0, ISA_MIPS2, CPU_R4010 },
14112 { "vr4100", 0, ISA_MIPS3, CPU_VR4100 },
14113 { "vr4111", 0, ISA_MIPS3, CPU_R4111 },
14114 { "vr4120", 0, ISA_MIPS3, CPU_VR4120 },
14115 { "vr4130", 0, ISA_MIPS3, CPU_VR4120 },
14116 { "vr4181", 0, ISA_MIPS3, CPU_R4111 },
14117 { "vr4300", 0, ISA_MIPS3, CPU_R4300 },
14118 { "r4400", 0, ISA_MIPS3, CPU_R4400 },
14119 { "r4600", 0, ISA_MIPS3, CPU_R4600 },
14120 { "orion", 0, ISA_MIPS3, CPU_R4600 },
14121 { "r4650", 0, ISA_MIPS3, CPU_R4650 },
14124 { "r8000", 0, ISA_MIPS4, CPU_R8000 },
14125 { "r10000", 0, ISA_MIPS4, CPU_R10000 },
14126 { "r12000", 0, ISA_MIPS4, CPU_R12000 },
14127 { "vr5000", 0, ISA_MIPS4, CPU_R5000 },
14128 { "vr5400", 0, ISA_MIPS4, CPU_VR5400 },
14129 { "vr5500", 0, ISA_MIPS4, CPU_VR5500 },
14130 { "rm5200", 0, ISA_MIPS4, CPU_R5000 },
14131 { "rm5230", 0, ISA_MIPS4, CPU_R5000 },
14132 { "rm5231", 0, ISA_MIPS4, CPU_R5000 },
14133 { "rm5261", 0, ISA_MIPS4, CPU_R5000 },
14134 { "rm5721", 0, ISA_MIPS4, CPU_R5000 },
14135 { "rm7000", 0, ISA_MIPS4, CPU_RM7000 },
14136 { "rm9000", 0, ISA_MIPS4, CPU_RM7000 },
14139 { "4kc", 0, ISA_MIPS32, CPU_MIPS32 },
14140 { "4km", 0, ISA_MIPS32, CPU_MIPS32 },
14141 { "4kp", 0, ISA_MIPS32, CPU_MIPS32 },
14144 { "5kc", 0, ISA_MIPS64, CPU_MIPS64 },
14145 { "20kc", 0, ISA_MIPS64, CPU_MIPS64 },
14147 /* Broadcom SB-1 CPU core */
14148 { "sb1", 0, ISA_MIPS64, CPU_SB1 },
14155 /* Return true if GIVEN is the same as CANONICAL, or if it is CANONICAL
14156 with a final "000" replaced by "k". Ignore case.
14158 Note: this function is shared between GCC and GAS. */
14161 mips_strict_matching_cpu_name_p (const char *canonical, const char *given)
14163 while (*given != 0 && TOLOWER (*given) == TOLOWER (*canonical))
14164 given++, canonical++;
14166 return ((*given == 0 && *canonical == 0)
14167 || (strcmp (canonical, "000") == 0 && strcasecmp (given, "k") == 0));
14171 /* Return true if GIVEN matches CANONICAL, where GIVEN is a user-supplied
14172 CPU name. We've traditionally allowed a lot of variation here.
14174 Note: this function is shared between GCC and GAS. */
14177 mips_matching_cpu_name_p (const char *canonical, const char *given)
14179 /* First see if the name matches exactly, or with a final "000"
14180 turned into "k". */
14181 if (mips_strict_matching_cpu_name_p (canonical, given))
14184 /* If not, try comparing based on numerical designation alone.
14185 See if GIVEN is an unadorned number, or 'r' followed by a number. */
14186 if (TOLOWER (*given) == 'r')
14188 if (!ISDIGIT (*given))
14191 /* Skip over some well-known prefixes in the canonical name,
14192 hoping to find a number there too. */
14193 if (TOLOWER (canonical[0]) == 'v' && TOLOWER (canonical[1]) == 'r')
14195 else if (TOLOWER (canonical[0]) == 'r' && TOLOWER (canonical[1]) == 'm')
14197 else if (TOLOWER (canonical[0]) == 'r')
14200 return mips_strict_matching_cpu_name_p (canonical, given);
14204 /* Parse an option that takes the name of a processor as its argument.
14205 OPTION is the name of the option and CPU_STRING is the argument.
14206 Return the corresponding processor enumeration if the CPU_STRING is
14207 recognized, otherwise report an error and return null.
14209 A similar function exists in GCC. */
14211 static const struct mips_cpu_info *
14212 mips_parse_cpu (const char *option, const char *cpu_string)
14214 const struct mips_cpu_info *p;
14216 /* 'from-abi' selects the most compatible architecture for the given
14217 ABI: MIPS I for 32-bit ABIs and MIPS III for 64-bit ABIs. For the
14218 EABIs, we have to decide whether we're using the 32-bit or 64-bit
14219 version. Look first at the -mgp options, if given, otherwise base
14220 the choice on MIPS_DEFAULT_64BIT.
14222 Treat NO_ABI like the EABIs. One reason to do this is that the
14223 plain 'mips' and 'mips64' configs have 'from-abi' as their default
14224 architecture. This code picks MIPS I for 'mips' and MIPS III for
14225 'mips64', just as we did in the days before 'from-abi'. */
14226 if (strcasecmp (cpu_string, "from-abi") == 0)
14228 if (ABI_NEEDS_32BIT_REGS (mips_abi))
14229 return mips_cpu_info_from_isa (ISA_MIPS1);
14231 if (ABI_NEEDS_64BIT_REGS (mips_abi))
14232 return mips_cpu_info_from_isa (ISA_MIPS3);
14234 if (file_mips_gp32 >= 0)
14235 return mips_cpu_info_from_isa (file_mips_gp32 ? ISA_MIPS1 : ISA_MIPS3);
14237 return mips_cpu_info_from_isa (MIPS_DEFAULT_64BIT
14242 /* 'default' has traditionally been a no-op. Probably not very useful. */
14243 if (strcasecmp (cpu_string, "default") == 0)
14246 for (p = mips_cpu_info_table; p->name != 0; p++)
14247 if (mips_matching_cpu_name_p (p->name, cpu_string))
14250 as_bad ("Bad value (%s) for %s", cpu_string, option);
14254 /* Return the canonical processor information for ISA (a member of the
14255 ISA_MIPS* enumeration). */
14257 static const struct mips_cpu_info *
14258 mips_cpu_info_from_isa (int isa)
14262 for (i = 0; mips_cpu_info_table[i].name != NULL; i++)
14263 if (mips_cpu_info_table[i].is_isa
14264 && isa == mips_cpu_info_table[i].isa)
14265 return (&mips_cpu_info_table[i]);
14270 static const struct mips_cpu_info *
14271 mips_cpu_info_from_arch (int arch)
14275 for (i = 0; mips_cpu_info_table[i].name != NULL; i++)
14276 if (arch == mips_cpu_info_table[i].cpu)
14277 return (&mips_cpu_info_table[i]);
14283 show (FILE *stream, const char *string, int *col_p, int *first_p)
14287 fprintf (stream, "%24s", "");
14292 fprintf (stream, ", ");
14296 if (*col_p + strlen (string) > 72)
14298 fprintf (stream, "\n%24s", "");
14302 fprintf (stream, "%s", string);
14303 *col_p += strlen (string);
14309 md_show_usage (FILE *stream)
14314 fprintf (stream, _("\
14316 -membedded-pic generate embedded position independent code\n\
14317 -EB generate big endian output\n\
14318 -EL generate little endian output\n\
14319 -g, -g2 do not remove unneeded NOPs or swap branches\n\
14320 -G NUM allow referencing objects up to NUM bytes\n\
14321 implicitly with the gp register [default 8]\n"));
14322 fprintf (stream, _("\
14323 -mips1 generate MIPS ISA I instructions\n\
14324 -mips2 generate MIPS ISA II instructions\n\
14325 -mips3 generate MIPS ISA III instructions\n\
14326 -mips4 generate MIPS ISA IV instructions\n\
14327 -mips5 generate MIPS ISA V instructions\n\
14328 -mips32 generate MIPS32 ISA instructions\n\
14329 -mips32r2 generate MIPS32 release 2 ISA instructions\n\
14330 -mips64 generate MIPS64 ISA instructions\n\
14331 -mips64r2 generate MIPS64 release 2 ISA instructions\n\
14332 -march=CPU/-mtune=CPU generate code/schedule for CPU, where CPU is one of:\n"));
14336 for (i = 0; mips_cpu_info_table[i].name != NULL; i++)
14337 show (stream, mips_cpu_info_table[i].name, &column, &first);
14338 show (stream, "from-abi", &column, &first);
14339 fputc ('\n', stream);
14341 fprintf (stream, _("\
14342 -mCPU equivalent to -march=CPU -mtune=CPU. Deprecated.\n\
14343 -no-mCPU don't generate code specific to CPU.\n\
14344 For -mCPU and -no-mCPU, CPU must be one of:\n"));
14348 show (stream, "3900", &column, &first);
14349 show (stream, "4010", &column, &first);
14350 show (stream, "4100", &column, &first);
14351 show (stream, "4650", &column, &first);
14352 fputc ('\n', stream);
14354 fprintf (stream, _("\
14355 -mips16 generate mips16 instructions\n\
14356 -no-mips16 do not generate mips16 instructions\n"));
14357 fprintf (stream, _("\
14358 -mgp32 use 32-bit GPRs, regardless of the chosen ISA\n\
14359 -mfp32 use 32-bit FPRs, regardless of the chosen ISA\n\
14360 -O0 remove unneeded NOPs, do not swap branches\n\
14361 -O remove unneeded NOPs and swap branches\n\
14362 --[no-]construct-floats [dis]allow floating point values to be constructed\n\
14363 --trap, --no-break trap exception on div by 0 and mult overflow\n\
14364 --break, --no-trap break exception on div by 0 and mult overflow\n"));
14366 fprintf (stream, _("\
14367 -KPIC, -call_shared generate SVR4 position independent code\n\
14368 -non_shared do not generate position independent code\n\
14369 -xgot assume a 32 bit GOT\n\
14370 -mpdr, -mno-pdr enable/disable creation of .pdr sections\n\
14371 -mabi=ABI create ABI conformant object file for:\n"));
14375 show (stream, "32", &column, &first);
14376 show (stream, "o64", &column, &first);
14377 show (stream, "n32", &column, &first);
14378 show (stream, "64", &column, &first);
14379 show (stream, "eabi", &column, &first);
14381 fputc ('\n', stream);
14383 fprintf (stream, _("\
14384 -32 create o32 ABI object file (default)\n\
14385 -n32 create n32 ABI object file\n\
14386 -64 create 64 ABI object file\n"));
14391 mips_dwarf2_format (void)
14393 if (mips_abi == N64_ABI)
14396 return dwarf2_format_64bit_irix;
14398 return dwarf2_format_64bit;
14402 return dwarf2_format_32bit;