1 /* tc-mips.c -- assemble code for a MIPS chip.
2 Copyright 1993, 1994, 1995, 1996, 1997, 1998, 1999, 2000, 2001, 2002
3 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"
38 #include "opcode/mips.h"
40 #include "dwarf2dbg.h"
43 #define DBG(x) printf x
49 /* Clean up namespace so we can include obj-elf.h too. */
50 static int mips_output_flavor PARAMS ((void));
51 static int mips_output_flavor () { return OUTPUT_FLAVOR; }
52 #undef OBJ_PROCESS_STAB
59 #undef obj_frob_file_after_relocs
60 #undef obj_frob_symbol
62 #undef obj_sec_sym_ok_for_reloc
63 #undef OBJ_COPY_SYMBOL_ATTRIBUTES
66 /* Fix any of them that we actually care about. */
68 #define OUTPUT_FLAVOR mips_output_flavor()
75 #ifndef ECOFF_DEBUGGING
76 #define NO_ECOFF_DEBUGGING
77 #define ECOFF_DEBUGGING 0
80 int mips_flag_mdebug = -1;
84 #if defined (OBJ_ELF) || defined (OBJ_MAYBE_ELF)
85 static char *mips_regmask_frag;
91 #define PIC_CALL_REG 25
99 #define ILLEGAL_REG (32)
101 /* Allow override of standard little-endian ECOFF format. */
103 #ifndef ECOFF_LITTLE_FORMAT
104 #define ECOFF_LITTLE_FORMAT "ecoff-littlemips"
107 extern int target_big_endian;
109 /* The name of the readonly data section. */
110 #define RDATA_SECTION_NAME (OUTPUT_FLAVOR == bfd_target_aout_flavour \
112 : OUTPUT_FLAVOR == bfd_target_ecoff_flavour \
114 : OUTPUT_FLAVOR == bfd_target_coff_flavour \
116 : OUTPUT_FLAVOR == bfd_target_elf_flavour \
120 /* The ABI to use. */
131 /* MIPS ABI we are using for this output file. */
132 static enum mips_abi_level mips_abi = NO_ABI;
134 /* This is the set of options which may be modified by the .set
135 pseudo-op. We use a struct so that .set push and .set pop are more
138 struct mips_set_options
140 /* MIPS ISA (Instruction Set Architecture) level. This is set to -1
141 if it has not been initialized. Changed by `.set mipsN', and the
142 -mipsN command line option, and the default CPU. */
144 /* Enabled Application Specific Extensions (ASEs). These are set to -1
145 if they have not been initialized. Changed by `.set <asename>', by
146 command line options, and based on the default architecture. */
149 /* Whether we are assembling for the mips16 processor. 0 if we are
150 not, 1 if we are, and -1 if the value has not been initialized.
151 Changed by `.set mips16' and `.set nomips16', and the -mips16 and
152 -nomips16 command line options, and the default CPU. */
154 /* Non-zero if we should not reorder instructions. Changed by `.set
155 reorder' and `.set noreorder'. */
157 /* Non-zero if we should not permit the $at ($1) register to be used
158 in instructions. Changed by `.set at' and `.set noat'. */
160 /* Non-zero if we should warn when a macro instruction expands into
161 more than one machine instruction. Changed by `.set nomacro' and
163 int warn_about_macros;
164 /* Non-zero if we should not move instructions. Changed by `.set
165 move', `.set volatile', `.set nomove', and `.set novolatile'. */
167 /* Non-zero if we should not optimize branches by moving the target
168 of the branch into the delay slot. Actually, we don't perform
169 this optimization anyhow. Changed by `.set bopt' and `.set
172 /* Non-zero if we should not autoextend mips16 instructions.
173 Changed by `.set autoextend' and `.set noautoextend'. */
175 /* Restrict general purpose registers and floating point registers
176 to 32 bit. This is initially determined when -mgp32 or -mfp32
177 is passed but can changed if the assembler code uses .set mipsN. */
182 /* True if -mgp32 was passed. */
183 static int file_mips_gp32 = -1;
185 /* True if -mfp32 was passed. */
186 static int file_mips_fp32 = -1;
188 /* This is the struct we use to hold the current set of options. Note
189 that we must set the isa field to ISA_UNKNOWN and the ASE fields to
190 -1 to indicate that they have not been initialized. */
192 static struct mips_set_options mips_opts =
194 ISA_UNKNOWN, -1, -1, -1, 0, 0, 0, 0, 0, 0, 0, 0
197 /* These variables are filled in with the masks of registers used.
198 The object format code reads them and puts them in the appropriate
200 unsigned long mips_gprmask;
201 unsigned long mips_cprmask[4];
203 /* MIPS ISA we are using for this output file. */
204 static int file_mips_isa = ISA_UNKNOWN;
206 /* True if -mips16 was passed or implied by arguments passed on the
207 command line (e.g., by -march). */
208 static int file_ase_mips16;
210 /* True if -mips3d was passed or implied by arguments passed on the
211 command line (e.g., by -march). */
212 static int file_ase_mips3d;
214 /* True if -mdmx was passed or implied by arguments passed on the
215 command line (e.g., by -march). */
216 static int file_ase_mdmx;
218 /* The argument of the -march= flag. The architecture we are assembling. */
219 static int mips_arch = CPU_UNKNOWN;
220 static const char *mips_arch_string;
221 static const struct mips_cpu_info *mips_arch_info;
223 /* The argument of the -mtune= flag. The architecture for which we
225 static int mips_tune = CPU_UNKNOWN;
226 static const char *mips_tune_string;
227 static const struct mips_cpu_info *mips_tune_info;
229 /* True when generating 32-bit code for a 64-bit processor. */
230 static int mips_32bitmode = 0;
232 /* Some ISA's have delay slots for instructions which read or write
233 from a coprocessor (eg. mips1-mips3); some don't (eg mips4).
234 Return true if instructions marked INSN_LOAD_COPROC_DELAY,
235 INSN_COPROC_MOVE_DELAY, or INSN_WRITE_COND_CODE actually have a
236 delay slot in this ISA. The uses of this macro assume that any
237 ISA that has delay slots for one of these, has them for all. They
238 also assume that ISAs which don't have delays for these insns, don't
239 have delays for the INSN_LOAD_MEMORY_DELAY instructions either. */
240 #define ISA_HAS_COPROC_DELAYS(ISA) ( \
242 || (ISA) == ISA_MIPS2 \
243 || (ISA) == ISA_MIPS3 \
246 /* True if the given ABI requires 32-bit registers. */
247 #define ABI_NEEDS_32BIT_REGS(ABI) ((ABI) == O32_ABI)
249 /* Likewise 64-bit registers. */
250 #define ABI_NEEDS_64BIT_REGS(ABI) \
252 || (ABI) == N64_ABI \
255 /* Return true if ISA supports 64 bit gp register instructions. */
256 #define ISA_HAS_64BIT_REGS(ISA) ( \
258 || (ISA) == ISA_MIPS4 \
259 || (ISA) == ISA_MIPS5 \
260 || (ISA) == ISA_MIPS64 \
263 #define HAVE_32BIT_GPRS \
264 (mips_opts.gp32 || ! ISA_HAS_64BIT_REGS (mips_opts.isa))
266 #define HAVE_32BIT_FPRS \
267 (mips_opts.fp32 || ! ISA_HAS_64BIT_REGS (mips_opts.isa))
269 #define HAVE_64BIT_GPRS (! HAVE_32BIT_GPRS)
270 #define HAVE_64BIT_FPRS (! HAVE_32BIT_FPRS)
272 #define HAVE_NEWABI (mips_abi == N32_ABI || mips_abi == N64_ABI)
274 #define HAVE_64BIT_OBJECTS (mips_abi == N64_ABI)
276 /* We can only have 64bit addresses if the object file format
278 #define HAVE_32BIT_ADDRESSES \
280 || ((bfd_arch_bits_per_address (stdoutput) == 32 \
281 || ! HAVE_64BIT_OBJECTS) \
282 && mips_pic != EMBEDDED_PIC))
284 #define HAVE_64BIT_ADDRESSES (! HAVE_32BIT_ADDRESSES)
286 /* Return true if the given CPU supports the MIPS16 ASE. */
287 #define CPU_HAS_MIPS16(cpu) \
288 (strncmp (TARGET_CPU, "mips16", sizeof ("mips16") - 1) == 0 \
289 || strncmp (TARGET_CANONICAL, "mips-lsi-elf", sizeof ("mips-lsi-elf") - 1) == 0)
291 /* Return true if the given CPU supports the MIPS3D ASE. */
292 #define CPU_HAS_MIPS3D(cpu) ((cpu) == CPU_SB1 \
295 /* Return true if the given CPU supports the MDMX ASE. */
296 #define CPU_HAS_MDMX(cpu) (false \
299 /* True if CPU has a dror instruction. */
300 #define CPU_HAS_DROR(CPU) ((CPU) == CPU_VR5400 || (CPU) == CPU_VR5500)
302 /* True if CPU has a ror instruction. */
303 #define CPU_HAS_ROR(CPU) CPU_HAS_DROR (CPU)
305 /* Whether the processor uses hardware interlocks to protect
306 reads from the HI and LO registers, and thus does not
307 require nops to be inserted. */
309 #define hilo_interlocks (mips_arch == CPU_R4010 \
310 || mips_arch == CPU_VR5500 \
311 || mips_arch == CPU_SB1 \
314 /* Whether the processor uses hardware interlocks to protect reads
315 from the GPRs, and thus does not require nops to be inserted. */
316 #define gpr_interlocks \
317 (mips_opts.isa != ISA_MIPS1 \
318 || mips_arch == CPU_VR5400 \
319 || mips_arch == CPU_VR5500 \
320 || mips_arch == CPU_R3900)
322 /* As with other "interlocks" this is used by hardware that has FP
323 (co-processor) interlocks. */
324 /* Itbl support may require additional care here. */
325 #define cop_interlocks (mips_arch == CPU_R4300 \
326 || mips_arch == CPU_VR5400 \
327 || mips_arch == CPU_VR5500 \
328 || mips_arch == CPU_SB1 \
331 /* Is this a mfhi or mflo instruction? */
332 #define MF_HILO_INSN(PINFO) \
333 ((PINFO & INSN_READ_HI) || (PINFO & INSN_READ_LO))
335 /* MIPS PIC level. */
337 enum mips_pic_level mips_pic;
339 /* Warn about all NOPS that the assembler generates. */
340 static int warn_nops = 0;
342 /* 1 if we should generate 32 bit offsets from the $gp register in
343 SVR4_PIC mode. Currently has no meaning in other modes. */
344 static int mips_big_got = 0;
346 /* 1 if trap instructions should used for overflow rather than break
348 static int mips_trap = 0;
350 /* 1 if double width floating point constants should not be constructed
351 by assembling two single width halves into two single width floating
352 point registers which just happen to alias the double width destination
353 register. On some architectures this aliasing can be disabled by a bit
354 in the status register, and the setting of this bit cannot be determined
355 automatically at assemble time. */
356 static int mips_disable_float_construction;
358 /* Non-zero if any .set noreorder directives were used. */
360 static int mips_any_noreorder;
362 /* Non-zero if nops should be inserted when the register referenced in
363 an mfhi/mflo instruction is read in the next two instructions. */
364 static int mips_7000_hilo_fix;
366 /* The size of the small data section. */
367 static unsigned int g_switch_value = 8;
368 /* Whether the -G option was used. */
369 static int g_switch_seen = 0;
374 /* If we can determine in advance that GP optimization won't be
375 possible, we can skip the relaxation stuff that tries to produce
376 GP-relative references. This makes delay slot optimization work
379 This function can only provide a guess, but it seems to work for
380 gcc output. It needs to guess right for gcc, otherwise gcc
381 will put what it thinks is a GP-relative instruction in a branch
384 I don't know if a fix is needed for the SVR4_PIC mode. I've only
385 fixed it for the non-PIC mode. KR 95/04/07 */
386 static int nopic_need_relax PARAMS ((symbolS *, int));
388 /* handle of the OPCODE hash table */
389 static struct hash_control *op_hash = NULL;
391 /* The opcode hash table we use for the mips16. */
392 static struct hash_control *mips16_op_hash = NULL;
394 /* This array holds the chars that always start a comment. If the
395 pre-processor is disabled, these aren't very useful */
396 const char comment_chars[] = "#";
398 /* This array holds the chars that only start a comment at the beginning of
399 a line. If the line seems to have the form '# 123 filename'
400 .line and .file directives will appear in the pre-processed output */
401 /* Note that input_file.c hand checks for '#' at the beginning of the
402 first line of the input file. This is because the compiler outputs
403 #NO_APP at the beginning of its output. */
404 /* Also note that C style comments are always supported. */
405 const char line_comment_chars[] = "#";
407 /* This array holds machine specific line separator characters. */
408 const char line_separator_chars[] = ";";
410 /* Chars that can be used to separate mant from exp in floating point nums */
411 const char EXP_CHARS[] = "eE";
413 /* Chars that mean this number is a floating point constant */
416 const char FLT_CHARS[] = "rRsSfFdDxXpP";
418 /* Also be aware that MAXIMUM_NUMBER_OF_CHARS_FOR_FLOAT may have to be
419 changed in read.c . Ideally it shouldn't have to know about it at all,
420 but nothing is ideal around here.
423 static char *insn_error;
425 static int auto_align = 1;
427 /* When outputting SVR4 PIC code, the assembler needs to know the
428 offset in the stack frame from which to restore the $gp register.
429 This is set by the .cprestore pseudo-op, and saved in this
431 static offsetT mips_cprestore_offset = -1;
433 /* Similiar for NewABI PIC code, where $gp is callee-saved. NewABI has some
434 more optimizations, it can use a register value instead of a memory-saved
435 offset and even an other register than $gp as global pointer. */
436 static offsetT mips_cpreturn_offset = -1;
437 static int mips_cpreturn_register = -1;
438 static int mips_gp_register = GP;
439 static int mips_gprel_offset = 0;
441 /* Whether mips_cprestore_offset has been set in the current function
442 (or whether it has already been warned about, if not). */
443 static int mips_cprestore_valid = 0;
445 /* This is the register which holds the stack frame, as set by the
446 .frame pseudo-op. This is needed to implement .cprestore. */
447 static int mips_frame_reg = SP;
449 /* Whether mips_frame_reg has been set in the current function
450 (or whether it has already been warned about, if not). */
451 static int mips_frame_reg_valid = 0;
453 /* To output NOP instructions correctly, we need to keep information
454 about the previous two instructions. */
456 /* Whether we are optimizing. The default value of 2 means to remove
457 unneeded NOPs and swap branch instructions when possible. A value
458 of 1 means to not swap branches. A value of 0 means to always
460 static int mips_optimize = 2;
462 /* Debugging level. -g sets this to 2. -gN sets this to N. -g0 is
463 equivalent to seeing no -g option at all. */
464 static int mips_debug = 0;
466 /* The previous instruction. */
467 static struct mips_cl_insn prev_insn;
469 /* The instruction before prev_insn. */
470 static struct mips_cl_insn prev_prev_insn;
472 /* If we don't want information for prev_insn or prev_prev_insn, we
473 point the insn_mo field at this dummy integer. */
474 static const struct mips_opcode dummy_opcode = { NULL, NULL, 0, 0, 0, 0 };
476 /* Non-zero if prev_insn is valid. */
477 static int prev_insn_valid;
479 /* The frag for the previous instruction. */
480 static struct frag *prev_insn_frag;
482 /* The offset into prev_insn_frag for the previous instruction. */
483 static long prev_insn_where;
485 /* The reloc type for the previous instruction, if any. */
486 static bfd_reloc_code_real_type prev_insn_reloc_type[3];
488 /* The reloc for the previous instruction, if any. */
489 static fixS *prev_insn_fixp[3];
491 /* Non-zero if the previous instruction was in a delay slot. */
492 static int prev_insn_is_delay_slot;
494 /* Non-zero if the previous instruction was in a .set noreorder. */
495 static int prev_insn_unreordered;
497 /* Non-zero if the previous instruction uses an extend opcode (if
499 static int prev_insn_extended;
501 /* Non-zero if the previous previous instruction was in a .set
503 static int prev_prev_insn_unreordered;
505 /* If this is set, it points to a frag holding nop instructions which
506 were inserted before the start of a noreorder section. If those
507 nops turn out to be unnecessary, the size of the frag can be
509 static fragS *prev_nop_frag;
511 /* The number of nop instructions we created in prev_nop_frag. */
512 static int prev_nop_frag_holds;
514 /* The number of nop instructions that we know we need in
516 static int prev_nop_frag_required;
518 /* The number of instructions we've seen since prev_nop_frag. */
519 static int prev_nop_frag_since;
521 /* For ECOFF and ELF, relocations against symbols are done in two
522 parts, with a HI relocation and a LO relocation. Each relocation
523 has only 16 bits of space to store an addend. This means that in
524 order for the linker to handle carries correctly, it must be able
525 to locate both the HI and the LO relocation. This means that the
526 relocations must appear in order in the relocation table.
528 In order to implement this, we keep track of each unmatched HI
529 relocation. We then sort them so that they immediately precede the
530 corresponding LO relocation. */
535 struct mips_hi_fixup *next;
538 /* The section this fixup is in. */
542 /* The list of unmatched HI relocs. */
544 static struct mips_hi_fixup *mips_hi_fixup_list;
546 /* Map normal MIPS register numbers to mips16 register numbers. */
548 #define X ILLEGAL_REG
549 static const int mips32_to_16_reg_map[] =
551 X, X, 2, 3, 4, 5, 6, 7,
552 X, X, X, X, X, X, X, X,
553 0, 1, X, X, X, X, X, X,
554 X, X, X, X, X, X, X, X
558 /* Map mips16 register numbers to normal MIPS register numbers. */
560 static const unsigned int mips16_to_32_reg_map[] =
562 16, 17, 2, 3, 4, 5, 6, 7
565 static int mips_fix_4122_bugs;
567 /* We don't relax branches by default, since this causes us to expand
568 `la .l2 - .l1' if there's a branch between .l1 and .l2, because we
569 fail to compute the offset before expanding the macro to the most
570 efficient expansion. */
572 static int mips_relax_branch;
574 /* Since the MIPS does not have multiple forms of PC relative
575 instructions, we do not have to do relaxing as is done on other
576 platforms. However, we do have to handle GP relative addressing
577 correctly, which turns out to be a similar problem.
579 Every macro that refers to a symbol can occur in (at least) two
580 forms, one with GP relative addressing and one without. For
581 example, loading a global variable into a register generally uses
582 a macro instruction like this:
584 If i can be addressed off the GP register (this is true if it is in
585 the .sbss or .sdata section, or if it is known to be smaller than
586 the -G argument) this will generate the following instruction:
588 This instruction will use a GPREL reloc. If i can not be addressed
589 off the GP register, the following instruction sequence will be used:
592 In this case the first instruction will have a HI16 reloc, and the
593 second reloc will have a LO16 reloc. Both relocs will be against
596 The issue here is that we may not know whether i is GP addressable
597 until after we see the instruction that uses it. Therefore, we
598 want to be able to choose the final instruction sequence only at
599 the end of the assembly. This is similar to the way other
600 platforms choose the size of a PC relative instruction only at the
603 When generating position independent code we do not use GP
604 addressing in quite the same way, but the issue still arises as
605 external symbols and local symbols must be handled differently.
607 We handle these issues by actually generating both possible
608 instruction sequences. The longer one is put in a frag_var with
609 type rs_machine_dependent. We encode what to do with the frag in
610 the subtype field. We encode (1) the number of existing bytes to
611 replace, (2) the number of new bytes to use, (3) the offset from
612 the start of the existing bytes to the first reloc we must generate
613 (that is, the offset is applied from the start of the existing
614 bytes after they are replaced by the new bytes, if any), (4) the
615 offset from the start of the existing bytes to the second reloc,
616 (5) whether a third reloc is needed (the third reloc is always four
617 bytes after the second reloc), and (6) whether to warn if this
618 variant is used (this is sometimes needed if .set nomacro or .set
619 noat is in effect). All these numbers are reasonably small.
621 Generating two instruction sequences must be handled carefully to
622 ensure that delay slots are handled correctly. Fortunately, there
623 are a limited number of cases. When the second instruction
624 sequence is generated, append_insn is directed to maintain the
625 existing delay slot information, so it continues to apply to any
626 code after the second instruction sequence. This means that the
627 second instruction sequence must not impose any requirements not
628 required by the first instruction sequence.
630 These variant frags are then handled in functions called by the
631 machine independent code. md_estimate_size_before_relax returns
632 the final size of the frag. md_convert_frag sets up the final form
633 of the frag. tc_gen_reloc adjust the first reloc and adds a second
635 #define RELAX_ENCODE(old, new, reloc1, reloc2, reloc3, warn) \
639 | (((reloc1) + 64) << 9) \
640 | (((reloc2) + 64) << 2) \
641 | ((reloc3) ? (1 << 1) : 0) \
643 #define RELAX_OLD(i) (((i) >> 23) & 0x7f)
644 #define RELAX_NEW(i) (((i) >> 16) & 0x7f)
645 #define RELAX_RELOC1(i) ((valueT) (((i) >> 9) & 0x7f) - 64)
646 #define RELAX_RELOC2(i) ((valueT) (((i) >> 2) & 0x7f) - 64)
647 #define RELAX_RELOC3(i) (((i) >> 1) & 1)
648 #define RELAX_WARN(i) ((i) & 1)
650 /* Branch without likely bit. If label is out of range, we turn:
652 beq reg1, reg2, label
662 with the following opcode replacements:
669 bltzal <-> bgezal (with jal label instead of j label)
671 Even though keeping the delay slot instruction in the delay slot of
672 the branch would be more efficient, it would be very tricky to do
673 correctly, because we'd have to introduce a variable frag *after*
674 the delay slot instruction, and expand that instead. Let's do it
675 the easy way for now, even if the branch-not-taken case now costs
676 one additional instruction. Out-of-range branches are not supposed
677 to be common, anyway.
679 Branch likely. If label is out of range, we turn:
681 beql reg1, reg2, label
682 delay slot (annulled if branch not taken)
691 delay slot (executed only if branch taken)
694 It would be possible to generate a shorter sequence by losing the
695 likely bit, generating something like:
700 delay slot (executed only if branch taken)
712 bltzall -> bgezal (with jal label instead of j label)
713 bgezall -> bltzal (ditto)
716 but it's not clear that it would actually improve performance. */
717 #define RELAX_BRANCH_ENCODE(reloc_s2, uncond, likely, link, toofar) \
720 | ((toofar) ? 1 : 0) \
722 | ((likely) ? 4 : 0) \
723 | ((uncond) ? 8 : 0) \
724 | ((reloc_s2) ? 16 : 0)))
725 #define RELAX_BRANCH_P(i) (((i) & 0xf0000000) == 0xc0000000)
726 #define RELAX_BRANCH_RELOC_S2(i) (((i) & 16) != 0)
727 #define RELAX_BRANCH_UNCOND(i) (((i) & 8) != 0)
728 #define RELAX_BRANCH_LIKELY(i) (((i) & 4) != 0)
729 #define RELAX_BRANCH_LINK(i) (((i) & 2) != 0)
730 #define RELAX_BRANCH_TOOFAR(i) (((i) & 1))
732 /* For mips16 code, we use an entirely different form of relaxation.
733 mips16 supports two versions of most instructions which take
734 immediate values: a small one which takes some small value, and a
735 larger one which takes a 16 bit value. Since branches also follow
736 this pattern, relaxing these values is required.
738 We can assemble both mips16 and normal MIPS code in a single
739 object. Therefore, we need to support this type of relaxation at
740 the same time that we support the relaxation described above. We
741 use the high bit of the subtype field to distinguish these cases.
743 The information we store for this type of relaxation is the
744 argument code found in the opcode file for this relocation, whether
745 the user explicitly requested a small or extended form, and whether
746 the relocation is in a jump or jal delay slot. That tells us the
747 size of the value, and how it should be stored. We also store
748 whether the fragment is considered to be extended or not. We also
749 store whether this is known to be a branch to a different section,
750 whether we have tried to relax this frag yet, and whether we have
751 ever extended a PC relative fragment because of a shift count. */
752 #define RELAX_MIPS16_ENCODE(type, small, ext, dslot, jal_dslot) \
755 | ((small) ? 0x100 : 0) \
756 | ((ext) ? 0x200 : 0) \
757 | ((dslot) ? 0x400 : 0) \
758 | ((jal_dslot) ? 0x800 : 0))
759 #define RELAX_MIPS16_P(i) (((i) & 0xc0000000) == 0x80000000)
760 #define RELAX_MIPS16_TYPE(i) ((i) & 0xff)
761 #define RELAX_MIPS16_USER_SMALL(i) (((i) & 0x100) != 0)
762 #define RELAX_MIPS16_USER_EXT(i) (((i) & 0x200) != 0)
763 #define RELAX_MIPS16_DSLOT(i) (((i) & 0x400) != 0)
764 #define RELAX_MIPS16_JAL_DSLOT(i) (((i) & 0x800) != 0)
765 #define RELAX_MIPS16_EXTENDED(i) (((i) & 0x1000) != 0)
766 #define RELAX_MIPS16_MARK_EXTENDED(i) ((i) | 0x1000)
767 #define RELAX_MIPS16_CLEAR_EXTENDED(i) ((i) &~ 0x1000)
768 #define RELAX_MIPS16_LONG_BRANCH(i) (((i) & 0x2000) != 0)
769 #define RELAX_MIPS16_MARK_LONG_BRANCH(i) ((i) | 0x2000)
770 #define RELAX_MIPS16_CLEAR_LONG_BRANCH(i) ((i) &~ 0x2000)
772 /* Is the given value a sign-extended 32-bit value? */
773 #define IS_SEXT_32BIT_NUM(x) \
774 (((x) &~ (offsetT) 0x7fffffff) == 0 \
775 || (((x) &~ (offsetT) 0x7fffffff) == ~ (offsetT) 0x7fffffff))
777 /* Is the given value a sign-extended 16-bit value? */
778 #define IS_SEXT_16BIT_NUM(x) \
779 (((x) &~ (offsetT) 0x7fff) == 0 \
780 || (((x) &~ (offsetT) 0x7fff) == ~ (offsetT) 0x7fff))
783 /* Prototypes for static functions. */
786 #define internalError() \
787 as_fatal (_("internal Error, line %d, %s"), __LINE__, __FILE__)
789 #define internalError() as_fatal (_("MIPS internal Error"));
792 enum mips_regclass { MIPS_GR_REG, MIPS_FP_REG, MIPS16_REG };
794 static int insn_uses_reg PARAMS ((struct mips_cl_insn *ip,
795 unsigned int reg, enum mips_regclass class));
796 static int reg_needs_delay PARAMS ((unsigned int));
797 static void mips16_mark_labels PARAMS ((void));
798 static void append_insn PARAMS ((char *place,
799 struct mips_cl_insn * ip,
801 bfd_reloc_code_real_type *r,
803 static void mips_no_prev_insn PARAMS ((int));
804 static void mips_emit_delays PARAMS ((boolean));
806 static void macro_build PARAMS ((char *place, int *counter, expressionS * ep,
807 const char *name, const char *fmt,
810 static void macro_build ();
812 static void mips16_macro_build PARAMS ((char *, int *, expressionS *,
813 const char *, const char *,
815 static void macro_build_jalr PARAMS ((int, expressionS *));
816 static void macro_build_lui PARAMS ((char *place, int *counter,
817 expressionS * ep, int regnum));
818 static void macro_build_ldst_constoffset PARAMS ((char *place, int *counter,
819 expressionS * ep, const char *op,
820 int valreg, int breg));
821 static void set_at PARAMS ((int *counter, int reg, int unsignedp));
822 static void check_absolute_expr PARAMS ((struct mips_cl_insn * ip,
824 static void load_register PARAMS ((int *, int, expressionS *, int));
825 static void load_address PARAMS ((int *, int, expressionS *, int *));
826 static void move_register PARAMS ((int *, int, int));
827 static void macro PARAMS ((struct mips_cl_insn * ip));
828 static void mips16_macro PARAMS ((struct mips_cl_insn * ip));
829 #ifdef LOSING_COMPILER
830 static void macro2 PARAMS ((struct mips_cl_insn * ip));
832 static void mips_ip PARAMS ((char *str, struct mips_cl_insn * ip));
833 static void mips16_ip PARAMS ((char *str, struct mips_cl_insn * ip));
834 static void mips16_immed PARAMS ((char *, unsigned int, int, offsetT, boolean,
835 boolean, boolean, unsigned long *,
836 boolean *, unsigned short *));
837 static int my_getPercentOp PARAMS ((char **, unsigned int *, int *));
838 static int my_getSmallParser PARAMS ((char **, unsigned int *, int *));
839 static int my_getSmallExpression PARAMS ((expressionS *, char *));
840 static void my_getExpression PARAMS ((expressionS *, char *));
842 static int support_64bit_objects PARAMS((void));
844 static void mips_set_option_string PARAMS ((const char **, const char *));
845 static symbolS *get_symbol PARAMS ((void));
846 static void mips_align PARAMS ((int to, int fill, symbolS *label));
847 static void s_align PARAMS ((int));
848 static void s_change_sec PARAMS ((int));
849 static void s_change_section PARAMS ((int));
850 static void s_cons PARAMS ((int));
851 static void s_float_cons PARAMS ((int));
852 static void s_mips_globl PARAMS ((int));
853 static void s_option PARAMS ((int));
854 static void s_mipsset PARAMS ((int));
855 static void s_abicalls PARAMS ((int));
856 static void s_cpload PARAMS ((int));
857 static void s_cpsetup PARAMS ((int));
858 static void s_cplocal PARAMS ((int));
859 static void s_cprestore PARAMS ((int));
860 static void s_cpreturn PARAMS ((int));
861 static void s_gpvalue PARAMS ((int));
862 static void s_gpword PARAMS ((int));
863 static void s_gpdword PARAMS ((int));
864 static void s_cpadd PARAMS ((int));
865 static void s_insn PARAMS ((int));
866 static void md_obj_begin PARAMS ((void));
867 static void md_obj_end PARAMS ((void));
868 static long get_number PARAMS ((void));
869 static void s_mips_ent PARAMS ((int));
870 static void s_mips_end PARAMS ((int));
871 static void s_mips_frame PARAMS ((int));
872 static void s_mips_mask PARAMS ((int));
873 static void s_mips_stab PARAMS ((int));
874 static void s_mips_weakext PARAMS ((int));
875 static void s_mips_file PARAMS ((int));
876 static void s_mips_loc PARAMS ((int));
877 static int mips16_extended_frag PARAMS ((fragS *, asection *, long));
878 static int relaxed_branch_length (fragS *, asection *, int);
879 static int validate_mips_insn PARAMS ((const struct mips_opcode *));
880 static void show PARAMS ((FILE *, const char *, int *, int *));
882 static int mips_need_elf_addend_fixup PARAMS ((fixS *));
885 /* Return values of my_getSmallExpression(). */
892 /* Direct relocation creation by %percent_op(). */
911 /* Table and functions used to map between CPU/ISA names, and
912 ISA levels, and CPU numbers. */
916 const char *name; /* CPU or ISA name. */
917 int is_isa; /* Is this an ISA? (If 0, a CPU.) */
918 int isa; /* ISA level. */
919 int cpu; /* CPU number (default CPU if ISA). */
922 static void mips_set_architecture PARAMS ((const struct mips_cpu_info *));
923 static void mips_set_tune PARAMS ((const struct mips_cpu_info *));
924 static boolean mips_strict_matching_cpu_name_p PARAMS ((const char *,
926 static boolean mips_matching_cpu_name_p PARAMS ((const char *, const char *));
927 static const struct mips_cpu_info *mips_parse_cpu PARAMS ((const char *,
929 static const struct mips_cpu_info *mips_cpu_info_from_isa PARAMS ((int));
933 The following pseudo-ops from the Kane and Heinrich MIPS book
934 should be defined here, but are currently unsupported: .alias,
935 .galive, .gjaldef, .gjrlive, .livereg, .noalias.
937 The following pseudo-ops from the Kane and Heinrich MIPS book are
938 specific to the type of debugging information being generated, and
939 should be defined by the object format: .aent, .begin, .bend,
940 .bgnb, .end, .endb, .ent, .fmask, .frame, .loc, .mask, .verstamp,
943 The following pseudo-ops from the Kane and Heinrich MIPS book are
944 not MIPS CPU specific, but are also not specific to the object file
945 format. This file is probably the best place to define them, but
946 they are not currently supported: .asm0, .endr, .lab, .repeat,
949 static const pseudo_typeS mips_pseudo_table[] =
951 /* MIPS specific pseudo-ops. */
952 {"option", s_option, 0},
953 {"set", s_mipsset, 0},
954 {"rdata", s_change_sec, 'r'},
955 {"sdata", s_change_sec, 's'},
956 {"livereg", s_ignore, 0},
957 {"abicalls", s_abicalls, 0},
958 {"cpload", s_cpload, 0},
959 {"cpsetup", s_cpsetup, 0},
960 {"cplocal", s_cplocal, 0},
961 {"cprestore", s_cprestore, 0},
962 {"cpreturn", s_cpreturn, 0},
963 {"gpvalue", s_gpvalue, 0},
964 {"gpword", s_gpword, 0},
965 {"gpdword", s_gpdword, 0},
966 {"cpadd", s_cpadd, 0},
969 /* Relatively generic pseudo-ops that happen to be used on MIPS
971 {"asciiz", stringer, 1},
972 {"bss", s_change_sec, 'b'},
975 {"dword", s_cons, 3},
976 {"weakext", s_mips_weakext, 0},
978 /* These pseudo-ops are defined in read.c, but must be overridden
979 here for one reason or another. */
980 {"align", s_align, 0},
982 {"data", s_change_sec, 'd'},
983 {"double", s_float_cons, 'd'},
984 {"float", s_float_cons, 'f'},
985 {"globl", s_mips_globl, 0},
986 {"global", s_mips_globl, 0},
987 {"hword", s_cons, 1},
992 {"section", s_change_section, 0},
993 {"short", s_cons, 1},
994 {"single", s_float_cons, 'f'},
995 {"stabn", s_mips_stab, 'n'},
996 {"text", s_change_sec, 't'},
999 { "extern", ecoff_directive_extern, 0},
1004 static const pseudo_typeS mips_nonecoff_pseudo_table[] =
1006 /* These pseudo-ops should be defined by the object file format.
1007 However, a.out doesn't support them, so we have versions here. */
1008 {"aent", s_mips_ent, 1},
1009 {"bgnb", s_ignore, 0},
1010 {"end", s_mips_end, 0},
1011 {"endb", s_ignore, 0},
1012 {"ent", s_mips_ent, 0},
1013 {"file", s_mips_file, 0},
1014 {"fmask", s_mips_mask, 'F'},
1015 {"frame", s_mips_frame, 0},
1016 {"loc", s_mips_loc, 0},
1017 {"mask", s_mips_mask, 'R'},
1018 {"verstamp", s_ignore, 0},
1022 extern void pop_insert PARAMS ((const pseudo_typeS *));
1027 pop_insert (mips_pseudo_table);
1028 if (! ECOFF_DEBUGGING)
1029 pop_insert (mips_nonecoff_pseudo_table);
1032 /* Symbols labelling the current insn. */
1034 struct insn_label_list
1036 struct insn_label_list *next;
1040 static struct insn_label_list *insn_labels;
1041 static struct insn_label_list *free_insn_labels;
1043 static void mips_clear_insn_labels PARAMS ((void));
1046 mips_clear_insn_labels ()
1048 register struct insn_label_list **pl;
1050 for (pl = &free_insn_labels; *pl != NULL; pl = &(*pl)->next)
1056 static char *expr_end;
1058 /* Expressions which appear in instructions. These are set by
1061 static expressionS imm_expr;
1062 static expressionS offset_expr;
1064 /* Relocs associated with imm_expr and offset_expr. */
1066 static bfd_reloc_code_real_type imm_reloc[3]
1067 = {BFD_RELOC_UNUSED, BFD_RELOC_UNUSED, BFD_RELOC_UNUSED};
1068 static bfd_reloc_code_real_type offset_reloc[3]
1069 = {BFD_RELOC_UNUSED, BFD_RELOC_UNUSED, BFD_RELOC_UNUSED};
1071 /* This is set by mips_ip if imm_reloc is an unmatched HI16_S reloc. */
1073 static boolean imm_unmatched_hi;
1075 /* These are set by mips16_ip if an explicit extension is used. */
1077 static boolean mips16_small, mips16_ext;
1080 /* The pdr segment for per procedure frame/regmask info. Not used for
1083 static segT pdr_seg;
1086 /* The default target format to use. */
1089 mips_target_format ()
1091 switch (OUTPUT_FLAVOR)
1093 case bfd_target_aout_flavour:
1094 return target_big_endian ? "a.out-mips-big" : "a.out-mips-little";
1095 case bfd_target_ecoff_flavour:
1096 return target_big_endian ? "ecoff-bigmips" : ECOFF_LITTLE_FORMAT;
1097 case bfd_target_coff_flavour:
1099 case bfd_target_elf_flavour:
1101 /* This is traditional mips. */
1102 return (target_big_endian
1103 ? (HAVE_64BIT_OBJECTS
1104 ? "elf64-tradbigmips"
1106 ? "elf32-ntradbigmips" : "elf32-tradbigmips"))
1107 : (HAVE_64BIT_OBJECTS
1108 ? "elf64-tradlittlemips"
1110 ? "elf32-ntradlittlemips" : "elf32-tradlittlemips")));
1112 return (target_big_endian
1113 ? (HAVE_64BIT_OBJECTS
1116 ? "elf32-nbigmips" : "elf32-bigmips"))
1117 : (HAVE_64BIT_OBJECTS
1118 ? "elf64-littlemips"
1120 ? "elf32-nlittlemips" : "elf32-littlemips")));
1128 /* This function is called once, at assembler startup time. It should
1129 set up all the tables, etc. that the MD part of the assembler will need. */
1134 register const char *retval = NULL;
1138 if (! bfd_set_arch_mach (stdoutput, bfd_arch_mips, mips_arch))
1139 as_warn (_("Could not set architecture and machine"));
1141 op_hash = hash_new ();
1143 for (i = 0; i < NUMOPCODES;)
1145 const char *name = mips_opcodes[i].name;
1147 retval = hash_insert (op_hash, name, (PTR) &mips_opcodes[i]);
1150 fprintf (stderr, _("internal error: can't hash `%s': %s\n"),
1151 mips_opcodes[i].name, retval);
1152 /* Probably a memory allocation problem? Give up now. */
1153 as_fatal (_("Broken assembler. No assembly attempted."));
1157 if (mips_opcodes[i].pinfo != INSN_MACRO)
1159 if (!validate_mips_insn (&mips_opcodes[i]))
1164 while ((i < NUMOPCODES) && !strcmp (mips_opcodes[i].name, name));
1167 mips16_op_hash = hash_new ();
1170 while (i < bfd_mips16_num_opcodes)
1172 const char *name = mips16_opcodes[i].name;
1174 retval = hash_insert (mips16_op_hash, name, (PTR) &mips16_opcodes[i]);
1176 as_fatal (_("internal: can't hash `%s': %s"),
1177 mips16_opcodes[i].name, retval);
1180 if (mips16_opcodes[i].pinfo != INSN_MACRO
1181 && ((mips16_opcodes[i].match & mips16_opcodes[i].mask)
1182 != mips16_opcodes[i].match))
1184 fprintf (stderr, _("internal error: bad mips16 opcode: %s %s\n"),
1185 mips16_opcodes[i].name, mips16_opcodes[i].args);
1190 while (i < bfd_mips16_num_opcodes
1191 && strcmp (mips16_opcodes[i].name, name) == 0);
1195 as_fatal (_("Broken assembler. No assembly attempted."));
1197 /* We add all the general register names to the symbol table. This
1198 helps us detect invalid uses of them. */
1199 for (i = 0; i < 32; i++)
1203 sprintf (buf, "$%d", i);
1204 symbol_table_insert (symbol_new (buf, reg_section, i,
1205 &zero_address_frag));
1207 symbol_table_insert (symbol_new ("$ra", reg_section, RA,
1208 &zero_address_frag));
1209 symbol_table_insert (symbol_new ("$fp", reg_section, FP,
1210 &zero_address_frag));
1211 symbol_table_insert (symbol_new ("$sp", reg_section, SP,
1212 &zero_address_frag));
1213 symbol_table_insert (symbol_new ("$gp", reg_section, GP,
1214 &zero_address_frag));
1215 symbol_table_insert (symbol_new ("$at", reg_section, AT,
1216 &zero_address_frag));
1217 symbol_table_insert (symbol_new ("$kt0", reg_section, KT0,
1218 &zero_address_frag));
1219 symbol_table_insert (symbol_new ("$kt1", reg_section, KT1,
1220 &zero_address_frag));
1221 symbol_table_insert (symbol_new ("$zero", reg_section, ZERO,
1222 &zero_address_frag));
1223 symbol_table_insert (symbol_new ("$pc", reg_section, -1,
1224 &zero_address_frag));
1226 /* If we don't add these register names to the symbol table, they
1227 may end up being added as regular symbols by operand(), and then
1228 make it to the object file as undefined in case they're not
1229 regarded as local symbols. They're local in o32, since `$' is a
1230 local symbol prefix, but not in n32 or n64. */
1231 for (i = 0; i < 8; i++)
1235 sprintf (buf, "$fcc%i", i);
1236 symbol_table_insert (symbol_new (buf, reg_section, -1,
1237 &zero_address_frag));
1240 mips_no_prev_insn (false);
1243 mips_cprmask[0] = 0;
1244 mips_cprmask[1] = 0;
1245 mips_cprmask[2] = 0;
1246 mips_cprmask[3] = 0;
1248 /* set the default alignment for the text section (2**2) */
1249 record_alignment (text_section, 2);
1251 if (USE_GLOBAL_POINTER_OPT)
1252 bfd_set_gp_size (stdoutput, g_switch_value);
1254 if (OUTPUT_FLAVOR == bfd_target_elf_flavour)
1256 /* On a native system, sections must be aligned to 16 byte
1257 boundaries. When configured for an embedded ELF target, we
1259 if (strcmp (TARGET_OS, "elf") != 0)
1261 (void) bfd_set_section_alignment (stdoutput, text_section, 4);
1262 (void) bfd_set_section_alignment (stdoutput, data_section, 4);
1263 (void) bfd_set_section_alignment (stdoutput, bss_section, 4);
1266 /* Create a .reginfo section for register masks and a .mdebug
1267 section for debugging information. */
1275 subseg = now_subseg;
1277 /* The ABI says this section should be loaded so that the
1278 running program can access it. However, we don't load it
1279 if we are configured for an embedded target */
1280 flags = SEC_READONLY | SEC_DATA;
1281 if (strcmp (TARGET_OS, "elf") != 0)
1282 flags |= SEC_ALLOC | SEC_LOAD;
1284 if (mips_abi != N64_ABI)
1286 sec = subseg_new (".reginfo", (subsegT) 0);
1288 bfd_set_section_flags (stdoutput, sec, flags);
1289 bfd_set_section_alignment (stdoutput, sec, HAVE_NEWABI ? 3 : 2);
1292 mips_regmask_frag = frag_more (sizeof (Elf32_External_RegInfo));
1297 /* The 64-bit ABI uses a .MIPS.options section rather than
1298 .reginfo section. */
1299 sec = subseg_new (".MIPS.options", (subsegT) 0);
1300 bfd_set_section_flags (stdoutput, sec, flags);
1301 bfd_set_section_alignment (stdoutput, sec, 3);
1304 /* Set up the option header. */
1306 Elf_Internal_Options opthdr;
1309 opthdr.kind = ODK_REGINFO;
1310 opthdr.size = (sizeof (Elf_External_Options)
1311 + sizeof (Elf64_External_RegInfo));
1314 f = frag_more (sizeof (Elf_External_Options));
1315 bfd_mips_elf_swap_options_out (stdoutput, &opthdr,
1316 (Elf_External_Options *) f);
1318 mips_regmask_frag = frag_more (sizeof (Elf64_External_RegInfo));
1323 if (ECOFF_DEBUGGING)
1325 sec = subseg_new (".mdebug", (subsegT) 0);
1326 (void) bfd_set_section_flags (stdoutput, sec,
1327 SEC_HAS_CONTENTS | SEC_READONLY);
1328 (void) bfd_set_section_alignment (stdoutput, sec, 2);
1331 else if (OUTPUT_FLAVOR == bfd_target_elf_flavour)
1333 pdr_seg = subseg_new (".pdr", (subsegT) 0);
1334 (void) bfd_set_section_flags (stdoutput, pdr_seg,
1335 SEC_READONLY | SEC_RELOC
1337 (void) bfd_set_section_alignment (stdoutput, pdr_seg, 2);
1341 subseg_set (seg, subseg);
1345 if (! ECOFF_DEBUGGING)
1352 if (! ECOFF_DEBUGGING)
1360 struct mips_cl_insn insn;
1361 bfd_reloc_code_real_type unused_reloc[3]
1362 = {BFD_RELOC_UNUSED, BFD_RELOC_UNUSED, BFD_RELOC_UNUSED};
1364 imm_expr.X_op = O_absent;
1365 imm_unmatched_hi = false;
1366 offset_expr.X_op = O_absent;
1367 imm_reloc[0] = BFD_RELOC_UNUSED;
1368 imm_reloc[1] = BFD_RELOC_UNUSED;
1369 imm_reloc[2] = BFD_RELOC_UNUSED;
1370 offset_reloc[0] = BFD_RELOC_UNUSED;
1371 offset_reloc[1] = BFD_RELOC_UNUSED;
1372 offset_reloc[2] = BFD_RELOC_UNUSED;
1374 if (mips_opts.mips16)
1375 mips16_ip (str, &insn);
1378 mips_ip (str, &insn);
1379 DBG ((_("returned from mips_ip(%s) insn_opcode = 0x%x\n"),
1380 str, insn.insn_opcode));
1385 as_bad ("%s `%s'", insn_error, str);
1389 if (insn.insn_mo->pinfo == INSN_MACRO)
1391 if (mips_opts.mips16)
1392 mips16_macro (&insn);
1398 if (imm_expr.X_op != O_absent)
1399 append_insn (NULL, &insn, &imm_expr, imm_reloc, imm_unmatched_hi);
1400 else if (offset_expr.X_op != O_absent)
1401 append_insn (NULL, &insn, &offset_expr, offset_reloc, false);
1403 append_insn (NULL, &insn, NULL, unused_reloc, false);
1407 /* See whether instruction IP reads register REG. CLASS is the type
1411 insn_uses_reg (ip, reg, class)
1412 struct mips_cl_insn *ip;
1414 enum mips_regclass class;
1416 if (class == MIPS16_REG)
1418 assert (mips_opts.mips16);
1419 reg = mips16_to_32_reg_map[reg];
1420 class = MIPS_GR_REG;
1423 /* Don't report on general register ZERO, since it never changes. */
1424 if (class == MIPS_GR_REG && reg == ZERO)
1427 if (class == MIPS_FP_REG)
1429 assert (! mips_opts.mips16);
1430 /* If we are called with either $f0 or $f1, we must check $f0.
1431 This is not optimal, because it will introduce an unnecessary
1432 NOP between "lwc1 $f0" and "swc1 $f1". To fix this we would
1433 need to distinguish reading both $f0 and $f1 or just one of
1434 them. Note that we don't have to check the other way,
1435 because there is no instruction that sets both $f0 and $f1
1436 and requires a delay. */
1437 if ((ip->insn_mo->pinfo & INSN_READ_FPR_S)
1438 && ((((ip->insn_opcode >> OP_SH_FS) & OP_MASK_FS) &~(unsigned)1)
1439 == (reg &~ (unsigned) 1)))
1441 if ((ip->insn_mo->pinfo & INSN_READ_FPR_T)
1442 && ((((ip->insn_opcode >> OP_SH_FT) & OP_MASK_FT) &~(unsigned)1)
1443 == (reg &~ (unsigned) 1)))
1446 else if (! mips_opts.mips16)
1448 if ((ip->insn_mo->pinfo & INSN_READ_GPR_S)
1449 && ((ip->insn_opcode >> OP_SH_RS) & OP_MASK_RS) == reg)
1451 if ((ip->insn_mo->pinfo & INSN_READ_GPR_T)
1452 && ((ip->insn_opcode >> OP_SH_RT) & OP_MASK_RT) == reg)
1457 if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_X)
1458 && (mips16_to_32_reg_map[((ip->insn_opcode >> MIPS16OP_SH_RX)
1459 & MIPS16OP_MASK_RX)]
1462 if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_Y)
1463 && (mips16_to_32_reg_map[((ip->insn_opcode >> MIPS16OP_SH_RY)
1464 & MIPS16OP_MASK_RY)]
1467 if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_Z)
1468 && (mips16_to_32_reg_map[((ip->insn_opcode >> MIPS16OP_SH_MOVE32Z)
1469 & MIPS16OP_MASK_MOVE32Z)]
1472 if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_T) && reg == TREG)
1474 if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_SP) && reg == SP)
1476 if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_31) && reg == RA)
1478 if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_GPR_X)
1479 && ((ip->insn_opcode >> MIPS16OP_SH_REGR32)
1480 & MIPS16OP_MASK_REGR32) == reg)
1487 /* This function returns true if modifying a register requires a
1491 reg_needs_delay (reg)
1494 unsigned long prev_pinfo;
1496 prev_pinfo = prev_insn.insn_mo->pinfo;
1497 if (! mips_opts.noreorder
1498 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
1499 && ((prev_pinfo & INSN_LOAD_COPROC_DELAY)
1500 || (! gpr_interlocks
1501 && (prev_pinfo & INSN_LOAD_MEMORY_DELAY))))
1503 /* A load from a coprocessor or from memory. All load
1504 delays delay the use of general register rt for one
1505 instruction on the r3000. The r6000 and r4000 use
1507 /* Itbl support may require additional care here. */
1508 know (prev_pinfo & INSN_WRITE_GPR_T);
1509 if (reg == ((prev_insn.insn_opcode >> OP_SH_RT) & OP_MASK_RT))
1516 /* Mark instruction labels in mips16 mode. This permits the linker to
1517 handle them specially, such as generating jalx instructions when
1518 needed. We also make them odd for the duration of the assembly, in
1519 order to generate the right sort of code. We will make them even
1520 in the adjust_symtab routine, while leaving them marked. This is
1521 convenient for the debugger and the disassembler. The linker knows
1522 to make them odd again. */
1525 mips16_mark_labels ()
1527 if (mips_opts.mips16)
1529 struct insn_label_list *l;
1532 for (l = insn_labels; l != NULL; l = l->next)
1535 if (OUTPUT_FLAVOR == bfd_target_elf_flavour)
1536 S_SET_OTHER (l->label, STO_MIPS16);
1538 val = S_GET_VALUE (l->label);
1540 S_SET_VALUE (l->label, val + 1);
1545 /* Output an instruction. PLACE is where to put the instruction; if
1546 it is NULL, this uses frag_more to get room. IP is the instruction
1547 information. ADDRESS_EXPR is an operand of the instruction to be
1548 used with RELOC_TYPE. */
1551 append_insn (place, ip, address_expr, reloc_type, unmatched_hi)
1553 struct mips_cl_insn *ip;
1554 expressionS *address_expr;
1555 bfd_reloc_code_real_type *reloc_type;
1556 boolean unmatched_hi;
1558 register unsigned long prev_pinfo, pinfo;
1563 /* Mark instruction labels in mips16 mode. */
1564 mips16_mark_labels ();
1566 prev_pinfo = prev_insn.insn_mo->pinfo;
1567 pinfo = ip->insn_mo->pinfo;
1569 if (place == NULL && (! mips_opts.noreorder || prev_nop_frag != NULL))
1573 /* If the previous insn required any delay slots, see if we need
1574 to insert a NOP or two. There are eight kinds of possible
1575 hazards, of which an instruction can have at most one type.
1576 (1) a load from memory delay
1577 (2) a load from a coprocessor delay
1578 (3) an unconditional branch delay
1579 (4) a conditional branch delay
1580 (5) a move to coprocessor register delay
1581 (6) a load coprocessor register from memory delay
1582 (7) a coprocessor condition code delay
1583 (8) a HI/LO special register delay
1585 There are a lot of optimizations we could do that we don't.
1586 In particular, we do not, in general, reorder instructions.
1587 If you use gcc with optimization, it will reorder
1588 instructions and generally do much more optimization then we
1589 do here; repeating all that work in the assembler would only
1590 benefit hand written assembly code, and does not seem worth
1593 /* This is how a NOP is emitted. */
1594 #define emit_nop() \
1596 ? md_number_to_chars (frag_more (2), 0x6500, 2) \
1597 : md_number_to_chars (frag_more (4), 0, 4))
1599 /* The previous insn might require a delay slot, depending upon
1600 the contents of the current insn. */
1601 if (! mips_opts.mips16
1602 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
1603 && (((prev_pinfo & INSN_LOAD_COPROC_DELAY)
1604 && ! cop_interlocks)
1605 || (! gpr_interlocks
1606 && (prev_pinfo & INSN_LOAD_MEMORY_DELAY))))
1608 /* A load from a coprocessor or from memory. All load
1609 delays delay the use of general register rt for one
1610 instruction on the r3000. The r6000 and r4000 use
1612 /* Itbl support may require additional care here. */
1613 know (prev_pinfo & INSN_WRITE_GPR_T);
1614 if (mips_optimize == 0
1615 || insn_uses_reg (ip,
1616 ((prev_insn.insn_opcode >> OP_SH_RT)
1621 else if (! mips_opts.mips16
1622 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
1623 && (((prev_pinfo & INSN_COPROC_MOVE_DELAY)
1624 && ! cop_interlocks)
1625 || (mips_opts.isa == ISA_MIPS1
1626 && (prev_pinfo & INSN_COPROC_MEMORY_DELAY))))
1628 /* A generic coprocessor delay. The previous instruction
1629 modified a coprocessor general or control register. If
1630 it modified a control register, we need to avoid any
1631 coprocessor instruction (this is probably not always
1632 required, but it sometimes is). If it modified a general
1633 register, we avoid using that register.
1635 On the r6000 and r4000 loading a coprocessor register
1636 from memory is interlocked, and does not require a delay.
1638 This case is not handled very well. There is no special
1639 knowledge of CP0 handling, and the coprocessors other
1640 than the floating point unit are not distinguished at
1642 /* Itbl support may require additional care here. FIXME!
1643 Need to modify this to include knowledge about
1644 user specified delays! */
1645 if (prev_pinfo & INSN_WRITE_FPR_T)
1647 if (mips_optimize == 0
1648 || insn_uses_reg (ip,
1649 ((prev_insn.insn_opcode >> OP_SH_FT)
1654 else if (prev_pinfo & INSN_WRITE_FPR_S)
1656 if (mips_optimize == 0
1657 || insn_uses_reg (ip,
1658 ((prev_insn.insn_opcode >> OP_SH_FS)
1665 /* We don't know exactly what the previous instruction
1666 does. If the current instruction uses a coprocessor
1667 register, we must insert a NOP. If previous
1668 instruction may set the condition codes, and the
1669 current instruction uses them, we must insert two
1671 /* Itbl support may require additional care here. */
1672 if (mips_optimize == 0
1673 || ((prev_pinfo & INSN_WRITE_COND_CODE)
1674 && (pinfo & INSN_READ_COND_CODE)))
1676 else if (pinfo & INSN_COP)
1680 else if (! mips_opts.mips16
1681 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
1682 && (prev_pinfo & INSN_WRITE_COND_CODE)
1683 && ! cop_interlocks)
1685 /* The previous instruction sets the coprocessor condition
1686 codes, but does not require a general coprocessor delay
1687 (this means it is a floating point comparison
1688 instruction). If this instruction uses the condition
1689 codes, we need to insert a single NOP. */
1690 /* Itbl support may require additional care here. */
1691 if (mips_optimize == 0
1692 || (pinfo & INSN_READ_COND_CODE))
1696 /* If we're fixing up mfhi/mflo for the r7000 and the
1697 previous insn was an mfhi/mflo and the current insn
1698 reads the register that the mfhi/mflo wrote to, then
1701 else if (mips_7000_hilo_fix
1702 && MF_HILO_INSN (prev_pinfo)
1703 && insn_uses_reg (ip, ((prev_insn.insn_opcode >> OP_SH_RD)
1710 /* If we're fixing up mfhi/mflo for the r7000 and the
1711 2nd previous insn was an mfhi/mflo and the current insn
1712 reads the register that the mfhi/mflo wrote to, then
1715 else if (mips_7000_hilo_fix
1716 && MF_HILO_INSN (prev_prev_insn.insn_opcode)
1717 && insn_uses_reg (ip, ((prev_prev_insn.insn_opcode >> OP_SH_RD)
1725 else if (prev_pinfo & INSN_READ_LO)
1727 /* The previous instruction reads the LO register; if the
1728 current instruction writes to the LO register, we must
1729 insert two NOPS. Some newer processors have interlocks.
1730 Also the tx39's multiply instructions can be exectuted
1731 immediatly after a read from HI/LO (without the delay),
1732 though the tx39's divide insns still do require the
1734 if (! (hilo_interlocks
1735 || (mips_tune == CPU_R3900 && (pinfo & INSN_MULT)))
1736 && (mips_optimize == 0
1737 || (pinfo & INSN_WRITE_LO)))
1739 /* Most mips16 branch insns don't have a delay slot.
1740 If a read from LO is immediately followed by a branch
1741 to a write to LO we have a read followed by a write
1742 less than 2 insns away. We assume the target of
1743 a branch might be a write to LO, and insert a nop
1744 between a read and an immediately following branch. */
1745 else if (mips_opts.mips16
1746 && (mips_optimize == 0
1747 || (pinfo & MIPS16_INSN_BRANCH)))
1750 else if (prev_insn.insn_mo->pinfo & INSN_READ_HI)
1752 /* The previous instruction reads the HI register; if the
1753 current instruction writes to the HI register, we must
1754 insert a NOP. Some newer processors have interlocks.
1755 Also the note tx39's multiply above. */
1756 if (! (hilo_interlocks
1757 || (mips_tune == CPU_R3900 && (pinfo & INSN_MULT)))
1758 && (mips_optimize == 0
1759 || (pinfo & INSN_WRITE_HI)))
1761 /* Most mips16 branch insns don't have a delay slot.
1762 If a read from HI is immediately followed by a branch
1763 to a write to HI we have a read followed by a write
1764 less than 2 insns away. We assume the target of
1765 a branch might be a write to HI, and insert a nop
1766 between a read and an immediately following branch. */
1767 else if (mips_opts.mips16
1768 && (mips_optimize == 0
1769 || (pinfo & MIPS16_INSN_BRANCH)))
1773 /* If the previous instruction was in a noreorder section, then
1774 we don't want to insert the nop after all. */
1775 /* Itbl support may require additional care here. */
1776 if (prev_insn_unreordered)
1779 /* There are two cases which require two intervening
1780 instructions: 1) setting the condition codes using a move to
1781 coprocessor instruction which requires a general coprocessor
1782 delay and then reading the condition codes 2) reading the HI
1783 or LO register and then writing to it (except on processors
1784 which have interlocks). If we are not already emitting a NOP
1785 instruction, we must check for these cases compared to the
1786 instruction previous to the previous instruction. */
1787 if ((! mips_opts.mips16
1788 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
1789 && (prev_prev_insn.insn_mo->pinfo & INSN_COPROC_MOVE_DELAY)
1790 && (prev_prev_insn.insn_mo->pinfo & INSN_WRITE_COND_CODE)
1791 && (pinfo & INSN_READ_COND_CODE)
1792 && ! cop_interlocks)
1793 || ((prev_prev_insn.insn_mo->pinfo & INSN_READ_LO)
1794 && (pinfo & INSN_WRITE_LO)
1795 && ! (hilo_interlocks
1796 || (mips_tune == CPU_R3900 && (pinfo & INSN_MULT))))
1797 || ((prev_prev_insn.insn_mo->pinfo & INSN_READ_HI)
1798 && (pinfo & INSN_WRITE_HI)
1799 && ! (hilo_interlocks
1800 || (mips_tune == CPU_R3900 && (pinfo & INSN_MULT)))))
1805 if (prev_prev_insn_unreordered)
1808 if (prev_prev_nop && nops == 0)
1811 if (mips_fix_4122_bugs && prev_insn.insn_mo->name)
1813 /* We're out of bits in pinfo, so we must resort to string
1814 ops here. Shortcuts are selected based on opcodes being
1815 limited to the VR4122 instruction set. */
1817 const char *pn = prev_insn.insn_mo->name;
1818 const char *tn = ip->insn_mo->name;
1819 if (strncmp(pn, "macc", 4) == 0
1820 || strncmp(pn, "dmacc", 5) == 0)
1822 /* Errata 21 - [D]DIV[U] after [D]MACC */
1823 if (strstr (tn, "div"))
1828 /* Errata 23 - Continuous DMULT[U]/DMACC instructions */
1829 if (pn[0] == 'd' /* dmacc */
1830 && (strncmp(tn, "dmult", 5) == 0
1831 || strncmp(tn, "dmacc", 5) == 0))
1836 /* Errata 24 - MT{LO,HI} after [D]MACC */
1837 if (strcmp (tn, "mtlo") == 0
1838 || strcmp (tn, "mthi") == 0)
1844 else if (strncmp(pn, "dmult", 5) == 0
1845 && (strncmp(tn, "dmult", 5) == 0
1846 || strncmp(tn, "dmacc", 5) == 0))
1848 /* Here is the rest of errata 23. */
1851 if (nops < min_nops)
1855 /* If we are being given a nop instruction, don't bother with
1856 one of the nops we would otherwise output. This will only
1857 happen when a nop instruction is used with mips_optimize set
1860 && ! mips_opts.noreorder
1861 && ip->insn_opcode == (unsigned) (mips_opts.mips16 ? 0x6500 : 0))
1864 /* Now emit the right number of NOP instructions. */
1865 if (nops > 0 && ! mips_opts.noreorder)
1868 unsigned long old_frag_offset;
1870 struct insn_label_list *l;
1872 old_frag = frag_now;
1873 old_frag_offset = frag_now_fix ();
1875 for (i = 0; i < nops; i++)
1880 listing_prev_line ();
1881 /* We may be at the start of a variant frag. In case we
1882 are, make sure there is enough space for the frag
1883 after the frags created by listing_prev_line. The
1884 argument to frag_grow here must be at least as large
1885 as the argument to all other calls to frag_grow in
1886 this file. We don't have to worry about being in the
1887 middle of a variant frag, because the variants insert
1888 all needed nop instructions themselves. */
1892 for (l = insn_labels; l != NULL; l = l->next)
1896 assert (S_GET_SEGMENT (l->label) == now_seg);
1897 symbol_set_frag (l->label, frag_now);
1898 val = (valueT) frag_now_fix ();
1899 /* mips16 text labels are stored as odd. */
1900 if (mips_opts.mips16)
1902 S_SET_VALUE (l->label, val);
1905 #ifndef NO_ECOFF_DEBUGGING
1906 if (ECOFF_DEBUGGING)
1907 ecoff_fix_loc (old_frag, old_frag_offset);
1910 else if (prev_nop_frag != NULL)
1912 /* We have a frag holding nops we may be able to remove. If
1913 we don't need any nops, we can decrease the size of
1914 prev_nop_frag by the size of one instruction. If we do
1915 need some nops, we count them in prev_nops_required. */
1916 if (prev_nop_frag_since == 0)
1920 prev_nop_frag->fr_fix -= mips_opts.mips16 ? 2 : 4;
1921 --prev_nop_frag_holds;
1924 prev_nop_frag_required += nops;
1928 if (prev_prev_nop == 0)
1930 prev_nop_frag->fr_fix -= mips_opts.mips16 ? 2 : 4;
1931 --prev_nop_frag_holds;
1934 ++prev_nop_frag_required;
1937 if (prev_nop_frag_holds <= prev_nop_frag_required)
1938 prev_nop_frag = NULL;
1940 ++prev_nop_frag_since;
1942 /* Sanity check: by the time we reach the second instruction
1943 after prev_nop_frag, we should have used up all the nops
1944 one way or another. */
1945 assert (prev_nop_frag_since <= 1 || prev_nop_frag == NULL);
1951 && ((*reloc_type == BFD_RELOC_16_PCREL
1952 && address_expr->X_op != O_constant)
1953 || *reloc_type == BFD_RELOC_16_PCREL_S2)
1954 && (pinfo & INSN_UNCOND_BRANCH_DELAY || pinfo & INSN_COND_BRANCH_DELAY
1955 || pinfo & INSN_COND_BRANCH_LIKELY)
1956 && mips_relax_branch
1957 /* Don't try branch relaxation within .set nomacro, or within
1958 .set noat if we use $at for PIC computations. If it turns
1959 out that the branch was out-of-range, we'll get an error. */
1960 && !mips_opts.warn_about_macros
1961 && !(mips_opts.noat && mips_pic != NO_PIC)
1962 && !mips_opts.mips16)
1964 f = frag_var (rs_machine_dependent,
1965 relaxed_branch_length
1967 (pinfo & INSN_UNCOND_BRANCH_DELAY) ? -1
1968 : (pinfo & INSN_COND_BRANCH_LIKELY) ? 1 : 0), 4,
1970 (*reloc_type == BFD_RELOC_16_PCREL_S2,
1971 pinfo & INSN_UNCOND_BRANCH_DELAY,
1972 pinfo & INSN_COND_BRANCH_LIKELY,
1973 pinfo & INSN_WRITE_GPR_31,
1975 address_expr->X_add_symbol,
1976 address_expr->X_add_number,
1978 *reloc_type = BFD_RELOC_UNUSED;
1980 else if (*reloc_type > BFD_RELOC_UNUSED)
1982 /* We need to set up a variant frag. */
1983 assert (mips_opts.mips16 && address_expr != NULL);
1984 f = frag_var (rs_machine_dependent, 4, 0,
1985 RELAX_MIPS16_ENCODE (*reloc_type - BFD_RELOC_UNUSED,
1986 mips16_small, mips16_ext,
1988 & INSN_UNCOND_BRANCH_DELAY),
1989 (*prev_insn_reloc_type
1990 == BFD_RELOC_MIPS16_JMP)),
1991 make_expr_symbol (address_expr), 0, NULL);
1993 else if (place != NULL)
1995 else if (mips_opts.mips16
1997 && *reloc_type != BFD_RELOC_MIPS16_JMP)
1999 /* Make sure there is enough room to swap this instruction with
2000 a following jump instruction. */
2006 if (mips_opts.mips16
2007 && mips_opts.noreorder
2008 && (prev_pinfo & INSN_UNCOND_BRANCH_DELAY) != 0)
2009 as_warn (_("extended instruction in delay slot"));
2014 fixp[0] = fixp[1] = fixp[2] = NULL;
2015 if (address_expr != NULL && *reloc_type < BFD_RELOC_UNUSED)
2017 if (address_expr->X_op == O_constant)
2021 switch (*reloc_type)
2024 ip->insn_opcode |= address_expr->X_add_number;
2027 case BFD_RELOC_MIPS_HIGHEST:
2028 tmp = (address_expr->X_add_number + 0x800080008000) >> 16;
2030 ip->insn_opcode |= (tmp >> 16) & 0xffff;
2033 case BFD_RELOC_MIPS_HIGHER:
2034 tmp = (address_expr->X_add_number + 0x80008000) >> 16;
2035 ip->insn_opcode |= (tmp >> 16) & 0xffff;
2038 case BFD_RELOC_HI16_S:
2039 ip->insn_opcode |= ((address_expr->X_add_number + 0x8000)
2043 case BFD_RELOC_HI16:
2044 ip->insn_opcode |= (address_expr->X_add_number >> 16) & 0xffff;
2047 case BFD_RELOC_LO16:
2048 case BFD_RELOC_MIPS_GOT_DISP:
2049 ip->insn_opcode |= address_expr->X_add_number & 0xffff;
2052 case BFD_RELOC_MIPS_JMP:
2053 if ((address_expr->X_add_number & 3) != 0)
2054 as_bad (_("jump to misaligned address (0x%lx)"),
2055 (unsigned long) address_expr->X_add_number);
2056 if (address_expr->X_add_number & ~0xfffffff)
2057 as_bad (_("jump address range overflow (0x%lx)"),
2058 (unsigned long) address_expr->X_add_number);
2059 ip->insn_opcode |= (address_expr->X_add_number >> 2) & 0x3ffffff;
2062 case BFD_RELOC_MIPS16_JMP:
2063 if ((address_expr->X_add_number & 3) != 0)
2064 as_bad (_("jump to misaligned address (0x%lx)"),
2065 (unsigned long) address_expr->X_add_number);
2066 if (address_expr->X_add_number & ~0xfffffff)
2067 as_bad (_("jump address range overflow (0x%lx)"),
2068 (unsigned long) address_expr->X_add_number);
2070 (((address_expr->X_add_number & 0x7c0000) << 3)
2071 | ((address_expr->X_add_number & 0xf800000) >> 7)
2072 | ((address_expr->X_add_number & 0x3fffc) >> 2));
2075 case BFD_RELOC_16_PCREL:
2076 ip->insn_opcode |= address_expr->X_add_number & 0xffff;
2079 case BFD_RELOC_16_PCREL_S2:
2089 /* Don't generate a reloc if we are writing into a variant frag. */
2092 fixp[0] = fix_new_exp (frag_now, f - frag_now->fr_literal, 4,
2094 (*reloc_type == BFD_RELOC_16_PCREL
2095 || *reloc_type == BFD_RELOC_16_PCREL_S2),
2098 /* These relocations can have an addend that won't fit in
2099 4 octets for 64bit assembly. */
2100 if (HAVE_64BIT_GPRS &&
2101 (*reloc_type == BFD_RELOC_16
2102 || *reloc_type == BFD_RELOC_32
2103 || *reloc_type == BFD_RELOC_MIPS_JMP
2104 || *reloc_type == BFD_RELOC_HI16_S
2105 || *reloc_type == BFD_RELOC_LO16
2106 || *reloc_type == BFD_RELOC_GPREL16
2107 || *reloc_type == BFD_RELOC_MIPS_LITERAL
2108 || *reloc_type == BFD_RELOC_GPREL32
2109 || *reloc_type == BFD_RELOC_64
2110 || *reloc_type == BFD_RELOC_CTOR
2111 || *reloc_type == BFD_RELOC_MIPS_SUB
2112 || *reloc_type == BFD_RELOC_MIPS_HIGHEST
2113 || *reloc_type == BFD_RELOC_MIPS_HIGHER
2114 || *reloc_type == BFD_RELOC_MIPS_SCN_DISP
2115 || *reloc_type == BFD_RELOC_MIPS_REL16
2116 || *reloc_type == BFD_RELOC_MIPS_RELGOT))
2117 fixp[0]->fx_no_overflow = 1;
2121 struct mips_hi_fixup *hi_fixup;
2123 assert (*reloc_type == BFD_RELOC_HI16_S);
2124 hi_fixup = ((struct mips_hi_fixup *)
2125 xmalloc (sizeof (struct mips_hi_fixup)));
2126 hi_fixup->fixp = fixp[0];
2127 hi_fixup->seg = now_seg;
2128 hi_fixup->next = mips_hi_fixup_list;
2129 mips_hi_fixup_list = hi_fixup;
2132 if (reloc_type[1] != BFD_RELOC_UNUSED)
2134 /* FIXME: This symbol can be one of
2135 RSS_UNDEF, RSS_GP, RSS_GP0, RSS_LOC. */
2136 address_expr->X_op = O_absent;
2137 address_expr->X_add_symbol = 0;
2138 address_expr->X_add_number = 0;
2140 fixp[1] = fix_new_exp (frag_now, f - frag_now->fr_literal,
2141 4, address_expr, false,
2144 /* These relocations can have an addend that won't fit in
2145 4 octets for 64bit assembly. */
2146 if (HAVE_64BIT_GPRS &&
2147 (*reloc_type == BFD_RELOC_16
2148 || *reloc_type == BFD_RELOC_32
2149 || *reloc_type == BFD_RELOC_MIPS_JMP
2150 || *reloc_type == BFD_RELOC_HI16_S
2151 || *reloc_type == BFD_RELOC_LO16
2152 || *reloc_type == BFD_RELOC_GPREL16
2153 || *reloc_type == BFD_RELOC_MIPS_LITERAL
2154 || *reloc_type == BFD_RELOC_GPREL32
2155 || *reloc_type == BFD_RELOC_64
2156 || *reloc_type == BFD_RELOC_CTOR
2157 || *reloc_type == BFD_RELOC_MIPS_SUB
2158 || *reloc_type == BFD_RELOC_MIPS_HIGHEST
2159 || *reloc_type == BFD_RELOC_MIPS_HIGHER
2160 || *reloc_type == BFD_RELOC_MIPS_SCN_DISP
2161 || *reloc_type == BFD_RELOC_MIPS_REL16
2162 || *reloc_type == BFD_RELOC_MIPS_RELGOT))
2163 fixp[1]->fx_no_overflow = 1;
2165 if (reloc_type[2] != BFD_RELOC_UNUSED)
2167 address_expr->X_op = O_absent;
2168 address_expr->X_add_symbol = 0;
2169 address_expr->X_add_number = 0;
2171 fixp[2] = fix_new_exp (frag_now,
2172 f - frag_now->fr_literal, 4,
2173 address_expr, false,
2176 /* These relocations can have an addend that won't fit in
2177 4 octets for 64bit assembly. */
2178 if (HAVE_64BIT_GPRS &&
2179 (*reloc_type == BFD_RELOC_16
2180 || *reloc_type == BFD_RELOC_32
2181 || *reloc_type == BFD_RELOC_MIPS_JMP
2182 || *reloc_type == BFD_RELOC_HI16_S
2183 || *reloc_type == BFD_RELOC_LO16
2184 || *reloc_type == BFD_RELOC_GPREL16
2185 || *reloc_type == BFD_RELOC_MIPS_LITERAL
2186 || *reloc_type == BFD_RELOC_GPREL32
2187 || *reloc_type == BFD_RELOC_64
2188 || *reloc_type == BFD_RELOC_CTOR
2189 || *reloc_type == BFD_RELOC_MIPS_SUB
2190 || *reloc_type == BFD_RELOC_MIPS_HIGHEST
2191 || *reloc_type == BFD_RELOC_MIPS_HIGHER
2192 || *reloc_type == BFD_RELOC_MIPS_SCN_DISP
2193 || *reloc_type == BFD_RELOC_MIPS_REL16
2194 || *reloc_type == BFD_RELOC_MIPS_RELGOT))
2195 fixp[2]->fx_no_overflow = 1;
2202 if (! mips_opts.mips16)
2204 md_number_to_chars (f, ip->insn_opcode, 4);
2206 dwarf2_emit_insn (4);
2209 else if (*reloc_type == BFD_RELOC_MIPS16_JMP)
2211 md_number_to_chars (f, ip->insn_opcode >> 16, 2);
2212 md_number_to_chars (f + 2, ip->insn_opcode & 0xffff, 2);
2214 dwarf2_emit_insn (4);
2221 md_number_to_chars (f, 0xf000 | ip->extend, 2);
2224 md_number_to_chars (f, ip->insn_opcode, 2);
2226 dwarf2_emit_insn (ip->use_extend ? 4 : 2);
2230 /* Update the register mask information. */
2231 if (! mips_opts.mips16)
2233 if (pinfo & INSN_WRITE_GPR_D)
2234 mips_gprmask |= 1 << ((ip->insn_opcode >> OP_SH_RD) & OP_MASK_RD);
2235 if ((pinfo & (INSN_WRITE_GPR_T | INSN_READ_GPR_T)) != 0)
2236 mips_gprmask |= 1 << ((ip->insn_opcode >> OP_SH_RT) & OP_MASK_RT);
2237 if (pinfo & INSN_READ_GPR_S)
2238 mips_gprmask |= 1 << ((ip->insn_opcode >> OP_SH_RS) & OP_MASK_RS);
2239 if (pinfo & INSN_WRITE_GPR_31)
2240 mips_gprmask |= 1 << RA;
2241 if (pinfo & INSN_WRITE_FPR_D)
2242 mips_cprmask[1] |= 1 << ((ip->insn_opcode >> OP_SH_FD) & OP_MASK_FD);
2243 if ((pinfo & (INSN_WRITE_FPR_S | INSN_READ_FPR_S)) != 0)
2244 mips_cprmask[1] |= 1 << ((ip->insn_opcode >> OP_SH_FS) & OP_MASK_FS);
2245 if ((pinfo & (INSN_WRITE_FPR_T | INSN_READ_FPR_T)) != 0)
2246 mips_cprmask[1] |= 1 << ((ip->insn_opcode >> OP_SH_FT) & OP_MASK_FT);
2247 if ((pinfo & INSN_READ_FPR_R) != 0)
2248 mips_cprmask[1] |= 1 << ((ip->insn_opcode >> OP_SH_FR) & OP_MASK_FR);
2249 if (pinfo & INSN_COP)
2251 /* We don't keep enough information to sort these cases out.
2252 The itbl support does keep this information however, although
2253 we currently don't support itbl fprmats as part of the cop
2254 instruction. May want to add this support in the future. */
2256 /* Never set the bit for $0, which is always zero. */
2257 mips_gprmask &= ~1 << 0;
2261 if (pinfo & (MIPS16_INSN_WRITE_X | MIPS16_INSN_READ_X))
2262 mips_gprmask |= 1 << ((ip->insn_opcode >> MIPS16OP_SH_RX)
2263 & MIPS16OP_MASK_RX);
2264 if (pinfo & (MIPS16_INSN_WRITE_Y | MIPS16_INSN_READ_Y))
2265 mips_gprmask |= 1 << ((ip->insn_opcode >> MIPS16OP_SH_RY)
2266 & MIPS16OP_MASK_RY);
2267 if (pinfo & MIPS16_INSN_WRITE_Z)
2268 mips_gprmask |= 1 << ((ip->insn_opcode >> MIPS16OP_SH_RZ)
2269 & MIPS16OP_MASK_RZ);
2270 if (pinfo & (MIPS16_INSN_WRITE_T | MIPS16_INSN_READ_T))
2271 mips_gprmask |= 1 << TREG;
2272 if (pinfo & (MIPS16_INSN_WRITE_SP | MIPS16_INSN_READ_SP))
2273 mips_gprmask |= 1 << SP;
2274 if (pinfo & (MIPS16_INSN_WRITE_31 | MIPS16_INSN_READ_31))
2275 mips_gprmask |= 1 << RA;
2276 if (pinfo & MIPS16_INSN_WRITE_GPR_Y)
2277 mips_gprmask |= 1 << MIPS16OP_EXTRACT_REG32R (ip->insn_opcode);
2278 if (pinfo & MIPS16_INSN_READ_Z)
2279 mips_gprmask |= 1 << ((ip->insn_opcode >> MIPS16OP_SH_MOVE32Z)
2280 & MIPS16OP_MASK_MOVE32Z);
2281 if (pinfo & MIPS16_INSN_READ_GPR_X)
2282 mips_gprmask |= 1 << ((ip->insn_opcode >> MIPS16OP_SH_REGR32)
2283 & MIPS16OP_MASK_REGR32);
2286 if (place == NULL && ! mips_opts.noreorder)
2288 /* Filling the branch delay slot is more complex. We try to
2289 switch the branch with the previous instruction, which we can
2290 do if the previous instruction does not set up a condition
2291 that the branch tests and if the branch is not itself the
2292 target of any branch. */
2293 if ((pinfo & INSN_UNCOND_BRANCH_DELAY)
2294 || (pinfo & INSN_COND_BRANCH_DELAY))
2296 if (mips_optimize < 2
2297 /* If we have seen .set volatile or .set nomove, don't
2299 || mips_opts.nomove != 0
2300 /* If we had to emit any NOP instructions, then we
2301 already know we can not swap. */
2303 /* If we don't even know the previous insn, we can not
2305 || ! prev_insn_valid
2306 /* If the previous insn is already in a branch delay
2307 slot, then we can not swap. */
2308 || prev_insn_is_delay_slot
2309 /* If the previous previous insn was in a .set
2310 noreorder, we can't swap. Actually, the MIPS
2311 assembler will swap in this situation. However, gcc
2312 configured -with-gnu-as will generate code like
2318 in which we can not swap the bne and INSN. If gcc is
2319 not configured -with-gnu-as, it does not output the
2320 .set pseudo-ops. We don't have to check
2321 prev_insn_unreordered, because prev_insn_valid will
2322 be 0 in that case. We don't want to use
2323 prev_prev_insn_valid, because we do want to be able
2324 to swap at the start of a function. */
2325 || prev_prev_insn_unreordered
2326 /* If the branch is itself the target of a branch, we
2327 can not swap. We cheat on this; all we check for is
2328 whether there is a label on this instruction. If
2329 there are any branches to anything other than a
2330 label, users must use .set noreorder. */
2331 || insn_labels != NULL
2332 /* If the previous instruction is in a variant frag, we
2333 can not do the swap. This does not apply to the
2334 mips16, which uses variant frags for different
2336 || (! mips_opts.mips16
2337 && prev_insn_frag->fr_type == rs_machine_dependent)
2338 /* If the branch reads the condition codes, we don't
2339 even try to swap, because in the sequence
2344 we can not swap, and I don't feel like handling that
2346 || (! mips_opts.mips16
2347 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
2348 && (pinfo & INSN_READ_COND_CODE))
2349 /* We can not swap with an instruction that requires a
2350 delay slot, becase the target of the branch might
2351 interfere with that instruction. */
2352 || (! mips_opts.mips16
2353 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
2355 /* Itbl support may require additional care here. */
2356 & (INSN_LOAD_COPROC_DELAY
2357 | INSN_COPROC_MOVE_DELAY
2358 | INSN_WRITE_COND_CODE)))
2359 || (! (hilo_interlocks
2360 || (mips_tune == CPU_R3900 && (pinfo & INSN_MULT)))
2364 || (! mips_opts.mips16
2366 && (prev_pinfo & INSN_LOAD_MEMORY_DELAY))
2367 || (! mips_opts.mips16
2368 && mips_opts.isa == ISA_MIPS1
2369 /* Itbl support may require additional care here. */
2370 && (prev_pinfo & INSN_COPROC_MEMORY_DELAY))
2371 /* We can not swap with a branch instruction. */
2373 & (INSN_UNCOND_BRANCH_DELAY
2374 | INSN_COND_BRANCH_DELAY
2375 | INSN_COND_BRANCH_LIKELY))
2376 /* We do not swap with a trap instruction, since it
2377 complicates trap handlers to have the trap
2378 instruction be in a delay slot. */
2379 || (prev_pinfo & INSN_TRAP)
2380 /* If the branch reads a register that the previous
2381 instruction sets, we can not swap. */
2382 || (! mips_opts.mips16
2383 && (prev_pinfo & INSN_WRITE_GPR_T)
2384 && insn_uses_reg (ip,
2385 ((prev_insn.insn_opcode >> OP_SH_RT)
2388 || (! mips_opts.mips16
2389 && (prev_pinfo & INSN_WRITE_GPR_D)
2390 && insn_uses_reg (ip,
2391 ((prev_insn.insn_opcode >> OP_SH_RD)
2394 || (mips_opts.mips16
2395 && (((prev_pinfo & MIPS16_INSN_WRITE_X)
2396 && insn_uses_reg (ip,
2397 ((prev_insn.insn_opcode
2399 & MIPS16OP_MASK_RX),
2401 || ((prev_pinfo & MIPS16_INSN_WRITE_Y)
2402 && insn_uses_reg (ip,
2403 ((prev_insn.insn_opcode
2405 & MIPS16OP_MASK_RY),
2407 || ((prev_pinfo & MIPS16_INSN_WRITE_Z)
2408 && insn_uses_reg (ip,
2409 ((prev_insn.insn_opcode
2411 & MIPS16OP_MASK_RZ),
2413 || ((prev_pinfo & MIPS16_INSN_WRITE_T)
2414 && insn_uses_reg (ip, TREG, MIPS_GR_REG))
2415 || ((prev_pinfo & MIPS16_INSN_WRITE_31)
2416 && insn_uses_reg (ip, RA, MIPS_GR_REG))
2417 || ((prev_pinfo & MIPS16_INSN_WRITE_GPR_Y)
2418 && insn_uses_reg (ip,
2419 MIPS16OP_EXTRACT_REG32R (prev_insn.
2422 /* If the branch writes a register that the previous
2423 instruction sets, we can not swap (we know that
2424 branches write only to RD or to $31). */
2425 || (! mips_opts.mips16
2426 && (prev_pinfo & INSN_WRITE_GPR_T)
2427 && (((pinfo & INSN_WRITE_GPR_D)
2428 && (((prev_insn.insn_opcode >> OP_SH_RT) & OP_MASK_RT)
2429 == ((ip->insn_opcode >> OP_SH_RD) & OP_MASK_RD)))
2430 || ((pinfo & INSN_WRITE_GPR_31)
2431 && (((prev_insn.insn_opcode >> OP_SH_RT)
2434 || (! mips_opts.mips16
2435 && (prev_pinfo & INSN_WRITE_GPR_D)
2436 && (((pinfo & INSN_WRITE_GPR_D)
2437 && (((prev_insn.insn_opcode >> OP_SH_RD) & OP_MASK_RD)
2438 == ((ip->insn_opcode >> OP_SH_RD) & OP_MASK_RD)))
2439 || ((pinfo & INSN_WRITE_GPR_31)
2440 && (((prev_insn.insn_opcode >> OP_SH_RD)
2443 || (mips_opts.mips16
2444 && (pinfo & MIPS16_INSN_WRITE_31)
2445 && ((prev_pinfo & MIPS16_INSN_WRITE_31)
2446 || ((prev_pinfo & MIPS16_INSN_WRITE_GPR_Y)
2447 && (MIPS16OP_EXTRACT_REG32R (prev_insn.insn_opcode)
2449 /* If the branch writes a register that the previous
2450 instruction reads, we can not swap (we know that
2451 branches only write to RD or to $31). */
2452 || (! mips_opts.mips16
2453 && (pinfo & INSN_WRITE_GPR_D)
2454 && insn_uses_reg (&prev_insn,
2455 ((ip->insn_opcode >> OP_SH_RD)
2458 || (! mips_opts.mips16
2459 && (pinfo & INSN_WRITE_GPR_31)
2460 && insn_uses_reg (&prev_insn, RA, MIPS_GR_REG))
2461 || (mips_opts.mips16
2462 && (pinfo & MIPS16_INSN_WRITE_31)
2463 && insn_uses_reg (&prev_insn, RA, MIPS_GR_REG))
2464 /* If we are generating embedded PIC code, the branch
2465 might be expanded into a sequence which uses $at, so
2466 we can't swap with an instruction which reads it. */
2467 || (mips_pic == EMBEDDED_PIC
2468 && insn_uses_reg (&prev_insn, AT, MIPS_GR_REG))
2469 /* If the previous previous instruction has a load
2470 delay, and sets a register that the branch reads, we
2472 || (! mips_opts.mips16
2473 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
2474 /* Itbl support may require additional care here. */
2475 && ((prev_prev_insn.insn_mo->pinfo & INSN_LOAD_COPROC_DELAY)
2476 || (! gpr_interlocks
2477 && (prev_prev_insn.insn_mo->pinfo
2478 & INSN_LOAD_MEMORY_DELAY)))
2479 && insn_uses_reg (ip,
2480 ((prev_prev_insn.insn_opcode >> OP_SH_RT)
2483 /* If one instruction sets a condition code and the
2484 other one uses a condition code, we can not swap. */
2485 || ((pinfo & INSN_READ_COND_CODE)
2486 && (prev_pinfo & INSN_WRITE_COND_CODE))
2487 || ((pinfo & INSN_WRITE_COND_CODE)
2488 && (prev_pinfo & INSN_READ_COND_CODE))
2489 /* If the previous instruction uses the PC, we can not
2491 || (mips_opts.mips16
2492 && (prev_pinfo & MIPS16_INSN_READ_PC))
2493 /* If the previous instruction was extended, we can not
2495 || (mips_opts.mips16 && prev_insn_extended)
2496 /* If the previous instruction had a fixup in mips16
2497 mode, we can not swap. This normally means that the
2498 previous instruction was a 4 byte branch anyhow. */
2499 || (mips_opts.mips16 && prev_insn_fixp[0])
2500 /* If the previous instruction is a sync, sync.l, or
2501 sync.p, we can not swap. */
2502 || (prev_pinfo & INSN_SYNC))
2504 /* We could do even better for unconditional branches to
2505 portions of this object file; we could pick up the
2506 instruction at the destination, put it in the delay
2507 slot, and bump the destination address. */
2509 /* Update the previous insn information. */
2510 prev_prev_insn = *ip;
2511 prev_insn.insn_mo = &dummy_opcode;
2515 /* It looks like we can actually do the swap. */
2516 if (! mips_opts.mips16)
2521 prev_f = prev_insn_frag->fr_literal + prev_insn_where;
2522 memcpy (temp, prev_f, 4);
2523 memcpy (prev_f, f, 4);
2524 memcpy (f, temp, 4);
2525 if (prev_insn_fixp[0])
2527 prev_insn_fixp[0]->fx_frag = frag_now;
2528 prev_insn_fixp[0]->fx_where = f - frag_now->fr_literal;
2530 if (prev_insn_fixp[1])
2532 prev_insn_fixp[1]->fx_frag = frag_now;
2533 prev_insn_fixp[1]->fx_where = f - frag_now->fr_literal;
2535 if (prev_insn_fixp[2])
2537 prev_insn_fixp[2]->fx_frag = frag_now;
2538 prev_insn_fixp[2]->fx_where = f - frag_now->fr_literal;
2542 fixp[0]->fx_frag = prev_insn_frag;
2543 fixp[0]->fx_where = prev_insn_where;
2547 fixp[1]->fx_frag = prev_insn_frag;
2548 fixp[1]->fx_where = prev_insn_where;
2552 fixp[2]->fx_frag = prev_insn_frag;
2553 fixp[2]->fx_where = prev_insn_where;
2561 assert (prev_insn_fixp[0] == NULL);
2562 assert (prev_insn_fixp[1] == NULL);
2563 assert (prev_insn_fixp[2] == NULL);
2564 prev_f = prev_insn_frag->fr_literal + prev_insn_where;
2565 memcpy (temp, prev_f, 2);
2566 memcpy (prev_f, f, 2);
2567 if (*reloc_type != BFD_RELOC_MIPS16_JMP)
2569 assert (*reloc_type == BFD_RELOC_UNUSED);
2570 memcpy (f, temp, 2);
2574 memcpy (f, f + 2, 2);
2575 memcpy (f + 2, temp, 2);
2579 fixp[0]->fx_frag = prev_insn_frag;
2580 fixp[0]->fx_where = prev_insn_where;
2584 fixp[1]->fx_frag = prev_insn_frag;
2585 fixp[1]->fx_where = prev_insn_where;
2589 fixp[2]->fx_frag = prev_insn_frag;
2590 fixp[2]->fx_where = prev_insn_where;
2594 /* Update the previous insn information; leave prev_insn
2596 prev_prev_insn = *ip;
2598 prev_insn_is_delay_slot = 1;
2600 /* If that was an unconditional branch, forget the previous
2601 insn information. */
2602 if (pinfo & INSN_UNCOND_BRANCH_DELAY)
2604 prev_prev_insn.insn_mo = &dummy_opcode;
2605 prev_insn.insn_mo = &dummy_opcode;
2608 prev_insn_fixp[0] = NULL;
2609 prev_insn_fixp[1] = NULL;
2610 prev_insn_fixp[2] = NULL;
2611 prev_insn_reloc_type[0] = BFD_RELOC_UNUSED;
2612 prev_insn_reloc_type[1] = BFD_RELOC_UNUSED;
2613 prev_insn_reloc_type[2] = BFD_RELOC_UNUSED;
2614 prev_insn_extended = 0;
2616 else if (pinfo & INSN_COND_BRANCH_LIKELY)
2618 /* We don't yet optimize a branch likely. What we should do
2619 is look at the target, copy the instruction found there
2620 into the delay slot, and increment the branch to jump to
2621 the next instruction. */
2623 /* Update the previous insn information. */
2624 prev_prev_insn = *ip;
2625 prev_insn.insn_mo = &dummy_opcode;
2626 prev_insn_fixp[0] = NULL;
2627 prev_insn_fixp[1] = NULL;
2628 prev_insn_fixp[2] = NULL;
2629 prev_insn_reloc_type[0] = BFD_RELOC_UNUSED;
2630 prev_insn_reloc_type[1] = BFD_RELOC_UNUSED;
2631 prev_insn_reloc_type[2] = BFD_RELOC_UNUSED;
2632 prev_insn_extended = 0;
2636 /* Update the previous insn information. */
2638 prev_prev_insn.insn_mo = &dummy_opcode;
2640 prev_prev_insn = prev_insn;
2643 /* Any time we see a branch, we always fill the delay slot
2644 immediately; since this insn is not a branch, we know it
2645 is not in a delay slot. */
2646 prev_insn_is_delay_slot = 0;
2648 prev_insn_fixp[0] = fixp[0];
2649 prev_insn_fixp[1] = fixp[1];
2650 prev_insn_fixp[2] = fixp[2];
2651 prev_insn_reloc_type[0] = reloc_type[0];
2652 prev_insn_reloc_type[1] = reloc_type[1];
2653 prev_insn_reloc_type[2] = reloc_type[2];
2654 if (mips_opts.mips16)
2655 prev_insn_extended = (ip->use_extend
2656 || *reloc_type > BFD_RELOC_UNUSED);
2659 prev_prev_insn_unreordered = prev_insn_unreordered;
2660 prev_insn_unreordered = 0;
2661 prev_insn_frag = frag_now;
2662 prev_insn_where = f - frag_now->fr_literal;
2663 prev_insn_valid = 1;
2665 else if (place == NULL)
2667 /* We need to record a bit of information even when we are not
2668 reordering, in order to determine the base address for mips16
2669 PC relative relocs. */
2670 prev_prev_insn = prev_insn;
2672 prev_insn_reloc_type[0] = reloc_type[0];
2673 prev_insn_reloc_type[1] = reloc_type[1];
2674 prev_insn_reloc_type[2] = reloc_type[2];
2675 prev_prev_insn_unreordered = prev_insn_unreordered;
2676 prev_insn_unreordered = 1;
2679 /* We just output an insn, so the next one doesn't have a label. */
2680 mips_clear_insn_labels ();
2682 /* We must ensure that a fixup associated with an unmatched %hi
2683 reloc does not become a variant frag. Otherwise, the
2684 rearrangement of %hi relocs in frob_file may confuse
2688 frag_wane (frag_now);
2693 /* This function forgets that there was any previous instruction or
2694 label. If PRESERVE is non-zero, it remembers enough information to
2695 know whether nops are needed before a noreorder section. */
2698 mips_no_prev_insn (preserve)
2703 prev_insn.insn_mo = &dummy_opcode;
2704 prev_prev_insn.insn_mo = &dummy_opcode;
2705 prev_nop_frag = NULL;
2706 prev_nop_frag_holds = 0;
2707 prev_nop_frag_required = 0;
2708 prev_nop_frag_since = 0;
2710 prev_insn_valid = 0;
2711 prev_insn_is_delay_slot = 0;
2712 prev_insn_unreordered = 0;
2713 prev_insn_extended = 0;
2714 prev_insn_reloc_type[0] = BFD_RELOC_UNUSED;
2715 prev_insn_reloc_type[1] = BFD_RELOC_UNUSED;
2716 prev_insn_reloc_type[2] = BFD_RELOC_UNUSED;
2717 prev_prev_insn_unreordered = 0;
2718 mips_clear_insn_labels ();
2721 /* This function must be called whenever we turn on noreorder or emit
2722 something other than instructions. It inserts any NOPS which might
2723 be needed by the previous instruction, and clears the information
2724 kept for the previous instructions. The INSNS parameter is true if
2725 instructions are to follow. */
2728 mips_emit_delays (insns)
2731 if (! mips_opts.noreorder)
2736 if ((! mips_opts.mips16
2737 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
2738 && (! cop_interlocks
2739 && (prev_insn.insn_mo->pinfo
2740 & (INSN_LOAD_COPROC_DELAY
2741 | INSN_COPROC_MOVE_DELAY
2742 | INSN_WRITE_COND_CODE))))
2743 || (! hilo_interlocks
2744 && (prev_insn.insn_mo->pinfo
2747 || (! mips_opts.mips16
2749 && (prev_insn.insn_mo->pinfo
2750 & INSN_LOAD_MEMORY_DELAY))
2751 || (! mips_opts.mips16
2752 && mips_opts.isa == ISA_MIPS1
2753 && (prev_insn.insn_mo->pinfo
2754 & INSN_COPROC_MEMORY_DELAY)))
2756 /* Itbl support may require additional care here. */
2758 if ((! mips_opts.mips16
2759 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
2760 && (! cop_interlocks
2761 && prev_insn.insn_mo->pinfo & INSN_WRITE_COND_CODE))
2762 || (! hilo_interlocks
2763 && ((prev_insn.insn_mo->pinfo & INSN_READ_HI)
2764 || (prev_insn.insn_mo->pinfo & INSN_READ_LO))))
2767 if (prev_insn_unreordered)
2770 else if ((! mips_opts.mips16
2771 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
2772 && (! cop_interlocks
2773 && prev_prev_insn.insn_mo->pinfo & INSN_WRITE_COND_CODE))
2774 || (! hilo_interlocks
2775 && ((prev_prev_insn.insn_mo->pinfo & INSN_READ_HI)
2776 || (prev_prev_insn.insn_mo->pinfo & INSN_READ_LO))))
2778 /* Itbl support may require additional care here. */
2779 if (! prev_prev_insn_unreordered)
2783 if (mips_fix_4122_bugs && prev_insn.insn_mo->name)
2786 const char *pn = prev_insn.insn_mo->name;
2787 if (strncmp(pn, "macc", 4) == 0
2788 || strncmp(pn, "dmacc", 5) == 0
2789 || strncmp(pn, "dmult", 5) == 0)
2793 if (nops < min_nops)
2799 struct insn_label_list *l;
2803 /* Record the frag which holds the nop instructions, so
2804 that we can remove them if we don't need them. */
2805 frag_grow (mips_opts.mips16 ? nops * 2 : nops * 4);
2806 prev_nop_frag = frag_now;
2807 prev_nop_frag_holds = nops;
2808 prev_nop_frag_required = 0;
2809 prev_nop_frag_since = 0;
2812 for (; nops > 0; --nops)
2817 /* Move on to a new frag, so that it is safe to simply
2818 decrease the size of prev_nop_frag. */
2819 frag_wane (frag_now);
2823 for (l = insn_labels; l != NULL; l = l->next)
2827 assert (S_GET_SEGMENT (l->label) == now_seg);
2828 symbol_set_frag (l->label, frag_now);
2829 val = (valueT) frag_now_fix ();
2830 /* mips16 text labels are stored as odd. */
2831 if (mips_opts.mips16)
2833 S_SET_VALUE (l->label, val);
2838 /* Mark instruction labels in mips16 mode. */
2840 mips16_mark_labels ();
2842 mips_no_prev_insn (insns);
2845 /* Build an instruction created by a macro expansion. This is passed
2846 a pointer to the count of instructions created so far, an
2847 expression, the name of the instruction to build, an operand format
2848 string, and corresponding arguments. */
2852 macro_build (char *place,
2860 macro_build (place, counter, ep, name, fmt, va_alist)
2869 struct mips_cl_insn insn;
2870 bfd_reloc_code_real_type r[3];
2874 va_start (args, fmt);
2880 * If the macro is about to expand into a second instruction,
2881 * print a warning if needed. We need to pass ip as a parameter
2882 * to generate a better warning message here...
2884 if (mips_opts.warn_about_macros && place == NULL && *counter == 1)
2885 as_warn (_("Macro instruction expanded into multiple instructions"));
2888 * If the macro is about to expand into a second instruction,
2889 * and it is in a delay slot, print a warning.
2893 && mips_opts.noreorder
2894 && (prev_prev_insn.insn_mo->pinfo
2895 & (INSN_UNCOND_BRANCH_DELAY | INSN_COND_BRANCH_DELAY
2896 | INSN_COND_BRANCH_LIKELY)) != 0)
2897 as_warn (_("Macro instruction expanded into multiple instructions in a branch delay slot"));
2900 ++*counter; /* bump instruction counter */
2902 if (mips_opts.mips16)
2904 mips16_macro_build (place, counter, ep, name, fmt, args);
2909 r[0] = BFD_RELOC_UNUSED;
2910 r[1] = BFD_RELOC_UNUSED;
2911 r[2] = BFD_RELOC_UNUSED;
2912 insn.insn_mo = (struct mips_opcode *) hash_find (op_hash, name);
2913 assert (insn.insn_mo);
2914 assert (strcmp (name, insn.insn_mo->name) == 0);
2916 /* Search until we get a match for NAME. */
2919 /* It is assumed here that macros will never generate
2920 MDMX or MIPS-3D instructions. */
2921 if (strcmp (fmt, insn.insn_mo->args) == 0
2922 && insn.insn_mo->pinfo != INSN_MACRO
2923 && OPCODE_IS_MEMBER (insn.insn_mo,
2925 | (file_ase_mips16 ? INSN_MIPS16 : 0)),
2927 && (mips_arch != CPU_R4650 || (insn.insn_mo->pinfo & FP_D) == 0))
2931 assert (insn.insn_mo->name);
2932 assert (strcmp (name, insn.insn_mo->name) == 0);
2935 insn.insn_opcode = insn.insn_mo->match;
2951 insn.insn_opcode |= va_arg (args, int) << OP_SH_RT;
2955 insn.insn_opcode |= va_arg (args, int) << OP_SH_CODE;
2960 insn.insn_opcode |= va_arg (args, int) << OP_SH_FT;
2965 insn.insn_opcode |= va_arg (args, int) << OP_SH_RD;
2970 int tmp = va_arg (args, int);
2972 insn.insn_opcode |= tmp << OP_SH_RT;
2973 insn.insn_opcode |= tmp << OP_SH_RD;
2979 insn.insn_opcode |= va_arg (args, int) << OP_SH_FS;
2986 insn.insn_opcode |= va_arg (args, int) << OP_SH_SHAMT;
2990 insn.insn_opcode |= va_arg (args, int) << OP_SH_FD;
2994 insn.insn_opcode |= va_arg (args, int) << OP_SH_CODE20;
2998 insn.insn_opcode |= va_arg (args, int) << OP_SH_CODE19;
3002 insn.insn_opcode |= va_arg (args, int) << OP_SH_CODE2;
3009 insn.insn_opcode |= va_arg (args, int) << OP_SH_RS;
3015 *r = (bfd_reloc_code_real_type) va_arg (args, int);
3016 assert (*r == BFD_RELOC_GPREL16
3017 || *r == BFD_RELOC_MIPS_LITERAL
3018 || *r == BFD_RELOC_MIPS_HIGHER
3019 || *r == BFD_RELOC_HI16_S
3020 || *r == BFD_RELOC_LO16
3021 || *r == BFD_RELOC_MIPS_GOT16
3022 || *r == BFD_RELOC_MIPS_CALL16
3023 || *r == BFD_RELOC_MIPS_GOT_DISP
3024 || *r == BFD_RELOC_MIPS_GOT_PAGE
3025 || *r == BFD_RELOC_MIPS_GOT_OFST
3026 || *r == BFD_RELOC_MIPS_GOT_LO16
3027 || *r == BFD_RELOC_MIPS_CALL_LO16
3028 || (ep->X_op == O_subtract
3029 && *r == BFD_RELOC_PCREL_LO16));
3033 *r = (bfd_reloc_code_real_type) va_arg (args, int);
3035 && (ep->X_op == O_constant
3036 || (ep->X_op == O_symbol
3037 && (*r == BFD_RELOC_MIPS_HIGHEST
3038 || *r == BFD_RELOC_HI16_S
3039 || *r == BFD_RELOC_HI16
3040 || *r == BFD_RELOC_GPREL16
3041 || *r == BFD_RELOC_MIPS_GOT_HI16
3042 || *r == BFD_RELOC_MIPS_CALL_HI16))
3043 || (ep->X_op == O_subtract
3044 && *r == BFD_RELOC_PCREL_HI16_S)));
3048 assert (ep != NULL);
3050 * This allows macro() to pass an immediate expression for
3051 * creating short branches without creating a symbol.
3052 * Note that the expression still might come from the assembly
3053 * input, in which case the value is not checked for range nor
3054 * is a relocation entry generated (yuck).
3056 if (ep->X_op == O_constant)
3058 insn.insn_opcode |= (ep->X_add_number >> 2) & 0xffff;
3062 if (mips_pic == EMBEDDED_PIC)
3063 *r = BFD_RELOC_16_PCREL_S2;
3065 *r = BFD_RELOC_16_PCREL;
3069 assert (ep != NULL);
3070 *r = BFD_RELOC_MIPS_JMP;
3074 insn.insn_opcode |= va_arg (args, unsigned long);
3083 assert (*r == BFD_RELOC_UNUSED ? ep == NULL : ep != NULL);
3085 append_insn (place, &insn, ep, r, false);
3089 mips16_macro_build (place, counter, ep, name, fmt, args)
3091 int *counter ATTRIBUTE_UNUSED;
3097 struct mips_cl_insn insn;
3098 bfd_reloc_code_real_type r[3]
3099 = {BFD_RELOC_UNUSED, BFD_RELOC_UNUSED, BFD_RELOC_UNUSED};
3101 insn.insn_mo = (struct mips_opcode *) hash_find (mips16_op_hash, name);
3102 assert (insn.insn_mo);
3103 assert (strcmp (name, insn.insn_mo->name) == 0);
3105 while (strcmp (fmt, insn.insn_mo->args) != 0
3106 || insn.insn_mo->pinfo == INSN_MACRO)
3109 assert (insn.insn_mo->name);
3110 assert (strcmp (name, insn.insn_mo->name) == 0);
3113 insn.insn_opcode = insn.insn_mo->match;
3114 insn.use_extend = false;
3133 insn.insn_opcode |= va_arg (args, int) << MIPS16OP_SH_RY;
3138 insn.insn_opcode |= va_arg (args, int) << MIPS16OP_SH_RX;
3142 insn.insn_opcode |= va_arg (args, int) << MIPS16OP_SH_RZ;
3146 insn.insn_opcode |= va_arg (args, int) << MIPS16OP_SH_MOVE32Z;
3156 insn.insn_opcode |= va_arg (args, int) << MIPS16OP_SH_REGR32;
3163 regno = va_arg (args, int);
3164 regno = ((regno & 7) << 2) | ((regno & 0x18) >> 3);
3165 insn.insn_opcode |= regno << MIPS16OP_SH_REG32R;
3186 assert (ep != NULL);
3188 if (ep->X_op != O_constant)
3189 *r = (int) BFD_RELOC_UNUSED + c;
3192 mips16_immed (NULL, 0, c, ep->X_add_number, false, false,
3193 false, &insn.insn_opcode, &insn.use_extend,
3196 *r = BFD_RELOC_UNUSED;
3202 insn.insn_opcode |= va_arg (args, int) << MIPS16OP_SH_IMM6;
3209 assert (*r == BFD_RELOC_UNUSED ? ep == NULL : ep != NULL);
3211 append_insn (place, &insn, ep, r, false);
3215 * Generate a "jalr" instruction with a relocation hint to the called
3216 * function. This occurs in NewABI PIC code.
3219 macro_build_jalr (icnt, ep)
3230 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "jalr", "d,s",
3233 fix_new_exp (frag_now, f - frag_now->fr_literal,
3234 0, ep, false, BFD_RELOC_MIPS_JALR);
3238 * Generate a "lui" instruction.
3241 macro_build_lui (place, counter, ep, regnum)
3247 expressionS high_expr;
3248 struct mips_cl_insn insn;
3249 bfd_reloc_code_real_type r[3]
3250 = {BFD_RELOC_UNUSED, BFD_RELOC_UNUSED, BFD_RELOC_UNUSED};
3251 const char *name = "lui";
3252 const char *fmt = "t,u";
3254 assert (! mips_opts.mips16);
3260 high_expr.X_op = O_constant;
3261 high_expr.X_add_number = ep->X_add_number;
3264 if (high_expr.X_op == O_constant)
3266 /* we can compute the instruction now without a relocation entry */
3267 high_expr.X_add_number = ((high_expr.X_add_number + 0x8000)
3269 *r = BFD_RELOC_UNUSED;
3271 else if (! HAVE_NEWABI)
3273 assert (ep->X_op == O_symbol);
3274 /* _gp_disp is a special case, used from s_cpload. */
3275 assert (mips_pic == NO_PIC
3276 || strcmp (S_GET_NAME (ep->X_add_symbol), "_gp_disp") == 0);
3277 *r = BFD_RELOC_HI16_S;
3281 * If the macro is about to expand into a second instruction,
3282 * print a warning if needed. We need to pass ip as a parameter
3283 * to generate a better warning message here...
3285 if (mips_opts.warn_about_macros && place == NULL && *counter == 1)
3286 as_warn (_("Macro instruction expanded into multiple instructions"));
3289 ++*counter; /* bump instruction counter */
3291 insn.insn_mo = (struct mips_opcode *) hash_find (op_hash, name);
3292 assert (insn.insn_mo);
3293 assert (strcmp (name, insn.insn_mo->name) == 0);
3294 assert (strcmp (fmt, insn.insn_mo->args) == 0);
3296 insn.insn_opcode = insn.insn_mo->match | (regnum << OP_SH_RT);
3297 if (*r == BFD_RELOC_UNUSED)
3299 insn.insn_opcode |= high_expr.X_add_number;
3300 append_insn (place, &insn, NULL, r, false);
3303 append_insn (place, &insn, &high_expr, r, false);
3306 /* Generate a sequence of instructions to do a load or store from a constant
3307 offset off of a base register (breg) into/from a target register (treg),
3308 using AT if necessary. */
3310 macro_build_ldst_constoffset (place, counter, ep, op, treg, breg)
3317 assert (ep->X_op == O_constant);
3319 /* Right now, this routine can only handle signed 32-bit contants. */
3320 if (! IS_SEXT_32BIT_NUM(ep->X_add_number))
3321 as_warn (_("operand overflow"));
3323 if (IS_SEXT_16BIT_NUM(ep->X_add_number))
3325 /* Signed 16-bit offset will fit in the op. Easy! */
3326 macro_build (place, counter, ep, op, "t,o(b)", treg,
3327 (int) BFD_RELOC_LO16, breg);
3331 /* 32-bit offset, need multiple instructions and AT, like:
3332 lui $tempreg,const_hi (BFD_RELOC_HI16_S)
3333 addu $tempreg,$tempreg,$breg
3334 <op> $treg,const_lo($tempreg) (BFD_RELOC_LO16)
3335 to handle the complete offset. */
3336 macro_build_lui (place, counter, ep, AT);
3339 macro_build (place, counter, (expressionS *) NULL,
3340 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
3341 "d,v,t", AT, AT, breg);
3344 macro_build (place, counter, ep, op, "t,o(b)", treg,
3345 (int) BFD_RELOC_LO16, AT);
3348 as_warn (_("Macro used $at after \".set noat\""));
3353 * Generates code to set the $at register to true (one)
3354 * if reg is less than the immediate expression.
3357 set_at (counter, reg, unsignedp)
3362 if (imm_expr.X_op == O_constant
3363 && imm_expr.X_add_number >= -0x8000
3364 && imm_expr.X_add_number < 0x8000)
3365 macro_build ((char *) NULL, counter, &imm_expr,
3366 unsignedp ? "sltiu" : "slti",
3367 "t,r,j", AT, reg, (int) BFD_RELOC_LO16);
3370 load_register (counter, AT, &imm_expr, HAVE_64BIT_GPRS);
3371 macro_build ((char *) NULL, counter, (expressionS *) NULL,
3372 unsignedp ? "sltu" : "slt",
3373 "d,v,t", AT, reg, AT);
3377 /* Warn if an expression is not a constant. */
3380 check_absolute_expr (ip, ex)
3381 struct mips_cl_insn *ip;
3384 if (ex->X_op == O_big)
3385 as_bad (_("unsupported large constant"));
3386 else if (ex->X_op != O_constant)
3387 as_bad (_("Instruction %s requires absolute expression"), ip->insn_mo->name);
3390 /* Count the leading zeroes by performing a binary chop. This is a
3391 bulky bit of source, but performance is a LOT better for the
3392 majority of values than a simple loop to count the bits:
3393 for (lcnt = 0; (lcnt < 32); lcnt++)
3394 if ((v) & (1 << (31 - lcnt)))
3396 However it is not code size friendly, and the gain will drop a bit
3397 on certain cached systems.
3399 #define COUNT_TOP_ZEROES(v) \
3400 (((v) & ~0xffff) == 0 \
3401 ? ((v) & ~0xff) == 0 \
3402 ? ((v) & ~0xf) == 0 \
3403 ? ((v) & ~0x3) == 0 \
3404 ? ((v) & ~0x1) == 0 \
3409 : ((v) & ~0x7) == 0 \
3412 : ((v) & ~0x3f) == 0 \
3413 ? ((v) & ~0x1f) == 0 \
3416 : ((v) & ~0x7f) == 0 \
3419 : ((v) & ~0xfff) == 0 \
3420 ? ((v) & ~0x3ff) == 0 \
3421 ? ((v) & ~0x1ff) == 0 \
3424 : ((v) & ~0x7ff) == 0 \
3427 : ((v) & ~0x3fff) == 0 \
3428 ? ((v) & ~0x1fff) == 0 \
3431 : ((v) & ~0x7fff) == 0 \
3434 : ((v) & ~0xffffff) == 0 \
3435 ? ((v) & ~0xfffff) == 0 \
3436 ? ((v) & ~0x3ffff) == 0 \
3437 ? ((v) & ~0x1ffff) == 0 \
3440 : ((v) & ~0x7ffff) == 0 \
3443 : ((v) & ~0x3fffff) == 0 \
3444 ? ((v) & ~0x1fffff) == 0 \
3447 : ((v) & ~0x7fffff) == 0 \
3450 : ((v) & ~0xfffffff) == 0 \
3451 ? ((v) & ~0x3ffffff) == 0 \
3452 ? ((v) & ~0x1ffffff) == 0 \
3455 : ((v) & ~0x7ffffff) == 0 \
3458 : ((v) & ~0x3fffffff) == 0 \
3459 ? ((v) & ~0x1fffffff) == 0 \
3462 : ((v) & ~0x7fffffff) == 0 \
3467 * This routine generates the least number of instructions neccessary to load
3468 * an absolute expression value into a register.
3471 load_register (counter, reg, ep, dbl)
3478 expressionS hi32, lo32;
3480 if (ep->X_op != O_big)
3482 assert (ep->X_op == O_constant);
3483 if (ep->X_add_number < 0x8000
3484 && (ep->X_add_number >= 0
3485 || (ep->X_add_number >= -0x8000
3488 || sizeof (ep->X_add_number) > 4))))
3490 /* We can handle 16 bit signed values with an addiu to
3491 $zero. No need to ever use daddiu here, since $zero and
3492 the result are always correct in 32 bit mode. */
3493 macro_build ((char *) NULL, counter, ep, "addiu", "t,r,j", reg, 0,
3494 (int) BFD_RELOC_LO16);
3497 else if (ep->X_add_number >= 0 && ep->X_add_number < 0x10000)
3499 /* We can handle 16 bit unsigned values with an ori to
3501 macro_build ((char *) NULL, counter, ep, "ori", "t,r,i", reg, 0,
3502 (int) BFD_RELOC_LO16);
3505 else if ((IS_SEXT_32BIT_NUM (ep->X_add_number)
3508 || sizeof (ep->X_add_number) > 4
3509 || (ep->X_add_number & 0x80000000) == 0))
3510 || ((HAVE_32BIT_GPRS || ! dbl)
3511 && (ep->X_add_number &~ (offsetT) 0xffffffff) == 0)
3514 && ((ep->X_add_number &~ (offsetT) 0xffffffff)
3515 == ~ (offsetT) 0xffffffff)))
3517 /* 32 bit values require an lui. */
3518 macro_build ((char *) NULL, counter, ep, "lui", "t,u", reg,
3519 (int) BFD_RELOC_HI16);
3520 if ((ep->X_add_number & 0xffff) != 0)
3521 macro_build ((char *) NULL, counter, ep, "ori", "t,r,i", reg, reg,
3522 (int) BFD_RELOC_LO16);
3527 /* The value is larger than 32 bits. */
3529 if (HAVE_32BIT_GPRS)
3531 as_bad (_("Number (0x%lx) larger than 32 bits"),
3532 (unsigned long) ep->X_add_number);
3533 macro_build ((char *) NULL, counter, ep, "addiu", "t,r,j", reg, 0,
3534 (int) BFD_RELOC_LO16);
3538 if (ep->X_op != O_big)
3541 hi32.X_add_number = (valueT) hi32.X_add_number >> 16;
3542 hi32.X_add_number = (valueT) hi32.X_add_number >> 16;
3543 hi32.X_add_number &= 0xffffffff;
3545 lo32.X_add_number &= 0xffffffff;
3549 assert (ep->X_add_number > 2);
3550 if (ep->X_add_number == 3)
3551 generic_bignum[3] = 0;
3552 else if (ep->X_add_number > 4)
3553 as_bad (_("Number larger than 64 bits"));
3554 lo32.X_op = O_constant;
3555 lo32.X_add_number = generic_bignum[0] + (generic_bignum[1] << 16);
3556 hi32.X_op = O_constant;
3557 hi32.X_add_number = generic_bignum[2] + (generic_bignum[3] << 16);
3560 if (hi32.X_add_number == 0)
3565 unsigned long hi, lo;
3567 if (hi32.X_add_number == (offsetT) 0xffffffff)
3569 if ((lo32.X_add_number & 0xffff8000) == 0xffff8000)
3571 macro_build ((char *) NULL, counter, &lo32, "addiu", "t,r,j",
3572 reg, 0, (int) BFD_RELOC_LO16);
3575 if (lo32.X_add_number & 0x80000000)
3577 macro_build ((char *) NULL, counter, &lo32, "lui", "t,u", reg,
3578 (int) BFD_RELOC_HI16);
3579 if (lo32.X_add_number & 0xffff)
3580 macro_build ((char *) NULL, counter, &lo32, "ori", "t,r,i",
3581 reg, reg, (int) BFD_RELOC_LO16);
3586 /* Check for 16bit shifted constant. We know that hi32 is
3587 non-zero, so start the mask on the first bit of the hi32
3592 unsigned long himask, lomask;
3596 himask = 0xffff >> (32 - shift);
3597 lomask = (0xffff << shift) & 0xffffffff;
3601 himask = 0xffff << (shift - 32);
3604 if ((hi32.X_add_number & ~(offsetT) himask) == 0
3605 && (lo32.X_add_number & ~(offsetT) lomask) == 0)
3609 tmp.X_op = O_constant;
3611 tmp.X_add_number = ((hi32.X_add_number << (32 - shift))
3612 | (lo32.X_add_number >> shift));
3614 tmp.X_add_number = hi32.X_add_number >> (shift - 32);
3615 macro_build ((char *) NULL, counter, &tmp,
3616 "ori", "t,r,i", reg, 0,
3617 (int) BFD_RELOC_LO16);
3618 macro_build ((char *) NULL, counter, (expressionS *) NULL,
3619 (shift >= 32) ? "dsll32" : "dsll",
3621 (shift >= 32) ? shift - 32 : shift);
3626 while (shift <= (64 - 16));
3628 /* Find the bit number of the lowest one bit, and store the
3629 shifted value in hi/lo. */
3630 hi = (unsigned long) (hi32.X_add_number & 0xffffffff);
3631 lo = (unsigned long) (lo32.X_add_number & 0xffffffff);
3635 while ((lo & 1) == 0)
3640 lo |= (hi & (((unsigned long) 1 << bit) - 1)) << (32 - bit);
3646 while ((hi & 1) == 0)
3655 /* Optimize if the shifted value is a (power of 2) - 1. */
3656 if ((hi == 0 && ((lo + 1) & lo) == 0)
3657 || (lo == 0xffffffff && ((hi + 1) & hi) == 0))
3659 shift = COUNT_TOP_ZEROES ((unsigned int) hi32.X_add_number);
3664 /* This instruction will set the register to be all
3666 tmp.X_op = O_constant;
3667 tmp.X_add_number = (offsetT) -1;
3668 macro_build ((char *) NULL, counter, &tmp, "addiu", "t,r,j",
3669 reg, 0, (int) BFD_RELOC_LO16);
3673 macro_build ((char *) NULL, counter, (expressionS *) NULL,
3674 (bit >= 32) ? "dsll32" : "dsll",
3676 (bit >= 32) ? bit - 32 : bit);
3678 macro_build ((char *) NULL, counter, (expressionS *) NULL,
3679 (shift >= 32) ? "dsrl32" : "dsrl",
3681 (shift >= 32) ? shift - 32 : shift);
3686 /* Sign extend hi32 before calling load_register, because we can
3687 generally get better code when we load a sign extended value. */
3688 if ((hi32.X_add_number & 0x80000000) != 0)
3689 hi32.X_add_number |= ~(offsetT) 0xffffffff;
3690 load_register (counter, reg, &hi32, 0);
3693 if ((lo32.X_add_number & 0xffff0000) == 0)
3697 macro_build ((char *) NULL, counter, (expressionS *) NULL,
3698 "dsll32", "d,w,<", reg, freg, 0);
3706 if ((freg == 0) && (lo32.X_add_number == (offsetT) 0xffffffff))
3708 macro_build ((char *) NULL, counter, &lo32, "lui", "t,u", reg,
3709 (int) BFD_RELOC_HI16);
3710 macro_build ((char *) NULL, counter, (expressionS *) NULL,
3711 "dsrl32", "d,w,<", reg, reg, 0);
3717 macro_build ((char *) NULL, counter, (expressionS *) NULL, "dsll",
3718 "d,w,<", reg, freg, 16);
3722 mid16.X_add_number >>= 16;
3723 macro_build ((char *) NULL, counter, &mid16, "ori", "t,r,i", reg,
3724 freg, (int) BFD_RELOC_LO16);
3725 macro_build ((char *) NULL, counter, (expressionS *) NULL, "dsll",
3726 "d,w,<", reg, reg, 16);
3729 if ((lo32.X_add_number & 0xffff) != 0)
3730 macro_build ((char *) NULL, counter, &lo32, "ori", "t,r,i", reg, freg,
3731 (int) BFD_RELOC_LO16);
3734 /* Load an address into a register. */
3737 load_address (counter, reg, ep, used_at)
3745 if (ep->X_op != O_constant
3746 && ep->X_op != O_symbol)
3748 as_bad (_("expression too complex"));
3749 ep->X_op = O_constant;
3752 if (ep->X_op == O_constant)
3754 load_register (counter, reg, ep, HAVE_64BIT_ADDRESSES);
3758 if (mips_pic == NO_PIC)
3760 /* If this is a reference to a GP relative symbol, we want
3761 addiu $reg,$gp,<sym> (BFD_RELOC_GPREL16)
3763 lui $reg,<sym> (BFD_RELOC_HI16_S)
3764 addiu $reg,$reg,<sym> (BFD_RELOC_LO16)
3765 If we have an addend, we always use the latter form.
3767 With 64bit address space and a usable $at we want
3768 lui $reg,<sym> (BFD_RELOC_MIPS_HIGHEST)
3769 lui $at,<sym> (BFD_RELOC_HI16_S)
3770 daddiu $reg,<sym> (BFD_RELOC_MIPS_HIGHER)
3771 daddiu $at,<sym> (BFD_RELOC_LO16)
3775 If $at is already in use, we use an path which is suboptimal
3776 on superscalar processors.
3777 lui $reg,<sym> (BFD_RELOC_MIPS_HIGHEST)
3778 daddiu $reg,<sym> (BFD_RELOC_MIPS_HIGHER)
3780 daddiu $reg,<sym> (BFD_RELOC_HI16_S)
3782 daddiu $reg,<sym> (BFD_RELOC_LO16)
3784 if (HAVE_64BIT_ADDRESSES)
3786 /* We don't do GP optimization for now because RELAX_ENCODE can't
3787 hold the data for such large chunks. */
3789 if (*used_at == 0 && ! mips_opts.noat)
3791 macro_build (p, counter, ep, "lui", "t,u",
3792 reg, (int) BFD_RELOC_MIPS_HIGHEST);
3793 macro_build (p, counter, ep, "lui", "t,u",
3794 AT, (int) BFD_RELOC_HI16_S);
3795 macro_build (p, counter, ep, "daddiu", "t,r,j",
3796 reg, reg, (int) BFD_RELOC_MIPS_HIGHER);
3797 macro_build (p, counter, ep, "daddiu", "t,r,j",
3798 AT, AT, (int) BFD_RELOC_LO16);
3799 macro_build (p, counter, (expressionS *) NULL, "dsll32",
3800 "d,w,<", reg, reg, 0);
3801 macro_build (p, counter, (expressionS *) NULL, "daddu",
3802 "d,v,t", reg, reg, AT);
3807 macro_build (p, counter, ep, "lui", "t,u",
3808 reg, (int) BFD_RELOC_MIPS_HIGHEST);
3809 macro_build (p, counter, ep, "daddiu", "t,r,j",
3810 reg, reg, (int) BFD_RELOC_MIPS_HIGHER);
3811 macro_build (p, counter, (expressionS *) NULL, "dsll",
3812 "d,w,<", reg, reg, 16);
3813 macro_build (p, counter, ep, "daddiu", "t,r,j",
3814 reg, reg, (int) BFD_RELOC_HI16_S);
3815 macro_build (p, counter, (expressionS *) NULL, "dsll",
3816 "d,w,<", reg, reg, 16);
3817 macro_build (p, counter, ep, "daddiu", "t,r,j",
3818 reg, reg, (int) BFD_RELOC_LO16);
3823 if ((valueT) ep->X_add_number <= MAX_GPREL_OFFSET
3824 && ! nopic_need_relax (ep->X_add_symbol, 1))
3827 macro_build ((char *) NULL, counter, ep,
3828 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu", "t,r,j",
3829 reg, mips_gp_register, (int) BFD_RELOC_GPREL16);
3830 p = frag_var (rs_machine_dependent, 8, 0,
3831 RELAX_ENCODE (4, 8, 0, 4, 0,
3832 mips_opts.warn_about_macros),
3833 ep->X_add_symbol, 0, NULL);
3835 macro_build_lui (p, counter, ep, reg);
3838 macro_build (p, counter, ep,
3839 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
3840 "t,r,j", reg, reg, (int) BFD_RELOC_LO16);
3843 else if (mips_pic == SVR4_PIC && ! mips_big_got)
3847 /* If this is a reference to an external symbol, we want
3848 lw $reg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
3850 lw $reg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
3852 addiu $reg,$reg,<sym> (BFD_RELOC_LO16)
3853 If we have NewABI, we want
3854 lw $reg,<sym>($gp) (BFD_RELOC_MIPS_GOT_DISP)
3855 If there is a constant, it must be added in after. */
3856 ex.X_add_number = ep->X_add_number;
3857 ep->X_add_number = 0;
3861 macro_build ((char *) NULL, counter, ep,
3862 HAVE_32BIT_ADDRESSES ? "lw" : "ld", "t,o(b)", reg,
3863 (int) BFD_RELOC_MIPS_GOT_DISP, mips_gp_register);
3867 macro_build ((char *) NULL, counter, ep,
3868 HAVE_32BIT_ADDRESSES ? "lw" : "ld", "t,o(b)",
3869 reg, (int) BFD_RELOC_MIPS_GOT16, mips_gp_register);
3870 macro_build ((char *) NULL, counter, (expressionS *) NULL, "nop", "");
3871 p = frag_var (rs_machine_dependent, 4, 0,
3872 RELAX_ENCODE (0, 4, -8, 0, 0, mips_opts.warn_about_macros),
3873 ep->X_add_symbol, (offsetT) 0, (char *) NULL);
3874 macro_build (p, counter, ep,
3875 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
3876 "t,r,j", reg, reg, (int) BFD_RELOC_LO16);
3879 if (ex.X_add_number != 0)
3881 if (ex.X_add_number < -0x8000 || ex.X_add_number >= 0x8000)
3882 as_bad (_("PIC code offset overflow (max 16 signed bits)"));
3883 ex.X_op = O_constant;
3884 macro_build ((char *) NULL, counter, &ex,
3885 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
3886 "t,r,j", reg, reg, (int) BFD_RELOC_LO16);
3889 else if (mips_pic == SVR4_PIC)
3894 /* This is the large GOT case. If this is a reference to an
3895 external symbol, we want
3896 lui $reg,<sym> (BFD_RELOC_MIPS_GOT_HI16)
3898 lw $reg,<sym>($reg) (BFD_RELOC_MIPS_GOT_LO16)
3899 Otherwise, for a reference to a local symbol, we want
3900 lw $reg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
3902 addiu $reg,$reg,<sym> (BFD_RELOC_LO16)
3903 If we have NewABI, we want
3904 lw $reg,<sym>($gp) (BFD_RELOC_MIPS_GOT_PAGE)
3905 addiu $reg,$reg,<sym> (BFD_RELOC_MIPS_GOT_OFST)
3906 If there is a constant, it must be added in after. */
3907 ex.X_add_number = ep->X_add_number;
3908 ep->X_add_number = 0;
3911 macro_build ((char *) NULL, counter, ep,
3912 HAVE_32BIT_ADDRESSES ? "lw" : "ld", "t,o(b)", reg,
3913 (int) BFD_RELOC_MIPS_GOT_PAGE, mips_gp_register);
3914 macro_build (p, counter, ep,
3915 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu", "t,r,j",
3916 reg, reg, (int) BFD_RELOC_MIPS_GOT_OFST);
3920 if (reg_needs_delay (mips_gp_register))
3925 macro_build ((char *) NULL, counter, ep, "lui", "t,u", reg,
3926 (int) BFD_RELOC_MIPS_GOT_HI16);
3927 macro_build ((char *) NULL, counter, (expressionS *) NULL,
3928 HAVE_32BIT_ADDRESSES ? "addu" : "daddu", "d,v,t", reg,
3929 reg, mips_gp_register);
3930 macro_build ((char *) NULL, counter, ep,
3931 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
3932 "t,o(b)", reg, (int) BFD_RELOC_MIPS_GOT_LO16, reg);
3933 p = frag_var (rs_machine_dependent, 12 + off, 0,
3934 RELAX_ENCODE (12, 12 + off, off, 8 + off, 0,
3935 mips_opts.warn_about_macros),
3936 ep->X_add_symbol, 0, NULL);
3939 /* We need a nop before loading from $gp. This special
3940 check is required because the lui which starts the main
3941 instruction stream does not refer to $gp, and so will not
3942 insert the nop which may be required. */
3943 macro_build (p, counter, (expressionS *) NULL, "nop", "");
3946 macro_build (p, counter, ep,
3947 HAVE_32BIT_ADDRESSES ? "lw" : "ld", "t,o(b)", reg,
3948 (int) BFD_RELOC_MIPS_GOT16, mips_gp_register);
3950 macro_build (p, counter, (expressionS *) NULL, "nop", "");
3952 macro_build (p, counter, ep,
3953 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
3954 "t,r,j", reg, reg, (int) BFD_RELOC_LO16);
3957 if (ex.X_add_number != 0)
3959 if (ex.X_add_number < -0x8000 || ex.X_add_number >= 0x8000)
3960 as_bad (_("PIC code offset overflow (max 16 signed bits)"));
3961 ex.X_op = O_constant;
3962 macro_build ((char *) NULL, counter, &ex,
3963 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
3964 "t,r,j", reg, reg, (int) BFD_RELOC_LO16);
3967 else if (mips_pic == EMBEDDED_PIC)
3970 addiu $reg,$gp,<sym> (BFD_RELOC_GPREL16)
3972 macro_build ((char *) NULL, counter, ep,
3973 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
3974 "t,r,j", reg, mips_gp_register, (int) BFD_RELOC_GPREL16);
3980 /* Move the contents of register SOURCE into register DEST. */
3983 move_register (counter, dest, source)
3988 macro_build ((char *) NULL, counter, (expressionS *) NULL,
3989 HAVE_32BIT_GPRS ? "addu" : "daddu",
3990 "d,v,t", dest, source, 0);
3995 * This routine implements the seemingly endless macro or synthesized
3996 * instructions and addressing modes in the mips assembly language. Many
3997 * of these macros are simple and are similar to each other. These could
3998 * probably be handled by some kind of table or grammer aproach instead of
3999 * this verbose method. Others are not simple macros but are more like
4000 * optimizing code generation.
4001 * One interesting optimization is when several store macros appear
4002 * consecutivly that would load AT with the upper half of the same address.
4003 * The ensuing load upper instructions are ommited. This implies some kind
4004 * of global optimization. We currently only optimize within a single macro.
4005 * For many of the load and store macros if the address is specified as a
4006 * constant expression in the first 64k of memory (ie ld $2,0x4000c) we
4007 * first load register 'at' with zero and use it as the base register. The
4008 * mips assembler simply uses register $zero. Just one tiny optimization
4013 struct mips_cl_insn *ip;
4015 register int treg, sreg, dreg, breg;
4031 bfd_reloc_code_real_type r;
4032 int hold_mips_optimize;
4034 assert (! mips_opts.mips16);
4036 treg = (ip->insn_opcode >> 16) & 0x1f;
4037 dreg = (ip->insn_opcode >> 11) & 0x1f;
4038 sreg = breg = (ip->insn_opcode >> 21) & 0x1f;
4039 mask = ip->insn_mo->mask;
4041 expr1.X_op = O_constant;
4042 expr1.X_op_symbol = NULL;
4043 expr1.X_add_symbol = NULL;
4044 expr1.X_add_number = 1;
4056 mips_emit_delays (true);
4057 ++mips_opts.noreorder;
4058 mips_any_noreorder = 1;
4060 expr1.X_add_number = 8;
4061 macro_build ((char *) NULL, &icnt, &expr1, "bgez", "s,p", sreg);
4063 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "",
4066 move_register (&icnt, dreg, sreg);
4067 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
4068 dbl ? "dsub" : "sub", "d,v,t", dreg, 0, sreg);
4070 --mips_opts.noreorder;
4091 if (imm_expr.X_op == O_constant
4092 && imm_expr.X_add_number >= -0x8000
4093 && imm_expr.X_add_number < 0x8000)
4095 macro_build ((char *) NULL, &icnt, &imm_expr, s, "t,r,j", treg, sreg,
4096 (int) BFD_RELOC_LO16);
4099 load_register (&icnt, AT, &imm_expr, dbl);
4100 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s2, "d,v,t",
4120 if (imm_expr.X_op == O_constant
4121 && imm_expr.X_add_number >= 0
4122 && imm_expr.X_add_number < 0x10000)
4124 if (mask != M_NOR_I)
4125 macro_build ((char *) NULL, &icnt, &imm_expr, s, "t,r,i", treg,
4126 sreg, (int) BFD_RELOC_LO16);
4129 macro_build ((char *) NULL, &icnt, &imm_expr, "ori", "t,r,i",
4130 treg, sreg, (int) BFD_RELOC_LO16);
4131 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nor",
4132 "d,v,t", treg, treg, 0);
4137 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_GPRS);
4138 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s2, "d,v,t",
4156 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
4158 macro_build ((char *) NULL, &icnt, &offset_expr, s, "s,t,p", sreg,
4162 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_GPRS);
4163 macro_build ((char *) NULL, &icnt, &offset_expr, s, "s,t,p", sreg, AT);
4171 macro_build ((char *) NULL, &icnt, &offset_expr,
4172 likely ? "bgezl" : "bgez", "s,p", sreg);
4177 macro_build ((char *) NULL, &icnt, &offset_expr,
4178 likely ? "blezl" : "blez", "s,p", treg);
4181 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "slt", "d,v,t",
4183 macro_build ((char *) NULL, &icnt, &offset_expr,
4184 likely ? "beql" : "beq", "s,t,p", AT, 0);
4190 /* check for > max integer */
4191 maxnum = 0x7fffffff;
4192 if (HAVE_64BIT_GPRS && sizeof (maxnum) > 4)
4199 if (imm_expr.X_op == O_constant
4200 && imm_expr.X_add_number >= maxnum
4201 && (HAVE_32BIT_GPRS || sizeof (maxnum) > 4))
4204 /* result is always false */
4208 as_warn (_("Branch %s is always false (nop)"),
4210 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop",
4216 as_warn (_("Branch likely %s is always false"),
4218 macro_build ((char *) NULL, &icnt, &offset_expr, "bnel",
4223 if (imm_expr.X_op != O_constant)
4224 as_bad (_("Unsupported large constant"));
4225 ++imm_expr.X_add_number;
4229 if (mask == M_BGEL_I)
4231 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
4233 macro_build ((char *) NULL, &icnt, &offset_expr,
4234 likely ? "bgezl" : "bgez", "s,p", sreg);
4237 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 1)
4239 macro_build ((char *) NULL, &icnt, &offset_expr,
4240 likely ? "bgtzl" : "bgtz", "s,p", sreg);
4243 maxnum = 0x7fffffff;
4244 if (HAVE_64BIT_GPRS && sizeof (maxnum) > 4)
4251 maxnum = - maxnum - 1;
4252 if (imm_expr.X_op == O_constant
4253 && imm_expr.X_add_number <= maxnum
4254 && (HAVE_32BIT_GPRS || sizeof (maxnum) > 4))
4257 /* result is always true */
4258 as_warn (_("Branch %s is always true"), ip->insn_mo->name);
4259 macro_build ((char *) NULL, &icnt, &offset_expr, "b", "p");
4262 set_at (&icnt, sreg, 0);
4263 macro_build ((char *) NULL, &icnt, &offset_expr,
4264 likely ? "beql" : "beq", "s,t,p", AT, 0);
4274 macro_build ((char *) NULL, &icnt, &offset_expr,
4275 likely ? "beql" : "beq", "s,t,p", 0, treg);
4278 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sltu",
4279 "d,v,t", AT, sreg, treg);
4280 macro_build ((char *) NULL, &icnt, &offset_expr,
4281 likely ? "beql" : "beq", "s,t,p", AT, 0);
4289 && imm_expr.X_op == O_constant
4290 && imm_expr.X_add_number == (offsetT) 0xffffffff))
4292 if (imm_expr.X_op != O_constant)
4293 as_bad (_("Unsupported large constant"));
4294 ++imm_expr.X_add_number;
4298 if (mask == M_BGEUL_I)
4300 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
4302 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 1)
4304 macro_build ((char *) NULL, &icnt, &offset_expr,
4305 likely ? "bnel" : "bne", "s,t,p", sreg, 0);
4308 set_at (&icnt, sreg, 1);
4309 macro_build ((char *) NULL, &icnt, &offset_expr,
4310 likely ? "beql" : "beq", "s,t,p", AT, 0);
4318 macro_build ((char *) NULL, &icnt, &offset_expr,
4319 likely ? "bgtzl" : "bgtz", "s,p", sreg);
4324 macro_build ((char *) NULL, &icnt, &offset_expr,
4325 likely ? "bltzl" : "bltz", "s,p", treg);
4328 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "slt", "d,v,t",
4330 macro_build ((char *) NULL, &icnt, &offset_expr,
4331 likely ? "bnel" : "bne", "s,t,p", AT, 0);
4339 macro_build ((char *) NULL, &icnt, &offset_expr,
4340 likely ? "bnel" : "bne", "s,t,p", sreg, 0);
4345 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sltu",
4346 "d,v,t", AT, treg, sreg);
4347 macro_build ((char *) NULL, &icnt, &offset_expr,
4348 likely ? "bnel" : "bne", "s,t,p", AT, 0);
4356 macro_build ((char *) NULL, &icnt, &offset_expr,
4357 likely ? "blezl" : "blez", "s,p", sreg);
4362 macro_build ((char *) NULL, &icnt, &offset_expr,
4363 likely ? "bgezl" : "bgez", "s,p", treg);
4366 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "slt", "d,v,t",
4368 macro_build ((char *) NULL, &icnt, &offset_expr,
4369 likely ? "beql" : "beq", "s,t,p", AT, 0);
4375 maxnum = 0x7fffffff;
4376 if (HAVE_64BIT_GPRS && sizeof (maxnum) > 4)
4383 if (imm_expr.X_op == O_constant
4384 && imm_expr.X_add_number >= maxnum
4385 && (HAVE_32BIT_GPRS || sizeof (maxnum) > 4))
4387 if (imm_expr.X_op != O_constant)
4388 as_bad (_("Unsupported large constant"));
4389 ++imm_expr.X_add_number;
4393 if (mask == M_BLTL_I)
4395 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
4397 macro_build ((char *) NULL, &icnt, &offset_expr,
4398 likely ? "bltzl" : "bltz", "s,p", sreg);
4401 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 1)
4403 macro_build ((char *) NULL, &icnt, &offset_expr,
4404 likely ? "blezl" : "blez", "s,p", sreg);
4407 set_at (&icnt, sreg, 0);
4408 macro_build ((char *) NULL, &icnt, &offset_expr,
4409 likely ? "bnel" : "bne", "s,t,p", AT, 0);
4417 macro_build ((char *) NULL, &icnt, &offset_expr,
4418 likely ? "beql" : "beq", "s,t,p", sreg, 0);
4423 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sltu",
4424 "d,v,t", AT, treg, sreg);
4425 macro_build ((char *) NULL, &icnt, &offset_expr,
4426 likely ? "beql" : "beq", "s,t,p", AT, 0);
4434 && imm_expr.X_op == O_constant
4435 && imm_expr.X_add_number == (offsetT) 0xffffffff))
4437 if (imm_expr.X_op != O_constant)
4438 as_bad (_("Unsupported large constant"));
4439 ++imm_expr.X_add_number;
4443 if (mask == M_BLTUL_I)
4445 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
4447 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 1)
4449 macro_build ((char *) NULL, &icnt, &offset_expr,
4450 likely ? "beql" : "beq",
4454 set_at (&icnt, sreg, 1);
4455 macro_build ((char *) NULL, &icnt, &offset_expr,
4456 likely ? "bnel" : "bne", "s,t,p", AT, 0);
4464 macro_build ((char *) NULL, &icnt, &offset_expr,
4465 likely ? "bltzl" : "bltz", "s,p", sreg);
4470 macro_build ((char *) NULL, &icnt, &offset_expr,
4471 likely ? "bgtzl" : "bgtz", "s,p", treg);
4474 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "slt", "d,v,t",
4476 macro_build ((char *) NULL, &icnt, &offset_expr,
4477 likely ? "bnel" : "bne", "s,t,p", AT, 0);
4487 macro_build ((char *) NULL, &icnt, &offset_expr,
4488 likely ? "bnel" : "bne", "s,t,p", 0, treg);
4491 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sltu",
4494 macro_build ((char *) NULL, &icnt, &offset_expr,
4495 likely ? "bnel" : "bne", "s,t,p", AT, 0);
4510 as_warn (_("Divide by zero."));
4512 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "teq",
4515 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "break",
4520 mips_emit_delays (true);
4521 ++mips_opts.noreorder;
4522 mips_any_noreorder = 1;
4525 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "teq",
4526 "s,t,q", treg, 0, 7);
4527 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
4528 dbl ? "ddiv" : "div", "z,s,t", sreg, treg);
4532 expr1.X_add_number = 8;
4533 macro_build ((char *) NULL, &icnt, &expr1, "bne", "s,t,p", treg, 0);
4534 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
4535 dbl ? "ddiv" : "div", "z,s,t", sreg, treg);
4536 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "break",
4539 expr1.X_add_number = -1;
4540 macro_build ((char *) NULL, &icnt, &expr1,
4541 dbl ? "daddiu" : "addiu",
4542 "t,r,j", AT, 0, (int) BFD_RELOC_LO16);
4543 expr1.X_add_number = mips_trap ? (dbl ? 12 : 8) : (dbl ? 20 : 16);
4544 macro_build ((char *) NULL, &icnt, &expr1, "bne", "s,t,p", treg, AT);
4547 expr1.X_add_number = 1;
4548 macro_build ((char *) NULL, &icnt, &expr1, "daddiu", "t,r,j", AT, 0,
4549 (int) BFD_RELOC_LO16);
4550 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "dsll32",
4551 "d,w,<", AT, AT, 31);
4555 expr1.X_add_number = 0x80000000;
4556 macro_build ((char *) NULL, &icnt, &expr1, "lui", "t,u", AT,
4557 (int) BFD_RELOC_HI16);
4561 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "teq",
4562 "s,t,q", sreg, AT, 6);
4563 /* We want to close the noreorder block as soon as possible, so
4564 that later insns are available for delay slot filling. */
4565 --mips_opts.noreorder;
4569 expr1.X_add_number = 8;
4570 macro_build ((char *) NULL, &icnt, &expr1, "bne", "s,t,p", sreg, AT);
4571 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "",
4574 /* We want to close the noreorder block as soon as possible, so
4575 that later insns are available for delay slot filling. */
4576 --mips_opts.noreorder;
4578 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "break",
4581 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "d", dreg);
4620 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
4622 as_warn (_("Divide by zero."));
4624 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "teq",
4627 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "break",
4631 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 1)
4633 if (strcmp (s2, "mflo") == 0)
4634 move_register (&icnt, dreg, sreg);
4636 move_register (&icnt, dreg, 0);
4639 if (imm_expr.X_op == O_constant
4640 && imm_expr.X_add_number == -1
4641 && s[strlen (s) - 1] != 'u')
4643 if (strcmp (s2, "mflo") == 0)
4645 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
4646 dbl ? "dneg" : "neg", "d,w", dreg, sreg);
4649 move_register (&icnt, dreg, 0);
4653 load_register (&icnt, AT, &imm_expr, dbl);
4654 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "z,s,t",
4656 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s2, "d", dreg);
4675 mips_emit_delays (true);
4676 ++mips_opts.noreorder;
4677 mips_any_noreorder = 1;
4680 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "teq",
4681 "s,t,q", treg, 0, 7);
4682 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "z,s,t",
4684 /* We want to close the noreorder block as soon as possible, so
4685 that later insns are available for delay slot filling. */
4686 --mips_opts.noreorder;
4690 expr1.X_add_number = 8;
4691 macro_build ((char *) NULL, &icnt, &expr1, "bne", "s,t,p", treg, 0);
4692 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "z,s,t",
4695 /* We want to close the noreorder block as soon as possible, so
4696 that later insns are available for delay slot filling. */
4697 --mips_opts.noreorder;
4698 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "break",
4701 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s2, "d", dreg);
4707 /* Load the address of a symbol into a register. If breg is not
4708 zero, we then add a base register to it. */
4710 if (dbl && HAVE_32BIT_GPRS)
4711 as_warn (_("dla used to load 32-bit register"));
4713 if (! dbl && HAVE_64BIT_OBJECTS)
4714 as_warn (_("la used to load 64-bit address"));
4716 if (offset_expr.X_op == O_constant
4717 && offset_expr.X_add_number >= -0x8000
4718 && offset_expr.X_add_number < 0x8000)
4720 macro_build ((char *) NULL, &icnt, &offset_expr,
4721 (dbl || HAVE_64BIT_ADDRESSES) ? "daddiu" : "addiu",
4722 "t,r,j", treg, sreg, (int) BFD_RELOC_LO16);
4737 /* When generating embedded PIC code, we permit expressions of
4740 la $treg,foo-bar($breg)
4741 where bar is an address in the current section. These are used
4742 when getting the addresses of functions. We don't permit
4743 X_add_number to be non-zero, because if the symbol is
4744 external the relaxing code needs to know that any addend is
4745 purely the offset to X_op_symbol. */
4746 if (mips_pic == EMBEDDED_PIC
4747 && offset_expr.X_op == O_subtract
4748 && (symbol_constant_p (offset_expr.X_op_symbol)
4749 ? S_GET_SEGMENT (offset_expr.X_op_symbol) == now_seg
4750 : (symbol_equated_p (offset_expr.X_op_symbol)
4752 (symbol_get_value_expression (offset_expr.X_op_symbol)
4755 && (offset_expr.X_add_number == 0
4756 || OUTPUT_FLAVOR == bfd_target_elf_flavour))
4762 macro_build ((char *) NULL, &icnt, &offset_expr, "lui", "t,u",
4763 tempreg, (int) BFD_RELOC_PCREL_HI16_S);
4767 macro_build ((char *) NULL, &icnt, &offset_expr, "lui", "t,u",
4768 tempreg, (int) BFD_RELOC_PCREL_HI16_S);
4769 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
4770 (dbl || HAVE_64BIT_ADDRESSES) ? "daddu" : "addu",
4771 "d,v,t", tempreg, tempreg, breg);
4773 macro_build ((char *) NULL, &icnt, &offset_expr,
4774 (dbl || HAVE_64BIT_ADDRESSES) ? "daddiu" : "addiu",
4775 "t,r,j", treg, tempreg, (int) BFD_RELOC_PCREL_LO16);
4781 if (offset_expr.X_op != O_symbol
4782 && offset_expr.X_op != O_constant)
4784 as_bad (_("expression too complex"));
4785 offset_expr.X_op = O_constant;
4788 if (offset_expr.X_op == O_constant)
4789 load_register (&icnt, tempreg, &offset_expr,
4790 ((mips_pic == EMBEDDED_PIC || mips_pic == NO_PIC)
4791 ? (dbl || HAVE_64BIT_ADDRESSES)
4792 : HAVE_64BIT_ADDRESSES));
4793 else if (mips_pic == NO_PIC)
4795 /* If this is a reference to a GP relative symbol, we want
4796 addiu $tempreg,$gp,<sym> (BFD_RELOC_GPREL16)
4798 lui $tempreg,<sym> (BFD_RELOC_HI16_S)
4799 addiu $tempreg,$tempreg,<sym> (BFD_RELOC_LO16)
4800 If we have a constant, we need two instructions anyhow,
4801 so we may as well always use the latter form.
4803 With 64bit address space and a usable $at we want
4804 lui $tempreg,<sym> (BFD_RELOC_MIPS_HIGHEST)
4805 lui $at,<sym> (BFD_RELOC_HI16_S)
4806 daddiu $tempreg,<sym> (BFD_RELOC_MIPS_HIGHER)
4807 daddiu $at,<sym> (BFD_RELOC_LO16)
4809 daddu $tempreg,$tempreg,$at
4811 If $at is already in use, we use an path which is suboptimal
4812 on superscalar processors.
4813 lui $tempreg,<sym> (BFD_RELOC_MIPS_HIGHEST)
4814 daddiu $tempreg,<sym> (BFD_RELOC_MIPS_HIGHER)
4816 daddiu $tempreg,<sym> (BFD_RELOC_HI16_S)
4818 daddiu $tempreg,<sym> (BFD_RELOC_LO16)
4821 if (HAVE_64BIT_ADDRESSES)
4823 /* We don't do GP optimization for now because RELAX_ENCODE can't
4824 hold the data for such large chunks. */
4826 if (used_at == 0 && ! mips_opts.noat)
4828 macro_build (p, &icnt, &offset_expr, "lui", "t,u",
4829 tempreg, (int) BFD_RELOC_MIPS_HIGHEST);
4830 macro_build (p, &icnt, &offset_expr, "lui", "t,u",
4831 AT, (int) BFD_RELOC_HI16_S);
4832 macro_build (p, &icnt, &offset_expr, "daddiu", "t,r,j",
4833 tempreg, tempreg, (int) BFD_RELOC_MIPS_HIGHER);
4834 macro_build (p, &icnt, &offset_expr, "daddiu", "t,r,j",
4835 AT, AT, (int) BFD_RELOC_LO16);
4836 macro_build (p, &icnt, (expressionS *) NULL, "dsll32",
4837 "d,w,<", tempreg, tempreg, 0);
4838 macro_build (p, &icnt, (expressionS *) NULL, "daddu",
4839 "d,v,t", tempreg, tempreg, AT);
4844 macro_build (p, &icnt, &offset_expr, "lui", "t,u",
4845 tempreg, (int) BFD_RELOC_MIPS_HIGHEST);
4846 macro_build (p, &icnt, &offset_expr, "daddiu", "t,r,j",
4847 tempreg, tempreg, (int) BFD_RELOC_MIPS_HIGHER);
4848 macro_build (p, &icnt, (expressionS *) NULL, "dsll", "d,w,<",
4849 tempreg, tempreg, 16);
4850 macro_build (p, &icnt, &offset_expr, "daddiu", "t,r,j",
4851 tempreg, tempreg, (int) BFD_RELOC_HI16_S);
4852 macro_build (p, &icnt, (expressionS *) NULL, "dsll", "d,w,<",
4853 tempreg, tempreg, 16);
4854 macro_build (p, &icnt, &offset_expr, "daddiu", "t,r,j",
4855 tempreg, tempreg, (int) BFD_RELOC_LO16);
4860 if ((valueT) offset_expr.X_add_number <= MAX_GPREL_OFFSET
4861 && ! nopic_need_relax (offset_expr.X_add_symbol, 1))
4864 macro_build ((char *) NULL, &icnt, &offset_expr, "addiu",
4865 "t,r,j", tempreg, mips_gp_register,
4866 (int) BFD_RELOC_GPREL16);
4867 p = frag_var (rs_machine_dependent, 8, 0,
4868 RELAX_ENCODE (4, 8, 0, 4, 0,
4869 mips_opts.warn_about_macros),
4870 offset_expr.X_add_symbol, 0, NULL);
4872 macro_build_lui (p, &icnt, &offset_expr, tempreg);
4875 macro_build (p, &icnt, &offset_expr, "addiu",
4876 "t,r,j", tempreg, tempreg, (int) BFD_RELOC_LO16);
4879 else if (mips_pic == SVR4_PIC && ! mips_big_got)
4881 int lw_reloc_type = (int) BFD_RELOC_MIPS_GOT16;
4883 /* If this is a reference to an external symbol, and there
4884 is no constant, we want
4885 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
4886 or if tempreg is PIC_CALL_REG
4887 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_CALL16)
4888 For a local symbol, we want
4889 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
4891 addiu $tempreg,$tempreg,<sym> (BFD_RELOC_LO16)
4893 If we have a small constant, and this is a reference to
4894 an external symbol, we want
4895 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
4897 addiu $tempreg,$tempreg,<constant>
4898 For a local symbol, we want the same instruction
4899 sequence, but we output a BFD_RELOC_LO16 reloc on the
4902 If we have a large constant, and this is a reference to
4903 an external symbol, we want
4904 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
4905 lui $at,<hiconstant>
4906 addiu $at,$at,<loconstant>
4907 addu $tempreg,$tempreg,$at
4908 For a local symbol, we want the same instruction
4909 sequence, but we output a BFD_RELOC_LO16 reloc on the
4912 For NewABI, we want for local or external data addresses
4913 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT_DISP)
4914 For a local function symbol, we want
4915 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT_PAGE)
4917 addiu $tempreg,$tempreg,<sym> (BFD_RELOC_MIPS_GOT_OFST)
4920 expr1.X_add_number = offset_expr.X_add_number;
4921 offset_expr.X_add_number = 0;
4923 if (expr1.X_add_number == 0 && tempreg == PIC_CALL_REG)
4924 lw_reloc_type = (int) BFD_RELOC_MIPS_CALL16;
4925 else if (HAVE_NEWABI)
4926 lw_reloc_type = (int) BFD_RELOC_MIPS_GOT_DISP;
4927 macro_build ((char *) NULL, &icnt, &offset_expr,
4928 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
4929 "t,o(b)", tempreg, lw_reloc_type, mips_gp_register);
4930 if (expr1.X_add_number == 0)
4939 /* We're going to put in an addu instruction using
4940 tempreg, so we may as well insert the nop right
4942 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
4946 p = frag_var (rs_machine_dependent, 8 - off, 0,
4947 RELAX_ENCODE (0, 8 - off, -4 - off, 4 - off, 0,
4949 ? mips_opts.warn_about_macros
4951 offset_expr.X_add_symbol, 0, NULL);
4954 macro_build (p, &icnt, (expressionS *) NULL, "nop", "");
4957 macro_build (p, &icnt, &expr1,
4958 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
4959 "t,r,j", tempreg, tempreg, (int) BFD_RELOC_LO16);
4960 /* FIXME: If breg == 0, and the next instruction uses
4961 $tempreg, then if this variant case is used an extra
4962 nop will be generated. */
4964 else if (expr1.X_add_number >= -0x8000
4965 && expr1.X_add_number < 0x8000)
4967 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
4969 macro_build ((char *) NULL, &icnt, &expr1,
4970 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
4971 "t,r,j", tempreg, tempreg, (int) BFD_RELOC_LO16);
4972 frag_var (rs_machine_dependent, 0, 0,
4973 RELAX_ENCODE (0, 0, -12, -4, 0, 0),
4974 offset_expr.X_add_symbol, 0, NULL);
4980 /* If we are going to add in a base register, and the
4981 target register and the base register are the same,
4982 then we are using AT as a temporary register. Since
4983 we want to load the constant into AT, we add our
4984 current AT (from the global offset table) and the
4985 register into the register now, and pretend we were
4986 not using a base register. */
4991 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
4993 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
4994 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
4995 "d,v,t", treg, AT, breg);
5001 /* Set mips_optimize around the lui instruction to avoid
5002 inserting an unnecessary nop after the lw. */
5003 hold_mips_optimize = mips_optimize;
5005 macro_build_lui (NULL, &icnt, &expr1, AT);
5006 mips_optimize = hold_mips_optimize;
5008 macro_build ((char *) NULL, &icnt, &expr1,
5009 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
5010 "t,r,j", AT, AT, (int) BFD_RELOC_LO16);
5011 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5012 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
5013 "d,v,t", tempreg, tempreg, AT);
5014 frag_var (rs_machine_dependent, 0, 0,
5015 RELAX_ENCODE (0, 0, -16 + off1, -8, 0, 0),
5016 offset_expr.X_add_symbol, 0, NULL);
5020 else if (mips_pic == SVR4_PIC)
5024 int lui_reloc_type = (int) BFD_RELOC_MIPS_GOT_HI16;
5025 int lw_reloc_type = (int) BFD_RELOC_MIPS_GOT_LO16;
5026 int local_reloc_type = (int) BFD_RELOC_MIPS_GOT16;
5028 /* This is the large GOT case. If this is a reference to an
5029 external symbol, and there is no constant, we want
5030 lui $tempreg,<sym> (BFD_RELOC_MIPS_GOT_HI16)
5031 addu $tempreg,$tempreg,$gp
5032 lw $tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_LO16)
5033 or if tempreg is PIC_CALL_REG
5034 lui $tempreg,<sym> (BFD_RELOC_MIPS_CALL_HI16)
5035 addu $tempreg,$tempreg,$gp
5036 lw $tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_CALL_LO16)
5037 For a local symbol, we want
5038 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
5040 addiu $tempreg,$tempreg,<sym> (BFD_RELOC_LO16)
5042 If we have a small constant, and this is a reference to
5043 an external symbol, we want
5044 lui $tempreg,<sym> (BFD_RELOC_MIPS_GOT_HI16)
5045 addu $tempreg,$tempreg,$gp
5046 lw $tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_LO16)
5048 addiu $tempreg,$tempreg,<constant>
5049 For a local symbol, we want
5050 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
5052 addiu $tempreg,$tempreg,<constant> (BFD_RELOC_LO16)
5054 If we have a large constant, and this is a reference to
5055 an external symbol, we want
5056 lui $tempreg,<sym> (BFD_RELOC_MIPS_GOT_HI16)
5057 addu $tempreg,$tempreg,$gp
5058 lw $tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_LO16)
5059 lui $at,<hiconstant>
5060 addiu $at,$at,<loconstant>
5061 addu $tempreg,$tempreg,$at
5062 For a local symbol, we want
5063 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
5064 lui $at,<hiconstant>
5065 addiu $at,$at,<loconstant> (BFD_RELOC_LO16)
5066 addu $tempreg,$tempreg,$at
5068 For NewABI, we want for local data addresses
5069 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT_DISP)
5072 expr1.X_add_number = offset_expr.X_add_number;
5073 offset_expr.X_add_number = 0;
5075 if (reg_needs_delay (mips_gp_register))
5079 if (expr1.X_add_number == 0 && tempreg == PIC_CALL_REG)
5081 lui_reloc_type = (int) BFD_RELOC_MIPS_CALL_HI16;
5082 lw_reloc_type = (int) BFD_RELOC_MIPS_CALL_LO16;
5084 macro_build ((char *) NULL, &icnt, &offset_expr, "lui", "t,u",
5085 tempreg, lui_reloc_type);
5086 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5087 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
5088 "d,v,t", tempreg, tempreg, mips_gp_register);
5089 macro_build ((char *) NULL, &icnt, &offset_expr,
5090 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
5091 "t,o(b)", tempreg, lw_reloc_type, tempreg);
5092 if (expr1.X_add_number == 0)
5100 /* We're going to put in an addu instruction using
5101 tempreg, so we may as well insert the nop right
5103 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5108 p = frag_var (rs_machine_dependent, 12 + gpdel, 0,
5109 RELAX_ENCODE (12 + off, 12 + gpdel, gpdel,
5112 ? mips_opts.warn_about_macros
5114 offset_expr.X_add_symbol, 0, NULL);
5116 else if (expr1.X_add_number >= -0x8000
5117 && expr1.X_add_number < 0x8000)
5119 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5121 macro_build ((char *) NULL, &icnt, &expr1,
5122 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
5123 "t,r,j", tempreg, tempreg, (int) BFD_RELOC_LO16);
5125 p = frag_var (rs_machine_dependent, 12 + gpdel, 0,
5126 RELAX_ENCODE (20, 12 + gpdel, gpdel, 8 + gpdel, 0,
5128 ? mips_opts.warn_about_macros
5130 offset_expr.X_add_symbol, 0, NULL);
5136 /* If we are going to add in a base register, and the
5137 target register and the base register are the same,
5138 then we are using AT as a temporary register. Since
5139 we want to load the constant into AT, we add our
5140 current AT (from the global offset table) and the
5141 register into the register now, and pretend we were
5142 not using a base register. */
5150 assert (tempreg == AT);
5151 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5153 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5154 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
5155 "d,v,t", treg, AT, breg);
5160 /* Set mips_optimize around the lui instruction to avoid
5161 inserting an unnecessary nop after the lw. */
5162 hold_mips_optimize = mips_optimize;
5164 macro_build_lui (NULL, &icnt, &expr1, AT);
5165 mips_optimize = hold_mips_optimize;
5167 macro_build ((char *) NULL, &icnt, &expr1,
5168 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
5169 "t,r,j", AT, AT, (int) BFD_RELOC_LO16);
5170 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5171 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
5172 "d,v,t", dreg, dreg, AT);
5174 p = frag_var (rs_machine_dependent, 16 + gpdel + adj, 0,
5175 RELAX_ENCODE (24 + adj, 16 + gpdel + adj, gpdel,
5178 ? mips_opts.warn_about_macros
5180 offset_expr.X_add_symbol, 0, NULL);
5187 /* This is needed because this instruction uses $gp, but
5188 the first instruction on the main stream does not. */
5189 macro_build (p, &icnt, (expressionS *) NULL, "nop", "");
5194 local_reloc_type = (int) BFD_RELOC_MIPS_GOT_DISP;
5195 macro_build (p, &icnt, &offset_expr,
5196 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
5201 if (expr1.X_add_number == 0 && HAVE_NEWABI)
5203 /* BFD_RELOC_MIPS_GOT_DISP is sufficient for newabi */
5206 if (expr1.X_add_number >= -0x8000
5207 && expr1.X_add_number < 0x8000)
5209 macro_build (p, &icnt, (expressionS *) NULL, "nop", "");
5211 macro_build (p, &icnt, &expr1,
5212 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
5213 "t,r,j", tempreg, tempreg, (int) BFD_RELOC_LO16);
5214 /* FIXME: If add_number is 0, and there was no base
5215 register, the external symbol case ended with a load,
5216 so if the symbol turns out to not be external, and
5217 the next instruction uses tempreg, an unnecessary nop
5218 will be inserted. */
5224 /* We must add in the base register now, as in the
5225 external symbol case. */
5226 assert (tempreg == AT);
5227 macro_build (p, &icnt, (expressionS *) NULL, "nop", "");
5229 macro_build (p, &icnt, (expressionS *) NULL,
5230 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
5231 "d,v,t", treg, AT, breg);
5234 /* We set breg to 0 because we have arranged to add
5235 it in in both cases. */
5239 macro_build_lui (p, &icnt, &expr1, AT);
5241 macro_build (p, &icnt, &expr1,
5242 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
5243 "t,r,j", AT, AT, (int) BFD_RELOC_LO16);
5245 macro_build (p, &icnt, (expressionS *) NULL,
5246 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
5247 "d,v,t", tempreg, tempreg, AT);
5251 else if (mips_pic == EMBEDDED_PIC)
5254 addiu $tempreg,$gp,<sym> (BFD_RELOC_GPREL16)
5256 macro_build ((char *) NULL, &icnt, &offset_expr,
5257 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu", "t,r,j",
5258 tempreg, mips_gp_register, (int) BFD_RELOC_GPREL16);
5267 if (mips_pic == EMBEDDED_PIC || mips_pic == NO_PIC)
5268 s = (dbl || HAVE_64BIT_ADDRESSES) ? "daddu" : "addu";
5270 s = HAVE_64BIT_ADDRESSES ? "daddu" : "addu";
5272 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s,
5273 "d,v,t", treg, tempreg, breg);
5282 /* The j instruction may not be used in PIC code, since it
5283 requires an absolute address. We convert it to a b
5285 if (mips_pic == NO_PIC)
5286 macro_build ((char *) NULL, &icnt, &offset_expr, "j", "a");
5288 macro_build ((char *) NULL, &icnt, &offset_expr, "b", "p");
5291 /* The jal instructions must be handled as macros because when
5292 generating PIC code they expand to multi-instruction
5293 sequences. Normally they are simple instructions. */
5298 if (mips_pic == NO_PIC
5299 || mips_pic == EMBEDDED_PIC)
5300 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "jalr",
5302 else if (mips_pic == SVR4_PIC)
5304 if (sreg != PIC_CALL_REG)
5305 as_warn (_("MIPS PIC call to register other than $25"));
5307 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "jalr",
5311 if (mips_cprestore_offset < 0)
5312 as_warn (_("No .cprestore pseudo-op used in PIC code"));
5315 if (! mips_frame_reg_valid)
5317 as_warn (_("No .frame pseudo-op used in PIC code"));
5318 /* Quiet this warning. */
5319 mips_frame_reg_valid = 1;
5321 if (! mips_cprestore_valid)
5323 as_warn (_("No .cprestore pseudo-op used in PIC code"));
5324 /* Quiet this warning. */
5325 mips_cprestore_valid = 1;
5327 expr1.X_add_number = mips_cprestore_offset;
5328 macro_build_ldst_constoffset ((char *) NULL, &icnt, &expr1,
5329 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
5330 mips_gp_register, mips_frame_reg);
5340 if (mips_pic == NO_PIC)
5341 macro_build ((char *) NULL, &icnt, &offset_expr, "jal", "a");
5342 else if (mips_pic == SVR4_PIC)
5346 /* If this is a reference to an external symbol, and we are
5347 using a small GOT, we want
5348 lw $25,<sym>($gp) (BFD_RELOC_MIPS_CALL16)
5352 lw $gp,cprestore($sp)
5353 The cprestore value is set using the .cprestore
5354 pseudo-op. If we are using a big GOT, we want
5355 lui $25,<sym> (BFD_RELOC_MIPS_CALL_HI16)
5357 lw $25,<sym>($25) (BFD_RELOC_MIPS_CALL_LO16)
5361 lw $gp,cprestore($sp)
5362 If the symbol is not external, we want
5363 lw $25,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
5365 addiu $25,$25,<sym> (BFD_RELOC_LO16)
5368 lw $gp,cprestore($sp)
5370 lw $25,<sym>($gp) (BFD_RELOC_MIPS_GOT_DISP)
5371 jalr $ra,$25 (BFD_RELOC_MIPS_JALR)
5375 macro_build ((char *) NULL, &icnt, &offset_expr,
5376 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
5377 "t,o(b)", PIC_CALL_REG,
5378 (int) BFD_RELOC_MIPS_GOT_DISP, mips_gp_register);
5379 macro_build_jalr (icnt, &offset_expr);
5386 macro_build ((char *) NULL, &icnt, &offset_expr,
5387 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
5388 "t,o(b)", PIC_CALL_REG,
5389 (int) BFD_RELOC_MIPS_CALL16, mips_gp_register);
5390 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5392 p = frag_var (rs_machine_dependent, 4, 0,
5393 RELAX_ENCODE (0, 4, -8, 0, 0, 0),
5394 offset_expr.X_add_symbol, 0, NULL);
5400 if (reg_needs_delay (mips_gp_register))
5404 macro_build ((char *) NULL, &icnt, &offset_expr, "lui",
5405 "t,u", PIC_CALL_REG,
5406 (int) BFD_RELOC_MIPS_CALL_HI16);
5407 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5408 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
5409 "d,v,t", PIC_CALL_REG, PIC_CALL_REG,
5411 macro_build ((char *) NULL, &icnt, &offset_expr,
5412 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
5413 "t,o(b)", PIC_CALL_REG,
5414 (int) BFD_RELOC_MIPS_CALL_LO16, PIC_CALL_REG);
5415 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5417 p = frag_var (rs_machine_dependent, 12 + gpdel, 0,
5418 RELAX_ENCODE (16, 12 + gpdel, gpdel,
5420 offset_expr.X_add_symbol, 0, NULL);
5423 macro_build (p, &icnt, (expressionS *) NULL, "nop", "");
5426 macro_build (p, &icnt, &offset_expr,
5427 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
5428 "t,o(b)", PIC_CALL_REG,
5429 (int) BFD_RELOC_MIPS_GOT16, mips_gp_register);
5431 macro_build (p, &icnt, (expressionS *) NULL, "nop", "");
5434 macro_build (p, &icnt, &offset_expr,
5435 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
5436 "t,r,j", PIC_CALL_REG, PIC_CALL_REG,
5437 (int) BFD_RELOC_LO16);
5438 macro_build_jalr (icnt, &offset_expr);
5440 if (mips_cprestore_offset < 0)
5441 as_warn (_("No .cprestore pseudo-op used in PIC code"));
5444 if (! mips_frame_reg_valid)
5446 as_warn (_("No .frame pseudo-op used in PIC code"));
5447 /* Quiet this warning. */
5448 mips_frame_reg_valid = 1;
5450 if (! mips_cprestore_valid)
5452 as_warn (_("No .cprestore pseudo-op used in PIC code"));
5453 /* Quiet this warning. */
5454 mips_cprestore_valid = 1;
5456 if (mips_opts.noreorder)
5457 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5459 expr1.X_add_number = mips_cprestore_offset;
5460 macro_build_ldst_constoffset ((char *) NULL, &icnt, &expr1,
5461 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
5462 mips_gp_register, mips_frame_reg);
5466 else if (mips_pic == EMBEDDED_PIC)
5468 macro_build ((char *) NULL, &icnt, &offset_expr, "bal", "p");
5469 /* The linker may expand the call to a longer sequence which
5470 uses $at, so we must break rather than return. */
5495 /* Itbl support may require additional care here. */
5500 /* Itbl support may require additional care here. */
5505 /* Itbl support may require additional care here. */
5510 /* Itbl support may require additional care here. */
5522 if (mips_arch == CPU_R4650)
5524 as_bad (_("opcode not supported on this processor"));
5528 /* Itbl support may require additional care here. */
5533 /* Itbl support may require additional care here. */
5538 /* Itbl support may require additional care here. */
5558 if (breg == treg || coproc || lr)
5580 /* Itbl support may require additional care here. */
5585 /* Itbl support may require additional care here. */
5590 /* Itbl support may require additional care here. */
5595 /* Itbl support may require additional care here. */
5611 if (mips_arch == CPU_R4650)
5613 as_bad (_("opcode not supported on this processor"));
5618 /* Itbl support may require additional care here. */
5622 /* Itbl support may require additional care here. */
5627 /* Itbl support may require additional care here. */
5639 /* Itbl support may require additional care here. */
5640 if (mask == M_LWC1_AB
5641 || mask == M_SWC1_AB
5642 || mask == M_LDC1_AB
5643 || mask == M_SDC1_AB
5652 /* For embedded PIC, we allow loads where the offset is calculated
5653 by subtracting a symbol in the current segment from an unknown
5654 symbol, relative to a base register, e.g.:
5655 <op> $treg, <sym>-<localsym>($breg)
5656 This is used by the compiler for switch statements. */
5657 if (mips_pic == EMBEDDED_PIC
5658 && offset_expr.X_op == O_subtract
5659 && (symbol_constant_p (offset_expr.X_op_symbol)
5660 ? S_GET_SEGMENT (offset_expr.X_op_symbol) == now_seg
5661 : (symbol_equated_p (offset_expr.X_op_symbol)
5663 (symbol_get_value_expression (offset_expr.X_op_symbol)
5667 && (offset_expr.X_add_number == 0
5668 || OUTPUT_FLAVOR == bfd_target_elf_flavour))
5670 /* For this case, we output the instructions:
5671 lui $tempreg,<sym> (BFD_RELOC_PCREL_HI16_S)
5672 addiu $tempreg,$tempreg,$breg
5673 <op> $treg,<sym>($tempreg) (BFD_RELOC_PCREL_LO16)
5674 If the relocation would fit entirely in 16 bits, it would be
5676 <op> $treg,<sym>($breg) (BFD_RELOC_PCREL_LO16)
5677 instead, but that seems quite difficult. */
5678 macro_build ((char *) NULL, &icnt, &offset_expr, "lui", "t,u",
5679 tempreg, (int) BFD_RELOC_PCREL_HI16_S);
5680 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5681 ((bfd_arch_bits_per_address (stdoutput) == 32
5682 || ! ISA_HAS_64BIT_REGS (mips_opts.isa))
5683 ? "addu" : "daddu"),
5684 "d,v,t", tempreg, tempreg, breg);
5685 macro_build ((char *) NULL, &icnt, &offset_expr, s, fmt, treg,
5686 (int) BFD_RELOC_PCREL_LO16, tempreg);
5692 if (offset_expr.X_op != O_constant
5693 && offset_expr.X_op != O_symbol)
5695 as_bad (_("expression too complex"));
5696 offset_expr.X_op = O_constant;
5699 /* A constant expression in PIC code can be handled just as it
5700 is in non PIC code. */
5701 if (mips_pic == NO_PIC
5702 || offset_expr.X_op == O_constant)
5706 /* If this is a reference to a GP relative symbol, and there
5707 is no base register, we want
5708 <op> $treg,<sym>($gp) (BFD_RELOC_GPREL16)
5709 Otherwise, if there is no base register, we want
5710 lui $tempreg,<sym> (BFD_RELOC_HI16_S)
5711 <op> $treg,<sym>($tempreg) (BFD_RELOC_LO16)
5712 If we have a constant, we need two instructions anyhow,
5713 so we always use the latter form.
5715 If we have a base register, and this is a reference to a
5716 GP relative symbol, we want
5717 addu $tempreg,$breg,$gp
5718 <op> $treg,<sym>($tempreg) (BFD_RELOC_GPREL16)
5720 lui $tempreg,<sym> (BFD_RELOC_HI16_S)
5721 addu $tempreg,$tempreg,$breg
5722 <op> $treg,<sym>($tempreg) (BFD_RELOC_LO16)
5723 With a constant we always use the latter case.
5725 With 64bit address space and no base register and $at usable,
5727 lui $tempreg,<sym> (BFD_RELOC_MIPS_HIGHEST)
5728 lui $at,<sym> (BFD_RELOC_HI16_S)
5729 daddiu $tempreg,<sym> (BFD_RELOC_MIPS_HIGHER)
5732 <op> $treg,<sym>($tempreg) (BFD_RELOC_LO16)
5733 If we have a base register, we want
5734 lui $tempreg,<sym> (BFD_RELOC_MIPS_HIGHEST)
5735 lui $at,<sym> (BFD_RELOC_HI16_S)
5736 daddiu $tempreg,<sym> (BFD_RELOC_MIPS_HIGHER)
5740 <op> $treg,<sym>($tempreg) (BFD_RELOC_LO16)
5742 Without $at we can't generate the optimal path for superscalar
5743 processors here since this would require two temporary registers.
5744 lui $tempreg,<sym> (BFD_RELOC_MIPS_HIGHEST)
5745 daddiu $tempreg,<sym> (BFD_RELOC_MIPS_HIGHER)
5747 daddiu $tempreg,<sym> (BFD_RELOC_HI16_S)
5749 <op> $treg,<sym>($tempreg) (BFD_RELOC_LO16)
5750 If we have a base register, we want
5751 lui $tempreg,<sym> (BFD_RELOC_MIPS_HIGHEST)
5752 daddiu $tempreg,<sym> (BFD_RELOC_MIPS_HIGHER)
5754 daddiu $tempreg,<sym> (BFD_RELOC_HI16_S)
5756 daddu $tempreg,$tempreg,$breg
5757 <op> $treg,<sym>($tempreg) (BFD_RELOC_LO16)
5759 If we have 64-bit addresses, as an optimization, for
5760 addresses which are 32-bit constants (e.g. kseg0/kseg1
5761 addresses) we fall back to the 32-bit address generation
5762 mechanism since it is more efficient. Note that due to
5763 the signed offset used by memory operations, the 32-bit
5764 range is shifted down by 32768 here. This code should
5765 probably attempt to generate 64-bit constants more
5766 efficiently in general.
5768 if (HAVE_64BIT_ADDRESSES
5769 && !(offset_expr.X_op == O_constant
5770 && IS_SEXT_32BIT_NUM (offset_expr.X_add_number + 0x8000)))
5774 /* We don't do GP optimization for now because RELAX_ENCODE can't
5775 hold the data for such large chunks. */
5777 if (used_at == 0 && ! mips_opts.noat)
5779 macro_build (p, &icnt, &offset_expr, "lui", "t,u",
5780 tempreg, (int) BFD_RELOC_MIPS_HIGHEST);
5781 macro_build (p, &icnt, &offset_expr, "lui", "t,u",
5782 AT, (int) BFD_RELOC_HI16_S);
5783 macro_build (p, &icnt, &offset_expr, "daddiu", "t,r,j",
5784 tempreg, tempreg, (int) BFD_RELOC_MIPS_HIGHER);
5786 macro_build (p, &icnt, (expressionS *) NULL, "daddu",
5787 "d,v,t", AT, AT, breg);
5788 macro_build (p, &icnt, (expressionS *) NULL, "dsll32",
5789 "d,w,<", tempreg, tempreg, 0);
5790 macro_build (p, &icnt, (expressionS *) NULL, "daddu",
5791 "d,v,t", tempreg, tempreg, AT);
5792 macro_build (p, &icnt, &offset_expr, s,
5793 fmt, treg, (int) BFD_RELOC_LO16, tempreg);
5798 macro_build (p, &icnt, &offset_expr, "lui", "t,u",
5799 tempreg, (int) BFD_RELOC_MIPS_HIGHEST);
5800 macro_build (p, &icnt, &offset_expr, "daddiu", "t,r,j",
5801 tempreg, tempreg, (int) BFD_RELOC_MIPS_HIGHER);
5802 macro_build (p, &icnt, (expressionS *) NULL, "dsll",
5803 "d,w,<", tempreg, tempreg, 16);
5804 macro_build (p, &icnt, &offset_expr, "daddiu", "t,r,j",
5805 tempreg, tempreg, (int) BFD_RELOC_HI16_S);
5806 macro_build (p, &icnt, (expressionS *) NULL, "dsll",
5807 "d,w,<", tempreg, tempreg, 16);
5809 macro_build (p, &icnt, (expressionS *) NULL, "daddu",
5810 "d,v,t", tempreg, tempreg, breg);
5811 macro_build (p, &icnt, &offset_expr, s,
5812 fmt, treg, (int) BFD_RELOC_LO16, tempreg);
5820 if ((valueT) offset_expr.X_add_number > MAX_GPREL_OFFSET
5821 || nopic_need_relax (offset_expr.X_add_symbol, 1))
5826 macro_build ((char *) NULL, &icnt, &offset_expr, s, fmt,
5827 treg, (int) BFD_RELOC_GPREL16,
5829 p = frag_var (rs_machine_dependent, 8, 0,
5830 RELAX_ENCODE (4, 8, 0, 4, 0,
5831 (mips_opts.warn_about_macros
5833 && mips_opts.noat))),
5834 offset_expr.X_add_symbol, 0, NULL);
5837 macro_build_lui (p, &icnt, &offset_expr, tempreg);
5840 macro_build (p, &icnt, &offset_expr, s, fmt, treg,
5841 (int) BFD_RELOC_LO16, tempreg);
5845 if ((valueT) offset_expr.X_add_number > MAX_GPREL_OFFSET
5846 || nopic_need_relax (offset_expr.X_add_symbol, 1))
5851 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5852 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
5853 "d,v,t", tempreg, breg, mips_gp_register);
5854 macro_build ((char *) NULL, &icnt, &offset_expr, s, fmt,
5855 treg, (int) BFD_RELOC_GPREL16, tempreg);
5856 p = frag_var (rs_machine_dependent, 12, 0,
5857 RELAX_ENCODE (8, 12, 0, 8, 0, 0),
5858 offset_expr.X_add_symbol, 0, NULL);
5860 macro_build_lui (p, &icnt, &offset_expr, tempreg);
5863 macro_build (p, &icnt, (expressionS *) NULL,
5864 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
5865 "d,v,t", tempreg, tempreg, breg);
5868 macro_build (p, &icnt, &offset_expr, s, fmt, treg,
5869 (int) BFD_RELOC_LO16, tempreg);
5872 else if (mips_pic == SVR4_PIC && ! mips_big_got)
5875 int lw_reloc_type = (int) BFD_RELOC_MIPS_GOT16;
5877 /* If this is a reference to an external symbol, we want
5878 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
5880 <op> $treg,0($tempreg)
5882 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
5884 addiu $tempreg,$tempreg,<sym> (BFD_RELOC_LO16)
5885 <op> $treg,0($tempreg)
5886 If we have NewABI, we want
5887 lw $reg,<sym>($gp) (BFD_RELOC_MIPS_GOT_DISP)
5888 If there is a base register, we add it to $tempreg before
5889 the <op>. If there is a constant, we stick it in the
5890 <op> instruction. We don't handle constants larger than
5891 16 bits, because we have no way to load the upper 16 bits
5892 (actually, we could handle them for the subset of cases
5893 in which we are not using $at). */
5894 assert (offset_expr.X_op == O_symbol);
5895 expr1.X_add_number = offset_expr.X_add_number;
5896 offset_expr.X_add_number = 0;
5898 lw_reloc_type = (int) BFD_RELOC_MIPS_GOT_DISP;
5899 if (expr1.X_add_number < -0x8000
5900 || expr1.X_add_number >= 0x8000)
5901 as_bad (_("PIC code offset overflow (max 16 signed bits)"));
5903 macro_build ((char *) NULL, &icnt, &offset_expr,
5904 HAVE_32BIT_ADDRESSES ? "lw" : "ld", "t,o(b)", tempreg,
5905 (int) lw_reloc_type, mips_gp_register);
5906 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "");
5907 p = frag_var (rs_machine_dependent, 4, 0,
5908 RELAX_ENCODE (0, 4, -8, 0, 0, 0),
5909 offset_expr.X_add_symbol, 0, NULL);
5910 macro_build (p, &icnt, &offset_expr,
5911 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
5912 "t,r,j", tempreg, tempreg, (int) BFD_RELOC_LO16);
5914 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5915 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
5916 "d,v,t", tempreg, tempreg, breg);
5917 macro_build ((char *) NULL, &icnt, &expr1, s, fmt, treg,
5918 (int) BFD_RELOC_LO16, tempreg);
5920 else if (mips_pic == SVR4_PIC)
5925 /* If this is a reference to an external symbol, we want
5926 lui $tempreg,<sym> (BFD_RELOC_MIPS_GOT_HI16)
5927 addu $tempreg,$tempreg,$gp
5928 lw $tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_LO16)
5929 <op> $treg,0($tempreg)
5931 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
5933 addiu $tempreg,$tempreg,<sym> (BFD_RELOC_LO16)
5934 <op> $treg,0($tempreg)
5935 If there is a base register, we add it to $tempreg before
5936 the <op>. If there is a constant, we stick it in the
5937 <op> instruction. We don't handle constants larger than
5938 16 bits, because we have no way to load the upper 16 bits
5939 (actually, we could handle them for the subset of cases
5940 in which we are not using $at).
5943 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT_PAGE)
5944 addiu $tempreg,$tempreg,<sym> (BFD_RELOC_MIPS_GOT_OFST)
5945 <op> $treg,0($tempreg)
5947 assert (offset_expr.X_op == O_symbol);
5948 expr1.X_add_number = offset_expr.X_add_number;
5949 offset_expr.X_add_number = 0;
5950 if (expr1.X_add_number < -0x8000
5951 || expr1.X_add_number >= 0x8000)
5952 as_bad (_("PIC code offset overflow (max 16 signed bits)"));
5955 macro_build ((char *) NULL, &icnt, &offset_expr,
5956 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
5957 "t,o(b)", tempreg, BFD_RELOC_MIPS_GOT_PAGE,
5959 macro_build ((char *) NULL, &icnt, &offset_expr,
5960 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
5961 "t,r,j", tempreg, tempreg,
5962 BFD_RELOC_MIPS_GOT_OFST);
5964 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5965 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
5966 "d,v,t", tempreg, tempreg, breg);
5967 macro_build ((char *) NULL, &icnt, &expr1, s, fmt, treg,
5968 (int) BFD_RELOC_LO16, tempreg);
5975 if (reg_needs_delay (mips_gp_register))
5980 macro_build ((char *) NULL, &icnt, &offset_expr, "lui", "t,u",
5981 tempreg, (int) BFD_RELOC_MIPS_GOT_HI16);
5982 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5983 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
5984 "d,v,t", tempreg, tempreg, mips_gp_register);
5985 macro_build ((char *) NULL, &icnt, &offset_expr,
5986 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
5987 "t,o(b)", tempreg, (int) BFD_RELOC_MIPS_GOT_LO16,
5989 p = frag_var (rs_machine_dependent, 12 + gpdel, 0,
5990 RELAX_ENCODE (12, 12 + gpdel, gpdel, 8 + gpdel, 0, 0),
5991 offset_expr.X_add_symbol, 0, NULL);
5994 macro_build (p, &icnt, (expressionS *) NULL, "nop", "");
5997 macro_build (p, &icnt, &offset_expr,
5998 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
5999 "t,o(b)", tempreg, (int) BFD_RELOC_MIPS_GOT16,
6002 macro_build (p, &icnt, (expressionS *) NULL, "nop", "");
6004 macro_build (p, &icnt, &offset_expr,
6005 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
6006 "t,r,j", tempreg, tempreg, (int) BFD_RELOC_LO16);
6008 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6009 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
6010 "d,v,t", tempreg, tempreg, breg);
6011 macro_build ((char *) NULL, &icnt, &expr1, s, fmt, treg,
6012 (int) BFD_RELOC_LO16, tempreg);
6014 else if (mips_pic == EMBEDDED_PIC)
6016 /* If there is no base register, we want
6017 <op> $treg,<sym>($gp) (BFD_RELOC_GPREL16)
6018 If there is a base register, we want
6019 addu $tempreg,$breg,$gp
6020 <op> $treg,<sym>($tempreg) (BFD_RELOC_GPREL16)
6022 assert (offset_expr.X_op == O_symbol);
6025 macro_build ((char *) NULL, &icnt, &offset_expr, s, fmt,
6026 treg, (int) BFD_RELOC_GPREL16, mips_gp_register);
6031 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6032 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
6033 "d,v,t", tempreg, breg, mips_gp_register);
6034 macro_build ((char *) NULL, &icnt, &offset_expr, s, fmt,
6035 treg, (int) BFD_RELOC_GPREL16, tempreg);
6048 load_register (&icnt, treg, &imm_expr, 0);
6052 load_register (&icnt, treg, &imm_expr, 1);
6056 if (imm_expr.X_op == O_constant)
6058 load_register (&icnt, AT, &imm_expr, 0);
6059 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6060 "mtc1", "t,G", AT, treg);
6065 assert (offset_expr.X_op == O_symbol
6066 && strcmp (segment_name (S_GET_SEGMENT
6067 (offset_expr.X_add_symbol)),
6069 && offset_expr.X_add_number == 0);
6070 macro_build ((char *) NULL, &icnt, &offset_expr, "lwc1", "T,o(b)",
6071 treg, (int) BFD_RELOC_MIPS_LITERAL, mips_gp_register);
6076 /* Check if we have a constant in IMM_EXPR. If the GPRs are 64 bits
6077 wide, IMM_EXPR is the entire value. Otherwise IMM_EXPR is the high
6078 order 32 bits of the value and the low order 32 bits are either
6079 zero or in OFFSET_EXPR. */
6080 if (imm_expr.X_op == O_constant || imm_expr.X_op == O_big)
6082 if (HAVE_64BIT_GPRS)
6083 load_register (&icnt, treg, &imm_expr, 1);
6088 if (target_big_endian)
6100 load_register (&icnt, hreg, &imm_expr, 0);
6103 if (offset_expr.X_op == O_absent)
6104 move_register (&icnt, lreg, 0);
6107 assert (offset_expr.X_op == O_constant);
6108 load_register (&icnt, lreg, &offset_expr, 0);
6115 /* We know that sym is in the .rdata section. First we get the
6116 upper 16 bits of the address. */
6117 if (mips_pic == NO_PIC)
6119 macro_build_lui (NULL, &icnt, &offset_expr, AT);
6121 else if (mips_pic == SVR4_PIC)
6123 macro_build ((char *) NULL, &icnt, &offset_expr,
6124 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
6125 "t,o(b)", AT, (int) BFD_RELOC_MIPS_GOT16,
6128 else if (mips_pic == EMBEDDED_PIC)
6130 /* For embedded PIC we pick up the entire address off $gp in
6131 a single instruction. */
6132 macro_build ((char *) NULL, &icnt, &offset_expr,
6133 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu", "t,r,j", AT,
6134 mips_gp_register, (int) BFD_RELOC_GPREL16);
6135 offset_expr.X_op = O_constant;
6136 offset_expr.X_add_number = 0;
6141 /* Now we load the register(s). */
6142 if (HAVE_64BIT_GPRS)
6143 macro_build ((char *) NULL, &icnt, &offset_expr, "ld", "t,o(b)",
6144 treg, (int) BFD_RELOC_LO16, AT);
6147 macro_build ((char *) NULL, &icnt, &offset_expr, "lw", "t,o(b)",
6148 treg, (int) BFD_RELOC_LO16, AT);
6151 /* FIXME: How in the world do we deal with the possible
6153 offset_expr.X_add_number += 4;
6154 macro_build ((char *) NULL, &icnt, &offset_expr, "lw", "t,o(b)",
6155 treg + 1, (int) BFD_RELOC_LO16, AT);
6159 /* To avoid confusion in tc_gen_reloc, we must ensure that this
6160 does not become a variant frag. */
6161 frag_wane (frag_now);
6167 /* Check if we have a constant in IMM_EXPR. If the FPRs are 64 bits
6168 wide, IMM_EXPR is the entire value and the GPRs are known to be 64
6169 bits wide as well. Otherwise IMM_EXPR is the high order 32 bits of
6170 the value and the low order 32 bits are either zero or in
6172 if (imm_expr.X_op == O_constant || imm_expr.X_op == O_big)
6174 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_FPRS);
6175 if (HAVE_64BIT_FPRS)
6177 assert (HAVE_64BIT_GPRS);
6178 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6179 "dmtc1", "t,S", AT, treg);
6183 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6184 "mtc1", "t,G", AT, treg + 1);
6185 if (offset_expr.X_op == O_absent)
6186 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6187 "mtc1", "t,G", 0, treg);
6190 assert (offset_expr.X_op == O_constant);
6191 load_register (&icnt, AT, &offset_expr, 0);
6192 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6193 "mtc1", "t,G", AT, treg);
6199 assert (offset_expr.X_op == O_symbol
6200 && offset_expr.X_add_number == 0);
6201 s = segment_name (S_GET_SEGMENT (offset_expr.X_add_symbol));
6202 if (strcmp (s, ".lit8") == 0)
6204 if (mips_opts.isa != ISA_MIPS1)
6206 macro_build ((char *) NULL, &icnt, &offset_expr, "ldc1",
6207 "T,o(b)", treg, (int) BFD_RELOC_MIPS_LITERAL,
6211 breg = mips_gp_register;
6212 r = BFD_RELOC_MIPS_LITERAL;
6217 assert (strcmp (s, RDATA_SECTION_NAME) == 0);
6218 if (mips_pic == SVR4_PIC)
6219 macro_build ((char *) NULL, &icnt, &offset_expr,
6220 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
6221 "t,o(b)", AT, (int) BFD_RELOC_MIPS_GOT16,
6225 /* FIXME: This won't work for a 64 bit address. */
6226 macro_build_lui (NULL, &icnt, &offset_expr, AT);
6229 if (mips_opts.isa != ISA_MIPS1)
6231 macro_build ((char *) NULL, &icnt, &offset_expr, "ldc1",
6232 "T,o(b)", treg, (int) BFD_RELOC_LO16, AT);
6234 /* To avoid confusion in tc_gen_reloc, we must ensure
6235 that this does not become a variant frag. */
6236 frag_wane (frag_now);
6247 if (mips_arch == CPU_R4650)
6249 as_bad (_("opcode not supported on this processor"));
6252 /* Even on a big endian machine $fn comes before $fn+1. We have
6253 to adjust when loading from memory. */
6256 assert (mips_opts.isa == ISA_MIPS1);
6257 macro_build ((char *) NULL, &icnt, &offset_expr, "lwc1", "T,o(b)",
6258 target_big_endian ? treg + 1 : treg,
6260 /* FIXME: A possible overflow which I don't know how to deal
6262 offset_expr.X_add_number += 4;
6263 macro_build ((char *) NULL, &icnt, &offset_expr, "lwc1", "T,o(b)",
6264 target_big_endian ? treg : treg + 1,
6267 /* To avoid confusion in tc_gen_reloc, we must ensure that this
6268 does not become a variant frag. */
6269 frag_wane (frag_now);
6278 * The MIPS assembler seems to check for X_add_number not
6279 * being double aligned and generating:
6282 * addiu at,at,%lo(foo+1)
6285 * But, the resulting address is the same after relocation so why
6286 * generate the extra instruction?
6288 if (mips_arch == CPU_R4650)
6290 as_bad (_("opcode not supported on this processor"));
6293 /* Itbl support may require additional care here. */
6295 if (mips_opts.isa != ISA_MIPS1)
6306 if (mips_arch == CPU_R4650)
6308 as_bad (_("opcode not supported on this processor"));
6312 if (mips_opts.isa != ISA_MIPS1)
6320 /* Itbl support may require additional care here. */
6325 if (HAVE_64BIT_GPRS)
6336 if (HAVE_64BIT_GPRS)
6346 /* We do _not_ bother to allow embedded PIC (symbol-local_symbol)
6347 loads for the case of doing a pair of loads to simulate an 'ld'.
6348 This is not currently done by the compiler, and assembly coders
6349 writing embedded-pic code can cope. */
6351 if (offset_expr.X_op != O_symbol
6352 && offset_expr.X_op != O_constant)
6354 as_bad (_("expression too complex"));
6355 offset_expr.X_op = O_constant;
6358 /* Even on a big endian machine $fn comes before $fn+1. We have
6359 to adjust when loading from memory. We set coproc if we must
6360 load $fn+1 first. */
6361 /* Itbl support may require additional care here. */
6362 if (! target_big_endian)
6365 if (mips_pic == NO_PIC
6366 || offset_expr.X_op == O_constant)
6370 /* If this is a reference to a GP relative symbol, we want
6371 <op> $treg,<sym>($gp) (BFD_RELOC_GPREL16)
6372 <op> $treg+1,<sym>+4($gp) (BFD_RELOC_GPREL16)
6373 If we have a base register, we use this
6375 <op> $treg,<sym>($at) (BFD_RELOC_GPREL16)
6376 <op> $treg+1,<sym>+4($at) (BFD_RELOC_GPREL16)
6377 If this is not a GP relative symbol, we want
6378 lui $at,<sym> (BFD_RELOC_HI16_S)
6379 <op> $treg,<sym>($at) (BFD_RELOC_LO16)
6380 <op> $treg+1,<sym>+4($at) (BFD_RELOC_LO16)
6381 If there is a base register, we add it to $at after the
6382 lui instruction. If there is a constant, we always use
6384 if ((valueT) offset_expr.X_add_number > MAX_GPREL_OFFSET
6385 || nopic_need_relax (offset_expr.X_add_symbol, 1))
6397 tempreg = mips_gp_register;
6404 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6405 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
6406 "d,v,t", AT, breg, mips_gp_register);
6412 /* Itbl support may require additional care here. */
6413 macro_build ((char *) NULL, &icnt, &offset_expr, s, fmt,
6414 coproc ? treg + 1 : treg,
6415 (int) BFD_RELOC_GPREL16, tempreg);
6416 offset_expr.X_add_number += 4;
6418 /* Set mips_optimize to 2 to avoid inserting an
6420 hold_mips_optimize = mips_optimize;
6422 /* Itbl support may require additional care here. */
6423 macro_build ((char *) NULL, &icnt, &offset_expr, s, fmt,
6424 coproc ? treg : treg + 1,
6425 (int) BFD_RELOC_GPREL16, tempreg);
6426 mips_optimize = hold_mips_optimize;
6428 p = frag_var (rs_machine_dependent, 12 + off, 0,
6429 RELAX_ENCODE (8 + off, 12 + off, 0, 4 + off, 1,
6430 used_at && mips_opts.noat),
6431 offset_expr.X_add_symbol, 0, NULL);
6433 /* We just generated two relocs. When tc_gen_reloc
6434 handles this case, it will skip the first reloc and
6435 handle the second. The second reloc already has an
6436 extra addend of 4, which we added above. We must
6437 subtract it out, and then subtract another 4 to make
6438 the first reloc come out right. The second reloc
6439 will come out right because we are going to add 4 to
6440 offset_expr when we build its instruction below.
6442 If we have a symbol, then we don't want to include
6443 the offset, because it will wind up being included
6444 when we generate the reloc. */
6446 if (offset_expr.X_op == O_constant)
6447 offset_expr.X_add_number -= 8;
6450 offset_expr.X_add_number = -4;
6451 offset_expr.X_op = O_constant;
6454 macro_build_lui (p, &icnt, &offset_expr, AT);
6459 macro_build (p, &icnt, (expressionS *) NULL,
6460 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
6461 "d,v,t", AT, breg, AT);
6465 /* Itbl support may require additional care here. */
6466 macro_build (p, &icnt, &offset_expr, s, fmt,
6467 coproc ? treg + 1 : treg,
6468 (int) BFD_RELOC_LO16, AT);
6471 /* FIXME: How do we handle overflow here? */
6472 offset_expr.X_add_number += 4;
6473 /* Itbl support may require additional care here. */
6474 macro_build (p, &icnt, &offset_expr, s, fmt,
6475 coproc ? treg : treg + 1,
6476 (int) BFD_RELOC_LO16, AT);
6478 else if (mips_pic == SVR4_PIC && ! mips_big_got)
6482 /* If this is a reference to an external symbol, we want
6483 lw $at,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
6488 lw $at,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
6490 <op> $treg,<sym>($at) (BFD_RELOC_LO16)
6491 <op> $treg+1,<sym>+4($at) (BFD_RELOC_LO16)
6492 If there is a base register we add it to $at before the
6493 lwc1 instructions. If there is a constant we include it
6494 in the lwc1 instructions. */
6496 expr1.X_add_number = offset_expr.X_add_number;
6497 offset_expr.X_add_number = 0;
6498 if (expr1.X_add_number < -0x8000
6499 || expr1.X_add_number >= 0x8000 - 4)
6500 as_bad (_("PIC code offset overflow (max 16 signed bits)"));
6505 frag_grow (24 + off);
6506 macro_build ((char *) NULL, &icnt, &offset_expr,
6507 HAVE_32BIT_ADDRESSES ? "lw" : "ld", "t,o(b)", AT,
6508 (int) BFD_RELOC_MIPS_GOT16, mips_gp_register);
6509 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "");
6511 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6512 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
6513 "d,v,t", AT, breg, AT);
6514 /* Itbl support may require additional care here. */
6515 macro_build ((char *) NULL, &icnt, &expr1, s, fmt,
6516 coproc ? treg + 1 : treg,
6517 (int) BFD_RELOC_LO16, AT);
6518 expr1.X_add_number += 4;
6520 /* Set mips_optimize to 2 to avoid inserting an undesired
6522 hold_mips_optimize = mips_optimize;
6524 /* Itbl support may require additional care here. */
6525 macro_build ((char *) NULL, &icnt, &expr1, s, fmt,
6526 coproc ? treg : treg + 1,
6527 (int) BFD_RELOC_LO16, AT);
6528 mips_optimize = hold_mips_optimize;
6530 (void) frag_var (rs_machine_dependent, 0, 0,
6531 RELAX_ENCODE (0, 0, -16 - off, -8, 1, 0),
6532 offset_expr.X_add_symbol, 0, NULL);
6534 else if (mips_pic == SVR4_PIC)
6539 /* If this is a reference to an external symbol, we want
6540 lui $at,<sym> (BFD_RELOC_MIPS_GOT_HI16)
6542 lw $at,<sym>($at) (BFD_RELOC_MIPS_GOT_LO16)
6547 lw $at,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
6549 <op> $treg,<sym>($at) (BFD_RELOC_LO16)
6550 <op> $treg+1,<sym>+4($at) (BFD_RELOC_LO16)
6551 If there is a base register we add it to $at before the
6552 lwc1 instructions. If there is a constant we include it
6553 in the lwc1 instructions. */
6555 expr1.X_add_number = offset_expr.X_add_number;
6556 offset_expr.X_add_number = 0;
6557 if (expr1.X_add_number < -0x8000
6558 || expr1.X_add_number >= 0x8000 - 4)
6559 as_bad (_("PIC code offset overflow (max 16 signed bits)"));
6560 if (reg_needs_delay (mips_gp_register))
6569 macro_build ((char *) NULL, &icnt, &offset_expr, "lui", "t,u",
6570 AT, (int) BFD_RELOC_MIPS_GOT_HI16);
6571 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6572 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
6573 "d,v,t", AT, AT, mips_gp_register);
6574 macro_build ((char *) NULL, &icnt, &offset_expr,
6575 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
6576 "t,o(b)", AT, (int) BFD_RELOC_MIPS_GOT_LO16, AT);
6577 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "");
6579 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6580 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
6581 "d,v,t", AT, breg, AT);
6582 /* Itbl support may require additional care here. */
6583 macro_build ((char *) NULL, &icnt, &expr1, s, fmt,
6584 coproc ? treg + 1 : treg,
6585 (int) BFD_RELOC_LO16, AT);
6586 expr1.X_add_number += 4;
6588 /* Set mips_optimize to 2 to avoid inserting an undesired
6590 hold_mips_optimize = mips_optimize;
6592 /* Itbl support may require additional care here. */
6593 macro_build ((char *) NULL, &icnt, &expr1, s, fmt,
6594 coproc ? treg : treg + 1,
6595 (int) BFD_RELOC_LO16, AT);
6596 mips_optimize = hold_mips_optimize;
6597 expr1.X_add_number -= 4;
6599 p = frag_var (rs_machine_dependent, 16 + gpdel + off, 0,
6600 RELAX_ENCODE (24 + off, 16 + gpdel + off, gpdel,
6601 8 + gpdel + off, 1, 0),
6602 offset_expr.X_add_symbol, 0, NULL);
6605 macro_build (p, &icnt, (expressionS *) NULL, "nop", "");
6608 macro_build (p, &icnt, &offset_expr,
6609 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
6610 "t,o(b)", AT, (int) BFD_RELOC_MIPS_GOT16,
6613 macro_build (p, &icnt, (expressionS *) NULL, "nop", "");
6617 macro_build (p, &icnt, (expressionS *) NULL,
6618 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
6619 "d,v,t", AT, breg, AT);
6622 /* Itbl support may require additional care here. */
6623 macro_build (p, &icnt, &expr1, s, fmt,
6624 coproc ? treg + 1 : treg,
6625 (int) BFD_RELOC_LO16, AT);
6627 expr1.X_add_number += 4;
6629 /* Set mips_optimize to 2 to avoid inserting an undesired
6631 hold_mips_optimize = mips_optimize;
6633 /* Itbl support may require additional care here. */
6634 macro_build (p, &icnt, &expr1, s, fmt,
6635 coproc ? treg : treg + 1,
6636 (int) BFD_RELOC_LO16, AT);
6637 mips_optimize = hold_mips_optimize;
6639 else if (mips_pic == EMBEDDED_PIC)
6641 /* If there is no base register, we use
6642 <op> $treg,<sym>($gp) (BFD_RELOC_GPREL16)
6643 <op> $treg+1,<sym>+4($gp) (BFD_RELOC_GPREL16)
6644 If we have a base register, we use
6646 <op> $treg,<sym>($at) (BFD_RELOC_GPREL16)
6647 <op> $treg+1,<sym>+4($at) (BFD_RELOC_GPREL16)
6651 tempreg = mips_gp_register;
6656 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6657 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
6658 "d,v,t", AT, breg, mips_gp_register);
6663 /* Itbl support may require additional care here. */
6664 macro_build ((char *) NULL, &icnt, &offset_expr, s, fmt,
6665 coproc ? treg + 1 : treg,
6666 (int) BFD_RELOC_GPREL16, tempreg);
6667 offset_expr.X_add_number += 4;
6668 /* Itbl support may require additional care here. */
6669 macro_build ((char *) NULL, &icnt, &offset_expr, s, fmt,
6670 coproc ? treg : treg + 1,
6671 (int) BFD_RELOC_GPREL16, tempreg);
6687 assert (HAVE_32BIT_ADDRESSES);
6688 macro_build ((char *) NULL, &icnt, &offset_expr, s, "t,o(b)", treg,
6689 (int) BFD_RELOC_LO16, breg);
6690 offset_expr.X_add_number += 4;
6691 macro_build ((char *) NULL, &icnt, &offset_expr, s, "t,o(b)", treg + 1,
6692 (int) BFD_RELOC_LO16, breg);
6695 /* New code added to support COPZ instructions.
6696 This code builds table entries out of the macros in mip_opcodes.
6697 R4000 uses interlocks to handle coproc delays.
6698 Other chips (like the R3000) require nops to be inserted for delays.
6700 FIXME: Currently, we require that the user handle delays.
6701 In order to fill delay slots for non-interlocked chips,
6702 we must have a way to specify delays based on the coprocessor.
6703 Eg. 4 cycles if load coproc reg from memory, 1 if in cache, etc.
6704 What are the side-effects of the cop instruction?
6705 What cache support might we have and what are its effects?
6706 Both coprocessor & memory require delays. how long???
6707 What registers are read/set/modified?
6709 If an itbl is provided to interpret cop instructions,
6710 this knowledge can be encoded in the itbl spec. */
6724 /* For now we just do C (same as Cz). The parameter will be
6725 stored in insn_opcode by mips_ip. */
6726 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "C",
6731 move_register (&icnt, dreg, sreg);
6734 #ifdef LOSING_COMPILER
6736 /* Try and see if this is a new itbl instruction.
6737 This code builds table entries out of the macros in mip_opcodes.
6738 FIXME: For now we just assemble the expression and pass it's
6739 value along as a 32-bit immediate.
6740 We may want to have the assembler assemble this value,
6741 so that we gain the assembler's knowledge of delay slots,
6743 Would it be more efficient to use mask (id) here? */
6744 if (itbl_have_entries
6745 && (immed_expr = itbl_assemble (ip->insn_mo->name, "")))
6747 s = ip->insn_mo->name;
6749 coproc = ITBL_DECODE_PNUM (immed_expr);;
6750 macro_build ((char *) NULL, &icnt, &immed_expr, s, "C");
6757 as_warn (_("Macro used $at after \".set noat\""));
6762 struct mips_cl_insn *ip;
6764 register int treg, sreg, dreg, breg;
6780 bfd_reloc_code_real_type r;
6783 treg = (ip->insn_opcode >> 16) & 0x1f;
6784 dreg = (ip->insn_opcode >> 11) & 0x1f;
6785 sreg = breg = (ip->insn_opcode >> 21) & 0x1f;
6786 mask = ip->insn_mo->mask;
6788 expr1.X_op = O_constant;
6789 expr1.X_op_symbol = NULL;
6790 expr1.X_add_symbol = NULL;
6791 expr1.X_add_number = 1;
6795 #endif /* LOSING_COMPILER */
6800 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6801 dbl ? "dmultu" : "multu", "s,t", sreg, treg);
6802 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "mflo", "d",
6809 /* The MIPS assembler some times generates shifts and adds. I'm
6810 not trying to be that fancy. GCC should do this for us
6812 load_register (&icnt, AT, &imm_expr, dbl);
6813 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6814 dbl ? "dmult" : "mult", "s,t", sreg, AT);
6815 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "mflo", "d",
6829 mips_emit_delays (true);
6830 ++mips_opts.noreorder;
6831 mips_any_noreorder = 1;
6833 load_register (&icnt, AT, &imm_expr, dbl);
6834 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6835 dbl ? "dmult" : "mult", "s,t", sreg, imm ? AT : treg);
6836 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "mflo", "d",
6838 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6839 dbl ? "dsra32" : "sra", "d,w,<", dreg, dreg, RA);
6840 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "mfhi", "d",
6843 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "tne",
6844 "s,t,q", dreg, AT, 6);
6847 expr1.X_add_number = 8;
6848 macro_build ((char *) NULL, &icnt, &expr1, "beq", "s,t,p", dreg,
6850 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "",
6852 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "break",
6855 --mips_opts.noreorder;
6856 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "mflo", "d", dreg);
6869 mips_emit_delays (true);
6870 ++mips_opts.noreorder;
6871 mips_any_noreorder = 1;
6873 load_register (&icnt, AT, &imm_expr, dbl);
6874 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6875 dbl ? "dmultu" : "multu",
6876 "s,t", sreg, imm ? AT : treg);
6877 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "mfhi", "d",
6879 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "mflo", "d",
6882 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "tne",
6886 expr1.X_add_number = 8;
6887 macro_build ((char *) NULL, &icnt, &expr1, "beq", "s,t,p", AT, 0);
6888 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "",
6890 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "break",
6893 --mips_opts.noreorder;
6897 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "dsubu",
6898 "d,v,t", AT, 0, treg);
6899 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "dsrlv",
6900 "d,t,s", AT, sreg, AT);
6901 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "dsllv",
6902 "d,t,s", dreg, sreg, treg);
6903 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or",
6904 "d,v,t", dreg, dreg, AT);
6908 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "subu",
6909 "d,v,t", AT, 0, treg);
6910 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "srlv",
6911 "d,t,s", AT, sreg, AT);
6912 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sllv",
6913 "d,t,s", dreg, sreg, treg);
6914 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or",
6915 "d,v,t", dreg, dreg, AT);
6922 if (imm_expr.X_op != O_constant)
6923 as_bad (_("rotate count too large"));
6924 rot = imm_expr.X_add_number & 0x3f;
6925 if (CPU_HAS_DROR (mips_arch))
6927 rot = (64 - rot) & 0x3f;
6929 macro_build ((char *) NULL, &icnt, NULL, "dror32",
6930 "d,w,<", dreg, sreg, rot - 32);
6932 macro_build ((char *) NULL, &icnt, NULL, "dror",
6933 "d,w,<", dreg, sreg, rot);
6937 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "dsrl",
6938 "d,w,<", dreg, sreg, 0);
6943 l = (rot < 0x20) ? "dsll" : "dsll32";
6944 r = ((0x40 - rot) < 0x20) ? "dsrl" : "dsrl32";
6946 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, l,
6947 "d,w,<", AT, sreg, rot);
6948 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, r,
6949 "d,w,<", dreg, sreg, (0x20 - rot) & 0x1f);
6950 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or",
6951 "d,v,t", dreg, dreg, AT);
6960 if (imm_expr.X_op != O_constant)
6961 as_bad (_("rotate count too large"));
6962 rot = imm_expr.X_add_number & 0x1f;
6963 if (CPU_HAS_ROR (mips_arch))
6965 macro_build ((char *) NULL, &icnt, NULL, "ror",
6966 "d,w,<", dreg, sreg, (32 - rot) & 0x1f);
6970 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "srl",
6971 "d,w,<", dreg, sreg, 0);
6974 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sll",
6975 "d,w,<", AT, sreg, rot);
6976 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "srl",
6977 "d,w,<", dreg, sreg, (0x20 - rot) & 0x1f);
6978 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or",
6979 "d,v,t", dreg, dreg, AT);
6985 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "dsubu",
6986 "d,v,t", AT, 0, treg);
6987 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "dsllv",
6988 "d,t,s", AT, sreg, AT);
6989 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "dsrlv",
6990 "d,t,s", dreg, sreg, treg);
6991 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or",
6992 "d,v,t", dreg, dreg, AT);
6996 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "subu",
6997 "d,v,t", AT, 0, treg);
6998 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sllv",
6999 "d,t,s", AT, sreg, AT);
7000 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "srlv",
7001 "d,t,s", dreg, sreg, treg);
7002 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or",
7003 "d,v,t", dreg, dreg, AT);
7010 if (imm_expr.X_op != O_constant)
7011 as_bad (_("rotate count too large"));
7012 rot = imm_expr.X_add_number & 0x3f;
7014 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "dsrl",
7015 "d,w,<", dreg, sreg, 0);
7020 r = (rot < 0x20) ? "dsrl" : "dsrl32";
7021 l = ((0x40 - rot) < 0x20) ? "dsll" : "dsll32";
7023 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, r,
7024 "d,w,<", AT, sreg, rot);
7025 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, l,
7026 "d,w,<", dreg, sreg, (0x20 - rot) & 0x1f);
7027 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or",
7028 "d,v,t", dreg, dreg, AT);
7037 if (imm_expr.X_op != O_constant)
7038 as_bad (_("rotate count too large"));
7039 rot = imm_expr.X_add_number & 0x1f;
7041 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "srl",
7042 "d,w,<", dreg, sreg, 0);
7045 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "srl",
7046 "d,w,<", AT, sreg, rot);
7047 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sll",
7048 "d,w,<", dreg, sreg, (0x20 - rot) & 0x1f);
7049 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or",
7050 "d,v,t", dreg, dreg, AT);
7056 if (mips_arch == CPU_R4650)
7058 as_bad (_("opcode not supported on this processor"));
7061 assert (mips_opts.isa == ISA_MIPS1);
7062 /* Even on a big endian machine $fn comes before $fn+1. We have
7063 to adjust when storing to memory. */
7064 macro_build ((char *) NULL, &icnt, &offset_expr, "swc1", "T,o(b)",
7065 target_big_endian ? treg + 1 : treg,
7066 (int) BFD_RELOC_LO16, breg);
7067 offset_expr.X_add_number += 4;
7068 macro_build ((char *) NULL, &icnt, &offset_expr, "swc1", "T,o(b)",
7069 target_big_endian ? treg : treg + 1,
7070 (int) BFD_RELOC_LO16, breg);
7075 macro_build ((char *) NULL, &icnt, &expr1, "sltiu", "t,r,j", dreg,
7076 treg, (int) BFD_RELOC_LO16);
7078 macro_build ((char *) NULL, &icnt, &expr1, "sltiu", "t,r,j", dreg,
7079 sreg, (int) BFD_RELOC_LO16);
7082 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "xor",
7083 "d,v,t", dreg, sreg, treg);
7084 macro_build ((char *) NULL, &icnt, &expr1, "sltiu", "t,r,j", dreg,
7085 dreg, (int) BFD_RELOC_LO16);
7090 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
7092 macro_build ((char *) NULL, &icnt, &expr1, "sltiu", "t,r,j", dreg,
7093 sreg, (int) BFD_RELOC_LO16);
7098 as_warn (_("Instruction %s: result is always false"),
7100 move_register (&icnt, dreg, 0);
7103 if (imm_expr.X_op == O_constant
7104 && imm_expr.X_add_number >= 0
7105 && imm_expr.X_add_number < 0x10000)
7107 macro_build ((char *) NULL, &icnt, &imm_expr, "xori", "t,r,i", dreg,
7108 sreg, (int) BFD_RELOC_LO16);
7111 else if (imm_expr.X_op == O_constant
7112 && imm_expr.X_add_number > -0x8000
7113 && imm_expr.X_add_number < 0)
7115 imm_expr.X_add_number = -imm_expr.X_add_number;
7116 macro_build ((char *) NULL, &icnt, &imm_expr,
7117 HAVE_32BIT_GPRS ? "addiu" : "daddiu",
7118 "t,r,j", dreg, sreg,
7119 (int) BFD_RELOC_LO16);
7124 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_GPRS);
7125 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "xor",
7126 "d,v,t", dreg, sreg, AT);
7129 macro_build ((char *) NULL, &icnt, &expr1, "sltiu", "t,r,j", dreg, dreg,
7130 (int) BFD_RELOC_LO16);
7135 case M_SGE: /* sreg >= treg <==> not (sreg < treg) */
7141 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "d,v,t",
7143 macro_build ((char *) NULL, &icnt, &expr1, "xori", "t,r,i", dreg, dreg,
7144 (int) BFD_RELOC_LO16);
7147 case M_SGE_I: /* sreg >= I <==> not (sreg < I) */
7149 if (imm_expr.X_op == O_constant
7150 && imm_expr.X_add_number >= -0x8000
7151 && imm_expr.X_add_number < 0x8000)
7153 macro_build ((char *) NULL, &icnt, &imm_expr,
7154 mask == M_SGE_I ? "slti" : "sltiu",
7155 "t,r,j", dreg, sreg, (int) BFD_RELOC_LO16);
7160 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_GPRS);
7161 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7162 mask == M_SGE_I ? "slt" : "sltu", "d,v,t", dreg, sreg,
7166 macro_build ((char *) NULL, &icnt, &expr1, "xori", "t,r,i", dreg, dreg,
7167 (int) BFD_RELOC_LO16);
7172 case M_SGT: /* sreg > treg <==> treg < sreg */
7178 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "d,v,t",
7182 case M_SGT_I: /* sreg > I <==> I < sreg */
7188 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_GPRS);
7189 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "d,v,t",
7193 case M_SLE: /* sreg <= treg <==> treg >= sreg <==> not (treg < sreg) */
7199 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "d,v,t",
7201 macro_build ((char *) NULL, &icnt, &expr1, "xori", "t,r,i", dreg, dreg,
7202 (int) BFD_RELOC_LO16);
7205 case M_SLE_I: /* sreg <= I <==> I >= sreg <==> not (I < sreg) */
7211 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_GPRS);
7212 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "d,v,t",
7214 macro_build ((char *) NULL, &icnt, &expr1, "xori", "t,r,i", dreg, dreg,
7215 (int) BFD_RELOC_LO16);
7219 if (imm_expr.X_op == O_constant
7220 && imm_expr.X_add_number >= -0x8000
7221 && imm_expr.X_add_number < 0x8000)
7223 macro_build ((char *) NULL, &icnt, &imm_expr, "slti", "t,r,j",
7224 dreg, sreg, (int) BFD_RELOC_LO16);
7227 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_GPRS);
7228 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "slt", "d,v,t",
7233 if (imm_expr.X_op == O_constant
7234 && imm_expr.X_add_number >= -0x8000
7235 && imm_expr.X_add_number < 0x8000)
7237 macro_build ((char *) NULL, &icnt, &imm_expr, "sltiu", "t,r,j",
7238 dreg, sreg, (int) BFD_RELOC_LO16);
7241 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_GPRS);
7242 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sltu",
7243 "d,v,t", dreg, sreg, AT);
7248 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sltu",
7249 "d,v,t", dreg, 0, treg);
7251 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sltu",
7252 "d,v,t", dreg, 0, sreg);
7255 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "xor",
7256 "d,v,t", dreg, sreg, treg);
7257 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sltu",
7258 "d,v,t", dreg, 0, dreg);
7263 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
7265 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sltu",
7266 "d,v,t", dreg, 0, sreg);
7271 as_warn (_("Instruction %s: result is always true"),
7273 macro_build ((char *) NULL, &icnt, &expr1,
7274 HAVE_32BIT_GPRS ? "addiu" : "daddiu",
7275 "t,r,j", dreg, 0, (int) BFD_RELOC_LO16);
7278 if (imm_expr.X_op == O_constant
7279 && imm_expr.X_add_number >= 0
7280 && imm_expr.X_add_number < 0x10000)
7282 macro_build ((char *) NULL, &icnt, &imm_expr, "xori", "t,r,i",
7283 dreg, sreg, (int) BFD_RELOC_LO16);
7286 else if (imm_expr.X_op == O_constant
7287 && imm_expr.X_add_number > -0x8000
7288 && imm_expr.X_add_number < 0)
7290 imm_expr.X_add_number = -imm_expr.X_add_number;
7291 macro_build ((char *) NULL, &icnt, &imm_expr,
7292 HAVE_32BIT_GPRS ? "addiu" : "daddiu",
7293 "t,r,j", dreg, sreg, (int) BFD_RELOC_LO16);
7298 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_GPRS);
7299 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "xor",
7300 "d,v,t", dreg, sreg, AT);
7303 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sltu",
7304 "d,v,t", dreg, 0, dreg);
7312 if (imm_expr.X_op == O_constant
7313 && imm_expr.X_add_number > -0x8000
7314 && imm_expr.X_add_number <= 0x8000)
7316 imm_expr.X_add_number = -imm_expr.X_add_number;
7317 macro_build ((char *) NULL, &icnt, &imm_expr,
7318 dbl ? "daddi" : "addi",
7319 "t,r,j", dreg, sreg, (int) BFD_RELOC_LO16);
7322 load_register (&icnt, AT, &imm_expr, dbl);
7323 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7324 dbl ? "dsub" : "sub", "d,v,t", dreg, sreg, AT);
7330 if (imm_expr.X_op == O_constant
7331 && imm_expr.X_add_number > -0x8000
7332 && imm_expr.X_add_number <= 0x8000)
7334 imm_expr.X_add_number = -imm_expr.X_add_number;
7335 macro_build ((char *) NULL, &icnt, &imm_expr,
7336 dbl ? "daddiu" : "addiu",
7337 "t,r,j", dreg, sreg, (int) BFD_RELOC_LO16);
7340 load_register (&icnt, AT, &imm_expr, dbl);
7341 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7342 dbl ? "dsubu" : "subu", "d,v,t", dreg, sreg, AT);
7363 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_GPRS);
7364 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "s,t", sreg,
7370 assert (mips_opts.isa == ISA_MIPS1);
7371 sreg = (ip->insn_opcode >> 11) & 0x1f; /* floating reg */
7372 dreg = (ip->insn_opcode >> 06) & 0x1f; /* floating reg */
7375 * Is the double cfc1 instruction a bug in the mips assembler;
7376 * or is there a reason for it?
7378 mips_emit_delays (true);
7379 ++mips_opts.noreorder;
7380 mips_any_noreorder = 1;
7381 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "cfc1", "t,G",
7383 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "cfc1", "t,G",
7385 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "");
7386 expr1.X_add_number = 3;
7387 macro_build ((char *) NULL, &icnt, &expr1, "ori", "t,r,i", AT, treg,
7388 (int) BFD_RELOC_LO16);
7389 expr1.X_add_number = 2;
7390 macro_build ((char *) NULL, &icnt, &expr1, "xori", "t,r,i", AT, AT,
7391 (int) BFD_RELOC_LO16);
7392 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "ctc1", "t,G",
7394 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "");
7395 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7396 mask == M_TRUNCWD ? "cvt.w.d" : "cvt.w.s", "D,S", dreg, sreg);
7397 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "ctc1", "t,G",
7399 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "");
7400 --mips_opts.noreorder;
7409 if (offset_expr.X_add_number >= 0x7fff)
7410 as_bad (_("operand overflow"));
7411 /* avoid load delay */
7412 if (! target_big_endian)
7413 ++offset_expr.X_add_number;
7414 macro_build ((char *) NULL, &icnt, &offset_expr, s, "t,o(b)", treg,
7415 (int) BFD_RELOC_LO16, breg);
7416 if (! target_big_endian)
7417 --offset_expr.X_add_number;
7419 ++offset_expr.X_add_number;
7420 macro_build ((char *) NULL, &icnt, &offset_expr, "lbu", "t,o(b)", AT,
7421 (int) BFD_RELOC_LO16, breg);
7422 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sll", "d,w,<",
7424 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or", "d,v,t",
7438 if (offset_expr.X_add_number >= 0x8000 - off)
7439 as_bad (_("operand overflow"));
7440 if (! target_big_endian)
7441 offset_expr.X_add_number += off;
7442 macro_build ((char *) NULL, &icnt, &offset_expr, s, "t,o(b)", treg,
7443 (int) BFD_RELOC_LO16, breg);
7444 if (! target_big_endian)
7445 offset_expr.X_add_number -= off;
7447 offset_expr.X_add_number += off;
7448 macro_build ((char *) NULL, &icnt, &offset_expr, s2, "t,o(b)", treg,
7449 (int) BFD_RELOC_LO16, breg);
7463 load_address (&icnt, AT, &offset_expr, &used_at);
7465 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7466 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
7467 "d,v,t", AT, AT, breg);
7468 if (! target_big_endian)
7469 expr1.X_add_number = off;
7471 expr1.X_add_number = 0;
7472 macro_build ((char *) NULL, &icnt, &expr1, s, "t,o(b)", treg,
7473 (int) BFD_RELOC_LO16, AT);
7474 if (! target_big_endian)
7475 expr1.X_add_number = 0;
7477 expr1.X_add_number = off;
7478 macro_build ((char *) NULL, &icnt, &expr1, s2, "t,o(b)", treg,
7479 (int) BFD_RELOC_LO16, AT);
7485 load_address (&icnt, AT, &offset_expr, &used_at);
7487 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7488 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
7489 "d,v,t", AT, AT, breg);
7490 if (target_big_endian)
7491 expr1.X_add_number = 0;
7492 macro_build ((char *) NULL, &icnt, &expr1,
7493 mask == M_ULH_A ? "lb" : "lbu", "t,o(b)", treg,
7494 (int) BFD_RELOC_LO16, AT);
7495 if (target_big_endian)
7496 expr1.X_add_number = 1;
7498 expr1.X_add_number = 0;
7499 macro_build ((char *) NULL, &icnt, &expr1, "lbu", "t,o(b)", AT,
7500 (int) BFD_RELOC_LO16, AT);
7501 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sll", "d,w,<",
7503 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or", "d,v,t",
7508 if (offset_expr.X_add_number >= 0x7fff)
7509 as_bad (_("operand overflow"));
7510 if (target_big_endian)
7511 ++offset_expr.X_add_number;
7512 macro_build ((char *) NULL, &icnt, &offset_expr, "sb", "t,o(b)", treg,
7513 (int) BFD_RELOC_LO16, breg);
7514 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "srl", "d,w,<",
7516 if (target_big_endian)
7517 --offset_expr.X_add_number;
7519 ++offset_expr.X_add_number;
7520 macro_build ((char *) NULL, &icnt, &offset_expr, "sb", "t,o(b)", AT,
7521 (int) BFD_RELOC_LO16, breg);
7534 if (offset_expr.X_add_number >= 0x8000 - off)
7535 as_bad (_("operand overflow"));
7536 if (! target_big_endian)
7537 offset_expr.X_add_number += off;
7538 macro_build ((char *) NULL, &icnt, &offset_expr, s, "t,o(b)", treg,
7539 (int) BFD_RELOC_LO16, breg);
7540 if (! target_big_endian)
7541 offset_expr.X_add_number -= off;
7543 offset_expr.X_add_number += off;
7544 macro_build ((char *) NULL, &icnt, &offset_expr, s2, "t,o(b)", treg,
7545 (int) BFD_RELOC_LO16, breg);
7559 load_address (&icnt, AT, &offset_expr, &used_at);
7561 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7562 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
7563 "d,v,t", AT, AT, breg);
7564 if (! target_big_endian)
7565 expr1.X_add_number = off;
7567 expr1.X_add_number = 0;
7568 macro_build ((char *) NULL, &icnt, &expr1, s, "t,o(b)", treg,
7569 (int) BFD_RELOC_LO16, AT);
7570 if (! target_big_endian)
7571 expr1.X_add_number = 0;
7573 expr1.X_add_number = off;
7574 macro_build ((char *) NULL, &icnt, &expr1, s2, "t,o(b)", treg,
7575 (int) BFD_RELOC_LO16, AT);
7580 load_address (&icnt, AT, &offset_expr, &used_at);
7582 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7583 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
7584 "d,v,t", AT, AT, breg);
7585 if (! target_big_endian)
7586 expr1.X_add_number = 0;
7587 macro_build ((char *) NULL, &icnt, &expr1, "sb", "t,o(b)", treg,
7588 (int) BFD_RELOC_LO16, AT);
7589 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "srl", "d,w,<",
7591 if (! target_big_endian)
7592 expr1.X_add_number = 1;
7594 expr1.X_add_number = 0;
7595 macro_build ((char *) NULL, &icnt, &expr1, "sb", "t,o(b)", treg,
7596 (int) BFD_RELOC_LO16, AT);
7597 if (! target_big_endian)
7598 expr1.X_add_number = 0;
7600 expr1.X_add_number = 1;
7601 macro_build ((char *) NULL, &icnt, &expr1, "lbu", "t,o(b)", AT,
7602 (int) BFD_RELOC_LO16, AT);
7603 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sll", "d,w,<",
7605 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or", "d,v,t",
7610 /* FIXME: Check if this is one of the itbl macros, since they
7611 are added dynamically. */
7612 as_bad (_("Macro %s not implemented yet"), ip->insn_mo->name);
7616 as_warn (_("Macro used $at after \".set noat\""));
7619 /* Implement macros in mips16 mode. */
7623 struct mips_cl_insn *ip;
7626 int xreg, yreg, zreg, tmp;
7630 const char *s, *s2, *s3;
7632 mask = ip->insn_mo->mask;
7634 xreg = (ip->insn_opcode >> MIPS16OP_SH_RX) & MIPS16OP_MASK_RX;
7635 yreg = (ip->insn_opcode >> MIPS16OP_SH_RY) & MIPS16OP_MASK_RY;
7636 zreg = (ip->insn_opcode >> MIPS16OP_SH_RZ) & MIPS16OP_MASK_RZ;
7640 expr1.X_op = O_constant;
7641 expr1.X_op_symbol = NULL;
7642 expr1.X_add_symbol = NULL;
7643 expr1.X_add_number = 1;
7662 mips_emit_delays (true);
7663 ++mips_opts.noreorder;
7664 mips_any_noreorder = 1;
7665 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7666 dbl ? "ddiv" : "div",
7667 "0,x,y", xreg, yreg);
7668 expr1.X_add_number = 2;
7669 macro_build ((char *) NULL, &icnt, &expr1, "bnez", "x,p", yreg);
7670 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "break", "6",
7673 /* FIXME: The normal code checks for of -1 / -0x80000000 here,
7674 since that causes an overflow. We should do that as well,
7675 but I don't see how to do the comparisons without a temporary
7677 --mips_opts.noreorder;
7678 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "x", zreg);
7697 mips_emit_delays (true);
7698 ++mips_opts.noreorder;
7699 mips_any_noreorder = 1;
7700 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "0,x,y",
7702 expr1.X_add_number = 2;
7703 macro_build ((char *) NULL, &icnt, &expr1, "bnez", "x,p", yreg);
7704 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "break",
7706 --mips_opts.noreorder;
7707 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s2, "x", zreg);
7713 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7714 dbl ? "dmultu" : "multu", "x,y", xreg, yreg);
7715 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "mflo", "x",
7724 if (imm_expr.X_op != O_constant)
7725 as_bad (_("Unsupported large constant"));
7726 imm_expr.X_add_number = -imm_expr.X_add_number;
7727 macro_build ((char *) NULL, &icnt, &imm_expr,
7728 dbl ? "daddiu" : "addiu", "y,x,4", yreg, xreg);
7732 if (imm_expr.X_op != O_constant)
7733 as_bad (_("Unsupported large constant"));
7734 imm_expr.X_add_number = -imm_expr.X_add_number;
7735 macro_build ((char *) NULL, &icnt, &imm_expr, "addiu",
7740 if (imm_expr.X_op != O_constant)
7741 as_bad (_("Unsupported large constant"));
7742 imm_expr.X_add_number = -imm_expr.X_add_number;
7743 macro_build ((char *) NULL, &icnt, &imm_expr, "daddiu",
7766 goto do_reverse_branch;
7770 goto do_reverse_branch;
7782 goto do_reverse_branch;
7793 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "x,y",
7795 macro_build ((char *) NULL, &icnt, &offset_expr, s2, "p");
7822 goto do_addone_branch_i;
7827 goto do_addone_branch_i;
7842 goto do_addone_branch_i;
7849 if (imm_expr.X_op != O_constant)
7850 as_bad (_("Unsupported large constant"));
7851 ++imm_expr.X_add_number;
7854 macro_build ((char *) NULL, &icnt, &imm_expr, s, s3, xreg);
7855 macro_build ((char *) NULL, &icnt, &offset_expr, s2, "p");
7859 expr1.X_add_number = 0;
7860 macro_build ((char *) NULL, &icnt, &expr1, "slti", "x,8", yreg);
7862 move_register (&icnt, xreg, yreg);
7863 expr1.X_add_number = 2;
7864 macro_build ((char *) NULL, &icnt, &expr1, "bteqz", "p");
7865 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7866 "neg", "x,w", xreg, xreg);
7870 /* For consistency checking, verify that all bits are specified either
7871 by the match/mask part of the instruction definition, or by the
7874 validate_mips_insn (opc)
7875 const struct mips_opcode *opc;
7877 const char *p = opc->args;
7879 unsigned long used_bits = opc->mask;
7881 if ((used_bits & opc->match) != opc->match)
7883 as_bad (_("internal: bad mips opcode (mask error): %s %s"),
7884 opc->name, opc->args);
7887 #define USE_BITS(mask,shift) (used_bits |= ((mask) << (shift)))
7894 case '<': USE_BITS (OP_MASK_SHAMT, OP_SH_SHAMT); break;
7895 case '>': USE_BITS (OP_MASK_SHAMT, OP_SH_SHAMT); break;
7897 case 'B': USE_BITS (OP_MASK_CODE20, OP_SH_CODE20); break;
7898 case 'C': USE_BITS (OP_MASK_COPZ, OP_SH_COPZ); break;
7899 case 'D': USE_BITS (OP_MASK_FD, OP_SH_FD); break;
7900 case 'E': USE_BITS (OP_MASK_RT, OP_SH_RT); break;
7902 case 'G': USE_BITS (OP_MASK_RD, OP_SH_RD); break;
7903 case 'H': USE_BITS (OP_MASK_SEL, OP_SH_SEL); break;
7905 case 'J': USE_BITS (OP_MASK_CODE19, OP_SH_CODE19); break;
7907 case 'M': USE_BITS (OP_MASK_CCC, OP_SH_CCC); break;
7908 case 'N': USE_BITS (OP_MASK_BCC, OP_SH_BCC); break;
7909 case 'O': USE_BITS (OP_MASK_ALN, OP_SH_ALN); break;
7910 case 'Q': USE_BITS (OP_MASK_VSEL, OP_SH_VSEL);
7911 USE_BITS (OP_MASK_FT, OP_SH_FT); break;
7912 case 'R': USE_BITS (OP_MASK_FR, OP_SH_FR); break;
7913 case 'S': USE_BITS (OP_MASK_FS, OP_SH_FS); break;
7914 case 'T': USE_BITS (OP_MASK_FT, OP_SH_FT); break;
7915 case 'V': USE_BITS (OP_MASK_FS, OP_SH_FS); break;
7916 case 'W': USE_BITS (OP_MASK_FT, OP_SH_FT); break;
7917 case 'X': USE_BITS (OP_MASK_FD, OP_SH_FD); break;
7918 case 'Y': USE_BITS (OP_MASK_FS, OP_SH_FS); break;
7919 case 'Z': USE_BITS (OP_MASK_FT, OP_SH_FT); break;
7920 case 'a': USE_BITS (OP_MASK_TARGET, OP_SH_TARGET); break;
7921 case 'b': USE_BITS (OP_MASK_RS, OP_SH_RS); break;
7922 case 'c': USE_BITS (OP_MASK_CODE, OP_SH_CODE); break;
7923 case 'd': USE_BITS (OP_MASK_RD, OP_SH_RD); break;
7925 case 'h': USE_BITS (OP_MASK_PREFX, OP_SH_PREFX); break;
7926 case 'i': USE_BITS (OP_MASK_IMMEDIATE, OP_SH_IMMEDIATE); break;
7927 case 'j': USE_BITS (OP_MASK_DELTA, OP_SH_DELTA); break;
7928 case 'k': USE_BITS (OP_MASK_CACHE, OP_SH_CACHE); break;
7930 case 'o': USE_BITS (OP_MASK_DELTA, OP_SH_DELTA); break;
7931 case 'p': USE_BITS (OP_MASK_DELTA, OP_SH_DELTA); break;
7932 case 'q': USE_BITS (OP_MASK_CODE2, OP_SH_CODE2); break;
7933 case 'r': USE_BITS (OP_MASK_RS, OP_SH_RS); break;
7934 case 's': USE_BITS (OP_MASK_RS, OP_SH_RS); break;
7935 case 't': USE_BITS (OP_MASK_RT, OP_SH_RT); break;
7936 case 'u': USE_BITS (OP_MASK_IMMEDIATE, OP_SH_IMMEDIATE); break;
7937 case 'v': USE_BITS (OP_MASK_RS, OP_SH_RS); break;
7938 case 'w': USE_BITS (OP_MASK_RT, OP_SH_RT); break;
7941 case 'P': USE_BITS (OP_MASK_PERFREG, OP_SH_PERFREG); break;
7942 case 'U': USE_BITS (OP_MASK_RD, OP_SH_RD);
7943 USE_BITS (OP_MASK_RT, OP_SH_RT); break;
7944 case 'e': USE_BITS (OP_MASK_VECBYTE, OP_SH_VECBYTE); break;
7945 case '%': USE_BITS (OP_MASK_VECALIGN, OP_SH_VECALIGN); break;
7949 as_bad (_("internal: bad mips opcode (unknown operand type `%c'): %s %s"),
7950 c, opc->name, opc->args);
7954 if (used_bits != 0xffffffff)
7956 as_bad (_("internal: bad mips opcode (bits 0x%lx undefined): %s %s"),
7957 ~used_bits & 0xffffffff, opc->name, opc->args);
7963 /* This routine assembles an instruction into its binary format. As a
7964 side effect, it sets one of the global variables imm_reloc or
7965 offset_reloc to the type of relocation to do if one of the operands
7966 is an address expression. */
7971 struct mips_cl_insn *ip;
7976 struct mips_opcode *insn;
7979 unsigned int lastregno = 0;
7985 /* If the instruction contains a '.', we first try to match an instruction
7986 including the '.'. Then we try again without the '.'. */
7988 for (s = str; *s != '\0' && !ISSPACE (*s); ++s)
7991 /* If we stopped on whitespace, then replace the whitespace with null for
7992 the call to hash_find. Save the character we replaced just in case we
7993 have to re-parse the instruction. */
8000 insn = (struct mips_opcode *) hash_find (op_hash, str);
8002 /* If we didn't find the instruction in the opcode table, try again, but
8003 this time with just the instruction up to, but not including the
8007 /* Restore the character we overwrite above (if any). */
8011 /* Scan up to the first '.' or whitespace. */
8013 *s != '\0' && *s != '.' && !ISSPACE (*s);
8017 /* If we did not find a '.', then we can quit now. */
8020 insn_error = "unrecognized opcode";
8024 /* Lookup the instruction in the hash table. */
8026 if ((insn = (struct mips_opcode *) hash_find (op_hash, str)) == NULL)
8028 insn_error = "unrecognized opcode";
8038 assert (strcmp (insn->name, str) == 0);
8040 if (OPCODE_IS_MEMBER (insn,
8042 | (file_ase_mips16 ? INSN_MIPS16 : 0)
8043 | (mips_opts.ase_mdmx ? INSN_MDMX : 0)
8044 | (mips_opts.ase_mips3d ? INSN_MIPS3D : 0)),
8050 if (insn->pinfo != INSN_MACRO)
8052 if (mips_arch == CPU_R4650 && (insn->pinfo & FP_D) != 0)
8058 if (insn + 1 < &mips_opcodes[NUMOPCODES]
8059 && strcmp (insn->name, insn[1].name) == 0)
8068 static char buf[100];
8069 if (mips_arch_info->is_isa)
8071 _("opcode not supported at this ISA level (%s)"),
8072 mips_cpu_info_from_isa (mips_opts.isa)->name);
8075 _("opcode not supported on this processor: %s (%s)"),
8076 mips_arch_info->name,
8077 mips_cpu_info_from_isa (mips_opts.isa)->name);
8087 ip->insn_opcode = insn->match;
8089 for (args = insn->args;; ++args)
8093 s += strspn (s, " \t");
8097 case '\0': /* end of args */
8110 ip->insn_opcode |= lastregno << OP_SH_RS;
8114 ip->insn_opcode |= lastregno << OP_SH_RT;
8118 ip->insn_opcode |= lastregno << OP_SH_FT;
8122 ip->insn_opcode |= lastregno << OP_SH_FS;
8128 /* Handle optional base register.
8129 Either the base register is omitted or
8130 we must have a left paren. */
8131 /* This is dependent on the next operand specifier
8132 is a base register specification. */
8133 assert (args[1] == 'b' || args[1] == '5'
8134 || args[1] == '-' || args[1] == '4');
8138 case ')': /* these must match exactly */
8145 case '<': /* must be at least one digit */
8147 * According to the manual, if the shift amount is greater
8148 * than 31 or less than 0, then the shift amount should be
8149 * mod 32. In reality the mips assembler issues an error.
8150 * We issue a warning and mask out all but the low 5 bits.
8152 my_getExpression (&imm_expr, s);
8153 check_absolute_expr (ip, &imm_expr);
8154 if ((unsigned long) imm_expr.X_add_number > 31)
8156 as_warn (_("Improper shift amount (%lu)"),
8157 (unsigned long) imm_expr.X_add_number);
8158 imm_expr.X_add_number &= OP_MASK_SHAMT;
8160 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_SHAMT;
8161 imm_expr.X_op = O_absent;
8165 case '>': /* shift amount minus 32 */
8166 my_getExpression (&imm_expr, s);
8167 check_absolute_expr (ip, &imm_expr);
8168 if ((unsigned long) imm_expr.X_add_number < 32
8169 || (unsigned long) imm_expr.X_add_number > 63)
8171 ip->insn_opcode |= (imm_expr.X_add_number - 32) << OP_SH_SHAMT;
8172 imm_expr.X_op = O_absent;
8176 case 'k': /* cache code */
8177 case 'h': /* prefx code */
8178 my_getExpression (&imm_expr, s);
8179 check_absolute_expr (ip, &imm_expr);
8180 if ((unsigned long) imm_expr.X_add_number > 31)
8182 as_warn (_("Invalid value for `%s' (%lu)"),
8184 (unsigned long) imm_expr.X_add_number);
8185 imm_expr.X_add_number &= 0x1f;
8188 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_CACHE;
8190 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_PREFX;
8191 imm_expr.X_op = O_absent;
8195 case 'c': /* break code */
8196 my_getExpression (&imm_expr, s);
8197 check_absolute_expr (ip, &imm_expr);
8198 if ((unsigned long) imm_expr.X_add_number > 1023)
8200 as_warn (_("Illegal break code (%lu)"),
8201 (unsigned long) imm_expr.X_add_number);
8202 imm_expr.X_add_number &= OP_MASK_CODE;
8204 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_CODE;
8205 imm_expr.X_op = O_absent;
8209 case 'q': /* lower break code */
8210 my_getExpression (&imm_expr, s);
8211 check_absolute_expr (ip, &imm_expr);
8212 if ((unsigned long) imm_expr.X_add_number > 1023)
8214 as_warn (_("Illegal lower break code (%lu)"),
8215 (unsigned long) imm_expr.X_add_number);
8216 imm_expr.X_add_number &= OP_MASK_CODE2;
8218 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_CODE2;
8219 imm_expr.X_op = O_absent;
8223 case 'B': /* 20-bit syscall/break code. */
8224 my_getExpression (&imm_expr, s);
8225 check_absolute_expr (ip, &imm_expr);
8226 if ((unsigned long) imm_expr.X_add_number > OP_MASK_CODE20)
8227 as_warn (_("Illegal 20-bit code (%lu)"),
8228 (unsigned long) imm_expr.X_add_number);
8229 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_CODE20;
8230 imm_expr.X_op = O_absent;
8234 case 'C': /* Coprocessor code */
8235 my_getExpression (&imm_expr, s);
8236 check_absolute_expr (ip, &imm_expr);
8237 if ((unsigned long) imm_expr.X_add_number >= (1 << 25))
8239 as_warn (_("Coproccesor code > 25 bits (%lu)"),
8240 (unsigned long) imm_expr.X_add_number);
8241 imm_expr.X_add_number &= ((1 << 25) - 1);
8243 ip->insn_opcode |= imm_expr.X_add_number;
8244 imm_expr.X_op = O_absent;
8248 case 'J': /* 19-bit wait code. */
8249 my_getExpression (&imm_expr, s);
8250 check_absolute_expr (ip, &imm_expr);
8251 if ((unsigned long) imm_expr.X_add_number > OP_MASK_CODE19)
8252 as_warn (_("Illegal 19-bit code (%lu)"),
8253 (unsigned long) imm_expr.X_add_number);
8254 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_CODE19;
8255 imm_expr.X_op = O_absent;
8259 case 'P': /* Performance register */
8260 my_getExpression (&imm_expr, s);
8261 check_absolute_expr (ip, &imm_expr);
8262 if (imm_expr.X_add_number != 0 && imm_expr.X_add_number != 1)
8264 as_warn (_("Invalid performance register (%lu)"),
8265 (unsigned long) imm_expr.X_add_number);
8266 imm_expr.X_add_number &= OP_MASK_PERFREG;
8268 ip->insn_opcode |= (imm_expr.X_add_number << OP_SH_PERFREG);
8269 imm_expr.X_op = O_absent;
8273 case 'b': /* base register */
8274 case 'd': /* destination register */
8275 case 's': /* source register */
8276 case 't': /* target register */
8277 case 'r': /* both target and source */
8278 case 'v': /* both dest and source */
8279 case 'w': /* both dest and target */
8280 case 'E': /* coprocessor target register */
8281 case 'G': /* coprocessor destination register */
8282 case 'x': /* ignore register name */
8283 case 'z': /* must be zero register */
8284 case 'U': /* destination register (clo/clz). */
8299 while (ISDIGIT (*s));
8301 as_bad (_("Invalid register number (%d)"), regno);
8303 else if (*args == 'E' || *args == 'G')
8307 if (s[1] == 'r' && s[2] == 'a')
8312 else if (s[1] == 'f' && s[2] == 'p')
8317 else if (s[1] == 's' && s[2] == 'p')
8322 else if (s[1] == 'g' && s[2] == 'p')
8327 else if (s[1] == 'a' && s[2] == 't')
8332 else if (s[1] == 'k' && s[2] == 't' && s[3] == '0')
8337 else if (s[1] == 'k' && s[2] == 't' && s[3] == '1')
8342 else if (s[1] == 'z' && s[2] == 'e' && s[3] == 'r' && s[4] == 'o')
8347 else if (itbl_have_entries)
8352 p = s + 1; /* advance past '$' */
8353 n = itbl_get_field (&p); /* n is name */
8355 /* See if this is a register defined in an
8357 if (itbl_get_reg_val (n, &r))
8359 /* Get_field advances to the start of
8360 the next field, so we need to back
8361 rack to the end of the last field. */
8365 s = strchr (s, '\0');
8378 as_warn (_("Used $at without \".set noat\""));
8384 if (c == 'r' || c == 'v' || c == 'w')
8391 /* 'z' only matches $0. */
8392 if (c == 'z' && regno != 0)
8395 /* Now that we have assembled one operand, we use the args string
8396 * to figure out where it goes in the instruction. */
8403 ip->insn_opcode |= regno << OP_SH_RS;
8407 ip->insn_opcode |= regno << OP_SH_RD;
8410 ip->insn_opcode |= regno << OP_SH_RD;
8411 ip->insn_opcode |= regno << OP_SH_RT;
8416 ip->insn_opcode |= regno << OP_SH_RT;
8419 /* This case exists because on the r3000 trunc
8420 expands into a macro which requires a gp
8421 register. On the r6000 or r4000 it is
8422 assembled into a single instruction which
8423 ignores the register. Thus the insn version
8424 is MIPS_ISA2 and uses 'x', and the macro
8425 version is MIPS_ISA1 and uses 't'. */
8428 /* This case is for the div instruction, which
8429 acts differently if the destination argument
8430 is $0. This only matches $0, and is checked
8431 outside the switch. */
8434 /* Itbl operand; not yet implemented. FIXME ?? */
8436 /* What about all other operands like 'i', which
8437 can be specified in the opcode table? */
8447 ip->insn_opcode |= lastregno << OP_SH_RS;
8450 ip->insn_opcode |= lastregno << OP_SH_RT;
8455 case 'O': /* MDMX alignment immediate constant. */
8456 my_getExpression (&imm_expr, s);
8457 check_absolute_expr (ip, &imm_expr);
8458 if ((unsigned long) imm_expr.X_add_number > OP_MASK_ALN)
8460 as_warn ("Improper align amount (%ld), using low bits",
8461 (long) imm_expr.X_add_number);
8462 imm_expr.X_add_number &= OP_MASK_ALN;
8464 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_ALN;
8465 imm_expr.X_op = O_absent;
8469 case 'Q': /* MDMX vector, element sel, or const. */
8472 /* MDMX Immediate. */
8473 my_getExpression (&imm_expr, s);
8474 check_absolute_expr (ip, &imm_expr);
8475 if ((unsigned long) imm_expr.X_add_number > OP_MASK_FT)
8477 as_warn (_("Invalid MDMX Immediate (%ld)"),
8478 (long) imm_expr.X_add_number);
8479 imm_expr.X_add_number &= OP_MASK_FT;
8481 imm_expr.X_add_number &= OP_MASK_FT;
8482 if (ip->insn_opcode & (OP_MASK_VSEL << OP_SH_VSEL))
8483 ip->insn_opcode |= MDMX_FMTSEL_IMM_QH << OP_SH_VSEL;
8485 ip->insn_opcode |= MDMX_FMTSEL_IMM_OB << OP_SH_VSEL;
8486 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_FT;
8487 imm_expr.X_op = O_absent;
8491 /* Not MDMX Immediate. Fall through. */
8492 case 'X': /* MDMX destination register. */
8493 case 'Y': /* MDMX source register. */
8494 case 'Z': /* MDMX target register. */
8496 case 'D': /* floating point destination register */
8497 case 'S': /* floating point source register */
8498 case 'T': /* floating point target register */
8499 case 'R': /* floating point source register */
8503 /* Accept $fN for FP and MDMX register numbers, and in
8504 addition accept $vN for MDMX register numbers. */
8505 if ((s[0] == '$' && s[1] == 'f' && ISDIGIT (s[2]))
8506 || (is_mdmx != 0 && s[0] == '$' && s[1] == 'v'
8517 while (ISDIGIT (*s));
8520 as_bad (_("Invalid float register number (%d)"), regno);
8522 if ((regno & 1) != 0
8524 && ! (strcmp (str, "mtc1") == 0
8525 || strcmp (str, "mfc1") == 0
8526 || strcmp (str, "lwc1") == 0
8527 || strcmp (str, "swc1") == 0
8528 || strcmp (str, "l.s") == 0
8529 || strcmp (str, "s.s") == 0))
8530 as_warn (_("Float register should be even, was %d"),
8538 if (c == 'V' || c == 'W')
8549 ip->insn_opcode |= regno << OP_SH_FD;
8554 ip->insn_opcode |= regno << OP_SH_FS;
8557 /* This is like 'Z', but also needs to fix the MDMX
8558 vector/scalar select bits. Note that the
8559 scalar immediate case is handled above. */
8562 int is_qh = (ip->insn_opcode & (1 << OP_SH_VSEL));
8563 int max_el = (is_qh ? 3 : 7);
8565 my_getExpression(&imm_expr, s);
8566 check_absolute_expr (ip, &imm_expr);
8568 if (imm_expr.X_add_number > max_el)
8569 as_bad(_("Bad element selector %ld"),
8570 (long) imm_expr.X_add_number);
8571 imm_expr.X_add_number &= max_el;
8572 ip->insn_opcode |= (imm_expr.X_add_number
8576 as_warn(_("Expecting ']' found '%s'"), s);
8582 if (ip->insn_opcode & (OP_MASK_VSEL << OP_SH_VSEL))
8583 ip->insn_opcode |= (MDMX_FMTSEL_VEC_QH
8586 ip->insn_opcode |= (MDMX_FMTSEL_VEC_OB <<
8593 ip->insn_opcode |= regno << OP_SH_FT;
8596 ip->insn_opcode |= regno << OP_SH_FR;
8606 ip->insn_opcode |= lastregno << OP_SH_FS;
8609 ip->insn_opcode |= lastregno << OP_SH_FT;
8615 my_getExpression (&imm_expr, s);
8616 if (imm_expr.X_op != O_big
8617 && imm_expr.X_op != O_constant)
8618 insn_error = _("absolute expression required");
8623 my_getExpression (&offset_expr, s);
8624 *imm_reloc = BFD_RELOC_32;
8637 unsigned char temp[8];
8639 unsigned int length;
8644 /* These only appear as the last operand in an
8645 instruction, and every instruction that accepts
8646 them in any variant accepts them in all variants.
8647 This means we don't have to worry about backing out
8648 any changes if the instruction does not match.
8650 The difference between them is the size of the
8651 floating point constant and where it goes. For 'F'
8652 and 'L' the constant is 64 bits; for 'f' and 'l' it
8653 is 32 bits. Where the constant is placed is based
8654 on how the MIPS assembler does things:
8657 f -- immediate value
8660 The .lit4 and .lit8 sections are only used if
8661 permitted by the -G argument.
8663 When generating embedded PIC code, we use the
8664 .lit8 section but not the .lit4 section (we can do
8665 .lit4 inline easily; we need to put .lit8
8666 somewhere in the data segment, and using .lit8
8667 permits the linker to eventually combine identical
8670 The code below needs to know whether the target register
8671 is 32 or 64 bits wide. It relies on the fact 'f' and
8672 'F' are used with GPR-based instructions and 'l' and
8673 'L' are used with FPR-based instructions. */
8675 f64 = *args == 'F' || *args == 'L';
8676 using_gprs = *args == 'F' || *args == 'f';
8678 save_in = input_line_pointer;
8679 input_line_pointer = s;
8680 err = md_atof (f64 ? 'd' : 'f', (char *) temp, &len);
8682 s = input_line_pointer;
8683 input_line_pointer = save_in;
8684 if (err != NULL && *err != '\0')
8686 as_bad (_("Bad floating point constant: %s"), err);
8687 memset (temp, '\0', sizeof temp);
8688 length = f64 ? 8 : 4;
8691 assert (length == (unsigned) (f64 ? 8 : 4));
8695 && (! USE_GLOBAL_POINTER_OPT
8696 || mips_pic == EMBEDDED_PIC
8697 || g_switch_value < 4
8698 || (temp[0] == 0 && temp[1] == 0)
8699 || (temp[2] == 0 && temp[3] == 0))))
8701 imm_expr.X_op = O_constant;
8702 if (! target_big_endian)
8703 imm_expr.X_add_number = bfd_getl32 (temp);
8705 imm_expr.X_add_number = bfd_getb32 (temp);
8708 && ! mips_disable_float_construction
8709 /* Constants can only be constructed in GPRs and
8710 copied to FPRs if the GPRs are at least as wide
8711 as the FPRs. Force the constant into memory if
8712 we are using 64-bit FPRs but the GPRs are only
8715 || ! (HAVE_64BIT_FPRS && HAVE_32BIT_GPRS))
8716 && ((temp[0] == 0 && temp[1] == 0)
8717 || (temp[2] == 0 && temp[3] == 0))
8718 && ((temp[4] == 0 && temp[5] == 0)
8719 || (temp[6] == 0 && temp[7] == 0)))
8721 /* The value is simple enough to load with a couple of
8722 instructions. If using 32-bit registers, set
8723 imm_expr to the high order 32 bits and offset_expr to
8724 the low order 32 bits. Otherwise, set imm_expr to
8725 the entire 64 bit constant. */
8726 if (using_gprs ? HAVE_32BIT_GPRS : HAVE_32BIT_FPRS)
8728 imm_expr.X_op = O_constant;
8729 offset_expr.X_op = O_constant;
8730 if (! target_big_endian)
8732 imm_expr.X_add_number = bfd_getl32 (temp + 4);
8733 offset_expr.X_add_number = bfd_getl32 (temp);
8737 imm_expr.X_add_number = bfd_getb32 (temp);
8738 offset_expr.X_add_number = bfd_getb32 (temp + 4);
8740 if (offset_expr.X_add_number == 0)
8741 offset_expr.X_op = O_absent;
8743 else if (sizeof (imm_expr.X_add_number) > 4)
8745 imm_expr.X_op = O_constant;
8746 if (! target_big_endian)
8747 imm_expr.X_add_number = bfd_getl64 (temp);
8749 imm_expr.X_add_number = bfd_getb64 (temp);
8753 imm_expr.X_op = O_big;
8754 imm_expr.X_add_number = 4;
8755 if (! target_big_endian)
8757 generic_bignum[0] = bfd_getl16 (temp);
8758 generic_bignum[1] = bfd_getl16 (temp + 2);
8759 generic_bignum[2] = bfd_getl16 (temp + 4);
8760 generic_bignum[3] = bfd_getl16 (temp + 6);
8764 generic_bignum[0] = bfd_getb16 (temp + 6);
8765 generic_bignum[1] = bfd_getb16 (temp + 4);
8766 generic_bignum[2] = bfd_getb16 (temp + 2);
8767 generic_bignum[3] = bfd_getb16 (temp);
8773 const char *newname;
8776 /* Switch to the right section. */
8778 subseg = now_subseg;
8781 default: /* unused default case avoids warnings. */
8783 newname = RDATA_SECTION_NAME;
8784 if ((USE_GLOBAL_POINTER_OPT && g_switch_value >= 8)
8785 || mips_pic == EMBEDDED_PIC)
8789 if (mips_pic == EMBEDDED_PIC)
8792 newname = RDATA_SECTION_NAME;
8795 assert (!USE_GLOBAL_POINTER_OPT
8796 || g_switch_value >= 4);
8800 new_seg = subseg_new (newname, (subsegT) 0);
8801 if (OUTPUT_FLAVOR == bfd_target_elf_flavour)
8802 bfd_set_section_flags (stdoutput, new_seg,
8807 frag_align (*args == 'l' ? 2 : 3, 0, 0);
8808 if (OUTPUT_FLAVOR == bfd_target_elf_flavour
8809 && strcmp (TARGET_OS, "elf") != 0)
8810 record_alignment (new_seg, 4);
8812 record_alignment (new_seg, *args == 'l' ? 2 : 3);
8814 as_bad (_("Can't use floating point insn in this section"));
8816 /* Set the argument to the current address in the
8818 offset_expr.X_op = O_symbol;
8819 offset_expr.X_add_symbol =
8820 symbol_new ("L0\001", now_seg,
8821 (valueT) frag_now_fix (), frag_now);
8822 offset_expr.X_add_number = 0;
8824 /* Put the floating point number into the section. */
8825 p = frag_more ((int) length);
8826 memcpy (p, temp, length);
8828 /* Switch back to the original section. */
8829 subseg_set (seg, subseg);
8834 case 'i': /* 16 bit unsigned immediate */
8835 case 'j': /* 16 bit signed immediate */
8836 *imm_reloc = BFD_RELOC_LO16;
8837 c = my_getSmallExpression (&imm_expr, s);
8844 *imm_reloc = BFD_RELOC_HI16_S;
8845 imm_unmatched_hi = true;
8848 else if (c == S_EX_HIGHEST)
8849 *imm_reloc = BFD_RELOC_MIPS_HIGHEST;
8850 else if (c == S_EX_HIGHER)
8851 *imm_reloc = BFD_RELOC_MIPS_HIGHER;
8852 else if (c == S_EX_GP_REL)
8854 /* This occurs in NewABI only. */
8855 c = my_getSmallExpression (&imm_expr, s);
8857 as_bad (_("bad composition of relocations"));
8860 c = my_getSmallExpression (&imm_expr, s);
8862 as_bad (_("bad composition of relocations"));
8865 imm_reloc[0] = BFD_RELOC_GPREL16;
8866 imm_reloc[1] = BFD_RELOC_MIPS_SUB;
8867 imm_reloc[2] = BFD_RELOC_LO16;
8873 *imm_reloc = BFD_RELOC_HI16;
8875 else if (imm_expr.X_op == O_constant)
8876 imm_expr.X_add_number &= 0xffff;
8880 if ((c == S_EX_NONE && imm_expr.X_op != O_constant)
8881 || ((imm_expr.X_add_number < 0
8882 || imm_expr.X_add_number >= 0x10000)
8883 && imm_expr.X_op == O_constant))
8885 if (insn + 1 < &mips_opcodes[NUMOPCODES] &&
8886 !strcmp (insn->name, insn[1].name))
8888 if (imm_expr.X_op == O_constant
8889 || imm_expr.X_op == O_big)
8890 as_bad (_("16 bit expression not in range 0..65535"));
8898 /* The upper bound should be 0x8000, but
8899 unfortunately the MIPS assembler accepts numbers
8900 from 0x8000 to 0xffff and sign extends them, and
8901 we want to be compatible. We only permit this
8902 extended range for an instruction which does not
8903 provide any further alternates, since those
8904 alternates may handle other cases. People should
8905 use the numbers they mean, rather than relying on
8906 a mysterious sign extension. */
8907 more = (insn + 1 < &mips_opcodes[NUMOPCODES] &&
8908 strcmp (insn->name, insn[1].name) == 0);
8913 if ((c == S_EX_NONE && imm_expr.X_op != O_constant)
8914 || ((imm_expr.X_add_number < -0x8000
8915 || imm_expr.X_add_number >= max)
8916 && imm_expr.X_op == O_constant)
8918 && imm_expr.X_add_number < 0
8920 && imm_expr.X_unsigned
8921 && sizeof (imm_expr.X_add_number) <= 4))
8925 if (imm_expr.X_op == O_constant
8926 || imm_expr.X_op == O_big)
8927 as_bad (_("16 bit expression not in range -32768..32767"));
8933 case 'o': /* 16 bit offset */
8934 c = my_getSmallExpression (&offset_expr, s);
8936 /* If this value won't fit into a 16 bit offset, then go
8937 find a macro that will generate the 32 bit offset
8940 && (offset_expr.X_op != O_constant
8941 || offset_expr.X_add_number >= 0x8000
8942 || offset_expr.X_add_number < -0x8000))
8947 if (offset_expr.X_op != O_constant)
8949 offset_expr.X_add_number =
8950 (offset_expr.X_add_number >> 16) & 0xffff;
8952 *offset_reloc = BFD_RELOC_LO16;
8956 case 'p': /* pc relative offset */
8957 if (mips_pic == EMBEDDED_PIC)
8958 *offset_reloc = BFD_RELOC_16_PCREL_S2;
8960 *offset_reloc = BFD_RELOC_16_PCREL;
8961 my_getExpression (&offset_expr, s);
8965 case 'u': /* upper 16 bits */
8966 c = my_getSmallExpression (&imm_expr, s);
8967 *imm_reloc = BFD_RELOC_LO16;
8974 *imm_reloc = BFD_RELOC_HI16_S;
8975 imm_unmatched_hi = true;
8978 else if (c == S_EX_HIGHEST)
8979 *imm_reloc = BFD_RELOC_MIPS_HIGHEST;
8980 else if (c == S_EX_GP_REL)
8982 /* This occurs in NewABI only. */
8983 c = my_getSmallExpression (&imm_expr, s);
8985 as_bad (_("bad composition of relocations"));
8988 c = my_getSmallExpression (&imm_expr, s);
8990 as_bad (_("bad composition of relocations"));
8993 imm_reloc[0] = BFD_RELOC_GPREL16;
8994 imm_reloc[1] = BFD_RELOC_MIPS_SUB;
8995 imm_reloc[2] = BFD_RELOC_HI16_S;
9001 *imm_reloc = BFD_RELOC_HI16;
9003 else if (imm_expr.X_op == O_constant)
9004 imm_expr.X_add_number &= 0xffff;
9006 else if (imm_expr.X_op == O_constant
9007 && (imm_expr.X_add_number < 0
9008 || imm_expr.X_add_number >= 0x10000))
9009 as_bad (_("lui expression not in range 0..65535"));
9013 case 'a': /* 26 bit address */
9014 my_getExpression (&offset_expr, s);
9016 *offset_reloc = BFD_RELOC_MIPS_JMP;
9019 case 'N': /* 3 bit branch condition code */
9020 case 'M': /* 3 bit compare condition code */
9021 if (strncmp (s, "$fcc", 4) != 0)
9031 while (ISDIGIT (*s));
9033 as_bad (_("invalid condition code register $fcc%d"), regno);
9035 ip->insn_opcode |= regno << OP_SH_BCC;
9037 ip->insn_opcode |= regno << OP_SH_CCC;
9041 if (s[0] == '0' && (s[1] == 'x' || s[1] == 'X'))
9052 while (ISDIGIT (*s));
9055 c = 8; /* Invalid sel value. */
9058 as_bad (_("invalid coprocessor sub-selection value (0-7)"));
9059 ip->insn_opcode |= c;
9063 /* Must be at least one digit. */
9064 my_getExpression (&imm_expr, s);
9065 check_absolute_expr (ip, &imm_expr);
9067 if ((unsigned long) imm_expr.X_add_number
9068 > (unsigned long) OP_MASK_VECBYTE)
9070 as_bad (_("bad byte vector index (%ld)"),
9071 (long) imm_expr.X_add_number);
9072 imm_expr.X_add_number = 0;
9075 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_VECBYTE;
9076 imm_expr.X_op = O_absent;
9081 my_getExpression (&imm_expr, s);
9082 check_absolute_expr (ip, &imm_expr);
9084 if ((unsigned long) imm_expr.X_add_number
9085 > (unsigned long) OP_MASK_VECALIGN)
9087 as_bad (_("bad byte vector index (%ld)"),
9088 (long) imm_expr.X_add_number);
9089 imm_expr.X_add_number = 0;
9092 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_VECALIGN;
9093 imm_expr.X_op = O_absent;
9098 as_bad (_("bad char = '%c'\n"), *args);
9103 /* Args don't match. */
9104 if (insn + 1 < &mips_opcodes[NUMOPCODES] &&
9105 !strcmp (insn->name, insn[1].name))
9109 insn_error = _("illegal operands");
9114 insn_error = _("illegal operands");
9119 /* This routine assembles an instruction into its binary format when
9120 assembling for the mips16. As a side effect, it sets one of the
9121 global variables imm_reloc or offset_reloc to the type of
9122 relocation to do if one of the operands is an address expression.
9123 It also sets mips16_small and mips16_ext if the user explicitly
9124 requested a small or extended instruction. */
9129 struct mips_cl_insn *ip;
9133 struct mips_opcode *insn;
9136 unsigned int lastregno = 0;
9141 mips16_small = false;
9144 for (s = str; ISLOWER (*s); ++s)
9156 if (s[1] == 't' && s[2] == ' ')
9159 mips16_small = true;
9163 else if (s[1] == 'e' && s[2] == ' ')
9172 insn_error = _("unknown opcode");
9176 if (mips_opts.noautoextend && ! mips16_ext)
9177 mips16_small = true;
9179 if ((insn = (struct mips_opcode *) hash_find (mips16_op_hash, str)) == NULL)
9181 insn_error = _("unrecognized opcode");
9188 assert (strcmp (insn->name, str) == 0);
9191 ip->insn_opcode = insn->match;
9192 ip->use_extend = false;
9193 imm_expr.X_op = O_absent;
9194 imm_reloc[0] = BFD_RELOC_UNUSED;
9195 imm_reloc[1] = BFD_RELOC_UNUSED;
9196 imm_reloc[2] = BFD_RELOC_UNUSED;
9197 offset_expr.X_op = O_absent;
9198 offset_reloc[0] = BFD_RELOC_UNUSED;
9199 offset_reloc[1] = BFD_RELOC_UNUSED;
9200 offset_reloc[2] = BFD_RELOC_UNUSED;
9201 for (args = insn->args; 1; ++args)
9208 /* In this switch statement we call break if we did not find
9209 a match, continue if we did find a match, or return if we
9218 /* Stuff the immediate value in now, if we can. */
9219 if (imm_expr.X_op == O_constant
9220 && *imm_reloc > BFD_RELOC_UNUSED
9221 && insn->pinfo != INSN_MACRO)
9223 mips16_immed (NULL, 0, *imm_reloc - BFD_RELOC_UNUSED,
9224 imm_expr.X_add_number, true, mips16_small,
9225 mips16_ext, &ip->insn_opcode,
9226 &ip->use_extend, &ip->extend);
9227 imm_expr.X_op = O_absent;
9228 *imm_reloc = BFD_RELOC_UNUSED;
9242 ip->insn_opcode |= lastregno << MIPS16OP_SH_RX;
9245 ip->insn_opcode |= lastregno << MIPS16OP_SH_RY;
9261 ip->insn_opcode |= lastregno << MIPS16OP_SH_RX;
9263 ip->insn_opcode |= lastregno << MIPS16OP_SH_RY;
9290 while (ISDIGIT (*s));
9293 as_bad (_("invalid register number (%d)"), regno);
9299 if (s[1] == 'r' && s[2] == 'a')
9304 else if (s[1] == 'f' && s[2] == 'p')
9309 else if (s[1] == 's' && s[2] == 'p')
9314 else if (s[1] == 'g' && s[2] == 'p')
9319 else if (s[1] == 'a' && s[2] == 't')
9324 else if (s[1] == 'k' && s[2] == 't' && s[3] == '0')
9329 else if (s[1] == 'k' && s[2] == 't' && s[3] == '1')
9334 else if (s[1] == 'z' && s[2] == 'e' && s[3] == 'r' && s[4] == 'o')
9347 if (c == 'v' || c == 'w')
9349 regno = mips16_to_32_reg_map[lastregno];
9363 regno = mips32_to_16_reg_map[regno];
9368 regno = ILLEGAL_REG;
9373 regno = ILLEGAL_REG;
9378 regno = ILLEGAL_REG;
9383 if (regno == AT && ! mips_opts.noat)
9384 as_warn (_("used $at without \".set noat\""));
9391 if (regno == ILLEGAL_REG)
9398 ip->insn_opcode |= regno << MIPS16OP_SH_RX;
9402 ip->insn_opcode |= regno << MIPS16OP_SH_RY;
9405 ip->insn_opcode |= regno << MIPS16OP_SH_RZ;
9408 ip->insn_opcode |= regno << MIPS16OP_SH_MOVE32Z;
9414 ip->insn_opcode |= regno << MIPS16OP_SH_REGR32;
9417 regno = ((regno & 7) << 2) | ((regno & 0x18) >> 3);
9418 ip->insn_opcode |= regno << MIPS16OP_SH_REG32R;
9428 if (strncmp (s, "$pc", 3) == 0)
9452 && strncmp (s + 1, "gprel(", sizeof "gprel(" - 1) == 0)
9454 /* This is %gprel(SYMBOL). We need to read SYMBOL,
9455 and generate the appropriate reloc. If the text
9456 inside %gprel is not a symbol name with an
9457 optional offset, then we generate a normal reloc
9458 and will probably fail later. */
9459 my_getExpression (&imm_expr, s + sizeof "%gprel" - 1);
9460 if (imm_expr.X_op == O_symbol)
9463 *imm_reloc = BFD_RELOC_MIPS16_GPREL;
9465 ip->use_extend = true;
9472 /* Just pick up a normal expression. */
9473 my_getExpression (&imm_expr, s);
9476 if (imm_expr.X_op == O_register)
9478 /* What we thought was an expression turned out to
9481 if (s[0] == '(' && args[1] == '(')
9483 /* It looks like the expression was omitted
9484 before a register indirection, which means
9485 that the expression is implicitly zero. We
9486 still set up imm_expr, so that we handle
9487 explicit extensions correctly. */
9488 imm_expr.X_op = O_constant;
9489 imm_expr.X_add_number = 0;
9490 *imm_reloc = (int) BFD_RELOC_UNUSED + c;
9497 /* We need to relax this instruction. */
9498 *imm_reloc = (int) BFD_RELOC_UNUSED + c;
9507 /* We use offset_reloc rather than imm_reloc for the PC
9508 relative operands. This lets macros with both
9509 immediate and address operands work correctly. */
9510 my_getExpression (&offset_expr, s);
9512 if (offset_expr.X_op == O_register)
9515 /* We need to relax this instruction. */
9516 *offset_reloc = (int) BFD_RELOC_UNUSED + c;
9520 case '6': /* break code */
9521 my_getExpression (&imm_expr, s);
9522 check_absolute_expr (ip, &imm_expr);
9523 if ((unsigned long) imm_expr.X_add_number > 63)
9525 as_warn (_("Invalid value for `%s' (%lu)"),
9527 (unsigned long) imm_expr.X_add_number);
9528 imm_expr.X_add_number &= 0x3f;
9530 ip->insn_opcode |= imm_expr.X_add_number << MIPS16OP_SH_IMM6;
9531 imm_expr.X_op = O_absent;
9535 case 'a': /* 26 bit address */
9536 my_getExpression (&offset_expr, s);
9538 *offset_reloc = BFD_RELOC_MIPS16_JMP;
9539 ip->insn_opcode <<= 16;
9542 case 'l': /* register list for entry macro */
9543 case 'L': /* register list for exit macro */
9553 int freg, reg1, reg2;
9555 while (*s == ' ' || *s == ',')
9559 as_bad (_("can't parse register list"));
9571 while (ISDIGIT (*s))
9593 as_bad (_("invalid register list"));
9598 while (ISDIGIT (*s))
9605 if (freg && reg1 == 0 && reg2 == 0 && c == 'L')
9610 else if (freg && reg1 == 0 && reg2 == 1 && c == 'L')
9615 else if (reg1 == 4 && reg2 >= 4 && reg2 <= 7 && c != 'L')
9616 mask |= (reg2 - 3) << 3;
9617 else if (reg1 == 16 && reg2 >= 16 && reg2 <= 17)
9618 mask |= (reg2 - 15) << 1;
9619 else if (reg1 == RA && reg2 == RA)
9623 as_bad (_("invalid register list"));
9627 /* The mask is filled in in the opcode table for the
9628 benefit of the disassembler. We remove it before
9629 applying the actual mask. */
9630 ip->insn_opcode &= ~ ((7 << 3) << MIPS16OP_SH_IMM6);
9631 ip->insn_opcode |= mask << MIPS16OP_SH_IMM6;
9635 case 'e': /* extend code */
9636 my_getExpression (&imm_expr, s);
9637 check_absolute_expr (ip, &imm_expr);
9638 if ((unsigned long) imm_expr.X_add_number > 0x7ff)
9640 as_warn (_("Invalid value for `%s' (%lu)"),
9642 (unsigned long) imm_expr.X_add_number);
9643 imm_expr.X_add_number &= 0x7ff;
9645 ip->insn_opcode |= imm_expr.X_add_number;
9646 imm_expr.X_op = O_absent;
9656 /* Args don't match. */
9657 if (insn + 1 < &mips16_opcodes[bfd_mips16_num_opcodes] &&
9658 strcmp (insn->name, insn[1].name) == 0)
9665 insn_error = _("illegal operands");
9671 /* This structure holds information we know about a mips16 immediate
9674 struct mips16_immed_operand
9676 /* The type code used in the argument string in the opcode table. */
9678 /* The number of bits in the short form of the opcode. */
9680 /* The number of bits in the extended form of the opcode. */
9682 /* The amount by which the short form is shifted when it is used;
9683 for example, the sw instruction has a shift count of 2. */
9685 /* The amount by which the short form is shifted when it is stored
9686 into the instruction code. */
9688 /* Non-zero if the short form is unsigned. */
9690 /* Non-zero if the extended form is unsigned. */
9692 /* Non-zero if the value is PC relative. */
9696 /* The mips16 immediate operand types. */
9698 static const struct mips16_immed_operand mips16_immed_operands[] =
9700 { '<', 3, 5, 0, MIPS16OP_SH_RZ, 1, 1, 0 },
9701 { '>', 3, 5, 0, MIPS16OP_SH_RX, 1, 1, 0 },
9702 { '[', 3, 6, 0, MIPS16OP_SH_RZ, 1, 1, 0 },
9703 { ']', 3, 6, 0, MIPS16OP_SH_RX, 1, 1, 0 },
9704 { '4', 4, 15, 0, MIPS16OP_SH_IMM4, 0, 0, 0 },
9705 { '5', 5, 16, 0, MIPS16OP_SH_IMM5, 1, 0, 0 },
9706 { 'H', 5, 16, 1, MIPS16OP_SH_IMM5, 1, 0, 0 },
9707 { 'W', 5, 16, 2, MIPS16OP_SH_IMM5, 1, 0, 0 },
9708 { 'D', 5, 16, 3, MIPS16OP_SH_IMM5, 1, 0, 0 },
9709 { 'j', 5, 16, 0, MIPS16OP_SH_IMM5, 0, 0, 0 },
9710 { '8', 8, 16, 0, MIPS16OP_SH_IMM8, 1, 0, 0 },
9711 { 'V', 8, 16, 2, MIPS16OP_SH_IMM8, 1, 0, 0 },
9712 { 'C', 8, 16, 3, MIPS16OP_SH_IMM8, 1, 0, 0 },
9713 { 'U', 8, 16, 0, MIPS16OP_SH_IMM8, 1, 1, 0 },
9714 { 'k', 8, 16, 0, MIPS16OP_SH_IMM8, 0, 0, 0 },
9715 { 'K', 8, 16, 3, MIPS16OP_SH_IMM8, 0, 0, 0 },
9716 { 'p', 8, 16, 0, MIPS16OP_SH_IMM8, 0, 0, 1 },
9717 { 'q', 11, 16, 0, MIPS16OP_SH_IMM8, 0, 0, 1 },
9718 { 'A', 8, 16, 2, MIPS16OP_SH_IMM8, 1, 0, 1 },
9719 { 'B', 5, 16, 3, MIPS16OP_SH_IMM5, 1, 0, 1 },
9720 { 'E', 5, 16, 2, MIPS16OP_SH_IMM5, 1, 0, 1 }
9723 #define MIPS16_NUM_IMMED \
9724 (sizeof mips16_immed_operands / sizeof mips16_immed_operands[0])
9726 /* Handle a mips16 instruction with an immediate value. This or's the
9727 small immediate value into *INSN. It sets *USE_EXTEND to indicate
9728 whether an extended value is needed; if one is needed, it sets
9729 *EXTEND to the value. The argument type is TYPE. The value is VAL.
9730 If SMALL is true, an unextended opcode was explicitly requested.
9731 If EXT is true, an extended opcode was explicitly requested. If
9732 WARN is true, warn if EXT does not match reality. */
9735 mips16_immed (file, line, type, val, warn, small, ext, insn, use_extend,
9744 unsigned long *insn;
9745 boolean *use_extend;
9746 unsigned short *extend;
9748 register const struct mips16_immed_operand *op;
9749 int mintiny, maxtiny;
9752 op = mips16_immed_operands;
9753 while (op->type != type)
9756 assert (op < mips16_immed_operands + MIPS16_NUM_IMMED);
9761 if (type == '<' || type == '>' || type == '[' || type == ']')
9764 maxtiny = 1 << op->nbits;
9769 maxtiny = (1 << op->nbits) - 1;
9774 mintiny = - (1 << (op->nbits - 1));
9775 maxtiny = (1 << (op->nbits - 1)) - 1;
9778 /* Branch offsets have an implicit 0 in the lowest bit. */
9779 if (type == 'p' || type == 'q')
9782 if ((val & ((1 << op->shift) - 1)) != 0
9783 || val < (mintiny << op->shift)
9784 || val > (maxtiny << op->shift))
9789 if (warn && ext && ! needext)
9790 as_warn_where (file, line,
9791 _("extended operand requested but not required"));
9792 if (small && needext)
9793 as_bad_where (file, line, _("invalid unextended operand value"));
9795 if (small || (! ext && ! needext))
9799 *use_extend = false;
9800 insnval = ((val >> op->shift) & ((1 << op->nbits) - 1));
9801 insnval <<= op->op_shift;
9806 long minext, maxext;
9812 maxext = (1 << op->extbits) - 1;
9816 minext = - (1 << (op->extbits - 1));
9817 maxext = (1 << (op->extbits - 1)) - 1;
9819 if (val < minext || val > maxext)
9820 as_bad_where (file, line,
9821 _("operand value out of range for instruction"));
9824 if (op->extbits == 16)
9826 extval = ((val >> 11) & 0x1f) | (val & 0x7e0);
9829 else if (op->extbits == 15)
9831 extval = ((val >> 11) & 0xf) | (val & 0x7f0);
9836 extval = ((val & 0x1f) << 6) | (val & 0x20);
9840 *extend = (unsigned short) extval;
9845 static struct percent_op_match
9848 const enum small_ex_type type;
9853 {"%call_hi", S_EX_CALL_HI},
9854 {"%call_lo", S_EX_CALL_LO},
9855 {"%call16", S_EX_CALL16},
9856 {"%got_disp", S_EX_GOT_DISP},
9857 {"%got_page", S_EX_GOT_PAGE},
9858 {"%got_ofst", S_EX_GOT_OFST},
9859 {"%got_hi", S_EX_GOT_HI},
9860 {"%got_lo", S_EX_GOT_LO},
9862 {"%gp_rel", S_EX_GP_REL},
9863 {"%half", S_EX_HALF},
9864 {"%highest", S_EX_HIGHEST},
9865 {"%higher", S_EX_HIGHER},
9871 /* Parse small expression input. STR gets adjusted to eat up whitespace.
9872 It detects valid "%percent_op(...)" and "($reg)" strings. Percent_op's
9873 can be nested, this is handled by blanking the innermost, parsing the
9874 rest by subsequent calls. */
9877 my_getSmallParser (str, len, nestlevel)
9883 *str += strspn (*str, " \t");
9884 /* Check for expression in parentheses. */
9887 char *b = *str + 1 + strspn (*str + 1, " \t");
9890 /* Check for base register. */
9894 && (e = b + strcspn (b, ") \t"))
9895 && e - b > 1 && e - b < 4)
9898 && ((b[1] == 'f' && b[2] == 'p')
9899 || (b[1] == 's' && b[2] == 'p')
9900 || (b[1] == 'g' && b[2] == 'p')
9901 || (b[1] == 'a' && b[2] == 't')
9903 && ISDIGIT (b[2]))))
9904 || (ISDIGIT (b[1])))
9906 *len = strcspn (*str, ")") + 1;
9907 return S_EX_REGISTER;
9911 /* Check for percent_op (in parentheses). */
9912 else if (b[0] == '%')
9915 return my_getPercentOp (str, len, nestlevel);
9918 /* Some other expression in the parentheses, which can contain
9919 parentheses itself. Attempt to find the matching one. */
9925 for (s = *str + 1; *s && pcnt; s++, (*len)++)
9934 /* Check for percent_op (outside of parentheses). */
9935 else if (*str[0] == '%')
9936 return my_getPercentOp (str, len, nestlevel);
9938 /* Any other expression. */
9943 my_getPercentOp (str, len, nestlevel)
9948 char *tmp = *str + 1;
9951 while (ISALPHA (*tmp) || *tmp == '_')
9953 *tmp = TOLOWER (*tmp);
9956 while (i < (sizeof (percent_op) / sizeof (struct percent_op_match)))
9958 if (strncmp (*str, percent_op[i].str, strlen (percent_op[i].str)))
9962 int type = percent_op[i].type;
9964 /* Only %hi and %lo are allowed for OldABI. */
9965 if (! HAVE_NEWABI && type != S_EX_HI && type != S_EX_LO)
9968 *len = strlen (percent_op[i].str);
9977 my_getSmallExpression (ep, str)
9981 static char *oldstr = NULL;
9987 /* Don't update oldstr if the last call had nested percent_op's. We need
9988 it to parse the outer ones later. */
9995 c = my_getSmallParser (&str, &len, &nestlevel);
9996 if (c != S_EX_NONE && c != S_EX_REGISTER)
9999 while (c != S_EX_NONE && c != S_EX_REGISTER);
10001 if (nestlevel >= 0)
10003 /* A percent_op was encountered. Don't try to get an expression if
10004 it is already blanked out. */
10005 if (*(str + strspn (str + 1, " )")) != ')')
10009 /* Let my_getExpression() stop at the closing parenthesis. */
10010 save = *(str + len);
10011 *(str + len) = '\0';
10012 my_getExpression (ep, str);
10013 *(str + len) = save;
10017 /* Blank out including the % sign and the proper matching
10020 char *s = strrchr (oldstr, '%');
10023 for (end = strchr (s, '(') + 1; *end && pcnt; end++)
10027 else if (*end == ')')
10031 memset (s, ' ', end - s);
10035 expr_end = str + len;
10039 else if (c == S_EX_NONE)
10041 my_getExpression (ep, str);
10043 else if (c == S_EX_REGISTER)
10045 ep->X_op = O_constant;
10047 ep->X_add_symbol = NULL;
10048 ep->X_op_symbol = NULL;
10049 ep->X_add_number = 0;
10053 as_fatal (_("internal error"));
10056 if (nestlevel <= 0)
10057 /* All percent_op's have been handled. */
10064 my_getExpression (ep, str)
10071 save_in = input_line_pointer;
10072 input_line_pointer = str;
10074 expr_end = input_line_pointer;
10075 input_line_pointer = save_in;
10077 /* If we are in mips16 mode, and this is an expression based on `.',
10078 then we bump the value of the symbol by 1 since that is how other
10079 text symbols are handled. We don't bother to handle complex
10080 expressions, just `.' plus or minus a constant. */
10081 if (mips_opts.mips16
10082 && ep->X_op == O_symbol
10083 && strcmp (S_GET_NAME (ep->X_add_symbol), FAKE_LABEL_NAME) == 0
10084 && S_GET_SEGMENT (ep->X_add_symbol) == now_seg
10085 && symbol_get_frag (ep->X_add_symbol) == frag_now
10086 && symbol_constant_p (ep->X_add_symbol)
10087 && (val = S_GET_VALUE (ep->X_add_symbol)) == frag_now_fix ())
10088 S_SET_VALUE (ep->X_add_symbol, val + 1);
10091 /* Turn a string in input_line_pointer into a floating point constant
10092 of type TYPE, and store the appropriate bytes in *LITP. The number
10093 of LITTLENUMS emitted is stored in *SIZEP. An error message is
10094 returned, or NULL on OK. */
10097 md_atof (type, litP, sizeP)
10103 LITTLENUM_TYPE words[4];
10119 return _("bad call to md_atof");
10122 t = atof_ieee (input_line_pointer, type, words);
10124 input_line_pointer = t;
10128 if (! target_big_endian)
10130 for (i = prec - 1; i >= 0; i--)
10132 md_number_to_chars (litP, (valueT) words[i], 2);
10138 for (i = 0; i < prec; i++)
10140 md_number_to_chars (litP, (valueT) words[i], 2);
10149 md_number_to_chars (buf, val, n)
10154 if (target_big_endian)
10155 number_to_chars_bigendian (buf, val, n);
10157 number_to_chars_littleendian (buf, val, n);
10161 static int support_64bit_objects(void)
10163 const char **list, **l;
10165 list = bfd_target_list ();
10166 for (l = list; *l != NULL; l++)
10168 /* This is traditional mips */
10169 if (strcmp (*l, "elf64-tradbigmips") == 0
10170 || strcmp (*l, "elf64-tradlittlemips") == 0)
10172 if (strcmp (*l, "elf64-bigmips") == 0
10173 || strcmp (*l, "elf64-littlemips") == 0)
10177 return (*l != NULL);
10179 #endif /* OBJ_ELF */
10181 const char *md_shortopts = "nO::g::G:";
10183 struct option md_longopts[] =
10185 #define OPTION_MIPS1 (OPTION_MD_BASE + 1)
10186 {"mips0", no_argument, NULL, OPTION_MIPS1},
10187 {"mips1", no_argument, NULL, OPTION_MIPS1},
10188 #define OPTION_MIPS2 (OPTION_MD_BASE + 2)
10189 {"mips2", no_argument, NULL, OPTION_MIPS2},
10190 #define OPTION_MIPS3 (OPTION_MD_BASE + 3)
10191 {"mips3", no_argument, NULL, OPTION_MIPS3},
10192 #define OPTION_MIPS4 (OPTION_MD_BASE + 4)
10193 {"mips4", no_argument, NULL, OPTION_MIPS4},
10194 #define OPTION_MIPS5 (OPTION_MD_BASE + 5)
10195 {"mips5", no_argument, NULL, OPTION_MIPS5},
10196 #define OPTION_MIPS32 (OPTION_MD_BASE + 6)
10197 {"mips32", no_argument, NULL, OPTION_MIPS32},
10198 #define OPTION_MIPS64 (OPTION_MD_BASE + 7)
10199 {"mips64", no_argument, NULL, OPTION_MIPS64},
10200 #define OPTION_MEMBEDDED_PIC (OPTION_MD_BASE + 8)
10201 {"membedded-pic", no_argument, NULL, OPTION_MEMBEDDED_PIC},
10202 #define OPTION_TRAP (OPTION_MD_BASE + 9)
10203 {"trap", no_argument, NULL, OPTION_TRAP},
10204 {"no-break", no_argument, NULL, OPTION_TRAP},
10205 #define OPTION_BREAK (OPTION_MD_BASE + 10)
10206 {"break", no_argument, NULL, OPTION_BREAK},
10207 {"no-trap", no_argument, NULL, OPTION_BREAK},
10208 #define OPTION_EB (OPTION_MD_BASE + 11)
10209 {"EB", no_argument, NULL, OPTION_EB},
10210 #define OPTION_EL (OPTION_MD_BASE + 12)
10211 {"EL", no_argument, NULL, OPTION_EL},
10212 #define OPTION_MIPS16 (OPTION_MD_BASE + 13)
10213 {"mips16", no_argument, NULL, OPTION_MIPS16},
10214 #define OPTION_NO_MIPS16 (OPTION_MD_BASE + 14)
10215 {"no-mips16", no_argument, NULL, OPTION_NO_MIPS16},
10216 #define OPTION_M7000_HILO_FIX (OPTION_MD_BASE + 15)
10217 {"mfix7000", no_argument, NULL, OPTION_M7000_HILO_FIX},
10218 #define OPTION_MNO_7000_HILO_FIX (OPTION_MD_BASE + 16)
10219 {"no-fix-7000", no_argument, NULL, OPTION_MNO_7000_HILO_FIX},
10220 {"mno-fix7000", no_argument, NULL, OPTION_MNO_7000_HILO_FIX},
10221 #define OPTION_FP32 (OPTION_MD_BASE + 17)
10222 {"mfp32", no_argument, NULL, OPTION_FP32},
10223 #define OPTION_GP32 (OPTION_MD_BASE + 18)
10224 {"mgp32", no_argument, NULL, OPTION_GP32},
10225 #define OPTION_CONSTRUCT_FLOATS (OPTION_MD_BASE + 19)
10226 {"construct-floats", no_argument, NULL, OPTION_CONSTRUCT_FLOATS},
10227 #define OPTION_NO_CONSTRUCT_FLOATS (OPTION_MD_BASE + 20)
10228 {"no-construct-floats", no_argument, NULL, OPTION_NO_CONSTRUCT_FLOATS},
10229 #define OPTION_MARCH (OPTION_MD_BASE + 21)
10230 {"march", required_argument, NULL, OPTION_MARCH},
10231 #define OPTION_MTUNE (OPTION_MD_BASE + 22)
10232 {"mtune", required_argument, NULL, OPTION_MTUNE},
10233 #define OPTION_FP64 (OPTION_MD_BASE + 23)
10234 {"mfp64", no_argument, NULL, OPTION_FP64},
10235 #define OPTION_M4650 (OPTION_MD_BASE + 24)
10236 {"m4650", no_argument, NULL, OPTION_M4650},
10237 #define OPTION_NO_M4650 (OPTION_MD_BASE + 25)
10238 {"no-m4650", no_argument, NULL, OPTION_NO_M4650},
10239 #define OPTION_M4010 (OPTION_MD_BASE + 26)
10240 {"m4010", no_argument, NULL, OPTION_M4010},
10241 #define OPTION_NO_M4010 (OPTION_MD_BASE + 27)
10242 {"no-m4010", no_argument, NULL, OPTION_NO_M4010},
10243 #define OPTION_M4100 (OPTION_MD_BASE + 28)
10244 {"m4100", no_argument, NULL, OPTION_M4100},
10245 #define OPTION_NO_M4100 (OPTION_MD_BASE + 29)
10246 {"no-m4100", no_argument, NULL, OPTION_NO_M4100},
10247 #define OPTION_M3900 (OPTION_MD_BASE + 30)
10248 {"m3900", no_argument, NULL, OPTION_M3900},
10249 #define OPTION_NO_M3900 (OPTION_MD_BASE + 31)
10250 {"no-m3900", no_argument, NULL, OPTION_NO_M3900},
10251 #define OPTION_GP64 (OPTION_MD_BASE + 32)
10252 {"mgp64", no_argument, NULL, OPTION_GP64},
10253 #define OPTION_MIPS3D (OPTION_MD_BASE + 33)
10254 {"mips3d", no_argument, NULL, OPTION_MIPS3D},
10255 #define OPTION_NO_MIPS3D (OPTION_MD_BASE + 34)
10256 {"no-mips3d", no_argument, NULL, OPTION_NO_MIPS3D},
10257 #define OPTION_MDMX (OPTION_MD_BASE + 35)
10258 {"mdmx", no_argument, NULL, OPTION_MDMX},
10259 #define OPTION_NO_MDMX (OPTION_MD_BASE + 36)
10260 {"no-mdmx", no_argument, NULL, OPTION_NO_MDMX},
10261 #define OPTION_FIX_VR4122 (OPTION_MD_BASE + 37)
10262 #define OPTION_NO_FIX_VR4122 (OPTION_MD_BASE + 38)
10263 {"mfix-vr4122-bugs", no_argument, NULL, OPTION_FIX_VR4122},
10264 {"no-mfix-vr4122-bugs", no_argument, NULL, OPTION_NO_FIX_VR4122},
10265 #define OPTION_RELAX_BRANCH (OPTION_MD_BASE + 39)
10266 #define OPTION_NO_RELAX_BRANCH (OPTION_MD_BASE + 40)
10267 {"relax-branch", no_argument, NULL, OPTION_RELAX_BRANCH},
10268 {"no-relax-branch", no_argument, NULL, OPTION_NO_RELAX_BRANCH},
10270 #define OPTION_ELF_BASE (OPTION_MD_BASE + 41)
10271 #define OPTION_CALL_SHARED (OPTION_ELF_BASE + 0)
10272 {"KPIC", no_argument, NULL, OPTION_CALL_SHARED},
10273 {"call_shared", no_argument, NULL, OPTION_CALL_SHARED},
10274 #define OPTION_NON_SHARED (OPTION_ELF_BASE + 1)
10275 {"non_shared", no_argument, NULL, OPTION_NON_SHARED},
10276 #define OPTION_XGOT (OPTION_ELF_BASE + 2)
10277 {"xgot", no_argument, NULL, OPTION_XGOT},
10278 #define OPTION_MABI (OPTION_ELF_BASE + 3)
10279 {"mabi", required_argument, NULL, OPTION_MABI},
10280 #define OPTION_32 (OPTION_ELF_BASE + 4)
10281 {"32", no_argument, NULL, OPTION_32},
10282 #define OPTION_N32 (OPTION_ELF_BASE + 5)
10283 {"n32", no_argument, NULL, OPTION_N32},
10284 #define OPTION_64 (OPTION_ELF_BASE + 6)
10285 {"64", no_argument, NULL, OPTION_64},
10286 #define OPTION_MDEBUG (OPTION_ELF_BASE + 7)
10287 {"mdebug", no_argument, NULL, OPTION_MDEBUG},
10288 #define OPTION_NO_MDEBUG (OPTION_ELF_BASE + 8)
10289 {"no-mdebug", no_argument, NULL, OPTION_NO_MDEBUG},
10290 #endif /* OBJ_ELF */
10291 {NULL, no_argument, NULL, 0}
10293 size_t md_longopts_size = sizeof (md_longopts);
10295 /* Set STRING_PTR (either &mips_arch_string or &mips_tune_string) to
10296 NEW_VALUE. Warn if another value was already specified. Note:
10297 we have to defer parsing the -march and -mtune arguments in order
10298 to handle 'from-abi' correctly, since the ABI might be specified
10299 in a later argument. */
10302 mips_set_option_string (string_ptr, new_value)
10303 const char **string_ptr, *new_value;
10305 if (*string_ptr != 0 && strcasecmp (*string_ptr, new_value) != 0)
10306 as_warn (_("A different %s was already specified, is now %s"),
10307 string_ptr == &mips_arch_string ? "-march" : "-mtune",
10310 *string_ptr = new_value;
10314 md_parse_option (c, arg)
10320 case OPTION_CONSTRUCT_FLOATS:
10321 mips_disable_float_construction = 0;
10324 case OPTION_NO_CONSTRUCT_FLOATS:
10325 mips_disable_float_construction = 1;
10337 target_big_endian = 1;
10341 target_big_endian = 0;
10349 if (arg && arg[1] == '0')
10359 mips_debug = atoi (arg);
10360 /* When the MIPS assembler sees -g or -g2, it does not do
10361 optimizations which limit full symbolic debugging. We take
10362 that to be equivalent to -O0. */
10363 if (mips_debug == 2)
10368 file_mips_isa = ISA_MIPS1;
10372 file_mips_isa = ISA_MIPS2;
10376 file_mips_isa = ISA_MIPS3;
10380 file_mips_isa = ISA_MIPS4;
10384 file_mips_isa = ISA_MIPS5;
10387 case OPTION_MIPS32:
10388 file_mips_isa = ISA_MIPS32;
10391 case OPTION_MIPS64:
10392 file_mips_isa = ISA_MIPS64;
10396 mips_set_option_string (&mips_tune_string, arg);
10400 mips_set_option_string (&mips_arch_string, arg);
10404 mips_set_option_string (&mips_arch_string, "4650");
10405 mips_set_option_string (&mips_tune_string, "4650");
10408 case OPTION_NO_M4650:
10412 mips_set_option_string (&mips_arch_string, "4010");
10413 mips_set_option_string (&mips_tune_string, "4010");
10416 case OPTION_NO_M4010:
10420 mips_set_option_string (&mips_arch_string, "4100");
10421 mips_set_option_string (&mips_tune_string, "4100");
10424 case OPTION_NO_M4100:
10428 mips_set_option_string (&mips_arch_string, "3900");
10429 mips_set_option_string (&mips_tune_string, "3900");
10432 case OPTION_NO_M3900:
10436 mips_opts.ase_mdmx = 1;
10439 case OPTION_NO_MDMX:
10440 mips_opts.ase_mdmx = 0;
10443 case OPTION_MIPS16:
10444 mips_opts.mips16 = 1;
10445 mips_no_prev_insn (false);
10448 case OPTION_NO_MIPS16:
10449 mips_opts.mips16 = 0;
10450 mips_no_prev_insn (false);
10453 case OPTION_MIPS3D:
10454 mips_opts.ase_mips3d = 1;
10457 case OPTION_NO_MIPS3D:
10458 mips_opts.ase_mips3d = 0;
10461 case OPTION_MEMBEDDED_PIC:
10462 mips_pic = EMBEDDED_PIC;
10463 if (USE_GLOBAL_POINTER_OPT && g_switch_seen)
10465 as_bad (_("-G may not be used with embedded PIC code"));
10468 g_switch_value = 0x7fffffff;
10471 case OPTION_FIX_VR4122:
10472 mips_fix_4122_bugs = 1;
10475 case OPTION_NO_FIX_VR4122:
10476 mips_fix_4122_bugs = 0;
10479 case OPTION_RELAX_BRANCH:
10480 mips_relax_branch = 1;
10483 case OPTION_NO_RELAX_BRANCH:
10484 mips_relax_branch = 0;
10488 /* When generating ELF code, we permit -KPIC and -call_shared to
10489 select SVR4_PIC, and -non_shared to select no PIC. This is
10490 intended to be compatible with Irix 5. */
10491 case OPTION_CALL_SHARED:
10492 if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
10494 as_bad (_("-call_shared is supported only for ELF format"));
10497 mips_pic = SVR4_PIC;
10498 if (g_switch_seen && g_switch_value != 0)
10500 as_bad (_("-G may not be used with SVR4 PIC code"));
10503 g_switch_value = 0;
10506 case OPTION_NON_SHARED:
10507 if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
10509 as_bad (_("-non_shared is supported only for ELF format"));
10515 /* The -xgot option tells the assembler to use 32 offsets when
10516 accessing the got in SVR4_PIC mode. It is for Irix
10521 #endif /* OBJ_ELF */
10524 if (! USE_GLOBAL_POINTER_OPT)
10526 as_bad (_("-G is not supported for this configuration"));
10529 else if (mips_pic == SVR4_PIC || mips_pic == EMBEDDED_PIC)
10531 as_bad (_("-G may not be used with SVR4 or embedded PIC code"));
10535 g_switch_value = atoi (arg);
10540 /* The -32, -n32 and -64 options are shortcuts for -mabi=32, -mabi=n32
10543 if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
10545 as_bad (_("-32 is supported for ELF format only"));
10548 mips_abi = O32_ABI;
10552 if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
10554 as_bad (_("-n32 is supported for ELF format only"));
10557 mips_abi = N32_ABI;
10561 if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
10563 as_bad (_("-64 is supported for ELF format only"));
10566 mips_abi = N64_ABI;
10567 if (! support_64bit_objects())
10568 as_fatal (_("No compiled in support for 64 bit object file format"));
10570 #endif /* OBJ_ELF */
10573 file_mips_gp32 = 1;
10577 file_mips_gp32 = 0;
10581 file_mips_fp32 = 1;
10585 file_mips_fp32 = 0;
10590 if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
10592 as_bad (_("-mabi is supported for ELF format only"));
10595 if (strcmp (arg, "32") == 0)
10596 mips_abi = O32_ABI;
10597 else if (strcmp (arg, "o64") == 0)
10598 mips_abi = O64_ABI;
10599 else if (strcmp (arg, "n32") == 0)
10600 mips_abi = N32_ABI;
10601 else if (strcmp (arg, "64") == 0)
10603 mips_abi = N64_ABI;
10604 if (! support_64bit_objects())
10605 as_fatal (_("No compiled in support for 64 bit object file "
10608 else if (strcmp (arg, "eabi") == 0)
10609 mips_abi = EABI_ABI;
10612 as_fatal (_("invalid abi -mabi=%s"), arg);
10616 #endif /* OBJ_ELF */
10618 case OPTION_M7000_HILO_FIX:
10619 mips_7000_hilo_fix = true;
10622 case OPTION_MNO_7000_HILO_FIX:
10623 mips_7000_hilo_fix = false;
10627 case OPTION_MDEBUG:
10628 mips_flag_mdebug = true;
10631 case OPTION_NO_MDEBUG:
10632 mips_flag_mdebug = false;
10634 #endif /* OBJ_ELF */
10643 /* Set up globals to generate code for the ISA or processor
10644 described by INFO. */
10647 mips_set_architecture (info)
10648 const struct mips_cpu_info *info;
10652 mips_arch_info = info;
10653 mips_arch = info->cpu;
10654 mips_opts.isa = info->isa;
10659 /* Likewise for tuning. */
10662 mips_set_tune (info)
10663 const struct mips_cpu_info *info;
10667 mips_tune_info = info;
10668 mips_tune = info->cpu;
10674 mips_after_parse_args ()
10676 /* GP relative stuff not working for PE */
10677 if (strncmp (TARGET_OS, "pe", 2) == 0
10678 && g_switch_value != 0)
10681 as_bad (_("-G not supported in this configuration."));
10682 g_switch_value = 0;
10685 /* The following code determines the architecture and register size.
10686 Similar code was added to GCC 3.3 (see override_options() in
10687 config/mips/mips.c). The GAS and GCC code should be kept in sync
10688 as much as possible. */
10690 if (mips_arch_string != 0)
10691 mips_set_architecture (mips_parse_cpu ("-march", mips_arch_string));
10693 if (mips_tune_string != 0)
10694 mips_set_tune (mips_parse_cpu ("-mtune", mips_tune_string));
10696 if (file_mips_isa != ISA_UNKNOWN)
10698 /* Handle -mipsN. At this point, file_mips_isa contains the
10699 ISA level specified by -mipsN, while mips_opts.isa contains
10700 the -march selection (if any). */
10701 if (mips_arch_info != 0)
10703 /* -march takes precedence over -mipsN, since it is more descriptive.
10704 There's no harm in specifying both as long as the ISA levels
10706 if (file_mips_isa != mips_opts.isa)
10707 as_bad (_("-%s conflicts with the other architecture options, which imply -%s"),
10708 mips_cpu_info_from_isa (file_mips_isa)->name,
10709 mips_cpu_info_from_isa (mips_opts.isa)->name);
10712 mips_set_architecture (mips_cpu_info_from_isa (file_mips_isa));
10715 if (mips_arch_info == 0)
10716 mips_set_architecture (mips_parse_cpu ("default CPU",
10717 MIPS_CPU_STRING_DEFAULT));
10719 if (ABI_NEEDS_64BIT_REGS (mips_abi) && !ISA_HAS_64BIT_REGS (mips_opts.isa))
10720 as_bad ("-march=%s is not compatible with the selected ABI",
10721 mips_arch_info->name);
10723 /* Optimize for mips_arch, unless -mtune selects a different processor. */
10724 if (mips_tune_info == 0)
10725 mips_set_tune (mips_arch_info);
10727 if (file_mips_gp32 >= 0)
10729 /* The user specified the size of the integer registers. Make sure
10730 it agrees with the ABI and ISA. */
10731 if (file_mips_gp32 == 0 && !ISA_HAS_64BIT_REGS (mips_opts.isa))
10732 as_bad (_("-mgp64 used with a 32-bit processor"));
10733 else if (file_mips_gp32 == 1 && ABI_NEEDS_64BIT_REGS (mips_abi))
10734 as_bad (_("-mgp32 used with a 64-bit ABI"));
10735 else if (file_mips_gp32 == 0 && ABI_NEEDS_32BIT_REGS (mips_abi))
10736 as_bad (_("-mgp64 used with a 32-bit ABI"));
10740 /* Infer the integer register size from the ABI and processor.
10741 Restrict ourselves to 32-bit registers if that's all the
10742 processor has, or if the ABI cannot handle 64-bit registers. */
10743 file_mips_gp32 = (ABI_NEEDS_32BIT_REGS (mips_abi)
10744 || !ISA_HAS_64BIT_REGS (mips_opts.isa));
10747 /* ??? GAS treats single-float processors as though they had 64-bit
10748 float registers (although it complains when double-precision
10749 instructions are used). As things stand, saying they have 32-bit
10750 registers would lead to spurious "register must be even" messages.
10751 So here we assume float registers are always the same size as
10752 integer ones, unless the user says otherwise. */
10753 if (file_mips_fp32 < 0)
10754 file_mips_fp32 = file_mips_gp32;
10756 /* End of GCC-shared inference code. */
10758 /* ??? When do we want this flag to be set? Who uses it? */
10759 if (file_mips_gp32 == 1
10760 && mips_abi == NO_ABI
10761 && ISA_HAS_64BIT_REGS (mips_opts.isa))
10762 mips_32bitmode = 1;
10764 if (mips_opts.isa == ISA_MIPS1 && mips_trap)
10765 as_bad (_("trap exception not supported at ISA 1"));
10767 /* If the selected architecture includes support for ASEs, enable
10768 generation of code for them. */
10769 if (mips_opts.mips16 == -1)
10770 mips_opts.mips16 = (CPU_HAS_MIPS16 (mips_arch)) ? 1 : 0;
10771 if (mips_opts.ase_mips3d == -1)
10772 mips_opts.ase_mips3d = (CPU_HAS_MIPS3D (mips_arch)) ? 1 : 0;
10773 if (mips_opts.ase_mdmx == -1)
10774 mips_opts.ase_mdmx = (CPU_HAS_MDMX (mips_arch)) ? 1 : 0;
10776 file_mips_isa = mips_opts.isa;
10777 file_ase_mips16 = mips_opts.mips16;
10778 file_ase_mips3d = mips_opts.ase_mips3d;
10779 file_ase_mdmx = mips_opts.ase_mdmx;
10780 mips_opts.gp32 = file_mips_gp32;
10781 mips_opts.fp32 = file_mips_fp32;
10783 if (mips_flag_mdebug < 0)
10785 #ifdef OBJ_MAYBE_ECOFF
10786 if (OUTPUT_FLAVOR == bfd_target_ecoff_flavour)
10787 mips_flag_mdebug = 1;
10789 #endif /* OBJ_MAYBE_ECOFF */
10790 mips_flag_mdebug = 0;
10795 mips_init_after_args ()
10797 /* initialize opcodes */
10798 bfd_mips_num_opcodes = bfd_mips_num_builtin_opcodes;
10799 mips_opcodes = (struct mips_opcode *) mips_builtin_opcodes;
10803 md_pcrel_from (fixP)
10806 if (OUTPUT_FLAVOR != bfd_target_aout_flavour
10807 && fixP->fx_addsy != (symbolS *) NULL
10808 && ! S_IS_DEFINED (fixP->fx_addsy))
10810 /* This makes a branch to an undefined symbol be a branch to the
10811 current location. */
10812 if (mips_pic == EMBEDDED_PIC)
10818 /* Return the address of the delay slot. */
10819 return fixP->fx_size + fixP->fx_where + fixP->fx_frag->fr_address;
10822 /* This is called before the symbol table is processed. In order to
10823 work with gcc when using mips-tfile, we must keep all local labels.
10824 However, in other cases, we want to discard them. If we were
10825 called with -g, but we didn't see any debugging information, it may
10826 mean that gcc is smuggling debugging information through to
10827 mips-tfile, in which case we must generate all local labels. */
10830 mips_frob_file_before_adjust ()
10832 #ifndef NO_ECOFF_DEBUGGING
10833 if (ECOFF_DEBUGGING
10835 && ! ecoff_debugging_seen)
10836 flag_keep_locals = 1;
10840 /* Sort any unmatched HI16_S relocs so that they immediately precede
10841 the corresponding LO reloc. This is called before md_apply_fix3 and
10842 tc_gen_reloc. Unmatched HI16_S relocs can only be generated by
10843 explicit use of the %hi modifier. */
10848 struct mips_hi_fixup *l;
10850 for (l = mips_hi_fixup_list; l != NULL; l = l->next)
10852 segment_info_type *seginfo;
10855 assert (l->fixp->fx_r_type == BFD_RELOC_HI16_S);
10857 /* Check quickly whether the next fixup happens to be a matching
10859 if (l->fixp->fx_next != NULL
10860 && l->fixp->fx_next->fx_r_type == BFD_RELOC_LO16
10861 && l->fixp->fx_addsy == l->fixp->fx_next->fx_addsy
10862 && l->fixp->fx_offset == l->fixp->fx_next->fx_offset)
10865 /* Look through the fixups for this segment for a matching %lo.
10866 When we find one, move the %hi just in front of it. We do
10867 this in two passes. In the first pass, we try to find a
10868 unique %lo. In the second pass, we permit multiple %hi
10869 relocs for a single %lo (this is a GNU extension). */
10870 seginfo = seg_info (l->seg);
10871 for (pass = 0; pass < 2; pass++)
10876 for (f = seginfo->fix_root; f != NULL; f = f->fx_next)
10878 /* Check whether this is a %lo fixup which matches l->fixp. */
10879 if (f->fx_r_type == BFD_RELOC_LO16
10880 && f->fx_addsy == l->fixp->fx_addsy
10881 && f->fx_offset == l->fixp->fx_offset
10884 || prev->fx_r_type != BFD_RELOC_HI16_S
10885 || prev->fx_addsy != f->fx_addsy
10886 || prev->fx_offset != f->fx_offset))
10890 /* Move l->fixp before f. */
10891 for (pf = &seginfo->fix_root;
10893 pf = &(*pf)->fx_next)
10894 assert (*pf != NULL);
10896 *pf = l->fixp->fx_next;
10898 l->fixp->fx_next = f;
10900 seginfo->fix_root = l->fixp;
10902 prev->fx_next = l->fixp;
10913 #if 0 /* GCC code motion plus incomplete dead code elimination
10914 can leave a %hi without a %lo. */
10916 as_warn_where (l->fixp->fx_file, l->fixp->fx_line,
10917 _("Unmatched %%hi reloc"));
10923 /* When generating embedded PIC code we need to use a special
10924 relocation to represent the difference of two symbols in the .text
10925 section (switch tables use a difference of this sort). See
10926 include/coff/mips.h for details. This macro checks whether this
10927 fixup requires the special reloc. */
10928 #define SWITCH_TABLE(fixp) \
10929 ((fixp)->fx_r_type == BFD_RELOC_32 \
10930 && OUTPUT_FLAVOR != bfd_target_elf_flavour \
10931 && (fixp)->fx_addsy != NULL \
10932 && (fixp)->fx_subsy != NULL \
10933 && S_GET_SEGMENT ((fixp)->fx_addsy) == text_section \
10934 && S_GET_SEGMENT ((fixp)->fx_subsy) == text_section)
10936 /* When generating embedded PIC code we must keep all PC relative
10937 relocations, in case the linker has to relax a call. We also need
10938 to keep relocations for switch table entries.
10940 We may have combined relocations without symbols in the N32/N64 ABI.
10941 We have to prevent gas from dropping them. */
10944 mips_force_relocation (fixp)
10947 if (fixp->fx_r_type == BFD_RELOC_VTABLE_INHERIT
10948 || fixp->fx_r_type == BFD_RELOC_VTABLE_ENTRY
10949 || S_FORCE_RELOC (fixp->fx_addsy))
10953 && S_GET_SEGMENT (fixp->fx_addsy) == bfd_abs_section_ptr
10954 && (fixp->fx_r_type == BFD_RELOC_MIPS_SUB
10955 || fixp->fx_r_type == BFD_RELOC_HI16_S
10956 || fixp->fx_r_type == BFD_RELOC_LO16))
10959 return (mips_pic == EMBEDDED_PIC
10961 || SWITCH_TABLE (fixp)
10962 || fixp->fx_r_type == BFD_RELOC_PCREL_HI16_S
10963 || fixp->fx_r_type == BFD_RELOC_PCREL_LO16));
10968 mips_need_elf_addend_fixup (fixP)
10971 if (S_GET_OTHER (fixP->fx_addsy) == STO_MIPS16)
10973 if (mips_pic == EMBEDDED_PIC
10974 && S_IS_WEAK (fixP->fx_addsy))
10976 if (mips_pic != EMBEDDED_PIC
10977 && (S_IS_WEAK (fixP->fx_addsy)
10978 || S_IS_EXTERNAL (fixP->fx_addsy))
10979 && !S_IS_COMMON (fixP->fx_addsy))
10981 if (symbol_used_in_reloc_p (fixP->fx_addsy)
10982 && (((bfd_get_section_flags (stdoutput,
10983 S_GET_SEGMENT (fixP->fx_addsy))
10984 & (SEC_LINK_ONCE | SEC_MERGE)) != 0)
10985 || !strncmp (segment_name (S_GET_SEGMENT (fixP->fx_addsy)),
10987 sizeof (".gnu.linkonce") - 1)))
10993 /* Apply a fixup to the object file. */
10996 md_apply_fix3 (fixP, valP, seg)
10999 segT seg ATTRIBUTE_UNUSED;
11004 static int previous_fx_r_type = 0;
11006 /* FIXME: Maybe just return for all reloc types not listed below?
11007 Eric Christopher says: "This is stupid, please rewrite md_apply_fix3. */
11008 if (fixP->fx_r_type == BFD_RELOC_8)
11011 assert (fixP->fx_size == 4
11012 || fixP->fx_r_type == BFD_RELOC_16
11013 || fixP->fx_r_type == BFD_RELOC_32
11014 || fixP->fx_r_type == BFD_RELOC_MIPS_JMP
11015 || fixP->fx_r_type == BFD_RELOC_HI16_S
11016 || fixP->fx_r_type == BFD_RELOC_LO16
11017 || fixP->fx_r_type == BFD_RELOC_GPREL16
11018 || fixP->fx_r_type == BFD_RELOC_MIPS_LITERAL
11019 || fixP->fx_r_type == BFD_RELOC_GPREL32
11020 || fixP->fx_r_type == BFD_RELOC_64
11021 || fixP->fx_r_type == BFD_RELOC_CTOR
11022 || fixP->fx_r_type == BFD_RELOC_MIPS_SUB
11023 || fixP->fx_r_type == BFD_RELOC_MIPS_HIGHEST
11024 || fixP->fx_r_type == BFD_RELOC_MIPS_HIGHER
11025 || fixP->fx_r_type == BFD_RELOC_MIPS_SCN_DISP
11026 || fixP->fx_r_type == BFD_RELOC_MIPS_REL16
11027 || fixP->fx_r_type == BFD_RELOC_MIPS_RELGOT
11028 || fixP->fx_r_type == BFD_RELOC_VTABLE_INHERIT
11029 || fixP->fx_r_type == BFD_RELOC_VTABLE_ENTRY
11030 || fixP->fx_r_type == BFD_RELOC_MIPS_JALR);
11034 /* If we aren't adjusting this fixup to be against the section
11035 symbol, we need to adjust the value. */
11037 if (fixP->fx_addsy != NULL && OUTPUT_FLAVOR == bfd_target_elf_flavour)
11039 if (mips_need_elf_addend_fixup (fixP))
11041 reloc_howto_type *howto;
11042 valueT symval = S_GET_VALUE (fixP->fx_addsy);
11046 howto = bfd_reloc_type_lookup (stdoutput, fixP->fx_r_type);
11047 if (value != 0 && howto->partial_inplace
11048 && (! fixP->fx_pcrel || howto->pcrel_offset))
11050 /* In this case, the bfd_install_relocation routine will
11051 incorrectly add the symbol value back in. We just want
11052 the addend to appear in the object file.
11054 howto->pcrel_offset is added for R_MIPS_PC16, which is
11055 generated for code like
11066 /* Make sure the addend is still non-zero. If it became zero
11067 after the last operation, set it to a spurious value and
11068 subtract the same value from the object file's contents. */
11073 /* The in-place addends for LO16 relocations are signed;
11074 leave the matching HI16 in-place addends as zero. */
11075 if (fixP->fx_r_type != BFD_RELOC_HI16_S)
11077 bfd_vma contents, mask, field;
11079 contents = bfd_get_bits (fixP->fx_frag->fr_literal
11082 target_big_endian);
11084 /* MASK has bits set where the relocation should go.
11085 FIELD is -value, shifted into the appropriate place
11086 for this relocation. */
11087 mask = 1 << (howto->bitsize - 1);
11088 mask = (((mask - 1) << 1) | 1) << howto->bitpos;
11089 field = (-value >> howto->rightshift) << howto->bitpos;
11091 bfd_put_bits ((field & mask) | (contents & ~mask),
11092 fixP->fx_frag->fr_literal + fixP->fx_where,
11094 target_big_endian);
11100 /* This code was generated using trial and error and so is
11101 fragile and not trustworthy. If you change it, you should
11102 rerun the elf-rel, elf-rel2, and empic testcases and ensure
11103 they still pass. */
11104 if (fixP->fx_pcrel || fixP->fx_subsy != NULL)
11106 value += fixP->fx_frag->fr_address + fixP->fx_where;
11108 /* BFD's REL handling, for MIPS, is _very_ weird.
11109 This gives the right results, but it can't possibly
11110 be the way things are supposed to work. */
11111 if ((fixP->fx_r_type != BFD_RELOC_16_PCREL
11112 && fixP->fx_r_type != BFD_RELOC_16_PCREL_S2)
11113 || S_GET_SEGMENT (fixP->fx_addsy) != undefined_section)
11114 value += fixP->fx_frag->fr_address + fixP->fx_where;
11119 fixP->fx_addnumber = value; /* Remember value for tc_gen_reloc. */
11121 /* We are not done if this is a composite relocation to set up gp. */
11122 if (fixP->fx_addsy == NULL && ! fixP->fx_pcrel
11123 && !(fixP->fx_r_type == BFD_RELOC_MIPS_SUB
11124 || (fixP->fx_r_type == BFD_RELOC_64
11125 && (previous_fx_r_type == BFD_RELOC_GPREL32
11126 || previous_fx_r_type == BFD_RELOC_GPREL16))
11127 || (previous_fx_r_type == BFD_RELOC_MIPS_SUB
11128 && (fixP->fx_r_type == BFD_RELOC_HI16_S
11129 || fixP->fx_r_type == BFD_RELOC_LO16))))
11131 previous_fx_r_type = fixP->fx_r_type;
11133 switch (fixP->fx_r_type)
11135 case BFD_RELOC_MIPS_JMP:
11136 case BFD_RELOC_MIPS_SHIFT5:
11137 case BFD_RELOC_MIPS_SHIFT6:
11138 case BFD_RELOC_MIPS_GOT_DISP:
11139 case BFD_RELOC_MIPS_GOT_PAGE:
11140 case BFD_RELOC_MIPS_GOT_OFST:
11141 case BFD_RELOC_MIPS_SUB:
11142 case BFD_RELOC_MIPS_INSERT_A:
11143 case BFD_RELOC_MIPS_INSERT_B:
11144 case BFD_RELOC_MIPS_DELETE:
11145 case BFD_RELOC_MIPS_HIGHEST:
11146 case BFD_RELOC_MIPS_HIGHER:
11147 case BFD_RELOC_MIPS_SCN_DISP:
11148 case BFD_RELOC_MIPS_REL16:
11149 case BFD_RELOC_MIPS_RELGOT:
11150 case BFD_RELOC_MIPS_JALR:
11151 case BFD_RELOC_HI16:
11152 case BFD_RELOC_HI16_S:
11153 case BFD_RELOC_GPREL16:
11154 case BFD_RELOC_MIPS_LITERAL:
11155 case BFD_RELOC_MIPS_CALL16:
11156 case BFD_RELOC_MIPS_GOT16:
11157 case BFD_RELOC_GPREL32:
11158 case BFD_RELOC_MIPS_GOT_HI16:
11159 case BFD_RELOC_MIPS_GOT_LO16:
11160 case BFD_RELOC_MIPS_CALL_HI16:
11161 case BFD_RELOC_MIPS_CALL_LO16:
11162 case BFD_RELOC_MIPS16_GPREL:
11163 if (fixP->fx_pcrel)
11164 as_bad_where (fixP->fx_file, fixP->fx_line,
11165 _("Invalid PC relative reloc"));
11166 /* Nothing needed to do. The value comes from the reloc entry */
11169 case BFD_RELOC_MIPS16_JMP:
11170 /* We currently always generate a reloc against a symbol, which
11171 means that we don't want an addend even if the symbol is
11173 fixP->fx_addnumber = 0;
11176 case BFD_RELOC_PCREL_HI16_S:
11177 /* The addend for this is tricky if it is internal, so we just
11178 do everything here rather than in bfd_install_relocation. */
11179 if (OUTPUT_FLAVOR == bfd_target_elf_flavour
11184 && (symbol_get_bfdsym (fixP->fx_addsy)->flags & BSF_SECTION_SYM) == 0)
11186 /* For an external symbol adjust by the address to make it
11187 pcrel_offset. We use the address of the RELLO reloc
11188 which follows this one. */
11189 value += (fixP->fx_next->fx_frag->fr_address
11190 + fixP->fx_next->fx_where);
11192 value = ((value + 0x8000) >> 16) & 0xffff;
11193 buf = (bfd_byte *) fixP->fx_frag->fr_literal + fixP->fx_where;
11194 if (target_big_endian)
11196 md_number_to_chars ((char *) buf, value, 2);
11199 case BFD_RELOC_PCREL_LO16:
11200 /* The addend for this is tricky if it is internal, so we just
11201 do everything here rather than in bfd_install_relocation. */
11202 if (OUTPUT_FLAVOR == bfd_target_elf_flavour
11207 && (symbol_get_bfdsym (fixP->fx_addsy)->flags & BSF_SECTION_SYM) == 0)
11208 value += fixP->fx_frag->fr_address + fixP->fx_where;
11209 buf = (bfd_byte *) fixP->fx_frag->fr_literal + fixP->fx_where;
11210 if (target_big_endian)
11212 md_number_to_chars ((char *) buf, value, 2);
11216 /* This is handled like BFD_RELOC_32, but we output a sign
11217 extended value if we are only 32 bits. */
11219 || (mips_pic == EMBEDDED_PIC && SWITCH_TABLE (fixP)))
11221 if (8 <= sizeof (valueT))
11222 md_number_to_chars (fixP->fx_frag->fr_literal + fixP->fx_where,
11229 w1 = w2 = fixP->fx_where;
11230 if (target_big_endian)
11234 md_number_to_chars (fixP->fx_frag->fr_literal + w1, value, 4);
11235 if ((value & 0x80000000) != 0)
11239 md_number_to_chars (fixP->fx_frag->fr_literal + w2, hiv, 4);
11244 case BFD_RELOC_RVA:
11246 /* If we are deleting this reloc entry, we must fill in the
11247 value now. This can happen if we have a .word which is not
11248 resolved when it appears but is later defined. We also need
11249 to fill in the value if this is an embedded PIC switch table
11252 || (mips_pic == EMBEDDED_PIC && SWITCH_TABLE (fixP)))
11253 md_number_to_chars (fixP->fx_frag->fr_literal + fixP->fx_where,
11258 /* If we are deleting this reloc entry, we must fill in the
11260 assert (fixP->fx_size == 2);
11262 md_number_to_chars (fixP->fx_frag->fr_literal + fixP->fx_where,
11266 case BFD_RELOC_LO16:
11267 /* When handling an embedded PIC switch statement, we can wind
11268 up deleting a LO16 reloc. See the 'o' case in mips_ip. */
11271 if (value + 0x8000 > 0xffff)
11272 as_bad_where (fixP->fx_file, fixP->fx_line,
11273 _("relocation overflow"));
11274 buf = (bfd_byte *) fixP->fx_frag->fr_literal + fixP->fx_where;
11275 if (target_big_endian)
11277 md_number_to_chars ((char *) buf, value, 2);
11281 case BFD_RELOC_16_PCREL_S2:
11282 if ((value & 0x3) != 0)
11283 as_bad_where (fixP->fx_file, fixP->fx_line,
11284 _("Branch to odd address (%lx)"), (long) value);
11286 /* Fall through. */
11288 case BFD_RELOC_16_PCREL:
11290 * We need to save the bits in the instruction since fixup_segment()
11291 * might be deleting the relocation entry (i.e., a branch within
11292 * the current segment).
11294 if (!fixP->fx_done && value != 0)
11296 /* If 'value' is zero, the remaining reloc code won't actually
11297 do the store, so it must be done here. This is probably
11298 a bug somewhere. */
11300 && (fixP->fx_r_type != BFD_RELOC_16_PCREL_S2
11301 || fixP->fx_addsy == NULL /* ??? */
11302 || ! S_IS_DEFINED (fixP->fx_addsy)))
11303 value -= fixP->fx_frag->fr_address + fixP->fx_where;
11305 value = (offsetT) value >> 2;
11307 /* update old instruction data */
11308 buf = (bfd_byte *) (fixP->fx_where + fixP->fx_frag->fr_literal);
11309 if (target_big_endian)
11310 insn = (buf[0] << 24) | (buf[1] << 16) | (buf[2] << 8) | buf[3];
11312 insn = (buf[3] << 24) | (buf[2] << 16) | (buf[1] << 8) | buf[0];
11314 if (value + 0x8000 <= 0xffff)
11315 insn |= value & 0xffff;
11318 /* The branch offset is too large. If this is an
11319 unconditional branch, and we are not generating PIC code,
11320 we can convert it to an absolute jump instruction. */
11321 if (mips_pic == NO_PIC
11323 && fixP->fx_frag->fr_address >= text_section->vma
11324 && (fixP->fx_frag->fr_address
11325 < text_section->vma + text_section->_raw_size)
11326 && ((insn & 0xffff0000) == 0x10000000 /* beq $0,$0 */
11327 || (insn & 0xffff0000) == 0x04010000 /* bgez $0 */
11328 || (insn & 0xffff0000) == 0x04110000)) /* bgezal $0 */
11330 if ((insn & 0xffff0000) == 0x04110000) /* bgezal $0 */
11331 insn = 0x0c000000; /* jal */
11333 insn = 0x08000000; /* j */
11334 fixP->fx_r_type = BFD_RELOC_MIPS_JMP;
11336 fixP->fx_addsy = section_symbol (text_section);
11337 fixP->fx_addnumber = (value << 2) + md_pcrel_from (fixP);
11341 /* If we got here, we have branch-relaxation disabled,
11342 and there's nothing we can do to fix this instruction
11343 without turning it into a longer sequence. */
11344 as_bad_where (fixP->fx_file, fixP->fx_line,
11345 _("Branch out of range"));
11349 md_number_to_chars ((char *) buf, (valueT) insn, 4);
11352 case BFD_RELOC_VTABLE_INHERIT:
11355 && !S_IS_DEFINED (fixP->fx_addsy)
11356 && !S_IS_WEAK (fixP->fx_addsy))
11357 S_SET_WEAK (fixP->fx_addsy);
11360 case BFD_RELOC_VTABLE_ENTRY:
11374 const struct mips_opcode *p;
11375 int treg, sreg, dreg, shamt;
11380 for (i = 0; i < NUMOPCODES; ++i)
11382 p = &mips_opcodes[i];
11383 if (((oc & p->mask) == p->match) && (p->pinfo != INSN_MACRO))
11385 printf ("%08lx %s\t", oc, p->name);
11386 treg = (oc >> 16) & 0x1f;
11387 sreg = (oc >> 21) & 0x1f;
11388 dreg = (oc >> 11) & 0x1f;
11389 shamt = (oc >> 6) & 0x1f;
11391 for (args = p->args;; ++args)
11402 printf ("%c", *args);
11406 assert (treg == sreg);
11407 printf ("$%d,$%d", treg, sreg);
11412 printf ("$%d", dreg);
11417 printf ("$%d", treg);
11421 printf ("0x%x", treg);
11426 printf ("$%d", sreg);
11430 printf ("0x%08lx", oc & 0x1ffffff);
11437 printf ("%d", imm);
11442 printf ("$%d", shamt);
11453 printf (_("%08lx UNDEFINED\n"), oc);
11464 name = input_line_pointer;
11465 c = get_symbol_end ();
11466 p = (symbolS *) symbol_find_or_make (name);
11467 *input_line_pointer = c;
11471 /* Align the current frag to a given power of two. The MIPS assembler
11472 also automatically adjusts any preceding label. */
11475 mips_align (to, fill, label)
11480 mips_emit_delays (false);
11481 frag_align (to, fill, 0);
11482 record_alignment (now_seg, to);
11485 assert (S_GET_SEGMENT (label) == now_seg);
11486 symbol_set_frag (label, frag_now);
11487 S_SET_VALUE (label, (valueT) frag_now_fix ());
11491 /* Align to a given power of two. .align 0 turns off the automatic
11492 alignment used by the data creating pseudo-ops. */
11496 int x ATTRIBUTE_UNUSED;
11499 register long temp_fill;
11500 long max_alignment = 15;
11504 o Note that the assembler pulls down any immediately preceeding label
11505 to the aligned address.
11506 o It's not documented but auto alignment is reinstated by
11507 a .align pseudo instruction.
11508 o Note also that after auto alignment is turned off the mips assembler
11509 issues an error on attempt to assemble an improperly aligned data item.
11514 temp = get_absolute_expression ();
11515 if (temp > max_alignment)
11516 as_bad (_("Alignment too large: %d. assumed."), temp = max_alignment);
11519 as_warn (_("Alignment negative: 0 assumed."));
11522 if (*input_line_pointer == ',')
11524 ++input_line_pointer;
11525 temp_fill = get_absolute_expression ();
11532 mips_align (temp, (int) temp_fill,
11533 insn_labels != NULL ? insn_labels->label : NULL);
11540 demand_empty_rest_of_line ();
11544 mips_flush_pending_output ()
11546 mips_emit_delays (false);
11547 mips_clear_insn_labels ();
11556 /* When generating embedded PIC code, we only use the .text, .lit8,
11557 .sdata and .sbss sections. We change the .data and .rdata
11558 pseudo-ops to use .sdata. */
11559 if (mips_pic == EMBEDDED_PIC
11560 && (sec == 'd' || sec == 'r'))
11564 /* The ELF backend needs to know that we are changing sections, so
11565 that .previous works correctly. We could do something like check
11566 for an obj_section_change_hook macro, but that might be confusing
11567 as it would not be appropriate to use it in the section changing
11568 functions in read.c, since obj-elf.c intercepts those. FIXME:
11569 This should be cleaner, somehow. */
11570 obj_elf_section_change_hook ();
11573 mips_emit_delays (false);
11583 subseg_set (bss_section, (subsegT) get_absolute_expression ());
11584 demand_empty_rest_of_line ();
11588 if (USE_GLOBAL_POINTER_OPT)
11590 seg = subseg_new (RDATA_SECTION_NAME,
11591 (subsegT) get_absolute_expression ());
11592 if (OUTPUT_FLAVOR == bfd_target_elf_flavour)
11594 bfd_set_section_flags (stdoutput, seg,
11600 if (strcmp (TARGET_OS, "elf") != 0)
11601 record_alignment (seg, 4);
11603 demand_empty_rest_of_line ();
11607 as_bad (_("No read only data section in this object file format"));
11608 demand_empty_rest_of_line ();
11614 if (USE_GLOBAL_POINTER_OPT)
11616 seg = subseg_new (".sdata", (subsegT) get_absolute_expression ());
11617 if (OUTPUT_FLAVOR == bfd_target_elf_flavour)
11619 bfd_set_section_flags (stdoutput, seg,
11620 SEC_ALLOC | SEC_LOAD | SEC_RELOC
11622 if (strcmp (TARGET_OS, "elf") != 0)
11623 record_alignment (seg, 4);
11625 demand_empty_rest_of_line ();
11630 as_bad (_("Global pointers not supported; recompile -G 0"));
11631 demand_empty_rest_of_line ();
11640 s_change_section (ignore)
11641 int ignore ATTRIBUTE_UNUSED;
11644 char *section_name;
11649 int section_entry_size;
11650 int section_alignment;
11652 if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
11655 section_name = input_line_pointer;
11656 c = get_symbol_end ();
11657 next_c = *(input_line_pointer + 1);
11659 /* Do we have .section Name<,"flags">? */
11660 if (c != ',' || (c == ',' && next_c == '"'))
11662 /* just after name is now '\0'. */
11663 *input_line_pointer = c;
11664 input_line_pointer = section_name;
11665 obj_elf_section (ignore);
11668 input_line_pointer++;
11670 /* Do we have .section Name<,type><,flag><,entry_size><,alignment> */
11672 section_type = get_absolute_expression ();
11675 if (*input_line_pointer++ == ',')
11676 section_flag = get_absolute_expression ();
11679 if (*input_line_pointer++ == ',')
11680 section_entry_size = get_absolute_expression ();
11682 section_entry_size = 0;
11683 if (*input_line_pointer++ == ',')
11684 section_alignment = get_absolute_expression ();
11686 section_alignment = 0;
11688 obj_elf_change_section (section_name, section_type, section_flag,
11689 section_entry_size, 0, 0, 0);
11690 #endif /* OBJ_ELF */
11694 mips_enable_auto_align ()
11705 label = insn_labels != NULL ? insn_labels->label : NULL;
11706 mips_emit_delays (false);
11707 if (log_size > 0 && auto_align)
11708 mips_align (log_size, 0, label);
11709 mips_clear_insn_labels ();
11710 cons (1 << log_size);
11714 s_float_cons (type)
11719 label = insn_labels != NULL ? insn_labels->label : NULL;
11721 mips_emit_delays (false);
11726 mips_align (3, 0, label);
11728 mips_align (2, 0, label);
11731 mips_clear_insn_labels ();
11736 /* Handle .globl. We need to override it because on Irix 5 you are
11739 where foo is an undefined symbol, to mean that foo should be
11740 considered to be the address of a function. */
11744 int x ATTRIBUTE_UNUSED;
11751 name = input_line_pointer;
11752 c = get_symbol_end ();
11753 symbolP = symbol_find_or_make (name);
11754 *input_line_pointer = c;
11755 SKIP_WHITESPACE ();
11757 /* On Irix 5, every global symbol that is not explicitly labelled as
11758 being a function is apparently labelled as being an object. */
11761 if (! is_end_of_line[(unsigned char) *input_line_pointer])
11766 secname = input_line_pointer;
11767 c = get_symbol_end ();
11768 sec = bfd_get_section_by_name (stdoutput, secname);
11770 as_bad (_("%s: no such section"), secname);
11771 *input_line_pointer = c;
11773 if (sec != NULL && (sec->flags & SEC_CODE) != 0)
11774 flag = BSF_FUNCTION;
11777 symbol_get_bfdsym (symbolP)->flags |= flag;
11779 S_SET_EXTERNAL (symbolP);
11780 demand_empty_rest_of_line ();
11785 int x ATTRIBUTE_UNUSED;
11790 opt = input_line_pointer;
11791 c = get_symbol_end ();
11795 /* FIXME: What does this mean? */
11797 else if (strncmp (opt, "pic", 3) == 0)
11801 i = atoi (opt + 3);
11805 mips_pic = SVR4_PIC;
11807 as_bad (_(".option pic%d not supported"), i);
11809 if (USE_GLOBAL_POINTER_OPT && mips_pic == SVR4_PIC)
11811 if (g_switch_seen && g_switch_value != 0)
11812 as_warn (_("-G may not be used with SVR4 PIC code"));
11813 g_switch_value = 0;
11814 bfd_set_gp_size (stdoutput, 0);
11818 as_warn (_("Unrecognized option \"%s\""), opt);
11820 *input_line_pointer = c;
11821 demand_empty_rest_of_line ();
11824 /* This structure is used to hold a stack of .set values. */
11826 struct mips_option_stack
11828 struct mips_option_stack *next;
11829 struct mips_set_options options;
11832 static struct mips_option_stack *mips_opts_stack;
11834 /* Handle the .set pseudo-op. */
11838 int x ATTRIBUTE_UNUSED;
11840 char *name = input_line_pointer, ch;
11842 while (!is_end_of_line[(unsigned char) *input_line_pointer])
11843 ++input_line_pointer;
11844 ch = *input_line_pointer;
11845 *input_line_pointer = '\0';
11847 if (strcmp (name, "reorder") == 0)
11849 if (mips_opts.noreorder && prev_nop_frag != NULL)
11851 /* If we still have pending nops, we can discard them. The
11852 usual nop handling will insert any that are still
11854 prev_nop_frag->fr_fix -= (prev_nop_frag_holds
11855 * (mips_opts.mips16 ? 2 : 4));
11856 prev_nop_frag = NULL;
11858 mips_opts.noreorder = 0;
11860 else if (strcmp (name, "noreorder") == 0)
11862 mips_emit_delays (true);
11863 mips_opts.noreorder = 1;
11864 mips_any_noreorder = 1;
11866 else if (strcmp (name, "at") == 0)
11868 mips_opts.noat = 0;
11870 else if (strcmp (name, "noat") == 0)
11872 mips_opts.noat = 1;
11874 else if (strcmp (name, "macro") == 0)
11876 mips_opts.warn_about_macros = 0;
11878 else if (strcmp (name, "nomacro") == 0)
11880 if (mips_opts.noreorder == 0)
11881 as_bad (_("`noreorder' must be set before `nomacro'"));
11882 mips_opts.warn_about_macros = 1;
11884 else if (strcmp (name, "move") == 0 || strcmp (name, "novolatile") == 0)
11886 mips_opts.nomove = 0;
11888 else if (strcmp (name, "nomove") == 0 || strcmp (name, "volatile") == 0)
11890 mips_opts.nomove = 1;
11892 else if (strcmp (name, "bopt") == 0)
11894 mips_opts.nobopt = 0;
11896 else if (strcmp (name, "nobopt") == 0)
11898 mips_opts.nobopt = 1;
11900 else if (strcmp (name, "mips16") == 0
11901 || strcmp (name, "MIPS-16") == 0)
11902 mips_opts.mips16 = 1;
11903 else if (strcmp (name, "nomips16") == 0
11904 || strcmp (name, "noMIPS-16") == 0)
11905 mips_opts.mips16 = 0;
11906 else if (strcmp (name, "mips3d") == 0)
11907 mips_opts.ase_mips3d = 1;
11908 else if (strcmp (name, "nomips3d") == 0)
11909 mips_opts.ase_mips3d = 0;
11910 else if (strcmp (name, "mdmx") == 0)
11911 mips_opts.ase_mdmx = 1;
11912 else if (strcmp (name, "nomdmx") == 0)
11913 mips_opts.ase_mdmx = 0;
11914 else if (strncmp (name, "mips", 4) == 0)
11918 /* Permit the user to change the ISA on the fly. Needless to
11919 say, misuse can cause serious problems. */
11920 isa = atoi (name + 4);
11924 mips_opts.gp32 = file_mips_gp32;
11925 mips_opts.fp32 = file_mips_fp32;
11930 mips_opts.gp32 = 1;
11931 mips_opts.fp32 = 1;
11937 mips_opts.gp32 = 0;
11938 mips_opts.fp32 = 0;
11941 as_bad (_("unknown ISA level %s"), name + 4);
11947 case 0: mips_opts.isa = file_mips_isa; break;
11948 case 1: mips_opts.isa = ISA_MIPS1; break;
11949 case 2: mips_opts.isa = ISA_MIPS2; break;
11950 case 3: mips_opts.isa = ISA_MIPS3; break;
11951 case 4: mips_opts.isa = ISA_MIPS4; break;
11952 case 5: mips_opts.isa = ISA_MIPS5; break;
11953 case 32: mips_opts.isa = ISA_MIPS32; break;
11954 case 64: mips_opts.isa = ISA_MIPS64; break;
11955 default: as_bad (_("unknown ISA level %s"), name + 4); break;
11958 else if (strcmp (name, "autoextend") == 0)
11959 mips_opts.noautoextend = 0;
11960 else if (strcmp (name, "noautoextend") == 0)
11961 mips_opts.noautoextend = 1;
11962 else if (strcmp (name, "push") == 0)
11964 struct mips_option_stack *s;
11966 s = (struct mips_option_stack *) xmalloc (sizeof *s);
11967 s->next = mips_opts_stack;
11968 s->options = mips_opts;
11969 mips_opts_stack = s;
11971 else if (strcmp (name, "pop") == 0)
11973 struct mips_option_stack *s;
11975 s = mips_opts_stack;
11977 as_bad (_(".set pop with no .set push"));
11980 /* If we're changing the reorder mode we need to handle
11981 delay slots correctly. */
11982 if (s->options.noreorder && ! mips_opts.noreorder)
11983 mips_emit_delays (true);
11984 else if (! s->options.noreorder && mips_opts.noreorder)
11986 if (prev_nop_frag != NULL)
11988 prev_nop_frag->fr_fix -= (prev_nop_frag_holds
11989 * (mips_opts.mips16 ? 2 : 4));
11990 prev_nop_frag = NULL;
11994 mips_opts = s->options;
11995 mips_opts_stack = s->next;
12001 as_warn (_("Tried to set unrecognized symbol: %s\n"), name);
12003 *input_line_pointer = ch;
12004 demand_empty_rest_of_line ();
12007 /* Handle the .abicalls pseudo-op. I believe this is equivalent to
12008 .option pic2. It means to generate SVR4 PIC calls. */
12011 s_abicalls (ignore)
12012 int ignore ATTRIBUTE_UNUSED;
12014 mips_pic = SVR4_PIC;
12015 if (USE_GLOBAL_POINTER_OPT)
12017 if (g_switch_seen && g_switch_value != 0)
12018 as_warn (_("-G may not be used with SVR4 PIC code"));
12019 g_switch_value = 0;
12021 bfd_set_gp_size (stdoutput, 0);
12022 demand_empty_rest_of_line ();
12025 /* Handle the .cpload pseudo-op. This is used when generating SVR4
12026 PIC code. It sets the $gp register for the function based on the
12027 function address, which is in the register named in the argument.
12028 This uses a relocation against _gp_disp, which is handled specially
12029 by the linker. The result is:
12030 lui $gp,%hi(_gp_disp)
12031 addiu $gp,$gp,%lo(_gp_disp)
12032 addu $gp,$gp,.cpload argument
12033 The .cpload argument is normally $25 == $t9. */
12037 int ignore ATTRIBUTE_UNUSED;
12042 /* If we are not generating SVR4 PIC code, or if this is NewABI code,
12043 .cpload is ignored. */
12044 if (mips_pic != SVR4_PIC || HAVE_NEWABI)
12050 /* .cpload should be in a .set noreorder section. */
12051 if (mips_opts.noreorder == 0)
12052 as_warn (_(".cpload not in noreorder section"));
12054 ex.X_op = O_symbol;
12055 ex.X_add_symbol = symbol_find_or_make ("_gp_disp");
12056 ex.X_op_symbol = NULL;
12057 ex.X_add_number = 0;
12059 /* In ELF, this symbol is implicitly an STT_OBJECT symbol. */
12060 symbol_get_bfdsym (ex.X_add_symbol)->flags |= BSF_OBJECT;
12062 macro_build_lui (NULL, &icnt, &ex, mips_gp_register);
12063 macro_build ((char *) NULL, &icnt, &ex, "addiu", "t,r,j",
12064 mips_gp_register, mips_gp_register, (int) BFD_RELOC_LO16);
12066 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "addu", "d,v,t",
12067 mips_gp_register, mips_gp_register, tc_get_register (0));
12069 demand_empty_rest_of_line ();
12072 /* Handle the .cpsetup pseudo-op defined for NewABI PIC code. The syntax is:
12073 .cpsetup $reg1, offset|$reg2, label
12075 If offset is given, this results in:
12076 sd $gp, offset($sp)
12077 lui $gp, %hi(%neg(%gp_rel(label)))
12078 addiu $gp, $gp, %lo(%neg(%gp_rel(label)))
12079 daddu $gp, $gp, $reg1
12081 If $reg2 is given, this results in:
12082 daddu $reg2, $gp, $0
12083 lui $gp, %hi(%neg(%gp_rel(label)))
12084 addiu $gp, $gp, %lo(%neg(%gp_rel(label)))
12085 daddu $gp, $gp, $reg1
12086 $reg1 is normally $25 == $t9. */
12089 int ignore ATTRIBUTE_UNUSED;
12091 expressionS ex_off;
12092 expressionS ex_sym;
12097 /* If we are not generating SVR4 PIC code, .cpsetup is ignored.
12098 We also need NewABI support. */
12099 if (mips_pic != SVR4_PIC || ! HAVE_NEWABI)
12105 reg1 = tc_get_register (0);
12106 SKIP_WHITESPACE ();
12107 if (*input_line_pointer != ',')
12109 as_bad (_("missing argument separator ',' for .cpsetup"));
12113 ++input_line_pointer;
12114 SKIP_WHITESPACE ();
12115 if (*input_line_pointer == '$')
12117 mips_cpreturn_register = tc_get_register (0);
12118 mips_cpreturn_offset = -1;
12122 mips_cpreturn_offset = get_absolute_expression ();
12123 mips_cpreturn_register = -1;
12125 SKIP_WHITESPACE ();
12126 if (*input_line_pointer != ',')
12128 as_bad (_("missing argument separator ',' for .cpsetup"));
12132 ++input_line_pointer;
12133 SKIP_WHITESPACE ();
12134 expression (&ex_sym);
12136 if (mips_cpreturn_register == -1)
12138 ex_off.X_op = O_constant;
12139 ex_off.X_add_symbol = NULL;
12140 ex_off.X_op_symbol = NULL;
12141 ex_off.X_add_number = mips_cpreturn_offset;
12143 macro_build ((char *) NULL, &icnt, &ex_off, "sd", "t,o(b)",
12144 mips_gp_register, (int) BFD_RELOC_LO16, SP);
12147 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "daddu",
12148 "d,v,t", mips_cpreturn_register, mips_gp_register, 0);
12150 /* Ensure there's room for the next two instructions, so that `f'
12151 doesn't end up with an address in the wrong frag. */
12154 macro_build ((char *) NULL, &icnt, &ex_sym, "lui", "t,u", mips_gp_register,
12155 (int) BFD_RELOC_GPREL16);
12156 fix_new (frag_now, f - frag_now->fr_literal,
12157 0, NULL, 0, 0, BFD_RELOC_MIPS_SUB);
12158 fix_new (frag_now, f - frag_now->fr_literal,
12159 0, NULL, 0, 0, BFD_RELOC_HI16_S);
12162 macro_build ((char *) NULL, &icnt, &ex_sym, "addiu", "t,r,j",
12163 mips_gp_register, mips_gp_register, (int) BFD_RELOC_GPREL16);
12164 fix_new (frag_now, f - frag_now->fr_literal,
12165 0, NULL, 0, 0, BFD_RELOC_MIPS_SUB);
12166 fix_new (frag_now, f - frag_now->fr_literal,
12167 0, NULL, 0, 0, BFD_RELOC_LO16);
12169 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
12170 HAVE_64BIT_ADDRESSES ? "daddu" : "addu", "d,v,t",
12171 mips_gp_register, mips_gp_register, reg1);
12173 demand_empty_rest_of_line ();
12178 int ignore ATTRIBUTE_UNUSED;
12180 /* If we are not generating SVR4 PIC code, or if this is not NewABI code,
12181 .cplocal is ignored. */
12182 if (mips_pic != SVR4_PIC || ! HAVE_NEWABI)
12188 mips_gp_register = tc_get_register (0);
12189 demand_empty_rest_of_line ();
12192 /* Handle the .cprestore pseudo-op. This stores $gp into a given
12193 offset from $sp. The offset is remembered, and after making a PIC
12194 call $gp is restored from that location. */
12197 s_cprestore (ignore)
12198 int ignore ATTRIBUTE_UNUSED;
12203 /* If we are not generating SVR4 PIC code, or if this is NewABI code,
12204 .cprestore is ignored. */
12205 if (mips_pic != SVR4_PIC || HAVE_NEWABI)
12211 mips_cprestore_offset = get_absolute_expression ();
12212 mips_cprestore_valid = 1;
12214 ex.X_op = O_constant;
12215 ex.X_add_symbol = NULL;
12216 ex.X_op_symbol = NULL;
12217 ex.X_add_number = mips_cprestore_offset;
12219 macro_build_ldst_constoffset ((char *) NULL, &icnt, &ex,
12220 HAVE_32BIT_ADDRESSES ? "sw" : "sd",
12221 mips_gp_register, SP);
12223 demand_empty_rest_of_line ();
12226 /* Handle the .cpreturn pseudo-op defined for NewABI PIC code. If an offset
12227 was given in the preceeding .gpsetup, it results in:
12228 ld $gp, offset($sp)
12230 If a register $reg2 was given there, it results in:
12231 daddiu $gp, $gp, $reg2
12234 s_cpreturn (ignore)
12235 int ignore ATTRIBUTE_UNUSED;
12240 /* If we are not generating SVR4 PIC code, .cpreturn is ignored.
12241 We also need NewABI support. */
12242 if (mips_pic != SVR4_PIC || ! HAVE_NEWABI)
12248 if (mips_cpreturn_register == -1)
12250 ex.X_op = O_constant;
12251 ex.X_add_symbol = NULL;
12252 ex.X_op_symbol = NULL;
12253 ex.X_add_number = mips_cpreturn_offset;
12255 macro_build ((char *) NULL, &icnt, &ex, "ld", "t,o(b)",
12256 mips_gp_register, (int) BFD_RELOC_LO16, SP);
12259 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "daddu",
12260 "d,v,t", mips_gp_register, mips_cpreturn_register, 0);
12262 demand_empty_rest_of_line ();
12265 /* Handle the .gpvalue pseudo-op. This is used when generating NewABI PIC
12266 code. It sets the offset to use in gp_rel relocations. */
12270 int ignore ATTRIBUTE_UNUSED;
12272 /* If we are not generating SVR4 PIC code, .gpvalue is ignored.
12273 We also need NewABI support. */
12274 if (mips_pic != SVR4_PIC || ! HAVE_NEWABI)
12280 mips_gprel_offset = get_absolute_expression ();
12282 demand_empty_rest_of_line ();
12285 /* Handle the .gpword pseudo-op. This is used when generating PIC
12286 code. It generates a 32 bit GP relative reloc. */
12290 int ignore ATTRIBUTE_UNUSED;
12296 /* When not generating PIC code, this is treated as .word. */
12297 if (mips_pic != SVR4_PIC)
12303 label = insn_labels != NULL ? insn_labels->label : NULL;
12304 mips_emit_delays (true);
12306 mips_align (2, 0, label);
12307 mips_clear_insn_labels ();
12311 if (ex.X_op != O_symbol || ex.X_add_number != 0)
12313 as_bad (_("Unsupported use of .gpword"));
12314 ignore_rest_of_line ();
12318 md_number_to_chars (p, (valueT) 0, 4);
12319 fix_new_exp (frag_now, p - frag_now->fr_literal, 4, &ex, false,
12320 BFD_RELOC_GPREL32);
12322 demand_empty_rest_of_line ();
12327 int ignore ATTRIBUTE_UNUSED;
12333 /* When not generating PIC code, this is treated as .dword. */
12334 if (mips_pic != SVR4_PIC)
12340 label = insn_labels != NULL ? insn_labels->label : NULL;
12341 mips_emit_delays (true);
12343 mips_align (3, 0, label);
12344 mips_clear_insn_labels ();
12348 if (ex.X_op != O_symbol || ex.X_add_number != 0)
12350 as_bad (_("Unsupported use of .gpdword"));
12351 ignore_rest_of_line ();
12355 md_number_to_chars (p, (valueT) 0, 8);
12356 fix_new_exp (frag_now, p - frag_now->fr_literal, 8, &ex, false,
12357 BFD_RELOC_GPREL32);
12359 /* GPREL32 composed with 64 gives a 64-bit GP offset. */
12360 ex.X_op = O_absent;
12361 ex.X_add_symbol = 0;
12362 ex.X_add_number = 0;
12363 fix_new_exp (frag_now, p - frag_now->fr_literal, 8, &ex, false,
12366 demand_empty_rest_of_line ();
12369 /* Handle the .cpadd pseudo-op. This is used when dealing with switch
12370 tables in SVR4 PIC code. */
12374 int ignore ATTRIBUTE_UNUSED;
12379 /* This is ignored when not generating SVR4 PIC code. */
12380 if (mips_pic != SVR4_PIC)
12386 /* Add $gp to the register named as an argument. */
12387 reg = tc_get_register (0);
12388 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
12389 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
12390 "d,v,t", reg, reg, mips_gp_register);
12392 demand_empty_rest_of_line ();
12395 /* Handle the .insn pseudo-op. This marks instruction labels in
12396 mips16 mode. This permits the linker to handle them specially,
12397 such as generating jalx instructions when needed. We also make
12398 them odd for the duration of the assembly, in order to generate the
12399 right sort of code. We will make them even in the adjust_symtab
12400 routine, while leaving them marked. This is convenient for the
12401 debugger and the disassembler. The linker knows to make them odd
12406 int ignore ATTRIBUTE_UNUSED;
12408 mips16_mark_labels ();
12410 demand_empty_rest_of_line ();
12413 /* Handle a .stabn directive. We need these in order to mark a label
12414 as being a mips16 text label correctly. Sometimes the compiler
12415 will emit a label, followed by a .stabn, and then switch sections.
12416 If the label and .stabn are in mips16 mode, then the label is
12417 really a mips16 text label. */
12424 mips16_mark_labels ();
12429 /* Handle the .weakext pseudo-op as defined in Kane and Heinrich.
12433 s_mips_weakext (ignore)
12434 int ignore ATTRIBUTE_UNUSED;
12441 name = input_line_pointer;
12442 c = get_symbol_end ();
12443 symbolP = symbol_find_or_make (name);
12444 S_SET_WEAK (symbolP);
12445 *input_line_pointer = c;
12447 SKIP_WHITESPACE ();
12449 if (! is_end_of_line[(unsigned char) *input_line_pointer])
12451 if (S_IS_DEFINED (symbolP))
12453 as_bad ("ignoring attempt to redefine symbol %s",
12454 S_GET_NAME (symbolP));
12455 ignore_rest_of_line ();
12459 if (*input_line_pointer == ',')
12461 ++input_line_pointer;
12462 SKIP_WHITESPACE ();
12466 if (exp.X_op != O_symbol)
12468 as_bad ("bad .weakext directive");
12469 ignore_rest_of_line ();
12472 symbol_set_value_expression (symbolP, &exp);
12475 demand_empty_rest_of_line ();
12478 /* Parse a register string into a number. Called from the ECOFF code
12479 to parse .frame. The argument is non-zero if this is the frame
12480 register, so that we can record it in mips_frame_reg. */
12483 tc_get_register (frame)
12488 SKIP_WHITESPACE ();
12489 if (*input_line_pointer++ != '$')
12491 as_warn (_("expected `$'"));
12494 else if (ISDIGIT (*input_line_pointer))
12496 reg = get_absolute_expression ();
12497 if (reg < 0 || reg >= 32)
12499 as_warn (_("Bad register number"));
12505 if (strncmp (input_line_pointer, "ra", 2) == 0)
12508 input_line_pointer += 2;
12510 else if (strncmp (input_line_pointer, "fp", 2) == 0)
12513 input_line_pointer += 2;
12515 else if (strncmp (input_line_pointer, "sp", 2) == 0)
12518 input_line_pointer += 2;
12520 else if (strncmp (input_line_pointer, "gp", 2) == 0)
12523 input_line_pointer += 2;
12525 else if (strncmp (input_line_pointer, "at", 2) == 0)
12528 input_line_pointer += 2;
12530 else if (strncmp (input_line_pointer, "kt0", 3) == 0)
12533 input_line_pointer += 3;
12535 else if (strncmp (input_line_pointer, "kt1", 3) == 0)
12538 input_line_pointer += 3;
12540 else if (strncmp (input_line_pointer, "zero", 4) == 0)
12543 input_line_pointer += 4;
12547 as_warn (_("Unrecognized register name"));
12549 while (ISALNUM(*input_line_pointer))
12550 input_line_pointer++;
12555 mips_frame_reg = reg != 0 ? reg : SP;
12556 mips_frame_reg_valid = 1;
12557 mips_cprestore_valid = 0;
12563 md_section_align (seg, addr)
12567 int align = bfd_get_section_alignment (stdoutput, seg);
12570 /* We don't need to align ELF sections to the full alignment.
12571 However, Irix 5 may prefer that we align them at least to a 16
12572 byte boundary. We don't bother to align the sections if we are
12573 targeted for an embedded system. */
12574 if (strcmp (TARGET_OS, "elf") == 0)
12580 return ((addr + (1 << align) - 1) & (-1 << align));
12583 /* Utility routine, called from above as well. If called while the
12584 input file is still being read, it's only an approximation. (For
12585 example, a symbol may later become defined which appeared to be
12586 undefined earlier.) */
12589 nopic_need_relax (sym, before_relaxing)
12591 int before_relaxing;
12596 if (USE_GLOBAL_POINTER_OPT && g_switch_value > 0)
12598 const char *symname;
12601 /* Find out whether this symbol can be referenced off the $gp
12602 register. It can be if it is smaller than the -G size or if
12603 it is in the .sdata or .sbss section. Certain symbols can
12604 not be referenced off the $gp, although it appears as though
12606 symname = S_GET_NAME (sym);
12607 if (symname != (const char *) NULL
12608 && (strcmp (symname, "eprol") == 0
12609 || strcmp (symname, "etext") == 0
12610 || strcmp (symname, "_gp") == 0
12611 || strcmp (symname, "edata") == 0
12612 || strcmp (symname, "_fbss") == 0
12613 || strcmp (symname, "_fdata") == 0
12614 || strcmp (symname, "_ftext") == 0
12615 || strcmp (symname, "end") == 0
12616 || strcmp (symname, "_gp_disp") == 0))
12618 else if ((! S_IS_DEFINED (sym) || S_IS_COMMON (sym))
12620 #ifndef NO_ECOFF_DEBUGGING
12621 || (symbol_get_obj (sym)->ecoff_extern_size != 0
12622 && (symbol_get_obj (sym)->ecoff_extern_size
12623 <= g_switch_value))
12625 /* We must defer this decision until after the whole
12626 file has been read, since there might be a .extern
12627 after the first use of this symbol. */
12628 || (before_relaxing
12629 #ifndef NO_ECOFF_DEBUGGING
12630 && symbol_get_obj (sym)->ecoff_extern_size == 0
12632 && S_GET_VALUE (sym) == 0)
12633 || (S_GET_VALUE (sym) != 0
12634 && S_GET_VALUE (sym) <= g_switch_value)))
12638 const char *segname;
12640 segname = segment_name (S_GET_SEGMENT (sym));
12641 assert (strcmp (segname, ".lit8") != 0
12642 && strcmp (segname, ".lit4") != 0);
12643 change = (strcmp (segname, ".sdata") != 0
12644 && strcmp (segname, ".sbss") != 0
12645 && strncmp (segname, ".sdata.", 7) != 0
12646 && strncmp (segname, ".gnu.linkonce.s.", 16) != 0);
12651 /* We are not optimizing for the $gp register. */
12655 /* Given a mips16 variant frag FRAGP, return non-zero if it needs an
12656 extended opcode. SEC is the section the frag is in. */
12659 mips16_extended_frag (fragp, sec, stretch)
12665 register const struct mips16_immed_operand *op;
12667 int mintiny, maxtiny;
12671 if (RELAX_MIPS16_USER_SMALL (fragp->fr_subtype))
12673 if (RELAX_MIPS16_USER_EXT (fragp->fr_subtype))
12676 type = RELAX_MIPS16_TYPE (fragp->fr_subtype);
12677 op = mips16_immed_operands;
12678 while (op->type != type)
12681 assert (op < mips16_immed_operands + MIPS16_NUM_IMMED);
12686 if (type == '<' || type == '>' || type == '[' || type == ']')
12689 maxtiny = 1 << op->nbits;
12694 maxtiny = (1 << op->nbits) - 1;
12699 mintiny = - (1 << (op->nbits - 1));
12700 maxtiny = (1 << (op->nbits - 1)) - 1;
12703 sym_frag = symbol_get_frag (fragp->fr_symbol);
12704 val = S_GET_VALUE (fragp->fr_symbol);
12705 symsec = S_GET_SEGMENT (fragp->fr_symbol);
12711 /* We won't have the section when we are called from
12712 mips_relax_frag. However, we will always have been called
12713 from md_estimate_size_before_relax first. If this is a
12714 branch to a different section, we mark it as such. If SEC is
12715 NULL, and the frag is not marked, then it must be a branch to
12716 the same section. */
12719 if (RELAX_MIPS16_LONG_BRANCH (fragp->fr_subtype))
12724 /* Must have been called from md_estimate_size_before_relax. */
12727 fragp->fr_subtype =
12728 RELAX_MIPS16_MARK_LONG_BRANCH (fragp->fr_subtype);
12730 /* FIXME: We should support this, and let the linker
12731 catch branches and loads that are out of range. */
12732 as_bad_where (fragp->fr_file, fragp->fr_line,
12733 _("unsupported PC relative reference to different section"));
12737 if (fragp != sym_frag && sym_frag->fr_address == 0)
12738 /* Assume non-extended on the first relaxation pass.
12739 The address we have calculated will be bogus if this is
12740 a forward branch to another frag, as the forward frag
12741 will have fr_address == 0. */
12745 /* In this case, we know for sure that the symbol fragment is in
12746 the same section. If the relax_marker of the symbol fragment
12747 differs from the relax_marker of this fragment, we have not
12748 yet adjusted the symbol fragment fr_address. We want to add
12749 in STRETCH in order to get a better estimate of the address.
12750 This particularly matters because of the shift bits. */
12752 && sym_frag->relax_marker != fragp->relax_marker)
12756 /* Adjust stretch for any alignment frag. Note that if have
12757 been expanding the earlier code, the symbol may be
12758 defined in what appears to be an earlier frag. FIXME:
12759 This doesn't handle the fr_subtype field, which specifies
12760 a maximum number of bytes to skip when doing an
12762 for (f = fragp; f != NULL && f != sym_frag; f = f->fr_next)
12764 if (f->fr_type == rs_align || f->fr_type == rs_align_code)
12767 stretch = - ((- stretch)
12768 & ~ ((1 << (int) f->fr_offset) - 1));
12770 stretch &= ~ ((1 << (int) f->fr_offset) - 1);
12779 addr = fragp->fr_address + fragp->fr_fix;
12781 /* The base address rules are complicated. The base address of
12782 a branch is the following instruction. The base address of a
12783 PC relative load or add is the instruction itself, but if it
12784 is in a delay slot (in which case it can not be extended) use
12785 the address of the instruction whose delay slot it is in. */
12786 if (type == 'p' || type == 'q')
12790 /* If we are currently assuming that this frag should be
12791 extended, then, the current address is two bytes
12793 if (RELAX_MIPS16_EXTENDED (fragp->fr_subtype))
12796 /* Ignore the low bit in the target, since it will be set
12797 for a text label. */
12798 if ((val & 1) != 0)
12801 else if (RELAX_MIPS16_JAL_DSLOT (fragp->fr_subtype))
12803 else if (RELAX_MIPS16_DSLOT (fragp->fr_subtype))
12806 val -= addr & ~ ((1 << op->shift) - 1);
12808 /* Branch offsets have an implicit 0 in the lowest bit. */
12809 if (type == 'p' || type == 'q')
12812 /* If any of the shifted bits are set, we must use an extended
12813 opcode. If the address depends on the size of this
12814 instruction, this can lead to a loop, so we arrange to always
12815 use an extended opcode. We only check this when we are in
12816 the main relaxation loop, when SEC is NULL. */
12817 if ((val & ((1 << op->shift) - 1)) != 0 && sec == NULL)
12819 fragp->fr_subtype =
12820 RELAX_MIPS16_MARK_LONG_BRANCH (fragp->fr_subtype);
12824 /* If we are about to mark a frag as extended because the value
12825 is precisely maxtiny + 1, then there is a chance of an
12826 infinite loop as in the following code:
12831 In this case when the la is extended, foo is 0x3fc bytes
12832 away, so the la can be shrunk, but then foo is 0x400 away, so
12833 the la must be extended. To avoid this loop, we mark the
12834 frag as extended if it was small, and is about to become
12835 extended with a value of maxtiny + 1. */
12836 if (val == ((maxtiny + 1) << op->shift)
12837 && ! RELAX_MIPS16_EXTENDED (fragp->fr_subtype)
12840 fragp->fr_subtype =
12841 RELAX_MIPS16_MARK_LONG_BRANCH (fragp->fr_subtype);
12845 else if (symsec != absolute_section && sec != NULL)
12846 as_bad_where (fragp->fr_file, fragp->fr_line, _("unsupported relocation"));
12848 if ((val & ((1 << op->shift) - 1)) != 0
12849 || val < (mintiny << op->shift)
12850 || val > (maxtiny << op->shift))
12856 /* Compute the length of a branch sequence, and adjust the
12857 RELAX_BRANCH_TOOFAR bit accordingly. If FRAGP is NULL, the
12858 worst-case length is computed, with UPDATE being used to indicate
12859 whether an unconditional (-1), branch-likely (+1) or regular (0)
12860 branch is to be computed. */
12862 relaxed_branch_length (fragp, sec, update)
12871 && S_IS_DEFINED (fragp->fr_symbol)
12872 && sec == S_GET_SEGMENT (fragp->fr_symbol))
12877 val = S_GET_VALUE (fragp->fr_symbol) + fragp->fr_offset;
12879 addr = fragp->fr_address + fragp->fr_fix + 4;
12883 toofar = val < - (0x8000 << 2) || val >= (0x8000 << 2);
12886 /* If the symbol is not defined or it's in a different segment,
12887 assume the user knows what's going on and emit a short
12893 if (fragp && update && toofar != RELAX_BRANCH_TOOFAR (fragp->fr_subtype))
12895 = RELAX_BRANCH_ENCODE (RELAX_BRANCH_RELOC_S2 (fragp->fr_subtype),
12896 RELAX_BRANCH_UNCOND (fragp->fr_subtype),
12897 RELAX_BRANCH_LIKELY (fragp->fr_subtype),
12898 RELAX_BRANCH_LINK (fragp->fr_subtype),
12904 if (fragp ? RELAX_BRANCH_LIKELY (fragp->fr_subtype) : (update > 0))
12907 if (mips_pic != NO_PIC)
12909 /* Additional space for PIC loading of target address. */
12911 if (mips_opts.isa == ISA_MIPS1)
12912 /* Additional space for $at-stabilizing nop. */
12916 /* If branch is conditional. */
12917 if (fragp ? !RELAX_BRANCH_UNCOND (fragp->fr_subtype) : (update >= 0))
12924 /* Estimate the size of a frag before relaxing. Unless this is the
12925 mips16, we are not really relaxing here, and the final size is
12926 encoded in the subtype information. For the mips16, we have to
12927 decide whether we are using an extended opcode or not. */
12930 md_estimate_size_before_relax (fragp, segtype)
12935 boolean linkonce = false;
12937 if (RELAX_BRANCH_P (fragp->fr_subtype))
12940 fragp->fr_var = relaxed_branch_length (fragp, segtype, false);
12942 return fragp->fr_var;
12945 if (RELAX_MIPS16_P (fragp->fr_subtype))
12946 /* We don't want to modify the EXTENDED bit here; it might get us
12947 into infinite loops. We change it only in mips_relax_frag(). */
12948 return (RELAX_MIPS16_EXTENDED (fragp->fr_subtype) ? 4 : 2);
12950 if (mips_pic == NO_PIC)
12952 change = nopic_need_relax (fragp->fr_symbol, 0);
12954 else if (mips_pic == SVR4_PIC)
12959 sym = fragp->fr_symbol;
12961 /* Handle the case of a symbol equated to another symbol. */
12962 while (symbol_equated_reloc_p (sym))
12966 /* It's possible to get a loop here in a badly written
12968 n = symbol_get_value_expression (sym)->X_add_symbol;
12974 symsec = S_GET_SEGMENT (sym);
12976 /* duplicate the test for LINK_ONCE sections as in adjust_reloc_syms */
12977 if (symsec != segtype && ! S_IS_LOCAL (sym))
12979 if ((bfd_get_section_flags (stdoutput, symsec) & SEC_LINK_ONCE)
12983 /* The GNU toolchain uses an extension for ELF: a section
12984 beginning with the magic string .gnu.linkonce is a linkonce
12986 if (strncmp (segment_name (symsec), ".gnu.linkonce",
12987 sizeof ".gnu.linkonce" - 1) == 0)
12991 /* This must duplicate the test in adjust_reloc_syms. */
12992 change = (symsec != &bfd_und_section
12993 && symsec != &bfd_abs_section
12994 && ! bfd_is_com_section (symsec)
12997 /* A global or weak symbol is treated as external. */
12998 && (OUTPUT_FLAVOR != bfd_target_elf_flavour
12999 || (! S_IS_WEAK (sym)
13000 && (! S_IS_EXTERNAL (sym)
13001 || mips_pic == EMBEDDED_PIC)))
13010 /* Record the offset to the first reloc in the fr_opcode field.
13011 This lets md_convert_frag and tc_gen_reloc know that the code
13012 must be expanded. */
13013 fragp->fr_opcode = (fragp->fr_literal
13015 - RELAX_OLD (fragp->fr_subtype)
13016 + RELAX_RELOC1 (fragp->fr_subtype));
13017 /* FIXME: This really needs as_warn_where. */
13018 if (RELAX_WARN (fragp->fr_subtype))
13019 as_warn (_("AT used after \".set noat\" or macro used after "
13020 "\".set nomacro\""));
13022 return RELAX_NEW (fragp->fr_subtype) - RELAX_OLD (fragp->fr_subtype);
13028 /* This is called to see whether a reloc against a defined symbol
13029 should be converted into a reloc against a section. Don't adjust
13030 MIPS16 jump relocations, so we don't have to worry about the format
13031 of the offset in the .o file. Don't adjust relocations against
13032 mips16 symbols, so that the linker can find them if it needs to set
13036 mips_fix_adjustable (fixp)
13039 if (fixp->fx_r_type == BFD_RELOC_MIPS16_JMP)
13042 if (fixp->fx_r_type == BFD_RELOC_VTABLE_INHERIT
13043 || fixp->fx_r_type == BFD_RELOC_VTABLE_ENTRY)
13046 if (fixp->fx_addsy == NULL)
13050 if (OUTPUT_FLAVOR == bfd_target_elf_flavour
13051 && S_GET_OTHER (fixp->fx_addsy) == STO_MIPS16
13052 && fixp->fx_subsy == NULL)
13059 /* Translate internal representation of relocation info to BFD target
13063 tc_gen_reloc (section, fixp)
13064 asection *section ATTRIBUTE_UNUSED;
13067 static arelent *retval[4];
13069 bfd_reloc_code_real_type code;
13071 reloc = retval[0] = (arelent *) xmalloc (sizeof (arelent));
13074 reloc->sym_ptr_ptr = (asymbol **) xmalloc (sizeof (asymbol *));
13075 *reloc->sym_ptr_ptr = symbol_get_bfdsym (fixp->fx_addsy);
13076 reloc->address = fixp->fx_frag->fr_address + fixp->fx_where;
13078 if (mips_pic == EMBEDDED_PIC
13079 && SWITCH_TABLE (fixp))
13081 /* For a switch table entry we use a special reloc. The addend
13082 is actually the difference between the reloc address and the
13084 reloc->addend = reloc->address - S_GET_VALUE (fixp->fx_subsy);
13085 if (OUTPUT_FLAVOR != bfd_target_ecoff_flavour)
13086 as_fatal (_("Double check fx_r_type in tc-mips.c:tc_gen_reloc"));
13087 fixp->fx_r_type = BFD_RELOC_GPREL32;
13089 else if (fixp->fx_r_type == BFD_RELOC_PCREL_LO16)
13091 if (OUTPUT_FLAVOR == bfd_target_elf_flavour)
13092 reloc->addend = fixp->fx_addnumber;
13095 /* We use a special addend for an internal RELLO reloc. */
13096 if (symbol_section_p (fixp->fx_addsy))
13097 reloc->addend = reloc->address - S_GET_VALUE (fixp->fx_subsy);
13099 reloc->addend = fixp->fx_addnumber + reloc->address;
13102 else if (fixp->fx_r_type == BFD_RELOC_PCREL_HI16_S)
13104 assert (fixp->fx_next != NULL
13105 && fixp->fx_next->fx_r_type == BFD_RELOC_PCREL_LO16);
13107 /* The reloc is relative to the RELLO; adjust the addend
13109 if (OUTPUT_FLAVOR == bfd_target_elf_flavour)
13110 reloc->addend = fixp->fx_next->fx_addnumber;
13113 /* We use a special addend for an internal RELHI reloc. */
13114 if (symbol_section_p (fixp->fx_addsy))
13115 reloc->addend = (fixp->fx_next->fx_frag->fr_address
13116 + fixp->fx_next->fx_where
13117 - S_GET_VALUE (fixp->fx_subsy));
13119 reloc->addend = (fixp->fx_addnumber
13120 + fixp->fx_next->fx_frag->fr_address
13121 + fixp->fx_next->fx_where);
13124 else if (fixp->fx_pcrel == 0 || OUTPUT_FLAVOR == bfd_target_elf_flavour)
13125 reloc->addend = fixp->fx_addnumber;
13128 if (OUTPUT_FLAVOR != bfd_target_aout_flavour)
13129 /* A gruesome hack which is a result of the gruesome gas reloc
13131 reloc->addend = reloc->address;
13133 reloc->addend = -reloc->address;
13136 /* If this is a variant frag, we may need to adjust the existing
13137 reloc and generate a new one. */
13138 if (fixp->fx_frag->fr_opcode != NULL
13139 && ((fixp->fx_r_type == BFD_RELOC_GPREL16
13141 || fixp->fx_r_type == BFD_RELOC_MIPS_GOT16
13142 || fixp->fx_r_type == BFD_RELOC_MIPS_CALL16
13143 || fixp->fx_r_type == BFD_RELOC_MIPS_GOT_HI16
13144 || fixp->fx_r_type == BFD_RELOC_MIPS_GOT_LO16
13145 || fixp->fx_r_type == BFD_RELOC_MIPS_CALL_HI16
13146 || fixp->fx_r_type == BFD_RELOC_MIPS_CALL_LO16)
13151 assert (! RELAX_MIPS16_P (fixp->fx_frag->fr_subtype));
13153 /* If this is not the last reloc in this frag, then we have two
13154 GPREL relocs, or a GOT_HI16/GOT_LO16 pair, or a
13155 CALL_HI16/CALL_LO16, both of which are being replaced. Let
13156 the second one handle all of them. */
13157 if (fixp->fx_next != NULL
13158 && fixp->fx_frag == fixp->fx_next->fx_frag)
13160 assert ((fixp->fx_r_type == BFD_RELOC_GPREL16
13161 && fixp->fx_next->fx_r_type == BFD_RELOC_GPREL16)
13162 || (fixp->fx_r_type == BFD_RELOC_MIPS_GOT_HI16
13163 && (fixp->fx_next->fx_r_type
13164 == BFD_RELOC_MIPS_GOT_LO16))
13165 || (fixp->fx_r_type == BFD_RELOC_MIPS_CALL_HI16
13166 && (fixp->fx_next->fx_r_type
13167 == BFD_RELOC_MIPS_CALL_LO16)));
13172 fixp->fx_where = fixp->fx_frag->fr_opcode - fixp->fx_frag->fr_literal;
13173 reloc->address = fixp->fx_frag->fr_address + fixp->fx_where;
13174 reloc2 = retval[1] = (arelent *) xmalloc (sizeof (arelent));
13176 reloc2->sym_ptr_ptr = (asymbol **) xmalloc (sizeof (asymbol *));
13177 *reloc2->sym_ptr_ptr = symbol_get_bfdsym (fixp->fx_addsy);
13178 reloc2->address = (reloc->address
13179 + (RELAX_RELOC2 (fixp->fx_frag->fr_subtype)
13180 - RELAX_RELOC1 (fixp->fx_frag->fr_subtype)));
13181 reloc2->addend = fixp->fx_addnumber;
13182 reloc2->howto = bfd_reloc_type_lookup (stdoutput, BFD_RELOC_LO16);
13183 assert (reloc2->howto != NULL);
13185 if (RELAX_RELOC3 (fixp->fx_frag->fr_subtype))
13189 reloc3 = retval[2] = (arelent *) xmalloc (sizeof (arelent));
13192 reloc3->address += 4;
13195 if (mips_pic == NO_PIC)
13197 assert (fixp->fx_r_type == BFD_RELOC_GPREL16);
13198 fixp->fx_r_type = BFD_RELOC_HI16_S;
13200 else if (mips_pic == SVR4_PIC)
13202 switch (fixp->fx_r_type)
13206 case BFD_RELOC_MIPS_GOT16:
13208 case BFD_RELOC_MIPS_GOT_LO16:
13209 case BFD_RELOC_MIPS_CALL_LO16:
13210 fixp->fx_r_type = BFD_RELOC_MIPS_GOT16;
13212 case BFD_RELOC_MIPS_CALL16:
13215 /* BFD_RELOC_MIPS_GOT16;*/
13216 fixp->fx_r_type = BFD_RELOC_MIPS_GOT_PAGE;
13217 reloc2->howto = bfd_reloc_type_lookup
13218 (stdoutput, BFD_RELOC_MIPS_GOT_OFST);
13221 fixp->fx_r_type = BFD_RELOC_MIPS_GOT16;
13228 /* newabi uses R_MIPS_GOT_DISP for local symbols */
13229 if (HAVE_NEWABI && BFD_RELOC_MIPS_GOT_LO16)
13231 fixp->fx_r_type = BFD_RELOC_MIPS_GOT_DISP;
13236 /* Since the old MIPS ELF ABI uses Rel instead of Rela, encode the vtable
13237 entry to be used in the relocation's section offset. */
13238 if (! HAVE_NEWABI && fixp->fx_r_type == BFD_RELOC_VTABLE_ENTRY)
13240 reloc->address = reloc->addend;
13244 /* Since DIFF_EXPR_OK is defined in tc-mips.h, it is possible that
13245 fixup_segment converted a non-PC relative reloc into a PC
13246 relative reloc. In such a case, we need to convert the reloc
13248 code = fixp->fx_r_type;
13249 if (fixp->fx_pcrel)
13254 code = BFD_RELOC_8_PCREL;
13257 code = BFD_RELOC_16_PCREL;
13260 code = BFD_RELOC_32_PCREL;
13263 code = BFD_RELOC_64_PCREL;
13265 case BFD_RELOC_8_PCREL:
13266 case BFD_RELOC_16_PCREL:
13267 case BFD_RELOC_32_PCREL:
13268 case BFD_RELOC_64_PCREL:
13269 case BFD_RELOC_16_PCREL_S2:
13270 case BFD_RELOC_PCREL_HI16_S:
13271 case BFD_RELOC_PCREL_LO16:
13274 as_bad_where (fixp->fx_file, fixp->fx_line,
13275 _("Cannot make %s relocation PC relative"),
13276 bfd_get_reloc_code_name (code));
13281 /* md_apply_fix3 has a double-subtraction hack to get
13282 bfd_install_relocation to behave nicely. GPREL relocations are
13283 handled correctly without this hack, so undo it here. We can't
13284 stop md_apply_fix3 from subtracting twice in the first place since
13285 the fake addend is required for variant frags above. */
13286 if (fixp->fx_addsy != NULL && OUTPUT_FLAVOR == bfd_target_elf_flavour
13287 && (code == BFD_RELOC_GPREL16 || code == BFD_RELOC_MIPS16_GPREL)
13288 && reloc->addend != 0
13289 && mips_need_elf_addend_fixup (fixp))
13290 reloc->addend += S_GET_VALUE (fixp->fx_addsy);
13293 /* To support a PC relative reloc when generating embedded PIC code
13294 for ECOFF, we use a Cygnus extension. We check for that here to
13295 make sure that we don't let such a reloc escape normally. */
13296 if ((OUTPUT_FLAVOR == bfd_target_ecoff_flavour
13297 || OUTPUT_FLAVOR == bfd_target_elf_flavour)
13298 && code == BFD_RELOC_16_PCREL_S2
13299 && mips_pic != EMBEDDED_PIC)
13300 reloc->howto = NULL;
13302 reloc->howto = bfd_reloc_type_lookup (stdoutput, code);
13304 if (reloc->howto == NULL)
13306 as_bad_where (fixp->fx_file, fixp->fx_line,
13307 _("Can not represent %s relocation in this object file format"),
13308 bfd_get_reloc_code_name (code));
13315 /* Relax a machine dependent frag. This returns the amount by which
13316 the current size of the frag should change. */
13319 mips_relax_frag (sec, fragp, stretch)
13324 if (RELAX_BRANCH_P (fragp->fr_subtype))
13326 offsetT old_var = fragp->fr_var;
13328 fragp->fr_var = relaxed_branch_length (fragp, sec, true);
13330 return fragp->fr_var - old_var;
13333 if (! RELAX_MIPS16_P (fragp->fr_subtype))
13336 if (mips16_extended_frag (fragp, NULL, stretch))
13338 if (RELAX_MIPS16_EXTENDED (fragp->fr_subtype))
13340 fragp->fr_subtype = RELAX_MIPS16_MARK_EXTENDED (fragp->fr_subtype);
13345 if (! RELAX_MIPS16_EXTENDED (fragp->fr_subtype))
13347 fragp->fr_subtype = RELAX_MIPS16_CLEAR_EXTENDED (fragp->fr_subtype);
13354 /* Convert a machine dependent frag. */
13357 md_convert_frag (abfd, asec, fragp)
13358 bfd *abfd ATTRIBUTE_UNUSED;
13365 if (RELAX_BRANCH_P (fragp->fr_subtype))
13368 unsigned long insn;
13372 buf = (bfd_byte *)fragp->fr_literal + fragp->fr_fix;
13374 if (target_big_endian)
13375 insn = bfd_getb32 (buf);
13377 insn = bfd_getl32 (buf);
13379 if (!RELAX_BRANCH_TOOFAR (fragp->fr_subtype))
13381 /* We generate a fixup instead of applying it right now
13382 because, if there are linker relaxations, we're going to
13383 need the relocations. */
13384 exp.X_op = O_symbol;
13385 exp.X_add_symbol = fragp->fr_symbol;
13386 exp.X_add_number = fragp->fr_offset;
13388 fixp = fix_new_exp (fragp, buf - (bfd_byte *)fragp->fr_literal,
13390 RELAX_BRANCH_RELOC_S2 (fragp->fr_subtype)
13391 ? BFD_RELOC_16_PCREL_S2
13392 : BFD_RELOC_16_PCREL);
13393 fixp->fx_file = fragp->fr_file;
13394 fixp->fx_line = fragp->fr_line;
13396 md_number_to_chars ((char *)buf, insn, 4);
13403 as_warn_where (fragp->fr_file, fragp->fr_line,
13404 _("relaxed out-of-range branch into a jump"));
13406 if (RELAX_BRANCH_UNCOND (fragp->fr_subtype))
13409 if (!RELAX_BRANCH_LIKELY (fragp->fr_subtype))
13411 /* Reverse the branch. */
13412 switch ((insn >> 28) & 0xf)
13415 /* bc[0-3][tf]l? and bc1any[24][ft] instructions can
13416 have the condition reversed by tweaking a single
13417 bit, and their opcodes all have 0x4???????. */
13418 assert ((insn & 0xf1000000) == 0x41000000);
13419 insn ^= 0x00010000;
13423 /* bltz 0x04000000 bgez 0x04010000
13424 bltzal 0x04100000 bgezal 0x04110000 */
13425 assert ((insn & 0xfc0e0000) == 0x04000000);
13426 insn ^= 0x00010000;
13430 /* beq 0x10000000 bne 0x14000000
13431 blez 0x18000000 bgtz 0x1c000000 */
13432 insn ^= 0x04000000;
13440 if (RELAX_BRANCH_LINK (fragp->fr_subtype))
13442 /* Clear the and-link bit. */
13443 assert ((insn & 0xfc1c0000) == 0x04100000);
13445 /* bltzal 0x04100000 bgezal 0x04110000
13446 bltzall 0x04120000 bgezall 0x04130000 */
13447 insn &= ~0x00100000;
13450 /* Branch over the branch (if the branch was likely) or the
13451 full jump (not likely case). Compute the offset from the
13452 current instruction to branch to. */
13453 if (RELAX_BRANCH_LIKELY (fragp->fr_subtype))
13457 /* How many bytes in instructions we've already emitted? */
13458 i = buf - (bfd_byte *)fragp->fr_literal - fragp->fr_fix;
13459 /* How many bytes in instructions from here to the end? */
13460 i = fragp->fr_var - i;
13462 /* Convert to instruction count. */
13464 /* Branch counts from the next instruction. */
13467 /* Branch over the jump. */
13468 md_number_to_chars ((char *)buf, insn, 4);
13472 md_number_to_chars ((char*)buf, 0, 4);
13475 if (RELAX_BRANCH_LIKELY (fragp->fr_subtype))
13477 /* beql $0, $0, 2f */
13479 /* Compute the PC offset from the current instruction to
13480 the end of the variable frag. */
13481 /* How many bytes in instructions we've already emitted? */
13482 i = buf - (bfd_byte *)fragp->fr_literal - fragp->fr_fix;
13483 /* How many bytes in instructions from here to the end? */
13484 i = fragp->fr_var - i;
13485 /* Convert to instruction count. */
13487 /* Don't decrement i, because we want to branch over the
13491 md_number_to_chars ((char *)buf, insn, 4);
13494 md_number_to_chars ((char *)buf, 0, 4);
13499 if (mips_pic == NO_PIC)
13502 insn = (RELAX_BRANCH_LINK (fragp->fr_subtype)
13503 ? 0x0c000000 : 0x08000000);
13504 exp.X_op = O_symbol;
13505 exp.X_add_symbol = fragp->fr_symbol;
13506 exp.X_add_number = fragp->fr_offset;
13508 fixp = fix_new_exp (fragp, buf - (bfd_byte *)fragp->fr_literal,
13509 4, &exp, 0, BFD_RELOC_MIPS_JMP);
13510 fixp->fx_file = fragp->fr_file;
13511 fixp->fx_line = fragp->fr_line;
13513 md_number_to_chars ((char*)buf, insn, 4);
13518 /* lw/ld $at, <sym>($gp) R_MIPS_GOT16 */
13519 insn = HAVE_64BIT_ADDRESSES ? 0xdf810000 : 0x8f810000;
13520 exp.X_op = O_symbol;
13521 exp.X_add_symbol = fragp->fr_symbol;
13522 exp.X_add_number = fragp->fr_offset;
13524 if (fragp->fr_offset)
13526 exp.X_add_symbol = make_expr_symbol (&exp);
13527 exp.X_add_number = 0;
13530 fixp = fix_new_exp (fragp, buf - (bfd_byte *)fragp->fr_literal,
13531 4, &exp, 0, BFD_RELOC_MIPS_GOT16);
13532 fixp->fx_file = fragp->fr_file;
13533 fixp->fx_line = fragp->fr_line;
13535 md_number_to_chars ((char*)buf, insn, 4);
13538 if (mips_opts.isa == ISA_MIPS1)
13541 md_number_to_chars ((char*)buf, 0, 4);
13545 /* d/addiu $at, $at, <sym> R_MIPS_LO16 */
13546 insn = HAVE_64BIT_ADDRESSES ? 0x64210000 : 0x24210000;
13548 fixp = fix_new_exp (fragp, buf - (bfd_byte *)fragp->fr_literal,
13549 4, &exp, 0, BFD_RELOC_LO16);
13550 fixp->fx_file = fragp->fr_file;
13551 fixp->fx_line = fragp->fr_line;
13553 md_number_to_chars ((char*)buf, insn, 4);
13557 if (RELAX_BRANCH_LINK (fragp->fr_subtype))
13562 md_number_to_chars ((char*)buf, insn, 4);
13567 assert (buf == (bfd_byte *)fragp->fr_literal
13568 + fragp->fr_fix + fragp->fr_var);
13570 fragp->fr_fix += fragp->fr_var;
13575 if (RELAX_MIPS16_P (fragp->fr_subtype))
13578 register const struct mips16_immed_operand *op;
13579 boolean small, ext;
13582 unsigned long insn;
13583 boolean use_extend;
13584 unsigned short extend;
13586 type = RELAX_MIPS16_TYPE (fragp->fr_subtype);
13587 op = mips16_immed_operands;
13588 while (op->type != type)
13591 if (RELAX_MIPS16_EXTENDED (fragp->fr_subtype))
13602 resolve_symbol_value (fragp->fr_symbol);
13603 val = S_GET_VALUE (fragp->fr_symbol);
13608 addr = fragp->fr_address + fragp->fr_fix;
13610 /* The rules for the base address of a PC relative reloc are
13611 complicated; see mips16_extended_frag. */
13612 if (type == 'p' || type == 'q')
13617 /* Ignore the low bit in the target, since it will be
13618 set for a text label. */
13619 if ((val & 1) != 0)
13622 else if (RELAX_MIPS16_JAL_DSLOT (fragp->fr_subtype))
13624 else if (RELAX_MIPS16_DSLOT (fragp->fr_subtype))
13627 addr &= ~ (addressT) ((1 << op->shift) - 1);
13630 /* Make sure the section winds up with the alignment we have
13633 record_alignment (asec, op->shift);
13637 && (RELAX_MIPS16_JAL_DSLOT (fragp->fr_subtype)
13638 || RELAX_MIPS16_DSLOT (fragp->fr_subtype)))
13639 as_warn_where (fragp->fr_file, fragp->fr_line,
13640 _("extended instruction in delay slot"));
13642 buf = (bfd_byte *) (fragp->fr_literal + fragp->fr_fix);
13644 if (target_big_endian)
13645 insn = bfd_getb16 (buf);
13647 insn = bfd_getl16 (buf);
13649 mips16_immed (fragp->fr_file, fragp->fr_line, type, val,
13650 RELAX_MIPS16_USER_EXT (fragp->fr_subtype),
13651 small, ext, &insn, &use_extend, &extend);
13655 md_number_to_chars ((char *) buf, 0xf000 | extend, 2);
13656 fragp->fr_fix += 2;
13660 md_number_to_chars ((char *) buf, insn, 2);
13661 fragp->fr_fix += 2;
13666 if (fragp->fr_opcode == NULL)
13669 old = RELAX_OLD (fragp->fr_subtype);
13670 new = RELAX_NEW (fragp->fr_subtype);
13671 fixptr = fragp->fr_literal + fragp->fr_fix;
13674 memcpy (fixptr - old, fixptr, new);
13676 fragp->fr_fix += new - old;
13682 /* This function is called after the relocs have been generated.
13683 We've been storing mips16 text labels as odd. Here we convert them
13684 back to even for the convenience of the debugger. */
13687 mips_frob_file_after_relocs ()
13690 unsigned int count, i;
13692 if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
13695 syms = bfd_get_outsymbols (stdoutput);
13696 count = bfd_get_symcount (stdoutput);
13697 for (i = 0; i < count; i++, syms++)
13699 if (elf_symbol (*syms)->internal_elf_sym.st_other == STO_MIPS16
13700 && ((*syms)->value & 1) != 0)
13702 (*syms)->value &= ~1;
13703 /* If the symbol has an odd size, it was probably computed
13704 incorrectly, so adjust that as well. */
13705 if ((elf_symbol (*syms)->internal_elf_sym.st_size & 1) != 0)
13706 ++elf_symbol (*syms)->internal_elf_sym.st_size;
13713 /* This function is called whenever a label is defined. It is used
13714 when handling branch delays; if a branch has a label, we assume we
13715 can not move it. */
13718 mips_define_label (sym)
13721 struct insn_label_list *l;
13723 if (free_insn_labels == NULL)
13724 l = (struct insn_label_list *) xmalloc (sizeof *l);
13727 l = free_insn_labels;
13728 free_insn_labels = l->next;
13732 l->next = insn_labels;
13736 #if defined (OBJ_ELF) || defined (OBJ_MAYBE_ELF)
13738 /* Some special processing for a MIPS ELF file. */
13741 mips_elf_final_processing ()
13743 /* Write out the register information. */
13744 if (mips_abi != N64_ABI)
13748 s.ri_gprmask = mips_gprmask;
13749 s.ri_cprmask[0] = mips_cprmask[0];
13750 s.ri_cprmask[1] = mips_cprmask[1];
13751 s.ri_cprmask[2] = mips_cprmask[2];
13752 s.ri_cprmask[3] = mips_cprmask[3];
13753 /* The gp_value field is set by the MIPS ELF backend. */
13755 bfd_mips_elf32_swap_reginfo_out (stdoutput, &s,
13756 ((Elf32_External_RegInfo *)
13757 mips_regmask_frag));
13761 Elf64_Internal_RegInfo s;
13763 s.ri_gprmask = mips_gprmask;
13765 s.ri_cprmask[0] = mips_cprmask[0];
13766 s.ri_cprmask[1] = mips_cprmask[1];
13767 s.ri_cprmask[2] = mips_cprmask[2];
13768 s.ri_cprmask[3] = mips_cprmask[3];
13769 /* The gp_value field is set by the MIPS ELF backend. */
13771 bfd_mips_elf64_swap_reginfo_out (stdoutput, &s,
13772 ((Elf64_External_RegInfo *)
13773 mips_regmask_frag));
13776 /* Set the MIPS ELF flag bits. FIXME: There should probably be some
13777 sort of BFD interface for this. */
13778 if (mips_any_noreorder)
13779 elf_elfheader (stdoutput)->e_flags |= EF_MIPS_NOREORDER;
13780 if (mips_pic != NO_PIC)
13781 elf_elfheader (stdoutput)->e_flags |= EF_MIPS_PIC;
13783 /* Set MIPS ELF flags for ASEs. */
13784 if (file_ase_mips16)
13785 elf_elfheader (stdoutput)->e_flags |= EF_MIPS_ARCH_ASE_M16;
13786 #if 0 /* XXX FIXME */
13787 if (file_ase_mips3d)
13788 elf_elfheader (stdoutput)->e_flags |= ???;
13791 elf_elfheader (stdoutput)->e_flags |= EF_MIPS_ARCH_ASE_MDMX;
13793 /* Set the MIPS ELF ABI flags. */
13794 if (mips_abi == O32_ABI && USE_E_MIPS_ABI_O32)
13795 elf_elfheader (stdoutput)->e_flags |= E_MIPS_ABI_O32;
13796 else if (mips_abi == O64_ABI)
13797 elf_elfheader (stdoutput)->e_flags |= E_MIPS_ABI_O64;
13798 else if (mips_abi == EABI_ABI)
13800 if (!file_mips_gp32)
13801 elf_elfheader (stdoutput)->e_flags |= E_MIPS_ABI_EABI64;
13803 elf_elfheader (stdoutput)->e_flags |= E_MIPS_ABI_EABI32;
13805 else if (mips_abi == N32_ABI)
13806 elf_elfheader (stdoutput)->e_flags |= EF_MIPS_ABI2;
13808 /* Nothing to do for N64_ABI. */
13810 if (mips_32bitmode)
13811 elf_elfheader (stdoutput)->e_flags |= EF_MIPS_32BITMODE;
13814 #endif /* OBJ_ELF || OBJ_MAYBE_ELF */
13816 typedef struct proc {
13818 unsigned long reg_mask;
13819 unsigned long reg_offset;
13820 unsigned long fpreg_mask;
13821 unsigned long fpreg_offset;
13822 unsigned long frame_offset;
13823 unsigned long frame_reg;
13824 unsigned long pc_reg;
13827 static procS cur_proc;
13828 static procS *cur_proc_ptr;
13829 static int numprocs;
13831 /* Fill in an rs_align_code fragment. */
13834 mips_handle_align (fragp)
13837 if (fragp->fr_type != rs_align_code)
13840 if (mips_opts.mips16)
13842 static const unsigned char be_nop[] = { 0x65, 0x00 };
13843 static const unsigned char le_nop[] = { 0x00, 0x65 };
13848 bytes = fragp->fr_next->fr_address - fragp->fr_address - fragp->fr_fix;
13849 p = fragp->fr_literal + fragp->fr_fix;
13857 memcpy (p, (target_big_endian ? be_nop : le_nop), 2);
13861 /* For mips32, a nop is a zero, which we trivially get by doing nothing. */
13872 /* check for premature end, nesting errors, etc */
13874 as_warn (_("missing .end at end of assembly"));
13883 if (*input_line_pointer == '-')
13885 ++input_line_pointer;
13888 if (!ISDIGIT (*input_line_pointer))
13889 as_bad (_("expected simple number"));
13890 if (input_line_pointer[0] == '0')
13892 if (input_line_pointer[1] == 'x')
13894 input_line_pointer += 2;
13895 while (ISXDIGIT (*input_line_pointer))
13898 val |= hex_value (*input_line_pointer++);
13900 return negative ? -val : val;
13904 ++input_line_pointer;
13905 while (ISDIGIT (*input_line_pointer))
13908 val |= *input_line_pointer++ - '0';
13910 return negative ? -val : val;
13913 if (!ISDIGIT (*input_line_pointer))
13915 printf (_(" *input_line_pointer == '%c' 0x%02x\n"),
13916 *input_line_pointer, *input_line_pointer);
13917 as_warn (_("invalid number"));
13920 while (ISDIGIT (*input_line_pointer))
13923 val += *input_line_pointer++ - '0';
13925 return negative ? -val : val;
13928 /* The .file directive; just like the usual .file directive, but there
13929 is an initial number which is the ECOFF file index. In the non-ECOFF
13930 case .file implies DWARF-2. */
13934 int x ATTRIBUTE_UNUSED;
13936 static int first_file_directive = 0;
13938 if (ECOFF_DEBUGGING)
13947 filename = dwarf2_directive_file (0);
13949 /* Versions of GCC up to 3.1 start files with a ".file"
13950 directive even for stabs output. Make sure that this
13951 ".file" is handled. Note that you need a version of GCC
13952 after 3.1 in order to support DWARF-2 on MIPS. */
13953 if (filename != NULL && ! first_file_directive)
13955 (void) new_logical_line (filename, -1);
13956 s_app_file_string (filename);
13958 first_file_directive = 1;
13962 /* The .loc directive, implying DWARF-2. */
13966 int x ATTRIBUTE_UNUSED;
13968 if (!ECOFF_DEBUGGING)
13969 dwarf2_directive_loc (0);
13972 /* The .end directive. */
13976 int x ATTRIBUTE_UNUSED;
13981 /* Following functions need their own .frame and .cprestore directives. */
13982 mips_frame_reg_valid = 0;
13983 mips_cprestore_valid = 0;
13985 if (!is_end_of_line[(unsigned char) *input_line_pointer])
13988 demand_empty_rest_of_line ();
13993 #ifdef BFD_ASSEMBLER
13994 if ((bfd_get_section_flags (stdoutput, now_seg) & SEC_CODE) != 0)
13999 if (now_seg != data_section && now_seg != bss_section)
14006 as_warn (_(".end not in text section"));
14010 as_warn (_(".end directive without a preceding .ent directive."));
14011 demand_empty_rest_of_line ();
14017 assert (S_GET_NAME (p));
14018 if (strcmp (S_GET_NAME (p), S_GET_NAME (cur_proc_ptr->isym)))
14019 as_warn (_(".end symbol does not match .ent symbol."));
14021 if (debug_type == DEBUG_STABS)
14022 stabs_generate_asm_endfunc (S_GET_NAME (p),
14026 as_warn (_(".end directive missing or unknown symbol"));
14029 /* Generate a .pdr section. */
14030 if (OUTPUT_FLAVOR == bfd_target_elf_flavour && ! ECOFF_DEBUGGING)
14032 segT saved_seg = now_seg;
14033 subsegT saved_subseg = now_subseg;
14038 dot = frag_now_fix ();
14040 #ifdef md_flush_pending_output
14041 md_flush_pending_output ();
14045 subseg_set (pdr_seg, 0);
14047 /* Write the symbol. */
14048 exp.X_op = O_symbol;
14049 exp.X_add_symbol = p;
14050 exp.X_add_number = 0;
14051 emit_expr (&exp, 4);
14053 fragp = frag_more (7 * 4);
14055 md_number_to_chars (fragp, (valueT) cur_proc_ptr->reg_mask, 4);
14056 md_number_to_chars (fragp + 4, (valueT) cur_proc_ptr->reg_offset, 4);
14057 md_number_to_chars (fragp + 8, (valueT) cur_proc_ptr->fpreg_mask, 4);
14058 md_number_to_chars (fragp + 12, (valueT) cur_proc_ptr->fpreg_offset, 4);
14059 md_number_to_chars (fragp + 16, (valueT) cur_proc_ptr->frame_offset, 4);
14060 md_number_to_chars (fragp + 20, (valueT) cur_proc_ptr->frame_reg, 4);
14061 md_number_to_chars (fragp + 24, (valueT) cur_proc_ptr->pc_reg, 4);
14063 subseg_set (saved_seg, saved_subseg);
14065 #endif /* OBJ_ELF */
14067 cur_proc_ptr = NULL;
14070 /* The .aent and .ent directives. */
14079 symbolP = get_symbol ();
14080 if (*input_line_pointer == ',')
14081 ++input_line_pointer;
14082 SKIP_WHITESPACE ();
14083 if (ISDIGIT (*input_line_pointer)
14084 || *input_line_pointer == '-')
14087 #ifdef BFD_ASSEMBLER
14088 if ((bfd_get_section_flags (stdoutput, now_seg) & SEC_CODE) != 0)
14093 if (now_seg != data_section && now_seg != bss_section)
14100 as_warn (_(".ent or .aent not in text section."));
14102 if (!aent && cur_proc_ptr)
14103 as_warn (_("missing .end"));
14107 /* This function needs its own .frame and .cprestore directives. */
14108 mips_frame_reg_valid = 0;
14109 mips_cprestore_valid = 0;
14111 cur_proc_ptr = &cur_proc;
14112 memset (cur_proc_ptr, '\0', sizeof (procS));
14114 cur_proc_ptr->isym = symbolP;
14116 symbol_get_bfdsym (symbolP)->flags |= BSF_FUNCTION;
14120 if (debug_type == DEBUG_STABS)
14121 stabs_generate_asm_func (S_GET_NAME (symbolP),
14122 S_GET_NAME (symbolP));
14125 demand_empty_rest_of_line ();
14128 /* The .frame directive. If the mdebug section is present (IRIX 5 native)
14129 then ecoff.c (ecoff_directive_frame) is used. For embedded targets,
14130 s_mips_frame is used so that we can set the PDR information correctly.
14131 We can't use the ecoff routines because they make reference to the ecoff
14132 symbol table (in the mdebug section). */
14135 s_mips_frame (ignore)
14136 int ignore ATTRIBUTE_UNUSED;
14139 if (OUTPUT_FLAVOR == bfd_target_elf_flavour && ! ECOFF_DEBUGGING)
14143 if (cur_proc_ptr == (procS *) NULL)
14145 as_warn (_(".frame outside of .ent"));
14146 demand_empty_rest_of_line ();
14150 cur_proc_ptr->frame_reg = tc_get_register (1);
14152 SKIP_WHITESPACE ();
14153 if (*input_line_pointer++ != ','
14154 || get_absolute_expression_and_terminator (&val) != ',')
14156 as_warn (_("Bad .frame directive"));
14157 --input_line_pointer;
14158 demand_empty_rest_of_line ();
14162 cur_proc_ptr->frame_offset = val;
14163 cur_proc_ptr->pc_reg = tc_get_register (0);
14165 demand_empty_rest_of_line ();
14168 #endif /* OBJ_ELF */
14172 /* The .fmask and .mask directives. If the mdebug section is present
14173 (IRIX 5 native) then ecoff.c (ecoff_directive_mask) is used. For
14174 embedded targets, s_mips_mask is used so that we can set the PDR
14175 information correctly. We can't use the ecoff routines because they
14176 make reference to the ecoff symbol table (in the mdebug section). */
14179 s_mips_mask (reg_type)
14183 if (OUTPUT_FLAVOR == bfd_target_elf_flavour && ! ECOFF_DEBUGGING)
14187 if (cur_proc_ptr == (procS *) NULL)
14189 as_warn (_(".mask/.fmask outside of .ent"));
14190 demand_empty_rest_of_line ();
14194 if (get_absolute_expression_and_terminator (&mask) != ',')
14196 as_warn (_("Bad .mask/.fmask directive"));
14197 --input_line_pointer;
14198 demand_empty_rest_of_line ();
14202 off = get_absolute_expression ();
14204 if (reg_type == 'F')
14206 cur_proc_ptr->fpreg_mask = mask;
14207 cur_proc_ptr->fpreg_offset = off;
14211 cur_proc_ptr->reg_mask = mask;
14212 cur_proc_ptr->reg_offset = off;
14215 demand_empty_rest_of_line ();
14218 #endif /* OBJ_ELF */
14219 s_ignore (reg_type);
14222 /* The .loc directive. */
14233 assert (now_seg == text_section);
14235 lineno = get_number ();
14236 addroff = frag_now_fix ();
14238 symbolP = symbol_new ("", N_SLINE, addroff, frag_now);
14239 S_SET_TYPE (symbolP, N_SLINE);
14240 S_SET_OTHER (symbolP, 0);
14241 S_SET_DESC (symbolP, lineno);
14242 symbolP->sy_segment = now_seg;
14246 /* A table describing all the processors gas knows about. Names are
14247 matched in the order listed.
14249 To ease comparison, please keep this table in the same order as
14250 gcc's mips_cpu_info_table[]. */
14251 static const struct mips_cpu_info mips_cpu_info_table[] =
14253 /* Entries for generic ISAs */
14254 { "mips1", 1, ISA_MIPS1, CPU_R3000 },
14255 { "mips2", 1, ISA_MIPS2, CPU_R6000 },
14256 { "mips3", 1, ISA_MIPS3, CPU_R4000 },
14257 { "mips4", 1, ISA_MIPS4, CPU_R8000 },
14258 { "mips5", 1, ISA_MIPS5, CPU_MIPS5 },
14259 { "mips32", 1, ISA_MIPS32, CPU_MIPS32 },
14260 { "mips64", 1, ISA_MIPS64, CPU_MIPS64 },
14263 { "r3000", 0, ISA_MIPS1, CPU_R3000 },
14264 { "r2000", 0, ISA_MIPS1, CPU_R3000 },
14265 { "r3900", 0, ISA_MIPS1, CPU_R3900 },
14268 { "r6000", 0, ISA_MIPS2, CPU_R6000 },
14271 { "r4000", 0, ISA_MIPS3, CPU_R4000 },
14272 { "r4010", 0, ISA_MIPS2, CPU_R4010 },
14273 { "vr4100", 0, ISA_MIPS3, CPU_VR4100 },
14274 { "vr4111", 0, ISA_MIPS3, CPU_R4111 },
14275 { "vr4120", 0, ISA_MIPS3, CPU_VR4120 },
14276 { "vr4130", 0, ISA_MIPS3, CPU_VR4120 },
14277 { "vr4181", 0, ISA_MIPS3, CPU_R4111 },
14278 { "vr4300", 0, ISA_MIPS3, CPU_R4300 },
14279 { "r4400", 0, ISA_MIPS3, CPU_R4400 },
14280 { "r4600", 0, ISA_MIPS3, CPU_R4600 },
14281 { "orion", 0, ISA_MIPS3, CPU_R4600 },
14282 { "r4650", 0, ISA_MIPS3, CPU_R4650 },
14285 { "r8000", 0, ISA_MIPS4, CPU_R8000 },
14286 { "r10000", 0, ISA_MIPS4, CPU_R10000 },
14287 { "r12000", 0, ISA_MIPS4, CPU_R12000 },
14288 { "vr5000", 0, ISA_MIPS4, CPU_R5000 },
14289 { "vr5400", 0, ISA_MIPS4, CPU_VR5400 },
14290 { "vr5500", 0, ISA_MIPS4, CPU_VR5500 },
14291 { "rm5200", 0, ISA_MIPS4, CPU_R5000 },
14292 { "rm5230", 0, ISA_MIPS4, CPU_R5000 },
14293 { "rm5231", 0, ISA_MIPS4, CPU_R5000 },
14294 { "rm5261", 0, ISA_MIPS4, CPU_R5000 },
14295 { "rm5721", 0, ISA_MIPS4, CPU_R5000 },
14296 { "r7000", 0, ISA_MIPS4, CPU_R5000 },
14299 { "4kc", 0, ISA_MIPS32, CPU_MIPS32, },
14300 { "4km", 0, ISA_MIPS32, CPU_MIPS32 },
14301 { "4kp", 0, ISA_MIPS32, CPU_MIPS32 },
14304 { "5kc", 0, ISA_MIPS64, CPU_MIPS64 },
14305 { "20kc", 0, ISA_MIPS64, CPU_MIPS64 },
14307 /* Broadcom SB-1 CPU core */
14308 { "sb1", 0, ISA_MIPS64, CPU_SB1 },
14315 /* Return true if GIVEN is the same as CANONICAL, or if it is CANONICAL
14316 with a final "000" replaced by "k". Ignore case.
14318 Note: this function is shared between GCC and GAS. */
14321 mips_strict_matching_cpu_name_p (canonical, given)
14322 const char *canonical, *given;
14324 while (*given != 0 && TOLOWER (*given) == TOLOWER (*canonical))
14325 given++, canonical++;
14327 return ((*given == 0 && *canonical == 0)
14328 || (strcmp (canonical, "000") == 0 && strcasecmp (given, "k") == 0));
14332 /* Return true if GIVEN matches CANONICAL, where GIVEN is a user-supplied
14333 CPU name. We've traditionally allowed a lot of variation here.
14335 Note: this function is shared between GCC and GAS. */
14338 mips_matching_cpu_name_p (canonical, given)
14339 const char *canonical, *given;
14341 /* First see if the name matches exactly, or with a final "000"
14342 turned into "k". */
14343 if (mips_strict_matching_cpu_name_p (canonical, given))
14346 /* If not, try comparing based on numerical designation alone.
14347 See if GIVEN is an unadorned number, or 'r' followed by a number. */
14348 if (TOLOWER (*given) == 'r')
14350 if (!ISDIGIT (*given))
14353 /* Skip over some well-known prefixes in the canonical name,
14354 hoping to find a number there too. */
14355 if (TOLOWER (canonical[0]) == 'v' && TOLOWER (canonical[1]) == 'r')
14357 else if (TOLOWER (canonical[0]) == 'r' && TOLOWER (canonical[1]) == 'm')
14359 else if (TOLOWER (canonical[0]) == 'r')
14362 return mips_strict_matching_cpu_name_p (canonical, given);
14366 /* Parse an option that takes the name of a processor as its argument.
14367 OPTION is the name of the option and CPU_STRING is the argument.
14368 Return the corresponding processor enumeration if the CPU_STRING is
14369 recognized, otherwise report an error and return null.
14371 A similar function exists in GCC. */
14373 static const struct mips_cpu_info *
14374 mips_parse_cpu (option, cpu_string)
14375 const char *option, *cpu_string;
14377 const struct mips_cpu_info *p;
14379 /* 'from-abi' selects the most compatible architecture for the given
14380 ABI: MIPS I for 32-bit ABIs and MIPS III for 64-bit ABIs. For the
14381 EABIs, we have to decide whether we're using the 32-bit or 64-bit
14382 version. Look first at the -mgp options, if given, otherwise base
14383 the choice on MIPS_DEFAULT_64BIT.
14385 Treat NO_ABI like the EABIs. One reason to do this is that the
14386 plain 'mips' and 'mips64' configs have 'from-abi' as their default
14387 architecture. This code picks MIPS I for 'mips' and MIPS III for
14388 'mips64', just as we did in the days before 'from-abi'. */
14389 if (strcasecmp (cpu_string, "from-abi") == 0)
14391 if (ABI_NEEDS_32BIT_REGS (mips_abi))
14392 return mips_cpu_info_from_isa (ISA_MIPS1);
14394 if (ABI_NEEDS_64BIT_REGS (mips_abi))
14395 return mips_cpu_info_from_isa (ISA_MIPS3);
14397 if (file_mips_gp32 >= 0)
14398 return mips_cpu_info_from_isa (file_mips_gp32 ? ISA_MIPS1 : ISA_MIPS3);
14400 return mips_cpu_info_from_isa (MIPS_DEFAULT_64BIT
14405 /* 'default' has traditionally been a no-op. Probably not very useful. */
14406 if (strcasecmp (cpu_string, "default") == 0)
14409 for (p = mips_cpu_info_table; p->name != 0; p++)
14410 if (mips_matching_cpu_name_p (p->name, cpu_string))
14413 as_bad ("Bad value (%s) for %s", cpu_string, option);
14417 /* Return the canonical processor information for ISA (a member of the
14418 ISA_MIPS* enumeration). */
14420 static const struct mips_cpu_info *
14421 mips_cpu_info_from_isa (isa)
14426 for (i = 0; mips_cpu_info_table[i].name != NULL; i++)
14427 if (mips_cpu_info_table[i].is_isa
14428 && isa == mips_cpu_info_table[i].isa)
14429 return (&mips_cpu_info_table[i]);
14435 show (stream, string, col_p, first_p)
14437 const char *string;
14443 fprintf (stream, "%24s", "");
14448 fprintf (stream, ", ");
14452 if (*col_p + strlen (string) > 72)
14454 fprintf (stream, "\n%24s", "");
14458 fprintf (stream, "%s", string);
14459 *col_p += strlen (string);
14465 md_show_usage (stream)
14471 fprintf (stream, _("\
14473 -membedded-pic generate embedded position independent code\n\
14474 -EB generate big endian output\n\
14475 -EL generate little endian output\n\
14476 -g, -g2 do not remove unneeded NOPs or swap branches\n\
14477 -G NUM allow referencing objects up to NUM bytes\n\
14478 implicitly with the gp register [default 8]\n"));
14479 fprintf (stream, _("\
14480 -mips1 generate MIPS ISA I instructions\n\
14481 -mips2 generate MIPS ISA II instructions\n\
14482 -mips3 generate MIPS ISA III instructions\n\
14483 -mips4 generate MIPS ISA IV instructions\n\
14484 -mips5 generate MIPS ISA V instructions\n\
14485 -mips32 generate MIPS32 ISA instructions\n\
14486 -mips64 generate MIPS64 ISA instructions\n\
14487 -march=CPU/-mtune=CPU generate code/schedule for CPU, where CPU is one of:\n"));
14491 for (i = 0; mips_cpu_info_table[i].name != NULL; i++)
14492 show (stream, mips_cpu_info_table[i].name, &column, &first);
14493 show (stream, "from-abi", &column, &first);
14494 fputc ('\n', stream);
14496 fprintf (stream, _("\
14497 -mCPU equivalent to -march=CPU -mtune=CPU. Deprecated.\n\
14498 -no-mCPU don't generate code specific to CPU.\n\
14499 For -mCPU and -no-mCPU, CPU must be one of:\n"));
14503 show (stream, "3900", &column, &first);
14504 show (stream, "4010", &column, &first);
14505 show (stream, "4100", &column, &first);
14506 show (stream, "4650", &column, &first);
14507 fputc ('\n', stream);
14509 fprintf (stream, _("\
14510 -mips16 generate mips16 instructions\n\
14511 -no-mips16 do not generate mips16 instructions\n"));
14512 fprintf (stream, _("\
14513 -mgp32 use 32-bit GPRs, regardless of the chosen ISA\n\
14514 -mfp32 use 32-bit FPRs, regardless of the chosen ISA\n\
14515 -O0 remove unneeded NOPs, do not swap branches\n\
14516 -O remove unneeded NOPs and swap branches\n\
14517 -n warn about NOPs generated from macros\n\
14518 --[no-]construct-floats [dis]allow floating point values to be constructed\n\
14519 --trap, --no-break trap exception on div by 0 and mult overflow\n\
14520 --break, --no-trap break exception on div by 0 and mult overflow\n"));
14522 fprintf (stream, _("\
14523 -KPIC, -call_shared generate SVR4 position independent code\n\
14524 -non_shared do not generate position independent code\n\
14525 -xgot assume a 32 bit GOT\n\
14526 -mabi=ABI create ABI conformant object file for:\n"));
14530 show (stream, "32", &column, &first);
14531 show (stream, "o64", &column, &first);
14532 show (stream, "n32", &column, &first);
14533 show (stream, "64", &column, &first);
14534 show (stream, "eabi", &column, &first);
14536 fputc ('\n', stream);
14538 fprintf (stream, _("\
14539 -32 create o32 ABI object file (default)\n\
14540 -n32 create n32 ABI object file\n\
14541 -64 create 64 ABI object file\n"));