1 /* tc-mips.c -- assemble code for a MIPS chip.
2 Copyright 1993, 1994, 1995, 1996, 1997, 1998, 1999, 2000, 2001, 2002, 2003
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 /* Return true if ISA supports 64-bit right rotate (dror et al.)
265 #define ISA_HAS_DROR(ISA) ( \
269 /* Return true if ISA supports 32-bit right rotate (ror et al.)
271 #define ISA_HAS_ROR(ISA) ( \
272 (ISA) == ISA_MIPS32R2 \
275 #define HAVE_32BIT_GPRS \
276 (mips_opts.gp32 || ! ISA_HAS_64BIT_REGS (mips_opts.isa))
278 #define HAVE_32BIT_FPRS \
279 (mips_opts.fp32 || ! ISA_HAS_64BIT_REGS (mips_opts.isa))
281 #define HAVE_64BIT_GPRS (! HAVE_32BIT_GPRS)
282 #define HAVE_64BIT_FPRS (! HAVE_32BIT_FPRS)
284 #define HAVE_NEWABI (mips_abi == N32_ABI || mips_abi == N64_ABI)
286 #define HAVE_64BIT_OBJECTS (mips_abi == N64_ABI)
288 /* We can only have 64bit addresses if the object file format
290 #define HAVE_32BIT_ADDRESSES \
292 || ((bfd_arch_bits_per_address (stdoutput) == 32 \
293 || ! HAVE_64BIT_OBJECTS) \
294 && mips_pic != EMBEDDED_PIC))
296 #define HAVE_64BIT_ADDRESSES (! HAVE_32BIT_ADDRESSES)
297 #define HAVE_64BIT_ADDRESS_CONSTANTS (HAVE_64BIT_ADDRESSES \
300 /* Return true if the given CPU supports the MIPS16 ASE. */
301 #define CPU_HAS_MIPS16(cpu) \
302 (strncmp (TARGET_CPU, "mips16", sizeof ("mips16") - 1) == 0 \
303 || strncmp (TARGET_CANONICAL, "mips-lsi-elf", sizeof ("mips-lsi-elf") - 1) == 0)
305 /* Return true if the given CPU supports the MIPS3D ASE. */
306 #define CPU_HAS_MIPS3D(cpu) ((cpu) == CPU_SB1 \
309 /* Return true if the given CPU supports the MDMX ASE. */
310 #define CPU_HAS_MDMX(cpu) (FALSE \
313 /* True if CPU has a dror instruction. */
314 #define CPU_HAS_DROR(CPU) ((CPU) == CPU_VR5400 || (CPU) == CPU_VR5500)
316 /* True if CPU has a ror instruction. */
317 #define CPU_HAS_ROR(CPU) CPU_HAS_DROR (CPU)
319 /* Whether the processor uses hardware interlocks to protect
320 reads from the HI and LO registers, and thus does not
321 require nops to be inserted. */
323 #define hilo_interlocks (mips_arch == CPU_R4010 \
324 || mips_arch == CPU_VR5500 \
325 || mips_arch == CPU_SB1 \
328 /* Whether the processor uses hardware interlocks to protect reads
329 from the GPRs, and thus does not require nops to be inserted. */
330 #define gpr_interlocks \
331 (mips_opts.isa != ISA_MIPS1 \
332 || mips_arch == CPU_VR5400 \
333 || mips_arch == CPU_VR5500 \
334 || mips_arch == CPU_R3900)
336 /* As with other "interlocks" this is used by hardware that has FP
337 (co-processor) interlocks. */
338 /* Itbl support may require additional care here. */
339 #define cop_interlocks (mips_arch == CPU_R4300 \
340 || mips_arch == CPU_VR5400 \
341 || mips_arch == CPU_VR5500 \
342 || mips_arch == CPU_SB1 \
345 /* Is this a mfhi or mflo instruction? */
346 #define MF_HILO_INSN(PINFO) \
347 ((PINFO & INSN_READ_HI) || (PINFO & INSN_READ_LO))
349 /* MIPS PIC level. */
351 enum mips_pic_level mips_pic;
353 /* Warn about all NOPS that the assembler generates. */
354 static int warn_nops = 0;
356 /* 1 if we should generate 32 bit offsets from the $gp register in
357 SVR4_PIC mode. Currently has no meaning in other modes. */
358 static int mips_big_got = 0;
360 /* 1 if trap instructions should used for overflow rather than break
362 static int mips_trap = 0;
364 /* 1 if double width floating point constants should not be constructed
365 by assembling two single width halves into two single width floating
366 point registers which just happen to alias the double width destination
367 register. On some architectures this aliasing can be disabled by a bit
368 in the status register, and the setting of this bit cannot be determined
369 automatically at assemble time. */
370 static int mips_disable_float_construction;
372 /* Non-zero if any .set noreorder directives were used. */
374 static int mips_any_noreorder;
376 /* Non-zero if nops should be inserted when the register referenced in
377 an mfhi/mflo instruction is read in the next two instructions. */
378 static int mips_7000_hilo_fix;
380 /* The size of the small data section. */
381 static unsigned int g_switch_value = 8;
382 /* Whether the -G option was used. */
383 static int g_switch_seen = 0;
388 /* If we can determine in advance that GP optimization won't be
389 possible, we can skip the relaxation stuff that tries to produce
390 GP-relative references. This makes delay slot optimization work
393 This function can only provide a guess, but it seems to work for
394 gcc output. It needs to guess right for gcc, otherwise gcc
395 will put what it thinks is a GP-relative instruction in a branch
398 I don't know if a fix is needed for the SVR4_PIC mode. I've only
399 fixed it for the non-PIC mode. KR 95/04/07 */
400 static int nopic_need_relax PARAMS ((symbolS *, int));
402 /* handle of the OPCODE hash table */
403 static struct hash_control *op_hash = NULL;
405 /* The opcode hash table we use for the mips16. */
406 static struct hash_control *mips16_op_hash = NULL;
408 /* This array holds the chars that always start a comment. If the
409 pre-processor is disabled, these aren't very useful */
410 const char comment_chars[] = "#";
412 /* This array holds the chars that only start a comment at the beginning of
413 a line. If the line seems to have the form '# 123 filename'
414 .line and .file directives will appear in the pre-processed output */
415 /* Note that input_file.c hand checks for '#' at the beginning of the
416 first line of the input file. This is because the compiler outputs
417 #NO_APP at the beginning of its output. */
418 /* Also note that C style comments are always supported. */
419 const char line_comment_chars[] = "#";
421 /* This array holds machine specific line separator characters. */
422 const char line_separator_chars[] = ";";
424 /* Chars that can be used to separate mant from exp in floating point nums */
425 const char EXP_CHARS[] = "eE";
427 /* Chars that mean this number is a floating point constant */
430 const char FLT_CHARS[] = "rRsSfFdDxXpP";
432 /* Also be aware that MAXIMUM_NUMBER_OF_CHARS_FOR_FLOAT may have to be
433 changed in read.c . Ideally it shouldn't have to know about it at all,
434 but nothing is ideal around here.
437 static char *insn_error;
439 static int auto_align = 1;
441 /* When outputting SVR4 PIC code, the assembler needs to know the
442 offset in the stack frame from which to restore the $gp register.
443 This is set by the .cprestore pseudo-op, and saved in this
445 static offsetT mips_cprestore_offset = -1;
447 /* Similiar for NewABI PIC code, where $gp is callee-saved. NewABI has some
448 more optimizations, it can use a register value instead of a memory-saved
449 offset and even an other register than $gp as global pointer. */
450 static offsetT mips_cpreturn_offset = -1;
451 static int mips_cpreturn_register = -1;
452 static int mips_gp_register = GP;
453 static int mips_gprel_offset = 0;
455 /* Whether mips_cprestore_offset has been set in the current function
456 (or whether it has already been warned about, if not). */
457 static int mips_cprestore_valid = 0;
459 /* This is the register which holds the stack frame, as set by the
460 .frame pseudo-op. This is needed to implement .cprestore. */
461 static int mips_frame_reg = SP;
463 /* Whether mips_frame_reg has been set in the current function
464 (or whether it has already been warned about, if not). */
465 static int mips_frame_reg_valid = 0;
467 /* To output NOP instructions correctly, we need to keep information
468 about the previous two instructions. */
470 /* Whether we are optimizing. The default value of 2 means to remove
471 unneeded NOPs and swap branch instructions when possible. A value
472 of 1 means to not swap branches. A value of 0 means to always
474 static int mips_optimize = 2;
476 /* Debugging level. -g sets this to 2. -gN sets this to N. -g0 is
477 equivalent to seeing no -g option at all. */
478 static int mips_debug = 0;
480 /* The previous instruction. */
481 static struct mips_cl_insn prev_insn;
483 /* The instruction before prev_insn. */
484 static struct mips_cl_insn prev_prev_insn;
486 /* If we don't want information for prev_insn or prev_prev_insn, we
487 point the insn_mo field at this dummy integer. */
488 static const struct mips_opcode dummy_opcode = { NULL, NULL, 0, 0, 0, 0 };
490 /* Non-zero if prev_insn is valid. */
491 static int prev_insn_valid;
493 /* The frag for the previous instruction. */
494 static struct frag *prev_insn_frag;
496 /* The offset into prev_insn_frag for the previous instruction. */
497 static long prev_insn_where;
499 /* The reloc type for the previous instruction, if any. */
500 static bfd_reloc_code_real_type prev_insn_reloc_type[3];
502 /* The reloc for the previous instruction, if any. */
503 static fixS *prev_insn_fixp[3];
505 /* Non-zero if the previous instruction was in a delay slot. */
506 static int prev_insn_is_delay_slot;
508 /* Non-zero if the previous instruction was in a .set noreorder. */
509 static int prev_insn_unreordered;
511 /* Non-zero if the previous instruction uses an extend opcode (if
513 static int prev_insn_extended;
515 /* Non-zero if the previous previous instruction was in a .set
517 static int prev_prev_insn_unreordered;
519 /* If this is set, it points to a frag holding nop instructions which
520 were inserted before the start of a noreorder section. If those
521 nops turn out to be unnecessary, the size of the frag can be
523 static fragS *prev_nop_frag;
525 /* The number of nop instructions we created in prev_nop_frag. */
526 static int prev_nop_frag_holds;
528 /* The number of nop instructions that we know we need in
530 static int prev_nop_frag_required;
532 /* The number of instructions we've seen since prev_nop_frag. */
533 static int prev_nop_frag_since;
535 /* For ECOFF and ELF, relocations against symbols are done in two
536 parts, with a HI relocation and a LO relocation. Each relocation
537 has only 16 bits of space to store an addend. This means that in
538 order for the linker to handle carries correctly, it must be able
539 to locate both the HI and the LO relocation. This means that the
540 relocations must appear in order in the relocation table.
542 In order to implement this, we keep track of each unmatched HI
543 relocation. We then sort them so that they immediately precede the
544 corresponding LO relocation. */
549 struct mips_hi_fixup *next;
552 /* The section this fixup is in. */
556 /* The list of unmatched HI relocs. */
558 static struct mips_hi_fixup *mips_hi_fixup_list;
560 /* The frag containing the last explicit relocation operator.
561 Null if explicit relocations have not been used. */
563 static fragS *prev_reloc_op_frag;
565 /* Map normal MIPS register numbers to mips16 register numbers. */
567 #define X ILLEGAL_REG
568 static const int mips32_to_16_reg_map[] =
570 X, X, 2, 3, 4, 5, 6, 7,
571 X, X, X, X, X, X, X, X,
572 0, 1, X, X, X, X, X, X,
573 X, X, X, X, X, X, X, X
577 /* Map mips16 register numbers to normal MIPS register numbers. */
579 static const unsigned int mips16_to_32_reg_map[] =
581 16, 17, 2, 3, 4, 5, 6, 7
584 static int mips_fix_4122_bugs;
586 /* We don't relax branches by default, since this causes us to expand
587 `la .l2 - .l1' if there's a branch between .l1 and .l2, because we
588 fail to compute the offset before expanding the macro to the most
589 efficient expansion. */
591 static int mips_relax_branch;
593 /* Since the MIPS does not have multiple forms of PC relative
594 instructions, we do not have to do relaxing as is done on other
595 platforms. However, we do have to handle GP relative addressing
596 correctly, which turns out to be a similar problem.
598 Every macro that refers to a symbol can occur in (at least) two
599 forms, one with GP relative addressing and one without. For
600 example, loading a global variable into a register generally uses
601 a macro instruction like this:
603 If i can be addressed off the GP register (this is true if it is in
604 the .sbss or .sdata section, or if it is known to be smaller than
605 the -G argument) this will generate the following instruction:
607 This instruction will use a GPREL reloc. If i can not be addressed
608 off the GP register, the following instruction sequence will be used:
611 In this case the first instruction will have a HI16 reloc, and the
612 second reloc will have a LO16 reloc. Both relocs will be against
615 The issue here is that we may not know whether i is GP addressable
616 until after we see the instruction that uses it. Therefore, we
617 want to be able to choose the final instruction sequence only at
618 the end of the assembly. This is similar to the way other
619 platforms choose the size of a PC relative instruction only at the
622 When generating position independent code we do not use GP
623 addressing in quite the same way, but the issue still arises as
624 external symbols and local symbols must be handled differently.
626 We handle these issues by actually generating both possible
627 instruction sequences. The longer one is put in a frag_var with
628 type rs_machine_dependent. We encode what to do with the frag in
629 the subtype field. We encode (1) the number of existing bytes to
630 replace, (2) the number of new bytes to use, (3) the offset from
631 the start of the existing bytes to the first reloc we must generate
632 (that is, the offset is applied from the start of the existing
633 bytes after they are replaced by the new bytes, if any), (4) the
634 offset from the start of the existing bytes to the second reloc,
635 (5) whether a third reloc is needed (the third reloc is always four
636 bytes after the second reloc), and (6) whether to warn if this
637 variant is used (this is sometimes needed if .set nomacro or .set
638 noat is in effect). All these numbers are reasonably small.
640 Generating two instruction sequences must be handled carefully to
641 ensure that delay slots are handled correctly. Fortunately, there
642 are a limited number of cases. When the second instruction
643 sequence is generated, append_insn is directed to maintain the
644 existing delay slot information, so it continues to apply to any
645 code after the second instruction sequence. This means that the
646 second instruction sequence must not impose any requirements not
647 required by the first instruction sequence.
649 These variant frags are then handled in functions called by the
650 machine independent code. md_estimate_size_before_relax returns
651 the final size of the frag. md_convert_frag sets up the final form
652 of the frag. tc_gen_reloc adjust the first reloc and adds a second
654 #define RELAX_ENCODE(old, new, reloc1, reloc2, reloc3, warn) \
658 | (((reloc1) + 64) << 9) \
659 | (((reloc2) + 64) << 2) \
660 | ((reloc3) ? (1 << 1) : 0) \
662 #define RELAX_OLD(i) (((i) >> 23) & 0x7f)
663 #define RELAX_NEW(i) (((i) >> 16) & 0x7f)
664 #define RELAX_RELOC1(i) ((valueT) (((i) >> 9) & 0x7f) - 64)
665 #define RELAX_RELOC2(i) ((valueT) (((i) >> 2) & 0x7f) - 64)
666 #define RELAX_RELOC3(i) (((i) >> 1) & 1)
667 #define RELAX_WARN(i) ((i) & 1)
669 /* Branch without likely bit. If label is out of range, we turn:
671 beq reg1, reg2, label
681 with the following opcode replacements:
688 bltzal <-> bgezal (with jal label instead of j label)
690 Even though keeping the delay slot instruction in the delay slot of
691 the branch would be more efficient, it would be very tricky to do
692 correctly, because we'd have to introduce a variable frag *after*
693 the delay slot instruction, and expand that instead. Let's do it
694 the easy way for now, even if the branch-not-taken case now costs
695 one additional instruction. Out-of-range branches are not supposed
696 to be common, anyway.
698 Branch likely. If label is out of range, we turn:
700 beql reg1, reg2, label
701 delay slot (annulled if branch not taken)
710 delay slot (executed only if branch taken)
713 It would be possible to generate a shorter sequence by losing the
714 likely bit, generating something like:
719 delay slot (executed only if branch taken)
731 bltzall -> bgezal (with jal label instead of j label)
732 bgezall -> bltzal (ditto)
735 but it's not clear that it would actually improve performance. */
736 #define RELAX_BRANCH_ENCODE(uncond, likely, link, toofar) \
739 | ((toofar) ? 1 : 0) \
741 | ((likely) ? 4 : 0) \
742 | ((uncond) ? 8 : 0)))
743 #define RELAX_BRANCH_P(i) (((i) & 0xf0000000) == 0xc0000000)
744 #define RELAX_BRANCH_UNCOND(i) (((i) & 8) != 0)
745 #define RELAX_BRANCH_LIKELY(i) (((i) & 4) != 0)
746 #define RELAX_BRANCH_LINK(i) (((i) & 2) != 0)
747 #define RELAX_BRANCH_TOOFAR(i) (((i) & 1) != 0)
749 /* For mips16 code, we use an entirely different form of relaxation.
750 mips16 supports two versions of most instructions which take
751 immediate values: a small one which takes some small value, and a
752 larger one which takes a 16 bit value. Since branches also follow
753 this pattern, relaxing these values is required.
755 We can assemble both mips16 and normal MIPS code in a single
756 object. Therefore, we need to support this type of relaxation at
757 the same time that we support the relaxation described above. We
758 use the high bit of the subtype field to distinguish these cases.
760 The information we store for this type of relaxation is the
761 argument code found in the opcode file for this relocation, whether
762 the user explicitly requested a small or extended form, and whether
763 the relocation is in a jump or jal delay slot. That tells us the
764 size of the value, and how it should be stored. We also store
765 whether the fragment is considered to be extended or not. We also
766 store whether this is known to be a branch to a different section,
767 whether we have tried to relax this frag yet, and whether we have
768 ever extended a PC relative fragment because of a shift count. */
769 #define RELAX_MIPS16_ENCODE(type, small, ext, dslot, jal_dslot) \
772 | ((small) ? 0x100 : 0) \
773 | ((ext) ? 0x200 : 0) \
774 | ((dslot) ? 0x400 : 0) \
775 | ((jal_dslot) ? 0x800 : 0))
776 #define RELAX_MIPS16_P(i) (((i) & 0xc0000000) == 0x80000000)
777 #define RELAX_MIPS16_TYPE(i) ((i) & 0xff)
778 #define RELAX_MIPS16_USER_SMALL(i) (((i) & 0x100) != 0)
779 #define RELAX_MIPS16_USER_EXT(i) (((i) & 0x200) != 0)
780 #define RELAX_MIPS16_DSLOT(i) (((i) & 0x400) != 0)
781 #define RELAX_MIPS16_JAL_DSLOT(i) (((i) & 0x800) != 0)
782 #define RELAX_MIPS16_EXTENDED(i) (((i) & 0x1000) != 0)
783 #define RELAX_MIPS16_MARK_EXTENDED(i) ((i) | 0x1000)
784 #define RELAX_MIPS16_CLEAR_EXTENDED(i) ((i) &~ 0x1000)
785 #define RELAX_MIPS16_LONG_BRANCH(i) (((i) & 0x2000) != 0)
786 #define RELAX_MIPS16_MARK_LONG_BRANCH(i) ((i) | 0x2000)
787 #define RELAX_MIPS16_CLEAR_LONG_BRANCH(i) ((i) &~ 0x2000)
789 /* Is the given value a sign-extended 32-bit value? */
790 #define IS_SEXT_32BIT_NUM(x) \
791 (((x) &~ (offsetT) 0x7fffffff) == 0 \
792 || (((x) &~ (offsetT) 0x7fffffff) == ~ (offsetT) 0x7fffffff))
794 /* Is the given value a sign-extended 16-bit value? */
795 #define IS_SEXT_16BIT_NUM(x) \
796 (((x) &~ (offsetT) 0x7fff) == 0 \
797 || (((x) &~ (offsetT) 0x7fff) == ~ (offsetT) 0x7fff))
800 /* Prototypes for static functions. */
803 #define internalError() \
804 as_fatal (_("internal Error, line %d, %s"), __LINE__, __FILE__)
806 #define internalError() as_fatal (_("MIPS internal Error"));
809 enum mips_regclass { MIPS_GR_REG, MIPS_FP_REG, MIPS16_REG };
811 static inline bfd_boolean reloc_needs_lo_p
812 PARAMS ((bfd_reloc_code_real_type));
813 static inline bfd_boolean fixup_has_matching_lo_p
815 static int insn_uses_reg
816 PARAMS ((struct mips_cl_insn *ip, unsigned int reg,
817 enum mips_regclass class));
818 static int reg_needs_delay
819 PARAMS ((unsigned int));
820 static void mips16_mark_labels
822 static void append_insn
823 PARAMS ((char *place, struct mips_cl_insn * ip, expressionS * p,
824 bfd_reloc_code_real_type *r));
825 static void mips_no_prev_insn
827 static void mips_emit_delays
828 PARAMS ((bfd_boolean));
830 static void macro_build
831 PARAMS ((char *place, int *counter, expressionS * ep, const char *name,
832 const char *fmt, ...));
834 static void macro_build ();
836 static void mips16_macro_build
837 PARAMS ((char *, int *, expressionS *, const char *, const char *, va_list));
838 static void macro_build_jalr
839 PARAMS ((int, expressionS *));
840 static void macro_build_lui
841 PARAMS ((char *place, int *counter, expressionS * ep, int regnum));
842 static void macro_build_ldst_constoffset
843 PARAMS ((char *place, int *counter, expressionS * ep, const char *op,
844 int valreg, int breg));
846 PARAMS ((int *counter, int reg, int unsignedp));
847 static void check_absolute_expr
848 PARAMS ((struct mips_cl_insn * ip, expressionS *));
849 static void load_register
850 PARAMS ((int *, int, expressionS *, int));
851 static void load_address
852 PARAMS ((int *, int, expressionS *, int *));
853 static void move_register
854 PARAMS ((int *, int, int));
856 PARAMS ((struct mips_cl_insn * ip));
857 static void mips16_macro
858 PARAMS ((struct mips_cl_insn * ip));
859 #ifdef LOSING_COMPILER
861 PARAMS ((struct mips_cl_insn * ip));
864 PARAMS ((char *str, struct mips_cl_insn * ip));
865 static void mips16_ip
866 PARAMS ((char *str, struct mips_cl_insn * ip));
867 static void mips16_immed
868 PARAMS ((char *, unsigned int, int, offsetT, bfd_boolean, bfd_boolean,
869 bfd_boolean, unsigned long *, bfd_boolean *, unsigned short *));
870 static bfd_boolean parse_relocation
871 PARAMS ((char **, bfd_reloc_code_real_type *));
872 static size_t my_getSmallExpression
873 PARAMS ((expressionS *, bfd_reloc_code_real_type *, char *));
874 static void my_getExpression
875 PARAMS ((expressionS *, char *));
877 static int support_64bit_objects
880 static void mips_set_option_string
881 PARAMS ((const char **, const char *));
882 static symbolS *get_symbol
884 static void mips_align
885 PARAMS ((int to, int fill, symbolS *label));
888 static void s_change_sec
890 static void s_change_section
894 static void s_float_cons
896 static void s_mips_globl
900 static void s_mipsset
902 static void s_abicalls
906 static void s_cpsetup
908 static void s_cplocal
910 static void s_cprestore
912 static void s_cpreturn
914 static void s_gpvalue
918 static void s_gpdword
924 static void md_obj_begin
926 static void md_obj_end
928 static long get_number
930 static void s_mips_ent
932 static void s_mips_end
934 static void s_mips_frame
936 static void s_mips_mask
938 static void s_mips_stab
940 static void s_mips_weakext
942 static void s_mips_file
944 static void s_mips_loc
946 static bfd_boolean pic_need_relax
947 PARAMS ((symbolS *, asection *));
948 static int mips16_extended_frag
949 PARAMS ((fragS *, asection *, long));
950 static int relaxed_branch_length (fragS *, asection *, int);
951 static int validate_mips_insn
952 PARAMS ((const struct mips_opcode *));
954 PARAMS ((FILE *, const char *, int *, int *));
956 static int mips_need_elf_addend_fixup
960 /* Table and functions used to map between CPU/ISA names, and
961 ISA levels, and CPU numbers. */
965 const char *name; /* CPU or ISA name. */
966 int is_isa; /* Is this an ISA? (If 0, a CPU.) */
967 int isa; /* ISA level. */
968 int cpu; /* CPU number (default CPU if ISA). */
971 static void mips_set_architecture
972 PARAMS ((const struct mips_cpu_info *));
973 static void mips_set_tune
974 PARAMS ((const struct mips_cpu_info *));
975 static bfd_boolean mips_strict_matching_cpu_name_p
976 PARAMS ((const char *, const char *));
977 static bfd_boolean mips_matching_cpu_name_p
978 PARAMS ((const char *, const char *));
979 static const struct mips_cpu_info *mips_parse_cpu
980 PARAMS ((const char *, const char *));
981 static const struct mips_cpu_info *mips_cpu_info_from_isa
986 The following pseudo-ops from the Kane and Heinrich MIPS book
987 should be defined here, but are currently unsupported: .alias,
988 .galive, .gjaldef, .gjrlive, .livereg, .noalias.
990 The following pseudo-ops from the Kane and Heinrich MIPS book are
991 specific to the type of debugging information being generated, and
992 should be defined by the object format: .aent, .begin, .bend,
993 .bgnb, .end, .endb, .ent, .fmask, .frame, .loc, .mask, .verstamp,
996 The following pseudo-ops from the Kane and Heinrich MIPS book are
997 not MIPS CPU specific, but are also not specific to the object file
998 format. This file is probably the best place to define them, but
999 they are not currently supported: .asm0, .endr, .lab, .repeat,
1002 static const pseudo_typeS mips_pseudo_table[] =
1004 /* MIPS specific pseudo-ops. */
1005 {"option", s_option, 0},
1006 {"set", s_mipsset, 0},
1007 {"rdata", s_change_sec, 'r'},
1008 {"sdata", s_change_sec, 's'},
1009 {"livereg", s_ignore, 0},
1010 {"abicalls", s_abicalls, 0},
1011 {"cpload", s_cpload, 0},
1012 {"cpsetup", s_cpsetup, 0},
1013 {"cplocal", s_cplocal, 0},
1014 {"cprestore", s_cprestore, 0},
1015 {"cpreturn", s_cpreturn, 0},
1016 {"gpvalue", s_gpvalue, 0},
1017 {"gpword", s_gpword, 0},
1018 {"gpdword", s_gpdword, 0},
1019 {"cpadd", s_cpadd, 0},
1020 {"insn", s_insn, 0},
1022 /* Relatively generic pseudo-ops that happen to be used on MIPS
1024 {"asciiz", stringer, 1},
1025 {"bss", s_change_sec, 'b'},
1027 {"half", s_cons, 1},
1028 {"dword", s_cons, 3},
1029 {"weakext", s_mips_weakext, 0},
1031 /* These pseudo-ops are defined in read.c, but must be overridden
1032 here for one reason or another. */
1033 {"align", s_align, 0},
1034 {"byte", s_cons, 0},
1035 {"data", s_change_sec, 'd'},
1036 {"double", s_float_cons, 'd'},
1037 {"float", s_float_cons, 'f'},
1038 {"globl", s_mips_globl, 0},
1039 {"global", s_mips_globl, 0},
1040 {"hword", s_cons, 1},
1042 {"long", s_cons, 2},
1043 {"octa", s_cons, 4},
1044 {"quad", s_cons, 3},
1045 {"section", s_change_section, 0},
1046 {"short", s_cons, 1},
1047 {"single", s_float_cons, 'f'},
1048 {"stabn", s_mips_stab, 'n'},
1049 {"text", s_change_sec, 't'},
1050 {"word", s_cons, 2},
1052 { "extern", ecoff_directive_extern, 0},
1057 static const pseudo_typeS mips_nonecoff_pseudo_table[] =
1059 /* These pseudo-ops should be defined by the object file format.
1060 However, a.out doesn't support them, so we have versions here. */
1061 {"aent", s_mips_ent, 1},
1062 {"bgnb", s_ignore, 0},
1063 {"end", s_mips_end, 0},
1064 {"endb", s_ignore, 0},
1065 {"ent", s_mips_ent, 0},
1066 {"file", s_mips_file, 0},
1067 {"fmask", s_mips_mask, 'F'},
1068 {"frame", s_mips_frame, 0},
1069 {"loc", s_mips_loc, 0},
1070 {"mask", s_mips_mask, 'R'},
1071 {"verstamp", s_ignore, 0},
1075 extern void pop_insert PARAMS ((const pseudo_typeS *));
1080 pop_insert (mips_pseudo_table);
1081 if (! ECOFF_DEBUGGING)
1082 pop_insert (mips_nonecoff_pseudo_table);
1085 /* Symbols labelling the current insn. */
1087 struct insn_label_list
1089 struct insn_label_list *next;
1093 static struct insn_label_list *insn_labels;
1094 static struct insn_label_list *free_insn_labels;
1096 static void mips_clear_insn_labels PARAMS ((void));
1099 mips_clear_insn_labels ()
1101 register struct insn_label_list **pl;
1103 for (pl = &free_insn_labels; *pl != NULL; pl = &(*pl)->next)
1109 static char *expr_end;
1111 /* Expressions which appear in instructions. These are set by
1114 static expressionS imm_expr;
1115 static expressionS offset_expr;
1117 /* Relocs associated with imm_expr and offset_expr. */
1119 static bfd_reloc_code_real_type imm_reloc[3]
1120 = {BFD_RELOC_UNUSED, BFD_RELOC_UNUSED, BFD_RELOC_UNUSED};
1121 static bfd_reloc_code_real_type offset_reloc[3]
1122 = {BFD_RELOC_UNUSED, BFD_RELOC_UNUSED, BFD_RELOC_UNUSED};
1124 /* These are set by mips16_ip if an explicit extension is used. */
1126 static bfd_boolean mips16_small, mips16_ext;
1129 /* The pdr segment for per procedure frame/regmask info. Not used for
1132 static segT pdr_seg;
1135 /* The default target format to use. */
1138 mips_target_format ()
1140 switch (OUTPUT_FLAVOR)
1142 case bfd_target_aout_flavour:
1143 return target_big_endian ? "a.out-mips-big" : "a.out-mips-little";
1144 case bfd_target_ecoff_flavour:
1145 return target_big_endian ? "ecoff-bigmips" : ECOFF_LITTLE_FORMAT;
1146 case bfd_target_coff_flavour:
1148 case bfd_target_elf_flavour:
1150 /* This is traditional mips. */
1151 return (target_big_endian
1152 ? (HAVE_64BIT_OBJECTS
1153 ? "elf64-tradbigmips"
1155 ? "elf32-ntradbigmips" : "elf32-tradbigmips"))
1156 : (HAVE_64BIT_OBJECTS
1157 ? "elf64-tradlittlemips"
1159 ? "elf32-ntradlittlemips" : "elf32-tradlittlemips")));
1161 return (target_big_endian
1162 ? (HAVE_64BIT_OBJECTS
1165 ? "elf32-nbigmips" : "elf32-bigmips"))
1166 : (HAVE_64BIT_OBJECTS
1167 ? "elf64-littlemips"
1169 ? "elf32-nlittlemips" : "elf32-littlemips")));
1177 /* This function is called once, at assembler startup time. It should
1178 set up all the tables, etc. that the MD part of the assembler will need. */
1183 register const char *retval = NULL;
1187 if (! bfd_set_arch_mach (stdoutput, bfd_arch_mips, mips_arch))
1188 as_warn (_("Could not set architecture and machine"));
1190 op_hash = hash_new ();
1192 for (i = 0; i < NUMOPCODES;)
1194 const char *name = mips_opcodes[i].name;
1196 retval = hash_insert (op_hash, name, (PTR) &mips_opcodes[i]);
1199 fprintf (stderr, _("internal error: can't hash `%s': %s\n"),
1200 mips_opcodes[i].name, retval);
1201 /* Probably a memory allocation problem? Give up now. */
1202 as_fatal (_("Broken assembler. No assembly attempted."));
1206 if (mips_opcodes[i].pinfo != INSN_MACRO)
1208 if (!validate_mips_insn (&mips_opcodes[i]))
1213 while ((i < NUMOPCODES) && !strcmp (mips_opcodes[i].name, name));
1216 mips16_op_hash = hash_new ();
1219 while (i < bfd_mips16_num_opcodes)
1221 const char *name = mips16_opcodes[i].name;
1223 retval = hash_insert (mips16_op_hash, name, (PTR) &mips16_opcodes[i]);
1225 as_fatal (_("internal: can't hash `%s': %s"),
1226 mips16_opcodes[i].name, retval);
1229 if (mips16_opcodes[i].pinfo != INSN_MACRO
1230 && ((mips16_opcodes[i].match & mips16_opcodes[i].mask)
1231 != mips16_opcodes[i].match))
1233 fprintf (stderr, _("internal error: bad mips16 opcode: %s %s\n"),
1234 mips16_opcodes[i].name, mips16_opcodes[i].args);
1239 while (i < bfd_mips16_num_opcodes
1240 && strcmp (mips16_opcodes[i].name, name) == 0);
1244 as_fatal (_("Broken assembler. No assembly attempted."));
1246 /* We add all the general register names to the symbol table. This
1247 helps us detect invalid uses of them. */
1248 for (i = 0; i < 32; i++)
1252 sprintf (buf, "$%d", i);
1253 symbol_table_insert (symbol_new (buf, reg_section, i,
1254 &zero_address_frag));
1256 symbol_table_insert (symbol_new ("$ra", reg_section, RA,
1257 &zero_address_frag));
1258 symbol_table_insert (symbol_new ("$fp", reg_section, FP,
1259 &zero_address_frag));
1260 symbol_table_insert (symbol_new ("$sp", reg_section, SP,
1261 &zero_address_frag));
1262 symbol_table_insert (symbol_new ("$gp", reg_section, GP,
1263 &zero_address_frag));
1264 symbol_table_insert (symbol_new ("$at", reg_section, AT,
1265 &zero_address_frag));
1266 symbol_table_insert (symbol_new ("$kt0", reg_section, KT0,
1267 &zero_address_frag));
1268 symbol_table_insert (symbol_new ("$kt1", reg_section, KT1,
1269 &zero_address_frag));
1270 symbol_table_insert (symbol_new ("$zero", reg_section, ZERO,
1271 &zero_address_frag));
1272 symbol_table_insert (symbol_new ("$pc", reg_section, -1,
1273 &zero_address_frag));
1275 /* If we don't add these register names to the symbol table, they
1276 may end up being added as regular symbols by operand(), and then
1277 make it to the object file as undefined in case they're not
1278 regarded as local symbols. They're local in o32, since `$' is a
1279 local symbol prefix, but not in n32 or n64. */
1280 for (i = 0; i < 8; i++)
1284 sprintf (buf, "$fcc%i", i);
1285 symbol_table_insert (symbol_new (buf, reg_section, -1,
1286 &zero_address_frag));
1289 mips_no_prev_insn (FALSE);
1292 mips_cprmask[0] = 0;
1293 mips_cprmask[1] = 0;
1294 mips_cprmask[2] = 0;
1295 mips_cprmask[3] = 0;
1297 /* set the default alignment for the text section (2**2) */
1298 record_alignment (text_section, 2);
1300 if (USE_GLOBAL_POINTER_OPT)
1301 bfd_set_gp_size (stdoutput, g_switch_value);
1303 if (OUTPUT_FLAVOR == bfd_target_elf_flavour)
1305 /* On a native system, sections must be aligned to 16 byte
1306 boundaries. When configured for an embedded ELF target, we
1308 if (strcmp (TARGET_OS, "elf") != 0)
1310 (void) bfd_set_section_alignment (stdoutput, text_section, 4);
1311 (void) bfd_set_section_alignment (stdoutput, data_section, 4);
1312 (void) bfd_set_section_alignment (stdoutput, bss_section, 4);
1315 /* Create a .reginfo section for register masks and a .mdebug
1316 section for debugging information. */
1324 subseg = now_subseg;
1326 /* The ABI says this section should be loaded so that the
1327 running program can access it. However, we don't load it
1328 if we are configured for an embedded target */
1329 flags = SEC_READONLY | SEC_DATA;
1330 if (strcmp (TARGET_OS, "elf") != 0)
1331 flags |= SEC_ALLOC | SEC_LOAD;
1333 if (mips_abi != N64_ABI)
1335 sec = subseg_new (".reginfo", (subsegT) 0);
1337 bfd_set_section_flags (stdoutput, sec, flags);
1338 bfd_set_section_alignment (stdoutput, sec, HAVE_NEWABI ? 3 : 2);
1341 mips_regmask_frag = frag_more (sizeof (Elf32_External_RegInfo));
1346 /* The 64-bit ABI uses a .MIPS.options section rather than
1347 .reginfo section. */
1348 sec = subseg_new (".MIPS.options", (subsegT) 0);
1349 bfd_set_section_flags (stdoutput, sec, flags);
1350 bfd_set_section_alignment (stdoutput, sec, 3);
1353 /* Set up the option header. */
1355 Elf_Internal_Options opthdr;
1358 opthdr.kind = ODK_REGINFO;
1359 opthdr.size = (sizeof (Elf_External_Options)
1360 + sizeof (Elf64_External_RegInfo));
1363 f = frag_more (sizeof (Elf_External_Options));
1364 bfd_mips_elf_swap_options_out (stdoutput, &opthdr,
1365 (Elf_External_Options *) f);
1367 mips_regmask_frag = frag_more (sizeof (Elf64_External_RegInfo));
1372 if (ECOFF_DEBUGGING)
1374 sec = subseg_new (".mdebug", (subsegT) 0);
1375 (void) bfd_set_section_flags (stdoutput, sec,
1376 SEC_HAS_CONTENTS | SEC_READONLY);
1377 (void) bfd_set_section_alignment (stdoutput, sec, 2);
1380 else if (OUTPUT_FLAVOR == bfd_target_elf_flavour)
1382 pdr_seg = subseg_new (".pdr", (subsegT) 0);
1383 (void) bfd_set_section_flags (stdoutput, pdr_seg,
1384 SEC_READONLY | SEC_RELOC
1386 (void) bfd_set_section_alignment (stdoutput, pdr_seg, 2);
1390 subseg_set (seg, subseg);
1394 if (! ECOFF_DEBUGGING)
1401 if (! ECOFF_DEBUGGING)
1409 struct mips_cl_insn insn;
1410 bfd_reloc_code_real_type unused_reloc[3]
1411 = {BFD_RELOC_UNUSED, BFD_RELOC_UNUSED, BFD_RELOC_UNUSED};
1413 imm_expr.X_op = O_absent;
1414 offset_expr.X_op = O_absent;
1415 imm_reloc[0] = BFD_RELOC_UNUSED;
1416 imm_reloc[1] = BFD_RELOC_UNUSED;
1417 imm_reloc[2] = BFD_RELOC_UNUSED;
1418 offset_reloc[0] = BFD_RELOC_UNUSED;
1419 offset_reloc[1] = BFD_RELOC_UNUSED;
1420 offset_reloc[2] = BFD_RELOC_UNUSED;
1422 if (mips_opts.mips16)
1423 mips16_ip (str, &insn);
1426 mips_ip (str, &insn);
1427 DBG ((_("returned from mips_ip(%s) insn_opcode = 0x%x\n"),
1428 str, insn.insn_opcode));
1433 as_bad ("%s `%s'", insn_error, str);
1437 if (insn.insn_mo->pinfo == INSN_MACRO)
1439 if (mips_opts.mips16)
1440 mips16_macro (&insn);
1446 if (imm_expr.X_op != O_absent)
1447 append_insn (NULL, &insn, &imm_expr, imm_reloc);
1448 else if (offset_expr.X_op != O_absent)
1449 append_insn (NULL, &insn, &offset_expr, offset_reloc);
1451 append_insn (NULL, &insn, NULL, unused_reloc);
1455 /* Return true if the given relocation might need a matching %lo().
1456 Note that R_MIPS_GOT16 relocations only need a matching %lo() when
1457 applied to local symbols. */
1459 static inline bfd_boolean
1460 reloc_needs_lo_p (reloc)
1461 bfd_reloc_code_real_type reloc;
1463 return (reloc == BFD_RELOC_HI16_S
1464 || reloc == BFD_RELOC_MIPS_GOT16);
1467 /* Return true if the given fixup is followed by a matching R_MIPS_LO16
1470 static inline bfd_boolean
1471 fixup_has_matching_lo_p (fixp)
1474 return (fixp->fx_next != NULL
1475 && fixp->fx_next->fx_r_type == BFD_RELOC_LO16
1476 && fixp->fx_addsy == fixp->fx_next->fx_addsy
1477 && fixp->fx_offset == fixp->fx_next->fx_offset);
1480 /* See whether instruction IP reads register REG. CLASS is the type
1484 insn_uses_reg (ip, reg, class)
1485 struct mips_cl_insn *ip;
1487 enum mips_regclass class;
1489 if (class == MIPS16_REG)
1491 assert (mips_opts.mips16);
1492 reg = mips16_to_32_reg_map[reg];
1493 class = MIPS_GR_REG;
1496 /* Don't report on general register ZERO, since it never changes. */
1497 if (class == MIPS_GR_REG && reg == ZERO)
1500 if (class == MIPS_FP_REG)
1502 assert (! mips_opts.mips16);
1503 /* If we are called with either $f0 or $f1, we must check $f0.
1504 This is not optimal, because it will introduce an unnecessary
1505 NOP between "lwc1 $f0" and "swc1 $f1". To fix this we would
1506 need to distinguish reading both $f0 and $f1 or just one of
1507 them. Note that we don't have to check the other way,
1508 because there is no instruction that sets both $f0 and $f1
1509 and requires a delay. */
1510 if ((ip->insn_mo->pinfo & INSN_READ_FPR_S)
1511 && ((((ip->insn_opcode >> OP_SH_FS) & OP_MASK_FS) &~(unsigned)1)
1512 == (reg &~ (unsigned) 1)))
1514 if ((ip->insn_mo->pinfo & INSN_READ_FPR_T)
1515 && ((((ip->insn_opcode >> OP_SH_FT) & OP_MASK_FT) &~(unsigned)1)
1516 == (reg &~ (unsigned) 1)))
1519 else if (! mips_opts.mips16)
1521 if ((ip->insn_mo->pinfo & INSN_READ_GPR_S)
1522 && ((ip->insn_opcode >> OP_SH_RS) & OP_MASK_RS) == reg)
1524 if ((ip->insn_mo->pinfo & INSN_READ_GPR_T)
1525 && ((ip->insn_opcode >> OP_SH_RT) & OP_MASK_RT) == reg)
1530 if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_X)
1531 && (mips16_to_32_reg_map[((ip->insn_opcode >> MIPS16OP_SH_RX)
1532 & MIPS16OP_MASK_RX)]
1535 if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_Y)
1536 && (mips16_to_32_reg_map[((ip->insn_opcode >> MIPS16OP_SH_RY)
1537 & MIPS16OP_MASK_RY)]
1540 if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_Z)
1541 && (mips16_to_32_reg_map[((ip->insn_opcode >> MIPS16OP_SH_MOVE32Z)
1542 & MIPS16OP_MASK_MOVE32Z)]
1545 if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_T) && reg == TREG)
1547 if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_SP) && reg == SP)
1549 if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_31) && reg == RA)
1551 if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_GPR_X)
1552 && ((ip->insn_opcode >> MIPS16OP_SH_REGR32)
1553 & MIPS16OP_MASK_REGR32) == reg)
1560 /* This function returns true if modifying a register requires a
1564 reg_needs_delay (reg)
1567 unsigned long prev_pinfo;
1569 prev_pinfo = prev_insn.insn_mo->pinfo;
1570 if (! mips_opts.noreorder
1571 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
1572 && ((prev_pinfo & INSN_LOAD_COPROC_DELAY)
1573 || (! gpr_interlocks
1574 && (prev_pinfo & INSN_LOAD_MEMORY_DELAY))))
1576 /* A load from a coprocessor or from memory. All load
1577 delays delay the use of general register rt for one
1578 instruction on the r3000. The r6000 and r4000 use
1580 /* Itbl support may require additional care here. */
1581 know (prev_pinfo & INSN_WRITE_GPR_T);
1582 if (reg == ((prev_insn.insn_opcode >> OP_SH_RT) & OP_MASK_RT))
1589 /* Mark instruction labels in mips16 mode. This permits the linker to
1590 handle them specially, such as generating jalx instructions when
1591 needed. We also make them odd for the duration of the assembly, in
1592 order to generate the right sort of code. We will make them even
1593 in the adjust_symtab routine, while leaving them marked. This is
1594 convenient for the debugger and the disassembler. The linker knows
1595 to make them odd again. */
1598 mips16_mark_labels ()
1600 if (mips_opts.mips16)
1602 struct insn_label_list *l;
1605 for (l = insn_labels; l != NULL; l = l->next)
1608 if (OUTPUT_FLAVOR == bfd_target_elf_flavour)
1609 S_SET_OTHER (l->label, STO_MIPS16);
1611 val = S_GET_VALUE (l->label);
1613 S_SET_VALUE (l->label, val + 1);
1618 /* Output an instruction. PLACE is where to put the instruction; if
1619 it is NULL, this uses frag_more to get room. IP is the instruction
1620 information. ADDRESS_EXPR is an operand of the instruction to be
1621 used with RELOC_TYPE. */
1624 append_insn (place, ip, address_expr, reloc_type)
1626 struct mips_cl_insn *ip;
1627 expressionS *address_expr;
1628 bfd_reloc_code_real_type *reloc_type;
1630 register unsigned long prev_pinfo, pinfo;
1635 /* Mark instruction labels in mips16 mode. */
1636 mips16_mark_labels ();
1638 prev_pinfo = prev_insn.insn_mo->pinfo;
1639 pinfo = ip->insn_mo->pinfo;
1641 if (place == NULL && (! mips_opts.noreorder || prev_nop_frag != NULL))
1645 /* If the previous insn required any delay slots, see if we need
1646 to insert a NOP or two. There are eight kinds of possible
1647 hazards, of which an instruction can have at most one type.
1648 (1) a load from memory delay
1649 (2) a load from a coprocessor delay
1650 (3) an unconditional branch delay
1651 (4) a conditional branch delay
1652 (5) a move to coprocessor register delay
1653 (6) a load coprocessor register from memory delay
1654 (7) a coprocessor condition code delay
1655 (8) a HI/LO special register delay
1657 There are a lot of optimizations we could do that we don't.
1658 In particular, we do not, in general, reorder instructions.
1659 If you use gcc with optimization, it will reorder
1660 instructions and generally do much more optimization then we
1661 do here; repeating all that work in the assembler would only
1662 benefit hand written assembly code, and does not seem worth
1665 /* This is how a NOP is emitted. */
1666 #define emit_nop() \
1668 ? md_number_to_chars (frag_more (2), 0x6500, 2) \
1669 : md_number_to_chars (frag_more (4), 0, 4))
1671 /* The previous insn might require a delay slot, depending upon
1672 the contents of the current insn. */
1673 if (! mips_opts.mips16
1674 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
1675 && (((prev_pinfo & INSN_LOAD_COPROC_DELAY)
1676 && ! cop_interlocks)
1677 || (! gpr_interlocks
1678 && (prev_pinfo & INSN_LOAD_MEMORY_DELAY))))
1680 /* A load from a coprocessor or from memory. All load
1681 delays delay the use of general register rt for one
1682 instruction on the r3000. The r6000 and r4000 use
1684 /* Itbl support may require additional care here. */
1685 know (prev_pinfo & INSN_WRITE_GPR_T);
1686 if (mips_optimize == 0
1687 || insn_uses_reg (ip,
1688 ((prev_insn.insn_opcode >> OP_SH_RT)
1693 else if (! mips_opts.mips16
1694 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
1695 && (((prev_pinfo & INSN_COPROC_MOVE_DELAY)
1696 && ! cop_interlocks)
1697 || (mips_opts.isa == ISA_MIPS1
1698 && (prev_pinfo & INSN_COPROC_MEMORY_DELAY))))
1700 /* A generic coprocessor delay. The previous instruction
1701 modified a coprocessor general or control register. If
1702 it modified a control register, we need to avoid any
1703 coprocessor instruction (this is probably not always
1704 required, but it sometimes is). If it modified a general
1705 register, we avoid using that register.
1707 On the r6000 and r4000 loading a coprocessor register
1708 from memory is interlocked, and does not require a delay.
1710 This case is not handled very well. There is no special
1711 knowledge of CP0 handling, and the coprocessors other
1712 than the floating point unit are not distinguished at
1714 /* Itbl support may require additional care here. FIXME!
1715 Need to modify this to include knowledge about
1716 user specified delays! */
1717 if (prev_pinfo & INSN_WRITE_FPR_T)
1719 if (mips_optimize == 0
1720 || insn_uses_reg (ip,
1721 ((prev_insn.insn_opcode >> OP_SH_FT)
1726 else if (prev_pinfo & INSN_WRITE_FPR_S)
1728 if (mips_optimize == 0
1729 || insn_uses_reg (ip,
1730 ((prev_insn.insn_opcode >> OP_SH_FS)
1737 /* We don't know exactly what the previous instruction
1738 does. If the current instruction uses a coprocessor
1739 register, we must insert a NOP. If previous
1740 instruction may set the condition codes, and the
1741 current instruction uses them, we must insert two
1743 /* Itbl support may require additional care here. */
1744 if (mips_optimize == 0
1745 || ((prev_pinfo & INSN_WRITE_COND_CODE)
1746 && (pinfo & INSN_READ_COND_CODE)))
1748 else if (pinfo & INSN_COP)
1752 else if (! mips_opts.mips16
1753 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
1754 && (prev_pinfo & INSN_WRITE_COND_CODE)
1755 && ! cop_interlocks)
1757 /* The previous instruction sets the coprocessor condition
1758 codes, but does not require a general coprocessor delay
1759 (this means it is a floating point comparison
1760 instruction). If this instruction uses the condition
1761 codes, we need to insert a single NOP. */
1762 /* Itbl support may require additional care here. */
1763 if (mips_optimize == 0
1764 || (pinfo & INSN_READ_COND_CODE))
1768 /* If we're fixing up mfhi/mflo for the r7000 and the
1769 previous insn was an mfhi/mflo and the current insn
1770 reads the register that the mfhi/mflo wrote to, then
1773 else if (mips_7000_hilo_fix
1774 && MF_HILO_INSN (prev_pinfo)
1775 && insn_uses_reg (ip, ((prev_insn.insn_opcode >> OP_SH_RD)
1782 /* If we're fixing up mfhi/mflo for the r7000 and the
1783 2nd previous insn was an mfhi/mflo and the current insn
1784 reads the register that the mfhi/mflo wrote to, then
1787 else if (mips_7000_hilo_fix
1788 && MF_HILO_INSN (prev_prev_insn.insn_opcode)
1789 && insn_uses_reg (ip, ((prev_prev_insn.insn_opcode >> OP_SH_RD)
1797 else if (prev_pinfo & INSN_READ_LO)
1799 /* The previous instruction reads the LO register; if the
1800 current instruction writes to the LO register, we must
1801 insert two NOPS. Some newer processors have interlocks.
1802 Also the tx39's multiply instructions can be exectuted
1803 immediatly after a read from HI/LO (without the delay),
1804 though the tx39's divide insns still do require the
1806 if (! (hilo_interlocks
1807 || (mips_tune == CPU_R3900 && (pinfo & INSN_MULT)))
1808 && (mips_optimize == 0
1809 || (pinfo & INSN_WRITE_LO)))
1811 /* Most mips16 branch insns don't have a delay slot.
1812 If a read from LO is immediately followed by a branch
1813 to a write to LO we have a read followed by a write
1814 less than 2 insns away. We assume the target of
1815 a branch might be a write to LO, and insert a nop
1816 between a read and an immediately following branch. */
1817 else if (mips_opts.mips16
1818 && (mips_optimize == 0
1819 || (pinfo & MIPS16_INSN_BRANCH)))
1822 else if (prev_insn.insn_mo->pinfo & INSN_READ_HI)
1824 /* The previous instruction reads the HI register; if the
1825 current instruction writes to the HI register, we must
1826 insert a NOP. Some newer processors have interlocks.
1827 Also the note tx39's multiply above. */
1828 if (! (hilo_interlocks
1829 || (mips_tune == CPU_R3900 && (pinfo & INSN_MULT)))
1830 && (mips_optimize == 0
1831 || (pinfo & INSN_WRITE_HI)))
1833 /* Most mips16 branch insns don't have a delay slot.
1834 If a read from HI is immediately followed by a branch
1835 to a write to HI we have a read followed by a write
1836 less than 2 insns away. We assume the target of
1837 a branch might be a write to HI, and insert a nop
1838 between a read and an immediately following branch. */
1839 else if (mips_opts.mips16
1840 && (mips_optimize == 0
1841 || (pinfo & MIPS16_INSN_BRANCH)))
1845 /* If the previous instruction was in a noreorder section, then
1846 we don't want to insert the nop after all. */
1847 /* Itbl support may require additional care here. */
1848 if (prev_insn_unreordered)
1851 /* There are two cases which require two intervening
1852 instructions: 1) setting the condition codes using a move to
1853 coprocessor instruction which requires a general coprocessor
1854 delay and then reading the condition codes 2) reading the HI
1855 or LO register and then writing to it (except on processors
1856 which have interlocks). If we are not already emitting a NOP
1857 instruction, we must check for these cases compared to the
1858 instruction previous to the previous instruction. */
1859 if ((! mips_opts.mips16
1860 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
1861 && (prev_prev_insn.insn_mo->pinfo & INSN_COPROC_MOVE_DELAY)
1862 && (prev_prev_insn.insn_mo->pinfo & INSN_WRITE_COND_CODE)
1863 && (pinfo & INSN_READ_COND_CODE)
1864 && ! cop_interlocks)
1865 || ((prev_prev_insn.insn_mo->pinfo & INSN_READ_LO)
1866 && (pinfo & INSN_WRITE_LO)
1867 && ! (hilo_interlocks
1868 || (mips_tune == CPU_R3900 && (pinfo & INSN_MULT))))
1869 || ((prev_prev_insn.insn_mo->pinfo & INSN_READ_HI)
1870 && (pinfo & INSN_WRITE_HI)
1871 && ! (hilo_interlocks
1872 || (mips_tune == CPU_R3900 && (pinfo & INSN_MULT)))))
1877 if (prev_prev_insn_unreordered)
1880 if (prev_prev_nop && nops == 0)
1883 if (mips_fix_4122_bugs && prev_insn.insn_mo->name)
1885 /* We're out of bits in pinfo, so we must resort to string
1886 ops here. Shortcuts are selected based on opcodes being
1887 limited to the VR4122 instruction set. */
1889 const char *pn = prev_insn.insn_mo->name;
1890 const char *tn = ip->insn_mo->name;
1891 if (strncmp(pn, "macc", 4) == 0
1892 || strncmp(pn, "dmacc", 5) == 0)
1894 /* Errata 21 - [D]DIV[U] after [D]MACC */
1895 if (strstr (tn, "div"))
1900 /* Errata 23 - Continuous DMULT[U]/DMACC instructions */
1901 if (pn[0] == 'd' /* dmacc */
1902 && (strncmp(tn, "dmult", 5) == 0
1903 || strncmp(tn, "dmacc", 5) == 0))
1908 /* Errata 24 - MT{LO,HI} after [D]MACC */
1909 if (strcmp (tn, "mtlo") == 0
1910 || strcmp (tn, "mthi") == 0)
1916 else if (strncmp(pn, "dmult", 5) == 0
1917 && (strncmp(tn, "dmult", 5) == 0
1918 || strncmp(tn, "dmacc", 5) == 0))
1920 /* Here is the rest of errata 23. */
1923 if (nops < min_nops)
1927 /* If we are being given a nop instruction, don't bother with
1928 one of the nops we would otherwise output. This will only
1929 happen when a nop instruction is used with mips_optimize set
1932 && ! mips_opts.noreorder
1933 && ip->insn_opcode == (unsigned) (mips_opts.mips16 ? 0x6500 : 0))
1936 /* Now emit the right number of NOP instructions. */
1937 if (nops > 0 && ! mips_opts.noreorder)
1940 unsigned long old_frag_offset;
1942 struct insn_label_list *l;
1944 old_frag = frag_now;
1945 old_frag_offset = frag_now_fix ();
1947 for (i = 0; i < nops; i++)
1952 listing_prev_line ();
1953 /* We may be at the start of a variant frag. In case we
1954 are, make sure there is enough space for the frag
1955 after the frags created by listing_prev_line. The
1956 argument to frag_grow here must be at least as large
1957 as the argument to all other calls to frag_grow in
1958 this file. We don't have to worry about being in the
1959 middle of a variant frag, because the variants insert
1960 all needed nop instructions themselves. */
1964 for (l = insn_labels; l != NULL; l = l->next)
1968 assert (S_GET_SEGMENT (l->label) == now_seg);
1969 symbol_set_frag (l->label, frag_now);
1970 val = (valueT) frag_now_fix ();
1971 /* mips16 text labels are stored as odd. */
1972 if (mips_opts.mips16)
1974 S_SET_VALUE (l->label, val);
1977 #ifndef NO_ECOFF_DEBUGGING
1978 if (ECOFF_DEBUGGING)
1979 ecoff_fix_loc (old_frag, old_frag_offset);
1982 else if (prev_nop_frag != NULL)
1984 /* We have a frag holding nops we may be able to remove. If
1985 we don't need any nops, we can decrease the size of
1986 prev_nop_frag by the size of one instruction. If we do
1987 need some nops, we count them in prev_nops_required. */
1988 if (prev_nop_frag_since == 0)
1992 prev_nop_frag->fr_fix -= mips_opts.mips16 ? 2 : 4;
1993 --prev_nop_frag_holds;
1996 prev_nop_frag_required += nops;
2000 if (prev_prev_nop == 0)
2002 prev_nop_frag->fr_fix -= mips_opts.mips16 ? 2 : 4;
2003 --prev_nop_frag_holds;
2006 ++prev_nop_frag_required;
2009 if (prev_nop_frag_holds <= prev_nop_frag_required)
2010 prev_nop_frag = NULL;
2012 ++prev_nop_frag_since;
2014 /* Sanity check: by the time we reach the second instruction
2015 after prev_nop_frag, we should have used up all the nops
2016 one way or another. */
2017 assert (prev_nop_frag_since <= 1 || prev_nop_frag == NULL);
2023 && *reloc_type == BFD_RELOC_16_PCREL_S2
2024 && (pinfo & INSN_UNCOND_BRANCH_DELAY || pinfo & INSN_COND_BRANCH_DELAY
2025 || pinfo & INSN_COND_BRANCH_LIKELY)
2026 && mips_relax_branch
2027 /* Don't try branch relaxation within .set nomacro, or within
2028 .set noat if we use $at for PIC computations. If it turns
2029 out that the branch was out-of-range, we'll get an error. */
2030 && !mips_opts.warn_about_macros
2031 && !(mips_opts.noat && mips_pic != NO_PIC)
2032 && !mips_opts.mips16)
2034 f = frag_var (rs_machine_dependent,
2035 relaxed_branch_length
2037 (pinfo & INSN_UNCOND_BRANCH_DELAY) ? -1
2038 : (pinfo & INSN_COND_BRANCH_LIKELY) ? 1 : 0), 4,
2040 (pinfo & INSN_UNCOND_BRANCH_DELAY,
2041 pinfo & INSN_COND_BRANCH_LIKELY,
2042 pinfo & INSN_WRITE_GPR_31,
2044 address_expr->X_add_symbol,
2045 address_expr->X_add_number,
2047 *reloc_type = BFD_RELOC_UNUSED;
2049 else if (*reloc_type > BFD_RELOC_UNUSED)
2051 /* We need to set up a variant frag. */
2052 assert (mips_opts.mips16 && address_expr != NULL);
2053 f = frag_var (rs_machine_dependent, 4, 0,
2054 RELAX_MIPS16_ENCODE (*reloc_type - BFD_RELOC_UNUSED,
2055 mips16_small, mips16_ext,
2057 & INSN_UNCOND_BRANCH_DELAY),
2058 (*prev_insn_reloc_type
2059 == BFD_RELOC_MIPS16_JMP)),
2060 make_expr_symbol (address_expr), 0, NULL);
2062 else if (place != NULL)
2064 else if (mips_opts.mips16
2066 && *reloc_type != BFD_RELOC_MIPS16_JMP)
2068 /* Make sure there is enough room to swap this instruction with
2069 a following jump instruction. */
2075 if (mips_opts.mips16
2076 && mips_opts.noreorder
2077 && (prev_pinfo & INSN_UNCOND_BRANCH_DELAY) != 0)
2078 as_warn (_("extended instruction in delay slot"));
2083 fixp[0] = fixp[1] = fixp[2] = NULL;
2084 if (address_expr != NULL && *reloc_type < BFD_RELOC_UNUSED)
2086 if (address_expr->X_op == O_constant)
2090 switch (*reloc_type)
2093 ip->insn_opcode |= address_expr->X_add_number;
2096 case BFD_RELOC_MIPS_HIGHEST:
2097 tmp = (address_expr->X_add_number + 0x800080008000) >> 16;
2099 ip->insn_opcode |= (tmp >> 16) & 0xffff;
2102 case BFD_RELOC_MIPS_HIGHER:
2103 tmp = (address_expr->X_add_number + 0x80008000) >> 16;
2104 ip->insn_opcode |= (tmp >> 16) & 0xffff;
2107 case BFD_RELOC_HI16_S:
2108 ip->insn_opcode |= ((address_expr->X_add_number + 0x8000)
2112 case BFD_RELOC_HI16:
2113 ip->insn_opcode |= (address_expr->X_add_number >> 16) & 0xffff;
2116 case BFD_RELOC_LO16:
2117 case BFD_RELOC_MIPS_GOT_DISP:
2118 ip->insn_opcode |= address_expr->X_add_number & 0xffff;
2121 case BFD_RELOC_MIPS_JMP:
2122 if ((address_expr->X_add_number & 3) != 0)
2123 as_bad (_("jump to misaligned address (0x%lx)"),
2124 (unsigned long) address_expr->X_add_number);
2125 if (address_expr->X_add_number & ~0xfffffff)
2126 as_bad (_("jump address range overflow (0x%lx)"),
2127 (unsigned long) address_expr->X_add_number);
2128 ip->insn_opcode |= (address_expr->X_add_number >> 2) & 0x3ffffff;
2131 case BFD_RELOC_MIPS16_JMP:
2132 if ((address_expr->X_add_number & 3) != 0)
2133 as_bad (_("jump to misaligned address (0x%lx)"),
2134 (unsigned long) address_expr->X_add_number);
2135 if (address_expr->X_add_number & ~0xfffffff)
2136 as_bad (_("jump address range overflow (0x%lx)"),
2137 (unsigned long) address_expr->X_add_number);
2139 (((address_expr->X_add_number & 0x7c0000) << 3)
2140 | ((address_expr->X_add_number & 0xf800000) >> 7)
2141 | ((address_expr->X_add_number & 0x3fffc) >> 2));
2144 case BFD_RELOC_16_PCREL_S2:
2154 /* Don't generate a reloc if we are writing into a variant frag. */
2157 fixp[0] = fix_new_exp (frag_now, f - frag_now->fr_literal, 4,
2159 *reloc_type == BFD_RELOC_16_PCREL_S2,
2162 /* These relocations can have an addend that won't fit in
2163 4 octets for 64bit assembly. */
2164 if (HAVE_64BIT_GPRS &&
2165 (*reloc_type == BFD_RELOC_16
2166 || *reloc_type == BFD_RELOC_32
2167 || *reloc_type == BFD_RELOC_MIPS_JMP
2168 || *reloc_type == BFD_RELOC_HI16_S
2169 || *reloc_type == BFD_RELOC_LO16
2170 || *reloc_type == BFD_RELOC_GPREL16
2171 || *reloc_type == BFD_RELOC_MIPS_LITERAL
2172 || *reloc_type == BFD_RELOC_GPREL32
2173 || *reloc_type == BFD_RELOC_64
2174 || *reloc_type == BFD_RELOC_CTOR
2175 || *reloc_type == BFD_RELOC_MIPS_SUB
2176 || *reloc_type == BFD_RELOC_MIPS_HIGHEST
2177 || *reloc_type == BFD_RELOC_MIPS_HIGHER
2178 || *reloc_type == BFD_RELOC_MIPS_SCN_DISP
2179 || *reloc_type == BFD_RELOC_MIPS_REL16
2180 || *reloc_type == BFD_RELOC_MIPS_RELGOT))
2181 fixp[0]->fx_no_overflow = 1;
2183 if (reloc_needs_lo_p (*reloc_type))
2185 struct mips_hi_fixup *hi_fixup;
2187 /* Reuse the last entry if it already has a matching %lo. */
2188 hi_fixup = mips_hi_fixup_list;
2190 || !fixup_has_matching_lo_p (hi_fixup->fixp))
2192 hi_fixup = ((struct mips_hi_fixup *)
2193 xmalloc (sizeof (struct mips_hi_fixup)));
2194 hi_fixup->next = mips_hi_fixup_list;
2195 mips_hi_fixup_list = hi_fixup;
2197 hi_fixup->fixp = fixp[0];
2198 hi_fixup->seg = now_seg;
2201 if (reloc_type[1] != BFD_RELOC_UNUSED)
2203 /* FIXME: This symbol can be one of
2204 RSS_UNDEF, RSS_GP, RSS_GP0, RSS_LOC. */
2205 address_expr->X_op = O_absent;
2206 address_expr->X_add_symbol = 0;
2207 address_expr->X_add_number = 0;
2209 fixp[1] = fix_new_exp (frag_now, f - frag_now->fr_literal,
2210 4, address_expr, FALSE,
2213 /* These relocations can have an addend that won't fit in
2214 4 octets for 64bit assembly. */
2215 if (HAVE_64BIT_GPRS &&
2216 (*reloc_type == BFD_RELOC_16
2217 || *reloc_type == BFD_RELOC_32
2218 || *reloc_type == BFD_RELOC_MIPS_JMP
2219 || *reloc_type == BFD_RELOC_HI16_S
2220 || *reloc_type == BFD_RELOC_LO16
2221 || *reloc_type == BFD_RELOC_GPREL16
2222 || *reloc_type == BFD_RELOC_MIPS_LITERAL
2223 || *reloc_type == BFD_RELOC_GPREL32
2224 || *reloc_type == BFD_RELOC_64
2225 || *reloc_type == BFD_RELOC_CTOR
2226 || *reloc_type == BFD_RELOC_MIPS_SUB
2227 || *reloc_type == BFD_RELOC_MIPS_HIGHEST
2228 || *reloc_type == BFD_RELOC_MIPS_HIGHER
2229 || *reloc_type == BFD_RELOC_MIPS_SCN_DISP
2230 || *reloc_type == BFD_RELOC_MIPS_REL16
2231 || *reloc_type == BFD_RELOC_MIPS_RELGOT))
2232 fixp[1]->fx_no_overflow = 1;
2234 if (reloc_type[2] != BFD_RELOC_UNUSED)
2236 address_expr->X_op = O_absent;
2237 address_expr->X_add_symbol = 0;
2238 address_expr->X_add_number = 0;
2240 fixp[2] = fix_new_exp (frag_now,
2241 f - frag_now->fr_literal, 4,
2242 address_expr, FALSE,
2245 /* These relocations can have an addend that won't fit in
2246 4 octets for 64bit assembly. */
2247 if (HAVE_64BIT_GPRS &&
2248 (*reloc_type == BFD_RELOC_16
2249 || *reloc_type == BFD_RELOC_32
2250 || *reloc_type == BFD_RELOC_MIPS_JMP
2251 || *reloc_type == BFD_RELOC_HI16_S
2252 || *reloc_type == BFD_RELOC_LO16
2253 || *reloc_type == BFD_RELOC_GPREL16
2254 || *reloc_type == BFD_RELOC_MIPS_LITERAL
2255 || *reloc_type == BFD_RELOC_GPREL32
2256 || *reloc_type == BFD_RELOC_64
2257 || *reloc_type == BFD_RELOC_CTOR
2258 || *reloc_type == BFD_RELOC_MIPS_SUB
2259 || *reloc_type == BFD_RELOC_MIPS_HIGHEST
2260 || *reloc_type == BFD_RELOC_MIPS_HIGHER
2261 || *reloc_type == BFD_RELOC_MIPS_SCN_DISP
2262 || *reloc_type == BFD_RELOC_MIPS_REL16
2263 || *reloc_type == BFD_RELOC_MIPS_RELGOT))
2264 fixp[2]->fx_no_overflow = 1;
2271 if (! mips_opts.mips16)
2273 md_number_to_chars (f, ip->insn_opcode, 4);
2275 dwarf2_emit_insn (4);
2278 else if (*reloc_type == BFD_RELOC_MIPS16_JMP)
2280 md_number_to_chars (f, ip->insn_opcode >> 16, 2);
2281 md_number_to_chars (f + 2, ip->insn_opcode & 0xffff, 2);
2283 dwarf2_emit_insn (4);
2290 md_number_to_chars (f, 0xf000 | ip->extend, 2);
2293 md_number_to_chars (f, ip->insn_opcode, 2);
2295 dwarf2_emit_insn (ip->use_extend ? 4 : 2);
2299 /* Update the register mask information. */
2300 if (! mips_opts.mips16)
2302 if (pinfo & INSN_WRITE_GPR_D)
2303 mips_gprmask |= 1 << ((ip->insn_opcode >> OP_SH_RD) & OP_MASK_RD);
2304 if ((pinfo & (INSN_WRITE_GPR_T | INSN_READ_GPR_T)) != 0)
2305 mips_gprmask |= 1 << ((ip->insn_opcode >> OP_SH_RT) & OP_MASK_RT);
2306 if (pinfo & INSN_READ_GPR_S)
2307 mips_gprmask |= 1 << ((ip->insn_opcode >> OP_SH_RS) & OP_MASK_RS);
2308 if (pinfo & INSN_WRITE_GPR_31)
2309 mips_gprmask |= 1 << RA;
2310 if (pinfo & INSN_WRITE_FPR_D)
2311 mips_cprmask[1] |= 1 << ((ip->insn_opcode >> OP_SH_FD) & OP_MASK_FD);
2312 if ((pinfo & (INSN_WRITE_FPR_S | INSN_READ_FPR_S)) != 0)
2313 mips_cprmask[1] |= 1 << ((ip->insn_opcode >> OP_SH_FS) & OP_MASK_FS);
2314 if ((pinfo & (INSN_WRITE_FPR_T | INSN_READ_FPR_T)) != 0)
2315 mips_cprmask[1] |= 1 << ((ip->insn_opcode >> OP_SH_FT) & OP_MASK_FT);
2316 if ((pinfo & INSN_READ_FPR_R) != 0)
2317 mips_cprmask[1] |= 1 << ((ip->insn_opcode >> OP_SH_FR) & OP_MASK_FR);
2318 if (pinfo & INSN_COP)
2320 /* We don't keep enough information to sort these cases out.
2321 The itbl support does keep this information however, although
2322 we currently don't support itbl fprmats as part of the cop
2323 instruction. May want to add this support in the future. */
2325 /* Never set the bit for $0, which is always zero. */
2326 mips_gprmask &= ~1 << 0;
2330 if (pinfo & (MIPS16_INSN_WRITE_X | MIPS16_INSN_READ_X))
2331 mips_gprmask |= 1 << ((ip->insn_opcode >> MIPS16OP_SH_RX)
2332 & MIPS16OP_MASK_RX);
2333 if (pinfo & (MIPS16_INSN_WRITE_Y | MIPS16_INSN_READ_Y))
2334 mips_gprmask |= 1 << ((ip->insn_opcode >> MIPS16OP_SH_RY)
2335 & MIPS16OP_MASK_RY);
2336 if (pinfo & MIPS16_INSN_WRITE_Z)
2337 mips_gprmask |= 1 << ((ip->insn_opcode >> MIPS16OP_SH_RZ)
2338 & MIPS16OP_MASK_RZ);
2339 if (pinfo & (MIPS16_INSN_WRITE_T | MIPS16_INSN_READ_T))
2340 mips_gprmask |= 1 << TREG;
2341 if (pinfo & (MIPS16_INSN_WRITE_SP | MIPS16_INSN_READ_SP))
2342 mips_gprmask |= 1 << SP;
2343 if (pinfo & (MIPS16_INSN_WRITE_31 | MIPS16_INSN_READ_31))
2344 mips_gprmask |= 1 << RA;
2345 if (pinfo & MIPS16_INSN_WRITE_GPR_Y)
2346 mips_gprmask |= 1 << MIPS16OP_EXTRACT_REG32R (ip->insn_opcode);
2347 if (pinfo & MIPS16_INSN_READ_Z)
2348 mips_gprmask |= 1 << ((ip->insn_opcode >> MIPS16OP_SH_MOVE32Z)
2349 & MIPS16OP_MASK_MOVE32Z);
2350 if (pinfo & MIPS16_INSN_READ_GPR_X)
2351 mips_gprmask |= 1 << ((ip->insn_opcode >> MIPS16OP_SH_REGR32)
2352 & MIPS16OP_MASK_REGR32);
2355 if (place == NULL && ! mips_opts.noreorder)
2357 /* Filling the branch delay slot is more complex. We try to
2358 switch the branch with the previous instruction, which we can
2359 do if the previous instruction does not set up a condition
2360 that the branch tests and if the branch is not itself the
2361 target of any branch. */
2362 if ((pinfo & INSN_UNCOND_BRANCH_DELAY)
2363 || (pinfo & INSN_COND_BRANCH_DELAY))
2365 if (mips_optimize < 2
2366 /* If we have seen .set volatile or .set nomove, don't
2368 || mips_opts.nomove != 0
2369 /* If we had to emit any NOP instructions, then we
2370 already know we can not swap. */
2372 /* If we don't even know the previous insn, we can not
2374 || ! prev_insn_valid
2375 /* If the previous insn is already in a branch delay
2376 slot, then we can not swap. */
2377 || prev_insn_is_delay_slot
2378 /* If the previous previous insn was in a .set
2379 noreorder, we can't swap. Actually, the MIPS
2380 assembler will swap in this situation. However, gcc
2381 configured -with-gnu-as will generate code like
2387 in which we can not swap the bne and INSN. If gcc is
2388 not configured -with-gnu-as, it does not output the
2389 .set pseudo-ops. We don't have to check
2390 prev_insn_unreordered, because prev_insn_valid will
2391 be 0 in that case. We don't want to use
2392 prev_prev_insn_valid, because we do want to be able
2393 to swap at the start of a function. */
2394 || prev_prev_insn_unreordered
2395 /* If the branch is itself the target of a branch, we
2396 can not swap. We cheat on this; all we check for is
2397 whether there is a label on this instruction. If
2398 there are any branches to anything other than a
2399 label, users must use .set noreorder. */
2400 || insn_labels != NULL
2401 /* If the previous instruction is in a variant frag, we
2402 can not do the swap. This does not apply to the
2403 mips16, which uses variant frags for different
2405 || (! mips_opts.mips16
2406 && prev_insn_frag->fr_type == rs_machine_dependent)
2407 /* If the branch reads the condition codes, we don't
2408 even try to swap, because in the sequence
2413 we can not swap, and I don't feel like handling that
2415 || (! mips_opts.mips16
2416 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
2417 && (pinfo & INSN_READ_COND_CODE))
2418 /* We can not swap with an instruction that requires a
2419 delay slot, becase the target of the branch might
2420 interfere with that instruction. */
2421 || (! mips_opts.mips16
2422 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
2424 /* Itbl support may require additional care here. */
2425 & (INSN_LOAD_COPROC_DELAY
2426 | INSN_COPROC_MOVE_DELAY
2427 | INSN_WRITE_COND_CODE)))
2428 || (! (hilo_interlocks
2429 || (mips_tune == CPU_R3900 && (pinfo & INSN_MULT)))
2433 || (! mips_opts.mips16
2435 && (prev_pinfo & INSN_LOAD_MEMORY_DELAY))
2436 || (! mips_opts.mips16
2437 && mips_opts.isa == ISA_MIPS1
2438 /* Itbl support may require additional care here. */
2439 && (prev_pinfo & INSN_COPROC_MEMORY_DELAY))
2440 /* We can not swap with a branch instruction. */
2442 & (INSN_UNCOND_BRANCH_DELAY
2443 | INSN_COND_BRANCH_DELAY
2444 | INSN_COND_BRANCH_LIKELY))
2445 /* We do not swap with a trap instruction, since it
2446 complicates trap handlers to have the trap
2447 instruction be in a delay slot. */
2448 || (prev_pinfo & INSN_TRAP)
2449 /* If the branch reads a register that the previous
2450 instruction sets, we can not swap. */
2451 || (! mips_opts.mips16
2452 && (prev_pinfo & INSN_WRITE_GPR_T)
2453 && insn_uses_reg (ip,
2454 ((prev_insn.insn_opcode >> OP_SH_RT)
2457 || (! mips_opts.mips16
2458 && (prev_pinfo & INSN_WRITE_GPR_D)
2459 && insn_uses_reg (ip,
2460 ((prev_insn.insn_opcode >> OP_SH_RD)
2463 || (mips_opts.mips16
2464 && (((prev_pinfo & MIPS16_INSN_WRITE_X)
2465 && insn_uses_reg (ip,
2466 ((prev_insn.insn_opcode
2468 & MIPS16OP_MASK_RX),
2470 || ((prev_pinfo & MIPS16_INSN_WRITE_Y)
2471 && insn_uses_reg (ip,
2472 ((prev_insn.insn_opcode
2474 & MIPS16OP_MASK_RY),
2476 || ((prev_pinfo & MIPS16_INSN_WRITE_Z)
2477 && insn_uses_reg (ip,
2478 ((prev_insn.insn_opcode
2480 & MIPS16OP_MASK_RZ),
2482 || ((prev_pinfo & MIPS16_INSN_WRITE_T)
2483 && insn_uses_reg (ip, TREG, MIPS_GR_REG))
2484 || ((prev_pinfo & MIPS16_INSN_WRITE_31)
2485 && insn_uses_reg (ip, RA, MIPS_GR_REG))
2486 || ((prev_pinfo & MIPS16_INSN_WRITE_GPR_Y)
2487 && insn_uses_reg (ip,
2488 MIPS16OP_EXTRACT_REG32R (prev_insn.
2491 /* If the branch writes a register that the previous
2492 instruction sets, we can not swap (we know that
2493 branches write only to RD or to $31). */
2494 || (! mips_opts.mips16
2495 && (prev_pinfo & INSN_WRITE_GPR_T)
2496 && (((pinfo & INSN_WRITE_GPR_D)
2497 && (((prev_insn.insn_opcode >> OP_SH_RT) & OP_MASK_RT)
2498 == ((ip->insn_opcode >> OP_SH_RD) & OP_MASK_RD)))
2499 || ((pinfo & INSN_WRITE_GPR_31)
2500 && (((prev_insn.insn_opcode >> OP_SH_RT)
2503 || (! mips_opts.mips16
2504 && (prev_pinfo & INSN_WRITE_GPR_D)
2505 && (((pinfo & INSN_WRITE_GPR_D)
2506 && (((prev_insn.insn_opcode >> OP_SH_RD) & OP_MASK_RD)
2507 == ((ip->insn_opcode >> OP_SH_RD) & OP_MASK_RD)))
2508 || ((pinfo & INSN_WRITE_GPR_31)
2509 && (((prev_insn.insn_opcode >> OP_SH_RD)
2512 || (mips_opts.mips16
2513 && (pinfo & MIPS16_INSN_WRITE_31)
2514 && ((prev_pinfo & MIPS16_INSN_WRITE_31)
2515 || ((prev_pinfo & MIPS16_INSN_WRITE_GPR_Y)
2516 && (MIPS16OP_EXTRACT_REG32R (prev_insn.insn_opcode)
2518 /* If the branch writes a register that the previous
2519 instruction reads, we can not swap (we know that
2520 branches only write to RD or to $31). */
2521 || (! mips_opts.mips16
2522 && (pinfo & INSN_WRITE_GPR_D)
2523 && insn_uses_reg (&prev_insn,
2524 ((ip->insn_opcode >> OP_SH_RD)
2527 || (! mips_opts.mips16
2528 && (pinfo & INSN_WRITE_GPR_31)
2529 && insn_uses_reg (&prev_insn, RA, MIPS_GR_REG))
2530 || (mips_opts.mips16
2531 && (pinfo & MIPS16_INSN_WRITE_31)
2532 && insn_uses_reg (&prev_insn, RA, MIPS_GR_REG))
2533 /* If we are generating embedded PIC code, the branch
2534 might be expanded into a sequence which uses $at, so
2535 we can't swap with an instruction which reads it. */
2536 || (mips_pic == EMBEDDED_PIC
2537 && insn_uses_reg (&prev_insn, AT, MIPS_GR_REG))
2538 /* If the previous previous instruction has a load
2539 delay, and sets a register that the branch reads, we
2541 || (! mips_opts.mips16
2542 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
2543 /* Itbl support may require additional care here. */
2544 && ((prev_prev_insn.insn_mo->pinfo & INSN_LOAD_COPROC_DELAY)
2545 || (! gpr_interlocks
2546 && (prev_prev_insn.insn_mo->pinfo
2547 & INSN_LOAD_MEMORY_DELAY)))
2548 && insn_uses_reg (ip,
2549 ((prev_prev_insn.insn_opcode >> OP_SH_RT)
2552 /* If one instruction sets a condition code and the
2553 other one uses a condition code, we can not swap. */
2554 || ((pinfo & INSN_READ_COND_CODE)
2555 && (prev_pinfo & INSN_WRITE_COND_CODE))
2556 || ((pinfo & INSN_WRITE_COND_CODE)
2557 && (prev_pinfo & INSN_READ_COND_CODE))
2558 /* If the previous instruction uses the PC, we can not
2560 || (mips_opts.mips16
2561 && (prev_pinfo & MIPS16_INSN_READ_PC))
2562 /* If the previous instruction was extended, we can not
2564 || (mips_opts.mips16 && prev_insn_extended)
2565 /* If the previous instruction had a fixup in mips16
2566 mode, we can not swap. This normally means that the
2567 previous instruction was a 4 byte branch anyhow. */
2568 || (mips_opts.mips16 && prev_insn_fixp[0])
2569 /* If the previous instruction is a sync, sync.l, or
2570 sync.p, we can not swap. */
2571 || (prev_pinfo & INSN_SYNC))
2573 /* We could do even better for unconditional branches to
2574 portions of this object file; we could pick up the
2575 instruction at the destination, put it in the delay
2576 slot, and bump the destination address. */
2578 /* Update the previous insn information. */
2579 prev_prev_insn = *ip;
2580 prev_insn.insn_mo = &dummy_opcode;
2584 /* It looks like we can actually do the swap. */
2585 if (! mips_opts.mips16)
2590 prev_f = prev_insn_frag->fr_literal + prev_insn_where;
2591 memcpy (temp, prev_f, 4);
2592 memcpy (prev_f, f, 4);
2593 memcpy (f, temp, 4);
2594 if (prev_insn_fixp[0])
2596 prev_insn_fixp[0]->fx_frag = frag_now;
2597 prev_insn_fixp[0]->fx_where = f - frag_now->fr_literal;
2599 if (prev_insn_fixp[1])
2601 prev_insn_fixp[1]->fx_frag = frag_now;
2602 prev_insn_fixp[1]->fx_where = f - frag_now->fr_literal;
2604 if (prev_insn_fixp[2])
2606 prev_insn_fixp[2]->fx_frag = frag_now;
2607 prev_insn_fixp[2]->fx_where = f - frag_now->fr_literal;
2611 fixp[0]->fx_frag = prev_insn_frag;
2612 fixp[0]->fx_where = prev_insn_where;
2616 fixp[1]->fx_frag = prev_insn_frag;
2617 fixp[1]->fx_where = prev_insn_where;
2621 fixp[2]->fx_frag = prev_insn_frag;
2622 fixp[2]->fx_where = prev_insn_where;
2630 assert (prev_insn_fixp[0] == NULL);
2631 assert (prev_insn_fixp[1] == NULL);
2632 assert (prev_insn_fixp[2] == NULL);
2633 prev_f = prev_insn_frag->fr_literal + prev_insn_where;
2634 memcpy (temp, prev_f, 2);
2635 memcpy (prev_f, f, 2);
2636 if (*reloc_type != BFD_RELOC_MIPS16_JMP)
2638 assert (*reloc_type == BFD_RELOC_UNUSED);
2639 memcpy (f, temp, 2);
2643 memcpy (f, f + 2, 2);
2644 memcpy (f + 2, temp, 2);
2648 fixp[0]->fx_frag = prev_insn_frag;
2649 fixp[0]->fx_where = prev_insn_where;
2653 fixp[1]->fx_frag = prev_insn_frag;
2654 fixp[1]->fx_where = prev_insn_where;
2658 fixp[2]->fx_frag = prev_insn_frag;
2659 fixp[2]->fx_where = prev_insn_where;
2663 /* Update the previous insn information; leave prev_insn
2665 prev_prev_insn = *ip;
2667 prev_insn_is_delay_slot = 1;
2669 /* If that was an unconditional branch, forget the previous
2670 insn information. */
2671 if (pinfo & INSN_UNCOND_BRANCH_DELAY)
2673 prev_prev_insn.insn_mo = &dummy_opcode;
2674 prev_insn.insn_mo = &dummy_opcode;
2677 prev_insn_fixp[0] = NULL;
2678 prev_insn_fixp[1] = NULL;
2679 prev_insn_fixp[2] = NULL;
2680 prev_insn_reloc_type[0] = BFD_RELOC_UNUSED;
2681 prev_insn_reloc_type[1] = BFD_RELOC_UNUSED;
2682 prev_insn_reloc_type[2] = BFD_RELOC_UNUSED;
2683 prev_insn_extended = 0;
2685 else if (pinfo & INSN_COND_BRANCH_LIKELY)
2687 /* We don't yet optimize a branch likely. What we should do
2688 is look at the target, copy the instruction found there
2689 into the delay slot, and increment the branch to jump to
2690 the next instruction. */
2692 /* Update the previous insn information. */
2693 prev_prev_insn = *ip;
2694 prev_insn.insn_mo = &dummy_opcode;
2695 prev_insn_fixp[0] = NULL;
2696 prev_insn_fixp[1] = NULL;
2697 prev_insn_fixp[2] = NULL;
2698 prev_insn_reloc_type[0] = BFD_RELOC_UNUSED;
2699 prev_insn_reloc_type[1] = BFD_RELOC_UNUSED;
2700 prev_insn_reloc_type[2] = BFD_RELOC_UNUSED;
2701 prev_insn_extended = 0;
2705 /* Update the previous insn information. */
2707 prev_prev_insn.insn_mo = &dummy_opcode;
2709 prev_prev_insn = prev_insn;
2712 /* Any time we see a branch, we always fill the delay slot
2713 immediately; since this insn is not a branch, we know it
2714 is not in a delay slot. */
2715 prev_insn_is_delay_slot = 0;
2717 prev_insn_fixp[0] = fixp[0];
2718 prev_insn_fixp[1] = fixp[1];
2719 prev_insn_fixp[2] = fixp[2];
2720 prev_insn_reloc_type[0] = reloc_type[0];
2721 prev_insn_reloc_type[1] = reloc_type[1];
2722 prev_insn_reloc_type[2] = reloc_type[2];
2723 if (mips_opts.mips16)
2724 prev_insn_extended = (ip->use_extend
2725 || *reloc_type > BFD_RELOC_UNUSED);
2728 prev_prev_insn_unreordered = prev_insn_unreordered;
2729 prev_insn_unreordered = 0;
2730 prev_insn_frag = frag_now;
2731 prev_insn_where = f - frag_now->fr_literal;
2732 prev_insn_valid = 1;
2734 else if (place == NULL)
2736 /* We need to record a bit of information even when we are not
2737 reordering, in order to determine the base address for mips16
2738 PC relative relocs. */
2739 prev_prev_insn = prev_insn;
2741 prev_insn_reloc_type[0] = reloc_type[0];
2742 prev_insn_reloc_type[1] = reloc_type[1];
2743 prev_insn_reloc_type[2] = reloc_type[2];
2744 prev_prev_insn_unreordered = prev_insn_unreordered;
2745 prev_insn_unreordered = 1;
2748 /* We just output an insn, so the next one doesn't have a label. */
2749 mips_clear_insn_labels ();
2752 /* This function forgets that there was any previous instruction or
2753 label. If PRESERVE is non-zero, it remembers enough information to
2754 know whether nops are needed before a noreorder section. */
2757 mips_no_prev_insn (preserve)
2762 prev_insn.insn_mo = &dummy_opcode;
2763 prev_prev_insn.insn_mo = &dummy_opcode;
2764 prev_nop_frag = NULL;
2765 prev_nop_frag_holds = 0;
2766 prev_nop_frag_required = 0;
2767 prev_nop_frag_since = 0;
2769 prev_insn_valid = 0;
2770 prev_insn_is_delay_slot = 0;
2771 prev_insn_unreordered = 0;
2772 prev_insn_extended = 0;
2773 prev_insn_reloc_type[0] = BFD_RELOC_UNUSED;
2774 prev_insn_reloc_type[1] = BFD_RELOC_UNUSED;
2775 prev_insn_reloc_type[2] = BFD_RELOC_UNUSED;
2776 prev_prev_insn_unreordered = 0;
2777 mips_clear_insn_labels ();
2780 /* This function must be called whenever we turn on noreorder or emit
2781 something other than instructions. It inserts any NOPS which might
2782 be needed by the previous instruction, and clears the information
2783 kept for the previous instructions. The INSNS parameter is true if
2784 instructions are to follow. */
2787 mips_emit_delays (insns)
2790 if (! mips_opts.noreorder)
2795 if ((! mips_opts.mips16
2796 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
2797 && (! cop_interlocks
2798 && (prev_insn.insn_mo->pinfo
2799 & (INSN_LOAD_COPROC_DELAY
2800 | INSN_COPROC_MOVE_DELAY
2801 | INSN_WRITE_COND_CODE))))
2802 || (! hilo_interlocks
2803 && (prev_insn.insn_mo->pinfo
2806 || (! mips_opts.mips16
2808 && (prev_insn.insn_mo->pinfo
2809 & INSN_LOAD_MEMORY_DELAY))
2810 || (! mips_opts.mips16
2811 && mips_opts.isa == ISA_MIPS1
2812 && (prev_insn.insn_mo->pinfo
2813 & INSN_COPROC_MEMORY_DELAY)))
2815 /* Itbl support may require additional care here. */
2817 if ((! mips_opts.mips16
2818 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
2819 && (! cop_interlocks
2820 && prev_insn.insn_mo->pinfo & INSN_WRITE_COND_CODE))
2821 || (! hilo_interlocks
2822 && ((prev_insn.insn_mo->pinfo & INSN_READ_HI)
2823 || (prev_insn.insn_mo->pinfo & INSN_READ_LO))))
2826 if (prev_insn_unreordered)
2829 else if ((! mips_opts.mips16
2830 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
2831 && (! cop_interlocks
2832 && prev_prev_insn.insn_mo->pinfo & INSN_WRITE_COND_CODE))
2833 || (! hilo_interlocks
2834 && ((prev_prev_insn.insn_mo->pinfo & INSN_READ_HI)
2835 || (prev_prev_insn.insn_mo->pinfo & INSN_READ_LO))))
2837 /* Itbl support may require additional care here. */
2838 if (! prev_prev_insn_unreordered)
2842 if (mips_fix_4122_bugs && prev_insn.insn_mo->name)
2845 const char *pn = prev_insn.insn_mo->name;
2846 if (strncmp(pn, "macc", 4) == 0
2847 || strncmp(pn, "dmacc", 5) == 0
2848 || strncmp(pn, "dmult", 5) == 0)
2852 if (nops < min_nops)
2858 struct insn_label_list *l;
2862 /* Record the frag which holds the nop instructions, so
2863 that we can remove them if we don't need them. */
2864 frag_grow (mips_opts.mips16 ? nops * 2 : nops * 4);
2865 prev_nop_frag = frag_now;
2866 prev_nop_frag_holds = nops;
2867 prev_nop_frag_required = 0;
2868 prev_nop_frag_since = 0;
2871 for (; nops > 0; --nops)
2876 /* Move on to a new frag, so that it is safe to simply
2877 decrease the size of prev_nop_frag. */
2878 frag_wane (frag_now);
2882 for (l = insn_labels; l != NULL; l = l->next)
2886 assert (S_GET_SEGMENT (l->label) == now_seg);
2887 symbol_set_frag (l->label, frag_now);
2888 val = (valueT) frag_now_fix ();
2889 /* mips16 text labels are stored as odd. */
2890 if (mips_opts.mips16)
2892 S_SET_VALUE (l->label, val);
2897 /* Mark instruction labels in mips16 mode. */
2899 mips16_mark_labels ();
2901 mips_no_prev_insn (insns);
2904 /* Build an instruction created by a macro expansion. This is passed
2905 a pointer to the count of instructions created so far, an
2906 expression, the name of the instruction to build, an operand format
2907 string, and corresponding arguments. */
2911 macro_build (char *place,
2919 macro_build (place, counter, ep, name, fmt, va_alist)
2928 struct mips_cl_insn insn;
2929 bfd_reloc_code_real_type r[3];
2933 va_start (args, fmt);
2939 * If the macro is about to expand into a second instruction,
2940 * print a warning if needed. We need to pass ip as a parameter
2941 * to generate a better warning message here...
2943 if (mips_opts.warn_about_macros && place == NULL && *counter == 1)
2944 as_warn (_("Macro instruction expanded into multiple instructions"));
2947 * If the macro is about to expand into a second instruction,
2948 * and it is in a delay slot, print a warning.
2952 && mips_opts.noreorder
2953 && (prev_prev_insn.insn_mo->pinfo
2954 & (INSN_UNCOND_BRANCH_DELAY | INSN_COND_BRANCH_DELAY
2955 | INSN_COND_BRANCH_LIKELY)) != 0)
2956 as_warn (_("Macro instruction expanded into multiple instructions in a branch delay slot"));
2959 ++*counter; /* bump instruction counter */
2961 if (mips_opts.mips16)
2963 mips16_macro_build (place, counter, ep, name, fmt, args);
2968 r[0] = BFD_RELOC_UNUSED;
2969 r[1] = BFD_RELOC_UNUSED;
2970 r[2] = BFD_RELOC_UNUSED;
2971 insn.insn_mo = (struct mips_opcode *) hash_find (op_hash, name);
2972 assert (insn.insn_mo);
2973 assert (strcmp (name, insn.insn_mo->name) == 0);
2975 /* Search until we get a match for NAME. */
2978 /* It is assumed here that macros will never generate
2979 MDMX or MIPS-3D instructions. */
2980 if (strcmp (fmt, insn.insn_mo->args) == 0
2981 && insn.insn_mo->pinfo != INSN_MACRO
2982 && OPCODE_IS_MEMBER (insn.insn_mo,
2984 | (file_ase_mips16 ? INSN_MIPS16 : 0)),
2986 && (mips_arch != CPU_R4650 || (insn.insn_mo->pinfo & FP_D) == 0))
2990 assert (insn.insn_mo->name);
2991 assert (strcmp (name, insn.insn_mo->name) == 0);
2994 insn.insn_opcode = insn.insn_mo->match;
3010 insn.insn_opcode |= va_arg (args, int) << OP_SH_RT;
3014 insn.insn_opcode |= va_arg (args, int) << OP_SH_CODE;
3019 insn.insn_opcode |= va_arg (args, int) << OP_SH_FT;
3025 insn.insn_opcode |= va_arg (args, int) << OP_SH_RD;
3030 int tmp = va_arg (args, int);
3032 insn.insn_opcode |= tmp << OP_SH_RT;
3033 insn.insn_opcode |= tmp << OP_SH_RD;
3039 insn.insn_opcode |= va_arg (args, int) << OP_SH_FS;
3046 insn.insn_opcode |= va_arg (args, int) << OP_SH_SHAMT;
3050 insn.insn_opcode |= va_arg (args, int) << OP_SH_FD;
3054 insn.insn_opcode |= va_arg (args, int) << OP_SH_CODE20;
3058 insn.insn_opcode |= va_arg (args, int) << OP_SH_CODE19;
3062 insn.insn_opcode |= va_arg (args, int) << OP_SH_CODE2;
3069 insn.insn_opcode |= va_arg (args, int) << OP_SH_RS;
3075 *r = (bfd_reloc_code_real_type) va_arg (args, int);
3076 assert (*r == BFD_RELOC_GPREL16
3077 || *r == BFD_RELOC_MIPS_LITERAL
3078 || *r == BFD_RELOC_MIPS_HIGHER
3079 || *r == BFD_RELOC_HI16_S
3080 || *r == BFD_RELOC_LO16
3081 || *r == BFD_RELOC_MIPS_GOT16
3082 || *r == BFD_RELOC_MIPS_CALL16
3083 || *r == BFD_RELOC_MIPS_GOT_DISP
3084 || *r == BFD_RELOC_MIPS_GOT_PAGE
3085 || *r == BFD_RELOC_MIPS_GOT_OFST
3086 || *r == BFD_RELOC_MIPS_GOT_LO16
3087 || *r == BFD_RELOC_MIPS_CALL_LO16
3088 || (ep->X_op == O_subtract
3089 && *r == BFD_RELOC_PCREL_LO16));
3093 *r = (bfd_reloc_code_real_type) va_arg (args, int);
3095 && (ep->X_op == O_constant
3096 || (ep->X_op == O_symbol
3097 && (*r == BFD_RELOC_MIPS_HIGHEST
3098 || *r == BFD_RELOC_HI16_S
3099 || *r == BFD_RELOC_HI16
3100 || *r == BFD_RELOC_GPREL16
3101 || *r == BFD_RELOC_MIPS_GOT_HI16
3102 || *r == BFD_RELOC_MIPS_CALL_HI16))
3103 || (ep->X_op == O_subtract
3104 && *r == BFD_RELOC_PCREL_HI16_S)));
3108 assert (ep != NULL);
3110 * This allows macro() to pass an immediate expression for
3111 * creating short branches without creating a symbol.
3112 * Note that the expression still might come from the assembly
3113 * input, in which case the value is not checked for range nor
3114 * is a relocation entry generated (yuck).
3116 if (ep->X_op == O_constant)
3118 insn.insn_opcode |= (ep->X_add_number >> 2) & 0xffff;
3122 *r = BFD_RELOC_16_PCREL_S2;
3126 assert (ep != NULL);
3127 *r = BFD_RELOC_MIPS_JMP;
3131 insn.insn_opcode |= va_arg (args, unsigned long);
3140 assert (*r == BFD_RELOC_UNUSED ? ep == NULL : ep != NULL);
3142 append_insn (place, &insn, ep, r);
3146 mips16_macro_build (place, counter, ep, name, fmt, args)
3148 int *counter ATTRIBUTE_UNUSED;
3154 struct mips_cl_insn insn;
3155 bfd_reloc_code_real_type r[3]
3156 = {BFD_RELOC_UNUSED, BFD_RELOC_UNUSED, BFD_RELOC_UNUSED};
3158 insn.insn_mo = (struct mips_opcode *) hash_find (mips16_op_hash, name);
3159 assert (insn.insn_mo);
3160 assert (strcmp (name, insn.insn_mo->name) == 0);
3162 while (strcmp (fmt, insn.insn_mo->args) != 0
3163 || insn.insn_mo->pinfo == INSN_MACRO)
3166 assert (insn.insn_mo->name);
3167 assert (strcmp (name, insn.insn_mo->name) == 0);
3170 insn.insn_opcode = insn.insn_mo->match;
3171 insn.use_extend = FALSE;
3190 insn.insn_opcode |= va_arg (args, int) << MIPS16OP_SH_RY;
3195 insn.insn_opcode |= va_arg (args, int) << MIPS16OP_SH_RX;
3199 insn.insn_opcode |= va_arg (args, int) << MIPS16OP_SH_RZ;
3203 insn.insn_opcode |= va_arg (args, int) << MIPS16OP_SH_MOVE32Z;
3213 insn.insn_opcode |= va_arg (args, int) << MIPS16OP_SH_REGR32;
3220 regno = va_arg (args, int);
3221 regno = ((regno & 7) << 2) | ((regno & 0x18) >> 3);
3222 insn.insn_opcode |= regno << MIPS16OP_SH_REG32R;
3243 assert (ep != NULL);
3245 if (ep->X_op != O_constant)
3246 *r = (int) BFD_RELOC_UNUSED + c;
3249 mips16_immed (NULL, 0, c, ep->X_add_number, FALSE, FALSE,
3250 FALSE, &insn.insn_opcode, &insn.use_extend,
3253 *r = BFD_RELOC_UNUSED;
3259 insn.insn_opcode |= va_arg (args, int) << MIPS16OP_SH_IMM6;
3266 assert (*r == BFD_RELOC_UNUSED ? ep == NULL : ep != NULL);
3268 append_insn (place, &insn, ep, r);
3272 * Generate a "jalr" instruction with a relocation hint to the called
3273 * function. This occurs in NewABI PIC code.
3276 macro_build_jalr (icnt, ep)
3287 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "jalr", "d,s",
3290 fix_new_exp (frag_now, f - frag_now->fr_literal,
3291 0, ep, FALSE, BFD_RELOC_MIPS_JALR);
3295 * Generate a "lui" instruction.
3298 macro_build_lui (place, counter, ep, regnum)
3304 expressionS high_expr;
3305 struct mips_cl_insn insn;
3306 bfd_reloc_code_real_type r[3]
3307 = {BFD_RELOC_UNUSED, BFD_RELOC_UNUSED, BFD_RELOC_UNUSED};
3308 const char *name = "lui";
3309 const char *fmt = "t,u";
3311 assert (! mips_opts.mips16);
3317 high_expr.X_op = O_constant;
3318 high_expr.X_add_number = ep->X_add_number;
3321 if (high_expr.X_op == O_constant)
3323 /* we can compute the instruction now without a relocation entry */
3324 high_expr.X_add_number = ((high_expr.X_add_number + 0x8000)
3326 *r = BFD_RELOC_UNUSED;
3330 assert (ep->X_op == O_symbol);
3331 /* _gp_disp is a special case, used from s_cpload. */
3332 assert (mips_pic == NO_PIC
3334 && strcmp (S_GET_NAME (ep->X_add_symbol), "_gp_disp") == 0));
3335 *r = BFD_RELOC_HI16_S;
3339 * If the macro is about to expand into a second instruction,
3340 * print a warning if needed. We need to pass ip as a parameter
3341 * to generate a better warning message here...
3343 if (mips_opts.warn_about_macros && place == NULL && *counter == 1)
3344 as_warn (_("Macro instruction expanded into multiple instructions"));
3347 ++*counter; /* bump instruction counter */
3349 insn.insn_mo = (struct mips_opcode *) hash_find (op_hash, name);
3350 assert (insn.insn_mo);
3351 assert (strcmp (name, insn.insn_mo->name) == 0);
3352 assert (strcmp (fmt, insn.insn_mo->args) == 0);
3354 insn.insn_opcode = insn.insn_mo->match | (regnum << OP_SH_RT);
3355 if (*r == BFD_RELOC_UNUSED)
3357 insn.insn_opcode |= high_expr.X_add_number;
3358 append_insn (place, &insn, NULL, r);
3361 append_insn (place, &insn, &high_expr, r);
3364 /* Generate a sequence of instructions to do a load or store from a constant
3365 offset off of a base register (breg) into/from a target register (treg),
3366 using AT if necessary. */
3368 macro_build_ldst_constoffset (place, counter, ep, op, treg, breg)
3375 assert (ep->X_op == O_constant);
3377 /* Right now, this routine can only handle signed 32-bit contants. */
3378 if (! IS_SEXT_32BIT_NUM(ep->X_add_number))
3379 as_warn (_("operand overflow"));
3381 if (IS_SEXT_16BIT_NUM(ep->X_add_number))
3383 /* Signed 16-bit offset will fit in the op. Easy! */
3384 macro_build (place, counter, ep, op, "t,o(b)", treg,
3385 (int) BFD_RELOC_LO16, breg);
3389 /* 32-bit offset, need multiple instructions and AT, like:
3390 lui $tempreg,const_hi (BFD_RELOC_HI16_S)
3391 addu $tempreg,$tempreg,$breg
3392 <op> $treg,const_lo($tempreg) (BFD_RELOC_LO16)
3393 to handle the complete offset. */
3394 macro_build_lui (place, counter, ep, AT);
3397 macro_build (place, counter, (expressionS *) NULL,
3398 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
3399 "d,v,t", AT, AT, breg);
3402 macro_build (place, counter, ep, op, "t,o(b)", treg,
3403 (int) BFD_RELOC_LO16, AT);
3406 as_warn (_("Macro used $at after \".set noat\""));
3411 * Generates code to set the $at register to true (one)
3412 * if reg is less than the immediate expression.
3415 set_at (counter, reg, unsignedp)
3420 if (imm_expr.X_op == O_constant
3421 && imm_expr.X_add_number >= -0x8000
3422 && imm_expr.X_add_number < 0x8000)
3423 macro_build ((char *) NULL, counter, &imm_expr,
3424 unsignedp ? "sltiu" : "slti",
3425 "t,r,j", AT, reg, (int) BFD_RELOC_LO16);
3428 load_register (counter, AT, &imm_expr, HAVE_64BIT_GPRS);
3429 macro_build ((char *) NULL, counter, (expressionS *) NULL,
3430 unsignedp ? "sltu" : "slt",
3431 "d,v,t", AT, reg, AT);
3435 /* Warn if an expression is not a constant. */
3438 check_absolute_expr (ip, ex)
3439 struct mips_cl_insn *ip;
3442 if (ex->X_op == O_big)
3443 as_bad (_("unsupported large constant"));
3444 else if (ex->X_op != O_constant)
3445 as_bad (_("Instruction %s requires absolute expression"), ip->insn_mo->name);
3448 /* Count the leading zeroes by performing a binary chop. This is a
3449 bulky bit of source, but performance is a LOT better for the
3450 majority of values than a simple loop to count the bits:
3451 for (lcnt = 0; (lcnt < 32); lcnt++)
3452 if ((v) & (1 << (31 - lcnt)))
3454 However it is not code size friendly, and the gain will drop a bit
3455 on certain cached systems.
3457 #define COUNT_TOP_ZEROES(v) \
3458 (((v) & ~0xffff) == 0 \
3459 ? ((v) & ~0xff) == 0 \
3460 ? ((v) & ~0xf) == 0 \
3461 ? ((v) & ~0x3) == 0 \
3462 ? ((v) & ~0x1) == 0 \
3467 : ((v) & ~0x7) == 0 \
3470 : ((v) & ~0x3f) == 0 \
3471 ? ((v) & ~0x1f) == 0 \
3474 : ((v) & ~0x7f) == 0 \
3477 : ((v) & ~0xfff) == 0 \
3478 ? ((v) & ~0x3ff) == 0 \
3479 ? ((v) & ~0x1ff) == 0 \
3482 : ((v) & ~0x7ff) == 0 \
3485 : ((v) & ~0x3fff) == 0 \
3486 ? ((v) & ~0x1fff) == 0 \
3489 : ((v) & ~0x7fff) == 0 \
3492 : ((v) & ~0xffffff) == 0 \
3493 ? ((v) & ~0xfffff) == 0 \
3494 ? ((v) & ~0x3ffff) == 0 \
3495 ? ((v) & ~0x1ffff) == 0 \
3498 : ((v) & ~0x7ffff) == 0 \
3501 : ((v) & ~0x3fffff) == 0 \
3502 ? ((v) & ~0x1fffff) == 0 \
3505 : ((v) & ~0x7fffff) == 0 \
3508 : ((v) & ~0xfffffff) == 0 \
3509 ? ((v) & ~0x3ffffff) == 0 \
3510 ? ((v) & ~0x1ffffff) == 0 \
3513 : ((v) & ~0x7ffffff) == 0 \
3516 : ((v) & ~0x3fffffff) == 0 \
3517 ? ((v) & ~0x1fffffff) == 0 \
3520 : ((v) & ~0x7fffffff) == 0 \
3525 * This routine generates the least number of instructions neccessary to load
3526 * an absolute expression value into a register.
3529 load_register (counter, reg, ep, dbl)
3536 expressionS hi32, lo32;
3538 if (ep->X_op != O_big)
3540 assert (ep->X_op == O_constant);
3541 if (ep->X_add_number < 0x8000
3542 && (ep->X_add_number >= 0
3543 || (ep->X_add_number >= -0x8000
3546 || sizeof (ep->X_add_number) > 4))))
3548 /* We can handle 16 bit signed values with an addiu to
3549 $zero. No need to ever use daddiu here, since $zero and
3550 the result are always correct in 32 bit mode. */
3551 macro_build ((char *) NULL, counter, ep, "addiu", "t,r,j", reg, 0,
3552 (int) BFD_RELOC_LO16);
3555 else if (ep->X_add_number >= 0 && ep->X_add_number < 0x10000)
3557 /* We can handle 16 bit unsigned values with an ori to
3559 macro_build ((char *) NULL, counter, ep, "ori", "t,r,i", reg, 0,
3560 (int) BFD_RELOC_LO16);
3563 else if ((IS_SEXT_32BIT_NUM (ep->X_add_number)
3566 || sizeof (ep->X_add_number) > 4
3567 || (ep->X_add_number & 0x80000000) == 0))
3568 || ((HAVE_32BIT_GPRS || ! dbl)
3569 && (ep->X_add_number &~ (offsetT) 0xffffffff) == 0)
3572 && ((ep->X_add_number &~ (offsetT) 0xffffffff)
3573 == ~ (offsetT) 0xffffffff)))
3575 /* 32 bit values require an lui. */
3576 macro_build ((char *) NULL, counter, ep, "lui", "t,u", reg,
3577 (int) BFD_RELOC_HI16);
3578 if ((ep->X_add_number & 0xffff) != 0)
3579 macro_build ((char *) NULL, counter, ep, "ori", "t,r,i", reg, reg,
3580 (int) BFD_RELOC_LO16);
3585 /* The value is larger than 32 bits. */
3587 if (HAVE_32BIT_GPRS)
3589 as_bad (_("Number (0x%lx) larger than 32 bits"),
3590 (unsigned long) ep->X_add_number);
3591 macro_build ((char *) NULL, counter, ep, "addiu", "t,r,j", reg, 0,
3592 (int) BFD_RELOC_LO16);
3596 if (ep->X_op != O_big)
3599 hi32.X_add_number = (valueT) hi32.X_add_number >> 16;
3600 hi32.X_add_number = (valueT) hi32.X_add_number >> 16;
3601 hi32.X_add_number &= 0xffffffff;
3603 lo32.X_add_number &= 0xffffffff;
3607 assert (ep->X_add_number > 2);
3608 if (ep->X_add_number == 3)
3609 generic_bignum[3] = 0;
3610 else if (ep->X_add_number > 4)
3611 as_bad (_("Number larger than 64 bits"));
3612 lo32.X_op = O_constant;
3613 lo32.X_add_number = generic_bignum[0] + (generic_bignum[1] << 16);
3614 hi32.X_op = O_constant;
3615 hi32.X_add_number = generic_bignum[2] + (generic_bignum[3] << 16);
3618 if (hi32.X_add_number == 0)
3623 unsigned long hi, lo;
3625 if (hi32.X_add_number == (offsetT) 0xffffffff)
3627 if ((lo32.X_add_number & 0xffff8000) == 0xffff8000)
3629 macro_build ((char *) NULL, counter, &lo32, "addiu", "t,r,j",
3630 reg, 0, (int) BFD_RELOC_LO16);
3633 if (lo32.X_add_number & 0x80000000)
3635 macro_build ((char *) NULL, counter, &lo32, "lui", "t,u", reg,
3636 (int) BFD_RELOC_HI16);
3637 if (lo32.X_add_number & 0xffff)
3638 macro_build ((char *) NULL, counter, &lo32, "ori", "t,r,i",
3639 reg, reg, (int) BFD_RELOC_LO16);
3644 /* Check for 16bit shifted constant. We know that hi32 is
3645 non-zero, so start the mask on the first bit of the hi32
3650 unsigned long himask, lomask;
3654 himask = 0xffff >> (32 - shift);
3655 lomask = (0xffff << shift) & 0xffffffff;
3659 himask = 0xffff << (shift - 32);
3662 if ((hi32.X_add_number & ~(offsetT) himask) == 0
3663 && (lo32.X_add_number & ~(offsetT) lomask) == 0)
3667 tmp.X_op = O_constant;
3669 tmp.X_add_number = ((hi32.X_add_number << (32 - shift))
3670 | (lo32.X_add_number >> shift));
3672 tmp.X_add_number = hi32.X_add_number >> (shift - 32);
3673 macro_build ((char *) NULL, counter, &tmp,
3674 "ori", "t,r,i", reg, 0,
3675 (int) BFD_RELOC_LO16);
3676 macro_build ((char *) NULL, counter, (expressionS *) NULL,
3677 (shift >= 32) ? "dsll32" : "dsll",
3679 (shift >= 32) ? shift - 32 : shift);
3684 while (shift <= (64 - 16));
3686 /* Find the bit number of the lowest one bit, and store the
3687 shifted value in hi/lo. */
3688 hi = (unsigned long) (hi32.X_add_number & 0xffffffff);
3689 lo = (unsigned long) (lo32.X_add_number & 0xffffffff);
3693 while ((lo & 1) == 0)
3698 lo |= (hi & (((unsigned long) 1 << bit) - 1)) << (32 - bit);
3704 while ((hi & 1) == 0)
3713 /* Optimize if the shifted value is a (power of 2) - 1. */
3714 if ((hi == 0 && ((lo + 1) & lo) == 0)
3715 || (lo == 0xffffffff && ((hi + 1) & hi) == 0))
3717 shift = COUNT_TOP_ZEROES ((unsigned int) hi32.X_add_number);
3722 /* This instruction will set the register to be all
3724 tmp.X_op = O_constant;
3725 tmp.X_add_number = (offsetT) -1;
3726 macro_build ((char *) NULL, counter, &tmp, "addiu", "t,r,j",
3727 reg, 0, (int) BFD_RELOC_LO16);
3731 macro_build ((char *) NULL, counter, (expressionS *) NULL,
3732 (bit >= 32) ? "dsll32" : "dsll",
3734 (bit >= 32) ? bit - 32 : bit);
3736 macro_build ((char *) NULL, counter, (expressionS *) NULL,
3737 (shift >= 32) ? "dsrl32" : "dsrl",
3739 (shift >= 32) ? shift - 32 : shift);
3744 /* Sign extend hi32 before calling load_register, because we can
3745 generally get better code when we load a sign extended value. */
3746 if ((hi32.X_add_number & 0x80000000) != 0)
3747 hi32.X_add_number |= ~(offsetT) 0xffffffff;
3748 load_register (counter, reg, &hi32, 0);
3751 if ((lo32.X_add_number & 0xffff0000) == 0)
3755 macro_build ((char *) NULL, counter, (expressionS *) NULL,
3756 "dsll32", "d,w,<", reg, freg, 0);
3764 if ((freg == 0) && (lo32.X_add_number == (offsetT) 0xffffffff))
3766 macro_build ((char *) NULL, counter, &lo32, "lui", "t,u", reg,
3767 (int) BFD_RELOC_HI16);
3768 macro_build ((char *) NULL, counter, (expressionS *) NULL,
3769 "dsrl32", "d,w,<", reg, reg, 0);
3775 macro_build ((char *) NULL, counter, (expressionS *) NULL, "dsll",
3776 "d,w,<", reg, freg, 16);
3780 mid16.X_add_number >>= 16;
3781 macro_build ((char *) NULL, counter, &mid16, "ori", "t,r,i", reg,
3782 freg, (int) BFD_RELOC_LO16);
3783 macro_build ((char *) NULL, counter, (expressionS *) NULL, "dsll",
3784 "d,w,<", reg, reg, 16);
3787 if ((lo32.X_add_number & 0xffff) != 0)
3788 macro_build ((char *) NULL, counter, &lo32, "ori", "t,r,i", reg, freg,
3789 (int) BFD_RELOC_LO16);
3792 /* Load an address into a register. */
3795 load_address (counter, reg, ep, used_at)
3803 if (ep->X_op != O_constant
3804 && ep->X_op != O_symbol)
3806 as_bad (_("expression too complex"));
3807 ep->X_op = O_constant;
3810 if (ep->X_op == O_constant)
3812 load_register (counter, reg, ep, HAVE_64BIT_ADDRESSES);
3816 if (mips_pic == NO_PIC)
3818 /* If this is a reference to a GP relative symbol, we want
3819 addiu $reg,$gp,<sym> (BFD_RELOC_GPREL16)
3821 lui $reg,<sym> (BFD_RELOC_HI16_S)
3822 addiu $reg,$reg,<sym> (BFD_RELOC_LO16)
3823 If we have an addend, we always use the latter form.
3825 With 64bit address space and a usable $at we want
3826 lui $reg,<sym> (BFD_RELOC_MIPS_HIGHEST)
3827 lui $at,<sym> (BFD_RELOC_HI16_S)
3828 daddiu $reg,<sym> (BFD_RELOC_MIPS_HIGHER)
3829 daddiu $at,<sym> (BFD_RELOC_LO16)
3833 If $at is already in use, we use a path which is suboptimal
3834 on superscalar processors.
3835 lui $reg,<sym> (BFD_RELOC_MIPS_HIGHEST)
3836 daddiu $reg,<sym> (BFD_RELOC_MIPS_HIGHER)
3838 daddiu $reg,<sym> (BFD_RELOC_HI16_S)
3840 daddiu $reg,<sym> (BFD_RELOC_LO16)
3842 if (HAVE_64BIT_ADDRESSES)
3844 /* We don't do GP optimization for now because RELAX_ENCODE can't
3845 hold the data for such large chunks. */
3847 if (*used_at == 0 && ! mips_opts.noat)
3849 macro_build (p, counter, ep, "lui", "t,u",
3850 reg, (int) BFD_RELOC_MIPS_HIGHEST);
3851 macro_build (p, counter, ep, "lui", "t,u",
3852 AT, (int) BFD_RELOC_HI16_S);
3853 macro_build (p, counter, ep, "daddiu", "t,r,j",
3854 reg, reg, (int) BFD_RELOC_MIPS_HIGHER);
3855 macro_build (p, counter, ep, "daddiu", "t,r,j",
3856 AT, AT, (int) BFD_RELOC_LO16);
3857 macro_build (p, counter, (expressionS *) NULL, "dsll32",
3858 "d,w,<", reg, reg, 0);
3859 macro_build (p, counter, (expressionS *) NULL, "daddu",
3860 "d,v,t", reg, reg, AT);
3865 macro_build (p, counter, ep, "lui", "t,u",
3866 reg, (int) BFD_RELOC_MIPS_HIGHEST);
3867 macro_build (p, counter, ep, "daddiu", "t,r,j",
3868 reg, reg, (int) BFD_RELOC_MIPS_HIGHER);
3869 macro_build (p, counter, (expressionS *) NULL, "dsll",
3870 "d,w,<", reg, reg, 16);
3871 macro_build (p, counter, ep, "daddiu", "t,r,j",
3872 reg, reg, (int) BFD_RELOC_HI16_S);
3873 macro_build (p, counter, (expressionS *) NULL, "dsll",
3874 "d,w,<", reg, reg, 16);
3875 macro_build (p, counter, ep, "daddiu", "t,r,j",
3876 reg, reg, (int) BFD_RELOC_LO16);
3881 if ((valueT) ep->X_add_number <= MAX_GPREL_OFFSET
3882 && ! nopic_need_relax (ep->X_add_symbol, 1))
3885 macro_build ((char *) NULL, counter, ep,
3886 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu", "t,r,j",
3887 reg, mips_gp_register, (int) BFD_RELOC_GPREL16);
3888 p = frag_var (rs_machine_dependent, 8, 0,
3889 RELAX_ENCODE (4, 8, 0, 4, 0,
3890 mips_opts.warn_about_macros),
3891 ep->X_add_symbol, 0, NULL);
3893 macro_build_lui (p, counter, ep, reg);
3896 macro_build (p, counter, ep,
3897 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
3898 "t,r,j", reg, reg, (int) BFD_RELOC_LO16);
3901 else if (mips_pic == SVR4_PIC && ! mips_big_got)
3905 /* If this is a reference to an external symbol, we want
3906 lw $reg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
3908 lw $reg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
3910 addiu $reg,$reg,<sym> (BFD_RELOC_LO16)
3911 If we have NewABI, we want
3912 lw $reg,<sym>($gp) (BFD_RELOC_MIPS_GOT_DISP)
3913 If there is a constant, it must be added in after. */
3914 ex.X_add_number = ep->X_add_number;
3915 ep->X_add_number = 0;
3919 macro_build ((char *) NULL, counter, ep,
3920 HAVE_32BIT_ADDRESSES ? "lw" : "ld", "t,o(b)", reg,
3921 (int) BFD_RELOC_MIPS_GOT_DISP, mips_gp_register);
3925 macro_build ((char *) NULL, counter, ep,
3926 HAVE_32BIT_ADDRESSES ? "lw" : "ld", "t,o(b)",
3927 reg, (int) BFD_RELOC_MIPS_GOT16, mips_gp_register);
3928 macro_build ((char *) NULL, counter, (expressionS *) NULL, "nop", "");
3929 p = frag_var (rs_machine_dependent, 4, 0,
3930 RELAX_ENCODE (0, 4, -8, 0, 0, mips_opts.warn_about_macros),
3931 ep->X_add_symbol, (offsetT) 0, (char *) NULL);
3932 macro_build (p, counter, ep,
3933 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
3934 "t,r,j", reg, reg, (int) BFD_RELOC_LO16);
3937 if (ex.X_add_number != 0)
3939 if (ex.X_add_number < -0x8000 || ex.X_add_number >= 0x8000)
3940 as_bad (_("PIC code offset overflow (max 16 signed bits)"));
3941 ex.X_op = O_constant;
3942 macro_build ((char *) NULL, counter, &ex,
3943 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
3944 "t,r,j", reg, reg, (int) BFD_RELOC_LO16);
3947 else if (mips_pic == SVR4_PIC)
3952 /* This is the large GOT case. If this is a reference to an
3953 external symbol, we want
3954 lui $reg,<sym> (BFD_RELOC_MIPS_GOT_HI16)
3956 lw $reg,<sym>($reg) (BFD_RELOC_MIPS_GOT_LO16)
3957 Otherwise, for a reference to a local symbol, we want
3958 lw $reg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
3960 addiu $reg,$reg,<sym> (BFD_RELOC_LO16)
3961 If we have NewABI, we want
3962 lw $reg,<sym>($gp) (BFD_RELOC_MIPS_GOT_PAGE)
3963 addiu $reg,$reg,<sym> (BFD_RELOC_MIPS_GOT_OFST)
3964 If there is a constant, it must be added in after. */
3965 ex.X_add_number = ep->X_add_number;
3966 ep->X_add_number = 0;
3969 macro_build ((char *) NULL, counter, ep,
3970 HAVE_32BIT_ADDRESSES ? "lw" : "ld", "t,o(b)", reg,
3971 (int) BFD_RELOC_MIPS_GOT_PAGE, mips_gp_register);
3972 macro_build (p, counter, ep,
3973 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu", "t,r,j",
3974 reg, reg, (int) BFD_RELOC_MIPS_GOT_OFST);
3978 if (reg_needs_delay (mips_gp_register))
3983 macro_build ((char *) NULL, counter, ep, "lui", "t,u", reg,
3984 (int) BFD_RELOC_MIPS_GOT_HI16);
3985 macro_build ((char *) NULL, counter, (expressionS *) NULL,
3986 HAVE_32BIT_ADDRESSES ? "addu" : "daddu", "d,v,t", reg,
3987 reg, mips_gp_register);
3988 macro_build ((char *) NULL, counter, ep,
3989 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
3990 "t,o(b)", reg, (int) BFD_RELOC_MIPS_GOT_LO16, reg);
3991 p = frag_var (rs_machine_dependent, 12 + off, 0,
3992 RELAX_ENCODE (12, 12 + off, off, 8 + off, 0,
3993 mips_opts.warn_about_macros),
3994 ep->X_add_symbol, 0, NULL);
3997 /* We need a nop before loading from $gp. This special
3998 check is required because the lui which starts the main
3999 instruction stream does not refer to $gp, and so will not
4000 insert the nop which may be required. */
4001 macro_build (p, counter, (expressionS *) NULL, "nop", "");
4004 macro_build (p, counter, ep,
4005 HAVE_32BIT_ADDRESSES ? "lw" : "ld", "t,o(b)", reg,
4006 (int) BFD_RELOC_MIPS_GOT16, mips_gp_register);
4008 macro_build (p, counter, (expressionS *) NULL, "nop", "");
4010 macro_build (p, counter, ep,
4011 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
4012 "t,r,j", reg, reg, (int) BFD_RELOC_LO16);
4015 if (ex.X_add_number != 0)
4017 if (ex.X_add_number < -0x8000 || ex.X_add_number >= 0x8000)
4018 as_bad (_("PIC code offset overflow (max 16 signed bits)"));
4019 ex.X_op = O_constant;
4020 macro_build ((char *) NULL, counter, &ex,
4021 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
4022 "t,r,j", reg, reg, (int) BFD_RELOC_LO16);
4025 else if (mips_pic == EMBEDDED_PIC)
4028 addiu $reg,$gp,<sym> (BFD_RELOC_GPREL16)
4030 macro_build ((char *) NULL, counter, ep,
4031 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
4032 "t,r,j", reg, mips_gp_register, (int) BFD_RELOC_GPREL16);
4038 /* Move the contents of register SOURCE into register DEST. */
4041 move_register (counter, dest, source)
4046 macro_build ((char *) NULL, counter, (expressionS *) NULL,
4047 HAVE_32BIT_GPRS ? "addu" : "daddu",
4048 "d,v,t", dest, source, 0);
4053 * This routine implements the seemingly endless macro or synthesized
4054 * instructions and addressing modes in the mips assembly language. Many
4055 * of these macros are simple and are similar to each other. These could
4056 * probably be handled by some kind of table or grammer aproach instead of
4057 * this verbose method. Others are not simple macros but are more like
4058 * optimizing code generation.
4059 * One interesting optimization is when several store macros appear
4060 * consecutivly that would load AT with the upper half of the same address.
4061 * The ensuing load upper instructions are ommited. This implies some kind
4062 * of global optimization. We currently only optimize within a single macro.
4063 * For many of the load and store macros if the address is specified as a
4064 * constant expression in the first 64k of memory (ie ld $2,0x4000c) we
4065 * first load register 'at' with zero and use it as the base register. The
4066 * mips assembler simply uses register $zero. Just one tiny optimization
4071 struct mips_cl_insn *ip;
4073 register int treg, sreg, dreg, breg;
4089 bfd_reloc_code_real_type r;
4090 int hold_mips_optimize;
4092 assert (! mips_opts.mips16);
4094 treg = (ip->insn_opcode >> 16) & 0x1f;
4095 dreg = (ip->insn_opcode >> 11) & 0x1f;
4096 sreg = breg = (ip->insn_opcode >> 21) & 0x1f;
4097 mask = ip->insn_mo->mask;
4099 expr1.X_op = O_constant;
4100 expr1.X_op_symbol = NULL;
4101 expr1.X_add_symbol = NULL;
4102 expr1.X_add_number = 1;
4104 /* Umatched fixups should not be put in the same frag as a relaxable
4105 macro. For example, suppose we have:
4109 addiu $4,$4,%lo(l1) # 3
4111 If instructions 1 and 2 were put in the same frag, md_frob_file would
4112 move the fixup for #1 after the fixups for the "unrelaxed" version of
4113 #2. This would confuse tc_gen_reloc, which expects the relocations
4114 for #2 to be the last for that frag.
4116 Also, if tc_gen_reloc sees certain relocations in a variant frag,
4117 it assumes that they belong to a relaxable macro. We mustn't put
4118 other uses of such relocations into a variant frag.
4120 To avoid both problems, finish the current frag it contains a
4121 %reloc() operator. The macro then goes into a new frag. */
4122 if (prev_reloc_op_frag == frag_now)
4124 frag_wane (frag_now);
4138 mips_emit_delays (TRUE);
4139 ++mips_opts.noreorder;
4140 mips_any_noreorder = 1;
4142 expr1.X_add_number = 8;
4143 macro_build ((char *) NULL, &icnt, &expr1, "bgez", "s,p", sreg);
4145 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "",
4148 move_register (&icnt, dreg, sreg);
4149 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
4150 dbl ? "dsub" : "sub", "d,v,t", dreg, 0, sreg);
4152 --mips_opts.noreorder;
4173 if (imm_expr.X_op == O_constant
4174 && imm_expr.X_add_number >= -0x8000
4175 && imm_expr.X_add_number < 0x8000)
4177 macro_build ((char *) NULL, &icnt, &imm_expr, s, "t,r,j", treg, sreg,
4178 (int) BFD_RELOC_LO16);
4181 load_register (&icnt, AT, &imm_expr, dbl);
4182 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s2, "d,v,t",
4202 if (imm_expr.X_op == O_constant
4203 && imm_expr.X_add_number >= 0
4204 && imm_expr.X_add_number < 0x10000)
4206 if (mask != M_NOR_I)
4207 macro_build ((char *) NULL, &icnt, &imm_expr, s, "t,r,i", treg,
4208 sreg, (int) BFD_RELOC_LO16);
4211 macro_build ((char *) NULL, &icnt, &imm_expr, "ori", "t,r,i",
4212 treg, sreg, (int) BFD_RELOC_LO16);
4213 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nor",
4214 "d,v,t", treg, treg, 0);
4219 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_GPRS);
4220 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s2, "d,v,t",
4238 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
4240 macro_build ((char *) NULL, &icnt, &offset_expr, s, "s,t,p", sreg,
4244 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_GPRS);
4245 macro_build ((char *) NULL, &icnt, &offset_expr, s, "s,t,p", sreg, AT);
4253 macro_build ((char *) NULL, &icnt, &offset_expr,
4254 likely ? "bgezl" : "bgez", "s,p", sreg);
4259 macro_build ((char *) NULL, &icnt, &offset_expr,
4260 likely ? "blezl" : "blez", "s,p", treg);
4263 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "slt", "d,v,t",
4265 macro_build ((char *) NULL, &icnt, &offset_expr,
4266 likely ? "beql" : "beq", "s,t,p", AT, 0);
4272 /* check for > max integer */
4273 maxnum = 0x7fffffff;
4274 if (HAVE_64BIT_GPRS && sizeof (maxnum) > 4)
4281 if (imm_expr.X_op == O_constant
4282 && imm_expr.X_add_number >= maxnum
4283 && (HAVE_32BIT_GPRS || sizeof (maxnum) > 4))
4286 /* result is always false */
4290 as_warn (_("Branch %s is always false (nop)"),
4292 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop",
4298 as_warn (_("Branch likely %s is always false"),
4300 macro_build ((char *) NULL, &icnt, &offset_expr, "bnel",
4305 if (imm_expr.X_op != O_constant)
4306 as_bad (_("Unsupported large constant"));
4307 ++imm_expr.X_add_number;
4311 if (mask == M_BGEL_I)
4313 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
4315 macro_build ((char *) NULL, &icnt, &offset_expr,
4316 likely ? "bgezl" : "bgez", "s,p", sreg);
4319 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 1)
4321 macro_build ((char *) NULL, &icnt, &offset_expr,
4322 likely ? "bgtzl" : "bgtz", "s,p", sreg);
4325 maxnum = 0x7fffffff;
4326 if (HAVE_64BIT_GPRS && sizeof (maxnum) > 4)
4333 maxnum = - maxnum - 1;
4334 if (imm_expr.X_op == O_constant
4335 && imm_expr.X_add_number <= maxnum
4336 && (HAVE_32BIT_GPRS || sizeof (maxnum) > 4))
4339 /* result is always true */
4340 as_warn (_("Branch %s is always true"), ip->insn_mo->name);
4341 macro_build ((char *) NULL, &icnt, &offset_expr, "b", "p");
4344 set_at (&icnt, sreg, 0);
4345 macro_build ((char *) NULL, &icnt, &offset_expr,
4346 likely ? "beql" : "beq", "s,t,p", AT, 0);
4356 macro_build ((char *) NULL, &icnt, &offset_expr,
4357 likely ? "beql" : "beq", "s,t,p", 0, treg);
4360 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sltu",
4361 "d,v,t", AT, sreg, treg);
4362 macro_build ((char *) NULL, &icnt, &offset_expr,
4363 likely ? "beql" : "beq", "s,t,p", AT, 0);
4371 && imm_expr.X_op == O_constant
4372 && imm_expr.X_add_number == (offsetT) 0xffffffff))
4374 if (imm_expr.X_op != O_constant)
4375 as_bad (_("Unsupported large constant"));
4376 ++imm_expr.X_add_number;
4380 if (mask == M_BGEUL_I)
4382 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
4384 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 1)
4386 macro_build ((char *) NULL, &icnt, &offset_expr,
4387 likely ? "bnel" : "bne", "s,t,p", sreg, 0);
4390 set_at (&icnt, sreg, 1);
4391 macro_build ((char *) NULL, &icnt, &offset_expr,
4392 likely ? "beql" : "beq", "s,t,p", AT, 0);
4400 macro_build ((char *) NULL, &icnt, &offset_expr,
4401 likely ? "bgtzl" : "bgtz", "s,p", sreg);
4406 macro_build ((char *) NULL, &icnt, &offset_expr,
4407 likely ? "bltzl" : "bltz", "s,p", treg);
4410 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "slt", "d,v,t",
4412 macro_build ((char *) NULL, &icnt, &offset_expr,
4413 likely ? "bnel" : "bne", "s,t,p", AT, 0);
4421 macro_build ((char *) NULL, &icnt, &offset_expr,
4422 likely ? "bnel" : "bne", "s,t,p", sreg, 0);
4427 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sltu",
4428 "d,v,t", AT, treg, sreg);
4429 macro_build ((char *) NULL, &icnt, &offset_expr,
4430 likely ? "bnel" : "bne", "s,t,p", AT, 0);
4438 macro_build ((char *) NULL, &icnt, &offset_expr,
4439 likely ? "blezl" : "blez", "s,p", sreg);
4444 macro_build ((char *) NULL, &icnt, &offset_expr,
4445 likely ? "bgezl" : "bgez", "s,p", treg);
4448 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "slt", "d,v,t",
4450 macro_build ((char *) NULL, &icnt, &offset_expr,
4451 likely ? "beql" : "beq", "s,t,p", AT, 0);
4457 maxnum = 0x7fffffff;
4458 if (HAVE_64BIT_GPRS && sizeof (maxnum) > 4)
4465 if (imm_expr.X_op == O_constant
4466 && imm_expr.X_add_number >= maxnum
4467 && (HAVE_32BIT_GPRS || sizeof (maxnum) > 4))
4469 if (imm_expr.X_op != O_constant)
4470 as_bad (_("Unsupported large constant"));
4471 ++imm_expr.X_add_number;
4475 if (mask == M_BLTL_I)
4477 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
4479 macro_build ((char *) NULL, &icnt, &offset_expr,
4480 likely ? "bltzl" : "bltz", "s,p", sreg);
4483 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 1)
4485 macro_build ((char *) NULL, &icnt, &offset_expr,
4486 likely ? "blezl" : "blez", "s,p", sreg);
4489 set_at (&icnt, sreg, 0);
4490 macro_build ((char *) NULL, &icnt, &offset_expr,
4491 likely ? "bnel" : "bne", "s,t,p", AT, 0);
4499 macro_build ((char *) NULL, &icnt, &offset_expr,
4500 likely ? "beql" : "beq", "s,t,p", sreg, 0);
4505 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sltu",
4506 "d,v,t", AT, treg, sreg);
4507 macro_build ((char *) NULL, &icnt, &offset_expr,
4508 likely ? "beql" : "beq", "s,t,p", AT, 0);
4516 && imm_expr.X_op == O_constant
4517 && imm_expr.X_add_number == (offsetT) 0xffffffff))
4519 if (imm_expr.X_op != O_constant)
4520 as_bad (_("Unsupported large constant"));
4521 ++imm_expr.X_add_number;
4525 if (mask == M_BLTUL_I)
4527 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
4529 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 1)
4531 macro_build ((char *) NULL, &icnt, &offset_expr,
4532 likely ? "beql" : "beq",
4536 set_at (&icnt, sreg, 1);
4537 macro_build ((char *) NULL, &icnt, &offset_expr,
4538 likely ? "bnel" : "bne", "s,t,p", AT, 0);
4546 macro_build ((char *) NULL, &icnt, &offset_expr,
4547 likely ? "bltzl" : "bltz", "s,p", sreg);
4552 macro_build ((char *) NULL, &icnt, &offset_expr,
4553 likely ? "bgtzl" : "bgtz", "s,p", treg);
4556 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "slt", "d,v,t",
4558 macro_build ((char *) NULL, &icnt, &offset_expr,
4559 likely ? "bnel" : "bne", "s,t,p", AT, 0);
4569 macro_build ((char *) NULL, &icnt, &offset_expr,
4570 likely ? "bnel" : "bne", "s,t,p", 0, treg);
4573 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sltu",
4576 macro_build ((char *) NULL, &icnt, &offset_expr,
4577 likely ? "bnel" : "bne", "s,t,p", AT, 0);
4592 as_warn (_("Divide by zero."));
4594 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "teq",
4597 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "break",
4602 mips_emit_delays (TRUE);
4603 ++mips_opts.noreorder;
4604 mips_any_noreorder = 1;
4607 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "teq",
4608 "s,t,q", treg, 0, 7);
4609 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
4610 dbl ? "ddiv" : "div", "z,s,t", sreg, treg);
4614 expr1.X_add_number = 8;
4615 macro_build ((char *) NULL, &icnt, &expr1, "bne", "s,t,p", treg, 0);
4616 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
4617 dbl ? "ddiv" : "div", "z,s,t", sreg, treg);
4618 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "break",
4621 expr1.X_add_number = -1;
4622 macro_build ((char *) NULL, &icnt, &expr1,
4623 dbl ? "daddiu" : "addiu",
4624 "t,r,j", AT, 0, (int) BFD_RELOC_LO16);
4625 expr1.X_add_number = mips_trap ? (dbl ? 12 : 8) : (dbl ? 20 : 16);
4626 macro_build ((char *) NULL, &icnt, &expr1, "bne", "s,t,p", treg, AT);
4629 expr1.X_add_number = 1;
4630 macro_build ((char *) NULL, &icnt, &expr1, "daddiu", "t,r,j", AT, 0,
4631 (int) BFD_RELOC_LO16);
4632 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "dsll32",
4633 "d,w,<", AT, AT, 31);
4637 expr1.X_add_number = 0x80000000;
4638 macro_build ((char *) NULL, &icnt, &expr1, "lui", "t,u", AT,
4639 (int) BFD_RELOC_HI16);
4643 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "teq",
4644 "s,t,q", sreg, AT, 6);
4645 /* We want to close the noreorder block as soon as possible, so
4646 that later insns are available for delay slot filling. */
4647 --mips_opts.noreorder;
4651 expr1.X_add_number = 8;
4652 macro_build ((char *) NULL, &icnt, &expr1, "bne", "s,t,p", sreg, AT);
4653 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "",
4656 /* We want to close the noreorder block as soon as possible, so
4657 that later insns are available for delay slot filling. */
4658 --mips_opts.noreorder;
4660 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "break",
4663 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "d", dreg);
4702 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
4704 as_warn (_("Divide by zero."));
4706 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "teq",
4709 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "break",
4713 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 1)
4715 if (strcmp (s2, "mflo") == 0)
4716 move_register (&icnt, dreg, sreg);
4718 move_register (&icnt, dreg, 0);
4721 if (imm_expr.X_op == O_constant
4722 && imm_expr.X_add_number == -1
4723 && s[strlen (s) - 1] != 'u')
4725 if (strcmp (s2, "mflo") == 0)
4727 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
4728 dbl ? "dneg" : "neg", "d,w", dreg, sreg);
4731 move_register (&icnt, dreg, 0);
4735 load_register (&icnt, AT, &imm_expr, dbl);
4736 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "z,s,t",
4738 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s2, "d", dreg);
4757 mips_emit_delays (TRUE);
4758 ++mips_opts.noreorder;
4759 mips_any_noreorder = 1;
4762 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "teq",
4763 "s,t,q", treg, 0, 7);
4764 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "z,s,t",
4766 /* We want to close the noreorder block as soon as possible, so
4767 that later insns are available for delay slot filling. */
4768 --mips_opts.noreorder;
4772 expr1.X_add_number = 8;
4773 macro_build ((char *) NULL, &icnt, &expr1, "bne", "s,t,p", treg, 0);
4774 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "z,s,t",
4777 /* We want to close the noreorder block as soon as possible, so
4778 that later insns are available for delay slot filling. */
4779 --mips_opts.noreorder;
4780 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "break",
4783 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s2, "d", dreg);
4789 /* Load the address of a symbol into a register. If breg is not
4790 zero, we then add a base register to it. */
4792 if (dbl && HAVE_32BIT_GPRS)
4793 as_warn (_("dla used to load 32-bit register"));
4795 if (! dbl && HAVE_64BIT_OBJECTS)
4796 as_warn (_("la used to load 64-bit address"));
4798 if (offset_expr.X_op == O_constant
4799 && offset_expr.X_add_number >= -0x8000
4800 && offset_expr.X_add_number < 0x8000)
4802 macro_build ((char *) NULL, &icnt, &offset_expr,
4803 (dbl || HAVE_64BIT_ADDRESSES) ? "daddiu" : "addiu",
4804 "t,r,j", treg, sreg, (int) BFD_RELOC_LO16);
4819 /* When generating embedded PIC code, we permit expressions of
4822 la $treg,foo-bar($breg)
4823 where bar is an address in the current section. These are used
4824 when getting the addresses of functions. We don't permit
4825 X_add_number to be non-zero, because if the symbol is
4826 external the relaxing code needs to know that any addend is
4827 purely the offset to X_op_symbol. */
4828 if (mips_pic == EMBEDDED_PIC
4829 && offset_expr.X_op == O_subtract
4830 && (symbol_constant_p (offset_expr.X_op_symbol)
4831 ? S_GET_SEGMENT (offset_expr.X_op_symbol) == now_seg
4832 : (symbol_equated_p (offset_expr.X_op_symbol)
4834 (symbol_get_value_expression (offset_expr.X_op_symbol)
4837 && (offset_expr.X_add_number == 0
4838 || OUTPUT_FLAVOR == bfd_target_elf_flavour))
4844 macro_build ((char *) NULL, &icnt, &offset_expr, "lui", "t,u",
4845 tempreg, (int) BFD_RELOC_PCREL_HI16_S);
4849 macro_build ((char *) NULL, &icnt, &offset_expr, "lui", "t,u",
4850 tempreg, (int) BFD_RELOC_PCREL_HI16_S);
4851 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
4852 (dbl || HAVE_64BIT_ADDRESSES) ? "daddu" : "addu",
4853 "d,v,t", tempreg, tempreg, breg);
4855 macro_build ((char *) NULL, &icnt, &offset_expr,
4856 (dbl || HAVE_64BIT_ADDRESSES) ? "daddiu" : "addiu",
4857 "t,r,j", treg, tempreg, (int) BFD_RELOC_PCREL_LO16);
4863 if (offset_expr.X_op != O_symbol
4864 && offset_expr.X_op != O_constant)
4866 as_bad (_("expression too complex"));
4867 offset_expr.X_op = O_constant;
4870 if (offset_expr.X_op == O_constant)
4871 load_register (&icnt, tempreg, &offset_expr,
4872 ((mips_pic == EMBEDDED_PIC || mips_pic == NO_PIC)
4873 ? (dbl || HAVE_64BIT_ADDRESSES)
4874 : HAVE_64BIT_ADDRESSES));
4875 else if (mips_pic == NO_PIC)
4877 /* If this is a reference to a GP relative symbol, we want
4878 addiu $tempreg,$gp,<sym> (BFD_RELOC_GPREL16)
4880 lui $tempreg,<sym> (BFD_RELOC_HI16_S)
4881 addiu $tempreg,$tempreg,<sym> (BFD_RELOC_LO16)
4882 If we have a constant, we need two instructions anyhow,
4883 so we may as well always use the latter form.
4885 With 64bit address space and a usable $at we want
4886 lui $tempreg,<sym> (BFD_RELOC_MIPS_HIGHEST)
4887 lui $at,<sym> (BFD_RELOC_HI16_S)
4888 daddiu $tempreg,<sym> (BFD_RELOC_MIPS_HIGHER)
4889 daddiu $at,<sym> (BFD_RELOC_LO16)
4891 daddu $tempreg,$tempreg,$at
4893 If $at is already in use, we use a path which is suboptimal
4894 on superscalar processors.
4895 lui $tempreg,<sym> (BFD_RELOC_MIPS_HIGHEST)
4896 daddiu $tempreg,<sym> (BFD_RELOC_MIPS_HIGHER)
4898 daddiu $tempreg,<sym> (BFD_RELOC_HI16_S)
4900 daddiu $tempreg,<sym> (BFD_RELOC_LO16)
4903 if (HAVE_64BIT_ADDRESSES)
4905 /* We don't do GP optimization for now because RELAX_ENCODE can't
4906 hold the data for such large chunks. */
4908 if (used_at == 0 && ! mips_opts.noat)
4910 macro_build (p, &icnt, &offset_expr, "lui", "t,u",
4911 tempreg, (int) BFD_RELOC_MIPS_HIGHEST);
4912 macro_build (p, &icnt, &offset_expr, "lui", "t,u",
4913 AT, (int) BFD_RELOC_HI16_S);
4914 macro_build (p, &icnt, &offset_expr, "daddiu", "t,r,j",
4915 tempreg, tempreg, (int) BFD_RELOC_MIPS_HIGHER);
4916 macro_build (p, &icnt, &offset_expr, "daddiu", "t,r,j",
4917 AT, AT, (int) BFD_RELOC_LO16);
4918 macro_build (p, &icnt, (expressionS *) NULL, "dsll32",
4919 "d,w,<", tempreg, tempreg, 0);
4920 macro_build (p, &icnt, (expressionS *) NULL, "daddu",
4921 "d,v,t", tempreg, tempreg, AT);
4926 macro_build (p, &icnt, &offset_expr, "lui", "t,u",
4927 tempreg, (int) BFD_RELOC_MIPS_HIGHEST);
4928 macro_build (p, &icnt, &offset_expr, "daddiu", "t,r,j",
4929 tempreg, tempreg, (int) BFD_RELOC_MIPS_HIGHER);
4930 macro_build (p, &icnt, (expressionS *) NULL, "dsll", "d,w,<",
4931 tempreg, tempreg, 16);
4932 macro_build (p, &icnt, &offset_expr, "daddiu", "t,r,j",
4933 tempreg, tempreg, (int) BFD_RELOC_HI16_S);
4934 macro_build (p, &icnt, (expressionS *) NULL, "dsll", "d,w,<",
4935 tempreg, tempreg, 16);
4936 macro_build (p, &icnt, &offset_expr, "daddiu", "t,r,j",
4937 tempreg, tempreg, (int) BFD_RELOC_LO16);
4942 if ((valueT) offset_expr.X_add_number <= MAX_GPREL_OFFSET
4943 && ! nopic_need_relax (offset_expr.X_add_symbol, 1))
4946 macro_build ((char *) NULL, &icnt, &offset_expr, "addiu",
4947 "t,r,j", tempreg, mips_gp_register,
4948 (int) BFD_RELOC_GPREL16);
4949 p = frag_var (rs_machine_dependent, 8, 0,
4950 RELAX_ENCODE (4, 8, 0, 4, 0,
4951 mips_opts.warn_about_macros),
4952 offset_expr.X_add_symbol, 0, NULL);
4954 macro_build_lui (p, &icnt, &offset_expr, tempreg);
4957 macro_build (p, &icnt, &offset_expr, "addiu",
4958 "t,r,j", tempreg, tempreg, (int) BFD_RELOC_LO16);
4961 else if (mips_pic == SVR4_PIC && ! mips_big_got)
4963 int lw_reloc_type = (int) BFD_RELOC_MIPS_GOT16;
4965 /* If this is a reference to an external symbol, and there
4966 is no constant, we want
4967 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
4968 or if tempreg is PIC_CALL_REG
4969 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_CALL16)
4970 For a local symbol, we want
4971 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
4973 addiu $tempreg,$tempreg,<sym> (BFD_RELOC_LO16)
4975 If we have a small constant, and this is a reference to
4976 an external symbol, we want
4977 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
4979 addiu $tempreg,$tempreg,<constant>
4980 For a local symbol, we want the same instruction
4981 sequence, but we output a BFD_RELOC_LO16 reloc on the
4984 If we have a large constant, and this is a reference to
4985 an external symbol, we want
4986 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
4987 lui $at,<hiconstant>
4988 addiu $at,$at,<loconstant>
4989 addu $tempreg,$tempreg,$at
4990 For a local symbol, we want the same instruction
4991 sequence, but we output a BFD_RELOC_LO16 reloc on the
4994 For NewABI, we want for local or external data addresses
4995 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT_DISP)
4996 For a local function symbol, we want
4997 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT_PAGE)
4999 addiu $tempreg,$tempreg,<sym> (BFD_RELOC_MIPS_GOT_OFST)
5002 expr1.X_add_number = offset_expr.X_add_number;
5003 offset_expr.X_add_number = 0;
5005 if (expr1.X_add_number == 0 && tempreg == PIC_CALL_REG)
5006 lw_reloc_type = (int) BFD_RELOC_MIPS_CALL16;
5007 else if (HAVE_NEWABI)
5008 lw_reloc_type = (int) BFD_RELOC_MIPS_GOT_DISP;
5009 macro_build ((char *) NULL, &icnt, &offset_expr,
5010 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
5011 "t,o(b)", tempreg, lw_reloc_type, mips_gp_register);
5012 if (expr1.X_add_number == 0)
5021 /* We're going to put in an addu instruction using
5022 tempreg, so we may as well insert the nop right
5024 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5028 p = frag_var (rs_machine_dependent, 8 - off, 0,
5029 RELAX_ENCODE (0, 8 - off, -4 - off, 4 - off, 0,
5031 ? mips_opts.warn_about_macros
5033 offset_expr.X_add_symbol, 0, NULL);
5036 macro_build (p, &icnt, (expressionS *) NULL, "nop", "");
5039 macro_build (p, &icnt, &expr1,
5040 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
5041 "t,r,j", tempreg, tempreg, (int) BFD_RELOC_LO16);
5042 /* FIXME: If breg == 0, and the next instruction uses
5043 $tempreg, then if this variant case is used an extra
5044 nop will be generated. */
5046 else if (expr1.X_add_number >= -0x8000
5047 && expr1.X_add_number < 0x8000)
5049 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5051 macro_build ((char *) NULL, &icnt, &expr1,
5052 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
5053 "t,r,j", tempreg, tempreg, (int) BFD_RELOC_LO16);
5054 frag_var (rs_machine_dependent, 0, 0,
5055 RELAX_ENCODE (0, 0, -12, -4, 0, 0),
5056 offset_expr.X_add_symbol, 0, NULL);
5062 /* If we are going to add in a base register, and the
5063 target register and the base register are the same,
5064 then we are using AT as a temporary register. Since
5065 we want to load the constant into AT, we add our
5066 current AT (from the global offset table) and the
5067 register into the register now, and pretend we were
5068 not using a base register. */
5073 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5075 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5076 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
5077 "d,v,t", treg, AT, breg);
5083 /* Set mips_optimize around the lui instruction to avoid
5084 inserting an unnecessary nop after the lw. */
5085 hold_mips_optimize = mips_optimize;
5087 macro_build_lui (NULL, &icnt, &expr1, AT);
5088 mips_optimize = hold_mips_optimize;
5090 macro_build ((char *) NULL, &icnt, &expr1,
5091 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
5092 "t,r,j", AT, AT, (int) BFD_RELOC_LO16);
5093 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5094 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
5095 "d,v,t", tempreg, tempreg, AT);
5096 frag_var (rs_machine_dependent, 0, 0,
5097 RELAX_ENCODE (0, 0, -16 + off1, -8, 0, 0),
5098 offset_expr.X_add_symbol, 0, NULL);
5102 else if (mips_pic == SVR4_PIC)
5106 int lui_reloc_type = (int) BFD_RELOC_MIPS_GOT_HI16;
5107 int lw_reloc_type = (int) BFD_RELOC_MIPS_GOT_LO16;
5108 int local_reloc_type = (int) BFD_RELOC_MIPS_GOT16;
5110 /* This is the large GOT case. If this is a reference to an
5111 external symbol, and there is no constant, we want
5112 lui $tempreg,<sym> (BFD_RELOC_MIPS_GOT_HI16)
5113 addu $tempreg,$tempreg,$gp
5114 lw $tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_LO16)
5115 or if tempreg is PIC_CALL_REG
5116 lui $tempreg,<sym> (BFD_RELOC_MIPS_CALL_HI16)
5117 addu $tempreg,$tempreg,$gp
5118 lw $tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_CALL_LO16)
5119 For a local symbol, we want
5120 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
5122 addiu $tempreg,$tempreg,<sym> (BFD_RELOC_LO16)
5124 If we have a small constant, and this is a reference to
5125 an external symbol, we want
5126 lui $tempreg,<sym> (BFD_RELOC_MIPS_GOT_HI16)
5127 addu $tempreg,$tempreg,$gp
5128 lw $tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_LO16)
5130 addiu $tempreg,$tempreg,<constant>
5131 For a local symbol, we want
5132 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
5134 addiu $tempreg,$tempreg,<constant> (BFD_RELOC_LO16)
5136 If we have a large constant, and this is a reference to
5137 an external symbol, we want
5138 lui $tempreg,<sym> (BFD_RELOC_MIPS_GOT_HI16)
5139 addu $tempreg,$tempreg,$gp
5140 lw $tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_LO16)
5141 lui $at,<hiconstant>
5142 addiu $at,$at,<loconstant>
5143 addu $tempreg,$tempreg,$at
5144 For a local symbol, we want
5145 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
5146 lui $at,<hiconstant>
5147 addiu $at,$at,<loconstant> (BFD_RELOC_LO16)
5148 addu $tempreg,$tempreg,$at
5150 For NewABI, we want for local data addresses
5151 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT_DISP)
5154 expr1.X_add_number = offset_expr.X_add_number;
5155 offset_expr.X_add_number = 0;
5157 if (reg_needs_delay (mips_gp_register))
5161 if (expr1.X_add_number == 0 && tempreg == PIC_CALL_REG)
5163 lui_reloc_type = (int) BFD_RELOC_MIPS_CALL_HI16;
5164 lw_reloc_type = (int) BFD_RELOC_MIPS_CALL_LO16;
5166 macro_build ((char *) NULL, &icnt, &offset_expr, "lui", "t,u",
5167 tempreg, lui_reloc_type);
5168 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5169 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
5170 "d,v,t", tempreg, tempreg, mips_gp_register);
5171 macro_build ((char *) NULL, &icnt, &offset_expr,
5172 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
5173 "t,o(b)", tempreg, lw_reloc_type, tempreg);
5174 if (expr1.X_add_number == 0)
5182 /* We're going to put in an addu instruction using
5183 tempreg, so we may as well insert the nop right
5185 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5190 p = frag_var (rs_machine_dependent, 12 + gpdel, 0,
5191 RELAX_ENCODE (12 + off, 12 + gpdel, gpdel,
5194 ? mips_opts.warn_about_macros
5196 offset_expr.X_add_symbol, 0, NULL);
5198 else if (expr1.X_add_number >= -0x8000
5199 && expr1.X_add_number < 0x8000)
5201 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5203 macro_build ((char *) NULL, &icnt, &expr1,
5204 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
5205 "t,r,j", tempreg, tempreg, (int) BFD_RELOC_LO16);
5207 p = frag_var (rs_machine_dependent, 12 + gpdel, 0,
5208 RELAX_ENCODE (20, 12 + gpdel, gpdel, 8 + gpdel, 0,
5210 ? mips_opts.warn_about_macros
5212 offset_expr.X_add_symbol, 0, NULL);
5218 /* If we are going to add in a base register, and the
5219 target register and the base register are the same,
5220 then we are using AT as a temporary register. Since
5221 we want to load the constant into AT, we add our
5222 current AT (from the global offset table) and the
5223 register into the register now, and pretend we were
5224 not using a base register. */
5232 assert (tempreg == AT);
5233 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5235 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5236 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
5237 "d,v,t", treg, AT, breg);
5242 /* Set mips_optimize around the lui instruction to avoid
5243 inserting an unnecessary nop after the lw. */
5244 hold_mips_optimize = mips_optimize;
5246 macro_build_lui (NULL, &icnt, &expr1, AT);
5247 mips_optimize = hold_mips_optimize;
5249 macro_build ((char *) NULL, &icnt, &expr1,
5250 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
5251 "t,r,j", AT, AT, (int) BFD_RELOC_LO16);
5252 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5253 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
5254 "d,v,t", dreg, dreg, AT);
5256 p = frag_var (rs_machine_dependent, 16 + gpdel + adj, 0,
5257 RELAX_ENCODE (24 + adj, 16 + gpdel + adj, gpdel,
5260 ? mips_opts.warn_about_macros
5262 offset_expr.X_add_symbol, 0, NULL);
5269 /* This is needed because this instruction uses $gp, but
5270 the first instruction on the main stream does not. */
5271 macro_build (p, &icnt, (expressionS *) NULL, "nop", "");
5276 local_reloc_type = (int) BFD_RELOC_MIPS_GOT_DISP;
5277 macro_build (p, &icnt, &offset_expr,
5278 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
5283 if (expr1.X_add_number == 0 && HAVE_NEWABI)
5285 /* BFD_RELOC_MIPS_GOT_DISP is sufficient for newabi */
5288 if (expr1.X_add_number >= -0x8000
5289 && expr1.X_add_number < 0x8000)
5291 macro_build (p, &icnt, (expressionS *) NULL, "nop", "");
5293 macro_build (p, &icnt, &expr1,
5294 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
5295 "t,r,j", tempreg, tempreg, (int) BFD_RELOC_LO16);
5296 /* FIXME: If add_number is 0, and there was no base
5297 register, the external symbol case ended with a load,
5298 so if the symbol turns out to not be external, and
5299 the next instruction uses tempreg, an unnecessary nop
5300 will be inserted. */
5306 /* We must add in the base register now, as in the
5307 external symbol case. */
5308 assert (tempreg == AT);
5309 macro_build (p, &icnt, (expressionS *) NULL, "nop", "");
5311 macro_build (p, &icnt, (expressionS *) NULL,
5312 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
5313 "d,v,t", treg, AT, breg);
5316 /* We set breg to 0 because we have arranged to add
5317 it in in both cases. */
5321 macro_build_lui (p, &icnt, &expr1, AT);
5323 macro_build (p, &icnt, &expr1,
5324 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
5325 "t,r,j", AT, AT, (int) BFD_RELOC_LO16);
5327 macro_build (p, &icnt, (expressionS *) NULL,
5328 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
5329 "d,v,t", tempreg, tempreg, AT);
5333 else if (mips_pic == EMBEDDED_PIC)
5336 addiu $tempreg,$gp,<sym> (BFD_RELOC_GPREL16)
5338 macro_build ((char *) NULL, &icnt, &offset_expr,
5339 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu", "t,r,j",
5340 tempreg, mips_gp_register, (int) BFD_RELOC_GPREL16);
5349 if (mips_pic == EMBEDDED_PIC || mips_pic == NO_PIC)
5350 s = (dbl || HAVE_64BIT_ADDRESSES) ? "daddu" : "addu";
5352 s = HAVE_64BIT_ADDRESSES ? "daddu" : "addu";
5354 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s,
5355 "d,v,t", treg, tempreg, breg);
5364 /* The j instruction may not be used in PIC code, since it
5365 requires an absolute address. We convert it to a b
5367 if (mips_pic == NO_PIC)
5368 macro_build ((char *) NULL, &icnt, &offset_expr, "j", "a");
5370 macro_build ((char *) NULL, &icnt, &offset_expr, "b", "p");
5373 /* The jal instructions must be handled as macros because when
5374 generating PIC code they expand to multi-instruction
5375 sequences. Normally they are simple instructions. */
5380 if (mips_pic == NO_PIC
5381 || mips_pic == EMBEDDED_PIC)
5382 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "jalr",
5384 else if (mips_pic == SVR4_PIC)
5386 if (sreg != PIC_CALL_REG)
5387 as_warn (_("MIPS PIC call to register other than $25"));
5389 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "jalr",
5393 if (mips_cprestore_offset < 0)
5394 as_warn (_("No .cprestore pseudo-op used in PIC code"));
5397 if (! mips_frame_reg_valid)
5399 as_warn (_("No .frame pseudo-op used in PIC code"));
5400 /* Quiet this warning. */
5401 mips_frame_reg_valid = 1;
5403 if (! mips_cprestore_valid)
5405 as_warn (_("No .cprestore pseudo-op used in PIC code"));
5406 /* Quiet this warning. */
5407 mips_cprestore_valid = 1;
5409 expr1.X_add_number = mips_cprestore_offset;
5410 macro_build_ldst_constoffset ((char *) NULL, &icnt, &expr1,
5411 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
5412 mips_gp_register, mips_frame_reg);
5422 if (mips_pic == NO_PIC)
5423 macro_build ((char *) NULL, &icnt, &offset_expr, "jal", "a");
5424 else if (mips_pic == SVR4_PIC)
5428 /* If this is a reference to an external symbol, and we are
5429 using a small GOT, we want
5430 lw $25,<sym>($gp) (BFD_RELOC_MIPS_CALL16)
5434 lw $gp,cprestore($sp)
5435 The cprestore value is set using the .cprestore
5436 pseudo-op. If we are using a big GOT, we want
5437 lui $25,<sym> (BFD_RELOC_MIPS_CALL_HI16)
5439 lw $25,<sym>($25) (BFD_RELOC_MIPS_CALL_LO16)
5443 lw $gp,cprestore($sp)
5444 If the symbol is not external, we want
5445 lw $25,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
5447 addiu $25,$25,<sym> (BFD_RELOC_LO16)
5450 lw $gp,cprestore($sp)
5452 lw $25,<sym>($gp) (BFD_RELOC_MIPS_GOT_DISP)
5453 jalr $ra,$25 (BFD_RELOC_MIPS_JALR)
5457 macro_build ((char *) NULL, &icnt, &offset_expr,
5458 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
5459 "t,o(b)", PIC_CALL_REG,
5460 (int) BFD_RELOC_MIPS_GOT_DISP, mips_gp_register);
5461 macro_build_jalr (icnt, &offset_expr);
5468 macro_build ((char *) NULL, &icnt, &offset_expr,
5469 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
5470 "t,o(b)", PIC_CALL_REG,
5471 (int) BFD_RELOC_MIPS_CALL16, mips_gp_register);
5472 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5474 p = frag_var (rs_machine_dependent, 4, 0,
5475 RELAX_ENCODE (0, 4, -8, 0, 0, 0),
5476 offset_expr.X_add_symbol, 0, NULL);
5482 if (reg_needs_delay (mips_gp_register))
5486 macro_build ((char *) NULL, &icnt, &offset_expr, "lui",
5487 "t,u", PIC_CALL_REG,
5488 (int) BFD_RELOC_MIPS_CALL_HI16);
5489 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5490 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
5491 "d,v,t", PIC_CALL_REG, PIC_CALL_REG,
5493 macro_build ((char *) NULL, &icnt, &offset_expr,
5494 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
5495 "t,o(b)", PIC_CALL_REG,
5496 (int) BFD_RELOC_MIPS_CALL_LO16, PIC_CALL_REG);
5497 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5499 p = frag_var (rs_machine_dependent, 12 + gpdel, 0,
5500 RELAX_ENCODE (16, 12 + gpdel, gpdel,
5502 offset_expr.X_add_symbol, 0, NULL);
5505 macro_build (p, &icnt, (expressionS *) NULL, "nop", "");
5508 macro_build (p, &icnt, &offset_expr,
5509 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
5510 "t,o(b)", PIC_CALL_REG,
5511 (int) BFD_RELOC_MIPS_GOT16, mips_gp_register);
5513 macro_build (p, &icnt, (expressionS *) NULL, "nop", "");
5516 macro_build (p, &icnt, &offset_expr,
5517 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
5518 "t,r,j", PIC_CALL_REG, PIC_CALL_REG,
5519 (int) BFD_RELOC_LO16);
5520 macro_build_jalr (icnt, &offset_expr);
5522 if (mips_cprestore_offset < 0)
5523 as_warn (_("No .cprestore pseudo-op used in PIC code"));
5526 if (! mips_frame_reg_valid)
5528 as_warn (_("No .frame pseudo-op used in PIC code"));
5529 /* Quiet this warning. */
5530 mips_frame_reg_valid = 1;
5532 if (! mips_cprestore_valid)
5534 as_warn (_("No .cprestore pseudo-op used in PIC code"));
5535 /* Quiet this warning. */
5536 mips_cprestore_valid = 1;
5538 if (mips_opts.noreorder)
5539 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5541 expr1.X_add_number = mips_cprestore_offset;
5542 macro_build_ldst_constoffset ((char *) NULL, &icnt, &expr1,
5543 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
5544 mips_gp_register, mips_frame_reg);
5548 else if (mips_pic == EMBEDDED_PIC)
5550 macro_build ((char *) NULL, &icnt, &offset_expr, "bal", "p");
5551 /* The linker may expand the call to a longer sequence which
5552 uses $at, so we must break rather than return. */
5577 /* Itbl support may require additional care here. */
5582 /* Itbl support may require additional care here. */
5587 /* Itbl support may require additional care here. */
5592 /* Itbl support may require additional care here. */
5604 if (mips_arch == CPU_R4650)
5606 as_bad (_("opcode not supported on this processor"));
5610 /* Itbl support may require additional care here. */
5615 /* Itbl support may require additional care here. */
5620 /* Itbl support may require additional care here. */
5640 if (breg == treg || coproc || lr)
5662 /* Itbl support may require additional care here. */
5667 /* Itbl support may require additional care here. */
5672 /* Itbl support may require additional care here. */
5677 /* Itbl support may require additional care here. */
5693 if (mips_arch == CPU_R4650)
5695 as_bad (_("opcode not supported on this processor"));
5700 /* Itbl support may require additional care here. */
5704 /* Itbl support may require additional care here. */
5709 /* Itbl support may require additional care here. */
5721 /* Itbl support may require additional care here. */
5722 if (mask == M_LWC1_AB
5723 || mask == M_SWC1_AB
5724 || mask == M_LDC1_AB
5725 || mask == M_SDC1_AB
5734 /* For embedded PIC, we allow loads where the offset is calculated
5735 by subtracting a symbol in the current segment from an unknown
5736 symbol, relative to a base register, e.g.:
5737 <op> $treg, <sym>-<localsym>($breg)
5738 This is used by the compiler for switch statements. */
5739 if (mips_pic == EMBEDDED_PIC
5740 && offset_expr.X_op == O_subtract
5741 && (symbol_constant_p (offset_expr.X_op_symbol)
5742 ? S_GET_SEGMENT (offset_expr.X_op_symbol) == now_seg
5743 : (symbol_equated_p (offset_expr.X_op_symbol)
5745 (symbol_get_value_expression (offset_expr.X_op_symbol)
5749 && (offset_expr.X_add_number == 0
5750 || OUTPUT_FLAVOR == bfd_target_elf_flavour))
5752 /* For this case, we output the instructions:
5753 lui $tempreg,<sym> (BFD_RELOC_PCREL_HI16_S)
5754 addiu $tempreg,$tempreg,$breg
5755 <op> $treg,<sym>($tempreg) (BFD_RELOC_PCREL_LO16)
5756 If the relocation would fit entirely in 16 bits, it would be
5758 <op> $treg,<sym>($breg) (BFD_RELOC_PCREL_LO16)
5759 instead, but that seems quite difficult. */
5760 macro_build ((char *) NULL, &icnt, &offset_expr, "lui", "t,u",
5761 tempreg, (int) BFD_RELOC_PCREL_HI16_S);
5762 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5763 ((bfd_arch_bits_per_address (stdoutput) == 32
5764 || ! ISA_HAS_64BIT_REGS (mips_opts.isa))
5765 ? "addu" : "daddu"),
5766 "d,v,t", tempreg, tempreg, breg);
5767 macro_build ((char *) NULL, &icnt, &offset_expr, s, fmt, treg,
5768 (int) BFD_RELOC_PCREL_LO16, tempreg);
5774 if (offset_expr.X_op != O_constant
5775 && offset_expr.X_op != O_symbol)
5777 as_bad (_("expression too complex"));
5778 offset_expr.X_op = O_constant;
5781 /* A constant expression in PIC code can be handled just as it
5782 is in non PIC code. */
5783 if (mips_pic == NO_PIC
5784 || offset_expr.X_op == O_constant)
5788 /* If this is a reference to a GP relative symbol, and there
5789 is no base register, we want
5790 <op> $treg,<sym>($gp) (BFD_RELOC_GPREL16)
5791 Otherwise, if there is no base register, we want
5792 lui $tempreg,<sym> (BFD_RELOC_HI16_S)
5793 <op> $treg,<sym>($tempreg) (BFD_RELOC_LO16)
5794 If we have a constant, we need two instructions anyhow,
5795 so we always use the latter form.
5797 If we have a base register, and this is a reference to a
5798 GP relative symbol, we want
5799 addu $tempreg,$breg,$gp
5800 <op> $treg,<sym>($tempreg) (BFD_RELOC_GPREL16)
5802 lui $tempreg,<sym> (BFD_RELOC_HI16_S)
5803 addu $tempreg,$tempreg,$breg
5804 <op> $treg,<sym>($tempreg) (BFD_RELOC_LO16)
5805 With a constant we always use the latter case.
5807 With 64bit address space and no base register and $at usable,
5809 lui $tempreg,<sym> (BFD_RELOC_MIPS_HIGHEST)
5810 lui $at,<sym> (BFD_RELOC_HI16_S)
5811 daddiu $tempreg,<sym> (BFD_RELOC_MIPS_HIGHER)
5814 <op> $treg,<sym>($tempreg) (BFD_RELOC_LO16)
5815 If we have a base register, we want
5816 lui $tempreg,<sym> (BFD_RELOC_MIPS_HIGHEST)
5817 lui $at,<sym> (BFD_RELOC_HI16_S)
5818 daddiu $tempreg,<sym> (BFD_RELOC_MIPS_HIGHER)
5822 <op> $treg,<sym>($tempreg) (BFD_RELOC_LO16)
5824 Without $at we can't generate the optimal path for superscalar
5825 processors here since this would require two temporary registers.
5826 lui $tempreg,<sym> (BFD_RELOC_MIPS_HIGHEST)
5827 daddiu $tempreg,<sym> (BFD_RELOC_MIPS_HIGHER)
5829 daddiu $tempreg,<sym> (BFD_RELOC_HI16_S)
5831 <op> $treg,<sym>($tempreg) (BFD_RELOC_LO16)
5832 If we have a base register, we want
5833 lui $tempreg,<sym> (BFD_RELOC_MIPS_HIGHEST)
5834 daddiu $tempreg,<sym> (BFD_RELOC_MIPS_HIGHER)
5836 daddiu $tempreg,<sym> (BFD_RELOC_HI16_S)
5838 daddu $tempreg,$tempreg,$breg
5839 <op> $treg,<sym>($tempreg) (BFD_RELOC_LO16)
5841 If we have 64-bit addresses, as an optimization, for
5842 addresses which are 32-bit constants (e.g. kseg0/kseg1
5843 addresses) we fall back to the 32-bit address generation
5844 mechanism since it is more efficient. Note that due to
5845 the signed offset used by memory operations, the 32-bit
5846 range is shifted down by 32768 here. This code should
5847 probably attempt to generate 64-bit constants more
5848 efficiently in general.
5850 if ((offset_expr.X_op != O_constant && HAVE_64BIT_ADDRESSES)
5851 || (offset_expr.X_op == O_constant
5852 && !IS_SEXT_32BIT_NUM (offset_expr.X_add_number)
5853 && HAVE_64BIT_ADDRESS_CONSTANTS))
5857 /* We don't do GP optimization for now because RELAX_ENCODE can't
5858 hold the data for such large chunks. */
5860 if (used_at == 0 && ! mips_opts.noat)
5862 macro_build (p, &icnt, &offset_expr, "lui", "t,u",
5863 tempreg, (int) BFD_RELOC_MIPS_HIGHEST);
5864 macro_build (p, &icnt, &offset_expr, "lui", "t,u",
5865 AT, (int) BFD_RELOC_HI16_S);
5866 macro_build (p, &icnt, &offset_expr, "daddiu", "t,r,j",
5867 tempreg, tempreg, (int) BFD_RELOC_MIPS_HIGHER);
5869 macro_build (p, &icnt, (expressionS *) NULL, "daddu",
5870 "d,v,t", AT, AT, breg);
5871 macro_build (p, &icnt, (expressionS *) NULL, "dsll32",
5872 "d,w,<", tempreg, tempreg, 0);
5873 macro_build (p, &icnt, (expressionS *) NULL, "daddu",
5874 "d,v,t", tempreg, tempreg, AT);
5875 macro_build (p, &icnt, &offset_expr, s,
5876 fmt, treg, (int) BFD_RELOC_LO16, tempreg);
5881 macro_build (p, &icnt, &offset_expr, "lui", "t,u",
5882 tempreg, (int) BFD_RELOC_MIPS_HIGHEST);
5883 macro_build (p, &icnt, &offset_expr, "daddiu", "t,r,j",
5884 tempreg, tempreg, (int) BFD_RELOC_MIPS_HIGHER);
5885 macro_build (p, &icnt, (expressionS *) NULL, "dsll",
5886 "d,w,<", tempreg, tempreg, 16);
5887 macro_build (p, &icnt, &offset_expr, "daddiu", "t,r,j",
5888 tempreg, tempreg, (int) BFD_RELOC_HI16_S);
5889 macro_build (p, &icnt, (expressionS *) NULL, "dsll",
5890 "d,w,<", tempreg, tempreg, 16);
5892 macro_build (p, &icnt, (expressionS *) NULL, "daddu",
5893 "d,v,t", tempreg, tempreg, breg);
5894 macro_build (p, &icnt, &offset_expr, s,
5895 fmt, treg, (int) BFD_RELOC_LO16, tempreg);
5900 else if (offset_expr.X_op == O_constant
5901 && !IS_SEXT_32BIT_NUM (offset_expr.X_add_number))
5902 as_bad (_("load/store address overflow (max 32 bits)"));
5906 if ((valueT) offset_expr.X_add_number > MAX_GPREL_OFFSET
5907 || nopic_need_relax (offset_expr.X_add_symbol, 1))
5912 macro_build ((char *) NULL, &icnt, &offset_expr, s, fmt,
5913 treg, (int) BFD_RELOC_GPREL16,
5915 p = frag_var (rs_machine_dependent, 8, 0,
5916 RELAX_ENCODE (4, 8, 0, 4, 0,
5917 (mips_opts.warn_about_macros
5919 && mips_opts.noat))),
5920 offset_expr.X_add_symbol, 0, NULL);
5923 macro_build_lui (p, &icnt, &offset_expr, tempreg);
5926 macro_build (p, &icnt, &offset_expr, s, fmt, treg,
5927 (int) BFD_RELOC_LO16, tempreg);
5931 if ((valueT) offset_expr.X_add_number > MAX_GPREL_OFFSET
5932 || nopic_need_relax (offset_expr.X_add_symbol, 1))
5937 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5938 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
5939 "d,v,t", tempreg, breg, mips_gp_register);
5940 macro_build ((char *) NULL, &icnt, &offset_expr, s, fmt,
5941 treg, (int) BFD_RELOC_GPREL16, tempreg);
5942 p = frag_var (rs_machine_dependent, 12, 0,
5943 RELAX_ENCODE (8, 12, 0, 8, 0, 0),
5944 offset_expr.X_add_symbol, 0, NULL);
5946 macro_build_lui (p, &icnt, &offset_expr, tempreg);
5949 macro_build (p, &icnt, (expressionS *) NULL,
5950 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
5951 "d,v,t", tempreg, tempreg, breg);
5954 macro_build (p, &icnt, &offset_expr, s, fmt, treg,
5955 (int) BFD_RELOC_LO16, tempreg);
5958 else if (mips_pic == SVR4_PIC && ! mips_big_got)
5961 int lw_reloc_type = (int) BFD_RELOC_MIPS_GOT16;
5963 /* If this is a reference to an external symbol, we want
5964 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
5966 <op> $treg,0($tempreg)
5968 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
5970 addiu $tempreg,$tempreg,<sym> (BFD_RELOC_LO16)
5971 <op> $treg,0($tempreg)
5972 If we have NewABI, we want
5973 lw $reg,<sym>($gp) (BFD_RELOC_MIPS_GOT_DISP)
5974 If there is a base register, we add it to $tempreg before
5975 the <op>. If there is a constant, we stick it in the
5976 <op> instruction. We don't handle constants larger than
5977 16 bits, because we have no way to load the upper 16 bits
5978 (actually, we could handle them for the subset of cases
5979 in which we are not using $at). */
5980 assert (offset_expr.X_op == O_symbol);
5981 expr1.X_add_number = offset_expr.X_add_number;
5982 offset_expr.X_add_number = 0;
5984 lw_reloc_type = (int) BFD_RELOC_MIPS_GOT_DISP;
5985 if (expr1.X_add_number < -0x8000
5986 || expr1.X_add_number >= 0x8000)
5987 as_bad (_("PIC code offset overflow (max 16 signed bits)"));
5989 macro_build ((char *) NULL, &icnt, &offset_expr,
5990 HAVE_32BIT_ADDRESSES ? "lw" : "ld", "t,o(b)", tempreg,
5991 (int) lw_reloc_type, mips_gp_register);
5992 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "");
5993 p = frag_var (rs_machine_dependent, 4, 0,
5994 RELAX_ENCODE (0, 4, -8, 0, 0, 0),
5995 offset_expr.X_add_symbol, 0, NULL);
5996 macro_build (p, &icnt, &offset_expr,
5997 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
5998 "t,r,j", tempreg, tempreg, (int) BFD_RELOC_LO16);
6000 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6001 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
6002 "d,v,t", tempreg, tempreg, breg);
6003 macro_build ((char *) NULL, &icnt, &expr1, s, fmt, treg,
6004 (int) BFD_RELOC_LO16, tempreg);
6006 else if (mips_pic == SVR4_PIC)
6011 /* If this is a reference to an external symbol, we want
6012 lui $tempreg,<sym> (BFD_RELOC_MIPS_GOT_HI16)
6013 addu $tempreg,$tempreg,$gp
6014 lw $tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_LO16)
6015 <op> $treg,0($tempreg)
6017 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
6019 addiu $tempreg,$tempreg,<sym> (BFD_RELOC_LO16)
6020 <op> $treg,0($tempreg)
6021 If there is a base register, we add it to $tempreg before
6022 the <op>. If there is a constant, we stick it in the
6023 <op> instruction. We don't handle constants larger than
6024 16 bits, because we have no way to load the upper 16 bits
6025 (actually, we could handle them for the subset of cases
6026 in which we are not using $at).
6029 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT_PAGE)
6030 addiu $tempreg,$tempreg,<sym> (BFD_RELOC_MIPS_GOT_OFST)
6031 <op> $treg,0($tempreg)
6033 assert (offset_expr.X_op == O_symbol);
6034 expr1.X_add_number = offset_expr.X_add_number;
6035 offset_expr.X_add_number = 0;
6036 if (expr1.X_add_number < -0x8000
6037 || expr1.X_add_number >= 0x8000)
6038 as_bad (_("PIC code offset overflow (max 16 signed bits)"));
6041 macro_build ((char *) NULL, &icnt, &offset_expr,
6042 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
6043 "t,o(b)", tempreg, BFD_RELOC_MIPS_GOT_PAGE,
6045 macro_build ((char *) NULL, &icnt, &offset_expr,
6046 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
6047 "t,r,j", tempreg, tempreg,
6048 BFD_RELOC_MIPS_GOT_OFST);
6050 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6051 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
6052 "d,v,t", tempreg, tempreg, breg);
6053 macro_build ((char *) NULL, &icnt, &expr1, s, fmt, treg,
6054 (int) BFD_RELOC_LO16, tempreg);
6061 if (reg_needs_delay (mips_gp_register))
6066 macro_build ((char *) NULL, &icnt, &offset_expr, "lui", "t,u",
6067 tempreg, (int) BFD_RELOC_MIPS_GOT_HI16);
6068 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6069 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
6070 "d,v,t", tempreg, tempreg, mips_gp_register);
6071 macro_build ((char *) NULL, &icnt, &offset_expr,
6072 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
6073 "t,o(b)", tempreg, (int) BFD_RELOC_MIPS_GOT_LO16,
6075 p = frag_var (rs_machine_dependent, 12 + gpdel, 0,
6076 RELAX_ENCODE (12, 12 + gpdel, gpdel, 8 + gpdel, 0, 0),
6077 offset_expr.X_add_symbol, 0, NULL);
6080 macro_build (p, &icnt, (expressionS *) NULL, "nop", "");
6083 macro_build (p, &icnt, &offset_expr,
6084 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
6085 "t,o(b)", tempreg, (int) BFD_RELOC_MIPS_GOT16,
6088 macro_build (p, &icnt, (expressionS *) NULL, "nop", "");
6090 macro_build (p, &icnt, &offset_expr,
6091 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
6092 "t,r,j", tempreg, tempreg, (int) BFD_RELOC_LO16);
6094 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6095 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
6096 "d,v,t", tempreg, tempreg, breg);
6097 macro_build ((char *) NULL, &icnt, &expr1, s, fmt, treg,
6098 (int) BFD_RELOC_LO16, tempreg);
6100 else if (mips_pic == EMBEDDED_PIC)
6102 /* If there is no base register, we want
6103 <op> $treg,<sym>($gp) (BFD_RELOC_GPREL16)
6104 If there is a base register, we want
6105 addu $tempreg,$breg,$gp
6106 <op> $treg,<sym>($tempreg) (BFD_RELOC_GPREL16)
6108 assert (offset_expr.X_op == O_symbol);
6111 macro_build ((char *) NULL, &icnt, &offset_expr, s, fmt,
6112 treg, (int) BFD_RELOC_GPREL16, mips_gp_register);
6117 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6118 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
6119 "d,v,t", tempreg, breg, mips_gp_register);
6120 macro_build ((char *) NULL, &icnt, &offset_expr, s, fmt,
6121 treg, (int) BFD_RELOC_GPREL16, tempreg);
6134 load_register (&icnt, treg, &imm_expr, 0);
6138 load_register (&icnt, treg, &imm_expr, 1);
6142 if (imm_expr.X_op == O_constant)
6144 load_register (&icnt, AT, &imm_expr, 0);
6145 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6146 "mtc1", "t,G", AT, treg);
6151 assert (offset_expr.X_op == O_symbol
6152 && strcmp (segment_name (S_GET_SEGMENT
6153 (offset_expr.X_add_symbol)),
6155 && offset_expr.X_add_number == 0);
6156 macro_build ((char *) NULL, &icnt, &offset_expr, "lwc1", "T,o(b)",
6157 treg, (int) BFD_RELOC_MIPS_LITERAL, mips_gp_register);
6162 /* Check if we have a constant in IMM_EXPR. If the GPRs are 64 bits
6163 wide, IMM_EXPR is the entire value. Otherwise IMM_EXPR is the high
6164 order 32 bits of the value and the low order 32 bits are either
6165 zero or in OFFSET_EXPR. */
6166 if (imm_expr.X_op == O_constant || imm_expr.X_op == O_big)
6168 if (HAVE_64BIT_GPRS)
6169 load_register (&icnt, treg, &imm_expr, 1);
6174 if (target_big_endian)
6186 load_register (&icnt, hreg, &imm_expr, 0);
6189 if (offset_expr.X_op == O_absent)
6190 move_register (&icnt, lreg, 0);
6193 assert (offset_expr.X_op == O_constant);
6194 load_register (&icnt, lreg, &offset_expr, 0);
6201 /* We know that sym is in the .rdata section. First we get the
6202 upper 16 bits of the address. */
6203 if (mips_pic == NO_PIC)
6205 macro_build_lui (NULL, &icnt, &offset_expr, AT);
6207 else if (mips_pic == SVR4_PIC)
6209 macro_build ((char *) NULL, &icnt, &offset_expr,
6210 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
6211 "t,o(b)", AT, (int) BFD_RELOC_MIPS_GOT16,
6214 else if (mips_pic == EMBEDDED_PIC)
6216 /* For embedded PIC we pick up the entire address off $gp in
6217 a single instruction. */
6218 macro_build ((char *) NULL, &icnt, &offset_expr,
6219 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu", "t,r,j", AT,
6220 mips_gp_register, (int) BFD_RELOC_GPREL16);
6221 offset_expr.X_op = O_constant;
6222 offset_expr.X_add_number = 0;
6227 /* Now we load the register(s). */
6228 if (HAVE_64BIT_GPRS)
6229 macro_build ((char *) NULL, &icnt, &offset_expr, "ld", "t,o(b)",
6230 treg, (int) BFD_RELOC_LO16, AT);
6233 macro_build ((char *) NULL, &icnt, &offset_expr, "lw", "t,o(b)",
6234 treg, (int) BFD_RELOC_LO16, AT);
6237 /* FIXME: How in the world do we deal with the possible
6239 offset_expr.X_add_number += 4;
6240 macro_build ((char *) NULL, &icnt, &offset_expr, "lw", "t,o(b)",
6241 treg + 1, (int) BFD_RELOC_LO16, AT);
6245 /* To avoid confusion in tc_gen_reloc, we must ensure that this
6246 does not become a variant frag. */
6247 frag_wane (frag_now);
6253 /* Check if we have a constant in IMM_EXPR. If the FPRs are 64 bits
6254 wide, IMM_EXPR is the entire value and the GPRs are known to be 64
6255 bits wide as well. Otherwise IMM_EXPR is the high order 32 bits of
6256 the value and the low order 32 bits are either zero or in
6258 if (imm_expr.X_op == O_constant || imm_expr.X_op == O_big)
6260 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_FPRS);
6261 if (HAVE_64BIT_FPRS)
6263 assert (HAVE_64BIT_GPRS);
6264 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6265 "dmtc1", "t,S", AT, treg);
6269 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6270 "mtc1", "t,G", AT, treg + 1);
6271 if (offset_expr.X_op == O_absent)
6272 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6273 "mtc1", "t,G", 0, treg);
6276 assert (offset_expr.X_op == O_constant);
6277 load_register (&icnt, AT, &offset_expr, 0);
6278 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6279 "mtc1", "t,G", AT, treg);
6285 assert (offset_expr.X_op == O_symbol
6286 && offset_expr.X_add_number == 0);
6287 s = segment_name (S_GET_SEGMENT (offset_expr.X_add_symbol));
6288 if (strcmp (s, ".lit8") == 0)
6290 if (mips_opts.isa != ISA_MIPS1)
6292 macro_build ((char *) NULL, &icnt, &offset_expr, "ldc1",
6293 "T,o(b)", treg, (int) BFD_RELOC_MIPS_LITERAL,
6297 breg = mips_gp_register;
6298 r = BFD_RELOC_MIPS_LITERAL;
6303 assert (strcmp (s, RDATA_SECTION_NAME) == 0);
6304 if (mips_pic == SVR4_PIC)
6305 macro_build ((char *) NULL, &icnt, &offset_expr,
6306 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
6307 "t,o(b)", AT, (int) BFD_RELOC_MIPS_GOT16,
6311 /* FIXME: This won't work for a 64 bit address. */
6312 macro_build_lui (NULL, &icnt, &offset_expr, AT);
6315 if (mips_opts.isa != ISA_MIPS1)
6317 macro_build ((char *) NULL, &icnt, &offset_expr, "ldc1",
6318 "T,o(b)", treg, (int) BFD_RELOC_LO16, AT);
6320 /* To avoid confusion in tc_gen_reloc, we must ensure
6321 that this does not become a variant frag. */
6322 frag_wane (frag_now);
6333 if (mips_arch == CPU_R4650)
6335 as_bad (_("opcode not supported on this processor"));
6338 /* Even on a big endian machine $fn comes before $fn+1. We have
6339 to adjust when loading from memory. */
6342 assert (mips_opts.isa == ISA_MIPS1);
6343 macro_build ((char *) NULL, &icnt, &offset_expr, "lwc1", "T,o(b)",
6344 target_big_endian ? treg + 1 : treg,
6346 /* FIXME: A possible overflow which I don't know how to deal
6348 offset_expr.X_add_number += 4;
6349 macro_build ((char *) NULL, &icnt, &offset_expr, "lwc1", "T,o(b)",
6350 target_big_endian ? treg : treg + 1,
6353 /* To avoid confusion in tc_gen_reloc, we must ensure that this
6354 does not become a variant frag. */
6355 frag_wane (frag_now);
6364 * The MIPS assembler seems to check for X_add_number not
6365 * being double aligned and generating:
6368 * addiu at,at,%lo(foo+1)
6371 * But, the resulting address is the same after relocation so why
6372 * generate the extra instruction?
6374 if (mips_arch == CPU_R4650)
6376 as_bad (_("opcode not supported on this processor"));
6379 /* Itbl support may require additional care here. */
6381 if (mips_opts.isa != ISA_MIPS1)
6392 if (mips_arch == CPU_R4650)
6394 as_bad (_("opcode not supported on this processor"));
6398 if (mips_opts.isa != ISA_MIPS1)
6406 /* Itbl support may require additional care here. */
6411 if (HAVE_64BIT_GPRS)
6422 if (HAVE_64BIT_GPRS)
6432 /* We do _not_ bother to allow embedded PIC (symbol-local_symbol)
6433 loads for the case of doing a pair of loads to simulate an 'ld'.
6434 This is not currently done by the compiler, and assembly coders
6435 writing embedded-pic code can cope. */
6437 if (offset_expr.X_op != O_symbol
6438 && offset_expr.X_op != O_constant)
6440 as_bad (_("expression too complex"));
6441 offset_expr.X_op = O_constant;
6444 /* Even on a big endian machine $fn comes before $fn+1. We have
6445 to adjust when loading from memory. We set coproc if we must
6446 load $fn+1 first. */
6447 /* Itbl support may require additional care here. */
6448 if (! target_big_endian)
6451 if (mips_pic == NO_PIC
6452 || offset_expr.X_op == O_constant)
6456 /* If this is a reference to a GP relative symbol, we want
6457 <op> $treg,<sym>($gp) (BFD_RELOC_GPREL16)
6458 <op> $treg+1,<sym>+4($gp) (BFD_RELOC_GPREL16)
6459 If we have a base register, we use this
6461 <op> $treg,<sym>($at) (BFD_RELOC_GPREL16)
6462 <op> $treg+1,<sym>+4($at) (BFD_RELOC_GPREL16)
6463 If this is not a GP relative symbol, we want
6464 lui $at,<sym> (BFD_RELOC_HI16_S)
6465 <op> $treg,<sym>($at) (BFD_RELOC_LO16)
6466 <op> $treg+1,<sym>+4($at) (BFD_RELOC_LO16)
6467 If there is a base register, we add it to $at after the
6468 lui instruction. If there is a constant, we always use
6470 if ((valueT) offset_expr.X_add_number > MAX_GPREL_OFFSET
6471 || nopic_need_relax (offset_expr.X_add_symbol, 1))
6483 tempreg = mips_gp_register;
6490 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6491 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
6492 "d,v,t", AT, breg, mips_gp_register);
6498 /* Itbl support may require additional care here. */
6499 macro_build ((char *) NULL, &icnt, &offset_expr, s, fmt,
6500 coproc ? treg + 1 : treg,
6501 (int) BFD_RELOC_GPREL16, tempreg);
6502 offset_expr.X_add_number += 4;
6504 /* Set mips_optimize to 2 to avoid inserting an
6506 hold_mips_optimize = mips_optimize;
6508 /* Itbl support may require additional care here. */
6509 macro_build ((char *) NULL, &icnt, &offset_expr, s, fmt,
6510 coproc ? treg : treg + 1,
6511 (int) BFD_RELOC_GPREL16, tempreg);
6512 mips_optimize = hold_mips_optimize;
6514 p = frag_var (rs_machine_dependent, 12 + off, 0,
6515 RELAX_ENCODE (8 + off, 12 + off, 0, 4 + off, 1,
6516 used_at && mips_opts.noat),
6517 offset_expr.X_add_symbol, 0, NULL);
6519 /* We just generated two relocs. When tc_gen_reloc
6520 handles this case, it will skip the first reloc and
6521 handle the second. The second reloc already has an
6522 extra addend of 4, which we added above. We must
6523 subtract it out, and then subtract another 4 to make
6524 the first reloc come out right. The second reloc
6525 will come out right because we are going to add 4 to
6526 offset_expr when we build its instruction below.
6528 If we have a symbol, then we don't want to include
6529 the offset, because it will wind up being included
6530 when we generate the reloc. */
6532 if (offset_expr.X_op == O_constant)
6533 offset_expr.X_add_number -= 8;
6536 offset_expr.X_add_number = -4;
6537 offset_expr.X_op = O_constant;
6540 macro_build_lui (p, &icnt, &offset_expr, AT);
6545 macro_build (p, &icnt, (expressionS *) NULL,
6546 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
6547 "d,v,t", AT, breg, AT);
6551 /* Itbl support may require additional care here. */
6552 macro_build (p, &icnt, &offset_expr, s, fmt,
6553 coproc ? treg + 1 : treg,
6554 (int) BFD_RELOC_LO16, AT);
6557 /* FIXME: How do we handle overflow here? */
6558 offset_expr.X_add_number += 4;
6559 /* Itbl support may require additional care here. */
6560 macro_build (p, &icnt, &offset_expr, s, fmt,
6561 coproc ? treg : treg + 1,
6562 (int) BFD_RELOC_LO16, AT);
6564 else if (mips_pic == SVR4_PIC && ! mips_big_got)
6568 /* If this is a reference to an external symbol, we want
6569 lw $at,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
6574 lw $at,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
6576 <op> $treg,<sym>($at) (BFD_RELOC_LO16)
6577 <op> $treg+1,<sym>+4($at) (BFD_RELOC_LO16)
6578 If there is a base register we add it to $at before the
6579 lwc1 instructions. If there is a constant we include it
6580 in the lwc1 instructions. */
6582 expr1.X_add_number = offset_expr.X_add_number;
6583 offset_expr.X_add_number = 0;
6584 if (expr1.X_add_number < -0x8000
6585 || expr1.X_add_number >= 0x8000 - 4)
6586 as_bad (_("PIC code offset overflow (max 16 signed bits)"));
6591 frag_grow (24 + off);
6592 macro_build ((char *) NULL, &icnt, &offset_expr,
6593 HAVE_32BIT_ADDRESSES ? "lw" : "ld", "t,o(b)", AT,
6594 (int) BFD_RELOC_MIPS_GOT16, mips_gp_register);
6595 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "");
6597 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6598 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
6599 "d,v,t", AT, breg, AT);
6600 /* Itbl support may require additional care here. */
6601 macro_build ((char *) NULL, &icnt, &expr1, s, fmt,
6602 coproc ? treg + 1 : treg,
6603 (int) BFD_RELOC_LO16, AT);
6604 expr1.X_add_number += 4;
6606 /* Set mips_optimize to 2 to avoid inserting an undesired
6608 hold_mips_optimize = mips_optimize;
6610 /* Itbl support may require additional care here. */
6611 macro_build ((char *) NULL, &icnt, &expr1, s, fmt,
6612 coproc ? treg : treg + 1,
6613 (int) BFD_RELOC_LO16, AT);
6614 mips_optimize = hold_mips_optimize;
6616 (void) frag_var (rs_machine_dependent, 0, 0,
6617 RELAX_ENCODE (0, 0, -16 - off, -8, 1, 0),
6618 offset_expr.X_add_symbol, 0, NULL);
6620 else if (mips_pic == SVR4_PIC)
6625 /* If this is a reference to an external symbol, we want
6626 lui $at,<sym> (BFD_RELOC_MIPS_GOT_HI16)
6628 lw $at,<sym>($at) (BFD_RELOC_MIPS_GOT_LO16)
6633 lw $at,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
6635 <op> $treg,<sym>($at) (BFD_RELOC_LO16)
6636 <op> $treg+1,<sym>+4($at) (BFD_RELOC_LO16)
6637 If there is a base register we add it to $at before the
6638 lwc1 instructions. If there is a constant we include it
6639 in the lwc1 instructions. */
6641 expr1.X_add_number = offset_expr.X_add_number;
6642 offset_expr.X_add_number = 0;
6643 if (expr1.X_add_number < -0x8000
6644 || expr1.X_add_number >= 0x8000 - 4)
6645 as_bad (_("PIC code offset overflow (max 16 signed bits)"));
6646 if (reg_needs_delay (mips_gp_register))
6655 macro_build ((char *) NULL, &icnt, &offset_expr, "lui", "t,u",
6656 AT, (int) BFD_RELOC_MIPS_GOT_HI16);
6657 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6658 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
6659 "d,v,t", AT, AT, mips_gp_register);
6660 macro_build ((char *) NULL, &icnt, &offset_expr,
6661 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
6662 "t,o(b)", AT, (int) BFD_RELOC_MIPS_GOT_LO16, AT);
6663 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "");
6665 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6666 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
6667 "d,v,t", AT, breg, AT);
6668 /* Itbl support may require additional care here. */
6669 macro_build ((char *) NULL, &icnt, &expr1, s, fmt,
6670 coproc ? treg + 1 : treg,
6671 (int) BFD_RELOC_LO16, AT);
6672 expr1.X_add_number += 4;
6674 /* Set mips_optimize to 2 to avoid inserting an undesired
6676 hold_mips_optimize = mips_optimize;
6678 /* Itbl support may require additional care here. */
6679 macro_build ((char *) NULL, &icnt, &expr1, s, fmt,
6680 coproc ? treg : treg + 1,
6681 (int) BFD_RELOC_LO16, AT);
6682 mips_optimize = hold_mips_optimize;
6683 expr1.X_add_number -= 4;
6685 p = frag_var (rs_machine_dependent, 16 + gpdel + off, 0,
6686 RELAX_ENCODE (24 + off, 16 + gpdel + off, gpdel,
6687 8 + gpdel + off, 1, 0),
6688 offset_expr.X_add_symbol, 0, NULL);
6691 macro_build (p, &icnt, (expressionS *) NULL, "nop", "");
6694 macro_build (p, &icnt, &offset_expr,
6695 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
6696 "t,o(b)", AT, (int) BFD_RELOC_MIPS_GOT16,
6699 macro_build (p, &icnt, (expressionS *) NULL, "nop", "");
6703 macro_build (p, &icnt, (expressionS *) NULL,
6704 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
6705 "d,v,t", AT, breg, AT);
6708 /* Itbl support may require additional care here. */
6709 macro_build (p, &icnt, &expr1, s, fmt,
6710 coproc ? treg + 1 : treg,
6711 (int) BFD_RELOC_LO16, AT);
6713 expr1.X_add_number += 4;
6715 /* Set mips_optimize to 2 to avoid inserting an undesired
6717 hold_mips_optimize = mips_optimize;
6719 /* Itbl support may require additional care here. */
6720 macro_build (p, &icnt, &expr1, s, fmt,
6721 coproc ? treg : treg + 1,
6722 (int) BFD_RELOC_LO16, AT);
6723 mips_optimize = hold_mips_optimize;
6725 else if (mips_pic == EMBEDDED_PIC)
6727 /* If there is no base register, we use
6728 <op> $treg,<sym>($gp) (BFD_RELOC_GPREL16)
6729 <op> $treg+1,<sym>+4($gp) (BFD_RELOC_GPREL16)
6730 If we have a base register, we use
6732 <op> $treg,<sym>($at) (BFD_RELOC_GPREL16)
6733 <op> $treg+1,<sym>+4($at) (BFD_RELOC_GPREL16)
6737 tempreg = mips_gp_register;
6742 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6743 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
6744 "d,v,t", AT, breg, mips_gp_register);
6749 /* Itbl support may require additional care here. */
6750 macro_build ((char *) NULL, &icnt, &offset_expr, s, fmt,
6751 coproc ? treg + 1 : treg,
6752 (int) BFD_RELOC_GPREL16, tempreg);
6753 offset_expr.X_add_number += 4;
6754 /* Itbl support may require additional care here. */
6755 macro_build ((char *) NULL, &icnt, &offset_expr, s, fmt,
6756 coproc ? treg : treg + 1,
6757 (int) BFD_RELOC_GPREL16, tempreg);
6773 assert (HAVE_32BIT_ADDRESSES);
6774 macro_build ((char *) NULL, &icnt, &offset_expr, s, "t,o(b)", treg,
6775 (int) BFD_RELOC_LO16, breg);
6776 offset_expr.X_add_number += 4;
6777 macro_build ((char *) NULL, &icnt, &offset_expr, s, "t,o(b)", treg + 1,
6778 (int) BFD_RELOC_LO16, breg);
6781 /* New code added to support COPZ instructions.
6782 This code builds table entries out of the macros in mip_opcodes.
6783 R4000 uses interlocks to handle coproc delays.
6784 Other chips (like the R3000) require nops to be inserted for delays.
6786 FIXME: Currently, we require that the user handle delays.
6787 In order to fill delay slots for non-interlocked chips,
6788 we must have a way to specify delays based on the coprocessor.
6789 Eg. 4 cycles if load coproc reg from memory, 1 if in cache, etc.
6790 What are the side-effects of the cop instruction?
6791 What cache support might we have and what are its effects?
6792 Both coprocessor & memory require delays. how long???
6793 What registers are read/set/modified?
6795 If an itbl is provided to interpret cop instructions,
6796 this knowledge can be encoded in the itbl spec. */
6810 /* For now we just do C (same as Cz). The parameter will be
6811 stored in insn_opcode by mips_ip. */
6812 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "C",
6817 move_register (&icnt, dreg, sreg);
6820 #ifdef LOSING_COMPILER
6822 /* Try and see if this is a new itbl instruction.
6823 This code builds table entries out of the macros in mip_opcodes.
6824 FIXME: For now we just assemble the expression and pass it's
6825 value along as a 32-bit immediate.
6826 We may want to have the assembler assemble this value,
6827 so that we gain the assembler's knowledge of delay slots,
6829 Would it be more efficient to use mask (id) here? */
6830 if (itbl_have_entries
6831 && (immed_expr = itbl_assemble (ip->insn_mo->name, "")))
6833 s = ip->insn_mo->name;
6835 coproc = ITBL_DECODE_PNUM (immed_expr);;
6836 macro_build ((char *) NULL, &icnt, &immed_expr, s, "C");
6843 as_warn (_("Macro used $at after \".set noat\""));
6848 struct mips_cl_insn *ip;
6850 register int treg, sreg, dreg, breg;
6866 bfd_reloc_code_real_type r;
6869 treg = (ip->insn_opcode >> 16) & 0x1f;
6870 dreg = (ip->insn_opcode >> 11) & 0x1f;
6871 sreg = breg = (ip->insn_opcode >> 21) & 0x1f;
6872 mask = ip->insn_mo->mask;
6874 expr1.X_op = O_constant;
6875 expr1.X_op_symbol = NULL;
6876 expr1.X_add_symbol = NULL;
6877 expr1.X_add_number = 1;
6881 #endif /* LOSING_COMPILER */
6886 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6887 dbl ? "dmultu" : "multu", "s,t", sreg, treg);
6888 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "mflo", "d",
6895 /* The MIPS assembler some times generates shifts and adds. I'm
6896 not trying to be that fancy. GCC should do this for us
6898 load_register (&icnt, AT, &imm_expr, dbl);
6899 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6900 dbl ? "dmult" : "mult", "s,t", sreg, AT);
6901 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "mflo", "d",
6915 mips_emit_delays (TRUE);
6916 ++mips_opts.noreorder;
6917 mips_any_noreorder = 1;
6919 load_register (&icnt, AT, &imm_expr, dbl);
6920 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6921 dbl ? "dmult" : "mult", "s,t", sreg, imm ? AT : treg);
6922 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "mflo", "d",
6924 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6925 dbl ? "dsra32" : "sra", "d,w,<", dreg, dreg, RA);
6926 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "mfhi", "d",
6929 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "tne",
6930 "s,t,q", dreg, AT, 6);
6933 expr1.X_add_number = 8;
6934 macro_build ((char *) NULL, &icnt, &expr1, "beq", "s,t,p", dreg,
6936 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "",
6938 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "break",
6941 --mips_opts.noreorder;
6942 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "mflo", "d", dreg);
6955 mips_emit_delays (TRUE);
6956 ++mips_opts.noreorder;
6957 mips_any_noreorder = 1;
6959 load_register (&icnt, AT, &imm_expr, dbl);
6960 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6961 dbl ? "dmultu" : "multu",
6962 "s,t", sreg, imm ? AT : treg);
6963 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "mfhi", "d",
6965 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "mflo", "d",
6968 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "tne",
6972 expr1.X_add_number = 8;
6973 macro_build ((char *) NULL, &icnt, &expr1, "beq", "s,t,p", AT, 0);
6974 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "",
6976 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "break",
6979 --mips_opts.noreorder;
6983 if (ISA_HAS_DROR (mips_opts.isa) || CPU_HAS_DROR (mips_arch))
6995 macro_build ((char *) NULL, &icnt, NULL, "dnegu",
6996 "d,w", tempreg, treg);
6997 macro_build ((char *) NULL, &icnt, NULL, "drorv",
6998 "d,t,s", dreg, sreg, tempreg);
7003 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "dsubu",
7004 "d,v,t", AT, 0, treg);
7005 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "dsrlv",
7006 "d,t,s", AT, sreg, AT);
7007 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "dsllv",
7008 "d,t,s", dreg, sreg, treg);
7009 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or",
7010 "d,v,t", dreg, dreg, AT);
7014 if (ISA_HAS_ROR (mips_opts.isa) || CPU_HAS_ROR (mips_arch))
7026 macro_build ((char *) NULL, &icnt, NULL, "negu",
7027 "d,w", tempreg, treg);
7028 macro_build ((char *) NULL, &icnt, NULL, "rorv",
7029 "d,t,s", dreg, sreg, tempreg);
7034 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "subu",
7035 "d,v,t", AT, 0, treg);
7036 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "srlv",
7037 "d,t,s", AT, sreg, AT);
7038 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sllv",
7039 "d,t,s", dreg, sreg, treg);
7040 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or",
7041 "d,v,t", dreg, dreg, AT);
7049 if (imm_expr.X_op != O_constant)
7050 as_bad (_("Improper rotate count"));
7051 rot = imm_expr.X_add_number & 0x3f;
7052 if (ISA_HAS_DROR (mips_opts.isa) || CPU_HAS_DROR (mips_arch))
7054 rot = (64 - rot) & 0x3f;
7056 macro_build ((char *) NULL, &icnt, NULL, "dror32",
7057 "d,w,<", dreg, sreg, rot - 32);
7059 macro_build ((char *) NULL, &icnt, NULL, "dror",
7060 "d,w,<", dreg, sreg, rot);
7065 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "dsrl",
7066 "d,w,<", dreg, sreg, 0);
7069 l = (rot < 0x20) ? "dsll" : "dsll32";
7070 r = ((0x40 - rot) < 0x20) ? "dsrl" : "dsrl32";
7072 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, l,
7073 "d,w,<", AT, sreg, rot);
7074 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, r,
7075 "d,w,<", dreg, sreg, (0x20 - rot) & 0x1f);
7076 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or",
7077 "d,v,t", dreg, dreg, AT);
7085 if (imm_expr.X_op != O_constant)
7086 as_bad (_("Improper rotate count"));
7087 rot = imm_expr.X_add_number & 0x1f;
7088 if (ISA_HAS_ROR (mips_opts.isa) || CPU_HAS_ROR (mips_arch))
7090 macro_build ((char *) NULL, &icnt, NULL, "ror",
7091 "d,w,<", dreg, sreg, (32 - rot) & 0x1f);
7096 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "srl",
7097 "d,w,<", dreg, sreg, 0);
7100 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sll",
7101 "d,w,<", AT, sreg, rot);
7102 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "srl",
7103 "d,w,<", dreg, sreg, (0x20 - rot) & 0x1f);
7104 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or",
7105 "d,v,t", dreg, dreg, AT);
7110 if (ISA_HAS_DROR (mips_opts.isa) || CPU_HAS_DROR (mips_arch))
7112 macro_build ((char *) NULL, &icnt, NULL, "drorv",
7113 "d,t,s", dreg, sreg, treg);
7116 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "dsubu",
7117 "d,v,t", AT, 0, treg);
7118 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "dsllv",
7119 "d,t,s", AT, sreg, AT);
7120 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "dsrlv",
7121 "d,t,s", dreg, sreg, treg);
7122 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or",
7123 "d,v,t", dreg, dreg, AT);
7127 if (ISA_HAS_ROR (mips_opts.isa) || CPU_HAS_ROR (mips_arch))
7129 macro_build ((char *) NULL, &icnt, NULL, "rorv",
7130 "d,t,s", dreg, sreg, treg);
7133 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "subu",
7134 "d,v,t", AT, 0, treg);
7135 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sllv",
7136 "d,t,s", AT, sreg, AT);
7137 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "srlv",
7138 "d,t,s", dreg, sreg, treg);
7139 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or",
7140 "d,v,t", dreg, dreg, AT);
7148 if (imm_expr.X_op != O_constant)
7149 as_bad (_("Improper rotate count"));
7150 rot = imm_expr.X_add_number & 0x3f;
7151 if (ISA_HAS_DROR (mips_opts.isa) || CPU_HAS_DROR (mips_arch))
7154 macro_build ((char *) NULL, &icnt, NULL, "dror32",
7155 "d,w,<", dreg, sreg, rot - 32);
7157 macro_build ((char *) NULL, &icnt, NULL, "dror",
7158 "d,w,<", dreg, sreg, rot);
7163 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "dsrl",
7164 "d,w,<", dreg, sreg, 0);
7167 r = (rot < 0x20) ? "dsrl" : "dsrl32";
7168 l = ((0x40 - rot) < 0x20) ? "dsll" : "dsll32";
7170 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, r,
7171 "d,w,<", AT, sreg, rot);
7172 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, l,
7173 "d,w,<", dreg, sreg, (0x20 - rot) & 0x1f);
7174 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or",
7175 "d,v,t", dreg, dreg, AT);
7183 if (imm_expr.X_op != O_constant)
7184 as_bad (_("Improper rotate count"));
7185 rot = imm_expr.X_add_number & 0x1f;
7186 if (ISA_HAS_ROR (mips_opts.isa) || CPU_HAS_ROR (mips_arch))
7188 macro_build ((char *) NULL, &icnt, NULL, "ror",
7189 "d,w,<", dreg, sreg, rot);
7194 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "srl",
7195 "d,w,<", dreg, sreg, 0);
7198 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "srl",
7199 "d,w,<", AT, sreg, rot);
7200 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sll",
7201 "d,w,<", dreg, sreg, (0x20 - rot) & 0x1f);
7202 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or",
7203 "d,v,t", dreg, dreg, AT);
7208 if (mips_arch == CPU_R4650)
7210 as_bad (_("opcode not supported on this processor"));
7213 assert (mips_opts.isa == ISA_MIPS1);
7214 /* Even on a big endian machine $fn comes before $fn+1. We have
7215 to adjust when storing to memory. */
7216 macro_build ((char *) NULL, &icnt, &offset_expr, "swc1", "T,o(b)",
7217 target_big_endian ? treg + 1 : treg,
7218 (int) BFD_RELOC_LO16, breg);
7219 offset_expr.X_add_number += 4;
7220 macro_build ((char *) NULL, &icnt, &offset_expr, "swc1", "T,o(b)",
7221 target_big_endian ? treg : treg + 1,
7222 (int) BFD_RELOC_LO16, breg);
7227 macro_build ((char *) NULL, &icnt, &expr1, "sltiu", "t,r,j", dreg,
7228 treg, (int) BFD_RELOC_LO16);
7230 macro_build ((char *) NULL, &icnt, &expr1, "sltiu", "t,r,j", dreg,
7231 sreg, (int) BFD_RELOC_LO16);
7234 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "xor",
7235 "d,v,t", dreg, sreg, treg);
7236 macro_build ((char *) NULL, &icnt, &expr1, "sltiu", "t,r,j", dreg,
7237 dreg, (int) BFD_RELOC_LO16);
7242 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
7244 macro_build ((char *) NULL, &icnt, &expr1, "sltiu", "t,r,j", dreg,
7245 sreg, (int) BFD_RELOC_LO16);
7250 as_warn (_("Instruction %s: result is always false"),
7252 move_register (&icnt, dreg, 0);
7255 if (imm_expr.X_op == O_constant
7256 && imm_expr.X_add_number >= 0
7257 && imm_expr.X_add_number < 0x10000)
7259 macro_build ((char *) NULL, &icnt, &imm_expr, "xori", "t,r,i", dreg,
7260 sreg, (int) BFD_RELOC_LO16);
7263 else if (imm_expr.X_op == O_constant
7264 && imm_expr.X_add_number > -0x8000
7265 && imm_expr.X_add_number < 0)
7267 imm_expr.X_add_number = -imm_expr.X_add_number;
7268 macro_build ((char *) NULL, &icnt, &imm_expr,
7269 HAVE_32BIT_GPRS ? "addiu" : "daddiu",
7270 "t,r,j", dreg, sreg,
7271 (int) BFD_RELOC_LO16);
7276 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_GPRS);
7277 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "xor",
7278 "d,v,t", dreg, sreg, AT);
7281 macro_build ((char *) NULL, &icnt, &expr1, "sltiu", "t,r,j", dreg, dreg,
7282 (int) BFD_RELOC_LO16);
7287 case M_SGE: /* sreg >= treg <==> not (sreg < treg) */
7293 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "d,v,t",
7295 macro_build ((char *) NULL, &icnt, &expr1, "xori", "t,r,i", dreg, dreg,
7296 (int) BFD_RELOC_LO16);
7299 case M_SGE_I: /* sreg >= I <==> not (sreg < I) */
7301 if (imm_expr.X_op == O_constant
7302 && imm_expr.X_add_number >= -0x8000
7303 && imm_expr.X_add_number < 0x8000)
7305 macro_build ((char *) NULL, &icnt, &imm_expr,
7306 mask == M_SGE_I ? "slti" : "sltiu",
7307 "t,r,j", dreg, sreg, (int) BFD_RELOC_LO16);
7312 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_GPRS);
7313 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7314 mask == M_SGE_I ? "slt" : "sltu", "d,v,t", dreg, sreg,
7318 macro_build ((char *) NULL, &icnt, &expr1, "xori", "t,r,i", dreg, dreg,
7319 (int) BFD_RELOC_LO16);
7324 case M_SGT: /* sreg > treg <==> treg < sreg */
7330 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "d,v,t",
7334 case M_SGT_I: /* sreg > I <==> I < sreg */
7340 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_GPRS);
7341 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "d,v,t",
7345 case M_SLE: /* sreg <= treg <==> treg >= sreg <==> not (treg < sreg) */
7351 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "d,v,t",
7353 macro_build ((char *) NULL, &icnt, &expr1, "xori", "t,r,i", dreg, dreg,
7354 (int) BFD_RELOC_LO16);
7357 case M_SLE_I: /* sreg <= I <==> I >= sreg <==> not (I < sreg) */
7363 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_GPRS);
7364 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "d,v,t",
7366 macro_build ((char *) NULL, &icnt, &expr1, "xori", "t,r,i", dreg, dreg,
7367 (int) BFD_RELOC_LO16);
7371 if (imm_expr.X_op == O_constant
7372 && imm_expr.X_add_number >= -0x8000
7373 && imm_expr.X_add_number < 0x8000)
7375 macro_build ((char *) NULL, &icnt, &imm_expr, "slti", "t,r,j",
7376 dreg, sreg, (int) BFD_RELOC_LO16);
7379 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_GPRS);
7380 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "slt", "d,v,t",
7385 if (imm_expr.X_op == O_constant
7386 && imm_expr.X_add_number >= -0x8000
7387 && imm_expr.X_add_number < 0x8000)
7389 macro_build ((char *) NULL, &icnt, &imm_expr, "sltiu", "t,r,j",
7390 dreg, sreg, (int) BFD_RELOC_LO16);
7393 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_GPRS);
7394 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sltu",
7395 "d,v,t", dreg, sreg, AT);
7400 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sltu",
7401 "d,v,t", dreg, 0, treg);
7403 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sltu",
7404 "d,v,t", dreg, 0, sreg);
7407 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "xor",
7408 "d,v,t", dreg, sreg, treg);
7409 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sltu",
7410 "d,v,t", dreg, 0, dreg);
7415 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
7417 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sltu",
7418 "d,v,t", dreg, 0, sreg);
7423 as_warn (_("Instruction %s: result is always true"),
7425 macro_build ((char *) NULL, &icnt, &expr1,
7426 HAVE_32BIT_GPRS ? "addiu" : "daddiu",
7427 "t,r,j", dreg, 0, (int) BFD_RELOC_LO16);
7430 if (imm_expr.X_op == O_constant
7431 && imm_expr.X_add_number >= 0
7432 && imm_expr.X_add_number < 0x10000)
7434 macro_build ((char *) NULL, &icnt, &imm_expr, "xori", "t,r,i",
7435 dreg, sreg, (int) BFD_RELOC_LO16);
7438 else if (imm_expr.X_op == O_constant
7439 && imm_expr.X_add_number > -0x8000
7440 && imm_expr.X_add_number < 0)
7442 imm_expr.X_add_number = -imm_expr.X_add_number;
7443 macro_build ((char *) NULL, &icnt, &imm_expr,
7444 HAVE_32BIT_GPRS ? "addiu" : "daddiu",
7445 "t,r,j", dreg, sreg, (int) BFD_RELOC_LO16);
7450 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_GPRS);
7451 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "xor",
7452 "d,v,t", dreg, sreg, AT);
7455 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sltu",
7456 "d,v,t", dreg, 0, dreg);
7464 if (imm_expr.X_op == O_constant
7465 && imm_expr.X_add_number > -0x8000
7466 && imm_expr.X_add_number <= 0x8000)
7468 imm_expr.X_add_number = -imm_expr.X_add_number;
7469 macro_build ((char *) NULL, &icnt, &imm_expr,
7470 dbl ? "daddi" : "addi",
7471 "t,r,j", dreg, sreg, (int) BFD_RELOC_LO16);
7474 load_register (&icnt, AT, &imm_expr, dbl);
7475 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7476 dbl ? "dsub" : "sub", "d,v,t", dreg, sreg, AT);
7482 if (imm_expr.X_op == O_constant
7483 && imm_expr.X_add_number > -0x8000
7484 && imm_expr.X_add_number <= 0x8000)
7486 imm_expr.X_add_number = -imm_expr.X_add_number;
7487 macro_build ((char *) NULL, &icnt, &imm_expr,
7488 dbl ? "daddiu" : "addiu",
7489 "t,r,j", dreg, sreg, (int) BFD_RELOC_LO16);
7492 load_register (&icnt, AT, &imm_expr, dbl);
7493 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7494 dbl ? "dsubu" : "subu", "d,v,t", dreg, sreg, AT);
7515 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_GPRS);
7516 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "s,t", sreg,
7522 assert (mips_opts.isa == ISA_MIPS1);
7523 sreg = (ip->insn_opcode >> 11) & 0x1f; /* floating reg */
7524 dreg = (ip->insn_opcode >> 06) & 0x1f; /* floating reg */
7527 * Is the double cfc1 instruction a bug in the mips assembler;
7528 * or is there a reason for it?
7530 mips_emit_delays (TRUE);
7531 ++mips_opts.noreorder;
7532 mips_any_noreorder = 1;
7533 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "cfc1", "t,G",
7535 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "cfc1", "t,G",
7537 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "");
7538 expr1.X_add_number = 3;
7539 macro_build ((char *) NULL, &icnt, &expr1, "ori", "t,r,i", AT, treg,
7540 (int) BFD_RELOC_LO16);
7541 expr1.X_add_number = 2;
7542 macro_build ((char *) NULL, &icnt, &expr1, "xori", "t,r,i", AT, AT,
7543 (int) BFD_RELOC_LO16);
7544 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "ctc1", "t,G",
7546 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "");
7547 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7548 mask == M_TRUNCWD ? "cvt.w.d" : "cvt.w.s", "D,S", dreg, sreg);
7549 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "ctc1", "t,G",
7551 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "");
7552 --mips_opts.noreorder;
7561 if (offset_expr.X_add_number >= 0x7fff)
7562 as_bad (_("operand overflow"));
7563 if (! target_big_endian)
7564 ++offset_expr.X_add_number;
7565 macro_build ((char *) NULL, &icnt, &offset_expr, s, "t,o(b)", AT,
7566 (int) BFD_RELOC_LO16, breg);
7567 if (! target_big_endian)
7568 --offset_expr.X_add_number;
7570 ++offset_expr.X_add_number;
7571 macro_build ((char *) NULL, &icnt, &offset_expr, "lbu", "t,o(b)", treg,
7572 (int) BFD_RELOC_LO16, breg);
7573 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sll", "d,w,<",
7575 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or", "d,v,t",
7589 if (offset_expr.X_add_number >= 0x8000 - off)
7590 as_bad (_("operand overflow"));
7595 if (! target_big_endian)
7596 offset_expr.X_add_number += off;
7597 macro_build ((char *) NULL, &icnt, &offset_expr, s, "t,o(b)", tempreg,
7598 (int) BFD_RELOC_LO16, breg);
7599 if (! target_big_endian)
7600 offset_expr.X_add_number -= off;
7602 offset_expr.X_add_number += off;
7603 macro_build ((char *) NULL, &icnt, &offset_expr, s2, "t,o(b)", tempreg,
7604 (int) BFD_RELOC_LO16, breg);
7606 /* If necessary, move the result in tempreg the final destination. */
7607 if (treg == tempreg)
7609 /* Protect second load's delay slot. */
7610 if (!gpr_interlocks)
7611 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "");
7612 move_register (&icnt, treg, tempreg);
7626 load_address (&icnt, AT, &offset_expr, &used_at);
7628 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7629 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
7630 "d,v,t", AT, AT, breg);
7631 if (! target_big_endian)
7632 expr1.X_add_number = off;
7634 expr1.X_add_number = 0;
7635 macro_build ((char *) NULL, &icnt, &expr1, s, "t,o(b)", treg,
7636 (int) BFD_RELOC_LO16, AT);
7637 if (! target_big_endian)
7638 expr1.X_add_number = 0;
7640 expr1.X_add_number = off;
7641 macro_build ((char *) NULL, &icnt, &expr1, s2, "t,o(b)", treg,
7642 (int) BFD_RELOC_LO16, AT);
7648 load_address (&icnt, AT, &offset_expr, &used_at);
7650 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7651 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
7652 "d,v,t", AT, AT, breg);
7653 if (target_big_endian)
7654 expr1.X_add_number = 0;
7655 macro_build ((char *) NULL, &icnt, &expr1,
7656 mask == M_ULH_A ? "lb" : "lbu", "t,o(b)", treg,
7657 (int) BFD_RELOC_LO16, AT);
7658 if (target_big_endian)
7659 expr1.X_add_number = 1;
7661 expr1.X_add_number = 0;
7662 macro_build ((char *) NULL, &icnt, &expr1, "lbu", "t,o(b)", AT,
7663 (int) BFD_RELOC_LO16, AT);
7664 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sll", "d,w,<",
7666 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or", "d,v,t",
7671 if (offset_expr.X_add_number >= 0x7fff)
7672 as_bad (_("operand overflow"));
7673 if (target_big_endian)
7674 ++offset_expr.X_add_number;
7675 macro_build ((char *) NULL, &icnt, &offset_expr, "sb", "t,o(b)", treg,
7676 (int) BFD_RELOC_LO16, breg);
7677 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "srl", "d,w,<",
7679 if (target_big_endian)
7680 --offset_expr.X_add_number;
7682 ++offset_expr.X_add_number;
7683 macro_build ((char *) NULL, &icnt, &offset_expr, "sb", "t,o(b)", AT,
7684 (int) BFD_RELOC_LO16, breg);
7697 if (offset_expr.X_add_number >= 0x8000 - off)
7698 as_bad (_("operand overflow"));
7699 if (! target_big_endian)
7700 offset_expr.X_add_number += off;
7701 macro_build ((char *) NULL, &icnt, &offset_expr, s, "t,o(b)", treg,
7702 (int) BFD_RELOC_LO16, breg);
7703 if (! target_big_endian)
7704 offset_expr.X_add_number -= off;
7706 offset_expr.X_add_number += off;
7707 macro_build ((char *) NULL, &icnt, &offset_expr, s2, "t,o(b)", treg,
7708 (int) BFD_RELOC_LO16, breg);
7722 load_address (&icnt, AT, &offset_expr, &used_at);
7724 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7725 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
7726 "d,v,t", AT, AT, breg);
7727 if (! target_big_endian)
7728 expr1.X_add_number = off;
7730 expr1.X_add_number = 0;
7731 macro_build ((char *) NULL, &icnt, &expr1, s, "t,o(b)", treg,
7732 (int) BFD_RELOC_LO16, AT);
7733 if (! target_big_endian)
7734 expr1.X_add_number = 0;
7736 expr1.X_add_number = off;
7737 macro_build ((char *) NULL, &icnt, &expr1, s2, "t,o(b)", treg,
7738 (int) BFD_RELOC_LO16, AT);
7743 load_address (&icnt, AT, &offset_expr, &used_at);
7745 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7746 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
7747 "d,v,t", AT, AT, breg);
7748 if (! target_big_endian)
7749 expr1.X_add_number = 0;
7750 macro_build ((char *) NULL, &icnt, &expr1, "sb", "t,o(b)", treg,
7751 (int) BFD_RELOC_LO16, AT);
7752 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "srl", "d,w,<",
7754 if (! target_big_endian)
7755 expr1.X_add_number = 1;
7757 expr1.X_add_number = 0;
7758 macro_build ((char *) NULL, &icnt, &expr1, "sb", "t,o(b)", treg,
7759 (int) BFD_RELOC_LO16, AT);
7760 if (! target_big_endian)
7761 expr1.X_add_number = 0;
7763 expr1.X_add_number = 1;
7764 macro_build ((char *) NULL, &icnt, &expr1, "lbu", "t,o(b)", AT,
7765 (int) BFD_RELOC_LO16, AT);
7766 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sll", "d,w,<",
7768 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or", "d,v,t",
7773 /* FIXME: Check if this is one of the itbl macros, since they
7774 are added dynamically. */
7775 as_bad (_("Macro %s not implemented yet"), ip->insn_mo->name);
7779 as_warn (_("Macro used $at after \".set noat\""));
7782 /* Implement macros in mips16 mode. */
7786 struct mips_cl_insn *ip;
7789 int xreg, yreg, zreg, tmp;
7793 const char *s, *s2, *s3;
7795 mask = ip->insn_mo->mask;
7797 xreg = (ip->insn_opcode >> MIPS16OP_SH_RX) & MIPS16OP_MASK_RX;
7798 yreg = (ip->insn_opcode >> MIPS16OP_SH_RY) & MIPS16OP_MASK_RY;
7799 zreg = (ip->insn_opcode >> MIPS16OP_SH_RZ) & MIPS16OP_MASK_RZ;
7803 expr1.X_op = O_constant;
7804 expr1.X_op_symbol = NULL;
7805 expr1.X_add_symbol = NULL;
7806 expr1.X_add_number = 1;
7825 mips_emit_delays (TRUE);
7826 ++mips_opts.noreorder;
7827 mips_any_noreorder = 1;
7828 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7829 dbl ? "ddiv" : "div",
7830 "0,x,y", xreg, yreg);
7831 expr1.X_add_number = 2;
7832 macro_build ((char *) NULL, &icnt, &expr1, "bnez", "x,p", yreg);
7833 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "break", "6",
7836 /* FIXME: The normal code checks for of -1 / -0x80000000 here,
7837 since that causes an overflow. We should do that as well,
7838 but I don't see how to do the comparisons without a temporary
7840 --mips_opts.noreorder;
7841 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "x", zreg);
7860 mips_emit_delays (TRUE);
7861 ++mips_opts.noreorder;
7862 mips_any_noreorder = 1;
7863 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "0,x,y",
7865 expr1.X_add_number = 2;
7866 macro_build ((char *) NULL, &icnt, &expr1, "bnez", "x,p", yreg);
7867 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "break",
7869 --mips_opts.noreorder;
7870 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s2, "x", zreg);
7876 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7877 dbl ? "dmultu" : "multu", "x,y", xreg, yreg);
7878 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "mflo", "x",
7887 if (imm_expr.X_op != O_constant)
7888 as_bad (_("Unsupported large constant"));
7889 imm_expr.X_add_number = -imm_expr.X_add_number;
7890 macro_build ((char *) NULL, &icnt, &imm_expr,
7891 dbl ? "daddiu" : "addiu", "y,x,4", yreg, xreg);
7895 if (imm_expr.X_op != O_constant)
7896 as_bad (_("Unsupported large constant"));
7897 imm_expr.X_add_number = -imm_expr.X_add_number;
7898 macro_build ((char *) NULL, &icnt, &imm_expr, "addiu",
7903 if (imm_expr.X_op != O_constant)
7904 as_bad (_("Unsupported large constant"));
7905 imm_expr.X_add_number = -imm_expr.X_add_number;
7906 macro_build ((char *) NULL, &icnt, &imm_expr, "daddiu",
7929 goto do_reverse_branch;
7933 goto do_reverse_branch;
7945 goto do_reverse_branch;
7956 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "x,y",
7958 macro_build ((char *) NULL, &icnt, &offset_expr, s2, "p");
7985 goto do_addone_branch_i;
7990 goto do_addone_branch_i;
8005 goto do_addone_branch_i;
8012 if (imm_expr.X_op != O_constant)
8013 as_bad (_("Unsupported large constant"));
8014 ++imm_expr.X_add_number;
8017 macro_build ((char *) NULL, &icnt, &imm_expr, s, s3, xreg);
8018 macro_build ((char *) NULL, &icnt, &offset_expr, s2, "p");
8022 expr1.X_add_number = 0;
8023 macro_build ((char *) NULL, &icnt, &expr1, "slti", "x,8", yreg);
8025 move_register (&icnt, xreg, yreg);
8026 expr1.X_add_number = 2;
8027 macro_build ((char *) NULL, &icnt, &expr1, "bteqz", "p");
8028 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
8029 "neg", "x,w", xreg, xreg);
8033 /* For consistency checking, verify that all bits are specified either
8034 by the match/mask part of the instruction definition, or by the
8037 validate_mips_insn (opc)
8038 const struct mips_opcode *opc;
8040 const char *p = opc->args;
8042 unsigned long used_bits = opc->mask;
8044 if ((used_bits & opc->match) != opc->match)
8046 as_bad (_("internal: bad mips opcode (mask error): %s %s"),
8047 opc->name, opc->args);
8050 #define USE_BITS(mask,shift) (used_bits |= ((mask) << (shift)))
8060 case 'A': USE_BITS (OP_MASK_SHAMT, OP_SH_SHAMT); break;
8061 case 'B': USE_BITS (OP_MASK_INSMSB, OP_SH_INSMSB); break;
8062 case 'C': USE_BITS (OP_MASK_EXTMSBD, OP_SH_EXTMSBD); break;
8063 case 'D': USE_BITS (OP_MASK_RD, OP_SH_RD);
8064 USE_BITS (OP_MASK_SEL, OP_SH_SEL); break;
8066 as_bad (_("internal: bad mips opcode (unknown extension operand type `+%c'): %s %s"),
8067 c, opc->name, opc->args);
8071 case '<': USE_BITS (OP_MASK_SHAMT, OP_SH_SHAMT); break;
8072 case '>': USE_BITS (OP_MASK_SHAMT, OP_SH_SHAMT); break;
8074 case 'B': USE_BITS (OP_MASK_CODE20, OP_SH_CODE20); break;
8075 case 'C': USE_BITS (OP_MASK_COPZ, OP_SH_COPZ); break;
8076 case 'D': USE_BITS (OP_MASK_FD, OP_SH_FD); break;
8077 case 'E': USE_BITS (OP_MASK_RT, OP_SH_RT); break;
8079 case 'G': USE_BITS (OP_MASK_RD, OP_SH_RD); break;
8080 case 'H': USE_BITS (OP_MASK_SEL, OP_SH_SEL); break;
8082 case 'J': USE_BITS (OP_MASK_CODE19, OP_SH_CODE19); break;
8083 case 'K': USE_BITS (OP_MASK_RD, OP_SH_RD); break;
8085 case 'M': USE_BITS (OP_MASK_CCC, OP_SH_CCC); break;
8086 case 'N': USE_BITS (OP_MASK_BCC, OP_SH_BCC); break;
8087 case 'O': USE_BITS (OP_MASK_ALN, OP_SH_ALN); break;
8088 case 'Q': USE_BITS (OP_MASK_VSEL, OP_SH_VSEL);
8089 USE_BITS (OP_MASK_FT, OP_SH_FT); break;
8090 case 'R': USE_BITS (OP_MASK_FR, OP_SH_FR); break;
8091 case 'S': USE_BITS (OP_MASK_FS, OP_SH_FS); break;
8092 case 'T': USE_BITS (OP_MASK_FT, OP_SH_FT); break;
8093 case 'V': USE_BITS (OP_MASK_FS, OP_SH_FS); break;
8094 case 'W': USE_BITS (OP_MASK_FT, OP_SH_FT); break;
8095 case 'X': USE_BITS (OP_MASK_FD, OP_SH_FD); break;
8096 case 'Y': USE_BITS (OP_MASK_FS, OP_SH_FS); break;
8097 case 'Z': USE_BITS (OP_MASK_FT, OP_SH_FT); break;
8098 case 'a': USE_BITS (OP_MASK_TARGET, OP_SH_TARGET); break;
8099 case 'b': USE_BITS (OP_MASK_RS, OP_SH_RS); break;
8100 case 'c': USE_BITS (OP_MASK_CODE, OP_SH_CODE); break;
8101 case 'd': USE_BITS (OP_MASK_RD, OP_SH_RD); break;
8103 case 'h': USE_BITS (OP_MASK_PREFX, OP_SH_PREFX); break;
8104 case 'i': USE_BITS (OP_MASK_IMMEDIATE, OP_SH_IMMEDIATE); break;
8105 case 'j': USE_BITS (OP_MASK_DELTA, OP_SH_DELTA); break;
8106 case 'k': USE_BITS (OP_MASK_CACHE, OP_SH_CACHE); break;
8108 case 'o': USE_BITS (OP_MASK_DELTA, OP_SH_DELTA); break;
8109 case 'p': USE_BITS (OP_MASK_DELTA, OP_SH_DELTA); break;
8110 case 'q': USE_BITS (OP_MASK_CODE2, OP_SH_CODE2); break;
8111 case 'r': USE_BITS (OP_MASK_RS, OP_SH_RS); break;
8112 case 's': USE_BITS (OP_MASK_RS, OP_SH_RS); break;
8113 case 't': USE_BITS (OP_MASK_RT, OP_SH_RT); break;
8114 case 'u': USE_BITS (OP_MASK_IMMEDIATE, OP_SH_IMMEDIATE); break;
8115 case 'v': USE_BITS (OP_MASK_RS, OP_SH_RS); break;
8116 case 'w': USE_BITS (OP_MASK_RT, OP_SH_RT); break;
8119 case 'P': USE_BITS (OP_MASK_PERFREG, OP_SH_PERFREG); break;
8120 case 'U': USE_BITS (OP_MASK_RD, OP_SH_RD);
8121 USE_BITS (OP_MASK_RT, OP_SH_RT); break;
8122 case 'e': USE_BITS (OP_MASK_VECBYTE, OP_SH_VECBYTE); break;
8123 case '%': USE_BITS (OP_MASK_VECALIGN, OP_SH_VECALIGN); break;
8127 as_bad (_("internal: bad mips opcode (unknown operand type `%c'): %s %s"),
8128 c, opc->name, opc->args);
8132 if (used_bits != 0xffffffff)
8134 as_bad (_("internal: bad mips opcode (bits 0x%lx undefined): %s %s"),
8135 ~used_bits & 0xffffffff, opc->name, opc->args);
8141 /* This routine assembles an instruction into its binary format. As a
8142 side effect, it sets one of the global variables imm_reloc or
8143 offset_reloc to the type of relocation to do if one of the operands
8144 is an address expression. */
8149 struct mips_cl_insn *ip;
8154 struct mips_opcode *insn;
8157 unsigned int lastregno = 0;
8158 unsigned int lastpos = 0;
8159 unsigned int limlo, limhi;
8165 /* If the instruction contains a '.', we first try to match an instruction
8166 including the '.'. Then we try again without the '.'. */
8168 for (s = str; *s != '\0' && !ISSPACE (*s); ++s)
8171 /* If we stopped on whitespace, then replace the whitespace with null for
8172 the call to hash_find. Save the character we replaced just in case we
8173 have to re-parse the instruction. */
8180 insn = (struct mips_opcode *) hash_find (op_hash, str);
8182 /* If we didn't find the instruction in the opcode table, try again, but
8183 this time with just the instruction up to, but not including the
8187 /* Restore the character we overwrite above (if any). */
8191 /* Scan up to the first '.' or whitespace. */
8193 *s != '\0' && *s != '.' && !ISSPACE (*s);
8197 /* If we did not find a '.', then we can quit now. */
8200 insn_error = "unrecognized opcode";
8204 /* Lookup the instruction in the hash table. */
8206 if ((insn = (struct mips_opcode *) hash_find (op_hash, str)) == NULL)
8208 insn_error = "unrecognized opcode";
8218 assert (strcmp (insn->name, str) == 0);
8220 if (OPCODE_IS_MEMBER (insn,
8222 | (file_ase_mips16 ? INSN_MIPS16 : 0)
8223 | (mips_opts.ase_mdmx ? INSN_MDMX : 0)
8224 | (mips_opts.ase_mips3d ? INSN_MIPS3D : 0)),
8230 if (insn->pinfo != INSN_MACRO)
8232 if (mips_arch == CPU_R4650 && (insn->pinfo & FP_D) != 0)
8238 if (insn + 1 < &mips_opcodes[NUMOPCODES]
8239 && strcmp (insn->name, insn[1].name) == 0)
8248 static char buf[100];
8249 if (mips_arch_info->is_isa)
8251 _("opcode not supported at this ISA level (%s)"),
8252 mips_cpu_info_from_isa (mips_opts.isa)->name);
8255 _("opcode not supported on this processor: %s (%s)"),
8256 mips_arch_info->name,
8257 mips_cpu_info_from_isa (mips_opts.isa)->name);
8267 ip->insn_opcode = insn->match;
8269 for (args = insn->args;; ++args)
8273 s += strspn (s, " \t");
8277 case '\0': /* end of args */
8290 ip->insn_opcode |= lastregno << OP_SH_RS;
8294 ip->insn_opcode |= lastregno << OP_SH_RT;
8298 ip->insn_opcode |= lastregno << OP_SH_FT;
8302 ip->insn_opcode |= lastregno << OP_SH_FS;
8308 /* Handle optional base register.
8309 Either the base register is omitted or
8310 we must have a left paren. */
8311 /* This is dependent on the next operand specifier
8312 is a base register specification. */
8313 assert (args[1] == 'b' || args[1] == '5'
8314 || args[1] == '-' || args[1] == '4');
8318 case ')': /* these must match exactly */
8325 case '+': /* Opcode extension character. */
8328 case 'A': /* ins/ext position, becomes LSB. */
8331 my_getExpression (&imm_expr, s);
8332 check_absolute_expr (ip, &imm_expr);
8333 if ((unsigned long) imm_expr.X_add_number < limlo
8334 || (unsigned long) imm_expr.X_add_number > limhi)
8336 as_bad (_("Improper position (%lu)"),
8337 (unsigned long) imm_expr.X_add_number);
8338 imm_expr.X_add_number = limlo;
8340 lastpos = imm_expr.X_add_number;
8341 ip->insn_opcode |= (imm_expr.X_add_number
8342 & OP_MASK_SHAMT) << OP_SH_SHAMT;
8343 imm_expr.X_op = O_absent;
8347 case 'B': /* ins size, becomes MSB. */
8350 my_getExpression (&imm_expr, s);
8351 check_absolute_expr (ip, &imm_expr);
8352 /* Check for negative input so that small negative numbers
8353 will not succeed incorrectly. The checks against
8354 (pos+size) transitively check "size" itself,
8355 assuming that "pos" is reasonable. */
8356 if ((long) imm_expr.X_add_number < 0
8357 || ((unsigned long) imm_expr.X_add_number
8359 || ((unsigned long) imm_expr.X_add_number
8362 as_bad (_("Improper insert size (%lu, position %lu)"),
8363 (unsigned long) imm_expr.X_add_number,
8364 (unsigned long) lastpos);
8365 imm_expr.X_add_number = limlo - lastpos;
8367 ip->insn_opcode |= ((lastpos + imm_expr.X_add_number - 1)
8368 & OP_MASK_INSMSB) << OP_SH_INSMSB;
8369 imm_expr.X_op = O_absent;
8373 case 'C': /* ext size, becomes MSBD. */
8376 my_getExpression (&imm_expr, s);
8377 check_absolute_expr (ip, &imm_expr);
8378 /* Check for negative input so that small negative numbers
8379 will not succeed incorrectly. The checks against
8380 (pos+size) transitively check "size" itself,
8381 assuming that "pos" is reasonable. */
8382 if ((long) imm_expr.X_add_number < 0
8383 || ((unsigned long) imm_expr.X_add_number
8385 || ((unsigned long) imm_expr.X_add_number
8388 as_bad (_("Improper extract size (%lu, position %lu)"),
8389 (unsigned long) imm_expr.X_add_number,
8390 (unsigned long) lastpos);
8391 imm_expr.X_add_number = limlo - lastpos;
8393 ip->insn_opcode |= ((imm_expr.X_add_number - 1)
8394 & OP_MASK_EXTMSBD) << OP_SH_EXTMSBD;
8395 imm_expr.X_op = O_absent;
8400 /* +D is for disassembly only; never match. */
8404 as_bad (_("internal: bad mips opcode (unknown extension operand type `+%c'): %s %s"),
8405 *args, insn->name, insn->args);
8406 /* Further processing is fruitless. */
8411 case '<': /* must be at least one digit */
8413 * According to the manual, if the shift amount is greater
8414 * than 31 or less than 0, then the shift amount should be
8415 * mod 32. In reality the mips assembler issues an error.
8416 * We issue a warning and mask out all but the low 5 bits.
8418 my_getExpression (&imm_expr, s);
8419 check_absolute_expr (ip, &imm_expr);
8420 if ((unsigned long) imm_expr.X_add_number > 31)
8422 as_warn (_("Improper shift amount (%lu)"),
8423 (unsigned long) imm_expr.X_add_number);
8424 imm_expr.X_add_number &= OP_MASK_SHAMT;
8426 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_SHAMT;
8427 imm_expr.X_op = O_absent;
8431 case '>': /* shift amount minus 32 */
8432 my_getExpression (&imm_expr, s);
8433 check_absolute_expr (ip, &imm_expr);
8434 if ((unsigned long) imm_expr.X_add_number < 32
8435 || (unsigned long) imm_expr.X_add_number > 63)
8437 ip->insn_opcode |= (imm_expr.X_add_number - 32) << OP_SH_SHAMT;
8438 imm_expr.X_op = O_absent;
8442 case 'k': /* cache code */
8443 case 'h': /* prefx code */
8444 my_getExpression (&imm_expr, s);
8445 check_absolute_expr (ip, &imm_expr);
8446 if ((unsigned long) imm_expr.X_add_number > 31)
8448 as_warn (_("Invalid value for `%s' (%lu)"),
8450 (unsigned long) imm_expr.X_add_number);
8451 imm_expr.X_add_number &= 0x1f;
8454 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_CACHE;
8456 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_PREFX;
8457 imm_expr.X_op = O_absent;
8461 case 'c': /* break code */
8462 my_getExpression (&imm_expr, s);
8463 check_absolute_expr (ip, &imm_expr);
8464 if ((unsigned long) imm_expr.X_add_number > 1023)
8466 as_warn (_("Illegal break code (%lu)"),
8467 (unsigned long) imm_expr.X_add_number);
8468 imm_expr.X_add_number &= OP_MASK_CODE;
8470 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_CODE;
8471 imm_expr.X_op = O_absent;
8475 case 'q': /* lower break code */
8476 my_getExpression (&imm_expr, s);
8477 check_absolute_expr (ip, &imm_expr);
8478 if ((unsigned long) imm_expr.X_add_number > 1023)
8480 as_warn (_("Illegal lower break code (%lu)"),
8481 (unsigned long) imm_expr.X_add_number);
8482 imm_expr.X_add_number &= OP_MASK_CODE2;
8484 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_CODE2;
8485 imm_expr.X_op = O_absent;
8489 case 'B': /* 20-bit syscall/break code. */
8490 my_getExpression (&imm_expr, s);
8491 check_absolute_expr (ip, &imm_expr);
8492 if ((unsigned long) imm_expr.X_add_number > OP_MASK_CODE20)
8493 as_warn (_("Illegal 20-bit code (%lu)"),
8494 (unsigned long) imm_expr.X_add_number);
8495 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_CODE20;
8496 imm_expr.X_op = O_absent;
8500 case 'C': /* Coprocessor code */
8501 my_getExpression (&imm_expr, s);
8502 check_absolute_expr (ip, &imm_expr);
8503 if ((unsigned long) imm_expr.X_add_number >= (1 << 25))
8505 as_warn (_("Coproccesor code > 25 bits (%lu)"),
8506 (unsigned long) imm_expr.X_add_number);
8507 imm_expr.X_add_number &= ((1 << 25) - 1);
8509 ip->insn_opcode |= imm_expr.X_add_number;
8510 imm_expr.X_op = O_absent;
8514 case 'J': /* 19-bit wait code. */
8515 my_getExpression (&imm_expr, s);
8516 check_absolute_expr (ip, &imm_expr);
8517 if ((unsigned long) imm_expr.X_add_number > OP_MASK_CODE19)
8518 as_warn (_("Illegal 19-bit code (%lu)"),
8519 (unsigned long) imm_expr.X_add_number);
8520 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_CODE19;
8521 imm_expr.X_op = O_absent;
8525 case 'P': /* Performance register */
8526 my_getExpression (&imm_expr, s);
8527 check_absolute_expr (ip, &imm_expr);
8528 if (imm_expr.X_add_number != 0 && imm_expr.X_add_number != 1)
8530 as_warn (_("Invalid performance register (%lu)"),
8531 (unsigned long) imm_expr.X_add_number);
8532 imm_expr.X_add_number &= OP_MASK_PERFREG;
8534 ip->insn_opcode |= (imm_expr.X_add_number << OP_SH_PERFREG);
8535 imm_expr.X_op = O_absent;
8539 case 'b': /* base register */
8540 case 'd': /* destination register */
8541 case 's': /* source register */
8542 case 't': /* target register */
8543 case 'r': /* both target and source */
8544 case 'v': /* both dest and source */
8545 case 'w': /* both dest and target */
8546 case 'E': /* coprocessor target register */
8547 case 'G': /* coprocessor destination register */
8548 case 'K': /* 'rdhwr' destination register */
8549 case 'x': /* ignore register name */
8550 case 'z': /* must be zero register */
8551 case 'U': /* destination register (clo/clz). */
8566 while (ISDIGIT (*s));
8568 as_bad (_("Invalid register number (%d)"), regno);
8570 else if (*args == 'E' || *args == 'G' || *args == 'K')
8574 if (s[1] == 'r' && s[2] == 'a')
8579 else if (s[1] == 'f' && s[2] == 'p')
8584 else if (s[1] == 's' && s[2] == 'p')
8589 else if (s[1] == 'g' && s[2] == 'p')
8594 else if (s[1] == 'a' && s[2] == 't')
8599 else if (s[1] == 'k' && s[2] == 't' && s[3] == '0')
8604 else if (s[1] == 'k' && s[2] == 't' && s[3] == '1')
8609 else if (s[1] == 'z' && s[2] == 'e' && s[3] == 'r' && s[4] == 'o')
8614 else if (itbl_have_entries)
8619 p = s + 1; /* advance past '$' */
8620 n = itbl_get_field (&p); /* n is name */
8622 /* See if this is a register defined in an
8624 if (itbl_get_reg_val (n, &r))
8626 /* Get_field advances to the start of
8627 the next field, so we need to back
8628 rack to the end of the last field. */
8632 s = strchr (s, '\0');
8646 as_warn (_("Used $at without \".set noat\""));
8652 if (c == 'r' || c == 'v' || c == 'w')
8659 /* 'z' only matches $0. */
8660 if (c == 'z' && regno != 0)
8663 /* Now that we have assembled one operand, we use the args string
8664 * to figure out where it goes in the instruction. */
8671 ip->insn_opcode |= regno << OP_SH_RS;
8676 ip->insn_opcode |= regno << OP_SH_RD;
8679 ip->insn_opcode |= regno << OP_SH_RD;
8680 ip->insn_opcode |= regno << OP_SH_RT;
8685 ip->insn_opcode |= regno << OP_SH_RT;
8688 /* This case exists because on the r3000 trunc
8689 expands into a macro which requires a gp
8690 register. On the r6000 or r4000 it is
8691 assembled into a single instruction which
8692 ignores the register. Thus the insn version
8693 is MIPS_ISA2 and uses 'x', and the macro
8694 version is MIPS_ISA1 and uses 't'. */
8697 /* This case is for the div instruction, which
8698 acts differently if the destination argument
8699 is $0. This only matches $0, and is checked
8700 outside the switch. */
8703 /* Itbl operand; not yet implemented. FIXME ?? */
8705 /* What about all other operands like 'i', which
8706 can be specified in the opcode table? */
8716 ip->insn_opcode |= lastregno << OP_SH_RS;
8719 ip->insn_opcode |= lastregno << OP_SH_RT;
8724 case 'O': /* MDMX alignment immediate constant. */
8725 my_getExpression (&imm_expr, s);
8726 check_absolute_expr (ip, &imm_expr);
8727 if ((unsigned long) imm_expr.X_add_number > OP_MASK_ALN)
8729 as_warn ("Improper align amount (%ld), using low bits",
8730 (long) imm_expr.X_add_number);
8731 imm_expr.X_add_number &= OP_MASK_ALN;
8733 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_ALN;
8734 imm_expr.X_op = O_absent;
8738 case 'Q': /* MDMX vector, element sel, or const. */
8741 /* MDMX Immediate. */
8742 my_getExpression (&imm_expr, s);
8743 check_absolute_expr (ip, &imm_expr);
8744 if ((unsigned long) imm_expr.X_add_number > OP_MASK_FT)
8746 as_warn (_("Invalid MDMX Immediate (%ld)"),
8747 (long) imm_expr.X_add_number);
8748 imm_expr.X_add_number &= OP_MASK_FT;
8750 imm_expr.X_add_number &= OP_MASK_FT;
8751 if (ip->insn_opcode & (OP_MASK_VSEL << OP_SH_VSEL))
8752 ip->insn_opcode |= MDMX_FMTSEL_IMM_QH << OP_SH_VSEL;
8754 ip->insn_opcode |= MDMX_FMTSEL_IMM_OB << OP_SH_VSEL;
8755 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_FT;
8756 imm_expr.X_op = O_absent;
8760 /* Not MDMX Immediate. Fall through. */
8761 case 'X': /* MDMX destination register. */
8762 case 'Y': /* MDMX source register. */
8763 case 'Z': /* MDMX target register. */
8765 case 'D': /* floating point destination register */
8766 case 'S': /* floating point source register */
8767 case 'T': /* floating point target register */
8768 case 'R': /* floating point source register */
8772 /* Accept $fN for FP and MDMX register numbers, and in
8773 addition accept $vN for MDMX register numbers. */
8774 if ((s[0] == '$' && s[1] == 'f' && ISDIGIT (s[2]))
8775 || (is_mdmx != 0 && s[0] == '$' && s[1] == 'v'
8786 while (ISDIGIT (*s));
8789 as_bad (_("Invalid float register number (%d)"), regno);
8791 if ((regno & 1) != 0
8793 && ! (strcmp (str, "mtc1") == 0
8794 || strcmp (str, "mfc1") == 0
8795 || strcmp (str, "lwc1") == 0
8796 || strcmp (str, "swc1") == 0
8797 || strcmp (str, "l.s") == 0
8798 || strcmp (str, "s.s") == 0))
8799 as_warn (_("Float register should be even, was %d"),
8807 if (c == 'V' || c == 'W')
8818 ip->insn_opcode |= regno << OP_SH_FD;
8823 ip->insn_opcode |= regno << OP_SH_FS;
8826 /* This is like 'Z', but also needs to fix the MDMX
8827 vector/scalar select bits. Note that the
8828 scalar immediate case is handled above. */
8831 int is_qh = (ip->insn_opcode & (1 << OP_SH_VSEL));
8832 int max_el = (is_qh ? 3 : 7);
8834 my_getExpression(&imm_expr, s);
8835 check_absolute_expr (ip, &imm_expr);
8837 if (imm_expr.X_add_number > max_el)
8838 as_bad(_("Bad element selector %ld"),
8839 (long) imm_expr.X_add_number);
8840 imm_expr.X_add_number &= max_el;
8841 ip->insn_opcode |= (imm_expr.X_add_number
8845 as_warn(_("Expecting ']' found '%s'"), s);
8851 if (ip->insn_opcode & (OP_MASK_VSEL << OP_SH_VSEL))
8852 ip->insn_opcode |= (MDMX_FMTSEL_VEC_QH
8855 ip->insn_opcode |= (MDMX_FMTSEL_VEC_OB <<
8862 ip->insn_opcode |= regno << OP_SH_FT;
8865 ip->insn_opcode |= regno << OP_SH_FR;
8875 ip->insn_opcode |= lastregno << OP_SH_FS;
8878 ip->insn_opcode |= lastregno << OP_SH_FT;
8884 my_getExpression (&imm_expr, s);
8885 if (imm_expr.X_op != O_big
8886 && imm_expr.X_op != O_constant)
8887 insn_error = _("absolute expression required");
8892 my_getExpression (&offset_expr, s);
8893 *imm_reloc = BFD_RELOC_32;
8906 unsigned char temp[8];
8908 unsigned int length;
8913 /* These only appear as the last operand in an
8914 instruction, and every instruction that accepts
8915 them in any variant accepts them in all variants.
8916 This means we don't have to worry about backing out
8917 any changes if the instruction does not match.
8919 The difference between them is the size of the
8920 floating point constant and where it goes. For 'F'
8921 and 'L' the constant is 64 bits; for 'f' and 'l' it
8922 is 32 bits. Where the constant is placed is based
8923 on how the MIPS assembler does things:
8926 f -- immediate value
8929 The .lit4 and .lit8 sections are only used if
8930 permitted by the -G argument.
8932 When generating embedded PIC code, we use the
8933 .lit8 section but not the .lit4 section (we can do
8934 .lit4 inline easily; we need to put .lit8
8935 somewhere in the data segment, and using .lit8
8936 permits the linker to eventually combine identical
8939 The code below needs to know whether the target register
8940 is 32 or 64 bits wide. It relies on the fact 'f' and
8941 'F' are used with GPR-based instructions and 'l' and
8942 'L' are used with FPR-based instructions. */
8944 f64 = *args == 'F' || *args == 'L';
8945 using_gprs = *args == 'F' || *args == 'f';
8947 save_in = input_line_pointer;
8948 input_line_pointer = s;
8949 err = md_atof (f64 ? 'd' : 'f', (char *) temp, &len);
8951 s = input_line_pointer;
8952 input_line_pointer = save_in;
8953 if (err != NULL && *err != '\0')
8955 as_bad (_("Bad floating point constant: %s"), err);
8956 memset (temp, '\0', sizeof temp);
8957 length = f64 ? 8 : 4;
8960 assert (length == (unsigned) (f64 ? 8 : 4));
8964 && (! USE_GLOBAL_POINTER_OPT
8965 || mips_pic == EMBEDDED_PIC
8966 || g_switch_value < 4
8967 || (temp[0] == 0 && temp[1] == 0)
8968 || (temp[2] == 0 && temp[3] == 0))))
8970 imm_expr.X_op = O_constant;
8971 if (! target_big_endian)
8972 imm_expr.X_add_number = bfd_getl32 (temp);
8974 imm_expr.X_add_number = bfd_getb32 (temp);
8977 && ! mips_disable_float_construction
8978 /* Constants can only be constructed in GPRs and
8979 copied to FPRs if the GPRs are at least as wide
8980 as the FPRs. Force the constant into memory if
8981 we are using 64-bit FPRs but the GPRs are only
8984 || ! (HAVE_64BIT_FPRS && HAVE_32BIT_GPRS))
8985 && ((temp[0] == 0 && temp[1] == 0)
8986 || (temp[2] == 0 && temp[3] == 0))
8987 && ((temp[4] == 0 && temp[5] == 0)
8988 || (temp[6] == 0 && temp[7] == 0)))
8990 /* The value is simple enough to load with a couple of
8991 instructions. If using 32-bit registers, set
8992 imm_expr to the high order 32 bits and offset_expr to
8993 the low order 32 bits. Otherwise, set imm_expr to
8994 the entire 64 bit constant. */
8995 if (using_gprs ? HAVE_32BIT_GPRS : HAVE_32BIT_FPRS)
8997 imm_expr.X_op = O_constant;
8998 offset_expr.X_op = O_constant;
8999 if (! target_big_endian)
9001 imm_expr.X_add_number = bfd_getl32 (temp + 4);
9002 offset_expr.X_add_number = bfd_getl32 (temp);
9006 imm_expr.X_add_number = bfd_getb32 (temp);
9007 offset_expr.X_add_number = bfd_getb32 (temp + 4);
9009 if (offset_expr.X_add_number == 0)
9010 offset_expr.X_op = O_absent;
9012 else if (sizeof (imm_expr.X_add_number) > 4)
9014 imm_expr.X_op = O_constant;
9015 if (! target_big_endian)
9016 imm_expr.X_add_number = bfd_getl64 (temp);
9018 imm_expr.X_add_number = bfd_getb64 (temp);
9022 imm_expr.X_op = O_big;
9023 imm_expr.X_add_number = 4;
9024 if (! target_big_endian)
9026 generic_bignum[0] = bfd_getl16 (temp);
9027 generic_bignum[1] = bfd_getl16 (temp + 2);
9028 generic_bignum[2] = bfd_getl16 (temp + 4);
9029 generic_bignum[3] = bfd_getl16 (temp + 6);
9033 generic_bignum[0] = bfd_getb16 (temp + 6);
9034 generic_bignum[1] = bfd_getb16 (temp + 4);
9035 generic_bignum[2] = bfd_getb16 (temp + 2);
9036 generic_bignum[3] = bfd_getb16 (temp);
9042 const char *newname;
9045 /* Switch to the right section. */
9047 subseg = now_subseg;
9050 default: /* unused default case avoids warnings. */
9052 newname = RDATA_SECTION_NAME;
9053 if ((USE_GLOBAL_POINTER_OPT && g_switch_value >= 8)
9054 || mips_pic == EMBEDDED_PIC)
9058 if (mips_pic == EMBEDDED_PIC)
9061 newname = RDATA_SECTION_NAME;
9064 assert (!USE_GLOBAL_POINTER_OPT
9065 || g_switch_value >= 4);
9069 new_seg = subseg_new (newname, (subsegT) 0);
9070 if (OUTPUT_FLAVOR == bfd_target_elf_flavour)
9071 bfd_set_section_flags (stdoutput, new_seg,
9076 frag_align (*args == 'l' ? 2 : 3, 0, 0);
9077 if (OUTPUT_FLAVOR == bfd_target_elf_flavour
9078 && strcmp (TARGET_OS, "elf") != 0)
9079 record_alignment (new_seg, 4);
9081 record_alignment (new_seg, *args == 'l' ? 2 : 3);
9083 as_bad (_("Can't use floating point insn in this section"));
9085 /* Set the argument to the current address in the
9087 offset_expr.X_op = O_symbol;
9088 offset_expr.X_add_symbol =
9089 symbol_new ("L0\001", now_seg,
9090 (valueT) frag_now_fix (), frag_now);
9091 offset_expr.X_add_number = 0;
9093 /* Put the floating point number into the section. */
9094 p = frag_more ((int) length);
9095 memcpy (p, temp, length);
9097 /* Switch back to the original section. */
9098 subseg_set (seg, subseg);
9103 case 'i': /* 16 bit unsigned immediate */
9104 case 'j': /* 16 bit signed immediate */
9105 *imm_reloc = BFD_RELOC_LO16;
9106 if (my_getSmallExpression (&imm_expr, imm_reloc, s) == 0)
9109 offsetT minval, maxval;
9111 more = (insn + 1 < &mips_opcodes[NUMOPCODES]
9112 && strcmp (insn->name, insn[1].name) == 0);
9114 /* If the expression was written as an unsigned number,
9115 only treat it as signed if there are no more
9119 && sizeof (imm_expr.X_add_number) <= 4
9120 && imm_expr.X_op == O_constant
9121 && imm_expr.X_add_number < 0
9122 && imm_expr.X_unsigned
9126 /* For compatibility with older assemblers, we accept
9127 0x8000-0xffff as signed 16-bit numbers when only
9128 signed numbers are allowed. */
9130 minval = 0, maxval = 0xffff;
9132 minval = -0x8000, maxval = 0x7fff;
9134 minval = -0x8000, maxval = 0xffff;
9136 if (imm_expr.X_op != O_constant
9137 || imm_expr.X_add_number < minval
9138 || imm_expr.X_add_number > maxval)
9142 if (imm_expr.X_op == O_constant
9143 || imm_expr.X_op == O_big)
9144 as_bad (_("expression out of range"));
9150 case 'o': /* 16 bit offset */
9151 /* Check whether there is only a single bracketed expression
9152 left. If so, it must be the base register and the
9153 constant must be zero. */
9154 if (*s == '(' && strchr (s + 1, '(') == 0)
9156 offset_expr.X_op = O_constant;
9157 offset_expr.X_add_number = 0;
9161 /* If this value won't fit into a 16 bit offset, then go
9162 find a macro that will generate the 32 bit offset
9164 if (my_getSmallExpression (&offset_expr, offset_reloc, s) == 0
9165 && (offset_expr.X_op != O_constant
9166 || offset_expr.X_add_number >= 0x8000
9167 || offset_expr.X_add_number < -0x8000))
9173 case 'p': /* pc relative offset */
9174 *offset_reloc = BFD_RELOC_16_PCREL_S2;
9175 my_getExpression (&offset_expr, s);
9179 case 'u': /* upper 16 bits */
9180 if (my_getSmallExpression (&imm_expr, imm_reloc, s) == 0
9181 && imm_expr.X_op == O_constant
9182 && (imm_expr.X_add_number < 0
9183 || imm_expr.X_add_number >= 0x10000))
9184 as_bad (_("lui expression not in range 0..65535"));
9188 case 'a': /* 26 bit address */
9189 my_getExpression (&offset_expr, s);
9191 *offset_reloc = BFD_RELOC_MIPS_JMP;
9194 case 'N': /* 3 bit branch condition code */
9195 case 'M': /* 3 bit compare condition code */
9196 if (strncmp (s, "$fcc", 4) != 0)
9206 while (ISDIGIT (*s));
9208 as_bad (_("invalid condition code register $fcc%d"), regno);
9210 ip->insn_opcode |= regno << OP_SH_BCC;
9212 ip->insn_opcode |= regno << OP_SH_CCC;
9216 if (s[0] == '0' && (s[1] == 'x' || s[1] == 'X'))
9227 while (ISDIGIT (*s));
9230 c = 8; /* Invalid sel value. */
9233 as_bad (_("invalid coprocessor sub-selection value (0-7)"));
9234 ip->insn_opcode |= c;
9238 /* Must be at least one digit. */
9239 my_getExpression (&imm_expr, s);
9240 check_absolute_expr (ip, &imm_expr);
9242 if ((unsigned long) imm_expr.X_add_number
9243 > (unsigned long) OP_MASK_VECBYTE)
9245 as_bad (_("bad byte vector index (%ld)"),
9246 (long) imm_expr.X_add_number);
9247 imm_expr.X_add_number = 0;
9250 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_VECBYTE;
9251 imm_expr.X_op = O_absent;
9256 my_getExpression (&imm_expr, s);
9257 check_absolute_expr (ip, &imm_expr);
9259 if ((unsigned long) imm_expr.X_add_number
9260 > (unsigned long) OP_MASK_VECALIGN)
9262 as_bad (_("bad byte vector index (%ld)"),
9263 (long) imm_expr.X_add_number);
9264 imm_expr.X_add_number = 0;
9267 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_VECALIGN;
9268 imm_expr.X_op = O_absent;
9273 as_bad (_("bad char = '%c'\n"), *args);
9278 /* Args don't match. */
9279 if (insn + 1 < &mips_opcodes[NUMOPCODES] &&
9280 !strcmp (insn->name, insn[1].name))
9284 insn_error = _("illegal operands");
9289 insn_error = _("illegal operands");
9294 /* This routine assembles an instruction into its binary format when
9295 assembling for the mips16. As a side effect, it sets one of the
9296 global variables imm_reloc or offset_reloc to the type of
9297 relocation to do if one of the operands is an address expression.
9298 It also sets mips16_small and mips16_ext if the user explicitly
9299 requested a small or extended instruction. */
9304 struct mips_cl_insn *ip;
9308 struct mips_opcode *insn;
9311 unsigned int lastregno = 0;
9316 mips16_small = FALSE;
9319 for (s = str; ISLOWER (*s); ++s)
9331 if (s[1] == 't' && s[2] == ' ')
9334 mips16_small = TRUE;
9338 else if (s[1] == 'e' && s[2] == ' ')
9347 insn_error = _("unknown opcode");
9351 if (mips_opts.noautoextend && ! mips16_ext)
9352 mips16_small = TRUE;
9354 if ((insn = (struct mips_opcode *) hash_find (mips16_op_hash, str)) == NULL)
9356 insn_error = _("unrecognized opcode");
9363 assert (strcmp (insn->name, str) == 0);
9366 ip->insn_opcode = insn->match;
9367 ip->use_extend = FALSE;
9368 imm_expr.X_op = O_absent;
9369 imm_reloc[0] = BFD_RELOC_UNUSED;
9370 imm_reloc[1] = BFD_RELOC_UNUSED;
9371 imm_reloc[2] = BFD_RELOC_UNUSED;
9372 offset_expr.X_op = O_absent;
9373 offset_reloc[0] = BFD_RELOC_UNUSED;
9374 offset_reloc[1] = BFD_RELOC_UNUSED;
9375 offset_reloc[2] = BFD_RELOC_UNUSED;
9376 for (args = insn->args; 1; ++args)
9383 /* In this switch statement we call break if we did not find
9384 a match, continue if we did find a match, or return if we
9393 /* Stuff the immediate value in now, if we can. */
9394 if (imm_expr.X_op == O_constant
9395 && *imm_reloc > BFD_RELOC_UNUSED
9396 && insn->pinfo != INSN_MACRO)
9398 mips16_immed (NULL, 0, *imm_reloc - BFD_RELOC_UNUSED,
9399 imm_expr.X_add_number, TRUE, mips16_small,
9400 mips16_ext, &ip->insn_opcode,
9401 &ip->use_extend, &ip->extend);
9402 imm_expr.X_op = O_absent;
9403 *imm_reloc = BFD_RELOC_UNUSED;
9417 ip->insn_opcode |= lastregno << MIPS16OP_SH_RX;
9420 ip->insn_opcode |= lastregno << MIPS16OP_SH_RY;
9436 ip->insn_opcode |= lastregno << MIPS16OP_SH_RX;
9438 ip->insn_opcode |= lastregno << MIPS16OP_SH_RY;
9465 while (ISDIGIT (*s));
9468 as_bad (_("invalid register number (%d)"), regno);
9474 if (s[1] == 'r' && s[2] == 'a')
9479 else if (s[1] == 'f' && s[2] == 'p')
9484 else if (s[1] == 's' && s[2] == 'p')
9489 else if (s[1] == 'g' && s[2] == 'p')
9494 else if (s[1] == 'a' && s[2] == 't')
9499 else if (s[1] == 'k' && s[2] == 't' && s[3] == '0')
9504 else if (s[1] == 'k' && s[2] == 't' && s[3] == '1')
9509 else if (s[1] == 'z' && s[2] == 'e' && s[3] == 'r' && s[4] == 'o')
9522 if (c == 'v' || c == 'w')
9524 regno = mips16_to_32_reg_map[lastregno];
9538 regno = mips32_to_16_reg_map[regno];
9543 regno = ILLEGAL_REG;
9548 regno = ILLEGAL_REG;
9553 regno = ILLEGAL_REG;
9558 if (regno == AT && ! mips_opts.noat)
9559 as_warn (_("used $at without \".set noat\""));
9566 if (regno == ILLEGAL_REG)
9573 ip->insn_opcode |= regno << MIPS16OP_SH_RX;
9577 ip->insn_opcode |= regno << MIPS16OP_SH_RY;
9580 ip->insn_opcode |= regno << MIPS16OP_SH_RZ;
9583 ip->insn_opcode |= regno << MIPS16OP_SH_MOVE32Z;
9589 ip->insn_opcode |= regno << MIPS16OP_SH_REGR32;
9592 regno = ((regno & 7) << 2) | ((regno & 0x18) >> 3);
9593 ip->insn_opcode |= regno << MIPS16OP_SH_REG32R;
9603 if (strncmp (s, "$pc", 3) == 0)
9627 && strncmp (s + 1, "gprel(", sizeof "gprel(" - 1) == 0)
9629 /* This is %gprel(SYMBOL). We need to read SYMBOL,
9630 and generate the appropriate reloc. If the text
9631 inside %gprel is not a symbol name with an
9632 optional offset, then we generate a normal reloc
9633 and will probably fail later. */
9634 my_getExpression (&imm_expr, s + sizeof "%gprel" - 1);
9635 if (imm_expr.X_op == O_symbol)
9638 *imm_reloc = BFD_RELOC_MIPS16_GPREL;
9640 ip->use_extend = TRUE;
9647 /* Just pick up a normal expression. */
9648 my_getExpression (&imm_expr, s);
9651 if (imm_expr.X_op == O_register)
9653 /* What we thought was an expression turned out to
9656 if (s[0] == '(' && args[1] == '(')
9658 /* It looks like the expression was omitted
9659 before a register indirection, which means
9660 that the expression is implicitly zero. We
9661 still set up imm_expr, so that we handle
9662 explicit extensions correctly. */
9663 imm_expr.X_op = O_constant;
9664 imm_expr.X_add_number = 0;
9665 *imm_reloc = (int) BFD_RELOC_UNUSED + c;
9672 /* We need to relax this instruction. */
9673 *imm_reloc = (int) BFD_RELOC_UNUSED + c;
9682 /* We use offset_reloc rather than imm_reloc for the PC
9683 relative operands. This lets macros with both
9684 immediate and address operands work correctly. */
9685 my_getExpression (&offset_expr, s);
9687 if (offset_expr.X_op == O_register)
9690 /* We need to relax this instruction. */
9691 *offset_reloc = (int) BFD_RELOC_UNUSED + c;
9695 case '6': /* break code */
9696 my_getExpression (&imm_expr, s);
9697 check_absolute_expr (ip, &imm_expr);
9698 if ((unsigned long) imm_expr.X_add_number > 63)
9700 as_warn (_("Invalid value for `%s' (%lu)"),
9702 (unsigned long) imm_expr.X_add_number);
9703 imm_expr.X_add_number &= 0x3f;
9705 ip->insn_opcode |= imm_expr.X_add_number << MIPS16OP_SH_IMM6;
9706 imm_expr.X_op = O_absent;
9710 case 'a': /* 26 bit address */
9711 my_getExpression (&offset_expr, s);
9713 *offset_reloc = BFD_RELOC_MIPS16_JMP;
9714 ip->insn_opcode <<= 16;
9717 case 'l': /* register list for entry macro */
9718 case 'L': /* register list for exit macro */
9728 int freg, reg1, reg2;
9730 while (*s == ' ' || *s == ',')
9734 as_bad (_("can't parse register list"));
9746 while (ISDIGIT (*s))
9768 as_bad (_("invalid register list"));
9773 while (ISDIGIT (*s))
9780 if (freg && reg1 == 0 && reg2 == 0 && c == 'L')
9785 else if (freg && reg1 == 0 && reg2 == 1 && c == 'L')
9790 else if (reg1 == 4 && reg2 >= 4 && reg2 <= 7 && c != 'L')
9791 mask |= (reg2 - 3) << 3;
9792 else if (reg1 == 16 && reg2 >= 16 && reg2 <= 17)
9793 mask |= (reg2 - 15) << 1;
9794 else if (reg1 == RA && reg2 == RA)
9798 as_bad (_("invalid register list"));
9802 /* The mask is filled in in the opcode table for the
9803 benefit of the disassembler. We remove it before
9804 applying the actual mask. */
9805 ip->insn_opcode &= ~ ((7 << 3) << MIPS16OP_SH_IMM6);
9806 ip->insn_opcode |= mask << MIPS16OP_SH_IMM6;
9810 case 'e': /* extend code */
9811 my_getExpression (&imm_expr, s);
9812 check_absolute_expr (ip, &imm_expr);
9813 if ((unsigned long) imm_expr.X_add_number > 0x7ff)
9815 as_warn (_("Invalid value for `%s' (%lu)"),
9817 (unsigned long) imm_expr.X_add_number);
9818 imm_expr.X_add_number &= 0x7ff;
9820 ip->insn_opcode |= imm_expr.X_add_number;
9821 imm_expr.X_op = O_absent;
9831 /* Args don't match. */
9832 if (insn + 1 < &mips16_opcodes[bfd_mips16_num_opcodes] &&
9833 strcmp (insn->name, insn[1].name) == 0)
9840 insn_error = _("illegal operands");
9846 /* This structure holds information we know about a mips16 immediate
9849 struct mips16_immed_operand
9851 /* The type code used in the argument string in the opcode table. */
9853 /* The number of bits in the short form of the opcode. */
9855 /* The number of bits in the extended form of the opcode. */
9857 /* The amount by which the short form is shifted when it is used;
9858 for example, the sw instruction has a shift count of 2. */
9860 /* The amount by which the short form is shifted when it is stored
9861 into the instruction code. */
9863 /* Non-zero if the short form is unsigned. */
9865 /* Non-zero if the extended form is unsigned. */
9867 /* Non-zero if the value is PC relative. */
9871 /* The mips16 immediate operand types. */
9873 static const struct mips16_immed_operand mips16_immed_operands[] =
9875 { '<', 3, 5, 0, MIPS16OP_SH_RZ, 1, 1, 0 },
9876 { '>', 3, 5, 0, MIPS16OP_SH_RX, 1, 1, 0 },
9877 { '[', 3, 6, 0, MIPS16OP_SH_RZ, 1, 1, 0 },
9878 { ']', 3, 6, 0, MIPS16OP_SH_RX, 1, 1, 0 },
9879 { '4', 4, 15, 0, MIPS16OP_SH_IMM4, 0, 0, 0 },
9880 { '5', 5, 16, 0, MIPS16OP_SH_IMM5, 1, 0, 0 },
9881 { 'H', 5, 16, 1, MIPS16OP_SH_IMM5, 1, 0, 0 },
9882 { 'W', 5, 16, 2, MIPS16OP_SH_IMM5, 1, 0, 0 },
9883 { 'D', 5, 16, 3, MIPS16OP_SH_IMM5, 1, 0, 0 },
9884 { 'j', 5, 16, 0, MIPS16OP_SH_IMM5, 0, 0, 0 },
9885 { '8', 8, 16, 0, MIPS16OP_SH_IMM8, 1, 0, 0 },
9886 { 'V', 8, 16, 2, MIPS16OP_SH_IMM8, 1, 0, 0 },
9887 { 'C', 8, 16, 3, MIPS16OP_SH_IMM8, 1, 0, 0 },
9888 { 'U', 8, 16, 0, MIPS16OP_SH_IMM8, 1, 1, 0 },
9889 { 'k', 8, 16, 0, MIPS16OP_SH_IMM8, 0, 0, 0 },
9890 { 'K', 8, 16, 3, MIPS16OP_SH_IMM8, 0, 0, 0 },
9891 { 'p', 8, 16, 0, MIPS16OP_SH_IMM8, 0, 0, 1 },
9892 { 'q', 11, 16, 0, MIPS16OP_SH_IMM8, 0, 0, 1 },
9893 { 'A', 8, 16, 2, MIPS16OP_SH_IMM8, 1, 0, 1 },
9894 { 'B', 5, 16, 3, MIPS16OP_SH_IMM5, 1, 0, 1 },
9895 { 'E', 5, 16, 2, MIPS16OP_SH_IMM5, 1, 0, 1 }
9898 #define MIPS16_NUM_IMMED \
9899 (sizeof mips16_immed_operands / sizeof mips16_immed_operands[0])
9901 /* Handle a mips16 instruction with an immediate value. This or's the
9902 small immediate value into *INSN. It sets *USE_EXTEND to indicate
9903 whether an extended value is needed; if one is needed, it sets
9904 *EXTEND to the value. The argument type is TYPE. The value is VAL.
9905 If SMALL is true, an unextended opcode was explicitly requested.
9906 If EXT is true, an extended opcode was explicitly requested. If
9907 WARN is true, warn if EXT does not match reality. */
9910 mips16_immed (file, line, type, val, warn, small, ext, insn, use_extend,
9919 unsigned long *insn;
9920 bfd_boolean *use_extend;
9921 unsigned short *extend;
9923 register const struct mips16_immed_operand *op;
9924 int mintiny, maxtiny;
9925 bfd_boolean needext;
9927 op = mips16_immed_operands;
9928 while (op->type != type)
9931 assert (op < mips16_immed_operands + MIPS16_NUM_IMMED);
9936 if (type == '<' || type == '>' || type == '[' || type == ']')
9939 maxtiny = 1 << op->nbits;
9944 maxtiny = (1 << op->nbits) - 1;
9949 mintiny = - (1 << (op->nbits - 1));
9950 maxtiny = (1 << (op->nbits - 1)) - 1;
9953 /* Branch offsets have an implicit 0 in the lowest bit. */
9954 if (type == 'p' || type == 'q')
9957 if ((val & ((1 << op->shift) - 1)) != 0
9958 || val < (mintiny << op->shift)
9959 || val > (maxtiny << op->shift))
9964 if (warn && ext && ! needext)
9965 as_warn_where (file, line,
9966 _("extended operand requested but not required"));
9967 if (small && needext)
9968 as_bad_where (file, line, _("invalid unextended operand value"));
9970 if (small || (! ext && ! needext))
9974 *use_extend = FALSE;
9975 insnval = ((val >> op->shift) & ((1 << op->nbits) - 1));
9976 insnval <<= op->op_shift;
9981 long minext, maxext;
9987 maxext = (1 << op->extbits) - 1;
9991 minext = - (1 << (op->extbits - 1));
9992 maxext = (1 << (op->extbits - 1)) - 1;
9994 if (val < minext || val > maxext)
9995 as_bad_where (file, line,
9996 _("operand value out of range for instruction"));
9999 if (op->extbits == 16)
10001 extval = ((val >> 11) & 0x1f) | (val & 0x7e0);
10004 else if (op->extbits == 15)
10006 extval = ((val >> 11) & 0xf) | (val & 0x7f0);
10011 extval = ((val & 0x1f) << 6) | (val & 0x20);
10015 *extend = (unsigned short) extval;
10020 static const struct percent_op_match
10023 bfd_reloc_code_real_type reloc;
10026 {"%lo", BFD_RELOC_LO16},
10028 {"%call_hi", BFD_RELOC_MIPS_CALL_HI16},
10029 {"%call_lo", BFD_RELOC_MIPS_CALL_LO16},
10030 {"%call16", BFD_RELOC_MIPS_CALL16},
10031 {"%got_disp", BFD_RELOC_MIPS_GOT_DISP},
10032 {"%got_page", BFD_RELOC_MIPS_GOT_PAGE},
10033 {"%got_ofst", BFD_RELOC_MIPS_GOT_OFST},
10034 {"%got_hi", BFD_RELOC_MIPS_GOT_HI16},
10035 {"%got_lo", BFD_RELOC_MIPS_GOT_LO16},
10036 {"%got", BFD_RELOC_MIPS_GOT16},
10037 {"%gp_rel", BFD_RELOC_GPREL16},
10038 {"%half", BFD_RELOC_16},
10039 {"%highest", BFD_RELOC_MIPS_HIGHEST},
10040 {"%higher", BFD_RELOC_MIPS_HIGHER},
10041 {"%neg", BFD_RELOC_MIPS_SUB},
10043 {"%hi", BFD_RELOC_HI16_S}
10047 /* Return true if *STR points to a relocation operator. When returning true,
10048 move *STR over the operator and store its relocation code in *RELOC.
10049 Leave both *STR and *RELOC alone when returning false. */
10052 parse_relocation (str, reloc)
10054 bfd_reloc_code_real_type *reloc;
10058 for (i = 0; i < ARRAY_SIZE (percent_op); i++)
10059 if (strncasecmp (*str, percent_op[i].str, strlen (percent_op[i].str)) == 0)
10061 *str += strlen (percent_op[i].str);
10062 *reloc = percent_op[i].reloc;
10064 /* Check whether the output BFD supports this relocation.
10065 If not, issue an error and fall back on something safe. */
10066 if (!bfd_reloc_type_lookup (stdoutput, percent_op[i].reloc))
10068 as_bad ("relocation %s isn't supported by the current ABI",
10069 percent_op[i].str);
10070 *reloc = BFD_RELOC_LO16;
10078 /* Parse string STR as a 16-bit relocatable operand. Store the
10079 expression in *EP and the relocations in the array starting
10080 at RELOC. Return the number of relocation operators used.
10082 On exit, EXPR_END points to the first character after the expression.
10083 If no relocation operators are used, RELOC[0] is set to BFD_RELOC_LO16. */
10086 my_getSmallExpression (ep, reloc, str)
10088 bfd_reloc_code_real_type *reloc;
10091 bfd_reloc_code_real_type reversed_reloc[3];
10092 size_t reloc_index, i;
10093 int crux_depth, str_depth;
10096 /* Search for the start of the main expression, recoding relocations
10097 in REVERSED_RELOC. End the loop with CRUX pointing to the start
10098 of the main expression and with CRUX_DEPTH containing the number
10099 of open brackets at that point. */
10106 crux_depth = str_depth;
10108 /* Skip over whitespace and brackets, keeping count of the number
10110 while (*str == ' ' || *str == '\t' || *str == '(')
10115 && reloc_index < (HAVE_NEWABI ? 3 : 1)
10116 && parse_relocation (&str, &reversed_reloc[reloc_index]));
10118 my_getExpression (ep, crux);
10121 /* Match every open bracket. */
10122 while (crux_depth > 0 && (*str == ')' || *str == ' ' || *str == '\t'))
10126 if (crux_depth > 0)
10127 as_bad ("unclosed '('");
10131 if (reloc_index == 0)
10132 reloc[0] = BFD_RELOC_LO16;
10135 prev_reloc_op_frag = frag_now;
10136 for (i = 0; i < reloc_index; i++)
10137 reloc[i] = reversed_reloc[reloc_index - 1 - i];
10140 return reloc_index;
10144 my_getExpression (ep, str)
10151 save_in = input_line_pointer;
10152 input_line_pointer = str;
10154 expr_end = input_line_pointer;
10155 input_line_pointer = save_in;
10157 /* If we are in mips16 mode, and this is an expression based on `.',
10158 then we bump the value of the symbol by 1 since that is how other
10159 text symbols are handled. We don't bother to handle complex
10160 expressions, just `.' plus or minus a constant. */
10161 if (mips_opts.mips16
10162 && ep->X_op == O_symbol
10163 && strcmp (S_GET_NAME (ep->X_add_symbol), FAKE_LABEL_NAME) == 0
10164 && S_GET_SEGMENT (ep->X_add_symbol) == now_seg
10165 && symbol_get_frag (ep->X_add_symbol) == frag_now
10166 && symbol_constant_p (ep->X_add_symbol)
10167 && (val = S_GET_VALUE (ep->X_add_symbol)) == frag_now_fix ())
10168 S_SET_VALUE (ep->X_add_symbol, val + 1);
10171 /* Turn a string in input_line_pointer into a floating point constant
10172 of type TYPE, and store the appropriate bytes in *LITP. The number
10173 of LITTLENUMS emitted is stored in *SIZEP. An error message is
10174 returned, or NULL on OK. */
10177 md_atof (type, litP, sizeP)
10183 LITTLENUM_TYPE words[4];
10199 return _("bad call to md_atof");
10202 t = atof_ieee (input_line_pointer, type, words);
10204 input_line_pointer = t;
10208 if (! target_big_endian)
10210 for (i = prec - 1; i >= 0; i--)
10212 md_number_to_chars (litP, (valueT) words[i], 2);
10218 for (i = 0; i < prec; i++)
10220 md_number_to_chars (litP, (valueT) words[i], 2);
10229 md_number_to_chars (buf, val, n)
10234 if (target_big_endian)
10235 number_to_chars_bigendian (buf, val, n);
10237 number_to_chars_littleendian (buf, val, n);
10241 static int support_64bit_objects(void)
10243 const char **list, **l;
10246 list = bfd_target_list ();
10247 for (l = list; *l != NULL; l++)
10249 /* This is traditional mips */
10250 if (strcmp (*l, "elf64-tradbigmips") == 0
10251 || strcmp (*l, "elf64-tradlittlemips") == 0)
10253 if (strcmp (*l, "elf64-bigmips") == 0
10254 || strcmp (*l, "elf64-littlemips") == 0)
10257 yes = (*l != NULL);
10261 #endif /* OBJ_ELF */
10263 const char *md_shortopts = "nO::g::G:";
10265 struct option md_longopts[] =
10267 #define OPTION_MIPS1 (OPTION_MD_BASE + 1)
10268 {"mips0", no_argument, NULL, OPTION_MIPS1},
10269 {"mips1", no_argument, NULL, OPTION_MIPS1},
10270 #define OPTION_MIPS2 (OPTION_MD_BASE + 2)
10271 {"mips2", no_argument, NULL, OPTION_MIPS2},
10272 #define OPTION_MIPS3 (OPTION_MD_BASE + 3)
10273 {"mips3", no_argument, NULL, OPTION_MIPS3},
10274 #define OPTION_MIPS4 (OPTION_MD_BASE + 4)
10275 {"mips4", no_argument, NULL, OPTION_MIPS4},
10276 #define OPTION_MIPS5 (OPTION_MD_BASE + 5)
10277 {"mips5", no_argument, NULL, OPTION_MIPS5},
10278 #define OPTION_MIPS32 (OPTION_MD_BASE + 6)
10279 {"mips32", no_argument, NULL, OPTION_MIPS32},
10280 #define OPTION_MIPS64 (OPTION_MD_BASE + 7)
10281 {"mips64", no_argument, NULL, OPTION_MIPS64},
10282 #define OPTION_MEMBEDDED_PIC (OPTION_MD_BASE + 8)
10283 {"membedded-pic", no_argument, NULL, OPTION_MEMBEDDED_PIC},
10284 #define OPTION_TRAP (OPTION_MD_BASE + 9)
10285 {"trap", no_argument, NULL, OPTION_TRAP},
10286 {"no-break", no_argument, NULL, OPTION_TRAP},
10287 #define OPTION_BREAK (OPTION_MD_BASE + 10)
10288 {"break", no_argument, NULL, OPTION_BREAK},
10289 {"no-trap", no_argument, NULL, OPTION_BREAK},
10290 #define OPTION_EB (OPTION_MD_BASE + 11)
10291 {"EB", no_argument, NULL, OPTION_EB},
10292 #define OPTION_EL (OPTION_MD_BASE + 12)
10293 {"EL", no_argument, NULL, OPTION_EL},
10294 #define OPTION_MIPS16 (OPTION_MD_BASE + 13)
10295 {"mips16", no_argument, NULL, OPTION_MIPS16},
10296 #define OPTION_NO_MIPS16 (OPTION_MD_BASE + 14)
10297 {"no-mips16", no_argument, NULL, OPTION_NO_MIPS16},
10298 #define OPTION_M7000_HILO_FIX (OPTION_MD_BASE + 15)
10299 {"mfix7000", no_argument, NULL, OPTION_M7000_HILO_FIX},
10300 #define OPTION_MNO_7000_HILO_FIX (OPTION_MD_BASE + 16)
10301 {"no-fix-7000", no_argument, NULL, OPTION_MNO_7000_HILO_FIX},
10302 {"mno-fix7000", no_argument, NULL, OPTION_MNO_7000_HILO_FIX},
10303 #define OPTION_FP32 (OPTION_MD_BASE + 17)
10304 {"mfp32", no_argument, NULL, OPTION_FP32},
10305 #define OPTION_GP32 (OPTION_MD_BASE + 18)
10306 {"mgp32", no_argument, NULL, OPTION_GP32},
10307 #define OPTION_CONSTRUCT_FLOATS (OPTION_MD_BASE + 19)
10308 {"construct-floats", no_argument, NULL, OPTION_CONSTRUCT_FLOATS},
10309 #define OPTION_NO_CONSTRUCT_FLOATS (OPTION_MD_BASE + 20)
10310 {"no-construct-floats", no_argument, NULL, OPTION_NO_CONSTRUCT_FLOATS},
10311 #define OPTION_MARCH (OPTION_MD_BASE + 21)
10312 {"march", required_argument, NULL, OPTION_MARCH},
10313 #define OPTION_MTUNE (OPTION_MD_BASE + 22)
10314 {"mtune", required_argument, NULL, OPTION_MTUNE},
10315 #define OPTION_FP64 (OPTION_MD_BASE + 23)
10316 {"mfp64", no_argument, NULL, OPTION_FP64},
10317 #define OPTION_M4650 (OPTION_MD_BASE + 24)
10318 {"m4650", no_argument, NULL, OPTION_M4650},
10319 #define OPTION_NO_M4650 (OPTION_MD_BASE + 25)
10320 {"no-m4650", no_argument, NULL, OPTION_NO_M4650},
10321 #define OPTION_M4010 (OPTION_MD_BASE + 26)
10322 {"m4010", no_argument, NULL, OPTION_M4010},
10323 #define OPTION_NO_M4010 (OPTION_MD_BASE + 27)
10324 {"no-m4010", no_argument, NULL, OPTION_NO_M4010},
10325 #define OPTION_M4100 (OPTION_MD_BASE + 28)
10326 {"m4100", no_argument, NULL, OPTION_M4100},
10327 #define OPTION_NO_M4100 (OPTION_MD_BASE + 29)
10328 {"no-m4100", no_argument, NULL, OPTION_NO_M4100},
10329 #define OPTION_M3900 (OPTION_MD_BASE + 30)
10330 {"m3900", no_argument, NULL, OPTION_M3900},
10331 #define OPTION_NO_M3900 (OPTION_MD_BASE + 31)
10332 {"no-m3900", no_argument, NULL, OPTION_NO_M3900},
10333 #define OPTION_GP64 (OPTION_MD_BASE + 32)
10334 {"mgp64", no_argument, NULL, OPTION_GP64},
10335 #define OPTION_MIPS3D (OPTION_MD_BASE + 33)
10336 {"mips3d", no_argument, NULL, OPTION_MIPS3D},
10337 #define OPTION_NO_MIPS3D (OPTION_MD_BASE + 34)
10338 {"no-mips3d", no_argument, NULL, OPTION_NO_MIPS3D},
10339 #define OPTION_MDMX (OPTION_MD_BASE + 35)
10340 {"mdmx", no_argument, NULL, OPTION_MDMX},
10341 #define OPTION_NO_MDMX (OPTION_MD_BASE + 36)
10342 {"no-mdmx", no_argument, NULL, OPTION_NO_MDMX},
10343 #define OPTION_FIX_VR4122 (OPTION_MD_BASE + 37)
10344 #define OPTION_NO_FIX_VR4122 (OPTION_MD_BASE + 38)
10345 {"mfix-vr4122-bugs", no_argument, NULL, OPTION_FIX_VR4122},
10346 {"no-mfix-vr4122-bugs", no_argument, NULL, OPTION_NO_FIX_VR4122},
10347 #define OPTION_RELAX_BRANCH (OPTION_MD_BASE + 39)
10348 #define OPTION_NO_RELAX_BRANCH (OPTION_MD_BASE + 40)
10349 {"relax-branch", no_argument, NULL, OPTION_RELAX_BRANCH},
10350 {"no-relax-branch", no_argument, NULL, OPTION_NO_RELAX_BRANCH},
10351 #define OPTION_MIPS32R2 (OPTION_MD_BASE + 41)
10352 {"mips32r2", no_argument, NULL, OPTION_MIPS32R2},
10354 #define OPTION_ELF_BASE (OPTION_MD_BASE + 42)
10355 #define OPTION_CALL_SHARED (OPTION_ELF_BASE + 0)
10356 {"KPIC", no_argument, NULL, OPTION_CALL_SHARED},
10357 {"call_shared", no_argument, NULL, OPTION_CALL_SHARED},
10358 #define OPTION_NON_SHARED (OPTION_ELF_BASE + 1)
10359 {"non_shared", no_argument, NULL, OPTION_NON_SHARED},
10360 #define OPTION_XGOT (OPTION_ELF_BASE + 2)
10361 {"xgot", no_argument, NULL, OPTION_XGOT},
10362 #define OPTION_MABI (OPTION_ELF_BASE + 3)
10363 {"mabi", required_argument, NULL, OPTION_MABI},
10364 #define OPTION_32 (OPTION_ELF_BASE + 4)
10365 {"32", no_argument, NULL, OPTION_32},
10366 #define OPTION_N32 (OPTION_ELF_BASE + 5)
10367 {"n32", no_argument, NULL, OPTION_N32},
10368 #define OPTION_64 (OPTION_ELF_BASE + 6)
10369 {"64", no_argument, NULL, OPTION_64},
10370 #define OPTION_MDEBUG (OPTION_ELF_BASE + 7)
10371 {"mdebug", no_argument, NULL, OPTION_MDEBUG},
10372 #define OPTION_NO_MDEBUG (OPTION_ELF_BASE + 8)
10373 {"no-mdebug", no_argument, NULL, OPTION_NO_MDEBUG},
10374 #endif /* OBJ_ELF */
10375 {NULL, no_argument, NULL, 0}
10377 size_t md_longopts_size = sizeof (md_longopts);
10379 /* Set STRING_PTR (either &mips_arch_string or &mips_tune_string) to
10380 NEW_VALUE. Warn if another value was already specified. Note:
10381 we have to defer parsing the -march and -mtune arguments in order
10382 to handle 'from-abi' correctly, since the ABI might be specified
10383 in a later argument. */
10386 mips_set_option_string (string_ptr, new_value)
10387 const char **string_ptr, *new_value;
10389 if (*string_ptr != 0 && strcasecmp (*string_ptr, new_value) != 0)
10390 as_warn (_("A different %s was already specified, is now %s"),
10391 string_ptr == &mips_arch_string ? "-march" : "-mtune",
10394 *string_ptr = new_value;
10398 md_parse_option (c, arg)
10404 case OPTION_CONSTRUCT_FLOATS:
10405 mips_disable_float_construction = 0;
10408 case OPTION_NO_CONSTRUCT_FLOATS:
10409 mips_disable_float_construction = 1;
10421 target_big_endian = 1;
10425 target_big_endian = 0;
10433 if (arg && arg[1] == '0')
10443 mips_debug = atoi (arg);
10444 /* When the MIPS assembler sees -g or -g2, it does not do
10445 optimizations which limit full symbolic debugging. We take
10446 that to be equivalent to -O0. */
10447 if (mips_debug == 2)
10452 file_mips_isa = ISA_MIPS1;
10456 file_mips_isa = ISA_MIPS2;
10460 file_mips_isa = ISA_MIPS3;
10464 file_mips_isa = ISA_MIPS4;
10468 file_mips_isa = ISA_MIPS5;
10471 case OPTION_MIPS32:
10472 file_mips_isa = ISA_MIPS32;
10475 case OPTION_MIPS32R2:
10476 file_mips_isa = ISA_MIPS32R2;
10479 case OPTION_MIPS64:
10480 file_mips_isa = ISA_MIPS64;
10484 mips_set_option_string (&mips_tune_string, arg);
10488 mips_set_option_string (&mips_arch_string, arg);
10492 mips_set_option_string (&mips_arch_string, "4650");
10493 mips_set_option_string (&mips_tune_string, "4650");
10496 case OPTION_NO_M4650:
10500 mips_set_option_string (&mips_arch_string, "4010");
10501 mips_set_option_string (&mips_tune_string, "4010");
10504 case OPTION_NO_M4010:
10508 mips_set_option_string (&mips_arch_string, "4100");
10509 mips_set_option_string (&mips_tune_string, "4100");
10512 case OPTION_NO_M4100:
10516 mips_set_option_string (&mips_arch_string, "3900");
10517 mips_set_option_string (&mips_tune_string, "3900");
10520 case OPTION_NO_M3900:
10524 mips_opts.ase_mdmx = 1;
10527 case OPTION_NO_MDMX:
10528 mips_opts.ase_mdmx = 0;
10531 case OPTION_MIPS16:
10532 mips_opts.mips16 = 1;
10533 mips_no_prev_insn (FALSE);
10536 case OPTION_NO_MIPS16:
10537 mips_opts.mips16 = 0;
10538 mips_no_prev_insn (FALSE);
10541 case OPTION_MIPS3D:
10542 mips_opts.ase_mips3d = 1;
10545 case OPTION_NO_MIPS3D:
10546 mips_opts.ase_mips3d = 0;
10549 case OPTION_MEMBEDDED_PIC:
10550 mips_pic = EMBEDDED_PIC;
10551 if (USE_GLOBAL_POINTER_OPT && g_switch_seen)
10553 as_bad (_("-G may not be used with embedded PIC code"));
10556 g_switch_value = 0x7fffffff;
10559 case OPTION_FIX_VR4122:
10560 mips_fix_4122_bugs = 1;
10563 case OPTION_NO_FIX_VR4122:
10564 mips_fix_4122_bugs = 0;
10567 case OPTION_RELAX_BRANCH:
10568 mips_relax_branch = 1;
10571 case OPTION_NO_RELAX_BRANCH:
10572 mips_relax_branch = 0;
10576 /* When generating ELF code, we permit -KPIC and -call_shared to
10577 select SVR4_PIC, and -non_shared to select no PIC. This is
10578 intended to be compatible with Irix 5. */
10579 case OPTION_CALL_SHARED:
10580 if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
10582 as_bad (_("-call_shared is supported only for ELF format"));
10585 mips_pic = SVR4_PIC;
10586 if (g_switch_seen && g_switch_value != 0)
10588 as_bad (_("-G may not be used with SVR4 PIC code"));
10591 g_switch_value = 0;
10594 case OPTION_NON_SHARED:
10595 if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
10597 as_bad (_("-non_shared is supported only for ELF format"));
10603 /* The -xgot option tells the assembler to use 32 offsets when
10604 accessing the got in SVR4_PIC mode. It is for Irix
10609 #endif /* OBJ_ELF */
10612 if (! USE_GLOBAL_POINTER_OPT)
10614 as_bad (_("-G is not supported for this configuration"));
10617 else if (mips_pic == SVR4_PIC || mips_pic == EMBEDDED_PIC)
10619 as_bad (_("-G may not be used with SVR4 or embedded PIC code"));
10623 g_switch_value = atoi (arg);
10628 /* The -32, -n32 and -64 options are shortcuts for -mabi=32, -mabi=n32
10631 if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
10633 as_bad (_("-32 is supported for ELF format only"));
10636 mips_abi = O32_ABI;
10640 if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
10642 as_bad (_("-n32 is supported for ELF format only"));
10645 mips_abi = N32_ABI;
10649 if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
10651 as_bad (_("-64 is supported for ELF format only"));
10654 mips_abi = N64_ABI;
10655 if (! support_64bit_objects())
10656 as_fatal (_("No compiled in support for 64 bit object file format"));
10658 #endif /* OBJ_ELF */
10661 file_mips_gp32 = 1;
10665 file_mips_gp32 = 0;
10669 file_mips_fp32 = 1;
10673 file_mips_fp32 = 0;
10678 if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
10680 as_bad (_("-mabi is supported for ELF format only"));
10683 if (strcmp (arg, "32") == 0)
10684 mips_abi = O32_ABI;
10685 else if (strcmp (arg, "o64") == 0)
10686 mips_abi = O64_ABI;
10687 else if (strcmp (arg, "n32") == 0)
10688 mips_abi = N32_ABI;
10689 else if (strcmp (arg, "64") == 0)
10691 mips_abi = N64_ABI;
10692 if (! support_64bit_objects())
10693 as_fatal (_("No compiled in support for 64 bit object file "
10696 else if (strcmp (arg, "eabi") == 0)
10697 mips_abi = EABI_ABI;
10700 as_fatal (_("invalid abi -mabi=%s"), arg);
10704 #endif /* OBJ_ELF */
10706 case OPTION_M7000_HILO_FIX:
10707 mips_7000_hilo_fix = TRUE;
10710 case OPTION_MNO_7000_HILO_FIX:
10711 mips_7000_hilo_fix = FALSE;
10715 case OPTION_MDEBUG:
10716 mips_flag_mdebug = TRUE;
10719 case OPTION_NO_MDEBUG:
10720 mips_flag_mdebug = FALSE;
10722 #endif /* OBJ_ELF */
10731 /* Set up globals to generate code for the ISA or processor
10732 described by INFO. */
10735 mips_set_architecture (info)
10736 const struct mips_cpu_info *info;
10740 mips_arch_info = info;
10741 mips_arch = info->cpu;
10742 mips_opts.isa = info->isa;
10747 /* Likewise for tuning. */
10750 mips_set_tune (info)
10751 const struct mips_cpu_info *info;
10755 mips_tune_info = info;
10756 mips_tune = info->cpu;
10762 mips_after_parse_args ()
10764 /* GP relative stuff not working for PE */
10765 if (strncmp (TARGET_OS, "pe", 2) == 0
10766 && g_switch_value != 0)
10769 as_bad (_("-G not supported in this configuration."));
10770 g_switch_value = 0;
10773 /* The following code determines the architecture and register size.
10774 Similar code was added to GCC 3.3 (see override_options() in
10775 config/mips/mips.c). The GAS and GCC code should be kept in sync
10776 as much as possible. */
10778 if (mips_arch_string != 0)
10779 mips_set_architecture (mips_parse_cpu ("-march", mips_arch_string));
10781 if (mips_tune_string != 0)
10782 mips_set_tune (mips_parse_cpu ("-mtune", mips_tune_string));
10784 if (file_mips_isa != ISA_UNKNOWN)
10786 /* Handle -mipsN. At this point, file_mips_isa contains the
10787 ISA level specified by -mipsN, while mips_opts.isa contains
10788 the -march selection (if any). */
10789 if (mips_arch_info != 0)
10791 /* -march takes precedence over -mipsN, since it is more descriptive.
10792 There's no harm in specifying both as long as the ISA levels
10794 if (file_mips_isa != mips_opts.isa)
10795 as_bad (_("-%s conflicts with the other architecture options, which imply -%s"),
10796 mips_cpu_info_from_isa (file_mips_isa)->name,
10797 mips_cpu_info_from_isa (mips_opts.isa)->name);
10800 mips_set_architecture (mips_cpu_info_from_isa (file_mips_isa));
10803 if (mips_arch_info == 0)
10804 mips_set_architecture (mips_parse_cpu ("default CPU",
10805 MIPS_CPU_STRING_DEFAULT));
10807 if (ABI_NEEDS_64BIT_REGS (mips_abi) && !ISA_HAS_64BIT_REGS (mips_opts.isa))
10808 as_bad ("-march=%s is not compatible with the selected ABI",
10809 mips_arch_info->name);
10811 /* Optimize for mips_arch, unless -mtune selects a different processor. */
10812 if (mips_tune_info == 0)
10813 mips_set_tune (mips_arch_info);
10815 if (file_mips_gp32 >= 0)
10817 /* The user specified the size of the integer registers. Make sure
10818 it agrees with the ABI and ISA. */
10819 if (file_mips_gp32 == 0 && !ISA_HAS_64BIT_REGS (mips_opts.isa))
10820 as_bad (_("-mgp64 used with a 32-bit processor"));
10821 else if (file_mips_gp32 == 1 && ABI_NEEDS_64BIT_REGS (mips_abi))
10822 as_bad (_("-mgp32 used with a 64-bit ABI"));
10823 else if (file_mips_gp32 == 0 && ABI_NEEDS_32BIT_REGS (mips_abi))
10824 as_bad (_("-mgp64 used with a 32-bit ABI"));
10828 /* Infer the integer register size from the ABI and processor.
10829 Restrict ourselves to 32-bit registers if that's all the
10830 processor has, or if the ABI cannot handle 64-bit registers. */
10831 file_mips_gp32 = (ABI_NEEDS_32BIT_REGS (mips_abi)
10832 || !ISA_HAS_64BIT_REGS (mips_opts.isa));
10835 /* ??? GAS treats single-float processors as though they had 64-bit
10836 float registers (although it complains when double-precision
10837 instructions are used). As things stand, saying they have 32-bit
10838 registers would lead to spurious "register must be even" messages.
10839 So here we assume float registers are always the same size as
10840 integer ones, unless the user says otherwise. */
10841 if (file_mips_fp32 < 0)
10842 file_mips_fp32 = file_mips_gp32;
10844 /* End of GCC-shared inference code. */
10846 /* ??? When do we want this flag to be set? Who uses it? */
10847 if (file_mips_gp32 == 1
10848 && mips_abi == NO_ABI
10849 && ISA_HAS_64BIT_REGS (mips_opts.isa))
10850 mips_32bitmode = 1;
10852 if (mips_opts.isa == ISA_MIPS1 && mips_trap)
10853 as_bad (_("trap exception not supported at ISA 1"));
10855 /* If the selected architecture includes support for ASEs, enable
10856 generation of code for them. */
10857 if (mips_opts.mips16 == -1)
10858 mips_opts.mips16 = (CPU_HAS_MIPS16 (mips_arch)) ? 1 : 0;
10859 if (mips_opts.ase_mips3d == -1)
10860 mips_opts.ase_mips3d = (CPU_HAS_MIPS3D (mips_arch)) ? 1 : 0;
10861 if (mips_opts.ase_mdmx == -1)
10862 mips_opts.ase_mdmx = (CPU_HAS_MDMX (mips_arch)) ? 1 : 0;
10864 file_mips_isa = mips_opts.isa;
10865 file_ase_mips16 = mips_opts.mips16;
10866 file_ase_mips3d = mips_opts.ase_mips3d;
10867 file_ase_mdmx = mips_opts.ase_mdmx;
10868 mips_opts.gp32 = file_mips_gp32;
10869 mips_opts.fp32 = file_mips_fp32;
10871 if (mips_flag_mdebug < 0)
10873 #ifdef OBJ_MAYBE_ECOFF
10874 if (OUTPUT_FLAVOR == bfd_target_ecoff_flavour)
10875 mips_flag_mdebug = 1;
10877 #endif /* OBJ_MAYBE_ECOFF */
10878 mips_flag_mdebug = 0;
10883 mips_init_after_args ()
10885 /* initialize opcodes */
10886 bfd_mips_num_opcodes = bfd_mips_num_builtin_opcodes;
10887 mips_opcodes = (struct mips_opcode *) mips_builtin_opcodes;
10891 md_pcrel_from (fixP)
10894 if (OUTPUT_FLAVOR != bfd_target_aout_flavour
10895 && fixP->fx_addsy != (symbolS *) NULL
10896 && ! S_IS_DEFINED (fixP->fx_addsy))
10899 /* Return the address of the delay slot. */
10900 return fixP->fx_size + fixP->fx_where + fixP->fx_frag->fr_address;
10903 /* This is called before the symbol table is processed. In order to
10904 work with gcc when using mips-tfile, we must keep all local labels.
10905 However, in other cases, we want to discard them. If we were
10906 called with -g, but we didn't see any debugging information, it may
10907 mean that gcc is smuggling debugging information through to
10908 mips-tfile, in which case we must generate all local labels. */
10911 mips_frob_file_before_adjust ()
10913 #ifndef NO_ECOFF_DEBUGGING
10914 if (ECOFF_DEBUGGING
10916 && ! ecoff_debugging_seen)
10917 flag_keep_locals = 1;
10921 /* Sort any unmatched HI16_S relocs so that they immediately precede
10922 the corresponding LO reloc. This is called before md_apply_fix3 and
10923 tc_gen_reloc. Unmatched HI16_S relocs can only be generated by
10924 explicit use of the %hi modifier. */
10929 struct mips_hi_fixup *l;
10931 for (l = mips_hi_fixup_list; l != NULL; l = l->next)
10933 segment_info_type *seginfo;
10936 assert (reloc_needs_lo_p (l->fixp->fx_r_type));
10938 /* If a GOT16 relocation turns out to be against a global symbol,
10939 there isn't supposed to be a matching LO. */
10940 if (l->fixp->fx_r_type == BFD_RELOC_MIPS_GOT16
10941 && !pic_need_relax (l->fixp->fx_addsy, l->seg))
10944 /* Check quickly whether the next fixup happens to be a matching %lo. */
10945 if (fixup_has_matching_lo_p (l->fixp))
10948 /* Look through the fixups for this segment for a matching %lo.
10949 When we find one, move the %hi just in front of it. We do
10950 this in two passes. In the first pass, we try to find a
10951 unique %lo. In the second pass, we permit multiple %hi
10952 relocs for a single %lo (this is a GNU extension). */
10953 seginfo = seg_info (l->seg);
10954 for (pass = 0; pass < 2; pass++)
10959 for (f = seginfo->fix_root; f != NULL; f = f->fx_next)
10961 /* Check whether this is a %lo fixup which matches l->fixp. */
10962 if (f->fx_r_type == BFD_RELOC_LO16
10963 && f->fx_addsy == l->fixp->fx_addsy
10964 && f->fx_offset == l->fixp->fx_offset
10967 || !reloc_needs_lo_p (prev->fx_r_type)
10968 || !fixup_has_matching_lo_p (prev)))
10972 /* Move l->fixp before f. */
10973 for (pf = &seginfo->fix_root;
10975 pf = &(*pf)->fx_next)
10976 assert (*pf != NULL);
10978 *pf = l->fixp->fx_next;
10980 l->fixp->fx_next = f;
10982 seginfo->fix_root = l->fixp;
10984 prev->fx_next = l->fixp;
10995 #if 0 /* GCC code motion plus incomplete dead code elimination
10996 can leave a %hi without a %lo. */
10998 as_warn_where (l->fixp->fx_file, l->fixp->fx_line,
10999 _("Unmatched %%hi reloc"));
11005 /* When generating embedded PIC code we need to use a special
11006 relocation to represent the difference of two symbols in the .text
11007 section (switch tables use a difference of this sort). See
11008 include/coff/mips.h for details. This macro checks whether this
11009 fixup requires the special reloc. */
11010 #define SWITCH_TABLE(fixp) \
11011 ((fixp)->fx_r_type == BFD_RELOC_32 \
11012 && OUTPUT_FLAVOR != bfd_target_elf_flavour \
11013 && (fixp)->fx_addsy != NULL \
11014 && (fixp)->fx_subsy != NULL \
11015 && S_GET_SEGMENT ((fixp)->fx_addsy) == text_section \
11016 && S_GET_SEGMENT ((fixp)->fx_subsy) == text_section)
11018 /* When generating embedded PIC code we must keep all PC relative
11019 relocations, in case the linker has to relax a call. We also need
11020 to keep relocations for switch table entries.
11022 We may have combined relocations without symbols in the N32/N64 ABI.
11023 We have to prevent gas from dropping them. */
11026 mips_force_relocation (fixp)
11029 if (generic_force_reloc (fixp))
11033 && S_GET_SEGMENT (fixp->fx_addsy) == bfd_abs_section_ptr
11034 && (fixp->fx_r_type == BFD_RELOC_MIPS_SUB
11035 || fixp->fx_r_type == BFD_RELOC_HI16_S
11036 || fixp->fx_r_type == BFD_RELOC_LO16))
11039 return (mips_pic == EMBEDDED_PIC
11041 || SWITCH_TABLE (fixp)
11042 || fixp->fx_r_type == BFD_RELOC_PCREL_HI16_S
11043 || fixp->fx_r_type == BFD_RELOC_PCREL_LO16));
11046 /* This hook is called before a fix is simplified. We don't really
11047 decide whether to skip a fix here. Rather, we turn global symbols
11048 used as branch targets into local symbols, such that they undergo
11049 simplification. We can only do this if the symbol is defined and
11050 it is in the same section as the branch. If this doesn't hold, we
11051 emit a better error message than just saying the relocation is not
11052 valid for the selected object format.
11054 FIXP is the fix-up we're going to try to simplify, SEG is the
11055 segment in which the fix up occurs. The return value should be
11056 non-zero to indicate the fix-up is valid for further
11057 simplifications. */
11060 mips_validate_fix (fixP, seg)
11064 /* There's a lot of discussion on whether it should be possible to
11065 use R_MIPS_PC16 to represent branch relocations. The outcome
11066 seems to be that it can, but gas/bfd are very broken in creating
11067 RELA relocations for this, so for now we only accept branches to
11068 symbols in the same section. Anything else is of dubious value,
11069 since there's no guarantee that at link time the symbol would be
11070 in range. Even for branches to local symbols this is arguably
11071 wrong, since it we assume the symbol is not going to be
11072 overridden, which should be possible per ELF library semantics,
11073 but then, there isn't a dynamic relocation that could be used to
11074 this effect, and the target would likely be out of range as well.
11076 Unfortunately, it seems that there is too much code out there
11077 that relies on branches to symbols that are global to be resolved
11078 as if they were local, like the IRIX tools do, so we do it as
11079 well, but with a warning so that people are reminded to fix their
11080 code. If we ever get back to using R_MIPS_PC16 for branch
11081 targets, this entire block should go away (and probably the
11082 whole function). */
11084 if (fixP->fx_r_type == BFD_RELOC_16_PCREL_S2
11085 && (((OUTPUT_FLAVOR == bfd_target_ecoff_flavour
11086 || OUTPUT_FLAVOR == bfd_target_elf_flavour)
11087 && mips_pic != EMBEDDED_PIC)
11088 || bfd_reloc_type_lookup (stdoutput, BFD_RELOC_16_PCREL_S2) == NULL)
11091 if (! S_IS_DEFINED (fixP->fx_addsy))
11093 as_bad_where (fixP->fx_file, fixP->fx_line,
11094 _("Cannot branch to undefined symbol."));
11095 /* Avoid any further errors about this fixup. */
11098 else if (S_GET_SEGMENT (fixP->fx_addsy) != seg)
11100 as_bad_where (fixP->fx_file, fixP->fx_line,
11101 _("Cannot branch to symbol in another section."));
11104 else if (S_IS_EXTERNAL (fixP->fx_addsy))
11106 symbolS *sym = fixP->fx_addsy;
11108 as_warn_where (fixP->fx_file, fixP->fx_line,
11109 _("Pretending global symbol used as branch target is local."));
11111 fixP->fx_addsy = symbol_create (S_GET_NAME (sym),
11112 S_GET_SEGMENT (sym),
11114 symbol_get_frag (sym));
11115 copy_symbol_attributes (fixP->fx_addsy, sym);
11116 S_CLEAR_EXTERNAL (fixP->fx_addsy);
11117 assert (symbol_resolved_p (sym));
11118 symbol_mark_resolved (fixP->fx_addsy);
11127 mips_need_elf_addend_fixup (fixP)
11130 if (S_GET_OTHER (fixP->fx_addsy) == STO_MIPS16)
11132 if (mips_pic == EMBEDDED_PIC
11133 && S_IS_WEAK (fixP->fx_addsy))
11135 if (mips_pic != EMBEDDED_PIC
11136 && (S_IS_WEAK (fixP->fx_addsy)
11137 || S_IS_EXTERNAL (fixP->fx_addsy))
11138 && !S_IS_COMMON (fixP->fx_addsy))
11140 if (symbol_used_in_reloc_p (fixP->fx_addsy)
11141 && (((bfd_get_section_flags (stdoutput,
11142 S_GET_SEGMENT (fixP->fx_addsy))
11143 & (SEC_LINK_ONCE | SEC_MERGE)) != 0)
11144 || !strncmp (segment_name (S_GET_SEGMENT (fixP->fx_addsy)),
11146 sizeof (".gnu.linkonce") - 1)))
11152 /* Apply a fixup to the object file. */
11155 md_apply_fix3 (fixP, valP, seg)
11158 segT seg ATTRIBUTE_UNUSED;
11163 static int previous_fx_r_type = 0;
11165 /* FIXME: Maybe just return for all reloc types not listed below?
11166 Eric Christopher says: "This is stupid, please rewrite md_apply_fix3. */
11167 if (fixP->fx_r_type == BFD_RELOC_8)
11170 assert (fixP->fx_size == 4
11171 || fixP->fx_r_type == BFD_RELOC_16
11172 || fixP->fx_r_type == BFD_RELOC_32
11173 || fixP->fx_r_type == BFD_RELOC_MIPS_JMP
11174 || fixP->fx_r_type == BFD_RELOC_HI16_S
11175 || fixP->fx_r_type == BFD_RELOC_LO16
11176 || fixP->fx_r_type == BFD_RELOC_GPREL16
11177 || fixP->fx_r_type == BFD_RELOC_MIPS_LITERAL
11178 || fixP->fx_r_type == BFD_RELOC_GPREL32
11179 || fixP->fx_r_type == BFD_RELOC_64
11180 || fixP->fx_r_type == BFD_RELOC_CTOR
11181 || fixP->fx_r_type == BFD_RELOC_MIPS_SUB
11182 || fixP->fx_r_type == BFD_RELOC_MIPS_HIGHEST
11183 || fixP->fx_r_type == BFD_RELOC_MIPS_HIGHER
11184 || fixP->fx_r_type == BFD_RELOC_MIPS_SCN_DISP
11185 || fixP->fx_r_type == BFD_RELOC_MIPS_REL16
11186 || fixP->fx_r_type == BFD_RELOC_MIPS_RELGOT
11187 || fixP->fx_r_type == BFD_RELOC_VTABLE_INHERIT
11188 || fixP->fx_r_type == BFD_RELOC_VTABLE_ENTRY
11189 || fixP->fx_r_type == BFD_RELOC_MIPS_JALR);
11193 /* If we aren't adjusting this fixup to be against the section
11194 symbol, we need to adjust the value. */
11196 if (fixP->fx_addsy != NULL && OUTPUT_FLAVOR == bfd_target_elf_flavour)
11198 if (mips_need_elf_addend_fixup (fixP))
11200 reloc_howto_type *howto;
11201 valueT symval = S_GET_VALUE (fixP->fx_addsy);
11205 howto = bfd_reloc_type_lookup (stdoutput, fixP->fx_r_type);
11206 if (value != 0 && howto && howto->partial_inplace
11207 && (! fixP->fx_pcrel || howto->pcrel_offset))
11209 /* In this case, the bfd_install_relocation routine will
11210 incorrectly add the symbol value back in. We just want
11211 the addend to appear in the object file.
11213 howto->pcrel_offset is added for R_MIPS_PC16, which is
11214 generated for code like
11225 /* Make sure the addend is still non-zero. If it became zero
11226 after the last operation, set it to a spurious value and
11227 subtract the same value from the object file's contents. */
11232 /* The in-place addends for LO16 relocations are signed;
11233 leave the matching HI16 in-place addends as zero. */
11234 if (fixP->fx_r_type != BFD_RELOC_HI16_S)
11236 bfd_vma contents, mask, field;
11238 contents = bfd_get_bits (fixP->fx_frag->fr_literal
11241 target_big_endian);
11243 /* MASK has bits set where the relocation should go.
11244 FIELD is -value, shifted into the appropriate place
11245 for this relocation. */
11246 mask = 1 << (howto->bitsize - 1);
11247 mask = (((mask - 1) << 1) | 1) << howto->bitpos;
11248 field = (-value >> howto->rightshift) << howto->bitpos;
11250 bfd_put_bits ((field & mask) | (contents & ~mask),
11251 fixP->fx_frag->fr_literal + fixP->fx_where,
11253 target_big_endian);
11259 /* This code was generated using trial and error and so is
11260 fragile and not trustworthy. If you change it, you should
11261 rerun the elf-rel, elf-rel2, and empic testcases and ensure
11262 they still pass. */
11263 if (fixP->fx_pcrel || fixP->fx_subsy != NULL)
11265 value += fixP->fx_frag->fr_address + fixP->fx_where;
11267 /* BFD's REL handling, for MIPS, is _very_ weird.
11268 This gives the right results, but it can't possibly
11269 be the way things are supposed to work. */
11270 if (fixP->fx_r_type != BFD_RELOC_16_PCREL_S2
11271 || S_GET_SEGMENT (fixP->fx_addsy) != undefined_section)
11272 value += fixP->fx_frag->fr_address + fixP->fx_where;
11277 fixP->fx_addnumber = value; /* Remember value for tc_gen_reloc. */
11279 /* We are not done if this is a composite relocation to set up gp. */
11280 if (fixP->fx_addsy == NULL && ! fixP->fx_pcrel
11281 && !(fixP->fx_r_type == BFD_RELOC_MIPS_SUB
11282 || (fixP->fx_r_type == BFD_RELOC_64
11283 && (previous_fx_r_type == BFD_RELOC_GPREL32
11284 || previous_fx_r_type == BFD_RELOC_GPREL16))
11285 || (previous_fx_r_type == BFD_RELOC_MIPS_SUB
11286 && (fixP->fx_r_type == BFD_RELOC_HI16_S
11287 || fixP->fx_r_type == BFD_RELOC_LO16))))
11289 previous_fx_r_type = fixP->fx_r_type;
11291 switch (fixP->fx_r_type)
11293 case BFD_RELOC_MIPS_JMP:
11294 case BFD_RELOC_MIPS_SHIFT5:
11295 case BFD_RELOC_MIPS_SHIFT6:
11296 case BFD_RELOC_MIPS_GOT_DISP:
11297 case BFD_RELOC_MIPS_GOT_PAGE:
11298 case BFD_RELOC_MIPS_GOT_OFST:
11299 case BFD_RELOC_MIPS_SUB:
11300 case BFD_RELOC_MIPS_INSERT_A:
11301 case BFD_RELOC_MIPS_INSERT_B:
11302 case BFD_RELOC_MIPS_DELETE:
11303 case BFD_RELOC_MIPS_HIGHEST:
11304 case BFD_RELOC_MIPS_HIGHER:
11305 case BFD_RELOC_MIPS_SCN_DISP:
11306 case BFD_RELOC_MIPS_REL16:
11307 case BFD_RELOC_MIPS_RELGOT:
11308 case BFD_RELOC_MIPS_JALR:
11309 case BFD_RELOC_HI16:
11310 case BFD_RELOC_HI16_S:
11311 case BFD_RELOC_GPREL16:
11312 case BFD_RELOC_MIPS_LITERAL:
11313 case BFD_RELOC_MIPS_CALL16:
11314 case BFD_RELOC_MIPS_GOT16:
11315 case BFD_RELOC_GPREL32:
11316 case BFD_RELOC_MIPS_GOT_HI16:
11317 case BFD_RELOC_MIPS_GOT_LO16:
11318 case BFD_RELOC_MIPS_CALL_HI16:
11319 case BFD_RELOC_MIPS_CALL_LO16:
11320 case BFD_RELOC_MIPS16_GPREL:
11321 if (fixP->fx_pcrel)
11322 as_bad_where (fixP->fx_file, fixP->fx_line,
11323 _("Invalid PC relative reloc"));
11324 /* Nothing needed to do. The value comes from the reloc entry */
11327 case BFD_RELOC_MIPS16_JMP:
11328 /* We currently always generate a reloc against a symbol, which
11329 means that we don't want an addend even if the symbol is
11331 fixP->fx_addnumber = 0;
11334 case BFD_RELOC_PCREL_HI16_S:
11335 /* The addend for this is tricky if it is internal, so we just
11336 do everything here rather than in bfd_install_relocation. */
11337 if (OUTPUT_FLAVOR == bfd_target_elf_flavour
11342 && (symbol_get_bfdsym (fixP->fx_addsy)->flags & BSF_SECTION_SYM) == 0)
11344 /* For an external symbol adjust by the address to make it
11345 pcrel_offset. We use the address of the RELLO reloc
11346 which follows this one. */
11347 value += (fixP->fx_next->fx_frag->fr_address
11348 + fixP->fx_next->fx_where);
11350 value = ((value + 0x8000) >> 16) & 0xffff;
11351 buf = (bfd_byte *) fixP->fx_frag->fr_literal + fixP->fx_where;
11352 if (target_big_endian)
11354 md_number_to_chars ((char *) buf, value, 2);
11357 case BFD_RELOC_PCREL_LO16:
11358 /* The addend for this is tricky if it is internal, so we just
11359 do everything here rather than in bfd_install_relocation. */
11360 if (OUTPUT_FLAVOR == bfd_target_elf_flavour
11365 && (symbol_get_bfdsym (fixP->fx_addsy)->flags & BSF_SECTION_SYM) == 0)
11366 value += fixP->fx_frag->fr_address + fixP->fx_where;
11367 buf = (bfd_byte *) fixP->fx_frag->fr_literal + fixP->fx_where;
11368 if (target_big_endian)
11370 md_number_to_chars ((char *) buf, value, 2);
11374 /* This is handled like BFD_RELOC_32, but we output a sign
11375 extended value if we are only 32 bits. */
11377 || (mips_pic == EMBEDDED_PIC && SWITCH_TABLE (fixP)))
11379 if (8 <= sizeof (valueT))
11380 md_number_to_chars (fixP->fx_frag->fr_literal + fixP->fx_where,
11387 w1 = w2 = fixP->fx_where;
11388 if (target_big_endian)
11392 md_number_to_chars (fixP->fx_frag->fr_literal + w1, value, 4);
11393 if ((value & 0x80000000) != 0)
11397 md_number_to_chars (fixP->fx_frag->fr_literal + w2, hiv, 4);
11402 case BFD_RELOC_RVA:
11404 /* If we are deleting this reloc entry, we must fill in the
11405 value now. This can happen if we have a .word which is not
11406 resolved when it appears but is later defined. We also need
11407 to fill in the value if this is an embedded PIC switch table
11410 || (mips_pic == EMBEDDED_PIC && SWITCH_TABLE (fixP)))
11411 md_number_to_chars (fixP->fx_frag->fr_literal + fixP->fx_where,
11416 /* If we are deleting this reloc entry, we must fill in the
11418 assert (fixP->fx_size == 2);
11420 md_number_to_chars (fixP->fx_frag->fr_literal + fixP->fx_where,
11424 case BFD_RELOC_LO16:
11425 /* When handling an embedded PIC switch statement, we can wind
11426 up deleting a LO16 reloc. See the 'o' case in mips_ip. */
11429 if (value + 0x8000 > 0xffff)
11430 as_bad_where (fixP->fx_file, fixP->fx_line,
11431 _("relocation overflow"));
11432 buf = (bfd_byte *) fixP->fx_frag->fr_literal + fixP->fx_where;
11433 if (target_big_endian)
11435 md_number_to_chars ((char *) buf, value, 2);
11439 case BFD_RELOC_16_PCREL_S2:
11440 if ((value & 0x3) != 0)
11441 as_bad_where (fixP->fx_file, fixP->fx_line,
11442 _("Branch to odd address (%lx)"), (long) value);
11445 * We need to save the bits in the instruction since fixup_segment()
11446 * might be deleting the relocation entry (i.e., a branch within
11447 * the current segment).
11449 if (!fixP->fx_done && (value != 0 || HAVE_NEWABI))
11451 /* If 'value' is zero, the remaining reloc code won't actually
11452 do the store, so it must be done here. This is probably
11453 a bug somewhere. */
11455 && (fixP->fx_r_type != BFD_RELOC_16_PCREL_S2
11456 || fixP->fx_addsy == NULL /* ??? */
11457 || ! S_IS_DEFINED (fixP->fx_addsy)))
11458 value -= fixP->fx_frag->fr_address + fixP->fx_where;
11460 value = (offsetT) value >> 2;
11462 /* update old instruction data */
11463 buf = (bfd_byte *) (fixP->fx_where + fixP->fx_frag->fr_literal);
11464 if (target_big_endian)
11465 insn = (buf[0] << 24) | (buf[1] << 16) | (buf[2] << 8) | buf[3];
11467 insn = (buf[3] << 24) | (buf[2] << 16) | (buf[1] << 8) | buf[0];
11469 if (value + 0x8000 <= 0xffff)
11470 insn |= value & 0xffff;
11473 /* The branch offset is too large. If this is an
11474 unconditional branch, and we are not generating PIC code,
11475 we can convert it to an absolute jump instruction. */
11476 if (mips_pic == NO_PIC
11478 && fixP->fx_frag->fr_address >= text_section->vma
11479 && (fixP->fx_frag->fr_address
11480 < text_section->vma + text_section->_raw_size)
11481 && ((insn & 0xffff0000) == 0x10000000 /* beq $0,$0 */
11482 || (insn & 0xffff0000) == 0x04010000 /* bgez $0 */
11483 || (insn & 0xffff0000) == 0x04110000)) /* bgezal $0 */
11485 if ((insn & 0xffff0000) == 0x04110000) /* bgezal $0 */
11486 insn = 0x0c000000; /* jal */
11488 insn = 0x08000000; /* j */
11489 fixP->fx_r_type = BFD_RELOC_MIPS_JMP;
11491 fixP->fx_addsy = section_symbol (text_section);
11492 fixP->fx_addnumber = (value << 2) + md_pcrel_from (fixP);
11496 /* If we got here, we have branch-relaxation disabled,
11497 and there's nothing we can do to fix this instruction
11498 without turning it into a longer sequence. */
11499 as_bad_where (fixP->fx_file, fixP->fx_line,
11500 _("Branch out of range"));
11504 md_number_to_chars ((char *) buf, (valueT) insn, 4);
11507 case BFD_RELOC_VTABLE_INHERIT:
11510 && !S_IS_DEFINED (fixP->fx_addsy)
11511 && !S_IS_WEAK (fixP->fx_addsy))
11512 S_SET_WEAK (fixP->fx_addsy);
11515 case BFD_RELOC_VTABLE_ENTRY:
11529 const struct mips_opcode *p;
11530 int treg, sreg, dreg, shamt;
11535 for (i = 0; i < NUMOPCODES; ++i)
11537 p = &mips_opcodes[i];
11538 if (((oc & p->mask) == p->match) && (p->pinfo != INSN_MACRO))
11540 printf ("%08lx %s\t", oc, p->name);
11541 treg = (oc >> 16) & 0x1f;
11542 sreg = (oc >> 21) & 0x1f;
11543 dreg = (oc >> 11) & 0x1f;
11544 shamt = (oc >> 6) & 0x1f;
11546 for (args = p->args;; ++args)
11557 printf ("%c", *args);
11561 assert (treg == sreg);
11562 printf ("$%d,$%d", treg, sreg);
11567 printf ("$%d", dreg);
11572 printf ("$%d", treg);
11576 printf ("0x%x", treg);
11581 printf ("$%d", sreg);
11585 printf ("0x%08lx", oc & 0x1ffffff);
11592 printf ("%d", imm);
11597 printf ("$%d", shamt);
11608 printf (_("%08lx UNDEFINED\n"), oc);
11619 name = input_line_pointer;
11620 c = get_symbol_end ();
11621 p = (symbolS *) symbol_find_or_make (name);
11622 *input_line_pointer = c;
11626 /* Align the current frag to a given power of two. The MIPS assembler
11627 also automatically adjusts any preceding label. */
11630 mips_align (to, fill, label)
11635 mips_emit_delays (FALSE);
11636 frag_align (to, fill, 0);
11637 record_alignment (now_seg, to);
11640 assert (S_GET_SEGMENT (label) == now_seg);
11641 symbol_set_frag (label, frag_now);
11642 S_SET_VALUE (label, (valueT) frag_now_fix ());
11646 /* Align to a given power of two. .align 0 turns off the automatic
11647 alignment used by the data creating pseudo-ops. */
11651 int x ATTRIBUTE_UNUSED;
11654 register long temp_fill;
11655 long max_alignment = 15;
11659 o Note that the assembler pulls down any immediately preceeding label
11660 to the aligned address.
11661 o It's not documented but auto alignment is reinstated by
11662 a .align pseudo instruction.
11663 o Note also that after auto alignment is turned off the mips assembler
11664 issues an error on attempt to assemble an improperly aligned data item.
11669 temp = get_absolute_expression ();
11670 if (temp > max_alignment)
11671 as_bad (_("Alignment too large: %d. assumed."), temp = max_alignment);
11674 as_warn (_("Alignment negative: 0 assumed."));
11677 if (*input_line_pointer == ',')
11679 ++input_line_pointer;
11680 temp_fill = get_absolute_expression ();
11687 mips_align (temp, (int) temp_fill,
11688 insn_labels != NULL ? insn_labels->label : NULL);
11695 demand_empty_rest_of_line ();
11699 mips_flush_pending_output ()
11701 mips_emit_delays (FALSE);
11702 mips_clear_insn_labels ();
11711 /* When generating embedded PIC code, we only use the .text, .lit8,
11712 .sdata and .sbss sections. We change the .data and .rdata
11713 pseudo-ops to use .sdata. */
11714 if (mips_pic == EMBEDDED_PIC
11715 && (sec == 'd' || sec == 'r'))
11719 /* The ELF backend needs to know that we are changing sections, so
11720 that .previous works correctly. We could do something like check
11721 for an obj_section_change_hook macro, but that might be confusing
11722 as it would not be appropriate to use it in the section changing
11723 functions in read.c, since obj-elf.c intercepts those. FIXME:
11724 This should be cleaner, somehow. */
11725 obj_elf_section_change_hook ();
11728 mips_emit_delays (FALSE);
11738 subseg_set (bss_section, (subsegT) get_absolute_expression ());
11739 demand_empty_rest_of_line ();
11743 if (USE_GLOBAL_POINTER_OPT)
11745 seg = subseg_new (RDATA_SECTION_NAME,
11746 (subsegT) get_absolute_expression ());
11747 if (OUTPUT_FLAVOR == bfd_target_elf_flavour)
11749 bfd_set_section_flags (stdoutput, seg,
11755 if (strcmp (TARGET_OS, "elf") != 0)
11756 record_alignment (seg, 4);
11758 demand_empty_rest_of_line ();
11762 as_bad (_("No read only data section in this object file format"));
11763 demand_empty_rest_of_line ();
11769 if (USE_GLOBAL_POINTER_OPT)
11771 seg = subseg_new (".sdata", (subsegT) get_absolute_expression ());
11772 if (OUTPUT_FLAVOR == bfd_target_elf_flavour)
11774 bfd_set_section_flags (stdoutput, seg,
11775 SEC_ALLOC | SEC_LOAD | SEC_RELOC
11777 if (strcmp (TARGET_OS, "elf") != 0)
11778 record_alignment (seg, 4);
11780 demand_empty_rest_of_line ();
11785 as_bad (_("Global pointers not supported; recompile -G 0"));
11786 demand_empty_rest_of_line ();
11795 s_change_section (ignore)
11796 int ignore ATTRIBUTE_UNUSED;
11799 char *section_name;
11804 int section_entry_size;
11805 int section_alignment;
11807 if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
11810 section_name = input_line_pointer;
11811 c = get_symbol_end ();
11813 next_c = *(input_line_pointer + 1);
11815 /* Do we have .section Name<,"flags">? */
11816 if (c != ',' || (c == ',' && next_c == '"'))
11818 /* just after name is now '\0'. */
11819 *input_line_pointer = c;
11820 input_line_pointer = section_name;
11821 obj_elf_section (ignore);
11824 input_line_pointer++;
11826 /* Do we have .section Name<,type><,flag><,entry_size><,alignment> */
11828 section_type = get_absolute_expression ();
11831 if (*input_line_pointer++ == ',')
11832 section_flag = get_absolute_expression ();
11835 if (*input_line_pointer++ == ',')
11836 section_entry_size = get_absolute_expression ();
11838 section_entry_size = 0;
11839 if (*input_line_pointer++ == ',')
11840 section_alignment = get_absolute_expression ();
11842 section_alignment = 0;
11844 section_name = xstrdup (section_name);
11846 obj_elf_change_section (section_name, section_type, section_flag,
11847 section_entry_size, 0, 0, 0);
11849 if (now_seg->name != section_name)
11850 free (section_name);
11851 #endif /* OBJ_ELF */
11855 mips_enable_auto_align ()
11866 label = insn_labels != NULL ? insn_labels->label : NULL;
11867 mips_emit_delays (FALSE);
11868 if (log_size > 0 && auto_align)
11869 mips_align (log_size, 0, label);
11870 mips_clear_insn_labels ();
11871 cons (1 << log_size);
11875 s_float_cons (type)
11880 label = insn_labels != NULL ? insn_labels->label : NULL;
11882 mips_emit_delays (FALSE);
11887 mips_align (3, 0, label);
11889 mips_align (2, 0, label);
11892 mips_clear_insn_labels ();
11897 /* Handle .globl. We need to override it because on Irix 5 you are
11900 where foo is an undefined symbol, to mean that foo should be
11901 considered to be the address of a function. */
11905 int x ATTRIBUTE_UNUSED;
11912 name = input_line_pointer;
11913 c = get_symbol_end ();
11914 symbolP = symbol_find_or_make (name);
11915 *input_line_pointer = c;
11916 SKIP_WHITESPACE ();
11918 /* On Irix 5, every global symbol that is not explicitly labelled as
11919 being a function is apparently labelled as being an object. */
11922 if (! is_end_of_line[(unsigned char) *input_line_pointer])
11927 secname = input_line_pointer;
11928 c = get_symbol_end ();
11929 sec = bfd_get_section_by_name (stdoutput, secname);
11931 as_bad (_("%s: no such section"), secname);
11932 *input_line_pointer = c;
11934 if (sec != NULL && (sec->flags & SEC_CODE) != 0)
11935 flag = BSF_FUNCTION;
11938 symbol_get_bfdsym (symbolP)->flags |= flag;
11940 S_SET_EXTERNAL (symbolP);
11941 demand_empty_rest_of_line ();
11946 int x ATTRIBUTE_UNUSED;
11951 opt = input_line_pointer;
11952 c = get_symbol_end ();
11956 /* FIXME: What does this mean? */
11958 else if (strncmp (opt, "pic", 3) == 0)
11962 i = atoi (opt + 3);
11966 mips_pic = SVR4_PIC;
11968 as_bad (_(".option pic%d not supported"), i);
11970 if (USE_GLOBAL_POINTER_OPT && mips_pic == SVR4_PIC)
11972 if (g_switch_seen && g_switch_value != 0)
11973 as_warn (_("-G may not be used with SVR4 PIC code"));
11974 g_switch_value = 0;
11975 bfd_set_gp_size (stdoutput, 0);
11979 as_warn (_("Unrecognized option \"%s\""), opt);
11981 *input_line_pointer = c;
11982 demand_empty_rest_of_line ();
11985 /* This structure is used to hold a stack of .set values. */
11987 struct mips_option_stack
11989 struct mips_option_stack *next;
11990 struct mips_set_options options;
11993 static struct mips_option_stack *mips_opts_stack;
11995 /* Handle the .set pseudo-op. */
11999 int x ATTRIBUTE_UNUSED;
12001 char *name = input_line_pointer, ch;
12003 while (!is_end_of_line[(unsigned char) *input_line_pointer])
12004 ++input_line_pointer;
12005 ch = *input_line_pointer;
12006 *input_line_pointer = '\0';
12008 if (strcmp (name, "reorder") == 0)
12010 if (mips_opts.noreorder && prev_nop_frag != NULL)
12012 /* If we still have pending nops, we can discard them. The
12013 usual nop handling will insert any that are still
12015 prev_nop_frag->fr_fix -= (prev_nop_frag_holds
12016 * (mips_opts.mips16 ? 2 : 4));
12017 prev_nop_frag = NULL;
12019 mips_opts.noreorder = 0;
12021 else if (strcmp (name, "noreorder") == 0)
12023 mips_emit_delays (TRUE);
12024 mips_opts.noreorder = 1;
12025 mips_any_noreorder = 1;
12027 else if (strcmp (name, "at") == 0)
12029 mips_opts.noat = 0;
12031 else if (strcmp (name, "noat") == 0)
12033 mips_opts.noat = 1;
12035 else if (strcmp (name, "macro") == 0)
12037 mips_opts.warn_about_macros = 0;
12039 else if (strcmp (name, "nomacro") == 0)
12041 if (mips_opts.noreorder == 0)
12042 as_bad (_("`noreorder' must be set before `nomacro'"));
12043 mips_opts.warn_about_macros = 1;
12045 else if (strcmp (name, "move") == 0 || strcmp (name, "novolatile") == 0)
12047 mips_opts.nomove = 0;
12049 else if (strcmp (name, "nomove") == 0 || strcmp (name, "volatile") == 0)
12051 mips_opts.nomove = 1;
12053 else if (strcmp (name, "bopt") == 0)
12055 mips_opts.nobopt = 0;
12057 else if (strcmp (name, "nobopt") == 0)
12059 mips_opts.nobopt = 1;
12061 else if (strcmp (name, "mips16") == 0
12062 || strcmp (name, "MIPS-16") == 0)
12063 mips_opts.mips16 = 1;
12064 else if (strcmp (name, "nomips16") == 0
12065 || strcmp (name, "noMIPS-16") == 0)
12066 mips_opts.mips16 = 0;
12067 else if (strcmp (name, "mips3d") == 0)
12068 mips_opts.ase_mips3d = 1;
12069 else if (strcmp (name, "nomips3d") == 0)
12070 mips_opts.ase_mips3d = 0;
12071 else if (strcmp (name, "mdmx") == 0)
12072 mips_opts.ase_mdmx = 1;
12073 else if (strcmp (name, "nomdmx") == 0)
12074 mips_opts.ase_mdmx = 0;
12075 else if (strncmp (name, "mips", 4) == 0)
12079 /* Permit the user to change the ISA on the fly. Needless to
12080 say, misuse can cause serious problems. */
12081 if (strcmp (name, "mips0") == 0)
12084 mips_opts.isa = file_mips_isa;
12086 else if (strcmp (name, "mips1") == 0)
12087 mips_opts.isa = ISA_MIPS1;
12088 else if (strcmp (name, "mips2") == 0)
12089 mips_opts.isa = ISA_MIPS2;
12090 else if (strcmp (name, "mips3") == 0)
12091 mips_opts.isa = ISA_MIPS3;
12092 else if (strcmp (name, "mips4") == 0)
12093 mips_opts.isa = ISA_MIPS4;
12094 else if (strcmp (name, "mips5") == 0)
12095 mips_opts.isa = ISA_MIPS5;
12096 else if (strcmp (name, "mips32") == 0)
12097 mips_opts.isa = ISA_MIPS32;
12098 else if (strcmp (name, "mips32r2") == 0)
12099 mips_opts.isa = ISA_MIPS32R2;
12100 else if (strcmp (name, "mips64") == 0)
12101 mips_opts.isa = ISA_MIPS64;
12103 as_bad (_("unknown ISA level %s"), name + 4);
12105 switch (mips_opts.isa)
12113 mips_opts.gp32 = 1;
12114 mips_opts.fp32 = 1;
12120 mips_opts.gp32 = 0;
12121 mips_opts.fp32 = 0;
12124 as_bad (_("unknown ISA level %s"), name + 4);
12129 mips_opts.gp32 = file_mips_gp32;
12130 mips_opts.fp32 = file_mips_fp32;
12133 else if (strcmp (name, "autoextend") == 0)
12134 mips_opts.noautoextend = 0;
12135 else if (strcmp (name, "noautoextend") == 0)
12136 mips_opts.noautoextend = 1;
12137 else if (strcmp (name, "push") == 0)
12139 struct mips_option_stack *s;
12141 s = (struct mips_option_stack *) xmalloc (sizeof *s);
12142 s->next = mips_opts_stack;
12143 s->options = mips_opts;
12144 mips_opts_stack = s;
12146 else if (strcmp (name, "pop") == 0)
12148 struct mips_option_stack *s;
12150 s = mips_opts_stack;
12152 as_bad (_(".set pop with no .set push"));
12155 /* If we're changing the reorder mode we need to handle
12156 delay slots correctly. */
12157 if (s->options.noreorder && ! mips_opts.noreorder)
12158 mips_emit_delays (TRUE);
12159 else if (! s->options.noreorder && mips_opts.noreorder)
12161 if (prev_nop_frag != NULL)
12163 prev_nop_frag->fr_fix -= (prev_nop_frag_holds
12164 * (mips_opts.mips16 ? 2 : 4));
12165 prev_nop_frag = NULL;
12169 mips_opts = s->options;
12170 mips_opts_stack = s->next;
12176 as_warn (_("Tried to set unrecognized symbol: %s\n"), name);
12178 *input_line_pointer = ch;
12179 demand_empty_rest_of_line ();
12182 /* Handle the .abicalls pseudo-op. I believe this is equivalent to
12183 .option pic2. It means to generate SVR4 PIC calls. */
12186 s_abicalls (ignore)
12187 int ignore ATTRIBUTE_UNUSED;
12189 mips_pic = SVR4_PIC;
12190 if (USE_GLOBAL_POINTER_OPT)
12192 if (g_switch_seen && g_switch_value != 0)
12193 as_warn (_("-G may not be used with SVR4 PIC code"));
12194 g_switch_value = 0;
12196 bfd_set_gp_size (stdoutput, 0);
12197 demand_empty_rest_of_line ();
12200 /* Handle the .cpload pseudo-op. This is used when generating SVR4
12201 PIC code. It sets the $gp register for the function based on the
12202 function address, which is in the register named in the argument.
12203 This uses a relocation against _gp_disp, which is handled specially
12204 by the linker. The result is:
12205 lui $gp,%hi(_gp_disp)
12206 addiu $gp,$gp,%lo(_gp_disp)
12207 addu $gp,$gp,.cpload argument
12208 The .cpload argument is normally $25 == $t9. */
12212 int ignore ATTRIBUTE_UNUSED;
12217 /* If we are not generating SVR4 PIC code, or if this is NewABI code,
12218 .cpload is ignored. */
12219 if (mips_pic != SVR4_PIC || HAVE_NEWABI)
12225 /* .cpload should be in a .set noreorder section. */
12226 if (mips_opts.noreorder == 0)
12227 as_warn (_(".cpload not in noreorder section"));
12229 ex.X_op = O_symbol;
12230 ex.X_add_symbol = symbol_find_or_make ("_gp_disp");
12231 ex.X_op_symbol = NULL;
12232 ex.X_add_number = 0;
12234 /* In ELF, this symbol is implicitly an STT_OBJECT symbol. */
12235 symbol_get_bfdsym (ex.X_add_symbol)->flags |= BSF_OBJECT;
12237 macro_build_lui (NULL, &icnt, &ex, mips_gp_register);
12238 macro_build ((char *) NULL, &icnt, &ex, "addiu", "t,r,j",
12239 mips_gp_register, mips_gp_register, (int) BFD_RELOC_LO16);
12241 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "addu", "d,v,t",
12242 mips_gp_register, mips_gp_register, tc_get_register (0));
12244 demand_empty_rest_of_line ();
12247 /* Handle the .cpsetup pseudo-op defined for NewABI PIC code. The syntax is:
12248 .cpsetup $reg1, offset|$reg2, label
12250 If offset is given, this results in:
12251 sd $gp, offset($sp)
12252 lui $gp, %hi(%neg(%gp_rel(label)))
12253 addiu $gp, $gp, %lo(%neg(%gp_rel(label)))
12254 daddu $gp, $gp, $reg1
12256 If $reg2 is given, this results in:
12257 daddu $reg2, $gp, $0
12258 lui $gp, %hi(%neg(%gp_rel(label)))
12259 addiu $gp, $gp, %lo(%neg(%gp_rel(label)))
12260 daddu $gp, $gp, $reg1
12261 $reg1 is normally $25 == $t9. */
12264 int ignore ATTRIBUTE_UNUSED;
12266 expressionS ex_off;
12267 expressionS ex_sym;
12272 /* If we are not generating SVR4 PIC code, .cpsetup is ignored.
12273 We also need NewABI support. */
12274 if (mips_pic != SVR4_PIC || ! HAVE_NEWABI)
12280 reg1 = tc_get_register (0);
12281 SKIP_WHITESPACE ();
12282 if (*input_line_pointer != ',')
12284 as_bad (_("missing argument separator ',' for .cpsetup"));
12288 ++input_line_pointer;
12289 SKIP_WHITESPACE ();
12290 if (*input_line_pointer == '$')
12292 mips_cpreturn_register = tc_get_register (0);
12293 mips_cpreturn_offset = -1;
12297 mips_cpreturn_offset = get_absolute_expression ();
12298 mips_cpreturn_register = -1;
12300 SKIP_WHITESPACE ();
12301 if (*input_line_pointer != ',')
12303 as_bad (_("missing argument separator ',' for .cpsetup"));
12307 ++input_line_pointer;
12308 SKIP_WHITESPACE ();
12309 expression (&ex_sym);
12311 if (mips_cpreturn_register == -1)
12313 ex_off.X_op = O_constant;
12314 ex_off.X_add_symbol = NULL;
12315 ex_off.X_op_symbol = NULL;
12316 ex_off.X_add_number = mips_cpreturn_offset;
12318 macro_build ((char *) NULL, &icnt, &ex_off, "sd", "t,o(b)",
12319 mips_gp_register, (int) BFD_RELOC_LO16, SP);
12322 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "daddu",
12323 "d,v,t", mips_cpreturn_register, mips_gp_register, 0);
12325 /* Ensure there's room for the next two instructions, so that `f'
12326 doesn't end up with an address in the wrong frag. */
12329 macro_build ((char *) NULL, &icnt, &ex_sym, "lui", "t,u", mips_gp_register,
12330 (int) BFD_RELOC_GPREL16);
12331 fix_new (frag_now, f - frag_now->fr_literal,
12332 0, NULL, 0, 0, BFD_RELOC_MIPS_SUB);
12333 fix_new (frag_now, f - frag_now->fr_literal,
12334 0, NULL, 0, 0, BFD_RELOC_HI16_S);
12337 macro_build ((char *) NULL, &icnt, &ex_sym, "addiu", "t,r,j",
12338 mips_gp_register, mips_gp_register, (int) BFD_RELOC_GPREL16);
12339 fix_new (frag_now, f - frag_now->fr_literal,
12340 0, NULL, 0, 0, BFD_RELOC_MIPS_SUB);
12341 fix_new (frag_now, f - frag_now->fr_literal,
12342 0, NULL, 0, 0, BFD_RELOC_LO16);
12344 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
12345 HAVE_64BIT_ADDRESSES ? "daddu" : "addu", "d,v,t",
12346 mips_gp_register, mips_gp_register, reg1);
12348 demand_empty_rest_of_line ();
12353 int ignore ATTRIBUTE_UNUSED;
12355 /* If we are not generating SVR4 PIC code, or if this is not NewABI code,
12356 .cplocal is ignored. */
12357 if (mips_pic != SVR4_PIC || ! HAVE_NEWABI)
12363 mips_gp_register = tc_get_register (0);
12364 demand_empty_rest_of_line ();
12367 /* Handle the .cprestore pseudo-op. This stores $gp into a given
12368 offset from $sp. The offset is remembered, and after making a PIC
12369 call $gp is restored from that location. */
12372 s_cprestore (ignore)
12373 int ignore ATTRIBUTE_UNUSED;
12378 /* If we are not generating SVR4 PIC code, or if this is NewABI code,
12379 .cprestore is ignored. */
12380 if (mips_pic != SVR4_PIC || HAVE_NEWABI)
12386 mips_cprestore_offset = get_absolute_expression ();
12387 mips_cprestore_valid = 1;
12389 ex.X_op = O_constant;
12390 ex.X_add_symbol = NULL;
12391 ex.X_op_symbol = NULL;
12392 ex.X_add_number = mips_cprestore_offset;
12394 macro_build_ldst_constoffset ((char *) NULL, &icnt, &ex,
12395 HAVE_32BIT_ADDRESSES ? "sw" : "sd",
12396 mips_gp_register, SP);
12398 demand_empty_rest_of_line ();
12401 /* Handle the .cpreturn pseudo-op defined for NewABI PIC code. If an offset
12402 was given in the preceeding .gpsetup, it results in:
12403 ld $gp, offset($sp)
12405 If a register $reg2 was given there, it results in:
12406 daddiu $gp, $gp, $reg2
12409 s_cpreturn (ignore)
12410 int ignore ATTRIBUTE_UNUSED;
12415 /* If we are not generating SVR4 PIC code, .cpreturn is ignored.
12416 We also need NewABI support. */
12417 if (mips_pic != SVR4_PIC || ! HAVE_NEWABI)
12423 if (mips_cpreturn_register == -1)
12425 ex.X_op = O_constant;
12426 ex.X_add_symbol = NULL;
12427 ex.X_op_symbol = NULL;
12428 ex.X_add_number = mips_cpreturn_offset;
12430 macro_build ((char *) NULL, &icnt, &ex, "ld", "t,o(b)",
12431 mips_gp_register, (int) BFD_RELOC_LO16, SP);
12434 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "daddu",
12435 "d,v,t", mips_gp_register, mips_cpreturn_register, 0);
12437 demand_empty_rest_of_line ();
12440 /* Handle the .gpvalue pseudo-op. This is used when generating NewABI PIC
12441 code. It sets the offset to use in gp_rel relocations. */
12445 int ignore ATTRIBUTE_UNUSED;
12447 /* If we are not generating SVR4 PIC code, .gpvalue is ignored.
12448 We also need NewABI support. */
12449 if (mips_pic != SVR4_PIC || ! HAVE_NEWABI)
12455 mips_gprel_offset = get_absolute_expression ();
12457 demand_empty_rest_of_line ();
12460 /* Handle the .gpword pseudo-op. This is used when generating PIC
12461 code. It generates a 32 bit GP relative reloc. */
12465 int ignore ATTRIBUTE_UNUSED;
12471 /* When not generating PIC code, this is treated as .word. */
12472 if (mips_pic != SVR4_PIC)
12478 label = insn_labels != NULL ? insn_labels->label : NULL;
12479 mips_emit_delays (TRUE);
12481 mips_align (2, 0, label);
12482 mips_clear_insn_labels ();
12486 if (ex.X_op != O_symbol || ex.X_add_number != 0)
12488 as_bad (_("Unsupported use of .gpword"));
12489 ignore_rest_of_line ();
12493 md_number_to_chars (p, (valueT) 0, 4);
12494 fix_new_exp (frag_now, p - frag_now->fr_literal, 4, &ex, FALSE,
12495 BFD_RELOC_GPREL32);
12497 demand_empty_rest_of_line ();
12502 int ignore ATTRIBUTE_UNUSED;
12508 /* When not generating PIC code, this is treated as .dword. */
12509 if (mips_pic != SVR4_PIC)
12515 label = insn_labels != NULL ? insn_labels->label : NULL;
12516 mips_emit_delays (TRUE);
12518 mips_align (3, 0, label);
12519 mips_clear_insn_labels ();
12523 if (ex.X_op != O_symbol || ex.X_add_number != 0)
12525 as_bad (_("Unsupported use of .gpdword"));
12526 ignore_rest_of_line ();
12530 md_number_to_chars (p, (valueT) 0, 8);
12531 fix_new_exp (frag_now, p - frag_now->fr_literal, 8, &ex, FALSE,
12532 BFD_RELOC_GPREL32);
12534 /* GPREL32 composed with 64 gives a 64-bit GP offset. */
12535 ex.X_op = O_absent;
12536 ex.X_add_symbol = 0;
12537 ex.X_add_number = 0;
12538 fix_new_exp (frag_now, p - frag_now->fr_literal, 8, &ex, FALSE,
12541 demand_empty_rest_of_line ();
12544 /* Handle the .cpadd pseudo-op. This is used when dealing with switch
12545 tables in SVR4 PIC code. */
12549 int ignore ATTRIBUTE_UNUSED;
12554 /* This is ignored when not generating SVR4 PIC code. */
12555 if (mips_pic != SVR4_PIC)
12561 /* Add $gp to the register named as an argument. */
12562 reg = tc_get_register (0);
12563 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
12564 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
12565 "d,v,t", reg, reg, mips_gp_register);
12567 demand_empty_rest_of_line ();
12570 /* Handle the .insn pseudo-op. This marks instruction labels in
12571 mips16 mode. This permits the linker to handle them specially,
12572 such as generating jalx instructions when needed. We also make
12573 them odd for the duration of the assembly, in order to generate the
12574 right sort of code. We will make them even in the adjust_symtab
12575 routine, while leaving them marked. This is convenient for the
12576 debugger and the disassembler. The linker knows to make them odd
12581 int ignore ATTRIBUTE_UNUSED;
12583 mips16_mark_labels ();
12585 demand_empty_rest_of_line ();
12588 /* Handle a .stabn directive. We need these in order to mark a label
12589 as being a mips16 text label correctly. Sometimes the compiler
12590 will emit a label, followed by a .stabn, and then switch sections.
12591 If the label and .stabn are in mips16 mode, then the label is
12592 really a mips16 text label. */
12599 mips16_mark_labels ();
12604 /* Handle the .weakext pseudo-op as defined in Kane and Heinrich.
12608 s_mips_weakext (ignore)
12609 int ignore ATTRIBUTE_UNUSED;
12616 name = input_line_pointer;
12617 c = get_symbol_end ();
12618 symbolP = symbol_find_or_make (name);
12619 S_SET_WEAK (symbolP);
12620 *input_line_pointer = c;
12622 SKIP_WHITESPACE ();
12624 if (! is_end_of_line[(unsigned char) *input_line_pointer])
12626 if (S_IS_DEFINED (symbolP))
12628 as_bad ("ignoring attempt to redefine symbol %s",
12629 S_GET_NAME (symbolP));
12630 ignore_rest_of_line ();
12634 if (*input_line_pointer == ',')
12636 ++input_line_pointer;
12637 SKIP_WHITESPACE ();
12641 if (exp.X_op != O_symbol)
12643 as_bad ("bad .weakext directive");
12644 ignore_rest_of_line ();
12647 symbol_set_value_expression (symbolP, &exp);
12650 demand_empty_rest_of_line ();
12653 /* Parse a register string into a number. Called from the ECOFF code
12654 to parse .frame. The argument is non-zero if this is the frame
12655 register, so that we can record it in mips_frame_reg. */
12658 tc_get_register (frame)
12663 SKIP_WHITESPACE ();
12664 if (*input_line_pointer++ != '$')
12666 as_warn (_("expected `$'"));
12669 else if (ISDIGIT (*input_line_pointer))
12671 reg = get_absolute_expression ();
12672 if (reg < 0 || reg >= 32)
12674 as_warn (_("Bad register number"));
12680 if (strncmp (input_line_pointer, "ra", 2) == 0)
12683 input_line_pointer += 2;
12685 else if (strncmp (input_line_pointer, "fp", 2) == 0)
12688 input_line_pointer += 2;
12690 else if (strncmp (input_line_pointer, "sp", 2) == 0)
12693 input_line_pointer += 2;
12695 else if (strncmp (input_line_pointer, "gp", 2) == 0)
12698 input_line_pointer += 2;
12700 else if (strncmp (input_line_pointer, "at", 2) == 0)
12703 input_line_pointer += 2;
12705 else if (strncmp (input_line_pointer, "kt0", 3) == 0)
12708 input_line_pointer += 3;
12710 else if (strncmp (input_line_pointer, "kt1", 3) == 0)
12713 input_line_pointer += 3;
12715 else if (strncmp (input_line_pointer, "zero", 4) == 0)
12718 input_line_pointer += 4;
12722 as_warn (_("Unrecognized register name"));
12724 while (ISALNUM(*input_line_pointer))
12725 input_line_pointer++;
12730 mips_frame_reg = reg != 0 ? reg : SP;
12731 mips_frame_reg_valid = 1;
12732 mips_cprestore_valid = 0;
12738 md_section_align (seg, addr)
12742 int align = bfd_get_section_alignment (stdoutput, seg);
12745 /* We don't need to align ELF sections to the full alignment.
12746 However, Irix 5 may prefer that we align them at least to a 16
12747 byte boundary. We don't bother to align the sections if we are
12748 targeted for an embedded system. */
12749 if (strcmp (TARGET_OS, "elf") == 0)
12755 return ((addr + (1 << align) - 1) & (-1 << align));
12758 /* Utility routine, called from above as well. If called while the
12759 input file is still being read, it's only an approximation. (For
12760 example, a symbol may later become defined which appeared to be
12761 undefined earlier.) */
12764 nopic_need_relax (sym, before_relaxing)
12766 int before_relaxing;
12771 if (USE_GLOBAL_POINTER_OPT && g_switch_value > 0)
12773 const char *symname;
12776 /* Find out whether this symbol can be referenced off the $gp
12777 register. It can be if it is smaller than the -G size or if
12778 it is in the .sdata or .sbss section. Certain symbols can
12779 not be referenced off the $gp, although it appears as though
12781 symname = S_GET_NAME (sym);
12782 if (symname != (const char *) NULL
12783 && (strcmp (symname, "eprol") == 0
12784 || strcmp (symname, "etext") == 0
12785 || strcmp (symname, "_gp") == 0
12786 || strcmp (symname, "edata") == 0
12787 || strcmp (symname, "_fbss") == 0
12788 || strcmp (symname, "_fdata") == 0
12789 || strcmp (symname, "_ftext") == 0
12790 || strcmp (symname, "end") == 0
12791 || strcmp (symname, "_gp_disp") == 0))
12793 else if ((! S_IS_DEFINED (sym) || S_IS_COMMON (sym))
12794 && !S_IS_EXTERN (sym)
12796 #ifndef NO_ECOFF_DEBUGGING
12797 || (symbol_get_obj (sym)->ecoff_extern_size != 0
12798 && (symbol_get_obj (sym)->ecoff_extern_size
12799 <= g_switch_value))
12801 /* We must defer this decision until after the whole
12802 file has been read, since there might be a .extern
12803 after the first use of this symbol. */
12804 || (before_relaxing
12805 #ifndef NO_ECOFF_DEBUGGING
12806 && symbol_get_obj (sym)->ecoff_extern_size == 0
12808 && S_GET_VALUE (sym) == 0)
12809 || (S_GET_VALUE (sym) != 0
12810 && S_GET_VALUE (sym) <= g_switch_value)))
12814 const char *segname;
12816 segname = segment_name (S_GET_SEGMENT (sym));
12817 assert (strcmp (segname, ".lit8") != 0
12818 && strcmp (segname, ".lit4") != 0);
12819 change = (strcmp (segname, ".sdata") != 0
12820 && strcmp (segname, ".sbss") != 0
12821 && strncmp (segname, ".sdata.", 7) != 0
12822 && strncmp (segname, ".gnu.linkonce.s.", 16) != 0);
12827 /* We are not optimizing for the $gp register. */
12832 /* Return true if the given symbol should be considered local for SVR4 PIC. */
12835 pic_need_relax (sym, segtype)
12840 bfd_boolean linkonce;
12842 /* Handle the case of a symbol equated to another symbol. */
12843 while (symbol_equated_reloc_p (sym))
12847 /* It's possible to get a loop here in a badly written
12849 n = symbol_get_value_expression (sym)->X_add_symbol;
12855 symsec = S_GET_SEGMENT (sym);
12857 /* duplicate the test for LINK_ONCE sections as in adjust_reloc_syms */
12859 if (symsec != segtype && ! S_IS_LOCAL (sym))
12861 if ((bfd_get_section_flags (stdoutput, symsec) & SEC_LINK_ONCE)
12865 /* The GNU toolchain uses an extension for ELF: a section
12866 beginning with the magic string .gnu.linkonce is a linkonce
12868 if (strncmp (segment_name (symsec), ".gnu.linkonce",
12869 sizeof ".gnu.linkonce" - 1) == 0)
12873 /* This must duplicate the test in adjust_reloc_syms. */
12874 return (symsec != &bfd_und_section
12875 && symsec != &bfd_abs_section
12876 && ! bfd_is_com_section (symsec)
12879 /* A global or weak symbol is treated as external. */
12880 && (OUTPUT_FLAVOR != bfd_target_elf_flavour
12881 || (! S_IS_WEAK (sym)
12882 && (! S_IS_EXTERNAL (sym)
12883 || mips_pic == EMBEDDED_PIC)))
12889 /* Given a mips16 variant frag FRAGP, return non-zero if it needs an
12890 extended opcode. SEC is the section the frag is in. */
12893 mips16_extended_frag (fragp, sec, stretch)
12899 register const struct mips16_immed_operand *op;
12901 int mintiny, maxtiny;
12905 if (RELAX_MIPS16_USER_SMALL (fragp->fr_subtype))
12907 if (RELAX_MIPS16_USER_EXT (fragp->fr_subtype))
12910 type = RELAX_MIPS16_TYPE (fragp->fr_subtype);
12911 op = mips16_immed_operands;
12912 while (op->type != type)
12915 assert (op < mips16_immed_operands + MIPS16_NUM_IMMED);
12920 if (type == '<' || type == '>' || type == '[' || type == ']')
12923 maxtiny = 1 << op->nbits;
12928 maxtiny = (1 << op->nbits) - 1;
12933 mintiny = - (1 << (op->nbits - 1));
12934 maxtiny = (1 << (op->nbits - 1)) - 1;
12937 sym_frag = symbol_get_frag (fragp->fr_symbol);
12938 val = S_GET_VALUE (fragp->fr_symbol);
12939 symsec = S_GET_SEGMENT (fragp->fr_symbol);
12945 /* We won't have the section when we are called from
12946 mips_relax_frag. However, we will always have been called
12947 from md_estimate_size_before_relax first. If this is a
12948 branch to a different section, we mark it as such. If SEC is
12949 NULL, and the frag is not marked, then it must be a branch to
12950 the same section. */
12953 if (RELAX_MIPS16_LONG_BRANCH (fragp->fr_subtype))
12958 /* Must have been called from md_estimate_size_before_relax. */
12961 fragp->fr_subtype =
12962 RELAX_MIPS16_MARK_LONG_BRANCH (fragp->fr_subtype);
12964 /* FIXME: We should support this, and let the linker
12965 catch branches and loads that are out of range. */
12966 as_bad_where (fragp->fr_file, fragp->fr_line,
12967 _("unsupported PC relative reference to different section"));
12971 if (fragp != sym_frag && sym_frag->fr_address == 0)
12972 /* Assume non-extended on the first relaxation pass.
12973 The address we have calculated will be bogus if this is
12974 a forward branch to another frag, as the forward frag
12975 will have fr_address == 0. */
12979 /* In this case, we know for sure that the symbol fragment is in
12980 the same section. If the relax_marker of the symbol fragment
12981 differs from the relax_marker of this fragment, we have not
12982 yet adjusted the symbol fragment fr_address. We want to add
12983 in STRETCH in order to get a better estimate of the address.
12984 This particularly matters because of the shift bits. */
12986 && sym_frag->relax_marker != fragp->relax_marker)
12990 /* Adjust stretch for any alignment frag. Note that if have
12991 been expanding the earlier code, the symbol may be
12992 defined in what appears to be an earlier frag. FIXME:
12993 This doesn't handle the fr_subtype field, which specifies
12994 a maximum number of bytes to skip when doing an
12996 for (f = fragp; f != NULL && f != sym_frag; f = f->fr_next)
12998 if (f->fr_type == rs_align || f->fr_type == rs_align_code)
13001 stretch = - ((- stretch)
13002 & ~ ((1 << (int) f->fr_offset) - 1));
13004 stretch &= ~ ((1 << (int) f->fr_offset) - 1);
13013 addr = fragp->fr_address + fragp->fr_fix;
13015 /* The base address rules are complicated. The base address of
13016 a branch is the following instruction. The base address of a
13017 PC relative load or add is the instruction itself, but if it
13018 is in a delay slot (in which case it can not be extended) use
13019 the address of the instruction whose delay slot it is in. */
13020 if (type == 'p' || type == 'q')
13024 /* If we are currently assuming that this frag should be
13025 extended, then, the current address is two bytes
13027 if (RELAX_MIPS16_EXTENDED (fragp->fr_subtype))
13030 /* Ignore the low bit in the target, since it will be set
13031 for a text label. */
13032 if ((val & 1) != 0)
13035 else if (RELAX_MIPS16_JAL_DSLOT (fragp->fr_subtype))
13037 else if (RELAX_MIPS16_DSLOT (fragp->fr_subtype))
13040 val -= addr & ~ ((1 << op->shift) - 1);
13042 /* Branch offsets have an implicit 0 in the lowest bit. */
13043 if (type == 'p' || type == 'q')
13046 /* If any of the shifted bits are set, we must use an extended
13047 opcode. If the address depends on the size of this
13048 instruction, this can lead to a loop, so we arrange to always
13049 use an extended opcode. We only check this when we are in
13050 the main relaxation loop, when SEC is NULL. */
13051 if ((val & ((1 << op->shift) - 1)) != 0 && sec == NULL)
13053 fragp->fr_subtype =
13054 RELAX_MIPS16_MARK_LONG_BRANCH (fragp->fr_subtype);
13058 /* If we are about to mark a frag as extended because the value
13059 is precisely maxtiny + 1, then there is a chance of an
13060 infinite loop as in the following code:
13065 In this case when the la is extended, foo is 0x3fc bytes
13066 away, so the la can be shrunk, but then foo is 0x400 away, so
13067 the la must be extended. To avoid this loop, we mark the
13068 frag as extended if it was small, and is about to become
13069 extended with a value of maxtiny + 1. */
13070 if (val == ((maxtiny + 1) << op->shift)
13071 && ! RELAX_MIPS16_EXTENDED (fragp->fr_subtype)
13074 fragp->fr_subtype =
13075 RELAX_MIPS16_MARK_LONG_BRANCH (fragp->fr_subtype);
13079 else if (symsec != absolute_section && sec != NULL)
13080 as_bad_where (fragp->fr_file, fragp->fr_line, _("unsupported relocation"));
13082 if ((val & ((1 << op->shift) - 1)) != 0
13083 || val < (mintiny << op->shift)
13084 || val > (maxtiny << op->shift))
13090 /* Compute the length of a branch sequence, and adjust the
13091 RELAX_BRANCH_TOOFAR bit accordingly. If FRAGP is NULL, the
13092 worst-case length is computed, with UPDATE being used to indicate
13093 whether an unconditional (-1), branch-likely (+1) or regular (0)
13094 branch is to be computed. */
13096 relaxed_branch_length (fragp, sec, update)
13101 bfd_boolean toofar;
13105 && S_IS_DEFINED (fragp->fr_symbol)
13106 && sec == S_GET_SEGMENT (fragp->fr_symbol))
13111 val = S_GET_VALUE (fragp->fr_symbol) + fragp->fr_offset;
13113 addr = fragp->fr_address + fragp->fr_fix + 4;
13117 toofar = val < - (0x8000 << 2) || val >= (0x8000 << 2);
13120 /* If the symbol is not defined or it's in a different segment,
13121 assume the user knows what's going on and emit a short
13127 if (fragp && update && toofar != RELAX_BRANCH_TOOFAR (fragp->fr_subtype))
13129 = RELAX_BRANCH_ENCODE (RELAX_BRANCH_UNCOND (fragp->fr_subtype),
13130 RELAX_BRANCH_LIKELY (fragp->fr_subtype),
13131 RELAX_BRANCH_LINK (fragp->fr_subtype),
13137 if (fragp ? RELAX_BRANCH_LIKELY (fragp->fr_subtype) : (update > 0))
13140 if (mips_pic != NO_PIC)
13142 /* Additional space for PIC loading of target address. */
13144 if (mips_opts.isa == ISA_MIPS1)
13145 /* Additional space for $at-stabilizing nop. */
13149 /* If branch is conditional. */
13150 if (fragp ? !RELAX_BRANCH_UNCOND (fragp->fr_subtype) : (update >= 0))
13157 /* Estimate the size of a frag before relaxing. Unless this is the
13158 mips16, we are not really relaxing here, and the final size is
13159 encoded in the subtype information. For the mips16, we have to
13160 decide whether we are using an extended opcode or not. */
13163 md_estimate_size_before_relax (fragp, segtype)
13169 if (RELAX_BRANCH_P (fragp->fr_subtype))
13172 fragp->fr_var = relaxed_branch_length (fragp, segtype, FALSE);
13174 return fragp->fr_var;
13177 if (RELAX_MIPS16_P (fragp->fr_subtype))
13178 /* We don't want to modify the EXTENDED bit here; it might get us
13179 into infinite loops. We change it only in mips_relax_frag(). */
13180 return (RELAX_MIPS16_EXTENDED (fragp->fr_subtype) ? 4 : 2);
13182 if (mips_pic == NO_PIC)
13183 change = nopic_need_relax (fragp->fr_symbol, 0);
13184 else if (mips_pic == SVR4_PIC)
13185 change = pic_need_relax (fragp->fr_symbol, segtype);
13191 /* Record the offset to the first reloc in the fr_opcode field.
13192 This lets md_convert_frag and tc_gen_reloc know that the code
13193 must be expanded. */
13194 fragp->fr_opcode = (fragp->fr_literal
13196 - RELAX_OLD (fragp->fr_subtype)
13197 + RELAX_RELOC1 (fragp->fr_subtype));
13198 /* FIXME: This really needs as_warn_where. */
13199 if (RELAX_WARN (fragp->fr_subtype))
13200 as_warn (_("AT used after \".set noat\" or macro used after "
13201 "\".set nomacro\""));
13203 return RELAX_NEW (fragp->fr_subtype) - RELAX_OLD (fragp->fr_subtype);
13209 /* This is called to see whether a reloc against a defined symbol
13210 should be converted into a reloc against a section. Don't adjust
13211 MIPS16 jump relocations, so we don't have to worry about the format
13212 of the offset in the .o file. Don't adjust relocations against
13213 mips16 symbols, so that the linker can find them if it needs to set
13217 mips_fix_adjustable (fixp)
13220 if (fixp->fx_r_type == BFD_RELOC_MIPS16_JMP)
13223 if (fixp->fx_r_type == BFD_RELOC_VTABLE_INHERIT
13224 || fixp->fx_r_type == BFD_RELOC_VTABLE_ENTRY)
13227 if (fixp->fx_addsy == NULL)
13231 if (OUTPUT_FLAVOR == bfd_target_elf_flavour
13232 && S_GET_OTHER (fixp->fx_addsy) == STO_MIPS16
13233 && fixp->fx_subsy == NULL)
13240 /* Translate internal representation of relocation info to BFD target
13244 tc_gen_reloc (section, fixp)
13245 asection *section ATTRIBUTE_UNUSED;
13248 static arelent *retval[4];
13250 bfd_reloc_code_real_type code;
13252 reloc = retval[0] = (arelent *) xmalloc (sizeof (arelent));
13255 reloc->sym_ptr_ptr = (asymbol **) xmalloc (sizeof (asymbol *));
13256 *reloc->sym_ptr_ptr = symbol_get_bfdsym (fixp->fx_addsy);
13257 reloc->address = fixp->fx_frag->fr_address + fixp->fx_where;
13259 if (mips_pic == EMBEDDED_PIC
13260 && SWITCH_TABLE (fixp))
13262 /* For a switch table entry we use a special reloc. The addend
13263 is actually the difference between the reloc address and the
13265 reloc->addend = reloc->address - S_GET_VALUE (fixp->fx_subsy);
13266 if (OUTPUT_FLAVOR != bfd_target_ecoff_flavour)
13267 as_fatal (_("Double check fx_r_type in tc-mips.c:tc_gen_reloc"));
13268 fixp->fx_r_type = BFD_RELOC_GPREL32;
13270 else if (fixp->fx_r_type == BFD_RELOC_PCREL_LO16)
13272 if (OUTPUT_FLAVOR == bfd_target_elf_flavour)
13273 reloc->addend = fixp->fx_addnumber;
13276 /* We use a special addend for an internal RELLO reloc. */
13277 if (symbol_section_p (fixp->fx_addsy))
13278 reloc->addend = reloc->address - S_GET_VALUE (fixp->fx_subsy);
13280 reloc->addend = fixp->fx_addnumber + reloc->address;
13283 else if (fixp->fx_r_type == BFD_RELOC_PCREL_HI16_S)
13285 assert (fixp->fx_next != NULL
13286 && fixp->fx_next->fx_r_type == BFD_RELOC_PCREL_LO16);
13288 /* The reloc is relative to the RELLO; adjust the addend
13290 if (OUTPUT_FLAVOR == bfd_target_elf_flavour)
13291 reloc->addend = fixp->fx_next->fx_addnumber;
13294 /* We use a special addend for an internal RELHI reloc. */
13295 if (symbol_section_p (fixp->fx_addsy))
13296 reloc->addend = (fixp->fx_next->fx_frag->fr_address
13297 + fixp->fx_next->fx_where
13298 - S_GET_VALUE (fixp->fx_subsy));
13300 reloc->addend = (fixp->fx_addnumber
13301 + fixp->fx_next->fx_frag->fr_address
13302 + fixp->fx_next->fx_where);
13305 else if (fixp->fx_pcrel == 0 || OUTPUT_FLAVOR == bfd_target_elf_flavour)
13306 reloc->addend = fixp->fx_addnumber;
13309 if (OUTPUT_FLAVOR != bfd_target_aout_flavour)
13310 /* A gruesome hack which is a result of the gruesome gas reloc
13312 reloc->addend = reloc->address;
13314 reloc->addend = -reloc->address;
13317 /* If this is a variant frag, we may need to adjust the existing
13318 reloc and generate a new one. */
13319 if (fixp->fx_frag->fr_opcode != NULL
13320 && ((fixp->fx_r_type == BFD_RELOC_GPREL16
13322 || fixp->fx_r_type == BFD_RELOC_MIPS_GOT16
13323 || fixp->fx_r_type == BFD_RELOC_MIPS_CALL16
13324 || fixp->fx_r_type == BFD_RELOC_MIPS_GOT_HI16
13325 || fixp->fx_r_type == BFD_RELOC_MIPS_GOT_LO16
13326 || fixp->fx_r_type == BFD_RELOC_MIPS_CALL_HI16
13327 || fixp->fx_r_type == BFD_RELOC_MIPS_CALL_LO16)
13332 assert (! RELAX_MIPS16_P (fixp->fx_frag->fr_subtype));
13334 /* If this is not the last reloc in this frag, then we have two
13335 GPREL relocs, or a GOT_HI16/GOT_LO16 pair, or a
13336 CALL_HI16/CALL_LO16, both of which are being replaced. Let
13337 the second one handle all of them. */
13338 if (fixp->fx_next != NULL
13339 && fixp->fx_frag == fixp->fx_next->fx_frag)
13341 assert ((fixp->fx_r_type == BFD_RELOC_GPREL16
13342 && fixp->fx_next->fx_r_type == BFD_RELOC_GPREL16)
13343 || (fixp->fx_r_type == BFD_RELOC_MIPS_GOT_HI16
13344 && (fixp->fx_next->fx_r_type
13345 == BFD_RELOC_MIPS_GOT_LO16))
13346 || (fixp->fx_r_type == BFD_RELOC_MIPS_CALL_HI16
13347 && (fixp->fx_next->fx_r_type
13348 == BFD_RELOC_MIPS_CALL_LO16)));
13353 fixp->fx_where = fixp->fx_frag->fr_opcode - fixp->fx_frag->fr_literal;
13354 reloc->address = fixp->fx_frag->fr_address + fixp->fx_where;
13355 reloc2 = retval[1] = (arelent *) xmalloc (sizeof (arelent));
13357 reloc2->sym_ptr_ptr = (asymbol **) xmalloc (sizeof (asymbol *));
13358 *reloc2->sym_ptr_ptr = symbol_get_bfdsym (fixp->fx_addsy);
13359 reloc2->address = (reloc->address
13360 + (RELAX_RELOC2 (fixp->fx_frag->fr_subtype)
13361 - RELAX_RELOC1 (fixp->fx_frag->fr_subtype)));
13362 reloc2->addend = fixp->fx_addnumber;
13363 reloc2->howto = bfd_reloc_type_lookup (stdoutput, BFD_RELOC_LO16);
13364 assert (reloc2->howto != NULL);
13366 if (RELAX_RELOC3 (fixp->fx_frag->fr_subtype))
13370 reloc3 = retval[2] = (arelent *) xmalloc (sizeof (arelent));
13373 reloc3->address += 4;
13376 if (mips_pic == NO_PIC)
13378 assert (fixp->fx_r_type == BFD_RELOC_GPREL16);
13379 fixp->fx_r_type = BFD_RELOC_HI16_S;
13381 else if (mips_pic == SVR4_PIC)
13383 switch (fixp->fx_r_type)
13387 case BFD_RELOC_MIPS_GOT16:
13389 case BFD_RELOC_MIPS_GOT_LO16:
13390 case BFD_RELOC_MIPS_CALL_LO16:
13391 fixp->fx_r_type = BFD_RELOC_MIPS_GOT16;
13393 case BFD_RELOC_MIPS_CALL16:
13396 /* BFD_RELOC_MIPS_GOT16;*/
13397 fixp->fx_r_type = BFD_RELOC_MIPS_GOT_PAGE;
13398 reloc2->howto = bfd_reloc_type_lookup
13399 (stdoutput, BFD_RELOC_MIPS_GOT_OFST);
13402 fixp->fx_r_type = BFD_RELOC_MIPS_GOT16;
13409 /* newabi uses R_MIPS_GOT_DISP for local symbols */
13410 if (HAVE_NEWABI && fixp->fx_r_type == BFD_RELOC_MIPS_GOT_LO16)
13412 fixp->fx_r_type = BFD_RELOC_MIPS_GOT_DISP;
13417 /* Since the old MIPS ELF ABI uses Rel instead of Rela, encode the vtable
13418 entry to be used in the relocation's section offset. */
13419 if (! HAVE_NEWABI && fixp->fx_r_type == BFD_RELOC_VTABLE_ENTRY)
13421 reloc->address = reloc->addend;
13425 /* Since DIFF_EXPR_OK is defined in tc-mips.h, it is possible that
13426 fixup_segment converted a non-PC relative reloc into a PC
13427 relative reloc. In such a case, we need to convert the reloc
13429 code = fixp->fx_r_type;
13430 if (fixp->fx_pcrel)
13435 code = BFD_RELOC_8_PCREL;
13438 code = BFD_RELOC_16_PCREL;
13441 code = BFD_RELOC_32_PCREL;
13444 code = BFD_RELOC_64_PCREL;
13446 case BFD_RELOC_8_PCREL:
13447 case BFD_RELOC_16_PCREL:
13448 case BFD_RELOC_32_PCREL:
13449 case BFD_RELOC_64_PCREL:
13450 case BFD_RELOC_16_PCREL_S2:
13451 case BFD_RELOC_PCREL_HI16_S:
13452 case BFD_RELOC_PCREL_LO16:
13455 as_bad_where (fixp->fx_file, fixp->fx_line,
13456 _("Cannot make %s relocation PC relative"),
13457 bfd_get_reloc_code_name (code));
13462 /* md_apply_fix3 has a double-subtraction hack to get
13463 bfd_install_relocation to behave nicely. GPREL relocations are
13464 handled correctly without this hack, so undo it here. We can't
13465 stop md_apply_fix3 from subtracting twice in the first place since
13466 the fake addend is required for variant frags above. */
13467 if (fixp->fx_addsy != NULL && OUTPUT_FLAVOR == bfd_target_elf_flavour
13468 && (code == BFD_RELOC_GPREL16 || code == BFD_RELOC_MIPS16_GPREL)
13469 && reloc->addend != 0
13470 && mips_need_elf_addend_fixup (fixp))
13471 reloc->addend += S_GET_VALUE (fixp->fx_addsy);
13474 /* To support a PC relative reloc when generating embedded PIC code
13475 for ECOFF, we use a Cygnus extension. We check for that here to
13476 make sure that we don't let such a reloc escape normally. */
13477 if ((OUTPUT_FLAVOR == bfd_target_ecoff_flavour
13478 || OUTPUT_FLAVOR == bfd_target_elf_flavour)
13479 && code == BFD_RELOC_16_PCREL_S2
13480 && mips_pic != EMBEDDED_PIC)
13481 reloc->howto = NULL;
13483 reloc->howto = bfd_reloc_type_lookup (stdoutput, code);
13485 if (reloc->howto == NULL)
13487 as_bad_where (fixp->fx_file, fixp->fx_line,
13488 _("Can not represent %s relocation in this object file format"),
13489 bfd_get_reloc_code_name (code));
13496 /* Relax a machine dependent frag. This returns the amount by which
13497 the current size of the frag should change. */
13500 mips_relax_frag (sec, fragp, stretch)
13505 if (RELAX_BRANCH_P (fragp->fr_subtype))
13507 offsetT old_var = fragp->fr_var;
13509 fragp->fr_var = relaxed_branch_length (fragp, sec, TRUE);
13511 return fragp->fr_var - old_var;
13514 if (! RELAX_MIPS16_P (fragp->fr_subtype))
13517 if (mips16_extended_frag (fragp, NULL, stretch))
13519 if (RELAX_MIPS16_EXTENDED (fragp->fr_subtype))
13521 fragp->fr_subtype = RELAX_MIPS16_MARK_EXTENDED (fragp->fr_subtype);
13526 if (! RELAX_MIPS16_EXTENDED (fragp->fr_subtype))
13528 fragp->fr_subtype = RELAX_MIPS16_CLEAR_EXTENDED (fragp->fr_subtype);
13535 /* Convert a machine dependent frag. */
13538 md_convert_frag (abfd, asec, fragp)
13539 bfd *abfd ATTRIBUTE_UNUSED;
13546 if (RELAX_BRANCH_P (fragp->fr_subtype))
13549 unsigned long insn;
13553 buf = (bfd_byte *)fragp->fr_literal + fragp->fr_fix;
13555 if (target_big_endian)
13556 insn = bfd_getb32 (buf);
13558 insn = bfd_getl32 (buf);
13560 if (!RELAX_BRANCH_TOOFAR (fragp->fr_subtype))
13562 /* We generate a fixup instead of applying it right now
13563 because, if there are linker relaxations, we're going to
13564 need the relocations. */
13565 exp.X_op = O_symbol;
13566 exp.X_add_symbol = fragp->fr_symbol;
13567 exp.X_add_number = fragp->fr_offset;
13569 fixp = fix_new_exp (fragp, buf - (bfd_byte *)fragp->fr_literal,
13571 BFD_RELOC_16_PCREL_S2);
13572 fixp->fx_file = fragp->fr_file;
13573 fixp->fx_line = fragp->fr_line;
13575 md_number_to_chars ((char *)buf, insn, 4);
13582 as_warn_where (fragp->fr_file, fragp->fr_line,
13583 _("relaxed out-of-range branch into a jump"));
13585 if (RELAX_BRANCH_UNCOND (fragp->fr_subtype))
13588 if (!RELAX_BRANCH_LIKELY (fragp->fr_subtype))
13590 /* Reverse the branch. */
13591 switch ((insn >> 28) & 0xf)
13594 /* bc[0-3][tf]l? and bc1any[24][ft] instructions can
13595 have the condition reversed by tweaking a single
13596 bit, and their opcodes all have 0x4???????. */
13597 assert ((insn & 0xf1000000) == 0x41000000);
13598 insn ^= 0x00010000;
13602 /* bltz 0x04000000 bgez 0x04010000
13603 bltzal 0x04100000 bgezal 0x04110000 */
13604 assert ((insn & 0xfc0e0000) == 0x04000000);
13605 insn ^= 0x00010000;
13609 /* beq 0x10000000 bne 0x14000000
13610 blez 0x18000000 bgtz 0x1c000000 */
13611 insn ^= 0x04000000;
13619 if (RELAX_BRANCH_LINK (fragp->fr_subtype))
13621 /* Clear the and-link bit. */
13622 assert ((insn & 0xfc1c0000) == 0x04100000);
13624 /* bltzal 0x04100000 bgezal 0x04110000
13625 bltzall 0x04120000 bgezall 0x04130000 */
13626 insn &= ~0x00100000;
13629 /* Branch over the branch (if the branch was likely) or the
13630 full jump (not likely case). Compute the offset from the
13631 current instruction to branch to. */
13632 if (RELAX_BRANCH_LIKELY (fragp->fr_subtype))
13636 /* How many bytes in instructions we've already emitted? */
13637 i = buf - (bfd_byte *)fragp->fr_literal - fragp->fr_fix;
13638 /* How many bytes in instructions from here to the end? */
13639 i = fragp->fr_var - i;
13641 /* Convert to instruction count. */
13643 /* Branch counts from the next instruction. */
13646 /* Branch over the jump. */
13647 md_number_to_chars ((char *)buf, insn, 4);
13651 md_number_to_chars ((char*)buf, 0, 4);
13654 if (RELAX_BRANCH_LIKELY (fragp->fr_subtype))
13656 /* beql $0, $0, 2f */
13658 /* Compute the PC offset from the current instruction to
13659 the end of the variable frag. */
13660 /* How many bytes in instructions we've already emitted? */
13661 i = buf - (bfd_byte *)fragp->fr_literal - fragp->fr_fix;
13662 /* How many bytes in instructions from here to the end? */
13663 i = fragp->fr_var - i;
13664 /* Convert to instruction count. */
13666 /* Don't decrement i, because we want to branch over the
13670 md_number_to_chars ((char *)buf, insn, 4);
13673 md_number_to_chars ((char *)buf, 0, 4);
13678 if (mips_pic == NO_PIC)
13681 insn = (RELAX_BRANCH_LINK (fragp->fr_subtype)
13682 ? 0x0c000000 : 0x08000000);
13683 exp.X_op = O_symbol;
13684 exp.X_add_symbol = fragp->fr_symbol;
13685 exp.X_add_number = fragp->fr_offset;
13687 fixp = fix_new_exp (fragp, buf - (bfd_byte *)fragp->fr_literal,
13688 4, &exp, 0, BFD_RELOC_MIPS_JMP);
13689 fixp->fx_file = fragp->fr_file;
13690 fixp->fx_line = fragp->fr_line;
13692 md_number_to_chars ((char*)buf, insn, 4);
13697 /* lw/ld $at, <sym>($gp) R_MIPS_GOT16 */
13698 insn = HAVE_64BIT_ADDRESSES ? 0xdf810000 : 0x8f810000;
13699 exp.X_op = O_symbol;
13700 exp.X_add_symbol = fragp->fr_symbol;
13701 exp.X_add_number = fragp->fr_offset;
13703 if (fragp->fr_offset)
13705 exp.X_add_symbol = make_expr_symbol (&exp);
13706 exp.X_add_number = 0;
13709 fixp = fix_new_exp (fragp, buf - (bfd_byte *)fragp->fr_literal,
13710 4, &exp, 0, BFD_RELOC_MIPS_GOT16);
13711 fixp->fx_file = fragp->fr_file;
13712 fixp->fx_line = fragp->fr_line;
13714 md_number_to_chars ((char*)buf, insn, 4);
13717 if (mips_opts.isa == ISA_MIPS1)
13720 md_number_to_chars ((char*)buf, 0, 4);
13724 /* d/addiu $at, $at, <sym> R_MIPS_LO16 */
13725 insn = HAVE_64BIT_ADDRESSES ? 0x64210000 : 0x24210000;
13727 fixp = fix_new_exp (fragp, buf - (bfd_byte *)fragp->fr_literal,
13728 4, &exp, 0, BFD_RELOC_LO16);
13729 fixp->fx_file = fragp->fr_file;
13730 fixp->fx_line = fragp->fr_line;
13732 md_number_to_chars ((char*)buf, insn, 4);
13736 if (RELAX_BRANCH_LINK (fragp->fr_subtype))
13741 md_number_to_chars ((char*)buf, insn, 4);
13746 assert (buf == (bfd_byte *)fragp->fr_literal
13747 + fragp->fr_fix + fragp->fr_var);
13749 fragp->fr_fix += fragp->fr_var;
13754 if (RELAX_MIPS16_P (fragp->fr_subtype))
13757 register const struct mips16_immed_operand *op;
13758 bfd_boolean small, ext;
13761 unsigned long insn;
13762 bfd_boolean use_extend;
13763 unsigned short extend;
13765 type = RELAX_MIPS16_TYPE (fragp->fr_subtype);
13766 op = mips16_immed_operands;
13767 while (op->type != type)
13770 if (RELAX_MIPS16_EXTENDED (fragp->fr_subtype))
13781 resolve_symbol_value (fragp->fr_symbol);
13782 val = S_GET_VALUE (fragp->fr_symbol);
13787 addr = fragp->fr_address + fragp->fr_fix;
13789 /* The rules for the base address of a PC relative reloc are
13790 complicated; see mips16_extended_frag. */
13791 if (type == 'p' || type == 'q')
13796 /* Ignore the low bit in the target, since it will be
13797 set for a text label. */
13798 if ((val & 1) != 0)
13801 else if (RELAX_MIPS16_JAL_DSLOT (fragp->fr_subtype))
13803 else if (RELAX_MIPS16_DSLOT (fragp->fr_subtype))
13806 addr &= ~ (addressT) ((1 << op->shift) - 1);
13809 /* Make sure the section winds up with the alignment we have
13812 record_alignment (asec, op->shift);
13816 && (RELAX_MIPS16_JAL_DSLOT (fragp->fr_subtype)
13817 || RELAX_MIPS16_DSLOT (fragp->fr_subtype)))
13818 as_warn_where (fragp->fr_file, fragp->fr_line,
13819 _("extended instruction in delay slot"));
13821 buf = (bfd_byte *) (fragp->fr_literal + fragp->fr_fix);
13823 if (target_big_endian)
13824 insn = bfd_getb16 (buf);
13826 insn = bfd_getl16 (buf);
13828 mips16_immed (fragp->fr_file, fragp->fr_line, type, val,
13829 RELAX_MIPS16_USER_EXT (fragp->fr_subtype),
13830 small, ext, &insn, &use_extend, &extend);
13834 md_number_to_chars ((char *) buf, 0xf000 | extend, 2);
13835 fragp->fr_fix += 2;
13839 md_number_to_chars ((char *) buf, insn, 2);
13840 fragp->fr_fix += 2;
13845 if (fragp->fr_opcode == NULL)
13848 old = RELAX_OLD (fragp->fr_subtype);
13849 new = RELAX_NEW (fragp->fr_subtype);
13850 fixptr = fragp->fr_literal + fragp->fr_fix;
13853 memcpy (fixptr - old, fixptr, new);
13855 fragp->fr_fix += new - old;
13861 /* This function is called after the relocs have been generated.
13862 We've been storing mips16 text labels as odd. Here we convert them
13863 back to even for the convenience of the debugger. */
13866 mips_frob_file_after_relocs ()
13869 unsigned int count, i;
13871 if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
13874 syms = bfd_get_outsymbols (stdoutput);
13875 count = bfd_get_symcount (stdoutput);
13876 for (i = 0; i < count; i++, syms++)
13878 if (elf_symbol (*syms)->internal_elf_sym.st_other == STO_MIPS16
13879 && ((*syms)->value & 1) != 0)
13881 (*syms)->value &= ~1;
13882 /* If the symbol has an odd size, it was probably computed
13883 incorrectly, so adjust that as well. */
13884 if ((elf_symbol (*syms)->internal_elf_sym.st_size & 1) != 0)
13885 ++elf_symbol (*syms)->internal_elf_sym.st_size;
13892 /* This function is called whenever a label is defined. It is used
13893 when handling branch delays; if a branch has a label, we assume we
13894 can not move it. */
13897 mips_define_label (sym)
13900 struct insn_label_list *l;
13902 if (free_insn_labels == NULL)
13903 l = (struct insn_label_list *) xmalloc (sizeof *l);
13906 l = free_insn_labels;
13907 free_insn_labels = l->next;
13911 l->next = insn_labels;
13915 #if defined (OBJ_ELF) || defined (OBJ_MAYBE_ELF)
13917 /* Some special processing for a MIPS ELF file. */
13920 mips_elf_final_processing ()
13922 /* Write out the register information. */
13923 if (mips_abi != N64_ABI)
13927 s.ri_gprmask = mips_gprmask;
13928 s.ri_cprmask[0] = mips_cprmask[0];
13929 s.ri_cprmask[1] = mips_cprmask[1];
13930 s.ri_cprmask[2] = mips_cprmask[2];
13931 s.ri_cprmask[3] = mips_cprmask[3];
13932 /* The gp_value field is set by the MIPS ELF backend. */
13934 bfd_mips_elf32_swap_reginfo_out (stdoutput, &s,
13935 ((Elf32_External_RegInfo *)
13936 mips_regmask_frag));
13940 Elf64_Internal_RegInfo s;
13942 s.ri_gprmask = mips_gprmask;
13944 s.ri_cprmask[0] = mips_cprmask[0];
13945 s.ri_cprmask[1] = mips_cprmask[1];
13946 s.ri_cprmask[2] = mips_cprmask[2];
13947 s.ri_cprmask[3] = mips_cprmask[3];
13948 /* The gp_value field is set by the MIPS ELF backend. */
13950 bfd_mips_elf64_swap_reginfo_out (stdoutput, &s,
13951 ((Elf64_External_RegInfo *)
13952 mips_regmask_frag));
13955 /* Set the MIPS ELF flag bits. FIXME: There should probably be some
13956 sort of BFD interface for this. */
13957 if (mips_any_noreorder)
13958 elf_elfheader (stdoutput)->e_flags |= EF_MIPS_NOREORDER;
13959 if (mips_pic != NO_PIC)
13960 elf_elfheader (stdoutput)->e_flags |= EF_MIPS_PIC;
13962 /* Set MIPS ELF flags for ASEs. */
13963 if (file_ase_mips16)
13964 elf_elfheader (stdoutput)->e_flags |= EF_MIPS_ARCH_ASE_M16;
13965 #if 0 /* XXX FIXME */
13966 if (file_ase_mips3d)
13967 elf_elfheader (stdoutput)->e_flags |= ???;
13970 elf_elfheader (stdoutput)->e_flags |= EF_MIPS_ARCH_ASE_MDMX;
13972 /* Set the MIPS ELF ABI flags. */
13973 if (mips_abi == O32_ABI && USE_E_MIPS_ABI_O32)
13974 elf_elfheader (stdoutput)->e_flags |= E_MIPS_ABI_O32;
13975 else if (mips_abi == O64_ABI)
13976 elf_elfheader (stdoutput)->e_flags |= E_MIPS_ABI_O64;
13977 else if (mips_abi == EABI_ABI)
13979 if (!file_mips_gp32)
13980 elf_elfheader (stdoutput)->e_flags |= E_MIPS_ABI_EABI64;
13982 elf_elfheader (stdoutput)->e_flags |= E_MIPS_ABI_EABI32;
13984 else if (mips_abi == N32_ABI)
13985 elf_elfheader (stdoutput)->e_flags |= EF_MIPS_ABI2;
13987 /* Nothing to do for N64_ABI. */
13989 if (mips_32bitmode)
13990 elf_elfheader (stdoutput)->e_flags |= EF_MIPS_32BITMODE;
13993 #endif /* OBJ_ELF || OBJ_MAYBE_ELF */
13995 typedef struct proc {
13997 unsigned long reg_mask;
13998 unsigned long reg_offset;
13999 unsigned long fpreg_mask;
14000 unsigned long fpreg_offset;
14001 unsigned long frame_offset;
14002 unsigned long frame_reg;
14003 unsigned long pc_reg;
14006 static procS cur_proc;
14007 static procS *cur_proc_ptr;
14008 static int numprocs;
14010 /* Fill in an rs_align_code fragment. */
14013 mips_handle_align (fragp)
14016 if (fragp->fr_type != rs_align_code)
14019 if (mips_opts.mips16)
14021 static const unsigned char be_nop[] = { 0x65, 0x00 };
14022 static const unsigned char le_nop[] = { 0x00, 0x65 };
14027 bytes = fragp->fr_next->fr_address - fragp->fr_address - fragp->fr_fix;
14028 p = fragp->fr_literal + fragp->fr_fix;
14036 memcpy (p, (target_big_endian ? be_nop : le_nop), 2);
14040 /* For mips32, a nop is a zero, which we trivially get by doing nothing. */
14051 /* check for premature end, nesting errors, etc */
14053 as_warn (_("missing .end at end of assembly"));
14062 if (*input_line_pointer == '-')
14064 ++input_line_pointer;
14067 if (!ISDIGIT (*input_line_pointer))
14068 as_bad (_("expected simple number"));
14069 if (input_line_pointer[0] == '0')
14071 if (input_line_pointer[1] == 'x')
14073 input_line_pointer += 2;
14074 while (ISXDIGIT (*input_line_pointer))
14077 val |= hex_value (*input_line_pointer++);
14079 return negative ? -val : val;
14083 ++input_line_pointer;
14084 while (ISDIGIT (*input_line_pointer))
14087 val |= *input_line_pointer++ - '0';
14089 return negative ? -val : val;
14092 if (!ISDIGIT (*input_line_pointer))
14094 printf (_(" *input_line_pointer == '%c' 0x%02x\n"),
14095 *input_line_pointer, *input_line_pointer);
14096 as_warn (_("invalid number"));
14099 while (ISDIGIT (*input_line_pointer))
14102 val += *input_line_pointer++ - '0';
14104 return negative ? -val : val;
14107 /* The .file directive; just like the usual .file directive, but there
14108 is an initial number which is the ECOFF file index. In the non-ECOFF
14109 case .file implies DWARF-2. */
14113 int x ATTRIBUTE_UNUSED;
14115 static int first_file_directive = 0;
14117 if (ECOFF_DEBUGGING)
14126 filename = dwarf2_directive_file (0);
14128 /* Versions of GCC up to 3.1 start files with a ".file"
14129 directive even for stabs output. Make sure that this
14130 ".file" is handled. Note that you need a version of GCC
14131 after 3.1 in order to support DWARF-2 on MIPS. */
14132 if (filename != NULL && ! first_file_directive)
14134 (void) new_logical_line (filename, -1);
14135 s_app_file_string (filename);
14137 first_file_directive = 1;
14141 /* The .loc directive, implying DWARF-2. */
14145 int x ATTRIBUTE_UNUSED;
14147 if (!ECOFF_DEBUGGING)
14148 dwarf2_directive_loc (0);
14151 /* The .end directive. */
14155 int x ATTRIBUTE_UNUSED;
14159 /* Following functions need their own .frame and .cprestore directives. */
14160 mips_frame_reg_valid = 0;
14161 mips_cprestore_valid = 0;
14163 if (!is_end_of_line[(unsigned char) *input_line_pointer])
14166 demand_empty_rest_of_line ();
14171 if ((bfd_get_section_flags (stdoutput, now_seg) & SEC_CODE) == 0)
14172 as_warn (_(".end not in text section"));
14176 as_warn (_(".end directive without a preceding .ent directive."));
14177 demand_empty_rest_of_line ();
14183 assert (S_GET_NAME (p));
14184 if (strcmp (S_GET_NAME (p), S_GET_NAME (cur_proc_ptr->isym)))
14185 as_warn (_(".end symbol does not match .ent symbol."));
14187 if (debug_type == DEBUG_STABS)
14188 stabs_generate_asm_endfunc (S_GET_NAME (p),
14192 as_warn (_(".end directive missing or unknown symbol"));
14195 /* Generate a .pdr section. */
14196 if (OUTPUT_FLAVOR == bfd_target_elf_flavour && ! ECOFF_DEBUGGING)
14198 segT saved_seg = now_seg;
14199 subsegT saved_subseg = now_subseg;
14204 dot = frag_now_fix ();
14206 #ifdef md_flush_pending_output
14207 md_flush_pending_output ();
14211 subseg_set (pdr_seg, 0);
14213 /* Write the symbol. */
14214 exp.X_op = O_symbol;
14215 exp.X_add_symbol = p;
14216 exp.X_add_number = 0;
14217 emit_expr (&exp, 4);
14219 fragp = frag_more (7 * 4);
14221 md_number_to_chars (fragp, (valueT) cur_proc_ptr->reg_mask, 4);
14222 md_number_to_chars (fragp + 4, (valueT) cur_proc_ptr->reg_offset, 4);
14223 md_number_to_chars (fragp + 8, (valueT) cur_proc_ptr->fpreg_mask, 4);
14224 md_number_to_chars (fragp + 12, (valueT) cur_proc_ptr->fpreg_offset, 4);
14225 md_number_to_chars (fragp + 16, (valueT) cur_proc_ptr->frame_offset, 4);
14226 md_number_to_chars (fragp + 20, (valueT) cur_proc_ptr->frame_reg, 4);
14227 md_number_to_chars (fragp + 24, (valueT) cur_proc_ptr->pc_reg, 4);
14229 subseg_set (saved_seg, saved_subseg);
14231 #endif /* OBJ_ELF */
14233 cur_proc_ptr = NULL;
14236 /* The .aent and .ent directives. */
14244 symbolP = get_symbol ();
14245 if (*input_line_pointer == ',')
14246 ++input_line_pointer;
14247 SKIP_WHITESPACE ();
14248 if (ISDIGIT (*input_line_pointer)
14249 || *input_line_pointer == '-')
14252 if ((bfd_get_section_flags (stdoutput, now_seg) & SEC_CODE) == 0)
14253 as_warn (_(".ent or .aent not in text section."));
14255 if (!aent && cur_proc_ptr)
14256 as_warn (_("missing .end"));
14260 /* This function needs its own .frame and .cprestore directives. */
14261 mips_frame_reg_valid = 0;
14262 mips_cprestore_valid = 0;
14264 cur_proc_ptr = &cur_proc;
14265 memset (cur_proc_ptr, '\0', sizeof (procS));
14267 cur_proc_ptr->isym = symbolP;
14269 symbol_get_bfdsym (symbolP)->flags |= BSF_FUNCTION;
14273 if (debug_type == DEBUG_STABS)
14274 stabs_generate_asm_func (S_GET_NAME (symbolP),
14275 S_GET_NAME (symbolP));
14278 demand_empty_rest_of_line ();
14281 /* The .frame directive. If the mdebug section is present (IRIX 5 native)
14282 then ecoff.c (ecoff_directive_frame) is used. For embedded targets,
14283 s_mips_frame is used so that we can set the PDR information correctly.
14284 We can't use the ecoff routines because they make reference to the ecoff
14285 symbol table (in the mdebug section). */
14288 s_mips_frame (ignore)
14289 int ignore ATTRIBUTE_UNUSED;
14292 if (OUTPUT_FLAVOR == bfd_target_elf_flavour && ! ECOFF_DEBUGGING)
14296 if (cur_proc_ptr == (procS *) NULL)
14298 as_warn (_(".frame outside of .ent"));
14299 demand_empty_rest_of_line ();
14303 cur_proc_ptr->frame_reg = tc_get_register (1);
14305 SKIP_WHITESPACE ();
14306 if (*input_line_pointer++ != ','
14307 || get_absolute_expression_and_terminator (&val) != ',')
14309 as_warn (_("Bad .frame directive"));
14310 --input_line_pointer;
14311 demand_empty_rest_of_line ();
14315 cur_proc_ptr->frame_offset = val;
14316 cur_proc_ptr->pc_reg = tc_get_register (0);
14318 demand_empty_rest_of_line ();
14321 #endif /* OBJ_ELF */
14325 /* The .fmask and .mask directives. If the mdebug section is present
14326 (IRIX 5 native) then ecoff.c (ecoff_directive_mask) is used. For
14327 embedded targets, s_mips_mask is used so that we can set the PDR
14328 information correctly. We can't use the ecoff routines because they
14329 make reference to the ecoff symbol table (in the mdebug section). */
14332 s_mips_mask (reg_type)
14336 if (OUTPUT_FLAVOR == bfd_target_elf_flavour && ! ECOFF_DEBUGGING)
14340 if (cur_proc_ptr == (procS *) NULL)
14342 as_warn (_(".mask/.fmask outside of .ent"));
14343 demand_empty_rest_of_line ();
14347 if (get_absolute_expression_and_terminator (&mask) != ',')
14349 as_warn (_("Bad .mask/.fmask directive"));
14350 --input_line_pointer;
14351 demand_empty_rest_of_line ();
14355 off = get_absolute_expression ();
14357 if (reg_type == 'F')
14359 cur_proc_ptr->fpreg_mask = mask;
14360 cur_proc_ptr->fpreg_offset = off;
14364 cur_proc_ptr->reg_mask = mask;
14365 cur_proc_ptr->reg_offset = off;
14368 demand_empty_rest_of_line ();
14371 #endif /* OBJ_ELF */
14372 s_ignore (reg_type);
14375 /* The .loc directive. */
14386 assert (now_seg == text_section);
14388 lineno = get_number ();
14389 addroff = frag_now_fix ();
14391 symbolP = symbol_new ("", N_SLINE, addroff, frag_now);
14392 S_SET_TYPE (symbolP, N_SLINE);
14393 S_SET_OTHER (symbolP, 0);
14394 S_SET_DESC (symbolP, lineno);
14395 symbolP->sy_segment = now_seg;
14399 /* A table describing all the processors gas knows about. Names are
14400 matched in the order listed.
14402 To ease comparison, please keep this table in the same order as
14403 gcc's mips_cpu_info_table[]. */
14404 static const struct mips_cpu_info mips_cpu_info_table[] =
14406 /* Entries for generic ISAs */
14407 { "mips1", 1, ISA_MIPS1, CPU_R3000 },
14408 { "mips2", 1, ISA_MIPS2, CPU_R6000 },
14409 { "mips3", 1, ISA_MIPS3, CPU_R4000 },
14410 { "mips4", 1, ISA_MIPS4, CPU_R8000 },
14411 { "mips5", 1, ISA_MIPS5, CPU_MIPS5 },
14412 { "mips32", 1, ISA_MIPS32, CPU_MIPS32 },
14413 { "mips32r2", 1, ISA_MIPS32R2, CPU_MIPS32R2 },
14414 { "mips64", 1, ISA_MIPS64, CPU_MIPS64 },
14417 { "r3000", 0, ISA_MIPS1, CPU_R3000 },
14418 { "r2000", 0, ISA_MIPS1, CPU_R3000 },
14419 { "r3900", 0, ISA_MIPS1, CPU_R3900 },
14422 { "r6000", 0, ISA_MIPS2, CPU_R6000 },
14425 { "r4000", 0, ISA_MIPS3, CPU_R4000 },
14426 { "r4010", 0, ISA_MIPS2, CPU_R4010 },
14427 { "vr4100", 0, ISA_MIPS3, CPU_VR4100 },
14428 { "vr4111", 0, ISA_MIPS3, CPU_R4111 },
14429 { "vr4120", 0, ISA_MIPS3, CPU_VR4120 },
14430 { "vr4130", 0, ISA_MIPS3, CPU_VR4120 },
14431 { "vr4181", 0, ISA_MIPS3, CPU_R4111 },
14432 { "vr4300", 0, ISA_MIPS3, CPU_R4300 },
14433 { "r4400", 0, ISA_MIPS3, CPU_R4400 },
14434 { "r4600", 0, ISA_MIPS3, CPU_R4600 },
14435 { "orion", 0, ISA_MIPS3, CPU_R4600 },
14436 { "r4650", 0, ISA_MIPS3, CPU_R4650 },
14439 { "r8000", 0, ISA_MIPS4, CPU_R8000 },
14440 { "r10000", 0, ISA_MIPS4, CPU_R10000 },
14441 { "r12000", 0, ISA_MIPS4, CPU_R12000 },
14442 { "vr5000", 0, ISA_MIPS4, CPU_R5000 },
14443 { "vr5400", 0, ISA_MIPS4, CPU_VR5400 },
14444 { "vr5500", 0, ISA_MIPS4, CPU_VR5500 },
14445 { "rm5200", 0, ISA_MIPS4, CPU_R5000 },
14446 { "rm5230", 0, ISA_MIPS4, CPU_R5000 },
14447 { "rm5231", 0, ISA_MIPS4, CPU_R5000 },
14448 { "rm5261", 0, ISA_MIPS4, CPU_R5000 },
14449 { "rm5721", 0, ISA_MIPS4, CPU_R5000 },
14450 { "r7000", 0, ISA_MIPS4, CPU_R5000 },
14453 { "4kc", 0, ISA_MIPS32, CPU_MIPS32, },
14454 { "4km", 0, ISA_MIPS32, CPU_MIPS32 },
14455 { "4kp", 0, ISA_MIPS32, CPU_MIPS32 },
14458 { "5kc", 0, ISA_MIPS64, CPU_MIPS64 },
14459 { "20kc", 0, ISA_MIPS64, CPU_MIPS64 },
14461 /* Broadcom SB-1 CPU core */
14462 { "sb1", 0, ISA_MIPS64, CPU_SB1 },
14469 /* Return true if GIVEN is the same as CANONICAL, or if it is CANONICAL
14470 with a final "000" replaced by "k". Ignore case.
14472 Note: this function is shared between GCC and GAS. */
14475 mips_strict_matching_cpu_name_p (canonical, given)
14476 const char *canonical, *given;
14478 while (*given != 0 && TOLOWER (*given) == TOLOWER (*canonical))
14479 given++, canonical++;
14481 return ((*given == 0 && *canonical == 0)
14482 || (strcmp (canonical, "000") == 0 && strcasecmp (given, "k") == 0));
14486 /* Return true if GIVEN matches CANONICAL, where GIVEN is a user-supplied
14487 CPU name. We've traditionally allowed a lot of variation here.
14489 Note: this function is shared between GCC and GAS. */
14492 mips_matching_cpu_name_p (canonical, given)
14493 const char *canonical, *given;
14495 /* First see if the name matches exactly, or with a final "000"
14496 turned into "k". */
14497 if (mips_strict_matching_cpu_name_p (canonical, given))
14500 /* If not, try comparing based on numerical designation alone.
14501 See if GIVEN is an unadorned number, or 'r' followed by a number. */
14502 if (TOLOWER (*given) == 'r')
14504 if (!ISDIGIT (*given))
14507 /* Skip over some well-known prefixes in the canonical name,
14508 hoping to find a number there too. */
14509 if (TOLOWER (canonical[0]) == 'v' && TOLOWER (canonical[1]) == 'r')
14511 else if (TOLOWER (canonical[0]) == 'r' && TOLOWER (canonical[1]) == 'm')
14513 else if (TOLOWER (canonical[0]) == 'r')
14516 return mips_strict_matching_cpu_name_p (canonical, given);
14520 /* Parse an option that takes the name of a processor as its argument.
14521 OPTION is the name of the option and CPU_STRING is the argument.
14522 Return the corresponding processor enumeration if the CPU_STRING is
14523 recognized, otherwise report an error and return null.
14525 A similar function exists in GCC. */
14527 static const struct mips_cpu_info *
14528 mips_parse_cpu (option, cpu_string)
14529 const char *option, *cpu_string;
14531 const struct mips_cpu_info *p;
14533 /* 'from-abi' selects the most compatible architecture for the given
14534 ABI: MIPS I for 32-bit ABIs and MIPS III for 64-bit ABIs. For the
14535 EABIs, we have to decide whether we're using the 32-bit or 64-bit
14536 version. Look first at the -mgp options, if given, otherwise base
14537 the choice on MIPS_DEFAULT_64BIT.
14539 Treat NO_ABI like the EABIs. One reason to do this is that the
14540 plain 'mips' and 'mips64' configs have 'from-abi' as their default
14541 architecture. This code picks MIPS I for 'mips' and MIPS III for
14542 'mips64', just as we did in the days before 'from-abi'. */
14543 if (strcasecmp (cpu_string, "from-abi") == 0)
14545 if (ABI_NEEDS_32BIT_REGS (mips_abi))
14546 return mips_cpu_info_from_isa (ISA_MIPS1);
14548 if (ABI_NEEDS_64BIT_REGS (mips_abi))
14549 return mips_cpu_info_from_isa (ISA_MIPS3);
14551 if (file_mips_gp32 >= 0)
14552 return mips_cpu_info_from_isa (file_mips_gp32 ? ISA_MIPS1 : ISA_MIPS3);
14554 return mips_cpu_info_from_isa (MIPS_DEFAULT_64BIT
14559 /* 'default' has traditionally been a no-op. Probably not very useful. */
14560 if (strcasecmp (cpu_string, "default") == 0)
14563 for (p = mips_cpu_info_table; p->name != 0; p++)
14564 if (mips_matching_cpu_name_p (p->name, cpu_string))
14567 as_bad ("Bad value (%s) for %s", cpu_string, option);
14571 /* Return the canonical processor information for ISA (a member of the
14572 ISA_MIPS* enumeration). */
14574 static const struct mips_cpu_info *
14575 mips_cpu_info_from_isa (isa)
14580 for (i = 0; mips_cpu_info_table[i].name != NULL; i++)
14581 if (mips_cpu_info_table[i].is_isa
14582 && isa == mips_cpu_info_table[i].isa)
14583 return (&mips_cpu_info_table[i]);
14589 show (stream, string, col_p, first_p)
14591 const char *string;
14597 fprintf (stream, "%24s", "");
14602 fprintf (stream, ", ");
14606 if (*col_p + strlen (string) > 72)
14608 fprintf (stream, "\n%24s", "");
14612 fprintf (stream, "%s", string);
14613 *col_p += strlen (string);
14619 md_show_usage (stream)
14625 fprintf (stream, _("\
14627 -membedded-pic generate embedded position independent code\n\
14628 -EB generate big endian output\n\
14629 -EL generate little endian output\n\
14630 -g, -g2 do not remove unneeded NOPs or swap branches\n\
14631 -G NUM allow referencing objects up to NUM bytes\n\
14632 implicitly with the gp register [default 8]\n"));
14633 fprintf (stream, _("\
14634 -mips1 generate MIPS ISA I instructions\n\
14635 -mips2 generate MIPS ISA II instructions\n\
14636 -mips3 generate MIPS ISA III instructions\n\
14637 -mips4 generate MIPS ISA IV instructions\n\
14638 -mips5 generate MIPS ISA V instructions\n\
14639 -mips32 generate MIPS32 ISA instructions\n\
14640 -mips32r2 generate MIPS32 release 2 ISA instructions\n\
14641 -mips64 generate MIPS64 ISA instructions\n\
14642 -march=CPU/-mtune=CPU generate code/schedule for CPU, where CPU is one of:\n"));
14646 for (i = 0; mips_cpu_info_table[i].name != NULL; i++)
14647 show (stream, mips_cpu_info_table[i].name, &column, &first);
14648 show (stream, "from-abi", &column, &first);
14649 fputc ('\n', stream);
14651 fprintf (stream, _("\
14652 -mCPU equivalent to -march=CPU -mtune=CPU. Deprecated.\n\
14653 -no-mCPU don't generate code specific to CPU.\n\
14654 For -mCPU and -no-mCPU, CPU must be one of:\n"));
14658 show (stream, "3900", &column, &first);
14659 show (stream, "4010", &column, &first);
14660 show (stream, "4100", &column, &first);
14661 show (stream, "4650", &column, &first);
14662 fputc ('\n', stream);
14664 fprintf (stream, _("\
14665 -mips16 generate mips16 instructions\n\
14666 -no-mips16 do not generate mips16 instructions\n"));
14667 fprintf (stream, _("\
14668 -mgp32 use 32-bit GPRs, regardless of the chosen ISA\n\
14669 -mfp32 use 32-bit FPRs, regardless of the chosen ISA\n\
14670 -O0 remove unneeded NOPs, do not swap branches\n\
14671 -O remove unneeded NOPs and swap branches\n\
14672 -n warn about NOPs generated from macros\n\
14673 --[no-]construct-floats [dis]allow floating point values to be constructed\n\
14674 --trap, --no-break trap exception on div by 0 and mult overflow\n\
14675 --break, --no-trap break exception on div by 0 and mult overflow\n"));
14677 fprintf (stream, _("\
14678 -KPIC, -call_shared generate SVR4 position independent code\n\
14679 -non_shared do not generate position independent code\n\
14680 -xgot assume a 32 bit GOT\n\
14681 -mabi=ABI create ABI conformant object file for:\n"));
14685 show (stream, "32", &column, &first);
14686 show (stream, "o64", &column, &first);
14687 show (stream, "n32", &column, &first);
14688 show (stream, "64", &column, &first);
14689 show (stream, "eabi", &column, &first);
14691 fputc ('\n', stream);
14693 fprintf (stream, _("\
14694 -32 create o32 ABI object file (default)\n\
14695 -n32 create n32 ABI object file\n\
14696 -64 create 64 ABI object file\n"));
14701 mips_dwarf2_format ()
14703 if (mips_abi == N64_ABI)
14706 return dwarf2_format_64bit_irix;
14708 return dwarf2_format_64bit;
14712 return dwarf2_format_32bit;