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 /* Whether or not we have code that can call pic code. */
135 int mips_abicalls = FALSE;
137 /* This is the set of options which may be modified by the .set
138 pseudo-op. We use a struct so that .set push and .set pop are more
141 struct mips_set_options
143 /* MIPS ISA (Instruction Set Architecture) level. This is set to -1
144 if it has not been initialized. Changed by `.set mipsN', and the
145 -mipsN command line option, and the default CPU. */
147 /* Enabled Application Specific Extensions (ASEs). These are set to -1
148 if they have not been initialized. Changed by `.set <asename>', by
149 command line options, and based on the default architecture. */
152 /* Whether we are assembling for the mips16 processor. 0 if we are
153 not, 1 if we are, and -1 if the value has not been initialized.
154 Changed by `.set mips16' and `.set nomips16', and the -mips16 and
155 -nomips16 command line options, and the default CPU. */
157 /* Non-zero if we should not reorder instructions. Changed by `.set
158 reorder' and `.set noreorder'. */
160 /* Non-zero if we should not permit the $at ($1) register to be used
161 in instructions. Changed by `.set at' and `.set noat'. */
163 /* Non-zero if we should warn when a macro instruction expands into
164 more than one machine instruction. Changed by `.set nomacro' and
166 int warn_about_macros;
167 /* Non-zero if we should not move instructions. Changed by `.set
168 move', `.set volatile', `.set nomove', and `.set novolatile'. */
170 /* Non-zero if we should not optimize branches by moving the target
171 of the branch into the delay slot. Actually, we don't perform
172 this optimization anyhow. Changed by `.set bopt' and `.set
175 /* Non-zero if we should not autoextend mips16 instructions.
176 Changed by `.set autoextend' and `.set noautoextend'. */
178 /* Restrict general purpose registers and floating point registers
179 to 32 bit. This is initially determined when -mgp32 or -mfp32
180 is passed but can changed if the assembler code uses .set mipsN. */
185 /* True if -mgp32 was passed. */
186 static int file_mips_gp32 = -1;
188 /* True if -mfp32 was passed. */
189 static int file_mips_fp32 = -1;
191 /* This is the struct we use to hold the current set of options. Note
192 that we must set the isa field to ISA_UNKNOWN and the ASE fields to
193 -1 to indicate that they have not been initialized. */
195 static struct mips_set_options mips_opts =
197 ISA_UNKNOWN, -1, -1, -1, 0, 0, 0, 0, 0, 0, 0, 0
200 /* These variables are filled in with the masks of registers used.
201 The object format code reads them and puts them in the appropriate
203 unsigned long mips_gprmask;
204 unsigned long mips_cprmask[4];
206 /* MIPS ISA we are using for this output file. */
207 static int file_mips_isa = ISA_UNKNOWN;
209 /* True if -mips16 was passed or implied by arguments passed on the
210 command line (e.g., by -march). */
211 static int file_ase_mips16;
213 /* True if -mips3d was passed or implied by arguments passed on the
214 command line (e.g., by -march). */
215 static int file_ase_mips3d;
217 /* True if -mdmx was passed or implied by arguments passed on the
218 command line (e.g., by -march). */
219 static int file_ase_mdmx;
221 /* The argument of the -march= flag. The architecture we are assembling. */
222 static int mips_arch = CPU_UNKNOWN;
223 static const char *mips_arch_string;
224 static const struct mips_cpu_info *mips_arch_info;
226 /* The argument of the -mtune= flag. The architecture for which we
228 static int mips_tune = CPU_UNKNOWN;
229 static const char *mips_tune_string;
230 static const struct mips_cpu_info *mips_tune_info;
232 /* True when generating 32-bit code for a 64-bit processor. */
233 static int mips_32bitmode = 0;
235 /* Some ISA's have delay slots for instructions which read or write
236 from a coprocessor (eg. mips1-mips3); some don't (eg mips4).
237 Return true if instructions marked INSN_LOAD_COPROC_DELAY,
238 INSN_COPROC_MOVE_DELAY, or INSN_WRITE_COND_CODE actually have a
239 delay slot in this ISA. The uses of this macro assume that any
240 ISA that has delay slots for one of these, has them for all. They
241 also assume that ISAs which don't have delays for these insns, don't
242 have delays for the INSN_LOAD_MEMORY_DELAY instructions either. */
243 #define ISA_HAS_COPROC_DELAYS(ISA) ( \
245 || (ISA) == ISA_MIPS2 \
246 || (ISA) == ISA_MIPS3 \
249 /* True if the given ABI requires 32-bit registers. */
250 #define ABI_NEEDS_32BIT_REGS(ABI) ((ABI) == O32_ABI)
252 /* Likewise 64-bit registers. */
253 #define ABI_NEEDS_64BIT_REGS(ABI) \
255 || (ABI) == N64_ABI \
258 /* Return true if ISA supports 64 bit gp register instructions. */
259 #define ISA_HAS_64BIT_REGS(ISA) ( \
261 || (ISA) == ISA_MIPS4 \
262 || (ISA) == ISA_MIPS5 \
263 || (ISA) == ISA_MIPS64 \
266 /* Return true if ISA supports 64-bit right rotate (dror et al.)
268 #define ISA_HAS_DROR(ISA) ( \
272 /* Return true if ISA supports 32-bit right rotate (ror et al.)
274 #define ISA_HAS_ROR(ISA) ( \
275 (ISA) == ISA_MIPS32R2 \
278 #define HAVE_32BIT_GPRS \
279 (mips_opts.gp32 || ! ISA_HAS_64BIT_REGS (mips_opts.isa))
281 #define HAVE_32BIT_FPRS \
282 (mips_opts.fp32 || ! ISA_HAS_64BIT_REGS (mips_opts.isa))
284 #define HAVE_64BIT_GPRS (! HAVE_32BIT_GPRS)
285 #define HAVE_64BIT_FPRS (! HAVE_32BIT_FPRS)
287 #define HAVE_NEWABI (mips_abi == N32_ABI || mips_abi == N64_ABI)
289 #define HAVE_64BIT_OBJECTS (mips_abi == N64_ABI)
291 /* We can only have 64bit addresses if the object file format
293 #define HAVE_32BIT_ADDRESSES \
295 || ((bfd_arch_bits_per_address (stdoutput) == 32 \
296 || ! HAVE_64BIT_OBJECTS) \
297 && mips_pic != EMBEDDED_PIC))
299 #define HAVE_64BIT_ADDRESSES (! HAVE_32BIT_ADDRESSES)
300 #define HAVE_64BIT_ADDRESS_CONSTANTS (HAVE_64BIT_ADDRESSES \
303 /* Return true if the given CPU supports the MIPS16 ASE. */
304 #define CPU_HAS_MIPS16(cpu) \
305 (strncmp (TARGET_CPU, "mips16", sizeof ("mips16") - 1) == 0 \
306 || strncmp (TARGET_CANONICAL, "mips-lsi-elf", sizeof ("mips-lsi-elf") - 1) == 0)
308 /* Return true if the given CPU supports the MIPS3D ASE. */
309 #define CPU_HAS_MIPS3D(cpu) ((cpu) == CPU_SB1 \
312 /* Return true if the given CPU supports the MDMX ASE. */
313 #define CPU_HAS_MDMX(cpu) (FALSE \
316 /* True if CPU has a dror instruction. */
317 #define CPU_HAS_DROR(CPU) ((CPU) == CPU_VR5400 || (CPU) == CPU_VR5500)
319 /* True if CPU has a ror instruction. */
320 #define CPU_HAS_ROR(CPU) CPU_HAS_DROR (CPU)
322 /* Whether the processor uses hardware interlocks to protect
323 reads from the HI and LO registers, and thus does not
324 require nops to be inserted. */
326 #define hilo_interlocks (mips_arch == CPU_R4010 \
327 || mips_arch == CPU_VR5500 \
328 || mips_arch == CPU_SB1 \
331 /* Whether the processor uses hardware interlocks to protect reads
332 from the GPRs, and thus does not require nops to be inserted. */
333 #define gpr_interlocks \
334 (mips_opts.isa != ISA_MIPS1 \
335 || mips_arch == CPU_VR5400 \
336 || mips_arch == CPU_VR5500 \
337 || mips_arch == CPU_R3900)
339 /* As with other "interlocks" this is used by hardware that has FP
340 (co-processor) interlocks. */
341 /* Itbl support may require additional care here. */
342 #define cop_interlocks (mips_arch == CPU_R4300 \
343 || mips_arch == CPU_VR5400 \
344 || mips_arch == CPU_VR5500 \
345 || mips_arch == CPU_SB1 \
348 /* Is this a mfhi or mflo instruction? */
349 #define MF_HILO_INSN(PINFO) \
350 ((PINFO & INSN_READ_HI) || (PINFO & INSN_READ_LO))
352 /* MIPS PIC level. */
354 enum mips_pic_level mips_pic;
356 /* Warn about all NOPS that the assembler generates. */
357 static int warn_nops = 0;
359 /* 1 if we should generate 32 bit offsets from the $gp register in
360 SVR4_PIC mode. Currently has no meaning in other modes. */
361 static int mips_big_got = 0;
363 /* 1 if trap instructions should used for overflow rather than break
365 static int mips_trap = 0;
367 /* 1 if double width floating point constants should not be constructed
368 by assembling two single width halves into two single width floating
369 point registers which just happen to alias the double width destination
370 register. On some architectures this aliasing can be disabled by a bit
371 in the status register, and the setting of this bit cannot be determined
372 automatically at assemble time. */
373 static int mips_disable_float_construction;
375 /* Non-zero if any .set noreorder directives were used. */
377 static int mips_any_noreorder;
379 /* Non-zero if nops should be inserted when the register referenced in
380 an mfhi/mflo instruction is read in the next two instructions. */
381 static int mips_7000_hilo_fix;
383 /* The size of the small data section. */
384 static unsigned int g_switch_value = 8;
385 /* Whether the -G option was used. */
386 static int g_switch_seen = 0;
391 /* If we can determine in advance that GP optimization won't be
392 possible, we can skip the relaxation stuff that tries to produce
393 GP-relative references. This makes delay slot optimization work
396 This function can only provide a guess, but it seems to work for
397 gcc output. It needs to guess right for gcc, otherwise gcc
398 will put what it thinks is a GP-relative instruction in a branch
401 I don't know if a fix is needed for the SVR4_PIC mode. I've only
402 fixed it for the non-PIC mode. KR 95/04/07 */
403 static int nopic_need_relax PARAMS ((symbolS *, int));
405 /* handle of the OPCODE hash table */
406 static struct hash_control *op_hash = NULL;
408 /* The opcode hash table we use for the mips16. */
409 static struct hash_control *mips16_op_hash = NULL;
411 /* This array holds the chars that always start a comment. If the
412 pre-processor is disabled, these aren't very useful */
413 const char comment_chars[] = "#";
415 /* This array holds the chars that only start a comment at the beginning of
416 a line. If the line seems to have the form '# 123 filename'
417 .line and .file directives will appear in the pre-processed output */
418 /* Note that input_file.c hand checks for '#' at the beginning of the
419 first line of the input file. This is because the compiler outputs
420 #NO_APP at the beginning of its output. */
421 /* Also note that C style comments are always supported. */
422 const char line_comment_chars[] = "#";
424 /* This array holds machine specific line separator characters. */
425 const char line_separator_chars[] = ";";
427 /* Chars that can be used to separate mant from exp in floating point nums */
428 const char EXP_CHARS[] = "eE";
430 /* Chars that mean this number is a floating point constant */
433 const char FLT_CHARS[] = "rRsSfFdDxXpP";
435 /* Also be aware that MAXIMUM_NUMBER_OF_CHARS_FOR_FLOAT may have to be
436 changed in read.c . Ideally it shouldn't have to know about it at all,
437 but nothing is ideal around here.
440 static char *insn_error;
442 static int auto_align = 1;
444 /* When outputting SVR4 PIC code, the assembler needs to know the
445 offset in the stack frame from which to restore the $gp register.
446 This is set by the .cprestore pseudo-op, and saved in this
448 static offsetT mips_cprestore_offset = -1;
450 /* Similiar for NewABI PIC code, where $gp is callee-saved. NewABI has some
451 more optimizations, it can use a register value instead of a memory-saved
452 offset and even an other register than $gp as global pointer. */
453 static offsetT mips_cpreturn_offset = -1;
454 static int mips_cpreturn_register = -1;
455 static int mips_gp_register = GP;
456 static int mips_gprel_offset = 0;
458 /* Whether mips_cprestore_offset has been set in the current function
459 (or whether it has already been warned about, if not). */
460 static int mips_cprestore_valid = 0;
462 /* This is the register which holds the stack frame, as set by the
463 .frame pseudo-op. This is needed to implement .cprestore. */
464 static int mips_frame_reg = SP;
466 /* Whether mips_frame_reg has been set in the current function
467 (or whether it has already been warned about, if not). */
468 static int mips_frame_reg_valid = 0;
470 /* To output NOP instructions correctly, we need to keep information
471 about the previous two instructions. */
473 /* Whether we are optimizing. The default value of 2 means to remove
474 unneeded NOPs and swap branch instructions when possible. A value
475 of 1 means to not swap branches. A value of 0 means to always
477 static int mips_optimize = 2;
479 /* Debugging level. -g sets this to 2. -gN sets this to N. -g0 is
480 equivalent to seeing no -g option at all. */
481 static int mips_debug = 0;
483 /* The previous instruction. */
484 static struct mips_cl_insn prev_insn;
486 /* The instruction before prev_insn. */
487 static struct mips_cl_insn prev_prev_insn;
489 /* If we don't want information for prev_insn or prev_prev_insn, we
490 point the insn_mo field at this dummy integer. */
491 static const struct mips_opcode dummy_opcode = { NULL, NULL, 0, 0, 0, 0 };
493 /* Non-zero if prev_insn is valid. */
494 static int prev_insn_valid;
496 /* The frag for the previous instruction. */
497 static struct frag *prev_insn_frag;
499 /* The offset into prev_insn_frag for the previous instruction. */
500 static long prev_insn_where;
502 /* The reloc type for the previous instruction, if any. */
503 static bfd_reloc_code_real_type prev_insn_reloc_type[3];
505 /* The reloc for the previous instruction, if any. */
506 static fixS *prev_insn_fixp[3];
508 /* Non-zero if the previous instruction was in a delay slot. */
509 static int prev_insn_is_delay_slot;
511 /* Non-zero if the previous instruction was in a .set noreorder. */
512 static int prev_insn_unreordered;
514 /* Non-zero if the previous instruction uses an extend opcode (if
516 static int prev_insn_extended;
518 /* Non-zero if the previous previous instruction was in a .set
520 static int prev_prev_insn_unreordered;
522 /* If this is set, it points to a frag holding nop instructions which
523 were inserted before the start of a noreorder section. If those
524 nops turn out to be unnecessary, the size of the frag can be
526 static fragS *prev_nop_frag;
528 /* The number of nop instructions we created in prev_nop_frag. */
529 static int prev_nop_frag_holds;
531 /* The number of nop instructions that we know we need in
533 static int prev_nop_frag_required;
535 /* The number of instructions we've seen since prev_nop_frag. */
536 static int prev_nop_frag_since;
538 /* For ECOFF and ELF, relocations against symbols are done in two
539 parts, with a HI relocation and a LO relocation. Each relocation
540 has only 16 bits of space to store an addend. This means that in
541 order for the linker to handle carries correctly, it must be able
542 to locate both the HI and the LO relocation. This means that the
543 relocations must appear in order in the relocation table.
545 In order to implement this, we keep track of each unmatched HI
546 relocation. We then sort them so that they immediately precede the
547 corresponding LO relocation. */
552 struct mips_hi_fixup *next;
555 /* The section this fixup is in. */
559 /* The list of unmatched HI relocs. */
561 static struct mips_hi_fixup *mips_hi_fixup_list;
563 /* The frag containing the last explicit relocation operator.
564 Null if explicit relocations have not been used. */
566 static fragS *prev_reloc_op_frag;
568 /* Map normal MIPS register numbers to mips16 register numbers. */
570 #define X ILLEGAL_REG
571 static const int mips32_to_16_reg_map[] =
573 X, X, 2, 3, 4, 5, 6, 7,
574 X, X, X, X, X, X, X, X,
575 0, 1, X, X, X, X, X, X,
576 X, X, X, X, X, X, X, X
580 /* Map mips16 register numbers to normal MIPS register numbers. */
582 static const unsigned int mips16_to_32_reg_map[] =
584 16, 17, 2, 3, 4, 5, 6, 7
587 static int mips_fix_4122_bugs;
589 /* We don't relax branches by default, since this causes us to expand
590 `la .l2 - .l1' if there's a branch between .l1 and .l2, because we
591 fail to compute the offset before expanding the macro to the most
592 efficient expansion. */
594 static int mips_relax_branch;
596 /* Since the MIPS does not have multiple forms of PC relative
597 instructions, we do not have to do relaxing as is done on other
598 platforms. However, we do have to handle GP relative addressing
599 correctly, which turns out to be a similar problem.
601 Every macro that refers to a symbol can occur in (at least) two
602 forms, one with GP relative addressing and one without. For
603 example, loading a global variable into a register generally uses
604 a macro instruction like this:
606 If i can be addressed off the GP register (this is true if it is in
607 the .sbss or .sdata section, or if it is known to be smaller than
608 the -G argument) this will generate the following instruction:
610 This instruction will use a GPREL reloc. If i can not be addressed
611 off the GP register, the following instruction sequence will be used:
614 In this case the first instruction will have a HI16 reloc, and the
615 second reloc will have a LO16 reloc. Both relocs will be against
618 The issue here is that we may not know whether i is GP addressable
619 until after we see the instruction that uses it. Therefore, we
620 want to be able to choose the final instruction sequence only at
621 the end of the assembly. This is similar to the way other
622 platforms choose the size of a PC relative instruction only at the
625 When generating position independent code we do not use GP
626 addressing in quite the same way, but the issue still arises as
627 external symbols and local symbols must be handled differently.
629 We handle these issues by actually generating both possible
630 instruction sequences. The longer one is put in a frag_var with
631 type rs_machine_dependent. We encode what to do with the frag in
632 the subtype field. We encode (1) the number of existing bytes to
633 replace, (2) the number of new bytes to use, (3) the offset from
634 the start of the existing bytes to the first reloc we must generate
635 (that is, the offset is applied from the start of the existing
636 bytes after they are replaced by the new bytes, if any), (4) the
637 offset from the start of the existing bytes to the second reloc,
638 (5) whether a third reloc is needed (the third reloc is always four
639 bytes after the second reloc), and (6) whether to warn if this
640 variant is used (this is sometimes needed if .set nomacro or .set
641 noat is in effect). All these numbers are reasonably small.
643 Generating two instruction sequences must be handled carefully to
644 ensure that delay slots are handled correctly. Fortunately, there
645 are a limited number of cases. When the second instruction
646 sequence is generated, append_insn is directed to maintain the
647 existing delay slot information, so it continues to apply to any
648 code after the second instruction sequence. This means that the
649 second instruction sequence must not impose any requirements not
650 required by the first instruction sequence.
652 These variant frags are then handled in functions called by the
653 machine independent code. md_estimate_size_before_relax returns
654 the final size of the frag. md_convert_frag sets up the final form
655 of the frag. tc_gen_reloc adjust the first reloc and adds a second
657 #define RELAX_ENCODE(old, new, reloc1, reloc2, reloc3, warn) \
661 | (((reloc1) + 64) << 9) \
662 | (((reloc2) + 64) << 2) \
663 | ((reloc3) ? (1 << 1) : 0) \
665 #define RELAX_OLD(i) (((i) >> 23) & 0x7f)
666 #define RELAX_NEW(i) (((i) >> 16) & 0x7f)
667 #define RELAX_RELOC1(i) ((valueT) (((i) >> 9) & 0x7f) - 64)
668 #define RELAX_RELOC2(i) ((valueT) (((i) >> 2) & 0x7f) - 64)
669 #define RELAX_RELOC3(i) (((i) >> 1) & 1)
670 #define RELAX_WARN(i) ((i) & 1)
672 /* Branch without likely bit. If label is out of range, we turn:
674 beq reg1, reg2, label
684 with the following opcode replacements:
691 bltzal <-> bgezal (with jal label instead of j label)
693 Even though keeping the delay slot instruction in the delay slot of
694 the branch would be more efficient, it would be very tricky to do
695 correctly, because we'd have to introduce a variable frag *after*
696 the delay slot instruction, and expand that instead. Let's do it
697 the easy way for now, even if the branch-not-taken case now costs
698 one additional instruction. Out-of-range branches are not supposed
699 to be common, anyway.
701 Branch likely. If label is out of range, we turn:
703 beql reg1, reg2, label
704 delay slot (annulled if branch not taken)
713 delay slot (executed only if branch taken)
716 It would be possible to generate a shorter sequence by losing the
717 likely bit, generating something like:
722 delay slot (executed only if branch taken)
734 bltzall -> bgezal (with jal label instead of j label)
735 bgezall -> bltzal (ditto)
738 but it's not clear that it would actually improve performance. */
739 #define RELAX_BRANCH_ENCODE(uncond, likely, link, toofar) \
742 | ((toofar) ? 1 : 0) \
744 | ((likely) ? 4 : 0) \
745 | ((uncond) ? 8 : 0)))
746 #define RELAX_BRANCH_P(i) (((i) & 0xf0000000) == 0xc0000000)
747 #define RELAX_BRANCH_UNCOND(i) (((i) & 8) != 0)
748 #define RELAX_BRANCH_LIKELY(i) (((i) & 4) != 0)
749 #define RELAX_BRANCH_LINK(i) (((i) & 2) != 0)
750 #define RELAX_BRANCH_TOOFAR(i) (((i) & 1) != 0)
752 /* For mips16 code, we use an entirely different form of relaxation.
753 mips16 supports two versions of most instructions which take
754 immediate values: a small one which takes some small value, and a
755 larger one which takes a 16 bit value. Since branches also follow
756 this pattern, relaxing these values is required.
758 We can assemble both mips16 and normal MIPS code in a single
759 object. Therefore, we need to support this type of relaxation at
760 the same time that we support the relaxation described above. We
761 use the high bit of the subtype field to distinguish these cases.
763 The information we store for this type of relaxation is the
764 argument code found in the opcode file for this relocation, whether
765 the user explicitly requested a small or extended form, and whether
766 the relocation is in a jump or jal delay slot. That tells us the
767 size of the value, and how it should be stored. We also store
768 whether the fragment is considered to be extended or not. We also
769 store whether this is known to be a branch to a different section,
770 whether we have tried to relax this frag yet, and whether we have
771 ever extended a PC relative fragment because of a shift count. */
772 #define RELAX_MIPS16_ENCODE(type, small, ext, dslot, jal_dslot) \
775 | ((small) ? 0x100 : 0) \
776 | ((ext) ? 0x200 : 0) \
777 | ((dslot) ? 0x400 : 0) \
778 | ((jal_dslot) ? 0x800 : 0))
779 #define RELAX_MIPS16_P(i) (((i) & 0xc0000000) == 0x80000000)
780 #define RELAX_MIPS16_TYPE(i) ((i) & 0xff)
781 #define RELAX_MIPS16_USER_SMALL(i) (((i) & 0x100) != 0)
782 #define RELAX_MIPS16_USER_EXT(i) (((i) & 0x200) != 0)
783 #define RELAX_MIPS16_DSLOT(i) (((i) & 0x400) != 0)
784 #define RELAX_MIPS16_JAL_DSLOT(i) (((i) & 0x800) != 0)
785 #define RELAX_MIPS16_EXTENDED(i) (((i) & 0x1000) != 0)
786 #define RELAX_MIPS16_MARK_EXTENDED(i) ((i) | 0x1000)
787 #define RELAX_MIPS16_CLEAR_EXTENDED(i) ((i) &~ 0x1000)
788 #define RELAX_MIPS16_LONG_BRANCH(i) (((i) & 0x2000) != 0)
789 #define RELAX_MIPS16_MARK_LONG_BRANCH(i) ((i) | 0x2000)
790 #define RELAX_MIPS16_CLEAR_LONG_BRANCH(i) ((i) &~ 0x2000)
792 /* Is the given value a sign-extended 32-bit value? */
793 #define IS_SEXT_32BIT_NUM(x) \
794 (((x) &~ (offsetT) 0x7fffffff) == 0 \
795 || (((x) &~ (offsetT) 0x7fffffff) == ~ (offsetT) 0x7fffffff))
797 /* Is the given value a sign-extended 16-bit value? */
798 #define IS_SEXT_16BIT_NUM(x) \
799 (((x) &~ (offsetT) 0x7fff) == 0 \
800 || (((x) &~ (offsetT) 0x7fff) == ~ (offsetT) 0x7fff))
803 /* Prototypes for static functions. */
806 #define internalError() \
807 as_fatal (_("internal Error, line %d, %s"), __LINE__, __FILE__)
809 #define internalError() as_fatal (_("MIPS internal Error"));
812 enum mips_regclass { MIPS_GR_REG, MIPS_FP_REG, MIPS16_REG };
814 static inline bfd_boolean reloc_needs_lo_p
815 PARAMS ((bfd_reloc_code_real_type));
816 static inline bfd_boolean fixup_has_matching_lo_p
818 static int insn_uses_reg
819 PARAMS ((struct mips_cl_insn *ip, unsigned int reg,
820 enum mips_regclass class));
821 static int reg_needs_delay
822 PARAMS ((unsigned int));
823 static void mips16_mark_labels
825 static void append_insn
826 PARAMS ((char *place, struct mips_cl_insn * ip, expressionS * p,
827 bfd_reloc_code_real_type *r));
828 static void mips_no_prev_insn
830 static void mips_emit_delays
831 PARAMS ((bfd_boolean));
833 static void macro_build
834 PARAMS ((char *place, int *counter, expressionS * ep, const char *name,
835 const char *fmt, ...));
837 static void macro_build ();
839 static void mips16_macro_build
840 PARAMS ((char *, int *, expressionS *, const char *, const char *, va_list));
841 static void macro_build_jalr
842 PARAMS ((int, expressionS *));
843 static void macro_build_lui
844 PARAMS ((char *place, int *counter, expressionS * ep, int regnum));
845 static void macro_build_ldst_constoffset
846 PARAMS ((char *place, int *counter, expressionS * ep, const char *op,
847 int valreg, int breg));
849 PARAMS ((int *counter, int reg, int unsignedp));
850 static void check_absolute_expr
851 PARAMS ((struct mips_cl_insn * ip, expressionS *));
852 static void load_register
853 PARAMS ((int *, int, expressionS *, int));
854 static void load_address
855 PARAMS ((int *, int, expressionS *, int *));
856 static void move_register
857 PARAMS ((int *, int, int));
859 PARAMS ((struct mips_cl_insn * ip));
860 static void mips16_macro
861 PARAMS ((struct mips_cl_insn * ip));
862 #ifdef LOSING_COMPILER
864 PARAMS ((struct mips_cl_insn * ip));
867 PARAMS ((char *str, struct mips_cl_insn * ip));
868 static void mips16_ip
869 PARAMS ((char *str, struct mips_cl_insn * ip));
870 static void mips16_immed
871 PARAMS ((char *, unsigned int, int, offsetT, bfd_boolean, bfd_boolean,
872 bfd_boolean, unsigned long *, bfd_boolean *, unsigned short *));
873 static bfd_boolean parse_relocation
874 PARAMS ((char **, bfd_reloc_code_real_type *));
875 static size_t my_getSmallExpression
876 PARAMS ((expressionS *, bfd_reloc_code_real_type *, char *));
877 static void my_getExpression
878 PARAMS ((expressionS *, char *));
880 static int support_64bit_objects
883 static void mips_set_option_string
884 PARAMS ((const char **, const char *));
885 static symbolS *get_symbol
887 static void mips_align
888 PARAMS ((int to, int fill, symbolS *label));
891 static void s_change_sec
893 static void s_change_section
897 static void s_float_cons
899 static void s_mips_globl
903 static void s_mipsset
905 static void s_abicalls
909 static void s_cpsetup
911 static void s_cplocal
913 static void s_cprestore
915 static void s_cpreturn
917 static void s_gpvalue
921 static void s_gpdword
927 static void md_obj_begin
929 static void md_obj_end
931 static long get_number
933 static void s_mips_ent
935 static void s_mips_end
937 static void s_mips_frame
939 static void s_mips_mask
941 static void s_mips_stab
943 static void s_mips_weakext
945 static void s_mips_file
947 static void s_mips_loc
949 static bfd_boolean pic_need_relax
950 PARAMS ((symbolS *, asection *));
951 static int mips16_extended_frag
952 PARAMS ((fragS *, asection *, long));
953 static int relaxed_branch_length (fragS *, asection *, int);
954 static int validate_mips_insn
955 PARAMS ((const struct mips_opcode *));
957 PARAMS ((FILE *, const char *, int *, int *));
959 static int mips_need_elf_addend_fixup
963 /* Table and functions used to map between CPU/ISA names, and
964 ISA levels, and CPU numbers. */
968 const char *name; /* CPU or ISA name. */
969 int is_isa; /* Is this an ISA? (If 0, a CPU.) */
970 int isa; /* ISA level. */
971 int cpu; /* CPU number (default CPU if ISA). */
974 static void mips_set_architecture
975 PARAMS ((const struct mips_cpu_info *));
976 static void mips_set_tune
977 PARAMS ((const struct mips_cpu_info *));
978 static bfd_boolean mips_strict_matching_cpu_name_p
979 PARAMS ((const char *, const char *));
980 static bfd_boolean mips_matching_cpu_name_p
981 PARAMS ((const char *, const char *));
982 static const struct mips_cpu_info *mips_parse_cpu
983 PARAMS ((const char *, const char *));
984 static const struct mips_cpu_info *mips_cpu_info_from_isa
989 The following pseudo-ops from the Kane and Heinrich MIPS book
990 should be defined here, but are currently unsupported: .alias,
991 .galive, .gjaldef, .gjrlive, .livereg, .noalias.
993 The following pseudo-ops from the Kane and Heinrich MIPS book are
994 specific to the type of debugging information being generated, and
995 should be defined by the object format: .aent, .begin, .bend,
996 .bgnb, .end, .endb, .ent, .fmask, .frame, .loc, .mask, .verstamp,
999 The following pseudo-ops from the Kane and Heinrich MIPS book are
1000 not MIPS CPU specific, but are also not specific to the object file
1001 format. This file is probably the best place to define them, but
1002 they are not currently supported: .asm0, .endr, .lab, .repeat,
1005 static const pseudo_typeS mips_pseudo_table[] =
1007 /* MIPS specific pseudo-ops. */
1008 {"option", s_option, 0},
1009 {"set", s_mipsset, 0},
1010 {"rdata", s_change_sec, 'r'},
1011 {"sdata", s_change_sec, 's'},
1012 {"livereg", s_ignore, 0},
1013 {"abicalls", s_abicalls, 0},
1014 {"cpload", s_cpload, 0},
1015 {"cpsetup", s_cpsetup, 0},
1016 {"cplocal", s_cplocal, 0},
1017 {"cprestore", s_cprestore, 0},
1018 {"cpreturn", s_cpreturn, 0},
1019 {"gpvalue", s_gpvalue, 0},
1020 {"gpword", s_gpword, 0},
1021 {"gpdword", s_gpdword, 0},
1022 {"cpadd", s_cpadd, 0},
1023 {"insn", s_insn, 0},
1025 /* Relatively generic pseudo-ops that happen to be used on MIPS
1027 {"asciiz", stringer, 1},
1028 {"bss", s_change_sec, 'b'},
1030 {"half", s_cons, 1},
1031 {"dword", s_cons, 3},
1032 {"weakext", s_mips_weakext, 0},
1034 /* These pseudo-ops are defined in read.c, but must be overridden
1035 here for one reason or another. */
1036 {"align", s_align, 0},
1037 {"byte", s_cons, 0},
1038 {"data", s_change_sec, 'd'},
1039 {"double", s_float_cons, 'd'},
1040 {"float", s_float_cons, 'f'},
1041 {"globl", s_mips_globl, 0},
1042 {"global", s_mips_globl, 0},
1043 {"hword", s_cons, 1},
1045 {"long", s_cons, 2},
1046 {"octa", s_cons, 4},
1047 {"quad", s_cons, 3},
1048 {"section", s_change_section, 0},
1049 {"short", s_cons, 1},
1050 {"single", s_float_cons, 'f'},
1051 {"stabn", s_mips_stab, 'n'},
1052 {"text", s_change_sec, 't'},
1053 {"word", s_cons, 2},
1055 { "extern", ecoff_directive_extern, 0},
1060 static const pseudo_typeS mips_nonecoff_pseudo_table[] =
1062 /* These pseudo-ops should be defined by the object file format.
1063 However, a.out doesn't support them, so we have versions here. */
1064 {"aent", s_mips_ent, 1},
1065 {"bgnb", s_ignore, 0},
1066 {"end", s_mips_end, 0},
1067 {"endb", s_ignore, 0},
1068 {"ent", s_mips_ent, 0},
1069 {"file", s_mips_file, 0},
1070 {"fmask", s_mips_mask, 'F'},
1071 {"frame", s_mips_frame, 0},
1072 {"loc", s_mips_loc, 0},
1073 {"mask", s_mips_mask, 'R'},
1074 {"verstamp", s_ignore, 0},
1078 extern void pop_insert PARAMS ((const pseudo_typeS *));
1083 pop_insert (mips_pseudo_table);
1084 if (! ECOFF_DEBUGGING)
1085 pop_insert (mips_nonecoff_pseudo_table);
1088 /* Symbols labelling the current insn. */
1090 struct insn_label_list
1092 struct insn_label_list *next;
1096 static struct insn_label_list *insn_labels;
1097 static struct insn_label_list *free_insn_labels;
1099 static void mips_clear_insn_labels PARAMS ((void));
1102 mips_clear_insn_labels ()
1104 register struct insn_label_list **pl;
1106 for (pl = &free_insn_labels; *pl != NULL; pl = &(*pl)->next)
1112 static char *expr_end;
1114 /* Expressions which appear in instructions. These are set by
1117 static expressionS imm_expr;
1118 static expressionS offset_expr;
1120 /* Relocs associated with imm_expr and offset_expr. */
1122 static bfd_reloc_code_real_type imm_reloc[3]
1123 = {BFD_RELOC_UNUSED, BFD_RELOC_UNUSED, BFD_RELOC_UNUSED};
1124 static bfd_reloc_code_real_type offset_reloc[3]
1125 = {BFD_RELOC_UNUSED, BFD_RELOC_UNUSED, BFD_RELOC_UNUSED};
1127 /* These are set by mips16_ip if an explicit extension is used. */
1129 static bfd_boolean mips16_small, mips16_ext;
1132 /* The pdr segment for per procedure frame/regmask info. Not used for
1135 static segT pdr_seg;
1138 /* The default target format to use. */
1141 mips_target_format ()
1143 switch (OUTPUT_FLAVOR)
1145 case bfd_target_aout_flavour:
1146 return target_big_endian ? "a.out-mips-big" : "a.out-mips-little";
1147 case bfd_target_ecoff_flavour:
1148 return target_big_endian ? "ecoff-bigmips" : ECOFF_LITTLE_FORMAT;
1149 case bfd_target_coff_flavour:
1151 case bfd_target_elf_flavour:
1153 /* This is traditional mips. */
1154 return (target_big_endian
1155 ? (HAVE_64BIT_OBJECTS
1156 ? "elf64-tradbigmips"
1158 ? "elf32-ntradbigmips" : "elf32-tradbigmips"))
1159 : (HAVE_64BIT_OBJECTS
1160 ? "elf64-tradlittlemips"
1162 ? "elf32-ntradlittlemips" : "elf32-tradlittlemips")));
1164 return (target_big_endian
1165 ? (HAVE_64BIT_OBJECTS
1168 ? "elf32-nbigmips" : "elf32-bigmips"))
1169 : (HAVE_64BIT_OBJECTS
1170 ? "elf64-littlemips"
1172 ? "elf32-nlittlemips" : "elf32-littlemips")));
1180 /* This function is called once, at assembler startup time. It should
1181 set up all the tables, etc. that the MD part of the assembler will need. */
1186 register const char *retval = NULL;
1190 if (! bfd_set_arch_mach (stdoutput, bfd_arch_mips, mips_arch))
1191 as_warn (_("Could not set architecture and machine"));
1193 op_hash = hash_new ();
1195 for (i = 0; i < NUMOPCODES;)
1197 const char *name = mips_opcodes[i].name;
1199 retval = hash_insert (op_hash, name, (PTR) &mips_opcodes[i]);
1202 fprintf (stderr, _("internal error: can't hash `%s': %s\n"),
1203 mips_opcodes[i].name, retval);
1204 /* Probably a memory allocation problem? Give up now. */
1205 as_fatal (_("Broken assembler. No assembly attempted."));
1209 if (mips_opcodes[i].pinfo != INSN_MACRO)
1211 if (!validate_mips_insn (&mips_opcodes[i]))
1216 while ((i < NUMOPCODES) && !strcmp (mips_opcodes[i].name, name));
1219 mips16_op_hash = hash_new ();
1222 while (i < bfd_mips16_num_opcodes)
1224 const char *name = mips16_opcodes[i].name;
1226 retval = hash_insert (mips16_op_hash, name, (PTR) &mips16_opcodes[i]);
1228 as_fatal (_("internal: can't hash `%s': %s"),
1229 mips16_opcodes[i].name, retval);
1232 if (mips16_opcodes[i].pinfo != INSN_MACRO
1233 && ((mips16_opcodes[i].match & mips16_opcodes[i].mask)
1234 != mips16_opcodes[i].match))
1236 fprintf (stderr, _("internal error: bad mips16 opcode: %s %s\n"),
1237 mips16_opcodes[i].name, mips16_opcodes[i].args);
1242 while (i < bfd_mips16_num_opcodes
1243 && strcmp (mips16_opcodes[i].name, name) == 0);
1247 as_fatal (_("Broken assembler. No assembly attempted."));
1249 /* We add all the general register names to the symbol table. This
1250 helps us detect invalid uses of them. */
1251 for (i = 0; i < 32; i++)
1255 sprintf (buf, "$%d", i);
1256 symbol_table_insert (symbol_new (buf, reg_section, i,
1257 &zero_address_frag));
1259 symbol_table_insert (symbol_new ("$ra", reg_section, RA,
1260 &zero_address_frag));
1261 symbol_table_insert (symbol_new ("$fp", reg_section, FP,
1262 &zero_address_frag));
1263 symbol_table_insert (symbol_new ("$sp", reg_section, SP,
1264 &zero_address_frag));
1265 symbol_table_insert (symbol_new ("$gp", reg_section, GP,
1266 &zero_address_frag));
1267 symbol_table_insert (symbol_new ("$at", reg_section, AT,
1268 &zero_address_frag));
1269 symbol_table_insert (symbol_new ("$kt0", reg_section, KT0,
1270 &zero_address_frag));
1271 symbol_table_insert (symbol_new ("$kt1", reg_section, KT1,
1272 &zero_address_frag));
1273 symbol_table_insert (symbol_new ("$zero", reg_section, ZERO,
1274 &zero_address_frag));
1275 symbol_table_insert (symbol_new ("$pc", reg_section, -1,
1276 &zero_address_frag));
1278 /* If we don't add these register names to the symbol table, they
1279 may end up being added as regular symbols by operand(), and then
1280 make it to the object file as undefined in case they're not
1281 regarded as local symbols. They're local in o32, since `$' is a
1282 local symbol prefix, but not in n32 or n64. */
1283 for (i = 0; i < 8; i++)
1287 sprintf (buf, "$fcc%i", i);
1288 symbol_table_insert (symbol_new (buf, reg_section, -1,
1289 &zero_address_frag));
1292 mips_no_prev_insn (FALSE);
1295 mips_cprmask[0] = 0;
1296 mips_cprmask[1] = 0;
1297 mips_cprmask[2] = 0;
1298 mips_cprmask[3] = 0;
1300 /* set the default alignment for the text section (2**2) */
1301 record_alignment (text_section, 2);
1303 if (USE_GLOBAL_POINTER_OPT)
1304 bfd_set_gp_size (stdoutput, g_switch_value);
1306 if (OUTPUT_FLAVOR == bfd_target_elf_flavour)
1308 /* On a native system, sections must be aligned to 16 byte
1309 boundaries. When configured for an embedded ELF target, we
1311 if (strcmp (TARGET_OS, "elf") != 0)
1313 (void) bfd_set_section_alignment (stdoutput, text_section, 4);
1314 (void) bfd_set_section_alignment (stdoutput, data_section, 4);
1315 (void) bfd_set_section_alignment (stdoutput, bss_section, 4);
1318 /* Create a .reginfo section for register masks and a .mdebug
1319 section for debugging information. */
1327 subseg = now_subseg;
1329 /* The ABI says this section should be loaded so that the
1330 running program can access it. However, we don't load it
1331 if we are configured for an embedded target */
1332 flags = SEC_READONLY | SEC_DATA;
1333 if (strcmp (TARGET_OS, "elf") != 0)
1334 flags |= SEC_ALLOC | SEC_LOAD;
1336 if (mips_abi != N64_ABI)
1338 sec = subseg_new (".reginfo", (subsegT) 0);
1340 bfd_set_section_flags (stdoutput, sec, flags);
1341 bfd_set_section_alignment (stdoutput, sec, HAVE_NEWABI ? 3 : 2);
1344 mips_regmask_frag = frag_more (sizeof (Elf32_External_RegInfo));
1349 /* The 64-bit ABI uses a .MIPS.options section rather than
1350 .reginfo section. */
1351 sec = subseg_new (".MIPS.options", (subsegT) 0);
1352 bfd_set_section_flags (stdoutput, sec, flags);
1353 bfd_set_section_alignment (stdoutput, sec, 3);
1356 /* Set up the option header. */
1358 Elf_Internal_Options opthdr;
1361 opthdr.kind = ODK_REGINFO;
1362 opthdr.size = (sizeof (Elf_External_Options)
1363 + sizeof (Elf64_External_RegInfo));
1366 f = frag_more (sizeof (Elf_External_Options));
1367 bfd_mips_elf_swap_options_out (stdoutput, &opthdr,
1368 (Elf_External_Options *) f);
1370 mips_regmask_frag = frag_more (sizeof (Elf64_External_RegInfo));
1375 if (ECOFF_DEBUGGING)
1377 sec = subseg_new (".mdebug", (subsegT) 0);
1378 (void) bfd_set_section_flags (stdoutput, sec,
1379 SEC_HAS_CONTENTS | SEC_READONLY);
1380 (void) bfd_set_section_alignment (stdoutput, sec, 2);
1383 else if (OUTPUT_FLAVOR == bfd_target_elf_flavour)
1385 pdr_seg = subseg_new (".pdr", (subsegT) 0);
1386 (void) bfd_set_section_flags (stdoutput, pdr_seg,
1387 SEC_READONLY | SEC_RELOC
1389 (void) bfd_set_section_alignment (stdoutput, pdr_seg, 2);
1393 subseg_set (seg, subseg);
1397 if (! ECOFF_DEBUGGING)
1404 if (! ECOFF_DEBUGGING)
1412 struct mips_cl_insn insn;
1413 bfd_reloc_code_real_type unused_reloc[3]
1414 = {BFD_RELOC_UNUSED, BFD_RELOC_UNUSED, BFD_RELOC_UNUSED};
1416 imm_expr.X_op = O_absent;
1417 offset_expr.X_op = O_absent;
1418 imm_reloc[0] = BFD_RELOC_UNUSED;
1419 imm_reloc[1] = BFD_RELOC_UNUSED;
1420 imm_reloc[2] = BFD_RELOC_UNUSED;
1421 offset_reloc[0] = BFD_RELOC_UNUSED;
1422 offset_reloc[1] = BFD_RELOC_UNUSED;
1423 offset_reloc[2] = BFD_RELOC_UNUSED;
1425 if (mips_opts.mips16)
1426 mips16_ip (str, &insn);
1429 mips_ip (str, &insn);
1430 DBG ((_("returned from mips_ip(%s) insn_opcode = 0x%x\n"),
1431 str, insn.insn_opcode));
1436 as_bad ("%s `%s'", insn_error, str);
1440 if (insn.insn_mo->pinfo == INSN_MACRO)
1442 if (mips_opts.mips16)
1443 mips16_macro (&insn);
1449 if (imm_expr.X_op != O_absent)
1450 append_insn (NULL, &insn, &imm_expr, imm_reloc);
1451 else if (offset_expr.X_op != O_absent)
1452 append_insn (NULL, &insn, &offset_expr, offset_reloc);
1454 append_insn (NULL, &insn, NULL, unused_reloc);
1458 /* Return true if the given relocation might need a matching %lo().
1459 Note that R_MIPS_GOT16 relocations only need a matching %lo() when
1460 applied to local symbols. */
1462 static inline bfd_boolean
1463 reloc_needs_lo_p (reloc)
1464 bfd_reloc_code_real_type reloc;
1466 return (reloc == BFD_RELOC_HI16_S
1467 || reloc == BFD_RELOC_MIPS_GOT16);
1470 /* Return true if the given fixup is followed by a matching R_MIPS_LO16
1473 static inline bfd_boolean
1474 fixup_has_matching_lo_p (fixp)
1477 return (fixp->fx_next != NULL
1478 && fixp->fx_next->fx_r_type == BFD_RELOC_LO16
1479 && fixp->fx_addsy == fixp->fx_next->fx_addsy
1480 && fixp->fx_offset == fixp->fx_next->fx_offset);
1483 /* See whether instruction IP reads register REG. CLASS is the type
1487 insn_uses_reg (ip, reg, class)
1488 struct mips_cl_insn *ip;
1490 enum mips_regclass class;
1492 if (class == MIPS16_REG)
1494 assert (mips_opts.mips16);
1495 reg = mips16_to_32_reg_map[reg];
1496 class = MIPS_GR_REG;
1499 /* Don't report on general register ZERO, since it never changes. */
1500 if (class == MIPS_GR_REG && reg == ZERO)
1503 if (class == MIPS_FP_REG)
1505 assert (! mips_opts.mips16);
1506 /* If we are called with either $f0 or $f1, we must check $f0.
1507 This is not optimal, because it will introduce an unnecessary
1508 NOP between "lwc1 $f0" and "swc1 $f1". To fix this we would
1509 need to distinguish reading both $f0 and $f1 or just one of
1510 them. Note that we don't have to check the other way,
1511 because there is no instruction that sets both $f0 and $f1
1512 and requires a delay. */
1513 if ((ip->insn_mo->pinfo & INSN_READ_FPR_S)
1514 && ((((ip->insn_opcode >> OP_SH_FS) & OP_MASK_FS) &~(unsigned)1)
1515 == (reg &~ (unsigned) 1)))
1517 if ((ip->insn_mo->pinfo & INSN_READ_FPR_T)
1518 && ((((ip->insn_opcode >> OP_SH_FT) & OP_MASK_FT) &~(unsigned)1)
1519 == (reg &~ (unsigned) 1)))
1522 else if (! mips_opts.mips16)
1524 if ((ip->insn_mo->pinfo & INSN_READ_GPR_S)
1525 && ((ip->insn_opcode >> OP_SH_RS) & OP_MASK_RS) == reg)
1527 if ((ip->insn_mo->pinfo & INSN_READ_GPR_T)
1528 && ((ip->insn_opcode >> OP_SH_RT) & OP_MASK_RT) == reg)
1533 if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_X)
1534 && (mips16_to_32_reg_map[((ip->insn_opcode >> MIPS16OP_SH_RX)
1535 & MIPS16OP_MASK_RX)]
1538 if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_Y)
1539 && (mips16_to_32_reg_map[((ip->insn_opcode >> MIPS16OP_SH_RY)
1540 & MIPS16OP_MASK_RY)]
1543 if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_Z)
1544 && (mips16_to_32_reg_map[((ip->insn_opcode >> MIPS16OP_SH_MOVE32Z)
1545 & MIPS16OP_MASK_MOVE32Z)]
1548 if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_T) && reg == TREG)
1550 if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_SP) && reg == SP)
1552 if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_31) && reg == RA)
1554 if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_GPR_X)
1555 && ((ip->insn_opcode >> MIPS16OP_SH_REGR32)
1556 & MIPS16OP_MASK_REGR32) == reg)
1563 /* This function returns true if modifying a register requires a
1567 reg_needs_delay (reg)
1570 unsigned long prev_pinfo;
1572 prev_pinfo = prev_insn.insn_mo->pinfo;
1573 if (! mips_opts.noreorder
1574 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
1575 && ((prev_pinfo & INSN_LOAD_COPROC_DELAY)
1576 || (! gpr_interlocks
1577 && (prev_pinfo & INSN_LOAD_MEMORY_DELAY))))
1579 /* A load from a coprocessor or from memory. All load
1580 delays delay the use of general register rt for one
1581 instruction on the r3000. The r6000 and r4000 use
1583 /* Itbl support may require additional care here. */
1584 know (prev_pinfo & INSN_WRITE_GPR_T);
1585 if (reg == ((prev_insn.insn_opcode >> OP_SH_RT) & OP_MASK_RT))
1592 /* Mark instruction labels in mips16 mode. This permits the linker to
1593 handle them specially, such as generating jalx instructions when
1594 needed. We also make them odd for the duration of the assembly, in
1595 order to generate the right sort of code. We will make them even
1596 in the adjust_symtab routine, while leaving them marked. This is
1597 convenient for the debugger and the disassembler. The linker knows
1598 to make them odd again. */
1601 mips16_mark_labels ()
1603 if (mips_opts.mips16)
1605 struct insn_label_list *l;
1608 for (l = insn_labels; l != NULL; l = l->next)
1611 if (OUTPUT_FLAVOR == bfd_target_elf_flavour)
1612 S_SET_OTHER (l->label, STO_MIPS16);
1614 val = S_GET_VALUE (l->label);
1616 S_SET_VALUE (l->label, val + 1);
1621 /* Output an instruction. PLACE is where to put the instruction; if
1622 it is NULL, this uses frag_more to get room. IP is the instruction
1623 information. ADDRESS_EXPR is an operand of the instruction to be
1624 used with RELOC_TYPE. */
1627 append_insn (place, ip, address_expr, reloc_type)
1629 struct mips_cl_insn *ip;
1630 expressionS *address_expr;
1631 bfd_reloc_code_real_type *reloc_type;
1633 register unsigned long prev_pinfo, pinfo;
1637 bfd_boolean force_new_frag = FALSE;
1639 /* Mark instruction labels in mips16 mode. */
1640 mips16_mark_labels ();
1642 prev_pinfo = prev_insn.insn_mo->pinfo;
1643 pinfo = ip->insn_mo->pinfo;
1645 if (place == NULL && (! mips_opts.noreorder || prev_nop_frag != NULL))
1649 /* If the previous insn required any delay slots, see if we need
1650 to insert a NOP or two. There are eight kinds of possible
1651 hazards, of which an instruction can have at most one type.
1652 (1) a load from memory delay
1653 (2) a load from a coprocessor delay
1654 (3) an unconditional branch delay
1655 (4) a conditional branch delay
1656 (5) a move to coprocessor register delay
1657 (6) a load coprocessor register from memory delay
1658 (7) a coprocessor condition code delay
1659 (8) a HI/LO special register delay
1661 There are a lot of optimizations we could do that we don't.
1662 In particular, we do not, in general, reorder instructions.
1663 If you use gcc with optimization, it will reorder
1664 instructions and generally do much more optimization then we
1665 do here; repeating all that work in the assembler would only
1666 benefit hand written assembly code, and does not seem worth
1669 /* This is how a NOP is emitted. */
1670 #define emit_nop() \
1672 ? md_number_to_chars (frag_more (2), 0x6500, 2) \
1673 : md_number_to_chars (frag_more (4), 0, 4))
1675 /* The previous insn might require a delay slot, depending upon
1676 the contents of the current insn. */
1677 if (! mips_opts.mips16
1678 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
1679 && (((prev_pinfo & INSN_LOAD_COPROC_DELAY)
1680 && ! cop_interlocks)
1681 || (! gpr_interlocks
1682 && (prev_pinfo & INSN_LOAD_MEMORY_DELAY))))
1684 /* A load from a coprocessor or from memory. All load
1685 delays delay the use of general register rt for one
1686 instruction on the r3000. The r6000 and r4000 use
1688 /* Itbl support may require additional care here. */
1689 know (prev_pinfo & INSN_WRITE_GPR_T);
1690 if (mips_optimize == 0
1691 || insn_uses_reg (ip,
1692 ((prev_insn.insn_opcode >> OP_SH_RT)
1697 else if (! mips_opts.mips16
1698 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
1699 && (((prev_pinfo & INSN_COPROC_MOVE_DELAY)
1700 && ! cop_interlocks)
1701 || (mips_opts.isa == ISA_MIPS1
1702 && (prev_pinfo & INSN_COPROC_MEMORY_DELAY))))
1704 /* A generic coprocessor delay. The previous instruction
1705 modified a coprocessor general or control register. If
1706 it modified a control register, we need to avoid any
1707 coprocessor instruction (this is probably not always
1708 required, but it sometimes is). If it modified a general
1709 register, we avoid using that register.
1711 On the r6000 and r4000 loading a coprocessor register
1712 from memory is interlocked, and does not require a delay.
1714 This case is not handled very well. There is no special
1715 knowledge of CP0 handling, and the coprocessors other
1716 than the floating point unit are not distinguished at
1718 /* Itbl support may require additional care here. FIXME!
1719 Need to modify this to include knowledge about
1720 user specified delays! */
1721 if (prev_pinfo & INSN_WRITE_FPR_T)
1723 if (mips_optimize == 0
1724 || insn_uses_reg (ip,
1725 ((prev_insn.insn_opcode >> OP_SH_FT)
1730 else if (prev_pinfo & INSN_WRITE_FPR_S)
1732 if (mips_optimize == 0
1733 || insn_uses_reg (ip,
1734 ((prev_insn.insn_opcode >> OP_SH_FS)
1741 /* We don't know exactly what the previous instruction
1742 does. If the current instruction uses a coprocessor
1743 register, we must insert a NOP. If previous
1744 instruction may set the condition codes, and the
1745 current instruction uses them, we must insert two
1747 /* Itbl support may require additional care here. */
1748 if (mips_optimize == 0
1749 || ((prev_pinfo & INSN_WRITE_COND_CODE)
1750 && (pinfo & INSN_READ_COND_CODE)))
1752 else if (pinfo & INSN_COP)
1756 else if (! mips_opts.mips16
1757 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
1758 && (prev_pinfo & INSN_WRITE_COND_CODE)
1759 && ! cop_interlocks)
1761 /* The previous instruction sets the coprocessor condition
1762 codes, but does not require a general coprocessor delay
1763 (this means it is a floating point comparison
1764 instruction). If this instruction uses the condition
1765 codes, we need to insert a single NOP. */
1766 /* Itbl support may require additional care here. */
1767 if (mips_optimize == 0
1768 || (pinfo & INSN_READ_COND_CODE))
1772 /* If we're fixing up mfhi/mflo for the r7000 and the
1773 previous insn was an mfhi/mflo and the current insn
1774 reads the register that the mfhi/mflo wrote to, then
1777 else if (mips_7000_hilo_fix
1778 && MF_HILO_INSN (prev_pinfo)
1779 && insn_uses_reg (ip, ((prev_insn.insn_opcode >> OP_SH_RD)
1786 /* If we're fixing up mfhi/mflo for the r7000 and the
1787 2nd previous insn was an mfhi/mflo and the current insn
1788 reads the register that the mfhi/mflo wrote to, then
1791 else if (mips_7000_hilo_fix
1792 && MF_HILO_INSN (prev_prev_insn.insn_opcode)
1793 && insn_uses_reg (ip, ((prev_prev_insn.insn_opcode >> OP_SH_RD)
1801 else if (prev_pinfo & INSN_READ_LO)
1803 /* The previous instruction reads the LO register; if the
1804 current instruction writes to the LO register, we must
1805 insert two NOPS. Some newer processors have interlocks.
1806 Also the tx39's multiply instructions can be exectuted
1807 immediatly after a read from HI/LO (without the delay),
1808 though the tx39's divide insns still do require the
1810 if (! (hilo_interlocks
1811 || (mips_tune == CPU_R3900 && (pinfo & INSN_MULT)))
1812 && (mips_optimize == 0
1813 || (pinfo & INSN_WRITE_LO)))
1815 /* Most mips16 branch insns don't have a delay slot.
1816 If a read from LO is immediately followed by a branch
1817 to a write to LO we have a read followed by a write
1818 less than 2 insns away. We assume the target of
1819 a branch might be a write to LO, and insert a nop
1820 between a read and an immediately following branch. */
1821 else if (mips_opts.mips16
1822 && (mips_optimize == 0
1823 || (pinfo & MIPS16_INSN_BRANCH)))
1826 else if (prev_insn.insn_mo->pinfo & INSN_READ_HI)
1828 /* The previous instruction reads the HI register; if the
1829 current instruction writes to the HI register, we must
1830 insert a NOP. Some newer processors have interlocks.
1831 Also the note tx39's multiply above. */
1832 if (! (hilo_interlocks
1833 || (mips_tune == CPU_R3900 && (pinfo & INSN_MULT)))
1834 && (mips_optimize == 0
1835 || (pinfo & INSN_WRITE_HI)))
1837 /* Most mips16 branch insns don't have a delay slot.
1838 If a read from HI is immediately followed by a branch
1839 to a write to HI we have a read followed by a write
1840 less than 2 insns away. We assume the target of
1841 a branch might be a write to HI, and insert a nop
1842 between a read and an immediately following branch. */
1843 else if (mips_opts.mips16
1844 && (mips_optimize == 0
1845 || (pinfo & MIPS16_INSN_BRANCH)))
1849 /* If the previous instruction was in a noreorder section, then
1850 we don't want to insert the nop after all. */
1851 /* Itbl support may require additional care here. */
1852 if (prev_insn_unreordered)
1855 /* There are two cases which require two intervening
1856 instructions: 1) setting the condition codes using a move to
1857 coprocessor instruction which requires a general coprocessor
1858 delay and then reading the condition codes 2) reading the HI
1859 or LO register and then writing to it (except on processors
1860 which have interlocks). If we are not already emitting a NOP
1861 instruction, we must check for these cases compared to the
1862 instruction previous to the previous instruction. */
1863 if ((! mips_opts.mips16
1864 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
1865 && (prev_prev_insn.insn_mo->pinfo & INSN_COPROC_MOVE_DELAY)
1866 && (prev_prev_insn.insn_mo->pinfo & INSN_WRITE_COND_CODE)
1867 && (pinfo & INSN_READ_COND_CODE)
1868 && ! cop_interlocks)
1869 || ((prev_prev_insn.insn_mo->pinfo & INSN_READ_LO)
1870 && (pinfo & INSN_WRITE_LO)
1871 && ! (hilo_interlocks
1872 || (mips_tune == CPU_R3900 && (pinfo & INSN_MULT))))
1873 || ((prev_prev_insn.insn_mo->pinfo & INSN_READ_HI)
1874 && (pinfo & INSN_WRITE_HI)
1875 && ! (hilo_interlocks
1876 || (mips_tune == CPU_R3900 && (pinfo & INSN_MULT)))))
1881 if (prev_prev_insn_unreordered)
1884 if (prev_prev_nop && nops == 0)
1887 if (mips_fix_4122_bugs && prev_insn.insn_mo->name)
1889 /* We're out of bits in pinfo, so we must resort to string
1890 ops here. Shortcuts are selected based on opcodes being
1891 limited to the VR4122 instruction set. */
1893 const char *pn = prev_insn.insn_mo->name;
1894 const char *tn = ip->insn_mo->name;
1895 if (strncmp(pn, "macc", 4) == 0
1896 || strncmp(pn, "dmacc", 5) == 0)
1898 /* Errata 21 - [D]DIV[U] after [D]MACC */
1899 if (strstr (tn, "div"))
1904 /* Errata 23 - Continuous DMULT[U]/DMACC instructions */
1905 if (pn[0] == 'd' /* dmacc */
1906 && (strncmp(tn, "dmult", 5) == 0
1907 || strncmp(tn, "dmacc", 5) == 0))
1912 /* Errata 24 - MT{LO,HI} after [D]MACC */
1913 if (strcmp (tn, "mtlo") == 0
1914 || strcmp (tn, "mthi") == 0)
1920 else if (strncmp(pn, "dmult", 5) == 0
1921 && (strncmp(tn, "dmult", 5) == 0
1922 || strncmp(tn, "dmacc", 5) == 0))
1924 /* Here is the rest of errata 23. */
1927 if (nops < min_nops)
1931 /* If we are being given a nop instruction, don't bother with
1932 one of the nops we would otherwise output. This will only
1933 happen when a nop instruction is used with mips_optimize set
1936 && ! mips_opts.noreorder
1937 && ip->insn_opcode == (unsigned) (mips_opts.mips16 ? 0x6500 : 0))
1940 /* Now emit the right number of NOP instructions. */
1941 if (nops > 0 && ! mips_opts.noreorder)
1944 unsigned long old_frag_offset;
1946 struct insn_label_list *l;
1948 old_frag = frag_now;
1949 old_frag_offset = frag_now_fix ();
1951 for (i = 0; i < nops; i++)
1956 listing_prev_line ();
1957 /* We may be at the start of a variant frag. In case we
1958 are, make sure there is enough space for the frag
1959 after the frags created by listing_prev_line. The
1960 argument to frag_grow here must be at least as large
1961 as the argument to all other calls to frag_grow in
1962 this file. We don't have to worry about being in the
1963 middle of a variant frag, because the variants insert
1964 all needed nop instructions themselves. */
1968 for (l = insn_labels; l != NULL; l = l->next)
1972 assert (S_GET_SEGMENT (l->label) == now_seg);
1973 symbol_set_frag (l->label, frag_now);
1974 val = (valueT) frag_now_fix ();
1975 /* mips16 text labels are stored as odd. */
1976 if (mips_opts.mips16)
1978 S_SET_VALUE (l->label, val);
1981 #ifndef NO_ECOFF_DEBUGGING
1982 if (ECOFF_DEBUGGING)
1983 ecoff_fix_loc (old_frag, old_frag_offset);
1986 else if (prev_nop_frag != NULL)
1988 /* We have a frag holding nops we may be able to remove. If
1989 we don't need any nops, we can decrease the size of
1990 prev_nop_frag by the size of one instruction. If we do
1991 need some nops, we count them in prev_nops_required. */
1992 if (prev_nop_frag_since == 0)
1996 prev_nop_frag->fr_fix -= mips_opts.mips16 ? 2 : 4;
1997 --prev_nop_frag_holds;
2000 prev_nop_frag_required += nops;
2004 if (prev_prev_nop == 0)
2006 prev_nop_frag->fr_fix -= mips_opts.mips16 ? 2 : 4;
2007 --prev_nop_frag_holds;
2010 ++prev_nop_frag_required;
2013 if (prev_nop_frag_holds <= prev_nop_frag_required)
2014 prev_nop_frag = NULL;
2016 ++prev_nop_frag_since;
2018 /* Sanity check: by the time we reach the second instruction
2019 after prev_nop_frag, we should have used up all the nops
2020 one way or another. */
2021 assert (prev_nop_frag_since <= 1 || prev_nop_frag == NULL);
2027 && *reloc_type == BFD_RELOC_16_PCREL_S2
2028 && (pinfo & INSN_UNCOND_BRANCH_DELAY || pinfo & INSN_COND_BRANCH_DELAY
2029 || pinfo & INSN_COND_BRANCH_LIKELY)
2030 && mips_relax_branch
2031 /* Don't try branch relaxation within .set nomacro, or within
2032 .set noat if we use $at for PIC computations. If it turns
2033 out that the branch was out-of-range, we'll get an error. */
2034 && !mips_opts.warn_about_macros
2035 && !(mips_opts.noat && mips_pic != NO_PIC)
2036 && !mips_opts.mips16)
2038 f = frag_var (rs_machine_dependent,
2039 relaxed_branch_length
2041 (pinfo & INSN_UNCOND_BRANCH_DELAY) ? -1
2042 : (pinfo & INSN_COND_BRANCH_LIKELY) ? 1 : 0), 4,
2044 (pinfo & INSN_UNCOND_BRANCH_DELAY,
2045 pinfo & INSN_COND_BRANCH_LIKELY,
2046 pinfo & INSN_WRITE_GPR_31,
2048 address_expr->X_add_symbol,
2049 address_expr->X_add_number,
2051 *reloc_type = BFD_RELOC_UNUSED;
2053 else if (*reloc_type > BFD_RELOC_UNUSED)
2055 /* We need to set up a variant frag. */
2056 assert (mips_opts.mips16 && address_expr != NULL);
2057 f = frag_var (rs_machine_dependent, 4, 0,
2058 RELAX_MIPS16_ENCODE (*reloc_type - BFD_RELOC_UNUSED,
2059 mips16_small, mips16_ext,
2061 & INSN_UNCOND_BRANCH_DELAY),
2062 (*prev_insn_reloc_type
2063 == BFD_RELOC_MIPS16_JMP)),
2064 make_expr_symbol (address_expr), 0, NULL);
2066 else if (place != NULL)
2068 else if (mips_opts.mips16
2070 && *reloc_type != BFD_RELOC_MIPS16_JMP)
2072 /* Make sure there is enough room to swap this instruction with
2073 a following jump instruction. */
2079 if (mips_opts.mips16
2080 && mips_opts.noreorder
2081 && (prev_pinfo & INSN_UNCOND_BRANCH_DELAY) != 0)
2082 as_warn (_("extended instruction in delay slot"));
2087 fixp[0] = fixp[1] = fixp[2] = NULL;
2088 if (address_expr != NULL && *reloc_type < BFD_RELOC_UNUSED)
2090 if (address_expr->X_op == O_constant)
2094 switch (*reloc_type)
2097 ip->insn_opcode |= address_expr->X_add_number;
2100 case BFD_RELOC_MIPS_HIGHEST:
2101 tmp = (address_expr->X_add_number + 0x800080008000) >> 16;
2103 ip->insn_opcode |= (tmp >> 16) & 0xffff;
2106 case BFD_RELOC_MIPS_HIGHER:
2107 tmp = (address_expr->X_add_number + 0x80008000) >> 16;
2108 ip->insn_opcode |= (tmp >> 16) & 0xffff;
2111 case BFD_RELOC_HI16_S:
2112 ip->insn_opcode |= ((address_expr->X_add_number + 0x8000)
2116 case BFD_RELOC_HI16:
2117 ip->insn_opcode |= (address_expr->X_add_number >> 16) & 0xffff;
2120 case BFD_RELOC_LO16:
2121 case BFD_RELOC_MIPS_GOT_DISP:
2122 ip->insn_opcode |= address_expr->X_add_number & 0xffff;
2125 case BFD_RELOC_MIPS_JMP:
2126 if ((address_expr->X_add_number & 3) != 0)
2127 as_bad (_("jump to misaligned address (0x%lx)"),
2128 (unsigned long) address_expr->X_add_number);
2129 if (address_expr->X_add_number & ~0xfffffff)
2130 as_bad (_("jump address range overflow (0x%lx)"),
2131 (unsigned long) address_expr->X_add_number);
2132 ip->insn_opcode |= (address_expr->X_add_number >> 2) & 0x3ffffff;
2135 case BFD_RELOC_MIPS16_JMP:
2136 if ((address_expr->X_add_number & 3) != 0)
2137 as_bad (_("jump to misaligned address (0x%lx)"),
2138 (unsigned long) address_expr->X_add_number);
2139 if (address_expr->X_add_number & ~0xfffffff)
2140 as_bad (_("jump address range overflow (0x%lx)"),
2141 (unsigned long) address_expr->X_add_number);
2143 (((address_expr->X_add_number & 0x7c0000) << 3)
2144 | ((address_expr->X_add_number & 0xf800000) >> 7)
2145 | ((address_expr->X_add_number & 0x3fffc) >> 2));
2148 case BFD_RELOC_16_PCREL_S2:
2157 reloc_howto_type *howto;
2160 /* Don't generate a reloc if we are writing into a variant frag. */
2163 howto = bfd_reloc_type_lookup (stdoutput, reloc_type[0]);
2164 fixp[0] = fix_new_exp (frag_now, f - frag_now->fr_literal,
2165 bfd_get_reloc_size(howto),
2167 reloc_type[0] == BFD_RELOC_16_PCREL_S2,
2170 /* These relocations can have an addend that won't fit in
2171 4 octets for 64bit assembly. */
2173 && ! howto->partial_inplace
2174 && (reloc_type[0] == BFD_RELOC_16
2175 || reloc_type[0] == BFD_RELOC_32
2176 || reloc_type[0] == BFD_RELOC_MIPS_JMP
2177 || reloc_type[0] == BFD_RELOC_HI16_S
2178 || reloc_type[0] == BFD_RELOC_LO16
2179 || reloc_type[0] == BFD_RELOC_GPREL16
2180 || reloc_type[0] == BFD_RELOC_MIPS_LITERAL
2181 || reloc_type[0] == BFD_RELOC_GPREL32
2182 || reloc_type[0] == BFD_RELOC_64
2183 || reloc_type[0] == BFD_RELOC_CTOR
2184 || reloc_type[0] == BFD_RELOC_MIPS_SUB
2185 || reloc_type[0] == BFD_RELOC_MIPS_HIGHEST
2186 || reloc_type[0] == BFD_RELOC_MIPS_HIGHER
2187 || reloc_type[0] == BFD_RELOC_MIPS_SCN_DISP
2188 || reloc_type[0] == BFD_RELOC_MIPS_REL16
2189 || reloc_type[0] == BFD_RELOC_MIPS_RELGOT))
2190 fixp[0]->fx_no_overflow = 1;
2192 if (reloc_needs_lo_p (*reloc_type))
2194 struct mips_hi_fixup *hi_fixup;
2196 /* Reuse the last entry if it already has a matching %lo. */
2197 hi_fixup = mips_hi_fixup_list;
2199 || !fixup_has_matching_lo_p (hi_fixup->fixp))
2201 hi_fixup = ((struct mips_hi_fixup *)
2202 xmalloc (sizeof (struct mips_hi_fixup)));
2203 hi_fixup->next = mips_hi_fixup_list;
2204 mips_hi_fixup_list = hi_fixup;
2206 hi_fixup->fixp = fixp[0];
2207 hi_fixup->seg = now_seg;
2210 if (reloc_type[1] != BFD_RELOC_UNUSED)
2212 /* FIXME: This symbol can be one of
2213 RSS_UNDEF, RSS_GP, RSS_GP0, RSS_LOC. */
2214 address_expr->X_op = O_absent;
2215 address_expr->X_add_symbol = 0;
2216 address_expr->X_add_number = 0;
2218 howto = bfd_reloc_type_lookup (stdoutput, reloc_type[1]);
2219 fixp[1] = fix_new_exp (frag_now, f - frag_now->fr_literal,
2220 bfd_get_reloc_size(howto),
2221 address_expr, FALSE, reloc_type[1]);
2223 /* These relocations can have an addend that won't fit in
2224 4 octets for 64bit assembly. */
2226 && ! howto->partial_inplace
2227 && (reloc_type[1] == BFD_RELOC_16
2228 || reloc_type[1] == BFD_RELOC_32
2229 || reloc_type[1] == BFD_RELOC_MIPS_JMP
2230 || reloc_type[1] == BFD_RELOC_HI16_S
2231 || reloc_type[1] == BFD_RELOC_LO16
2232 || reloc_type[1] == BFD_RELOC_GPREL16
2233 || reloc_type[1] == BFD_RELOC_MIPS_LITERAL
2234 || reloc_type[1] == BFD_RELOC_GPREL32
2235 || reloc_type[1] == BFD_RELOC_64
2236 || reloc_type[1] == BFD_RELOC_CTOR
2237 || reloc_type[1] == BFD_RELOC_MIPS_SUB
2238 || reloc_type[1] == BFD_RELOC_MIPS_HIGHEST
2239 || reloc_type[1] == BFD_RELOC_MIPS_HIGHER
2240 || reloc_type[1] == BFD_RELOC_MIPS_SCN_DISP
2241 || reloc_type[1] == BFD_RELOC_MIPS_REL16
2242 || reloc_type[1] == BFD_RELOC_MIPS_RELGOT))
2243 fixp[1]->fx_no_overflow = 1;
2245 if (reloc_type[2] != BFD_RELOC_UNUSED)
2247 address_expr->X_op = O_absent;
2248 address_expr->X_add_symbol = 0;
2249 address_expr->X_add_number = 0;
2251 howto = bfd_reloc_type_lookup (stdoutput, reloc_type[2]);
2252 fixp[2] = fix_new_exp (frag_now,
2253 f - frag_now->fr_literal,
2254 bfd_get_reloc_size(howto),
2255 address_expr, FALSE,
2258 /* These relocations can have an addend that won't fit in
2259 4 octets for 64bit assembly. */
2261 && ! howto->partial_inplace
2262 && (reloc_type[2] == BFD_RELOC_16
2263 || reloc_type[2] == BFD_RELOC_32
2264 || reloc_type[2] == BFD_RELOC_MIPS_JMP
2265 || reloc_type[2] == BFD_RELOC_HI16_S
2266 || reloc_type[2] == BFD_RELOC_LO16
2267 || reloc_type[2] == BFD_RELOC_GPREL16
2268 || reloc_type[2] == BFD_RELOC_MIPS_LITERAL
2269 || reloc_type[2] == BFD_RELOC_GPREL32
2270 || reloc_type[2] == BFD_RELOC_64
2271 || reloc_type[2] == BFD_RELOC_CTOR
2272 || reloc_type[2] == BFD_RELOC_MIPS_SUB
2273 || reloc_type[2] == BFD_RELOC_MIPS_HIGHEST
2274 || reloc_type[2] == BFD_RELOC_MIPS_HIGHER
2275 || reloc_type[2] == BFD_RELOC_MIPS_SCN_DISP
2276 || reloc_type[2] == BFD_RELOC_MIPS_REL16
2277 || reloc_type[2] == BFD_RELOC_MIPS_RELGOT))
2278 fixp[2]->fx_no_overflow = 1;
2285 if (! mips_opts.mips16)
2287 md_number_to_chars (f, ip->insn_opcode, 4);
2289 dwarf2_emit_insn (4);
2292 else if (*reloc_type == BFD_RELOC_MIPS16_JMP)
2294 md_number_to_chars (f, ip->insn_opcode >> 16, 2);
2295 md_number_to_chars (f + 2, ip->insn_opcode & 0xffff, 2);
2297 dwarf2_emit_insn (4);
2304 md_number_to_chars (f, 0xf000 | ip->extend, 2);
2307 md_number_to_chars (f, ip->insn_opcode, 2);
2309 dwarf2_emit_insn (ip->use_extend ? 4 : 2);
2313 /* Update the register mask information. */
2314 if (! mips_opts.mips16)
2316 if (pinfo & INSN_WRITE_GPR_D)
2317 mips_gprmask |= 1 << ((ip->insn_opcode >> OP_SH_RD) & OP_MASK_RD);
2318 if ((pinfo & (INSN_WRITE_GPR_T | INSN_READ_GPR_T)) != 0)
2319 mips_gprmask |= 1 << ((ip->insn_opcode >> OP_SH_RT) & OP_MASK_RT);
2320 if (pinfo & INSN_READ_GPR_S)
2321 mips_gprmask |= 1 << ((ip->insn_opcode >> OP_SH_RS) & OP_MASK_RS);
2322 if (pinfo & INSN_WRITE_GPR_31)
2323 mips_gprmask |= 1 << RA;
2324 if (pinfo & INSN_WRITE_FPR_D)
2325 mips_cprmask[1] |= 1 << ((ip->insn_opcode >> OP_SH_FD) & OP_MASK_FD);
2326 if ((pinfo & (INSN_WRITE_FPR_S | INSN_READ_FPR_S)) != 0)
2327 mips_cprmask[1] |= 1 << ((ip->insn_opcode >> OP_SH_FS) & OP_MASK_FS);
2328 if ((pinfo & (INSN_WRITE_FPR_T | INSN_READ_FPR_T)) != 0)
2329 mips_cprmask[1] |= 1 << ((ip->insn_opcode >> OP_SH_FT) & OP_MASK_FT);
2330 if ((pinfo & INSN_READ_FPR_R) != 0)
2331 mips_cprmask[1] |= 1 << ((ip->insn_opcode >> OP_SH_FR) & OP_MASK_FR);
2332 if (pinfo & INSN_COP)
2334 /* We don't keep enough information to sort these cases out.
2335 The itbl support does keep this information however, although
2336 we currently don't support itbl fprmats as part of the cop
2337 instruction. May want to add this support in the future. */
2339 /* Never set the bit for $0, which is always zero. */
2340 mips_gprmask &= ~1 << 0;
2344 if (pinfo & (MIPS16_INSN_WRITE_X | MIPS16_INSN_READ_X))
2345 mips_gprmask |= 1 << ((ip->insn_opcode >> MIPS16OP_SH_RX)
2346 & MIPS16OP_MASK_RX);
2347 if (pinfo & (MIPS16_INSN_WRITE_Y | MIPS16_INSN_READ_Y))
2348 mips_gprmask |= 1 << ((ip->insn_opcode >> MIPS16OP_SH_RY)
2349 & MIPS16OP_MASK_RY);
2350 if (pinfo & MIPS16_INSN_WRITE_Z)
2351 mips_gprmask |= 1 << ((ip->insn_opcode >> MIPS16OP_SH_RZ)
2352 & MIPS16OP_MASK_RZ);
2353 if (pinfo & (MIPS16_INSN_WRITE_T | MIPS16_INSN_READ_T))
2354 mips_gprmask |= 1 << TREG;
2355 if (pinfo & (MIPS16_INSN_WRITE_SP | MIPS16_INSN_READ_SP))
2356 mips_gprmask |= 1 << SP;
2357 if (pinfo & (MIPS16_INSN_WRITE_31 | MIPS16_INSN_READ_31))
2358 mips_gprmask |= 1 << RA;
2359 if (pinfo & MIPS16_INSN_WRITE_GPR_Y)
2360 mips_gprmask |= 1 << MIPS16OP_EXTRACT_REG32R (ip->insn_opcode);
2361 if (pinfo & MIPS16_INSN_READ_Z)
2362 mips_gprmask |= 1 << ((ip->insn_opcode >> MIPS16OP_SH_MOVE32Z)
2363 & MIPS16OP_MASK_MOVE32Z);
2364 if (pinfo & MIPS16_INSN_READ_GPR_X)
2365 mips_gprmask |= 1 << ((ip->insn_opcode >> MIPS16OP_SH_REGR32)
2366 & MIPS16OP_MASK_REGR32);
2369 if (place == NULL && ! mips_opts.noreorder)
2371 /* Filling the branch delay slot is more complex. We try to
2372 switch the branch with the previous instruction, which we can
2373 do if the previous instruction does not set up a condition
2374 that the branch tests and if the branch is not itself the
2375 target of any branch. */
2376 if ((pinfo & INSN_UNCOND_BRANCH_DELAY)
2377 || (pinfo & INSN_COND_BRANCH_DELAY))
2379 if (mips_optimize < 2
2380 /* If we have seen .set volatile or .set nomove, don't
2382 || mips_opts.nomove != 0
2383 /* If we had to emit any NOP instructions, then we
2384 already know we can not swap. */
2386 /* If we don't even know the previous insn, we can not
2388 || ! prev_insn_valid
2389 /* If the previous insn is already in a branch delay
2390 slot, then we can not swap. */
2391 || prev_insn_is_delay_slot
2392 /* If the previous previous insn was in a .set
2393 noreorder, we can't swap. Actually, the MIPS
2394 assembler will swap in this situation. However, gcc
2395 configured -with-gnu-as will generate code like
2401 in which we can not swap the bne and INSN. If gcc is
2402 not configured -with-gnu-as, it does not output the
2403 .set pseudo-ops. We don't have to check
2404 prev_insn_unreordered, because prev_insn_valid will
2405 be 0 in that case. We don't want to use
2406 prev_prev_insn_valid, because we do want to be able
2407 to swap at the start of a function. */
2408 || prev_prev_insn_unreordered
2409 /* If the branch is itself the target of a branch, we
2410 can not swap. We cheat on this; all we check for is
2411 whether there is a label on this instruction. If
2412 there are any branches to anything other than a
2413 label, users must use .set noreorder. */
2414 || insn_labels != NULL
2415 /* If the previous instruction is in a variant frag, we
2416 can not do the swap. This does not apply to the
2417 mips16, which uses variant frags for different
2419 || (! mips_opts.mips16
2420 && prev_insn_frag->fr_type == rs_machine_dependent)
2421 /* If the branch reads the condition codes, we don't
2422 even try to swap, because in the sequence
2427 we can not swap, and I don't feel like handling that
2429 || (! mips_opts.mips16
2430 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
2431 && (pinfo & INSN_READ_COND_CODE))
2432 /* We can not swap with an instruction that requires a
2433 delay slot, becase the target of the branch might
2434 interfere with that instruction. */
2435 || (! mips_opts.mips16
2436 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
2438 /* Itbl support may require additional care here. */
2439 & (INSN_LOAD_COPROC_DELAY
2440 | INSN_COPROC_MOVE_DELAY
2441 | INSN_WRITE_COND_CODE)))
2442 || (! (hilo_interlocks
2443 || (mips_tune == CPU_R3900 && (pinfo & INSN_MULT)))
2447 || (! mips_opts.mips16
2449 && (prev_pinfo & INSN_LOAD_MEMORY_DELAY))
2450 || (! mips_opts.mips16
2451 && mips_opts.isa == ISA_MIPS1
2452 /* Itbl support may require additional care here. */
2453 && (prev_pinfo & INSN_COPROC_MEMORY_DELAY))
2454 /* We can not swap with a branch instruction. */
2456 & (INSN_UNCOND_BRANCH_DELAY
2457 | INSN_COND_BRANCH_DELAY
2458 | INSN_COND_BRANCH_LIKELY))
2459 /* We do not swap with a trap instruction, since it
2460 complicates trap handlers to have the trap
2461 instruction be in a delay slot. */
2462 || (prev_pinfo & INSN_TRAP)
2463 /* If the branch reads a register that the previous
2464 instruction sets, we can not swap. */
2465 || (! mips_opts.mips16
2466 && (prev_pinfo & INSN_WRITE_GPR_T)
2467 && insn_uses_reg (ip,
2468 ((prev_insn.insn_opcode >> OP_SH_RT)
2471 || (! mips_opts.mips16
2472 && (prev_pinfo & INSN_WRITE_GPR_D)
2473 && insn_uses_reg (ip,
2474 ((prev_insn.insn_opcode >> OP_SH_RD)
2477 || (mips_opts.mips16
2478 && (((prev_pinfo & MIPS16_INSN_WRITE_X)
2479 && insn_uses_reg (ip,
2480 ((prev_insn.insn_opcode
2482 & MIPS16OP_MASK_RX),
2484 || ((prev_pinfo & MIPS16_INSN_WRITE_Y)
2485 && insn_uses_reg (ip,
2486 ((prev_insn.insn_opcode
2488 & MIPS16OP_MASK_RY),
2490 || ((prev_pinfo & MIPS16_INSN_WRITE_Z)
2491 && insn_uses_reg (ip,
2492 ((prev_insn.insn_opcode
2494 & MIPS16OP_MASK_RZ),
2496 || ((prev_pinfo & MIPS16_INSN_WRITE_T)
2497 && insn_uses_reg (ip, TREG, MIPS_GR_REG))
2498 || ((prev_pinfo & MIPS16_INSN_WRITE_31)
2499 && insn_uses_reg (ip, RA, MIPS_GR_REG))
2500 || ((prev_pinfo & MIPS16_INSN_WRITE_GPR_Y)
2501 && insn_uses_reg (ip,
2502 MIPS16OP_EXTRACT_REG32R (prev_insn.
2505 /* If the branch writes a register that the previous
2506 instruction sets, we can not swap (we know that
2507 branches write only to RD or to $31). */
2508 || (! mips_opts.mips16
2509 && (prev_pinfo & INSN_WRITE_GPR_T)
2510 && (((pinfo & INSN_WRITE_GPR_D)
2511 && (((prev_insn.insn_opcode >> OP_SH_RT) & OP_MASK_RT)
2512 == ((ip->insn_opcode >> OP_SH_RD) & OP_MASK_RD)))
2513 || ((pinfo & INSN_WRITE_GPR_31)
2514 && (((prev_insn.insn_opcode >> OP_SH_RT)
2517 || (! mips_opts.mips16
2518 && (prev_pinfo & INSN_WRITE_GPR_D)
2519 && (((pinfo & INSN_WRITE_GPR_D)
2520 && (((prev_insn.insn_opcode >> OP_SH_RD) & OP_MASK_RD)
2521 == ((ip->insn_opcode >> OP_SH_RD) & OP_MASK_RD)))
2522 || ((pinfo & INSN_WRITE_GPR_31)
2523 && (((prev_insn.insn_opcode >> OP_SH_RD)
2526 || (mips_opts.mips16
2527 && (pinfo & MIPS16_INSN_WRITE_31)
2528 && ((prev_pinfo & MIPS16_INSN_WRITE_31)
2529 || ((prev_pinfo & MIPS16_INSN_WRITE_GPR_Y)
2530 && (MIPS16OP_EXTRACT_REG32R (prev_insn.insn_opcode)
2532 /* If the branch writes a register that the previous
2533 instruction reads, we can not swap (we know that
2534 branches only write to RD or to $31). */
2535 || (! mips_opts.mips16
2536 && (pinfo & INSN_WRITE_GPR_D)
2537 && insn_uses_reg (&prev_insn,
2538 ((ip->insn_opcode >> OP_SH_RD)
2541 || (! mips_opts.mips16
2542 && (pinfo & INSN_WRITE_GPR_31)
2543 && insn_uses_reg (&prev_insn, RA, MIPS_GR_REG))
2544 || (mips_opts.mips16
2545 && (pinfo & MIPS16_INSN_WRITE_31)
2546 && insn_uses_reg (&prev_insn, RA, MIPS_GR_REG))
2547 /* If we are generating embedded PIC code, the branch
2548 might be expanded into a sequence which uses $at, so
2549 we can't swap with an instruction which reads it. */
2550 || (mips_pic == EMBEDDED_PIC
2551 && insn_uses_reg (&prev_insn, AT, MIPS_GR_REG))
2552 /* If the previous previous instruction has a load
2553 delay, and sets a register that the branch reads, we
2555 || (! mips_opts.mips16
2556 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
2557 /* Itbl support may require additional care here. */
2558 && ((prev_prev_insn.insn_mo->pinfo & INSN_LOAD_COPROC_DELAY)
2559 || (! gpr_interlocks
2560 && (prev_prev_insn.insn_mo->pinfo
2561 & INSN_LOAD_MEMORY_DELAY)))
2562 && insn_uses_reg (ip,
2563 ((prev_prev_insn.insn_opcode >> OP_SH_RT)
2566 /* If one instruction sets a condition code and the
2567 other one uses a condition code, we can not swap. */
2568 || ((pinfo & INSN_READ_COND_CODE)
2569 && (prev_pinfo & INSN_WRITE_COND_CODE))
2570 || ((pinfo & INSN_WRITE_COND_CODE)
2571 && (prev_pinfo & INSN_READ_COND_CODE))
2572 /* If the previous instruction uses the PC, we can not
2574 || (mips_opts.mips16
2575 && (prev_pinfo & MIPS16_INSN_READ_PC))
2576 /* If the previous instruction was extended, we can not
2578 || (mips_opts.mips16 && prev_insn_extended)
2579 /* If the previous instruction had a fixup in mips16
2580 mode, we can not swap. This normally means that the
2581 previous instruction was a 4 byte branch anyhow. */
2582 || (mips_opts.mips16 && prev_insn_fixp[0])
2583 /* If the previous instruction is a sync, sync.l, or
2584 sync.p, we can not swap. */
2585 || (prev_pinfo & INSN_SYNC))
2587 /* We could do even better for unconditional branches to
2588 portions of this object file; we could pick up the
2589 instruction at the destination, put it in the delay
2590 slot, and bump the destination address. */
2592 /* Update the previous insn information. */
2593 prev_prev_insn = *ip;
2594 prev_insn.insn_mo = &dummy_opcode;
2598 /* It looks like we can actually do the swap. */
2599 if (! mips_opts.mips16)
2604 prev_f = prev_insn_frag->fr_literal + prev_insn_where;
2605 memcpy (temp, prev_f, 4);
2606 memcpy (prev_f, f, 4);
2607 memcpy (f, temp, 4);
2608 if (prev_insn_fixp[0])
2610 prev_insn_fixp[0]->fx_frag = frag_now;
2611 prev_insn_fixp[0]->fx_where = f - frag_now->fr_literal;
2613 if (prev_insn_fixp[1])
2615 prev_insn_fixp[1]->fx_frag = frag_now;
2616 prev_insn_fixp[1]->fx_where = f - frag_now->fr_literal;
2618 if (prev_insn_fixp[2])
2620 prev_insn_fixp[2]->fx_frag = frag_now;
2621 prev_insn_fixp[2]->fx_where = f - frag_now->fr_literal;
2623 if (prev_insn_fixp[0] && HAVE_NEWABI
2624 && prev_insn_frag != frag_now
2625 && (prev_insn_fixp[0]->fx_r_type
2626 == BFD_RELOC_MIPS_GOT_DISP
2627 || (prev_insn_fixp[0]->fx_r_type
2628 == BFD_RELOC_MIPS_CALL16)))
2630 /* To avoid confusion in tc_gen_reloc, we must
2631 ensure that this does not become a variant
2633 force_new_frag = TRUE;
2637 fixp[0]->fx_frag = prev_insn_frag;
2638 fixp[0]->fx_where = prev_insn_where;
2642 fixp[1]->fx_frag = prev_insn_frag;
2643 fixp[1]->fx_where = prev_insn_where;
2647 fixp[2]->fx_frag = prev_insn_frag;
2648 fixp[2]->fx_where = prev_insn_where;
2656 assert (prev_insn_fixp[0] == NULL);
2657 assert (prev_insn_fixp[1] == NULL);
2658 assert (prev_insn_fixp[2] == NULL);
2659 prev_f = prev_insn_frag->fr_literal + prev_insn_where;
2660 memcpy (temp, prev_f, 2);
2661 memcpy (prev_f, f, 2);
2662 if (*reloc_type != BFD_RELOC_MIPS16_JMP)
2664 assert (*reloc_type == BFD_RELOC_UNUSED);
2665 memcpy (f, temp, 2);
2669 memcpy (f, f + 2, 2);
2670 memcpy (f + 2, temp, 2);
2674 fixp[0]->fx_frag = prev_insn_frag;
2675 fixp[0]->fx_where = prev_insn_where;
2679 fixp[1]->fx_frag = prev_insn_frag;
2680 fixp[1]->fx_where = prev_insn_where;
2684 fixp[2]->fx_frag = prev_insn_frag;
2685 fixp[2]->fx_where = prev_insn_where;
2689 /* Update the previous insn information; leave prev_insn
2691 prev_prev_insn = *ip;
2693 prev_insn_is_delay_slot = 1;
2695 /* If that was an unconditional branch, forget the previous
2696 insn information. */
2697 if (pinfo & INSN_UNCOND_BRANCH_DELAY)
2699 prev_prev_insn.insn_mo = &dummy_opcode;
2700 prev_insn.insn_mo = &dummy_opcode;
2703 prev_insn_fixp[0] = NULL;
2704 prev_insn_fixp[1] = NULL;
2705 prev_insn_fixp[2] = NULL;
2706 prev_insn_reloc_type[0] = BFD_RELOC_UNUSED;
2707 prev_insn_reloc_type[1] = BFD_RELOC_UNUSED;
2708 prev_insn_reloc_type[2] = BFD_RELOC_UNUSED;
2709 prev_insn_extended = 0;
2711 else if (pinfo & INSN_COND_BRANCH_LIKELY)
2713 /* We don't yet optimize a branch likely. What we should do
2714 is look at the target, copy the instruction found there
2715 into the delay slot, and increment the branch to jump to
2716 the next instruction. */
2718 /* Update the previous insn information. */
2719 prev_prev_insn = *ip;
2720 prev_insn.insn_mo = &dummy_opcode;
2721 prev_insn_fixp[0] = NULL;
2722 prev_insn_fixp[1] = NULL;
2723 prev_insn_fixp[2] = NULL;
2724 prev_insn_reloc_type[0] = BFD_RELOC_UNUSED;
2725 prev_insn_reloc_type[1] = BFD_RELOC_UNUSED;
2726 prev_insn_reloc_type[2] = BFD_RELOC_UNUSED;
2727 prev_insn_extended = 0;
2731 /* Update the previous insn information. */
2733 prev_prev_insn.insn_mo = &dummy_opcode;
2735 prev_prev_insn = prev_insn;
2738 /* Any time we see a branch, we always fill the delay slot
2739 immediately; since this insn is not a branch, we know it
2740 is not in a delay slot. */
2741 prev_insn_is_delay_slot = 0;
2743 prev_insn_fixp[0] = fixp[0];
2744 prev_insn_fixp[1] = fixp[1];
2745 prev_insn_fixp[2] = fixp[2];
2746 prev_insn_reloc_type[0] = reloc_type[0];
2747 prev_insn_reloc_type[1] = reloc_type[1];
2748 prev_insn_reloc_type[2] = reloc_type[2];
2749 if (mips_opts.mips16)
2750 prev_insn_extended = (ip->use_extend
2751 || *reloc_type > BFD_RELOC_UNUSED);
2754 prev_prev_insn_unreordered = prev_insn_unreordered;
2755 prev_insn_unreordered = 0;
2756 prev_insn_frag = frag_now;
2757 prev_insn_where = f - frag_now->fr_literal;
2758 prev_insn_valid = 1;
2760 else if (place == NULL)
2762 /* We need to record a bit of information even when we are not
2763 reordering, in order to determine the base address for mips16
2764 PC relative relocs. */
2765 prev_prev_insn = prev_insn;
2767 prev_insn_reloc_type[0] = reloc_type[0];
2768 prev_insn_reloc_type[1] = reloc_type[1];
2769 prev_insn_reloc_type[2] = reloc_type[2];
2770 prev_prev_insn_unreordered = prev_insn_unreordered;
2771 prev_insn_unreordered = 1;
2774 /* We just output an insn, so the next one doesn't have a label. */
2775 mips_clear_insn_labels ();
2777 /* We must ensure that the frag to which an instruction that was
2778 moved from a non-variant frag doesn't become a variant frag,
2779 otherwise tc_gen_reloc may get confused. */
2782 frag_wane (frag_now);
2787 /* This function forgets that there was any previous instruction or
2788 label. If PRESERVE is non-zero, it remembers enough information to
2789 know whether nops are needed before a noreorder section. */
2792 mips_no_prev_insn (preserve)
2797 prev_insn.insn_mo = &dummy_opcode;
2798 prev_prev_insn.insn_mo = &dummy_opcode;
2799 prev_nop_frag = NULL;
2800 prev_nop_frag_holds = 0;
2801 prev_nop_frag_required = 0;
2802 prev_nop_frag_since = 0;
2804 prev_insn_valid = 0;
2805 prev_insn_is_delay_slot = 0;
2806 prev_insn_unreordered = 0;
2807 prev_insn_extended = 0;
2808 prev_insn_reloc_type[0] = BFD_RELOC_UNUSED;
2809 prev_insn_reloc_type[1] = BFD_RELOC_UNUSED;
2810 prev_insn_reloc_type[2] = BFD_RELOC_UNUSED;
2811 prev_prev_insn_unreordered = 0;
2812 mips_clear_insn_labels ();
2815 /* This function must be called whenever we turn on noreorder or emit
2816 something other than instructions. It inserts any NOPS which might
2817 be needed by the previous instruction, and clears the information
2818 kept for the previous instructions. The INSNS parameter is true if
2819 instructions are to follow. */
2822 mips_emit_delays (insns)
2825 if (! mips_opts.noreorder)
2830 if ((! mips_opts.mips16
2831 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
2832 && (! cop_interlocks
2833 && (prev_insn.insn_mo->pinfo
2834 & (INSN_LOAD_COPROC_DELAY
2835 | INSN_COPROC_MOVE_DELAY
2836 | INSN_WRITE_COND_CODE))))
2837 || (! hilo_interlocks
2838 && (prev_insn.insn_mo->pinfo
2841 || (! mips_opts.mips16
2843 && (prev_insn.insn_mo->pinfo
2844 & INSN_LOAD_MEMORY_DELAY))
2845 || (! mips_opts.mips16
2846 && mips_opts.isa == ISA_MIPS1
2847 && (prev_insn.insn_mo->pinfo
2848 & INSN_COPROC_MEMORY_DELAY)))
2850 /* Itbl support may require additional care here. */
2852 if ((! mips_opts.mips16
2853 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
2854 && (! cop_interlocks
2855 && prev_insn.insn_mo->pinfo & INSN_WRITE_COND_CODE))
2856 || (! hilo_interlocks
2857 && ((prev_insn.insn_mo->pinfo & INSN_READ_HI)
2858 || (prev_insn.insn_mo->pinfo & INSN_READ_LO))))
2861 if (prev_insn_unreordered)
2864 else if ((! mips_opts.mips16
2865 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
2866 && (! cop_interlocks
2867 && prev_prev_insn.insn_mo->pinfo & INSN_WRITE_COND_CODE))
2868 || (! hilo_interlocks
2869 && ((prev_prev_insn.insn_mo->pinfo & INSN_READ_HI)
2870 || (prev_prev_insn.insn_mo->pinfo & INSN_READ_LO))))
2872 /* Itbl support may require additional care here. */
2873 if (! prev_prev_insn_unreordered)
2877 if (mips_fix_4122_bugs && prev_insn.insn_mo->name)
2880 const char *pn = prev_insn.insn_mo->name;
2881 if (strncmp(pn, "macc", 4) == 0
2882 || strncmp(pn, "dmacc", 5) == 0
2883 || strncmp(pn, "dmult", 5) == 0)
2887 if (nops < min_nops)
2893 struct insn_label_list *l;
2897 /* Record the frag which holds the nop instructions, so
2898 that we can remove them if we don't need them. */
2899 frag_grow (mips_opts.mips16 ? nops * 2 : nops * 4);
2900 prev_nop_frag = frag_now;
2901 prev_nop_frag_holds = nops;
2902 prev_nop_frag_required = 0;
2903 prev_nop_frag_since = 0;
2906 for (; nops > 0; --nops)
2911 /* Move on to a new frag, so that it is safe to simply
2912 decrease the size of prev_nop_frag. */
2913 frag_wane (frag_now);
2917 for (l = insn_labels; l != NULL; l = l->next)
2921 assert (S_GET_SEGMENT (l->label) == now_seg);
2922 symbol_set_frag (l->label, frag_now);
2923 val = (valueT) frag_now_fix ();
2924 /* mips16 text labels are stored as odd. */
2925 if (mips_opts.mips16)
2927 S_SET_VALUE (l->label, val);
2932 /* Mark instruction labels in mips16 mode. */
2934 mips16_mark_labels ();
2936 mips_no_prev_insn (insns);
2939 /* Build an instruction created by a macro expansion. This is passed
2940 a pointer to the count of instructions created so far, an
2941 expression, the name of the instruction to build, an operand format
2942 string, and corresponding arguments. */
2946 macro_build (char *place,
2954 macro_build (place, counter, ep, name, fmt, va_alist)
2963 struct mips_cl_insn insn;
2964 bfd_reloc_code_real_type r[3];
2968 va_start (args, fmt);
2974 * If the macro is about to expand into a second instruction,
2975 * print a warning if needed. We need to pass ip as a parameter
2976 * to generate a better warning message here...
2978 if (mips_opts.warn_about_macros && place == NULL && *counter == 1)
2979 as_warn (_("Macro instruction expanded into multiple instructions"));
2982 * If the macro is about to expand into a second instruction,
2983 * and it is in a delay slot, print a warning.
2987 && mips_opts.noreorder
2988 && (prev_prev_insn.insn_mo->pinfo
2989 & (INSN_UNCOND_BRANCH_DELAY | INSN_COND_BRANCH_DELAY
2990 | INSN_COND_BRANCH_LIKELY)) != 0)
2991 as_warn (_("Macro instruction expanded into multiple instructions in a branch delay slot"));
2994 ++*counter; /* bump instruction counter */
2996 if (mips_opts.mips16)
2998 mips16_macro_build (place, counter, ep, name, fmt, args);
3003 r[0] = BFD_RELOC_UNUSED;
3004 r[1] = BFD_RELOC_UNUSED;
3005 r[2] = BFD_RELOC_UNUSED;
3006 insn.insn_mo = (struct mips_opcode *) hash_find (op_hash, name);
3007 assert (insn.insn_mo);
3008 assert (strcmp (name, insn.insn_mo->name) == 0);
3010 /* Search until we get a match for NAME. */
3013 /* It is assumed here that macros will never generate
3014 MDMX or MIPS-3D instructions. */
3015 if (strcmp (fmt, insn.insn_mo->args) == 0
3016 && insn.insn_mo->pinfo != INSN_MACRO
3017 && OPCODE_IS_MEMBER (insn.insn_mo,
3019 | (file_ase_mips16 ? INSN_MIPS16 : 0)),
3021 && (mips_arch != CPU_R4650 || (insn.insn_mo->pinfo & FP_D) == 0))
3025 assert (insn.insn_mo->name);
3026 assert (strcmp (name, insn.insn_mo->name) == 0);
3029 insn.insn_opcode = insn.insn_mo->match;
3045 insn.insn_opcode |= va_arg (args, int) << OP_SH_RT;
3049 insn.insn_opcode |= va_arg (args, int) << OP_SH_CODE;
3054 insn.insn_opcode |= va_arg (args, int) << OP_SH_FT;
3060 insn.insn_opcode |= va_arg (args, int) << OP_SH_RD;
3065 int tmp = va_arg (args, int);
3067 insn.insn_opcode |= tmp << OP_SH_RT;
3068 insn.insn_opcode |= tmp << OP_SH_RD;
3074 insn.insn_opcode |= va_arg (args, int) << OP_SH_FS;
3081 insn.insn_opcode |= va_arg (args, int) << OP_SH_SHAMT;
3085 insn.insn_opcode |= va_arg (args, int) << OP_SH_FD;
3089 insn.insn_opcode |= va_arg (args, int) << OP_SH_CODE20;
3093 insn.insn_opcode |= va_arg (args, int) << OP_SH_CODE19;
3097 insn.insn_opcode |= va_arg (args, int) << OP_SH_CODE2;
3104 insn.insn_opcode |= va_arg (args, int) << OP_SH_RS;
3110 *r = (bfd_reloc_code_real_type) va_arg (args, int);
3111 assert (*r == BFD_RELOC_GPREL16
3112 || *r == BFD_RELOC_MIPS_LITERAL
3113 || *r == BFD_RELOC_MIPS_HIGHER
3114 || *r == BFD_RELOC_HI16_S
3115 || *r == BFD_RELOC_LO16
3116 || *r == BFD_RELOC_MIPS_GOT16
3117 || *r == BFD_RELOC_MIPS_CALL16
3118 || *r == BFD_RELOC_MIPS_GOT_DISP
3119 || *r == BFD_RELOC_MIPS_GOT_PAGE
3120 || *r == BFD_RELOC_MIPS_GOT_OFST
3121 || *r == BFD_RELOC_MIPS_GOT_LO16
3122 || *r == BFD_RELOC_MIPS_CALL_LO16
3123 || (ep->X_op == O_subtract
3124 && *r == BFD_RELOC_PCREL_LO16));
3128 *r = (bfd_reloc_code_real_type) va_arg (args, int);
3130 && (ep->X_op == O_constant
3131 || (ep->X_op == O_symbol
3132 && (*r == BFD_RELOC_MIPS_HIGHEST
3133 || *r == BFD_RELOC_HI16_S
3134 || *r == BFD_RELOC_HI16
3135 || *r == BFD_RELOC_GPREL16
3136 || *r == BFD_RELOC_MIPS_GOT_HI16
3137 || *r == BFD_RELOC_MIPS_CALL_HI16))
3138 || (ep->X_op == O_subtract
3139 && *r == BFD_RELOC_PCREL_HI16_S)));
3143 assert (ep != NULL);
3145 * This allows macro() to pass an immediate expression for
3146 * creating short branches without creating a symbol.
3147 * Note that the expression still might come from the assembly
3148 * input, in which case the value is not checked for range nor
3149 * is a relocation entry generated (yuck).
3151 if (ep->X_op == O_constant)
3153 insn.insn_opcode |= (ep->X_add_number >> 2) & 0xffff;
3157 *r = BFD_RELOC_16_PCREL_S2;
3161 assert (ep != NULL);
3162 *r = BFD_RELOC_MIPS_JMP;
3166 insn.insn_opcode |= va_arg (args, unsigned long);
3175 assert (*r == BFD_RELOC_UNUSED ? ep == NULL : ep != NULL);
3177 append_insn (place, &insn, ep, r);
3181 mips16_macro_build (place, counter, ep, name, fmt, args)
3183 int *counter ATTRIBUTE_UNUSED;
3189 struct mips_cl_insn insn;
3190 bfd_reloc_code_real_type r[3]
3191 = {BFD_RELOC_UNUSED, BFD_RELOC_UNUSED, BFD_RELOC_UNUSED};
3193 insn.insn_mo = (struct mips_opcode *) hash_find (mips16_op_hash, name);
3194 assert (insn.insn_mo);
3195 assert (strcmp (name, insn.insn_mo->name) == 0);
3197 while (strcmp (fmt, insn.insn_mo->args) != 0
3198 || insn.insn_mo->pinfo == INSN_MACRO)
3201 assert (insn.insn_mo->name);
3202 assert (strcmp (name, insn.insn_mo->name) == 0);
3205 insn.insn_opcode = insn.insn_mo->match;
3206 insn.use_extend = FALSE;
3225 insn.insn_opcode |= va_arg (args, int) << MIPS16OP_SH_RY;
3230 insn.insn_opcode |= va_arg (args, int) << MIPS16OP_SH_RX;
3234 insn.insn_opcode |= va_arg (args, int) << MIPS16OP_SH_RZ;
3238 insn.insn_opcode |= va_arg (args, int) << MIPS16OP_SH_MOVE32Z;
3248 insn.insn_opcode |= va_arg (args, int) << MIPS16OP_SH_REGR32;
3255 regno = va_arg (args, int);
3256 regno = ((regno & 7) << 2) | ((regno & 0x18) >> 3);
3257 insn.insn_opcode |= regno << MIPS16OP_SH_REG32R;
3278 assert (ep != NULL);
3280 if (ep->X_op != O_constant)
3281 *r = (int) BFD_RELOC_UNUSED + c;
3284 mips16_immed (NULL, 0, c, ep->X_add_number, FALSE, FALSE,
3285 FALSE, &insn.insn_opcode, &insn.use_extend,
3288 *r = BFD_RELOC_UNUSED;
3294 insn.insn_opcode |= va_arg (args, int) << MIPS16OP_SH_IMM6;
3301 assert (*r == BFD_RELOC_UNUSED ? ep == NULL : ep != NULL);
3303 append_insn (place, &insn, ep, r);
3307 * Generate a "jalr" instruction with a relocation hint to the called
3308 * function. This occurs in NewABI PIC code.
3311 macro_build_jalr (icnt, ep)
3322 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "jalr", "d,s",
3325 fix_new_exp (frag_now, f - frag_now->fr_literal,
3326 4, ep, FALSE, BFD_RELOC_MIPS_JALR);
3330 * Generate a "lui" instruction.
3333 macro_build_lui (place, counter, ep, regnum)
3339 expressionS high_expr;
3340 struct mips_cl_insn insn;
3341 bfd_reloc_code_real_type r[3]
3342 = {BFD_RELOC_UNUSED, BFD_RELOC_UNUSED, BFD_RELOC_UNUSED};
3343 const char *name = "lui";
3344 const char *fmt = "t,u";
3346 assert (! mips_opts.mips16);
3352 high_expr.X_op = O_constant;
3353 high_expr.X_add_number = ep->X_add_number;
3356 if (high_expr.X_op == O_constant)
3358 /* we can compute the instruction now without a relocation entry */
3359 high_expr.X_add_number = ((high_expr.X_add_number + 0x8000)
3361 *r = BFD_RELOC_UNUSED;
3365 assert (ep->X_op == O_symbol);
3366 /* _gp_disp is a special case, used from s_cpload. */
3367 assert (mips_pic == NO_PIC
3369 && strcmp (S_GET_NAME (ep->X_add_symbol), "_gp_disp") == 0));
3370 *r = BFD_RELOC_HI16_S;
3374 * If the macro is about to expand into a second instruction,
3375 * print a warning if needed. We need to pass ip as a parameter
3376 * to generate a better warning message here...
3378 if (mips_opts.warn_about_macros && place == NULL && *counter == 1)
3379 as_warn (_("Macro instruction expanded into multiple instructions"));
3382 ++*counter; /* bump instruction counter */
3384 insn.insn_mo = (struct mips_opcode *) hash_find (op_hash, name);
3385 assert (insn.insn_mo);
3386 assert (strcmp (name, insn.insn_mo->name) == 0);
3387 assert (strcmp (fmt, insn.insn_mo->args) == 0);
3389 insn.insn_opcode = insn.insn_mo->match | (regnum << OP_SH_RT);
3390 if (*r == BFD_RELOC_UNUSED)
3392 insn.insn_opcode |= high_expr.X_add_number;
3393 append_insn (place, &insn, NULL, r);
3396 append_insn (place, &insn, &high_expr, r);
3399 /* Generate a sequence of instructions to do a load or store from a constant
3400 offset off of a base register (breg) into/from a target register (treg),
3401 using AT if necessary. */
3403 macro_build_ldst_constoffset (place, counter, ep, op, treg, breg)
3410 assert (ep->X_op == O_constant);
3412 /* Right now, this routine can only handle signed 32-bit contants. */
3413 if (! IS_SEXT_32BIT_NUM(ep->X_add_number))
3414 as_warn (_("operand overflow"));
3416 if (IS_SEXT_16BIT_NUM(ep->X_add_number))
3418 /* Signed 16-bit offset will fit in the op. Easy! */
3419 macro_build (place, counter, ep, op, "t,o(b)", treg,
3420 (int) BFD_RELOC_LO16, breg);
3424 /* 32-bit offset, need multiple instructions and AT, like:
3425 lui $tempreg,const_hi (BFD_RELOC_HI16_S)
3426 addu $tempreg,$tempreg,$breg
3427 <op> $treg,const_lo($tempreg) (BFD_RELOC_LO16)
3428 to handle the complete offset. */
3429 macro_build_lui (place, counter, ep, AT);
3432 macro_build (place, counter, (expressionS *) NULL,
3433 HAVE_32BIT_ADDRESSES ? HAVE_NEWABI
3434 ? "add" : "addu" : "daddu",
3435 "d,v,t", AT, AT, breg);
3438 macro_build (place, counter, ep, op, "t,o(b)", treg,
3439 (int) BFD_RELOC_LO16, AT);
3442 as_warn (_("Macro used $at after \".set noat\""));
3447 * Generates code to set the $at register to true (one)
3448 * if reg is less than the immediate expression.
3451 set_at (counter, reg, unsignedp)
3456 if (imm_expr.X_op == O_constant
3457 && imm_expr.X_add_number >= -0x8000
3458 && imm_expr.X_add_number < 0x8000)
3459 macro_build ((char *) NULL, counter, &imm_expr,
3460 unsignedp ? "sltiu" : "slti",
3461 "t,r,j", AT, reg, (int) BFD_RELOC_LO16);
3464 load_register (counter, AT, &imm_expr, HAVE_64BIT_GPRS);
3465 macro_build ((char *) NULL, counter, (expressionS *) NULL,
3466 unsignedp ? "sltu" : "slt",
3467 "d,v,t", AT, reg, AT);
3471 /* Warn if an expression is not a constant. */
3474 check_absolute_expr (ip, ex)
3475 struct mips_cl_insn *ip;
3478 if (ex->X_op == O_big)
3479 as_bad (_("unsupported large constant"));
3480 else if (ex->X_op != O_constant)
3481 as_bad (_("Instruction %s requires absolute expression"), ip->insn_mo->name);
3484 /* Count the leading zeroes by performing a binary chop. This is a
3485 bulky bit of source, but performance is a LOT better for the
3486 majority of values than a simple loop to count the bits:
3487 for (lcnt = 0; (lcnt < 32); lcnt++)
3488 if ((v) & (1 << (31 - lcnt)))
3490 However it is not code size friendly, and the gain will drop a bit
3491 on certain cached systems.
3493 #define COUNT_TOP_ZEROES(v) \
3494 (((v) & ~0xffff) == 0 \
3495 ? ((v) & ~0xff) == 0 \
3496 ? ((v) & ~0xf) == 0 \
3497 ? ((v) & ~0x3) == 0 \
3498 ? ((v) & ~0x1) == 0 \
3503 : ((v) & ~0x7) == 0 \
3506 : ((v) & ~0x3f) == 0 \
3507 ? ((v) & ~0x1f) == 0 \
3510 : ((v) & ~0x7f) == 0 \
3513 : ((v) & ~0xfff) == 0 \
3514 ? ((v) & ~0x3ff) == 0 \
3515 ? ((v) & ~0x1ff) == 0 \
3518 : ((v) & ~0x7ff) == 0 \
3521 : ((v) & ~0x3fff) == 0 \
3522 ? ((v) & ~0x1fff) == 0 \
3525 : ((v) & ~0x7fff) == 0 \
3528 : ((v) & ~0xffffff) == 0 \
3529 ? ((v) & ~0xfffff) == 0 \
3530 ? ((v) & ~0x3ffff) == 0 \
3531 ? ((v) & ~0x1ffff) == 0 \
3534 : ((v) & ~0x7ffff) == 0 \
3537 : ((v) & ~0x3fffff) == 0 \
3538 ? ((v) & ~0x1fffff) == 0 \
3541 : ((v) & ~0x7fffff) == 0 \
3544 : ((v) & ~0xfffffff) == 0 \
3545 ? ((v) & ~0x3ffffff) == 0 \
3546 ? ((v) & ~0x1ffffff) == 0 \
3549 : ((v) & ~0x7ffffff) == 0 \
3552 : ((v) & ~0x3fffffff) == 0 \
3553 ? ((v) & ~0x1fffffff) == 0 \
3556 : ((v) & ~0x7fffffff) == 0 \
3561 * This routine generates the least number of instructions neccessary to load
3562 * an absolute expression value into a register.
3565 load_register (counter, reg, ep, dbl)
3572 expressionS hi32, lo32;
3574 if (ep->X_op != O_big)
3576 assert (ep->X_op == O_constant);
3577 if (ep->X_add_number < 0x8000
3578 && (ep->X_add_number >= 0
3579 || (ep->X_add_number >= -0x8000
3582 || sizeof (ep->X_add_number) > 4))))
3584 /* We can handle 16 bit signed values with an addiu to
3585 $zero. No need to ever use daddiu here, since $zero and
3586 the result are always correct in 32 bit mode. */
3587 macro_build ((char *) NULL, counter, ep, "addiu", "t,r,j", reg, 0,
3588 (int) BFD_RELOC_LO16);
3591 else if (ep->X_add_number >= 0 && ep->X_add_number < 0x10000)
3593 /* We can handle 16 bit unsigned values with an ori to
3595 macro_build ((char *) NULL, counter, ep, "ori", "t,r,i", reg, 0,
3596 (int) BFD_RELOC_LO16);
3599 else if ((IS_SEXT_32BIT_NUM (ep->X_add_number)
3602 || sizeof (ep->X_add_number) > 4
3603 || (ep->X_add_number & 0x80000000) == 0))
3604 || ((HAVE_32BIT_GPRS || ! dbl)
3605 && (ep->X_add_number &~ (offsetT) 0xffffffff) == 0)
3608 && ((ep->X_add_number &~ (offsetT) 0xffffffff)
3609 == ~ (offsetT) 0xffffffff)))
3611 /* 32 bit values require an lui. */
3612 macro_build ((char *) NULL, counter, ep, "lui", "t,u", reg,
3613 (int) BFD_RELOC_HI16);
3614 if ((ep->X_add_number & 0xffff) != 0)
3615 macro_build ((char *) NULL, counter, ep, "ori", "t,r,i", reg, reg,
3616 (int) BFD_RELOC_LO16);
3621 /* The value is larger than 32 bits. */
3623 if (HAVE_32BIT_GPRS)
3625 as_bad (_("Number (0x%lx) larger than 32 bits"),
3626 (unsigned long) ep->X_add_number);
3627 macro_build ((char *) NULL, counter, ep, "addiu", "t,r,j", reg, 0,
3628 (int) BFD_RELOC_LO16);
3632 if (ep->X_op != O_big)
3635 hi32.X_add_number = (valueT) hi32.X_add_number >> 16;
3636 hi32.X_add_number = (valueT) hi32.X_add_number >> 16;
3637 hi32.X_add_number &= 0xffffffff;
3639 lo32.X_add_number &= 0xffffffff;
3643 assert (ep->X_add_number > 2);
3644 if (ep->X_add_number == 3)
3645 generic_bignum[3] = 0;
3646 else if (ep->X_add_number > 4)
3647 as_bad (_("Number larger than 64 bits"));
3648 lo32.X_op = O_constant;
3649 lo32.X_add_number = generic_bignum[0] + (generic_bignum[1] << 16);
3650 hi32.X_op = O_constant;
3651 hi32.X_add_number = generic_bignum[2] + (generic_bignum[3] << 16);
3654 if (hi32.X_add_number == 0)
3659 unsigned long hi, lo;
3661 if (hi32.X_add_number == (offsetT) 0xffffffff)
3663 if ((lo32.X_add_number & 0xffff8000) == 0xffff8000)
3665 macro_build ((char *) NULL, counter, &lo32, "addiu", "t,r,j",
3666 reg, 0, (int) BFD_RELOC_LO16);
3669 if (lo32.X_add_number & 0x80000000)
3671 macro_build ((char *) NULL, counter, &lo32, "lui", "t,u", reg,
3672 (int) BFD_RELOC_HI16);
3673 if (lo32.X_add_number & 0xffff)
3674 macro_build ((char *) NULL, counter, &lo32, "ori", "t,r,i",
3675 reg, reg, (int) BFD_RELOC_LO16);
3680 /* Check for 16bit shifted constant. We know that hi32 is
3681 non-zero, so start the mask on the first bit of the hi32
3686 unsigned long himask, lomask;
3690 himask = 0xffff >> (32 - shift);
3691 lomask = (0xffff << shift) & 0xffffffff;
3695 himask = 0xffff << (shift - 32);
3698 if ((hi32.X_add_number & ~(offsetT) himask) == 0
3699 && (lo32.X_add_number & ~(offsetT) lomask) == 0)
3703 tmp.X_op = O_constant;
3705 tmp.X_add_number = ((hi32.X_add_number << (32 - shift))
3706 | (lo32.X_add_number >> shift));
3708 tmp.X_add_number = hi32.X_add_number >> (shift - 32);
3709 macro_build ((char *) NULL, counter, &tmp,
3710 "ori", "t,r,i", reg, 0,
3711 (int) BFD_RELOC_LO16);
3712 macro_build ((char *) NULL, counter, (expressionS *) NULL,
3713 (shift >= 32) ? "dsll32" : "dsll",
3715 (shift >= 32) ? shift - 32 : shift);
3720 while (shift <= (64 - 16));
3722 /* Find the bit number of the lowest one bit, and store the
3723 shifted value in hi/lo. */
3724 hi = (unsigned long) (hi32.X_add_number & 0xffffffff);
3725 lo = (unsigned long) (lo32.X_add_number & 0xffffffff);
3729 while ((lo & 1) == 0)
3734 lo |= (hi & (((unsigned long) 1 << bit) - 1)) << (32 - bit);
3740 while ((hi & 1) == 0)
3749 /* Optimize if the shifted value is a (power of 2) - 1. */
3750 if ((hi == 0 && ((lo + 1) & lo) == 0)
3751 || (lo == 0xffffffff && ((hi + 1) & hi) == 0))
3753 shift = COUNT_TOP_ZEROES ((unsigned int) hi32.X_add_number);
3758 /* This instruction will set the register to be all
3760 tmp.X_op = O_constant;
3761 tmp.X_add_number = (offsetT) -1;
3762 macro_build ((char *) NULL, counter, &tmp, "addiu", "t,r,j",
3763 reg, 0, (int) BFD_RELOC_LO16);
3767 macro_build ((char *) NULL, counter, (expressionS *) NULL,
3768 (bit >= 32) ? "dsll32" : "dsll",
3770 (bit >= 32) ? bit - 32 : bit);
3772 macro_build ((char *) NULL, counter, (expressionS *) NULL,
3773 (shift >= 32) ? "dsrl32" : "dsrl",
3775 (shift >= 32) ? shift - 32 : shift);
3780 /* Sign extend hi32 before calling load_register, because we can
3781 generally get better code when we load a sign extended value. */
3782 if ((hi32.X_add_number & 0x80000000) != 0)
3783 hi32.X_add_number |= ~(offsetT) 0xffffffff;
3784 load_register (counter, reg, &hi32, 0);
3787 if ((lo32.X_add_number & 0xffff0000) == 0)
3791 macro_build ((char *) NULL, counter, (expressionS *) NULL,
3792 "dsll32", "d,w,<", reg, freg, 0);
3800 if ((freg == 0) && (lo32.X_add_number == (offsetT) 0xffffffff))
3802 macro_build ((char *) NULL, counter, &lo32, "lui", "t,u", reg,
3803 (int) BFD_RELOC_HI16);
3804 macro_build ((char *) NULL, counter, (expressionS *) NULL,
3805 "dsrl32", "d,w,<", reg, reg, 0);
3811 macro_build ((char *) NULL, counter, (expressionS *) NULL, "dsll",
3812 "d,w,<", reg, freg, 16);
3816 mid16.X_add_number >>= 16;
3817 macro_build ((char *) NULL, counter, &mid16, "ori", "t,r,i", reg,
3818 freg, (int) BFD_RELOC_LO16);
3819 macro_build ((char *) NULL, counter, (expressionS *) NULL, "dsll",
3820 "d,w,<", reg, reg, 16);
3823 if ((lo32.X_add_number & 0xffff) != 0)
3824 macro_build ((char *) NULL, counter, &lo32, "ori", "t,r,i", reg, freg,
3825 (int) BFD_RELOC_LO16);
3828 /* Load an address into a register. */
3831 load_address (counter, reg, ep, used_at)
3839 if (ep->X_op != O_constant
3840 && ep->X_op != O_symbol)
3842 as_bad (_("expression too complex"));
3843 ep->X_op = O_constant;
3846 if (ep->X_op == O_constant)
3848 load_register (counter, reg, ep, HAVE_64BIT_ADDRESSES);
3852 if (mips_pic == NO_PIC)
3854 /* If this is a reference to a GP relative symbol, we want
3855 addiu $reg,$gp,<sym> (BFD_RELOC_GPREL16)
3857 lui $reg,<sym> (BFD_RELOC_HI16_S)
3858 addiu $reg,$reg,<sym> (BFD_RELOC_LO16)
3859 If we have an addend, we always use the latter form.
3861 With 64bit address space and a usable $at we want
3862 lui $reg,<sym> (BFD_RELOC_MIPS_HIGHEST)
3863 lui $at,<sym> (BFD_RELOC_HI16_S)
3864 daddiu $reg,<sym> (BFD_RELOC_MIPS_HIGHER)
3865 daddiu $at,<sym> (BFD_RELOC_LO16)
3869 If $at is already in use, we use a path which is suboptimal
3870 on superscalar processors.
3871 lui $reg,<sym> (BFD_RELOC_MIPS_HIGHEST)
3872 daddiu $reg,<sym> (BFD_RELOC_MIPS_HIGHER)
3874 daddiu $reg,<sym> (BFD_RELOC_HI16_S)
3876 daddiu $reg,<sym> (BFD_RELOC_LO16)
3878 if (HAVE_64BIT_ADDRESSES)
3880 /* We don't do GP optimization for now because RELAX_ENCODE can't
3881 hold the data for such large chunks. */
3883 if (*used_at == 0 && ! mips_opts.noat)
3885 macro_build (p, counter, ep, "lui", "t,u",
3886 reg, (int) BFD_RELOC_MIPS_HIGHEST);
3887 macro_build (p, counter, ep, "lui", "t,u",
3888 AT, (int) BFD_RELOC_HI16_S);
3889 macro_build (p, counter, ep, "daddiu", "t,r,j",
3890 reg, reg, (int) BFD_RELOC_MIPS_HIGHER);
3891 macro_build (p, counter, ep, "daddiu", "t,r,j",
3892 AT, AT, (int) BFD_RELOC_LO16);
3893 macro_build (p, counter, (expressionS *) NULL, "dsll32",
3894 "d,w,<", reg, reg, 0);
3895 macro_build (p, counter, (expressionS *) NULL, "daddu",
3896 "d,v,t", reg, reg, AT);
3901 macro_build (p, counter, ep, "lui", "t,u",
3902 reg, (int) BFD_RELOC_MIPS_HIGHEST);
3903 macro_build (p, counter, ep, "daddiu", "t,r,j",
3904 reg, reg, (int) BFD_RELOC_MIPS_HIGHER);
3905 macro_build (p, counter, (expressionS *) NULL, "dsll",
3906 "d,w,<", reg, reg, 16);
3907 macro_build (p, counter, ep, "daddiu", "t,r,j",
3908 reg, reg, (int) BFD_RELOC_HI16_S);
3909 macro_build (p, counter, (expressionS *) NULL, "dsll",
3910 "d,w,<", reg, reg, 16);
3911 macro_build (p, counter, ep, "daddiu", "t,r,j",
3912 reg, reg, (int) BFD_RELOC_LO16);
3917 if ((valueT) ep->X_add_number <= MAX_GPREL_OFFSET
3918 && ! nopic_need_relax (ep->X_add_symbol, 1))
3921 macro_build ((char *) NULL, counter, ep,
3922 HAVE_32BIT_ADDRESSES ? HAVE_NEWABI
3923 ? "addi" : "addiu" : "daddiu", "t,r,j",
3924 reg, mips_gp_register, (int) BFD_RELOC_GPREL16);
3925 p = frag_var (rs_machine_dependent, 8, 0,
3926 RELAX_ENCODE (4, 8, 0, 4, 0,
3927 mips_opts.warn_about_macros),
3928 ep->X_add_symbol, 0, NULL);
3930 macro_build_lui (p, counter, ep, reg);
3933 macro_build (p, counter, ep,
3934 HAVE_32BIT_ADDRESSES ? HAVE_NEWABI
3935 ? "addi" : "addiu" : "daddiu",
3936 "t,r,j", reg, reg, (int) BFD_RELOC_LO16);
3939 else if (mips_pic == SVR4_PIC && ! mips_big_got)
3943 /* If this is a reference to an external symbol, we want
3944 lw $reg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
3946 lw $reg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
3948 addiu $reg,$reg,<sym> (BFD_RELOC_LO16)
3949 If there is a constant, it must be added in after.
3951 If we have NewABI, we want
3952 lw $reg,<sym+cst>($gp) (BFD_RELOC_MIPS_GOT_DISP)
3953 unless we're referencing a global symbol with a non-zero
3954 offset, in which case cst must be added separately. */
3959 if (ep->X_add_number)
3961 frag_now->tc_frag_data.tc_fr_offset =
3962 ex.X_add_number = ep->X_add_number;
3963 ep->X_add_number = 0;
3964 macro_build ((char *) NULL, counter, ep,
3965 HAVE_32BIT_ADDRESSES ? "lw" : "ld", "t,o(b)", reg,
3966 (int) BFD_RELOC_MIPS_GOT_DISP, mips_gp_register);
3967 if (ex.X_add_number < -0x8000 || ex.X_add_number >= 0x8000)
3968 as_bad (_("PIC code offset overflow (max 16 signed bits)"));
3969 ex.X_op = O_constant;
3970 macro_build ((char *) NULL, counter, &ex,
3971 HAVE_32BIT_ADDRESSES ? "addi" : "daddiu",
3972 "t,r,j", reg, reg, (int) BFD_RELOC_LO16);
3973 p = frag_var (rs_machine_dependent, 8, 0,
3974 RELAX_ENCODE (8, 4, 0, 0, 0,
3975 mips_opts.warn_about_macros),
3976 ep->X_add_symbol, 0, (char *) NULL);
3977 ep->X_add_number = ex.X_add_number;
3980 macro_build (p, counter, ep,
3981 HAVE_32BIT_ADDRESSES ? "lw" : "ld", "t,o(b)", reg,
3982 (int) BFD_RELOC_MIPS_GOT_DISP, mips_gp_register);
3986 /* To avoid confusion in tc_gen_reloc, we must ensure
3987 that this does not become a variant frag. */
3988 frag_wane (frag_now);
3994 ex.X_add_number = ep->X_add_number;
3995 ep->X_add_number = 0;
3997 macro_build ((char *) NULL, counter, ep,
3998 HAVE_32BIT_ADDRESSES ? "lw" : "ld", "t,o(b)",
3999 reg, (int) BFD_RELOC_MIPS_GOT16, mips_gp_register);
4000 macro_build ((char *) NULL, counter, (expressionS *) NULL, "nop", "");
4001 p = frag_var (rs_machine_dependent, 4, 0,
4002 RELAX_ENCODE (0, 4, -8, 0, 0, mips_opts.warn_about_macros),
4003 ep->X_add_symbol, (offsetT) 0, (char *) NULL);
4004 macro_build (p, counter, ep,
4005 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
4006 "t,r,j", reg, reg, (int) BFD_RELOC_LO16);
4008 if (ex.X_add_number != 0)
4010 if (ex.X_add_number < -0x8000 || ex.X_add_number >= 0x8000)
4011 as_bad (_("PIC code offset overflow (max 16 signed bits)"));
4012 ex.X_op = O_constant;
4013 macro_build ((char *) NULL, counter, &ex,
4014 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
4015 "t,r,j", reg, reg, (int) BFD_RELOC_LO16);
4019 else if (mips_pic == SVR4_PIC)
4024 /* This is the large GOT case. If this is a reference to an
4025 external symbol, we want
4026 lui $reg,<sym> (BFD_RELOC_MIPS_GOT_HI16)
4028 lw $reg,<sym>($reg) (BFD_RELOC_MIPS_GOT_LO16)
4030 Otherwise, for a reference to a local symbol in old ABI, we want
4031 lw $reg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
4033 addiu $reg,$reg,<sym> (BFD_RELOC_LO16)
4034 If there is a constant, it must be added in after.
4036 In the NewABI, for local symbols, with or without offsets, we want:
4037 lw $reg,<sym>($gp) (BFD_RELOC_MIPS_GOT_PAGE)
4038 addiu $reg,$reg,<sym> (BFD_RELOC_MIPS_GOT_OFST)
4044 frag_now->tc_frag_data.tc_fr_offset =
4045 ex.X_add_number = ep->X_add_number;
4046 ep->X_add_number = 0;
4047 macro_build ((char *) NULL, counter, ep, "lui", "t,u", reg,
4048 (int) BFD_RELOC_MIPS_GOT_HI16);
4049 macro_build ((char *) NULL, counter, (expressionS *) NULL,
4050 HAVE_32BIT_ADDRESSES ? "add" : "daddu", "d,v,t", reg,
4051 reg, mips_gp_register);
4052 macro_build ((char *) NULL, counter, ep,
4053 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
4054 "t,o(b)", reg, (int) BFD_RELOC_MIPS_GOT_LO16, reg);
4055 if (ex.X_add_number < -0x8000 || ex.X_add_number >= 0x8000)
4056 as_bad (_("PIC code offset overflow (max 16 signed bits)"));
4057 else if (ex.X_add_number)
4059 ex.X_op = O_constant;
4060 macro_build ((char *) NULL, counter, &ex,
4061 HAVE_32BIT_ADDRESSES ? "addi" : "daddiu",
4062 "t,r,j", reg, reg, (int) BFD_RELOC_LO16);
4065 ep->X_add_number = ex.X_add_number;
4066 p = frag_var (rs_machine_dependent, 8, 0,
4067 RELAX_ENCODE (ex.X_add_number ? 16 : 12, 8, 0, 4, 0,
4068 mips_opts.warn_about_macros),
4069 ep->X_add_symbol, 0, (char *) NULL);
4070 macro_build (p, counter, ep,
4071 HAVE_32BIT_ADDRESSES ? "lw" : "ld", "t,o(b)", reg,
4072 (int) BFD_RELOC_MIPS_GOT_PAGE, mips_gp_register);
4073 macro_build (p + 4, counter, ep,
4074 HAVE_32BIT_ADDRESSES ? "addi" : "daddiu", "t,r,j",
4075 reg, reg, (int) BFD_RELOC_MIPS_GOT_OFST);
4079 ex.X_add_number = ep->X_add_number;
4080 ep->X_add_number = 0;
4081 if (reg_needs_delay (mips_gp_register))
4086 macro_build ((char *) NULL, counter, ep, "lui", "t,u", reg,
4087 (int) BFD_RELOC_MIPS_GOT_HI16);
4088 macro_build ((char *) NULL, counter, (expressionS *) NULL,
4089 HAVE_32BIT_ADDRESSES ? "addu" : "daddu", "d,v,t", reg,
4090 reg, mips_gp_register);
4091 macro_build ((char *) NULL, counter, ep,
4092 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
4093 "t,o(b)", reg, (int) BFD_RELOC_MIPS_GOT_LO16, reg);
4094 p = frag_var (rs_machine_dependent, 12 + off, 0,
4095 RELAX_ENCODE (12, 12 + off, off, 8 + off, 0,
4096 mips_opts.warn_about_macros),
4097 ep->X_add_symbol, 0, NULL);
4100 /* We need a nop before loading from $gp. This special
4101 check is required because the lui which starts the main
4102 instruction stream does not refer to $gp, and so will not
4103 insert the nop which may be required. */
4104 macro_build (p, counter, (expressionS *) NULL, "nop", "");
4107 macro_build (p, counter, ep,
4108 HAVE_32BIT_ADDRESSES ? "lw" : "ld", "t,o(b)", reg,
4109 (int) BFD_RELOC_MIPS_GOT16, mips_gp_register);
4111 macro_build (p, counter, (expressionS *) NULL, "nop", "");
4113 macro_build (p, counter, ep,
4114 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
4115 "t,r,j", reg, reg, (int) BFD_RELOC_LO16);
4117 if (ex.X_add_number != 0)
4119 if (ex.X_add_number < -0x8000 || ex.X_add_number >= 0x8000)
4120 as_bad (_("PIC code offset overflow (max 16 signed bits)"));
4121 ex.X_op = O_constant;
4122 macro_build ((char *) NULL, counter, &ex,
4123 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
4124 "t,r,j", reg, reg, (int) BFD_RELOC_LO16);
4128 else if (mips_pic == EMBEDDED_PIC)
4131 addiu $reg,$gp,<sym> (BFD_RELOC_GPREL16)
4133 macro_build ((char *) NULL, counter, ep,
4134 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
4135 "t,r,j", reg, mips_gp_register, (int) BFD_RELOC_GPREL16);
4141 /* Move the contents of register SOURCE into register DEST. */
4144 move_register (counter, dest, source)
4149 macro_build ((char *) NULL, counter, (expressionS *) NULL,
4150 HAVE_32BIT_GPRS ? "addu" : "daddu",
4151 "d,v,t", dest, source, 0);
4156 * This routine implements the seemingly endless macro or synthesized
4157 * instructions and addressing modes in the mips assembly language. Many
4158 * of these macros are simple and are similar to each other. These could
4159 * probably be handled by some kind of table or grammer aproach instead of
4160 * this verbose method. Others are not simple macros but are more like
4161 * optimizing code generation.
4162 * One interesting optimization is when several store macros appear
4163 * consecutivly that would load AT with the upper half of the same address.
4164 * The ensuing load upper instructions are ommited. This implies some kind
4165 * of global optimization. We currently only optimize within a single macro.
4166 * For many of the load and store macros if the address is specified as a
4167 * constant expression in the first 64k of memory (ie ld $2,0x4000c) we
4168 * first load register 'at' with zero and use it as the base register. The
4169 * mips assembler simply uses register $zero. Just one tiny optimization
4174 struct mips_cl_insn *ip;
4176 register int treg, sreg, dreg, breg;
4192 bfd_reloc_code_real_type r;
4193 int hold_mips_optimize;
4195 assert (! mips_opts.mips16);
4197 treg = (ip->insn_opcode >> 16) & 0x1f;
4198 dreg = (ip->insn_opcode >> 11) & 0x1f;
4199 sreg = breg = (ip->insn_opcode >> 21) & 0x1f;
4200 mask = ip->insn_mo->mask;
4202 expr1.X_op = O_constant;
4203 expr1.X_op_symbol = NULL;
4204 expr1.X_add_symbol = NULL;
4205 expr1.X_add_number = 1;
4207 /* Umatched fixups should not be put in the same frag as a relaxable
4208 macro. For example, suppose we have:
4212 addiu $4,$4,%lo(l1) # 3
4214 If instructions 1 and 2 were put in the same frag, md_frob_file would
4215 move the fixup for #1 after the fixups for the "unrelaxed" version of
4216 #2. This would confuse tc_gen_reloc, which expects the relocations
4217 for #2 to be the last for that frag.
4219 Also, if tc_gen_reloc sees certain relocations in a variant frag,
4220 it assumes that they belong to a relaxable macro. We mustn't put
4221 other uses of such relocations into a variant frag.
4223 To avoid both problems, finish the current frag it contains a
4224 %reloc() operator. The macro then goes into a new frag. */
4225 if (prev_reloc_op_frag == frag_now)
4227 frag_wane (frag_now);
4241 mips_emit_delays (TRUE);
4242 ++mips_opts.noreorder;
4243 mips_any_noreorder = 1;
4245 expr1.X_add_number = 8;
4246 macro_build ((char *) NULL, &icnt, &expr1, "bgez", "s,p", sreg);
4248 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "",
4251 move_register (&icnt, dreg, sreg);
4252 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
4253 dbl ? "dsub" : "sub", "d,v,t", dreg, 0, sreg);
4255 --mips_opts.noreorder;
4276 if (imm_expr.X_op == O_constant
4277 && imm_expr.X_add_number >= -0x8000
4278 && imm_expr.X_add_number < 0x8000)
4280 macro_build ((char *) NULL, &icnt, &imm_expr, s, "t,r,j", treg, sreg,
4281 (int) BFD_RELOC_LO16);
4284 load_register (&icnt, AT, &imm_expr, dbl);
4285 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s2, "d,v,t",
4305 if (imm_expr.X_op == O_constant
4306 && imm_expr.X_add_number >= 0
4307 && imm_expr.X_add_number < 0x10000)
4309 if (mask != M_NOR_I)
4310 macro_build ((char *) NULL, &icnt, &imm_expr, s, "t,r,i", treg,
4311 sreg, (int) BFD_RELOC_LO16);
4314 macro_build ((char *) NULL, &icnt, &imm_expr, "ori", "t,r,i",
4315 treg, sreg, (int) BFD_RELOC_LO16);
4316 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nor",
4317 "d,v,t", treg, treg, 0);
4322 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_GPRS);
4323 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s2, "d,v,t",
4341 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
4343 macro_build ((char *) NULL, &icnt, &offset_expr, s, "s,t,p", sreg,
4347 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_GPRS);
4348 macro_build ((char *) NULL, &icnt, &offset_expr, s, "s,t,p", sreg, AT);
4356 macro_build ((char *) NULL, &icnt, &offset_expr,
4357 likely ? "bgezl" : "bgez", "s,p", sreg);
4362 macro_build ((char *) NULL, &icnt, &offset_expr,
4363 likely ? "blezl" : "blez", "s,p", treg);
4366 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "slt", "d,v,t",
4368 macro_build ((char *) NULL, &icnt, &offset_expr,
4369 likely ? "beql" : "beq", "s,t,p", AT, 0);
4375 /* check for > max integer */
4376 maxnum = 0x7fffffff;
4377 if (HAVE_64BIT_GPRS && sizeof (maxnum) > 4)
4384 if (imm_expr.X_op == O_constant
4385 && imm_expr.X_add_number >= maxnum
4386 && (HAVE_32BIT_GPRS || sizeof (maxnum) > 4))
4389 /* result is always false */
4393 as_warn (_("Branch %s is always false (nop)"),
4395 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop",
4401 as_warn (_("Branch likely %s is always false"),
4403 macro_build ((char *) NULL, &icnt, &offset_expr, "bnel",
4408 if (imm_expr.X_op != O_constant)
4409 as_bad (_("Unsupported large constant"));
4410 ++imm_expr.X_add_number;
4414 if (mask == M_BGEL_I)
4416 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
4418 macro_build ((char *) NULL, &icnt, &offset_expr,
4419 likely ? "bgezl" : "bgez", "s,p", sreg);
4422 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 1)
4424 macro_build ((char *) NULL, &icnt, &offset_expr,
4425 likely ? "bgtzl" : "bgtz", "s,p", sreg);
4428 maxnum = 0x7fffffff;
4429 if (HAVE_64BIT_GPRS && sizeof (maxnum) > 4)
4436 maxnum = - maxnum - 1;
4437 if (imm_expr.X_op == O_constant
4438 && imm_expr.X_add_number <= maxnum
4439 && (HAVE_32BIT_GPRS || sizeof (maxnum) > 4))
4442 /* result is always true */
4443 as_warn (_("Branch %s is always true"), ip->insn_mo->name);
4444 macro_build ((char *) NULL, &icnt, &offset_expr, "b", "p");
4447 set_at (&icnt, sreg, 0);
4448 macro_build ((char *) NULL, &icnt, &offset_expr,
4449 likely ? "beql" : "beq", "s,t,p", AT, 0);
4459 macro_build ((char *) NULL, &icnt, &offset_expr,
4460 likely ? "beql" : "beq", "s,t,p", 0, treg);
4463 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sltu",
4464 "d,v,t", AT, sreg, treg);
4465 macro_build ((char *) NULL, &icnt, &offset_expr,
4466 likely ? "beql" : "beq", "s,t,p", AT, 0);
4474 && imm_expr.X_op == O_constant
4475 && imm_expr.X_add_number == (offsetT) 0xffffffff))
4477 if (imm_expr.X_op != O_constant)
4478 as_bad (_("Unsupported large constant"));
4479 ++imm_expr.X_add_number;
4483 if (mask == M_BGEUL_I)
4485 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
4487 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 1)
4489 macro_build ((char *) NULL, &icnt, &offset_expr,
4490 likely ? "bnel" : "bne", "s,t,p", sreg, 0);
4493 set_at (&icnt, sreg, 1);
4494 macro_build ((char *) NULL, &icnt, &offset_expr,
4495 likely ? "beql" : "beq", "s,t,p", AT, 0);
4503 macro_build ((char *) NULL, &icnt, &offset_expr,
4504 likely ? "bgtzl" : "bgtz", "s,p", sreg);
4509 macro_build ((char *) NULL, &icnt, &offset_expr,
4510 likely ? "bltzl" : "bltz", "s,p", treg);
4513 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "slt", "d,v,t",
4515 macro_build ((char *) NULL, &icnt, &offset_expr,
4516 likely ? "bnel" : "bne", "s,t,p", AT, 0);
4524 macro_build ((char *) NULL, &icnt, &offset_expr,
4525 likely ? "bnel" : "bne", "s,t,p", sreg, 0);
4530 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sltu",
4531 "d,v,t", AT, treg, sreg);
4532 macro_build ((char *) NULL, &icnt, &offset_expr,
4533 likely ? "bnel" : "bne", "s,t,p", AT, 0);
4541 macro_build ((char *) NULL, &icnt, &offset_expr,
4542 likely ? "blezl" : "blez", "s,p", sreg);
4547 macro_build ((char *) NULL, &icnt, &offset_expr,
4548 likely ? "bgezl" : "bgez", "s,p", treg);
4551 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "slt", "d,v,t",
4553 macro_build ((char *) NULL, &icnt, &offset_expr,
4554 likely ? "beql" : "beq", "s,t,p", AT, 0);
4560 maxnum = 0x7fffffff;
4561 if (HAVE_64BIT_GPRS && sizeof (maxnum) > 4)
4568 if (imm_expr.X_op == O_constant
4569 && imm_expr.X_add_number >= maxnum
4570 && (HAVE_32BIT_GPRS || sizeof (maxnum) > 4))
4572 if (imm_expr.X_op != O_constant)
4573 as_bad (_("Unsupported large constant"));
4574 ++imm_expr.X_add_number;
4578 if (mask == M_BLTL_I)
4580 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
4582 macro_build ((char *) NULL, &icnt, &offset_expr,
4583 likely ? "bltzl" : "bltz", "s,p", sreg);
4586 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 1)
4588 macro_build ((char *) NULL, &icnt, &offset_expr,
4589 likely ? "blezl" : "blez", "s,p", sreg);
4592 set_at (&icnt, sreg, 0);
4593 macro_build ((char *) NULL, &icnt, &offset_expr,
4594 likely ? "bnel" : "bne", "s,t,p", AT, 0);
4602 macro_build ((char *) NULL, &icnt, &offset_expr,
4603 likely ? "beql" : "beq", "s,t,p", sreg, 0);
4608 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sltu",
4609 "d,v,t", AT, treg, sreg);
4610 macro_build ((char *) NULL, &icnt, &offset_expr,
4611 likely ? "beql" : "beq", "s,t,p", AT, 0);
4619 && imm_expr.X_op == O_constant
4620 && imm_expr.X_add_number == (offsetT) 0xffffffff))
4622 if (imm_expr.X_op != O_constant)
4623 as_bad (_("Unsupported large constant"));
4624 ++imm_expr.X_add_number;
4628 if (mask == M_BLTUL_I)
4630 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
4632 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 1)
4634 macro_build ((char *) NULL, &icnt, &offset_expr,
4635 likely ? "beql" : "beq",
4639 set_at (&icnt, sreg, 1);
4640 macro_build ((char *) NULL, &icnt, &offset_expr,
4641 likely ? "bnel" : "bne", "s,t,p", AT, 0);
4649 macro_build ((char *) NULL, &icnt, &offset_expr,
4650 likely ? "bltzl" : "bltz", "s,p", sreg);
4655 macro_build ((char *) NULL, &icnt, &offset_expr,
4656 likely ? "bgtzl" : "bgtz", "s,p", treg);
4659 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "slt", "d,v,t",
4661 macro_build ((char *) NULL, &icnt, &offset_expr,
4662 likely ? "bnel" : "bne", "s,t,p", AT, 0);
4672 macro_build ((char *) NULL, &icnt, &offset_expr,
4673 likely ? "bnel" : "bne", "s,t,p", 0, treg);
4676 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sltu",
4679 macro_build ((char *) NULL, &icnt, &offset_expr,
4680 likely ? "bnel" : "bne", "s,t,p", AT, 0);
4695 as_warn (_("Divide by zero."));
4697 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "teq",
4700 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "break",
4705 mips_emit_delays (TRUE);
4706 ++mips_opts.noreorder;
4707 mips_any_noreorder = 1;
4710 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "teq",
4711 "s,t,q", treg, 0, 7);
4712 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
4713 dbl ? "ddiv" : "div", "z,s,t", sreg, treg);
4717 expr1.X_add_number = 8;
4718 macro_build ((char *) NULL, &icnt, &expr1, "bne", "s,t,p", treg, 0);
4719 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
4720 dbl ? "ddiv" : "div", "z,s,t", sreg, treg);
4721 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "break",
4724 expr1.X_add_number = -1;
4725 macro_build ((char *) NULL, &icnt, &expr1,
4726 dbl ? "daddiu" : "addiu",
4727 "t,r,j", AT, 0, (int) BFD_RELOC_LO16);
4728 expr1.X_add_number = mips_trap ? (dbl ? 12 : 8) : (dbl ? 20 : 16);
4729 macro_build ((char *) NULL, &icnt, &expr1, "bne", "s,t,p", treg, AT);
4732 expr1.X_add_number = 1;
4733 macro_build ((char *) NULL, &icnt, &expr1, "daddiu", "t,r,j", AT, 0,
4734 (int) BFD_RELOC_LO16);
4735 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "dsll32",
4736 "d,w,<", AT, AT, 31);
4740 expr1.X_add_number = 0x80000000;
4741 macro_build ((char *) NULL, &icnt, &expr1, "lui", "t,u", AT,
4742 (int) BFD_RELOC_HI16);
4746 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "teq",
4747 "s,t,q", sreg, AT, 6);
4748 /* We want to close the noreorder block as soon as possible, so
4749 that later insns are available for delay slot filling. */
4750 --mips_opts.noreorder;
4754 expr1.X_add_number = 8;
4755 macro_build ((char *) NULL, &icnt, &expr1, "bne", "s,t,p", sreg, AT);
4756 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "",
4759 /* We want to close the noreorder block as soon as possible, so
4760 that later insns are available for delay slot filling. */
4761 --mips_opts.noreorder;
4763 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "break",
4766 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "d", dreg);
4805 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
4807 as_warn (_("Divide by zero."));
4809 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "teq",
4812 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "break",
4816 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 1)
4818 if (strcmp (s2, "mflo") == 0)
4819 move_register (&icnt, dreg, sreg);
4821 move_register (&icnt, dreg, 0);
4824 if (imm_expr.X_op == O_constant
4825 && imm_expr.X_add_number == -1
4826 && s[strlen (s) - 1] != 'u')
4828 if (strcmp (s2, "mflo") == 0)
4830 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
4831 dbl ? "dneg" : "neg", "d,w", dreg, sreg);
4834 move_register (&icnt, dreg, 0);
4838 load_register (&icnt, AT, &imm_expr, dbl);
4839 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "z,s,t",
4841 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s2, "d", dreg);
4860 mips_emit_delays (TRUE);
4861 ++mips_opts.noreorder;
4862 mips_any_noreorder = 1;
4865 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "teq",
4866 "s,t,q", treg, 0, 7);
4867 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "z,s,t",
4869 /* We want to close the noreorder block as soon as possible, so
4870 that later insns are available for delay slot filling. */
4871 --mips_opts.noreorder;
4875 expr1.X_add_number = 8;
4876 macro_build ((char *) NULL, &icnt, &expr1, "bne", "s,t,p", treg, 0);
4877 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "z,s,t",
4880 /* We want to close the noreorder block as soon as possible, so
4881 that later insns are available for delay slot filling. */
4882 --mips_opts.noreorder;
4883 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "break",
4886 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s2, "d", dreg);
4892 /* Load the address of a symbol into a register. If breg is not
4893 zero, we then add a base register to it. */
4895 if (dbl && HAVE_32BIT_GPRS)
4896 as_warn (_("dla used to load 32-bit register"));
4898 if (! dbl && HAVE_64BIT_OBJECTS)
4899 as_warn (_("la used to load 64-bit address"));
4901 if (offset_expr.X_op == O_constant
4902 && offset_expr.X_add_number >= -0x8000
4903 && offset_expr.X_add_number < 0x8000)
4905 macro_build ((char *) NULL, &icnt, &offset_expr,
4906 (dbl || HAVE_64BIT_ADDRESSES) ? "daddiu" :
4907 HAVE_NEWABI ? "addi" : "addiu",
4908 "t,r,j", treg, sreg, (int) BFD_RELOC_LO16);
4923 /* When generating embedded PIC code, we permit expressions of
4926 la $treg,foo-bar($breg)
4927 where bar is an address in the current section. These are used
4928 when getting the addresses of functions. We don't permit
4929 X_add_number to be non-zero, because if the symbol is
4930 external the relaxing code needs to know that any addend is
4931 purely the offset to X_op_symbol. */
4932 if (mips_pic == EMBEDDED_PIC
4933 && offset_expr.X_op == O_subtract
4934 && (symbol_constant_p (offset_expr.X_op_symbol)
4935 ? S_GET_SEGMENT (offset_expr.X_op_symbol) == now_seg
4936 : (symbol_equated_p (offset_expr.X_op_symbol)
4938 (symbol_get_value_expression (offset_expr.X_op_symbol)
4941 && (offset_expr.X_add_number == 0
4942 || OUTPUT_FLAVOR == bfd_target_elf_flavour))
4948 macro_build ((char *) NULL, &icnt, &offset_expr, "lui", "t,u",
4949 tempreg, (int) BFD_RELOC_PCREL_HI16_S);
4953 macro_build ((char *) NULL, &icnt, &offset_expr, "lui", "t,u",
4954 tempreg, (int) BFD_RELOC_PCREL_HI16_S);
4955 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
4956 (dbl || HAVE_64BIT_ADDRESSES) ? "daddu" : "addu",
4957 "d,v,t", tempreg, tempreg, breg);
4959 macro_build ((char *) NULL, &icnt, &offset_expr,
4960 (dbl || HAVE_64BIT_ADDRESSES) ? "daddiu" : "addiu",
4961 "t,r,j", treg, tempreg, (int) BFD_RELOC_PCREL_LO16);
4967 if (offset_expr.X_op != O_symbol
4968 && offset_expr.X_op != O_constant)
4970 as_bad (_("expression too complex"));
4971 offset_expr.X_op = O_constant;
4974 if (offset_expr.X_op == O_constant)
4975 load_register (&icnt, tempreg, &offset_expr,
4976 ((mips_pic == EMBEDDED_PIC || mips_pic == NO_PIC)
4977 ? (dbl || HAVE_64BIT_ADDRESSES)
4978 : HAVE_64BIT_ADDRESSES));
4979 else if (mips_pic == NO_PIC)
4981 /* If this is a reference to a GP relative symbol, we want
4982 addiu $tempreg,$gp,<sym> (BFD_RELOC_GPREL16)
4984 lui $tempreg,<sym> (BFD_RELOC_HI16_S)
4985 addiu $tempreg,$tempreg,<sym> (BFD_RELOC_LO16)
4986 If we have a constant, we need two instructions anyhow,
4987 so we may as well always use the latter form.
4989 With 64bit address space and a usable $at we want
4990 lui $tempreg,<sym> (BFD_RELOC_MIPS_HIGHEST)
4991 lui $at,<sym> (BFD_RELOC_HI16_S)
4992 daddiu $tempreg,<sym> (BFD_RELOC_MIPS_HIGHER)
4993 daddiu $at,<sym> (BFD_RELOC_LO16)
4995 daddu $tempreg,$tempreg,$at
4997 If $at is already in use, we use a path which is suboptimal
4998 on superscalar processors.
4999 lui $tempreg,<sym> (BFD_RELOC_MIPS_HIGHEST)
5000 daddiu $tempreg,<sym> (BFD_RELOC_MIPS_HIGHER)
5002 daddiu $tempreg,<sym> (BFD_RELOC_HI16_S)
5004 daddiu $tempreg,<sym> (BFD_RELOC_LO16)
5007 if (HAVE_64BIT_ADDRESSES)
5009 /* We don't do GP optimization for now because RELAX_ENCODE can't
5010 hold the data for such large chunks. */
5012 if (used_at == 0 && ! mips_opts.noat)
5014 macro_build (p, &icnt, &offset_expr, "lui", "t,u",
5015 tempreg, (int) BFD_RELOC_MIPS_HIGHEST);
5016 macro_build (p, &icnt, &offset_expr, "lui", "t,u",
5017 AT, (int) BFD_RELOC_HI16_S);
5018 macro_build (p, &icnt, &offset_expr, "daddiu", "t,r,j",
5019 tempreg, tempreg, (int) BFD_RELOC_MIPS_HIGHER);
5020 macro_build (p, &icnt, &offset_expr, "daddiu", "t,r,j",
5021 AT, AT, (int) BFD_RELOC_LO16);
5022 macro_build (p, &icnt, (expressionS *) NULL, "dsll32",
5023 "d,w,<", tempreg, tempreg, 0);
5024 macro_build (p, &icnt, (expressionS *) NULL, "daddu",
5025 "d,v,t", tempreg, tempreg, AT);
5030 macro_build (p, &icnt, &offset_expr, "lui", "t,u",
5031 tempreg, (int) BFD_RELOC_MIPS_HIGHEST);
5032 macro_build (p, &icnt, &offset_expr, "daddiu", "t,r,j",
5033 tempreg, tempreg, (int) BFD_RELOC_MIPS_HIGHER);
5034 macro_build (p, &icnt, (expressionS *) NULL, "dsll", "d,w,<",
5035 tempreg, tempreg, 16);
5036 macro_build (p, &icnt, &offset_expr, "daddiu", "t,r,j",
5037 tempreg, tempreg, (int) BFD_RELOC_HI16_S);
5038 macro_build (p, &icnt, (expressionS *) NULL, "dsll", "d,w,<",
5039 tempreg, tempreg, 16);
5040 macro_build (p, &icnt, &offset_expr, "daddiu", "t,r,j",
5041 tempreg, tempreg, (int) BFD_RELOC_LO16);
5046 if ((valueT) offset_expr.X_add_number <= MAX_GPREL_OFFSET
5047 && ! nopic_need_relax (offset_expr.X_add_symbol, 1))
5050 macro_build ((char *) NULL, &icnt, &offset_expr,
5051 HAVE_NEWABI ? "addi" : "addiu",
5052 "t,r,j", tempreg, mips_gp_register,
5053 (int) BFD_RELOC_GPREL16);
5054 p = frag_var (rs_machine_dependent, 8, 0,
5055 RELAX_ENCODE (4, 8, 0, 4, 0,
5056 mips_opts.warn_about_macros),
5057 offset_expr.X_add_symbol, 0, NULL);
5059 macro_build_lui (p, &icnt, &offset_expr, tempreg);
5062 macro_build (p, &icnt, &offset_expr,
5063 HAVE_NEWABI ? "addi" : "addiu",
5064 "t,r,j", tempreg, tempreg, (int) BFD_RELOC_LO16);
5067 else if (mips_pic == SVR4_PIC && ! mips_big_got && ! HAVE_NEWABI)
5069 int lw_reloc_type = (int) BFD_RELOC_MIPS_GOT16;
5071 /* If this is a reference to an external symbol, and there
5072 is no constant, we want
5073 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
5074 or if tempreg is PIC_CALL_REG
5075 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_CALL16)
5076 For a local symbol, we want
5077 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
5079 addiu $tempreg,$tempreg,<sym> (BFD_RELOC_LO16)
5081 If we have a small constant, and this is a reference to
5082 an external symbol, we want
5083 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
5085 addiu $tempreg,$tempreg,<constant>
5086 For a local symbol, we want the same instruction
5087 sequence, but we output a BFD_RELOC_LO16 reloc on the
5090 If we have a large constant, and this is a reference to
5091 an external symbol, we want
5092 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
5093 lui $at,<hiconstant>
5094 addiu $at,$at,<loconstant>
5095 addu $tempreg,$tempreg,$at
5096 For a local symbol, we want the same instruction
5097 sequence, but we output a BFD_RELOC_LO16 reloc on the
5101 expr1.X_add_number = offset_expr.X_add_number;
5102 offset_expr.X_add_number = 0;
5104 if (expr1.X_add_number == 0 && tempreg == PIC_CALL_REG)
5105 lw_reloc_type = (int) BFD_RELOC_MIPS_CALL16;
5106 macro_build ((char *) NULL, &icnt, &offset_expr,
5107 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
5108 "t,o(b)", tempreg, lw_reloc_type, mips_gp_register);
5109 if (expr1.X_add_number == 0)
5118 /* We're going to put in an addu instruction using
5119 tempreg, so we may as well insert the nop right
5121 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5125 p = frag_var (rs_machine_dependent, 8 - off, 0,
5126 RELAX_ENCODE (0, 8 - off, -4 - off, 4 - off, 0,
5128 ? mips_opts.warn_about_macros
5130 offset_expr.X_add_symbol, 0, NULL);
5133 macro_build (p, &icnt, (expressionS *) NULL, "nop", "");
5136 macro_build (p, &icnt, &expr1,
5137 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
5138 "t,r,j", tempreg, tempreg, (int) BFD_RELOC_LO16);
5139 /* FIXME: If breg == 0, and the next instruction uses
5140 $tempreg, then if this variant case is used an extra
5141 nop will be generated. */
5143 else if (expr1.X_add_number >= -0x8000
5144 && expr1.X_add_number < 0x8000)
5146 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5148 macro_build ((char *) NULL, &icnt, &expr1,
5149 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
5150 "t,r,j", tempreg, tempreg, (int) BFD_RELOC_LO16);
5151 frag_var (rs_machine_dependent, 0, 0,
5152 RELAX_ENCODE (0, 0, -12, -4, 0, 0),
5153 offset_expr.X_add_symbol, 0, NULL);
5159 /* If we are going to add in a base register, and the
5160 target register and the base register are the same,
5161 then we are using AT as a temporary register. Since
5162 we want to load the constant into AT, we add our
5163 current AT (from the global offset table) and the
5164 register into the register now, and pretend we were
5165 not using a base register. */
5170 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5172 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5173 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
5174 "d,v,t", treg, AT, breg);
5180 /* Set mips_optimize around the lui instruction to avoid
5181 inserting an unnecessary nop after the lw. */
5182 hold_mips_optimize = mips_optimize;
5184 macro_build_lui (NULL, &icnt, &expr1, AT);
5185 mips_optimize = hold_mips_optimize;
5187 macro_build ((char *) NULL, &icnt, &expr1,
5188 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
5189 "t,r,j", AT, AT, (int) BFD_RELOC_LO16);
5190 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5191 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
5192 "d,v,t", tempreg, tempreg, AT);
5193 frag_var (rs_machine_dependent, 0, 0,
5194 RELAX_ENCODE (0, 0, -16 + off1, -8, 0, 0),
5195 offset_expr.X_add_symbol, 0, NULL);
5199 else if (mips_pic == SVR4_PIC && ! mips_big_got && HAVE_NEWABI)
5202 int lw_reloc_type = (int) BFD_RELOC_MIPS_GOT_DISP;
5205 /* If this is a reference to an external, and there is no
5206 constant, or local symbol (*), with or without a
5208 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT_DISP)
5209 or if tempreg is PIC_CALL_REG
5210 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_CALL16)
5212 If we have a small constant, and this is a reference to
5213 an external symbol, we want
5214 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT_DISP)
5215 addiu $tempreg,$tempreg,<constant>
5217 If we have a large constant, and this is a reference to
5218 an external symbol, we want
5219 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT_DISP)
5220 lui $at,<hiconstant>
5221 addiu $at,$at,<loconstant>
5222 addu $tempreg,$tempreg,$at
5224 (*) Other assemblers seem to prefer GOT_PAGE/GOT_OFST for
5225 local symbols, even though it introduces an additional
5229 if (offset_expr.X_add_number == 0 && tempreg == PIC_CALL_REG)
5230 lw_reloc_type = (int) BFD_RELOC_MIPS_CALL16;
5231 if (offset_expr.X_add_number)
5233 frag_now->tc_frag_data.tc_fr_offset =
5234 expr1.X_add_number = offset_expr.X_add_number;
5235 offset_expr.X_add_number = 0;
5237 macro_build ((char *) NULL, &icnt, &offset_expr,
5238 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
5239 "t,o(b)", tempreg, lw_reloc_type,
5242 if (expr1.X_add_number >= -0x8000
5243 && expr1.X_add_number < 0x8000)
5245 macro_build ((char *) NULL, &icnt, &expr1,
5246 HAVE_32BIT_ADDRESSES ? "addi" : "daddiu",
5247 "t,r,j", tempreg, tempreg,
5248 (int) BFD_RELOC_LO16);
5249 p = frag_var (rs_machine_dependent, 4, 0,
5250 RELAX_ENCODE (8, 4, 0, 0, 0, 0),
5251 offset_expr.X_add_symbol, 0, NULL);
5253 else if (IS_SEXT_32BIT_NUM (expr1.X_add_number))
5257 /* If we are going to add in a base register, and the
5258 target register and the base register are the same,
5259 then we are using AT as a temporary register. Since
5260 we want to load the constant into AT, we add our
5261 current AT (from the global offset table) and the
5262 register into the register now, and pretend we were
5263 not using a base register. */
5268 assert (tempreg == AT);
5269 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5270 HAVE_32BIT_ADDRESSES ? "add" : "daddu",
5271 "d,v,t", treg, AT, breg);
5276 macro_build_lui ((char *) NULL, &icnt, &expr1, AT);
5277 macro_build ((char *) NULL, &icnt, &expr1,
5278 HAVE_32BIT_ADDRESSES ? "addi" : "daddiu",
5279 "t,r,j", AT, AT, (int) BFD_RELOC_LO16);
5280 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5281 HAVE_32BIT_ADDRESSES ? "add" : "daddu",
5282 "d,v,t", dreg, dreg, AT);
5284 p = frag_var (rs_machine_dependent, 4 + adj, 0,
5285 RELAX_ENCODE (16 + adj, 4 + adj,
5287 offset_expr.X_add_symbol, 0, NULL);
5292 as_bad (_("PIC code offset overflow (max 32 signed bits)"));
5294 offset_expr.X_add_number = expr1.X_add_number;
5296 macro_build (p, &icnt, &offset_expr,
5297 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
5298 "t,o(b)", tempreg, (int) BFD_RELOC_MIPS_GOT_DISP,
5302 macro_build (p + 4, &icnt, (expressionS *) NULL,
5303 HAVE_32BIT_ADDRESSES ? "add" : "daddu",
5304 "d,v,t", treg, tempreg, breg);
5311 macro_build ((char *) NULL, &icnt, &offset_expr,
5312 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
5313 "t,o(b)", tempreg, lw_reloc_type,
5315 if (lw_reloc_type != BFD_RELOC_MIPS_GOT_DISP)
5316 p = frag_var (rs_machine_dependent, 0, 0,
5317 RELAX_ENCODE (0, 0, -4, 0, 0, 0),
5318 offset_expr.X_add_symbol, 0, NULL);
5323 /* To avoid confusion in tc_gen_reloc, we must ensure
5324 that this does not become a variant frag. */
5325 frag_wane (frag_now);
5329 else if (mips_pic == SVR4_PIC && ! HAVE_NEWABI)
5333 int lui_reloc_type = (int) BFD_RELOC_MIPS_GOT_HI16;
5334 int lw_reloc_type = (int) BFD_RELOC_MIPS_GOT_LO16;
5335 int local_reloc_type = (int) BFD_RELOC_MIPS_GOT16;
5337 /* This is the large GOT case. If this is a reference to an
5338 external symbol, and there is no constant, we want
5339 lui $tempreg,<sym> (BFD_RELOC_MIPS_GOT_HI16)
5340 addu $tempreg,$tempreg,$gp
5341 lw $tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_LO16)
5342 or if tempreg is PIC_CALL_REG
5343 lui $tempreg,<sym> (BFD_RELOC_MIPS_CALL_HI16)
5344 addu $tempreg,$tempreg,$gp
5345 lw $tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_CALL_LO16)
5346 For a local symbol, we want
5347 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
5349 addiu $tempreg,$tempreg,<sym> (BFD_RELOC_LO16)
5351 If we have a small constant, and this is a reference to
5352 an external symbol, we want
5353 lui $tempreg,<sym> (BFD_RELOC_MIPS_GOT_HI16)
5354 addu $tempreg,$tempreg,$gp
5355 lw $tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_LO16)
5357 addiu $tempreg,$tempreg,<constant>
5358 For a local symbol, we want
5359 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
5361 addiu $tempreg,$tempreg,<constant> (BFD_RELOC_LO16)
5363 If we have a large constant, and this is a reference to
5364 an external symbol, we want
5365 lui $tempreg,<sym> (BFD_RELOC_MIPS_GOT_HI16)
5366 addu $tempreg,$tempreg,$gp
5367 lw $tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_LO16)
5368 lui $at,<hiconstant>
5369 addiu $at,$at,<loconstant>
5370 addu $tempreg,$tempreg,$at
5371 For a local symbol, we want
5372 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
5373 lui $at,<hiconstant>
5374 addiu $at,$at,<loconstant> (BFD_RELOC_LO16)
5375 addu $tempreg,$tempreg,$at
5378 expr1.X_add_number = offset_expr.X_add_number;
5379 offset_expr.X_add_number = 0;
5381 if (reg_needs_delay (mips_gp_register))
5385 if (expr1.X_add_number == 0 && tempreg == PIC_CALL_REG)
5387 lui_reloc_type = (int) BFD_RELOC_MIPS_CALL_HI16;
5388 lw_reloc_type = (int) BFD_RELOC_MIPS_CALL_LO16;
5390 macro_build ((char *) NULL, &icnt, &offset_expr, "lui", "t,u",
5391 tempreg, lui_reloc_type);
5392 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5393 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
5394 "d,v,t", tempreg, tempreg, mips_gp_register);
5395 macro_build ((char *) NULL, &icnt, &offset_expr,
5396 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
5397 "t,o(b)", tempreg, lw_reloc_type, tempreg);
5398 if (expr1.X_add_number == 0)
5406 /* We're going to put in an addu instruction using
5407 tempreg, so we may as well insert the nop right
5409 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5414 p = frag_var (rs_machine_dependent, 12 + gpdel, 0,
5415 RELAX_ENCODE (12 + off, 12 + gpdel, gpdel,
5418 ? mips_opts.warn_about_macros
5420 offset_expr.X_add_symbol, 0, NULL);
5422 else if (expr1.X_add_number >= -0x8000
5423 && expr1.X_add_number < 0x8000)
5425 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5427 macro_build ((char *) NULL, &icnt, &expr1,
5428 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
5429 "t,r,j", tempreg, tempreg, (int) BFD_RELOC_LO16);
5431 p = frag_var (rs_machine_dependent, 12 + gpdel, 0,
5432 RELAX_ENCODE (20, 12 + gpdel, gpdel, 8 + gpdel, 0,
5434 ? mips_opts.warn_about_macros
5436 offset_expr.X_add_symbol, 0, NULL);
5442 /* If we are going to add in a base register, and the
5443 target register and the base register are the same,
5444 then we are using AT as a temporary register. Since
5445 we want to load the constant into AT, we add our
5446 current AT (from the global offset table) and the
5447 register into the register now, and pretend we were
5448 not using a base register. */
5456 assert (tempreg == AT);
5457 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5459 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5460 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
5461 "d,v,t", treg, AT, breg);
5466 /* Set mips_optimize around the lui instruction to avoid
5467 inserting an unnecessary nop after the lw. */
5468 hold_mips_optimize = mips_optimize;
5470 macro_build_lui (NULL, &icnt, &expr1, AT);
5471 mips_optimize = hold_mips_optimize;
5473 macro_build ((char *) NULL, &icnt, &expr1,
5474 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
5475 "t,r,j", AT, AT, (int) BFD_RELOC_LO16);
5476 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5477 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
5478 "d,v,t", dreg, dreg, AT);
5480 p = frag_var (rs_machine_dependent, 16 + gpdel + adj, 0,
5481 RELAX_ENCODE (24 + adj, 16 + gpdel + adj, gpdel,
5484 ? mips_opts.warn_about_macros
5486 offset_expr.X_add_symbol, 0, NULL);
5493 /* This is needed because this instruction uses $gp, but
5494 the first instruction on the main stream does not. */
5495 macro_build (p, &icnt, (expressionS *) NULL, "nop", "");
5499 macro_build (p, &icnt, &offset_expr,
5500 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
5505 if (expr1.X_add_number >= -0x8000
5506 && expr1.X_add_number < 0x8000)
5508 macro_build (p, &icnt, (expressionS *) NULL, "nop", "");
5510 macro_build (p, &icnt, &expr1,
5511 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
5512 "t,r,j", tempreg, tempreg, (int) BFD_RELOC_LO16);
5513 /* FIXME: If add_number is 0, and there was no base
5514 register, the external symbol case ended with a load,
5515 so if the symbol turns out to not be external, and
5516 the next instruction uses tempreg, an unnecessary nop
5517 will be inserted. */
5523 /* We must add in the base register now, as in the
5524 external symbol case. */
5525 assert (tempreg == AT);
5526 macro_build (p, &icnt, (expressionS *) NULL, "nop", "");
5528 macro_build (p, &icnt, (expressionS *) NULL,
5529 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
5530 "d,v,t", treg, AT, breg);
5533 /* We set breg to 0 because we have arranged to add
5534 it in in both cases. */
5538 macro_build_lui (p, &icnt, &expr1, AT);
5540 macro_build (p, &icnt, &expr1,
5541 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
5542 "t,r,j", AT, AT, (int) BFD_RELOC_LO16);
5544 macro_build (p, &icnt, (expressionS *) NULL,
5545 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
5546 "d,v,t", tempreg, tempreg, AT);
5550 else if (mips_pic == SVR4_PIC && HAVE_NEWABI)
5553 int lui_reloc_type = (int) BFD_RELOC_MIPS_GOT_HI16;
5554 int lw_reloc_type = (int) BFD_RELOC_MIPS_GOT_LO16;
5557 /* This is the large GOT case. If this is a reference to an
5558 external symbol, and there is no constant, we want
5559 lui $tempreg,<sym> (BFD_RELOC_MIPS_GOT_HI16)
5560 add $tempreg,$tempreg,$gp
5561 lw $tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_LO16)
5562 or if tempreg is PIC_CALL_REG
5563 lui $tempreg,<sym> (BFD_RELOC_MIPS_CALL_HI16)
5564 add $tempreg,$tempreg,$gp
5565 lw $tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_CALL_LO16)
5567 If we have a small constant, and this is a reference to
5568 an external symbol, we want
5569 lui $tempreg,<sym> (BFD_RELOC_MIPS_GOT_HI16)
5570 add $tempreg,$tempreg,$gp
5571 lw $tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_LO16)
5572 addi $tempreg,$tempreg,<constant>
5574 If we have a large constant, and this is a reference to
5575 an external symbol, we want
5576 lui $tempreg,<sym> (BFD_RELOC_MIPS_GOT_HI16)
5577 addu $tempreg,$tempreg,$gp
5578 lw $tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_LO16)
5579 lui $at,<hiconstant>
5580 addi $at,$at,<loconstant>
5581 add $tempreg,$tempreg,$at
5583 If we have NewABI, and we know it's a local symbol, we want
5584 lw $reg,<sym>($gp) (BFD_RELOC_MIPS_GOT_PAGE)
5585 addiu $reg,$reg,<sym> (BFD_RELOC_MIPS_GOT_OFST)
5586 otherwise we have to resort to GOT_HI16/GOT_LO16. */
5590 frag_now->tc_frag_data.tc_fr_offset =
5591 expr1.X_add_number = offset_expr.X_add_number;
5592 offset_expr.X_add_number = 0;
5594 if (expr1.X_add_number == 0 && tempreg == PIC_CALL_REG)
5596 lui_reloc_type = (int) BFD_RELOC_MIPS_CALL_HI16;
5597 lw_reloc_type = (int) BFD_RELOC_MIPS_CALL_LO16;
5599 macro_build ((char *) NULL, &icnt, &offset_expr, "lui", "t,u",
5600 tempreg, lui_reloc_type);
5601 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5602 HAVE_32BIT_ADDRESSES ? "add" : "daddu",
5603 "d,v,t", tempreg, tempreg, mips_gp_register);
5604 macro_build ((char *) NULL, &icnt, &offset_expr,
5605 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
5606 "t,o(b)", tempreg, lw_reloc_type, tempreg);
5608 if (expr1.X_add_number == 0)
5610 p = frag_var (rs_machine_dependent, 8, 0,
5611 RELAX_ENCODE (12, 8, 0, 4, 0,
5612 mips_opts.warn_about_macros),
5613 offset_expr.X_add_symbol, 0, NULL);
5615 else if (expr1.X_add_number >= -0x8000
5616 && expr1.X_add_number < 0x8000)
5618 macro_build ((char *) NULL, &icnt, &expr1,
5619 HAVE_32BIT_ADDRESSES ? "addi" : "daddiu",
5620 "t,r,j", tempreg, tempreg,
5621 (int) BFD_RELOC_LO16);
5622 p = frag_var (rs_machine_dependent, 8, 0,
5623 RELAX_ENCODE (16, 8, 0, 4, 0,
5624 mips_opts.warn_about_macros),
5625 offset_expr.X_add_symbol, 0, NULL);
5627 else if (IS_SEXT_32BIT_NUM (expr1.X_add_number))
5631 /* If we are going to add in a base register, and the
5632 target register and the base register are the same,
5633 then we are using AT as a temporary register. Since
5634 we want to load the constant into AT, we add our
5635 current AT (from the global offset table) and the
5636 register into the register now, and pretend we were
5637 not using a base register. */
5642 assert (tempreg == AT);
5643 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5644 HAVE_32BIT_ADDRESSES ? "add" : "daddu",
5645 "d,v,t", treg, AT, breg);
5650 /* Set mips_optimize around the lui instruction to avoid
5651 inserting an unnecessary nop after the lw. */
5652 macro_build_lui ((char *) NULL, &icnt, &expr1, AT);
5653 macro_build ((char *) NULL, &icnt, &expr1,
5654 HAVE_32BIT_ADDRESSES ? "addi" : "daddiu",
5655 "t,r,j", AT, AT, (int) BFD_RELOC_LO16);
5656 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5657 HAVE_32BIT_ADDRESSES ? "add" : "daddu",
5658 "d,v,t", dreg, dreg, AT);
5660 p = frag_var (rs_machine_dependent, 8 + adj, 0,
5661 RELAX_ENCODE (24 + adj, 8 + adj,
5664 ? mips_opts.warn_about_macros
5666 offset_expr.X_add_symbol, 0, NULL);
5671 as_bad (_("PIC code offset overflow (max 32 signed bits)"));
5673 offset_expr.X_add_number = expr1.X_add_number;
5674 macro_build (p, &icnt, &offset_expr,
5675 HAVE_32BIT_ADDRESSES ? "lw" : "ld", "t,o(b)",
5677 (int) BFD_RELOC_MIPS_GOT_PAGE, mips_gp_register);
5678 macro_build (p + 4, &icnt, &offset_expr,
5679 HAVE_32BIT_ADDRESSES ? "addi" : "daddiu", "t,r,j",
5680 tempreg, tempreg, (int) BFD_RELOC_MIPS_GOT_OFST);
5683 macro_build (p + 8, &icnt, (expressionS *) NULL,
5684 HAVE_32BIT_ADDRESSES ? "add" : "daddu",
5685 "d,v,t", treg, tempreg, breg);
5690 else if (mips_pic == EMBEDDED_PIC)
5693 addiu $tempreg,$gp,<sym> (BFD_RELOC_GPREL16)
5695 macro_build ((char *) NULL, &icnt, &offset_expr,
5696 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu", "t,r,j",
5697 tempreg, mips_gp_register, (int) BFD_RELOC_GPREL16);
5706 if (mips_pic == EMBEDDED_PIC || mips_pic == NO_PIC)
5707 s = (dbl || HAVE_64BIT_ADDRESSES) ? "daddu" :
5708 HAVE_NEWABI ? "add" : "addu";
5710 s = HAVE_64BIT_ADDRESSES ? "daddu" : HAVE_NEWABI ? "add" : "addu";
5712 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s,
5713 "d,v,t", treg, tempreg, breg);
5722 /* The j instruction may not be used in PIC code, since it
5723 requires an absolute address. We convert it to a b
5725 if (mips_pic == NO_PIC)
5726 macro_build ((char *) NULL, &icnt, &offset_expr, "j", "a");
5728 macro_build ((char *) NULL, &icnt, &offset_expr, "b", "p");
5731 /* The jal instructions must be handled as macros because when
5732 generating PIC code they expand to multi-instruction
5733 sequences. Normally they are simple instructions. */
5738 if (mips_pic == NO_PIC
5739 || mips_pic == EMBEDDED_PIC)
5740 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "jalr",
5742 else if (mips_pic == SVR4_PIC)
5744 if (sreg != PIC_CALL_REG)
5745 as_warn (_("MIPS PIC call to register other than $25"));
5747 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "jalr",
5751 if (mips_cprestore_offset < 0)
5752 as_warn (_("No .cprestore pseudo-op used in PIC code"));
5755 if (! mips_frame_reg_valid)
5757 as_warn (_("No .frame pseudo-op used in PIC code"));
5758 /* Quiet this warning. */
5759 mips_frame_reg_valid = 1;
5761 if (! mips_cprestore_valid)
5763 as_warn (_("No .cprestore pseudo-op used in PIC code"));
5764 /* Quiet this warning. */
5765 mips_cprestore_valid = 1;
5767 expr1.X_add_number = mips_cprestore_offset;
5768 macro_build_ldst_constoffset ((char *) NULL, &icnt, &expr1,
5769 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
5770 mips_gp_register, mips_frame_reg);
5780 if (mips_pic == NO_PIC)
5781 macro_build ((char *) NULL, &icnt, &offset_expr, "jal", "a");
5782 else if (mips_pic == SVR4_PIC)
5786 /* If this is a reference to an external symbol, and we are
5787 using a small GOT, we want
5788 lw $25,<sym>($gp) (BFD_RELOC_MIPS_CALL16)
5792 lw $gp,cprestore($sp)
5793 The cprestore value is set using the .cprestore
5794 pseudo-op. If we are using a big GOT, we want
5795 lui $25,<sym> (BFD_RELOC_MIPS_CALL_HI16)
5797 lw $25,<sym>($25) (BFD_RELOC_MIPS_CALL_LO16)
5801 lw $gp,cprestore($sp)
5802 If the symbol is not external, we want
5803 lw $25,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
5805 addiu $25,$25,<sym> (BFD_RELOC_LO16)
5808 lw $gp,cprestore($sp)
5810 For NewABI, we use the same CALL16 or CALL_HI16/CALL_LO16
5811 sequences above, minus nops, unless the symbol is local,
5812 which enables us to use GOT_PAGE/GOT_OFST (big got) or
5819 macro_build ((char *) NULL, &icnt, &offset_expr,
5820 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
5821 "t,o(b)", PIC_CALL_REG,
5822 (int) BFD_RELOC_MIPS_CALL16,
5824 frag_var (rs_machine_dependent, 0, 0,
5825 RELAX_ENCODE (0, 0, -4, 0, 0, 0),
5826 offset_expr.X_add_symbol, 0, NULL);
5831 macro_build ((char *) NULL, &icnt, &offset_expr, "lui",
5832 "t,u", PIC_CALL_REG,
5833 (int) BFD_RELOC_MIPS_CALL_HI16);
5834 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5835 HAVE_32BIT_ADDRESSES ? "add" : "daddu",
5836 "d,v,t", PIC_CALL_REG, PIC_CALL_REG,
5838 macro_build ((char *) NULL, &icnt, &offset_expr,
5839 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
5840 "t,o(b)", PIC_CALL_REG,
5841 (int) BFD_RELOC_MIPS_CALL_LO16, PIC_CALL_REG);
5842 p = frag_var (rs_machine_dependent, 8, 0,
5843 RELAX_ENCODE (12, 8, 0, 4, 0, 0),
5844 offset_expr.X_add_symbol, 0, NULL);
5845 macro_build (p, &icnt, &offset_expr,
5846 HAVE_32BIT_ADDRESSES ? "lw" : "ld", "t,o(b)",
5847 PIC_CALL_REG, (int) BFD_RELOC_MIPS_GOT_PAGE,
5849 macro_build (p + 4, &icnt, &offset_expr,
5850 HAVE_32BIT_ADDRESSES ? "addi" : "daddiu",
5851 "t,r,j", PIC_CALL_REG, PIC_CALL_REG,
5852 (int) BFD_RELOC_MIPS_GOT_OFST);
5855 macro_build_jalr (icnt, &offset_expr);
5862 macro_build ((char *) NULL, &icnt, &offset_expr,
5863 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
5864 "t,o(b)", PIC_CALL_REG,
5865 (int) BFD_RELOC_MIPS_CALL16, mips_gp_register);
5866 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5868 p = frag_var (rs_machine_dependent, 4, 0,
5869 RELAX_ENCODE (0, 4, -8, 0, 0, 0),
5870 offset_expr.X_add_symbol, 0, NULL);
5876 if (reg_needs_delay (mips_gp_register))
5880 macro_build ((char *) NULL, &icnt, &offset_expr, "lui",
5881 "t,u", PIC_CALL_REG,
5882 (int) BFD_RELOC_MIPS_CALL_HI16);
5883 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5884 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
5885 "d,v,t", PIC_CALL_REG, PIC_CALL_REG,
5887 macro_build ((char *) NULL, &icnt, &offset_expr,
5888 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
5889 "t,o(b)", PIC_CALL_REG,
5890 (int) BFD_RELOC_MIPS_CALL_LO16, PIC_CALL_REG);
5891 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5893 p = frag_var (rs_machine_dependent, 12 + gpdel, 0,
5894 RELAX_ENCODE (16, 12 + gpdel, gpdel,
5896 offset_expr.X_add_symbol, 0, NULL);
5899 macro_build (p, &icnt, (expressionS *) NULL, "nop", "");
5902 macro_build (p, &icnt, &offset_expr,
5903 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
5904 "t,o(b)", PIC_CALL_REG,
5905 (int) BFD_RELOC_MIPS_GOT16, mips_gp_register);
5907 macro_build (p, &icnt, (expressionS *) NULL, "nop", "");
5910 macro_build (p, &icnt, &offset_expr,
5911 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
5912 "t,r,j", PIC_CALL_REG, PIC_CALL_REG,
5913 (int) BFD_RELOC_LO16);
5914 macro_build_jalr (icnt, &offset_expr);
5916 if (mips_cprestore_offset < 0)
5917 as_warn (_("No .cprestore pseudo-op used in PIC code"));
5920 if (! mips_frame_reg_valid)
5922 as_warn (_("No .frame pseudo-op used in PIC code"));
5923 /* Quiet this warning. */
5924 mips_frame_reg_valid = 1;
5926 if (! mips_cprestore_valid)
5928 as_warn (_("No .cprestore pseudo-op used in PIC code"));
5929 /* Quiet this warning. */
5930 mips_cprestore_valid = 1;
5932 if (mips_opts.noreorder)
5933 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5935 expr1.X_add_number = mips_cprestore_offset;
5936 macro_build_ldst_constoffset ((char *) NULL, &icnt, &expr1,
5937 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
5938 mips_gp_register, mips_frame_reg);
5942 else if (mips_pic == EMBEDDED_PIC)
5944 macro_build ((char *) NULL, &icnt, &offset_expr, "bal", "p");
5945 /* The linker may expand the call to a longer sequence which
5946 uses $at, so we must break rather than return. */
5971 /* Itbl support may require additional care here. */
5976 /* Itbl support may require additional care here. */
5981 /* Itbl support may require additional care here. */
5986 /* Itbl support may require additional care here. */
5998 if (mips_arch == CPU_R4650)
6000 as_bad (_("opcode not supported on this processor"));
6004 /* Itbl support may require additional care here. */
6009 /* Itbl support may require additional care here. */
6014 /* Itbl support may require additional care here. */
6034 if (breg == treg || coproc || lr)
6056 /* Itbl support may require additional care here. */
6061 /* Itbl support may require additional care here. */
6066 /* Itbl support may require additional care here. */
6071 /* Itbl support may require additional care here. */
6087 if (mips_arch == CPU_R4650)
6089 as_bad (_("opcode not supported on this processor"));
6094 /* Itbl support may require additional care here. */
6098 /* Itbl support may require additional care here. */
6103 /* Itbl support may require additional care here. */
6115 /* Itbl support may require additional care here. */
6116 if (mask == M_LWC1_AB
6117 || mask == M_SWC1_AB
6118 || mask == M_LDC1_AB
6119 || mask == M_SDC1_AB
6128 /* For embedded PIC, we allow loads where the offset is calculated
6129 by subtracting a symbol in the current segment from an unknown
6130 symbol, relative to a base register, e.g.:
6131 <op> $treg, <sym>-<localsym>($breg)
6132 This is used by the compiler for switch statements. */
6133 if (mips_pic == EMBEDDED_PIC
6134 && offset_expr.X_op == O_subtract
6135 && (symbol_constant_p (offset_expr.X_op_symbol)
6136 ? S_GET_SEGMENT (offset_expr.X_op_symbol) == now_seg
6137 : (symbol_equated_p (offset_expr.X_op_symbol)
6139 (symbol_get_value_expression (offset_expr.X_op_symbol)
6143 && (offset_expr.X_add_number == 0
6144 || OUTPUT_FLAVOR == bfd_target_elf_flavour))
6146 /* For this case, we output the instructions:
6147 lui $tempreg,<sym> (BFD_RELOC_PCREL_HI16_S)
6148 addiu $tempreg,$tempreg,$breg
6149 <op> $treg,<sym>($tempreg) (BFD_RELOC_PCREL_LO16)
6150 If the relocation would fit entirely in 16 bits, it would be
6152 <op> $treg,<sym>($breg) (BFD_RELOC_PCREL_LO16)
6153 instead, but that seems quite difficult. */
6154 macro_build ((char *) NULL, &icnt, &offset_expr, "lui", "t,u",
6155 tempreg, (int) BFD_RELOC_PCREL_HI16_S);
6156 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6157 ((bfd_arch_bits_per_address (stdoutput) == 32
6158 || ! ISA_HAS_64BIT_REGS (mips_opts.isa))
6159 ? HAVE_NEWABI ? "add" : "addu" : "daddu"),
6160 "d,v,t", tempreg, tempreg, breg);
6161 macro_build ((char *) NULL, &icnt, &offset_expr, s, fmt, treg,
6162 (int) BFD_RELOC_PCREL_LO16, tempreg);
6168 if (offset_expr.X_op != O_constant
6169 && offset_expr.X_op != O_symbol)
6171 as_bad (_("expression too complex"));
6172 offset_expr.X_op = O_constant;
6175 /* A constant expression in PIC code can be handled just as it
6176 is in non PIC code. */
6177 if (mips_pic == NO_PIC
6178 || offset_expr.X_op == O_constant)
6182 /* If this is a reference to a GP relative symbol, and there
6183 is no base register, we want
6184 <op> $treg,<sym>($gp) (BFD_RELOC_GPREL16)
6185 Otherwise, if there is no base register, we want
6186 lui $tempreg,<sym> (BFD_RELOC_HI16_S)
6187 <op> $treg,<sym>($tempreg) (BFD_RELOC_LO16)
6188 If we have a constant, we need two instructions anyhow,
6189 so we always use the latter form.
6191 If we have a base register, and this is a reference to a
6192 GP relative symbol, we want
6193 addu $tempreg,$breg,$gp
6194 <op> $treg,<sym>($tempreg) (BFD_RELOC_GPREL16)
6196 lui $tempreg,<sym> (BFD_RELOC_HI16_S)
6197 addu $tempreg,$tempreg,$breg
6198 <op> $treg,<sym>($tempreg) (BFD_RELOC_LO16)
6199 With a constant we always use the latter case.
6201 With 64bit address space and no base register and $at usable,
6203 lui $tempreg,<sym> (BFD_RELOC_MIPS_HIGHEST)
6204 lui $at,<sym> (BFD_RELOC_HI16_S)
6205 daddiu $tempreg,<sym> (BFD_RELOC_MIPS_HIGHER)
6208 <op> $treg,<sym>($tempreg) (BFD_RELOC_LO16)
6209 If we have a base register, we want
6210 lui $tempreg,<sym> (BFD_RELOC_MIPS_HIGHEST)
6211 lui $at,<sym> (BFD_RELOC_HI16_S)
6212 daddiu $tempreg,<sym> (BFD_RELOC_MIPS_HIGHER)
6216 <op> $treg,<sym>($tempreg) (BFD_RELOC_LO16)
6218 Without $at we can't generate the optimal path for superscalar
6219 processors here since this would require two temporary registers.
6220 lui $tempreg,<sym> (BFD_RELOC_MIPS_HIGHEST)
6221 daddiu $tempreg,<sym> (BFD_RELOC_MIPS_HIGHER)
6223 daddiu $tempreg,<sym> (BFD_RELOC_HI16_S)
6225 <op> $treg,<sym>($tempreg) (BFD_RELOC_LO16)
6226 If we have a base register, we want
6227 lui $tempreg,<sym> (BFD_RELOC_MIPS_HIGHEST)
6228 daddiu $tempreg,<sym> (BFD_RELOC_MIPS_HIGHER)
6230 daddiu $tempreg,<sym> (BFD_RELOC_HI16_S)
6232 daddu $tempreg,$tempreg,$breg
6233 <op> $treg,<sym>($tempreg) (BFD_RELOC_LO16)
6235 If we have 64-bit addresses, as an optimization, for
6236 addresses which are 32-bit constants (e.g. kseg0/kseg1
6237 addresses) we fall back to the 32-bit address generation
6238 mechanism since it is more efficient. Note that due to
6239 the signed offset used by memory operations, the 32-bit
6240 range is shifted down by 32768 here. This code should
6241 probably attempt to generate 64-bit constants more
6242 efficiently in general.
6244 As an extension for architectures with 64-bit registers,
6245 we don't truncate 64-bit addresses given as literal
6246 constants down to 32 bits, to support existing practice
6247 in the mips64 Linux (the kernel), that compiles source
6248 files with -mabi=64, assembling them as o32 or n32 (with
6249 -Wa,-32 or -Wa,-n32). This is not beautiful, but since
6250 the whole kernel is loaded into a memory region that is
6251 addressible with sign-extended 32-bit addresses, it is
6252 wasteful to compute the upper 32 bits of every
6253 non-literal address, that takes more space and time.
6254 Some day this should probably be implemented as an
6255 assembler option, such that the kernel doesn't have to
6256 use such ugly hacks, even though it will still have to
6257 end up converting the binary to ELF32 for a number of
6258 platforms whose boot loaders don't support ELF64
6260 if ((offset_expr.X_op != O_constant && HAVE_64BIT_ADDRESSES)
6261 || (offset_expr.X_op == O_constant
6262 && !IS_SEXT_32BIT_NUM (offset_expr.X_add_number + 0x8000)
6263 && HAVE_64BIT_ADDRESS_CONSTANTS))
6267 /* We don't do GP optimization for now because RELAX_ENCODE can't
6268 hold the data for such large chunks. */
6270 if (used_at == 0 && ! mips_opts.noat)
6272 macro_build (p, &icnt, &offset_expr, "lui", "t,u",
6273 tempreg, (int) BFD_RELOC_MIPS_HIGHEST);
6274 macro_build (p, &icnt, &offset_expr, "lui", "t,u",
6275 AT, (int) BFD_RELOC_HI16_S);
6276 macro_build (p, &icnt, &offset_expr, "daddiu", "t,r,j",
6277 tempreg, tempreg, (int) BFD_RELOC_MIPS_HIGHER);
6279 macro_build (p, &icnt, (expressionS *) NULL, "daddu",
6280 "d,v,t", AT, AT, breg);
6281 macro_build (p, &icnt, (expressionS *) NULL, "dsll32",
6282 "d,w,<", tempreg, tempreg, 0);
6283 macro_build (p, &icnt, (expressionS *) NULL, "daddu",
6284 "d,v,t", tempreg, tempreg, AT);
6285 macro_build (p, &icnt, &offset_expr, s,
6286 fmt, treg, (int) BFD_RELOC_LO16, tempreg);
6291 macro_build (p, &icnt, &offset_expr, "lui", "t,u",
6292 tempreg, (int) BFD_RELOC_MIPS_HIGHEST);
6293 macro_build (p, &icnt, &offset_expr, "daddiu", "t,r,j",
6294 tempreg, tempreg, (int) BFD_RELOC_MIPS_HIGHER);
6295 macro_build (p, &icnt, (expressionS *) NULL, "dsll",
6296 "d,w,<", tempreg, tempreg, 16);
6297 macro_build (p, &icnt, &offset_expr, "daddiu", "t,r,j",
6298 tempreg, tempreg, (int) BFD_RELOC_HI16_S);
6299 macro_build (p, &icnt, (expressionS *) NULL, "dsll",
6300 "d,w,<", tempreg, tempreg, 16);
6302 macro_build (p, &icnt, (expressionS *) NULL, "daddu",
6303 "d,v,t", tempreg, tempreg, breg);
6304 macro_build (p, &icnt, &offset_expr, s,
6305 fmt, treg, (int) BFD_RELOC_LO16, tempreg);
6310 else if (offset_expr.X_op == O_constant
6311 && !HAVE_64BIT_ADDRESS_CONSTANTS
6312 && !IS_SEXT_32BIT_NUM (offset_expr.X_add_number))
6313 as_bad (_("load/store address overflow (max 32 bits)"));
6317 if ((valueT) offset_expr.X_add_number > MAX_GPREL_OFFSET
6318 || nopic_need_relax (offset_expr.X_add_symbol, 1))
6323 macro_build ((char *) NULL, &icnt, &offset_expr, s, fmt,
6324 treg, (int) BFD_RELOC_GPREL16,
6326 p = frag_var (rs_machine_dependent, 8, 0,
6327 RELAX_ENCODE (4, 8, 0, 4, 0,
6328 (mips_opts.warn_about_macros
6330 && mips_opts.noat))),
6331 offset_expr.X_add_symbol, 0, NULL);
6334 macro_build_lui (p, &icnt, &offset_expr, tempreg);
6337 macro_build (p, &icnt, &offset_expr, s, fmt, treg,
6338 (int) BFD_RELOC_LO16, tempreg);
6342 if ((valueT) offset_expr.X_add_number > MAX_GPREL_OFFSET
6343 || nopic_need_relax (offset_expr.X_add_symbol, 1))
6348 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6349 HAVE_32BIT_ADDRESSES ? HAVE_NEWABI
6350 ? "add" : "addu" : "daddu",
6351 "d,v,t", tempreg, breg, mips_gp_register);
6352 macro_build ((char *) NULL, &icnt, &offset_expr, s, fmt,
6353 treg, (int) BFD_RELOC_GPREL16, tempreg);
6354 p = frag_var (rs_machine_dependent, 12, 0,
6355 RELAX_ENCODE (8, 12, 0, 8, 0, 0),
6356 offset_expr.X_add_symbol, 0, NULL);
6358 macro_build_lui (p, &icnt, &offset_expr, tempreg);
6361 macro_build (p, &icnt, (expressionS *) NULL,
6362 HAVE_32BIT_ADDRESSES ? HAVE_NEWABI
6363 ? "add" : "addu" : "daddu",
6364 "d,v,t", tempreg, tempreg, breg);
6367 macro_build (p, &icnt, &offset_expr, s, fmt, treg,
6368 (int) BFD_RELOC_LO16, tempreg);
6371 else if (mips_pic == SVR4_PIC && ! mips_big_got)
6374 int lw_reloc_type = (int) BFD_RELOC_MIPS_GOT16;
6376 /* If this is a reference to an external symbol, we want
6377 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
6379 <op> $treg,0($tempreg)
6381 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
6383 addiu $tempreg,$tempreg,<sym> (BFD_RELOC_LO16)
6384 <op> $treg,0($tempreg)
6387 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT_PAGE)
6388 <op> $treg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_OFST)
6390 If there is a base register, we add it to $tempreg before
6391 the <op>. If there is a constant, we stick it in the
6392 <op> instruction. We don't handle constants larger than
6393 16 bits, because we have no way to load the upper 16 bits
6394 (actually, we could handle them for the subset of cases
6395 in which we are not using $at). */
6396 assert (offset_expr.X_op == O_symbol);
6399 macro_build ((char *) NULL, &icnt, &offset_expr,
6400 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
6401 "t,o(b)", tempreg, BFD_RELOC_MIPS_GOT_PAGE,
6404 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6405 HAVE_32BIT_ADDRESSES ? "add" : "daddu",
6406 "d,v,t", tempreg, tempreg, breg);
6407 macro_build ((char *) NULL, &icnt, &offset_expr, s, fmt, treg,
6408 (int) BFD_RELOC_MIPS_GOT_OFST, tempreg);
6415 expr1.X_add_number = offset_expr.X_add_number;
6416 offset_expr.X_add_number = 0;
6417 if (expr1.X_add_number < -0x8000
6418 || expr1.X_add_number >= 0x8000)
6419 as_bad (_("PIC code offset overflow (max 16 signed bits)"));
6421 macro_build ((char *) NULL, &icnt, &offset_expr,
6422 HAVE_32BIT_ADDRESSES ? "lw" : "ld", "t,o(b)", tempreg,
6423 (int) lw_reloc_type, mips_gp_register);
6424 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "");
6425 p = frag_var (rs_machine_dependent, 4, 0,
6426 RELAX_ENCODE (0, 4, -8, 0, 0, 0),
6427 offset_expr.X_add_symbol, 0, NULL);
6428 macro_build (p, &icnt, &offset_expr,
6429 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
6430 "t,r,j", tempreg, tempreg, (int) BFD_RELOC_LO16);
6432 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6433 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
6434 "d,v,t", tempreg, tempreg, breg);
6435 macro_build ((char *) NULL, &icnt, &expr1, s, fmt, treg,
6436 (int) BFD_RELOC_LO16, tempreg);
6438 else if (mips_pic == SVR4_PIC && ! HAVE_NEWABI)
6443 /* If this is a reference to an external symbol, we want
6444 lui $tempreg,<sym> (BFD_RELOC_MIPS_GOT_HI16)
6445 addu $tempreg,$tempreg,$gp
6446 lw $tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_LO16)
6447 <op> $treg,0($tempreg)
6449 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
6451 addiu $tempreg,$tempreg,<sym> (BFD_RELOC_LO16)
6452 <op> $treg,0($tempreg)
6453 If there is a base register, we add it to $tempreg before
6454 the <op>. If there is a constant, we stick it in the
6455 <op> instruction. We don't handle constants larger than
6456 16 bits, because we have no way to load the upper 16 bits
6457 (actually, we could handle them for the subset of cases
6458 in which we are not using $at). */
6459 assert (offset_expr.X_op == O_symbol);
6460 expr1.X_add_number = offset_expr.X_add_number;
6461 offset_expr.X_add_number = 0;
6462 if (expr1.X_add_number < -0x8000
6463 || expr1.X_add_number >= 0x8000)
6464 as_bad (_("PIC code offset overflow (max 16 signed bits)"));
6465 if (reg_needs_delay (mips_gp_register))
6470 macro_build ((char *) NULL, &icnt, &offset_expr, "lui", "t,u",
6471 tempreg, (int) BFD_RELOC_MIPS_GOT_HI16);
6472 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6473 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
6474 "d,v,t", tempreg, tempreg, mips_gp_register);
6475 macro_build ((char *) NULL, &icnt, &offset_expr,
6476 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
6477 "t,o(b)", tempreg, (int) BFD_RELOC_MIPS_GOT_LO16,
6479 p = frag_var (rs_machine_dependent, 12 + gpdel, 0,
6480 RELAX_ENCODE (12, 12 + gpdel, gpdel, 8 + gpdel, 0, 0),
6481 offset_expr.X_add_symbol, 0, NULL);
6484 macro_build (p, &icnt, (expressionS *) NULL, "nop", "");
6487 macro_build (p, &icnt, &offset_expr,
6488 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
6489 "t,o(b)", tempreg, (int) BFD_RELOC_MIPS_GOT16,
6492 macro_build (p, &icnt, (expressionS *) NULL, "nop", "");
6494 macro_build (p, &icnt, &offset_expr,
6495 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
6496 "t,r,j", tempreg, tempreg, (int) BFD_RELOC_LO16);
6498 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6499 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
6500 "d,v,t", tempreg, tempreg, breg);
6501 macro_build ((char *) NULL, &icnt, &expr1, s, fmt, treg,
6502 (int) BFD_RELOC_LO16, tempreg);
6504 else if (mips_pic == SVR4_PIC && HAVE_NEWABI)
6507 int bregsz = breg != 0 ? 4 : 0;
6509 /* If this is a reference to an external symbol, we want
6510 lui $tempreg,<sym> (BFD_RELOC_MIPS_GOT_HI16)
6511 add $tempreg,$tempreg,$gp
6512 lw $tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_LO16)
6513 <op> $treg,<ofst>($tempreg)
6514 Otherwise, for local symbols, we want:
6515 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT_PAGE)
6516 <op> $treg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_OFST) */
6517 assert (offset_expr.X_op == O_symbol);
6518 frag_now->tc_frag_data.tc_fr_offset =
6519 expr1.X_add_number = offset_expr.X_add_number;
6520 offset_expr.X_add_number = 0;
6521 if (expr1.X_add_number < -0x8000
6522 || expr1.X_add_number >= 0x8000)
6523 as_bad (_("PIC code offset overflow (max 16 signed bits)"));
6525 macro_build ((char *) NULL, &icnt, &offset_expr, "lui", "t,u",
6526 tempreg, (int) BFD_RELOC_MIPS_GOT_HI16);
6527 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6528 HAVE_32BIT_ADDRESSES ? "add" : "daddu",
6529 "d,v,t", tempreg, tempreg, mips_gp_register);
6530 macro_build ((char *) NULL, &icnt, &offset_expr,
6531 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
6532 "t,o(b)", tempreg, (int) BFD_RELOC_MIPS_GOT_LO16,
6535 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6536 HAVE_32BIT_ADDRESSES ? "add" : "daddu",
6537 "d,v,t", tempreg, tempreg, breg);
6538 macro_build ((char *) NULL, &icnt, &expr1, s, fmt, treg,
6539 (int) BFD_RELOC_LO16, tempreg);
6541 offset_expr.X_add_number = expr1.X_add_number;
6542 p = frag_var (rs_machine_dependent, 12 + bregsz, 0,
6543 RELAX_ENCODE (16 + bregsz, 8 + bregsz,
6544 0, 4 + bregsz, 0, 0),
6545 offset_expr.X_add_symbol, 0, NULL);
6546 macro_build (p, &icnt, &offset_expr,
6547 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
6549 (int) BFD_RELOC_MIPS_GOT_PAGE,
6552 macro_build (p + 4, &icnt, (expressionS *) NULL,
6553 HAVE_32BIT_ADDRESSES ? "add" : "daddu",
6554 "d,v,t", tempreg, tempreg, breg);
6555 macro_build (p + 4 + bregsz, &icnt, &offset_expr, s, fmt, treg,
6556 (int) BFD_RELOC_MIPS_GOT_OFST, tempreg);
6558 else if (mips_pic == EMBEDDED_PIC)
6560 /* If there is no base register, we want
6561 <op> $treg,<sym>($gp) (BFD_RELOC_GPREL16)
6562 If there is a base register, we want
6563 addu $tempreg,$breg,$gp
6564 <op> $treg,<sym>($tempreg) (BFD_RELOC_GPREL16)
6566 assert (offset_expr.X_op == O_symbol);
6569 macro_build ((char *) NULL, &icnt, &offset_expr, s, fmt,
6570 treg, (int) BFD_RELOC_GPREL16, mips_gp_register);
6575 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6576 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
6577 "d,v,t", tempreg, breg, mips_gp_register);
6578 macro_build ((char *) NULL, &icnt, &offset_expr, s, fmt,
6579 treg, (int) BFD_RELOC_GPREL16, tempreg);
6592 load_register (&icnt, treg, &imm_expr, 0);
6596 load_register (&icnt, treg, &imm_expr, 1);
6600 if (imm_expr.X_op == O_constant)
6602 load_register (&icnt, AT, &imm_expr, 0);
6603 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6604 "mtc1", "t,G", AT, treg);
6609 assert (offset_expr.X_op == O_symbol
6610 && strcmp (segment_name (S_GET_SEGMENT
6611 (offset_expr.X_add_symbol)),
6613 && offset_expr.X_add_number == 0);
6614 macro_build ((char *) NULL, &icnt, &offset_expr, "lwc1", "T,o(b)",
6615 treg, (int) BFD_RELOC_MIPS_LITERAL, mips_gp_register);
6620 /* Check if we have a constant in IMM_EXPR. If the GPRs are 64 bits
6621 wide, IMM_EXPR is the entire value. Otherwise IMM_EXPR is the high
6622 order 32 bits of the value and the low order 32 bits are either
6623 zero or in OFFSET_EXPR. */
6624 if (imm_expr.X_op == O_constant || imm_expr.X_op == O_big)
6626 if (HAVE_64BIT_GPRS)
6627 load_register (&icnt, treg, &imm_expr, 1);
6632 if (target_big_endian)
6644 load_register (&icnt, hreg, &imm_expr, 0);
6647 if (offset_expr.X_op == O_absent)
6648 move_register (&icnt, lreg, 0);
6651 assert (offset_expr.X_op == O_constant);
6652 load_register (&icnt, lreg, &offset_expr, 0);
6659 /* We know that sym is in the .rdata section. First we get the
6660 upper 16 bits of the address. */
6661 if (mips_pic == NO_PIC)
6663 macro_build_lui (NULL, &icnt, &offset_expr, AT);
6665 else if (mips_pic == SVR4_PIC)
6667 macro_build ((char *) NULL, &icnt, &offset_expr,
6668 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
6669 "t,o(b)", AT, (int) BFD_RELOC_MIPS_GOT16,
6672 else if (mips_pic == EMBEDDED_PIC)
6674 /* For embedded PIC we pick up the entire address off $gp in
6675 a single instruction. */
6676 macro_build ((char *) NULL, &icnt, &offset_expr,
6677 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu", "t,r,j", AT,
6678 mips_gp_register, (int) BFD_RELOC_GPREL16);
6679 offset_expr.X_op = O_constant;
6680 offset_expr.X_add_number = 0;
6685 /* Now we load the register(s). */
6686 if (HAVE_64BIT_GPRS)
6687 macro_build ((char *) NULL, &icnt, &offset_expr, "ld", "t,o(b)",
6688 treg, (int) BFD_RELOC_LO16, AT);
6691 macro_build ((char *) NULL, &icnt, &offset_expr, "lw", "t,o(b)",
6692 treg, (int) BFD_RELOC_LO16, AT);
6695 /* FIXME: How in the world do we deal with the possible
6697 offset_expr.X_add_number += 4;
6698 macro_build ((char *) NULL, &icnt, &offset_expr, "lw", "t,o(b)",
6699 treg + 1, (int) BFD_RELOC_LO16, AT);
6703 /* To avoid confusion in tc_gen_reloc, we must ensure that this
6704 does not become a variant frag. */
6705 frag_wane (frag_now);
6711 /* Check if we have a constant in IMM_EXPR. If the FPRs are 64 bits
6712 wide, IMM_EXPR is the entire value and the GPRs are known to be 64
6713 bits wide as well. Otherwise IMM_EXPR is the high order 32 bits of
6714 the value and the low order 32 bits are either zero or in
6716 if (imm_expr.X_op == O_constant || imm_expr.X_op == O_big)
6718 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_FPRS);
6719 if (HAVE_64BIT_FPRS)
6721 assert (HAVE_64BIT_GPRS);
6722 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6723 "dmtc1", "t,S", AT, treg);
6727 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6728 "mtc1", "t,G", AT, treg + 1);
6729 if (offset_expr.X_op == O_absent)
6730 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6731 "mtc1", "t,G", 0, treg);
6734 assert (offset_expr.X_op == O_constant);
6735 load_register (&icnt, AT, &offset_expr, 0);
6736 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6737 "mtc1", "t,G", AT, treg);
6743 assert (offset_expr.X_op == O_symbol
6744 && offset_expr.X_add_number == 0);
6745 s = segment_name (S_GET_SEGMENT (offset_expr.X_add_symbol));
6746 if (strcmp (s, ".lit8") == 0)
6748 if (mips_opts.isa != ISA_MIPS1)
6750 macro_build ((char *) NULL, &icnt, &offset_expr, "ldc1",
6751 "T,o(b)", treg, (int) BFD_RELOC_MIPS_LITERAL,
6755 breg = mips_gp_register;
6756 r = BFD_RELOC_MIPS_LITERAL;
6761 assert (strcmp (s, RDATA_SECTION_NAME) == 0);
6762 if (mips_pic == SVR4_PIC)
6763 macro_build ((char *) NULL, &icnt, &offset_expr,
6764 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
6765 "t,o(b)", AT, (int) BFD_RELOC_MIPS_GOT16,
6769 /* FIXME: This won't work for a 64 bit address. */
6770 macro_build_lui (NULL, &icnt, &offset_expr, AT);
6773 if (mips_opts.isa != ISA_MIPS1)
6775 macro_build ((char *) NULL, &icnt, &offset_expr, "ldc1",
6776 "T,o(b)", treg, (int) BFD_RELOC_LO16, AT);
6778 /* To avoid confusion in tc_gen_reloc, we must ensure
6779 that this does not become a variant frag. */
6780 frag_wane (frag_now);
6791 if (mips_arch == CPU_R4650)
6793 as_bad (_("opcode not supported on this processor"));
6796 /* Even on a big endian machine $fn comes before $fn+1. We have
6797 to adjust when loading from memory. */
6800 assert (mips_opts.isa == ISA_MIPS1);
6801 macro_build ((char *) NULL, &icnt, &offset_expr, "lwc1", "T,o(b)",
6802 target_big_endian ? treg + 1 : treg,
6804 /* FIXME: A possible overflow which I don't know how to deal
6806 offset_expr.X_add_number += 4;
6807 macro_build ((char *) NULL, &icnt, &offset_expr, "lwc1", "T,o(b)",
6808 target_big_endian ? treg : treg + 1,
6811 /* To avoid confusion in tc_gen_reloc, we must ensure that this
6812 does not become a variant frag. */
6813 frag_wane (frag_now);
6822 * The MIPS assembler seems to check for X_add_number not
6823 * being double aligned and generating:
6826 * addiu at,at,%lo(foo+1)
6829 * But, the resulting address is the same after relocation so why
6830 * generate the extra instruction?
6832 if (mips_arch == CPU_R4650)
6834 as_bad (_("opcode not supported on this processor"));
6837 /* Itbl support may require additional care here. */
6839 if (mips_opts.isa != ISA_MIPS1)
6850 if (mips_arch == CPU_R4650)
6852 as_bad (_("opcode not supported on this processor"));
6856 if (mips_opts.isa != ISA_MIPS1)
6864 /* Itbl support may require additional care here. */
6869 if (HAVE_64BIT_GPRS)
6880 if (HAVE_64BIT_GPRS)
6890 /* We do _not_ bother to allow embedded PIC (symbol-local_symbol)
6891 loads for the case of doing a pair of loads to simulate an 'ld'.
6892 This is not currently done by the compiler, and assembly coders
6893 writing embedded-pic code can cope. */
6895 if (offset_expr.X_op != O_symbol
6896 && offset_expr.X_op != O_constant)
6898 as_bad (_("expression too complex"));
6899 offset_expr.X_op = O_constant;
6902 /* Even on a big endian machine $fn comes before $fn+1. We have
6903 to adjust when loading from memory. We set coproc if we must
6904 load $fn+1 first. */
6905 /* Itbl support may require additional care here. */
6906 if (! target_big_endian)
6909 if (mips_pic == NO_PIC
6910 || offset_expr.X_op == O_constant)
6914 /* If this is a reference to a GP relative symbol, we want
6915 <op> $treg,<sym>($gp) (BFD_RELOC_GPREL16)
6916 <op> $treg+1,<sym>+4($gp) (BFD_RELOC_GPREL16)
6917 If we have a base register, we use this
6919 <op> $treg,<sym>($at) (BFD_RELOC_GPREL16)
6920 <op> $treg+1,<sym>+4($at) (BFD_RELOC_GPREL16)
6921 If this is not a GP relative symbol, we want
6922 lui $at,<sym> (BFD_RELOC_HI16_S)
6923 <op> $treg,<sym>($at) (BFD_RELOC_LO16)
6924 <op> $treg+1,<sym>+4($at) (BFD_RELOC_LO16)
6925 If there is a base register, we add it to $at after the
6926 lui instruction. If there is a constant, we always use
6928 if ((valueT) offset_expr.X_add_number > MAX_GPREL_OFFSET
6929 || nopic_need_relax (offset_expr.X_add_symbol, 1))
6941 tempreg = mips_gp_register;
6948 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6949 HAVE_32BIT_ADDRESSES ? HAVE_NEWABI
6950 ? "add" : "addu" : "daddu",
6951 "d,v,t", AT, breg, mips_gp_register);
6957 /* Itbl support may require additional care here. */
6958 macro_build ((char *) NULL, &icnt, &offset_expr, s, fmt,
6959 coproc ? treg + 1 : treg,
6960 (int) BFD_RELOC_GPREL16, tempreg);
6961 offset_expr.X_add_number += 4;
6963 /* Set mips_optimize to 2 to avoid inserting an
6965 hold_mips_optimize = mips_optimize;
6967 /* Itbl support may require additional care here. */
6968 macro_build ((char *) NULL, &icnt, &offset_expr, s, fmt,
6969 coproc ? treg : treg + 1,
6970 (int) BFD_RELOC_GPREL16, tempreg);
6971 mips_optimize = hold_mips_optimize;
6973 p = frag_var (rs_machine_dependent, 12 + off, 0,
6974 RELAX_ENCODE (8 + off, 12 + off, 0, 4 + off, 1,
6975 used_at && mips_opts.noat),
6976 offset_expr.X_add_symbol, 0, NULL);
6978 /* We just generated two relocs. When tc_gen_reloc
6979 handles this case, it will skip the first reloc and
6980 handle the second. The second reloc already has an
6981 extra addend of 4, which we added above. We must
6982 subtract it out, and then subtract another 4 to make
6983 the first reloc come out right. The second reloc
6984 will come out right because we are going to add 4 to
6985 offset_expr when we build its instruction below.
6987 If we have a symbol, then we don't want to include
6988 the offset, because it will wind up being included
6989 when we generate the reloc. */
6991 if (offset_expr.X_op == O_constant)
6992 offset_expr.X_add_number -= 8;
6995 offset_expr.X_add_number = -4;
6996 offset_expr.X_op = O_constant;
6999 macro_build_lui (p, &icnt, &offset_expr, AT);
7004 macro_build (p, &icnt, (expressionS *) NULL,
7005 HAVE_32BIT_ADDRESSES ? HAVE_NEWABI
7006 ? "add" : "addu" : "daddu",
7007 "d,v,t", AT, breg, AT);
7011 /* Itbl support may require additional care here. */
7012 macro_build (p, &icnt, &offset_expr, s, fmt,
7013 coproc ? treg + 1 : treg,
7014 (int) BFD_RELOC_LO16, AT);
7017 /* FIXME: How do we handle overflow here? */
7018 offset_expr.X_add_number += 4;
7019 /* Itbl support may require additional care here. */
7020 macro_build (p, &icnt, &offset_expr, s, fmt,
7021 coproc ? treg : treg + 1,
7022 (int) BFD_RELOC_LO16, AT);
7024 else if (mips_pic == SVR4_PIC && ! mips_big_got)
7028 /* If this is a reference to an external symbol, we want
7029 lw $at,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
7034 lw $at,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
7036 <op> $treg,<sym>($at) (BFD_RELOC_LO16)
7037 <op> $treg+1,<sym>+4($at) (BFD_RELOC_LO16)
7038 If there is a base register we add it to $at before the
7039 lwc1 instructions. If there is a constant we include it
7040 in the lwc1 instructions. */
7042 expr1.X_add_number = offset_expr.X_add_number;
7043 offset_expr.X_add_number = 0;
7044 if (expr1.X_add_number < -0x8000
7045 || expr1.X_add_number >= 0x8000 - 4)
7046 as_bad (_("PIC code offset overflow (max 16 signed bits)"));
7051 frag_grow (24 + off);
7052 macro_build ((char *) NULL, &icnt, &offset_expr,
7053 HAVE_32BIT_ADDRESSES ? "lw" : "ld", "t,o(b)", AT,
7054 (int) BFD_RELOC_MIPS_GOT16, mips_gp_register);
7055 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "");
7057 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7058 HAVE_32BIT_ADDRESSES ? HAVE_NEWABI
7059 ? "add" : "addu" : "daddu",
7060 "d,v,t", AT, breg, AT);
7061 /* Itbl support may require additional care here. */
7062 macro_build ((char *) NULL, &icnt, &expr1, s, fmt,
7063 coproc ? treg + 1 : treg,
7064 (int) BFD_RELOC_LO16, AT);
7065 expr1.X_add_number += 4;
7067 /* Set mips_optimize to 2 to avoid inserting an undesired
7069 hold_mips_optimize = mips_optimize;
7071 /* Itbl support may require additional care here. */
7072 macro_build ((char *) NULL, &icnt, &expr1, s, fmt,
7073 coproc ? treg : treg + 1,
7074 (int) BFD_RELOC_LO16, AT);
7075 mips_optimize = hold_mips_optimize;
7077 (void) frag_var (rs_machine_dependent, 0, 0,
7078 RELAX_ENCODE (0, 0, -16 - off, -8, 1, 0),
7079 offset_expr.X_add_symbol, 0, NULL);
7081 else if (mips_pic == SVR4_PIC)
7086 /* If this is a reference to an external symbol, we want
7087 lui $at,<sym> (BFD_RELOC_MIPS_GOT_HI16)
7089 lw $at,<sym>($at) (BFD_RELOC_MIPS_GOT_LO16)
7094 lw $at,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
7096 <op> $treg,<sym>($at) (BFD_RELOC_LO16)
7097 <op> $treg+1,<sym>+4($at) (BFD_RELOC_LO16)
7098 If there is a base register we add it to $at before the
7099 lwc1 instructions. If there is a constant we include it
7100 in the lwc1 instructions. */
7102 expr1.X_add_number = offset_expr.X_add_number;
7103 offset_expr.X_add_number = 0;
7104 if (expr1.X_add_number < -0x8000
7105 || expr1.X_add_number >= 0x8000 - 4)
7106 as_bad (_("PIC code offset overflow (max 16 signed bits)"));
7107 if (reg_needs_delay (mips_gp_register))
7116 macro_build ((char *) NULL, &icnt, &offset_expr, "lui", "t,u",
7117 AT, (int) BFD_RELOC_MIPS_GOT_HI16);
7118 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7119 HAVE_32BIT_ADDRESSES ? HAVE_NEWABI
7120 ? "add" : "addu" : "daddu",
7121 "d,v,t", AT, AT, mips_gp_register);
7122 macro_build ((char *) NULL, &icnt, &offset_expr,
7123 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
7124 "t,o(b)", AT, (int) BFD_RELOC_MIPS_GOT_LO16, AT);
7125 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "");
7127 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7128 HAVE_32BIT_ADDRESSES ? HAVE_NEWABI
7129 ? "add" : "addu" : "daddu",
7130 "d,v,t", AT, breg, AT);
7131 /* Itbl support may require additional care here. */
7132 macro_build ((char *) NULL, &icnt, &expr1, s, fmt,
7133 coproc ? treg + 1 : treg,
7134 (int) BFD_RELOC_LO16, AT);
7135 expr1.X_add_number += 4;
7137 /* Set mips_optimize to 2 to avoid inserting an undesired
7139 hold_mips_optimize = mips_optimize;
7141 /* Itbl support may require additional care here. */
7142 macro_build ((char *) NULL, &icnt, &expr1, s, fmt,
7143 coproc ? treg : treg + 1,
7144 (int) BFD_RELOC_LO16, AT);
7145 mips_optimize = hold_mips_optimize;
7146 expr1.X_add_number -= 4;
7148 p = frag_var (rs_machine_dependent, 16 + gpdel + off, 0,
7149 RELAX_ENCODE (24 + off, 16 + gpdel + off, gpdel,
7150 8 + gpdel + off, 1, 0),
7151 offset_expr.X_add_symbol, 0, NULL);
7154 macro_build (p, &icnt, (expressionS *) NULL, "nop", "");
7157 macro_build (p, &icnt, &offset_expr,
7158 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
7159 "t,o(b)", AT, (int) BFD_RELOC_MIPS_GOT16,
7162 macro_build (p, &icnt, (expressionS *) NULL, "nop", "");
7166 macro_build (p, &icnt, (expressionS *) NULL,
7167 HAVE_32BIT_ADDRESSES ? HAVE_NEWABI
7168 ? "add" : "addu" : "daddu",
7169 "d,v,t", AT, breg, AT);
7172 /* Itbl support may require additional care here. */
7173 macro_build (p, &icnt, &expr1, s, fmt,
7174 coproc ? treg + 1 : treg,
7175 (int) BFD_RELOC_LO16, AT);
7177 expr1.X_add_number += 4;
7179 /* Set mips_optimize to 2 to avoid inserting an undesired
7181 hold_mips_optimize = mips_optimize;
7183 /* Itbl support may require additional care here. */
7184 macro_build (p, &icnt, &expr1, s, fmt,
7185 coproc ? treg : treg + 1,
7186 (int) BFD_RELOC_LO16, AT);
7187 mips_optimize = hold_mips_optimize;
7189 else if (mips_pic == EMBEDDED_PIC)
7191 /* If there is no base register, we use
7192 <op> $treg,<sym>($gp) (BFD_RELOC_GPREL16)
7193 <op> $treg+1,<sym>+4($gp) (BFD_RELOC_GPREL16)
7194 If we have a base register, we use
7196 <op> $treg,<sym>($at) (BFD_RELOC_GPREL16)
7197 <op> $treg+1,<sym>+4($at) (BFD_RELOC_GPREL16)
7201 tempreg = mips_gp_register;
7206 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7207 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
7208 "d,v,t", AT, breg, mips_gp_register);
7213 /* Itbl support may require additional care here. */
7214 macro_build ((char *) NULL, &icnt, &offset_expr, s, fmt,
7215 coproc ? treg + 1 : treg,
7216 (int) BFD_RELOC_GPREL16, tempreg);
7217 offset_expr.X_add_number += 4;
7218 /* Itbl support may require additional care here. */
7219 macro_build ((char *) NULL, &icnt, &offset_expr, s, fmt,
7220 coproc ? treg : treg + 1,
7221 (int) BFD_RELOC_GPREL16, tempreg);
7237 assert (HAVE_32BIT_ADDRESSES);
7238 macro_build ((char *) NULL, &icnt, &offset_expr, s, "t,o(b)", treg,
7239 (int) BFD_RELOC_LO16, breg);
7240 offset_expr.X_add_number += 4;
7241 macro_build ((char *) NULL, &icnt, &offset_expr, s, "t,o(b)", treg + 1,
7242 (int) BFD_RELOC_LO16, breg);
7245 /* New code added to support COPZ instructions.
7246 This code builds table entries out of the macros in mip_opcodes.
7247 R4000 uses interlocks to handle coproc delays.
7248 Other chips (like the R3000) require nops to be inserted for delays.
7250 FIXME: Currently, we require that the user handle delays.
7251 In order to fill delay slots for non-interlocked chips,
7252 we must have a way to specify delays based on the coprocessor.
7253 Eg. 4 cycles if load coproc reg from memory, 1 if in cache, etc.
7254 What are the side-effects of the cop instruction?
7255 What cache support might we have and what are its effects?
7256 Both coprocessor & memory require delays. how long???
7257 What registers are read/set/modified?
7259 If an itbl is provided to interpret cop instructions,
7260 this knowledge can be encoded in the itbl spec. */
7274 /* For now we just do C (same as Cz). The parameter will be
7275 stored in insn_opcode by mips_ip. */
7276 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "C",
7281 move_register (&icnt, dreg, sreg);
7284 #ifdef LOSING_COMPILER
7286 /* Try and see if this is a new itbl instruction.
7287 This code builds table entries out of the macros in mip_opcodes.
7288 FIXME: For now we just assemble the expression and pass it's
7289 value along as a 32-bit immediate.
7290 We may want to have the assembler assemble this value,
7291 so that we gain the assembler's knowledge of delay slots,
7293 Would it be more efficient to use mask (id) here? */
7294 if (itbl_have_entries
7295 && (immed_expr = itbl_assemble (ip->insn_mo->name, "")))
7297 s = ip->insn_mo->name;
7299 coproc = ITBL_DECODE_PNUM (immed_expr);;
7300 macro_build ((char *) NULL, &icnt, &immed_expr, s, "C");
7307 as_warn (_("Macro used $at after \".set noat\""));
7312 struct mips_cl_insn *ip;
7314 register int treg, sreg, dreg, breg;
7330 bfd_reloc_code_real_type r;
7333 treg = (ip->insn_opcode >> 16) & 0x1f;
7334 dreg = (ip->insn_opcode >> 11) & 0x1f;
7335 sreg = breg = (ip->insn_opcode >> 21) & 0x1f;
7336 mask = ip->insn_mo->mask;
7338 expr1.X_op = O_constant;
7339 expr1.X_op_symbol = NULL;
7340 expr1.X_add_symbol = NULL;
7341 expr1.X_add_number = 1;
7345 #endif /* LOSING_COMPILER */
7350 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7351 dbl ? "dmultu" : "multu", "s,t", sreg, treg);
7352 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "mflo", "d",
7359 /* The MIPS assembler some times generates shifts and adds. I'm
7360 not trying to be that fancy. GCC should do this for us
7362 load_register (&icnt, AT, &imm_expr, dbl);
7363 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7364 dbl ? "dmult" : "mult", "s,t", sreg, AT);
7365 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "mflo", "d",
7379 mips_emit_delays (TRUE);
7380 ++mips_opts.noreorder;
7381 mips_any_noreorder = 1;
7383 load_register (&icnt, AT, &imm_expr, dbl);
7384 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7385 dbl ? "dmult" : "mult", "s,t", sreg, imm ? AT : treg);
7386 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "mflo", "d",
7388 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7389 dbl ? "dsra32" : "sra", "d,w,<", dreg, dreg, RA);
7390 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "mfhi", "d",
7393 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "tne",
7394 "s,t,q", dreg, AT, 6);
7397 expr1.X_add_number = 8;
7398 macro_build ((char *) NULL, &icnt, &expr1, "beq", "s,t,p", dreg,
7400 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "",
7402 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "break",
7405 --mips_opts.noreorder;
7406 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "mflo", "d", dreg);
7419 mips_emit_delays (TRUE);
7420 ++mips_opts.noreorder;
7421 mips_any_noreorder = 1;
7423 load_register (&icnt, AT, &imm_expr, dbl);
7424 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7425 dbl ? "dmultu" : "multu",
7426 "s,t", sreg, imm ? AT : treg);
7427 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "mfhi", "d",
7429 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "mflo", "d",
7432 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "tne",
7436 expr1.X_add_number = 8;
7437 macro_build ((char *) NULL, &icnt, &expr1, "beq", "s,t,p", AT, 0);
7438 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "",
7440 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "break",
7443 --mips_opts.noreorder;
7447 if (ISA_HAS_DROR (mips_opts.isa) || CPU_HAS_DROR (mips_arch))
7459 macro_build ((char *) NULL, &icnt, NULL, "dnegu",
7460 "d,w", tempreg, treg);
7461 macro_build ((char *) NULL, &icnt, NULL, "drorv",
7462 "d,t,s", dreg, sreg, tempreg);
7467 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "dsubu",
7468 "d,v,t", AT, 0, treg);
7469 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "dsrlv",
7470 "d,t,s", AT, sreg, AT);
7471 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "dsllv",
7472 "d,t,s", dreg, sreg, treg);
7473 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or",
7474 "d,v,t", dreg, dreg, AT);
7478 if (ISA_HAS_ROR (mips_opts.isa) || CPU_HAS_ROR (mips_arch))
7490 macro_build ((char *) NULL, &icnt, NULL, "negu",
7491 "d,w", tempreg, treg);
7492 macro_build ((char *) NULL, &icnt, NULL, "rorv",
7493 "d,t,s", dreg, sreg, tempreg);
7498 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "subu",
7499 "d,v,t", AT, 0, treg);
7500 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "srlv",
7501 "d,t,s", AT, sreg, AT);
7502 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sllv",
7503 "d,t,s", dreg, sreg, treg);
7504 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or",
7505 "d,v,t", dreg, dreg, AT);
7513 if (imm_expr.X_op != O_constant)
7514 as_bad (_("Improper rotate count"));
7515 rot = imm_expr.X_add_number & 0x3f;
7516 if (ISA_HAS_DROR (mips_opts.isa) || CPU_HAS_DROR (mips_arch))
7518 rot = (64 - rot) & 0x3f;
7520 macro_build ((char *) NULL, &icnt, NULL, "dror32",
7521 "d,w,<", dreg, sreg, rot - 32);
7523 macro_build ((char *) NULL, &icnt, NULL, "dror",
7524 "d,w,<", dreg, sreg, rot);
7529 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "dsrl",
7530 "d,w,<", dreg, sreg, 0);
7533 l = (rot < 0x20) ? "dsll" : "dsll32";
7534 r = ((0x40 - rot) < 0x20) ? "dsrl" : "dsrl32";
7536 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, l,
7537 "d,w,<", AT, sreg, rot);
7538 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, r,
7539 "d,w,<", dreg, sreg, (0x20 - rot) & 0x1f);
7540 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or",
7541 "d,v,t", dreg, dreg, AT);
7549 if (imm_expr.X_op != O_constant)
7550 as_bad (_("Improper rotate count"));
7551 rot = imm_expr.X_add_number & 0x1f;
7552 if (ISA_HAS_ROR (mips_opts.isa) || CPU_HAS_ROR (mips_arch))
7554 macro_build ((char *) NULL, &icnt, NULL, "ror",
7555 "d,w,<", dreg, sreg, (32 - rot) & 0x1f);
7560 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "srl",
7561 "d,w,<", dreg, sreg, 0);
7564 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sll",
7565 "d,w,<", AT, sreg, rot);
7566 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "srl",
7567 "d,w,<", dreg, sreg, (0x20 - rot) & 0x1f);
7568 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or",
7569 "d,v,t", dreg, dreg, AT);
7574 if (ISA_HAS_DROR (mips_opts.isa) || CPU_HAS_DROR (mips_arch))
7576 macro_build ((char *) NULL, &icnt, NULL, "drorv",
7577 "d,t,s", dreg, sreg, treg);
7580 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "dsubu",
7581 "d,v,t", AT, 0, treg);
7582 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "dsllv",
7583 "d,t,s", AT, sreg, AT);
7584 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "dsrlv",
7585 "d,t,s", dreg, sreg, treg);
7586 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or",
7587 "d,v,t", dreg, dreg, AT);
7591 if (ISA_HAS_ROR (mips_opts.isa) || CPU_HAS_ROR (mips_arch))
7593 macro_build ((char *) NULL, &icnt, NULL, "rorv",
7594 "d,t,s", dreg, sreg, treg);
7597 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "subu",
7598 "d,v,t", AT, 0, treg);
7599 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sllv",
7600 "d,t,s", AT, sreg, AT);
7601 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "srlv",
7602 "d,t,s", dreg, sreg, treg);
7603 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or",
7604 "d,v,t", dreg, dreg, AT);
7612 if (imm_expr.X_op != O_constant)
7613 as_bad (_("Improper rotate count"));
7614 rot = imm_expr.X_add_number & 0x3f;
7615 if (ISA_HAS_DROR (mips_opts.isa) || CPU_HAS_DROR (mips_arch))
7618 macro_build ((char *) NULL, &icnt, NULL, "dror32",
7619 "d,w,<", dreg, sreg, rot - 32);
7621 macro_build ((char *) NULL, &icnt, NULL, "dror",
7622 "d,w,<", dreg, sreg, rot);
7627 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "dsrl",
7628 "d,w,<", dreg, sreg, 0);
7631 r = (rot < 0x20) ? "dsrl" : "dsrl32";
7632 l = ((0x40 - rot) < 0x20) ? "dsll" : "dsll32";
7634 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, r,
7635 "d,w,<", AT, sreg, rot);
7636 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, l,
7637 "d,w,<", dreg, sreg, (0x20 - rot) & 0x1f);
7638 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or",
7639 "d,v,t", dreg, dreg, AT);
7647 if (imm_expr.X_op != O_constant)
7648 as_bad (_("Improper rotate count"));
7649 rot = imm_expr.X_add_number & 0x1f;
7650 if (ISA_HAS_ROR (mips_opts.isa) || CPU_HAS_ROR (mips_arch))
7652 macro_build ((char *) NULL, &icnt, NULL, "ror",
7653 "d,w,<", dreg, sreg, rot);
7658 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "srl",
7659 "d,w,<", dreg, sreg, 0);
7662 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "srl",
7663 "d,w,<", AT, sreg, rot);
7664 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sll",
7665 "d,w,<", dreg, sreg, (0x20 - rot) & 0x1f);
7666 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or",
7667 "d,v,t", dreg, dreg, AT);
7672 if (mips_arch == CPU_R4650)
7674 as_bad (_("opcode not supported on this processor"));
7677 assert (mips_opts.isa == ISA_MIPS1);
7678 /* Even on a big endian machine $fn comes before $fn+1. We have
7679 to adjust when storing to memory. */
7680 macro_build ((char *) NULL, &icnt, &offset_expr, "swc1", "T,o(b)",
7681 target_big_endian ? treg + 1 : treg,
7682 (int) BFD_RELOC_LO16, breg);
7683 offset_expr.X_add_number += 4;
7684 macro_build ((char *) NULL, &icnt, &offset_expr, "swc1", "T,o(b)",
7685 target_big_endian ? treg : treg + 1,
7686 (int) BFD_RELOC_LO16, breg);
7691 macro_build ((char *) NULL, &icnt, &expr1, "sltiu", "t,r,j", dreg,
7692 treg, (int) BFD_RELOC_LO16);
7694 macro_build ((char *) NULL, &icnt, &expr1, "sltiu", "t,r,j", dreg,
7695 sreg, (int) BFD_RELOC_LO16);
7698 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "xor",
7699 "d,v,t", dreg, sreg, treg);
7700 macro_build ((char *) NULL, &icnt, &expr1, "sltiu", "t,r,j", dreg,
7701 dreg, (int) BFD_RELOC_LO16);
7706 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
7708 macro_build ((char *) NULL, &icnt, &expr1, "sltiu", "t,r,j", dreg,
7709 sreg, (int) BFD_RELOC_LO16);
7714 as_warn (_("Instruction %s: result is always false"),
7716 move_register (&icnt, dreg, 0);
7719 if (imm_expr.X_op == O_constant
7720 && imm_expr.X_add_number >= 0
7721 && imm_expr.X_add_number < 0x10000)
7723 macro_build ((char *) NULL, &icnt, &imm_expr, "xori", "t,r,i", dreg,
7724 sreg, (int) BFD_RELOC_LO16);
7727 else if (imm_expr.X_op == O_constant
7728 && imm_expr.X_add_number > -0x8000
7729 && imm_expr.X_add_number < 0)
7731 imm_expr.X_add_number = -imm_expr.X_add_number;
7732 macro_build ((char *) NULL, &icnt, &imm_expr,
7733 HAVE_32BIT_GPRS ? "addiu" : "daddiu",
7734 "t,r,j", dreg, sreg,
7735 (int) BFD_RELOC_LO16);
7740 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_GPRS);
7741 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "xor",
7742 "d,v,t", dreg, sreg, AT);
7745 macro_build ((char *) NULL, &icnt, &expr1, "sltiu", "t,r,j", dreg, dreg,
7746 (int) BFD_RELOC_LO16);
7751 case M_SGE: /* sreg >= treg <==> not (sreg < treg) */
7757 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "d,v,t",
7759 macro_build ((char *) NULL, &icnt, &expr1, "xori", "t,r,i", dreg, dreg,
7760 (int) BFD_RELOC_LO16);
7763 case M_SGE_I: /* sreg >= I <==> not (sreg < I) */
7765 if (imm_expr.X_op == O_constant
7766 && imm_expr.X_add_number >= -0x8000
7767 && imm_expr.X_add_number < 0x8000)
7769 macro_build ((char *) NULL, &icnt, &imm_expr,
7770 mask == M_SGE_I ? "slti" : "sltiu",
7771 "t,r,j", dreg, sreg, (int) BFD_RELOC_LO16);
7776 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_GPRS);
7777 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7778 mask == M_SGE_I ? "slt" : "sltu", "d,v,t", dreg, sreg,
7782 macro_build ((char *) NULL, &icnt, &expr1, "xori", "t,r,i", dreg, dreg,
7783 (int) BFD_RELOC_LO16);
7788 case M_SGT: /* sreg > treg <==> treg < sreg */
7794 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "d,v,t",
7798 case M_SGT_I: /* sreg > I <==> I < sreg */
7804 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_GPRS);
7805 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "d,v,t",
7809 case M_SLE: /* sreg <= treg <==> treg >= sreg <==> not (treg < sreg) */
7815 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "d,v,t",
7817 macro_build ((char *) NULL, &icnt, &expr1, "xori", "t,r,i", dreg, dreg,
7818 (int) BFD_RELOC_LO16);
7821 case M_SLE_I: /* sreg <= I <==> I >= sreg <==> not (I < sreg) */
7827 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_GPRS);
7828 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "d,v,t",
7830 macro_build ((char *) NULL, &icnt, &expr1, "xori", "t,r,i", dreg, dreg,
7831 (int) BFD_RELOC_LO16);
7835 if (imm_expr.X_op == O_constant
7836 && imm_expr.X_add_number >= -0x8000
7837 && imm_expr.X_add_number < 0x8000)
7839 macro_build ((char *) NULL, &icnt, &imm_expr, "slti", "t,r,j",
7840 dreg, sreg, (int) BFD_RELOC_LO16);
7843 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_GPRS);
7844 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "slt", "d,v,t",
7849 if (imm_expr.X_op == O_constant
7850 && imm_expr.X_add_number >= -0x8000
7851 && imm_expr.X_add_number < 0x8000)
7853 macro_build ((char *) NULL, &icnt, &imm_expr, "sltiu", "t,r,j",
7854 dreg, sreg, (int) BFD_RELOC_LO16);
7857 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_GPRS);
7858 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sltu",
7859 "d,v,t", dreg, sreg, AT);
7864 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sltu",
7865 "d,v,t", dreg, 0, treg);
7867 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sltu",
7868 "d,v,t", dreg, 0, sreg);
7871 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "xor",
7872 "d,v,t", dreg, sreg, treg);
7873 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sltu",
7874 "d,v,t", dreg, 0, dreg);
7879 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
7881 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sltu",
7882 "d,v,t", dreg, 0, sreg);
7887 as_warn (_("Instruction %s: result is always true"),
7889 macro_build ((char *) NULL, &icnt, &expr1,
7890 HAVE_32BIT_GPRS ? "addiu" : "daddiu",
7891 "t,r,j", dreg, 0, (int) BFD_RELOC_LO16);
7894 if (imm_expr.X_op == O_constant
7895 && imm_expr.X_add_number >= 0
7896 && imm_expr.X_add_number < 0x10000)
7898 macro_build ((char *) NULL, &icnt, &imm_expr, "xori", "t,r,i",
7899 dreg, sreg, (int) BFD_RELOC_LO16);
7902 else if (imm_expr.X_op == O_constant
7903 && imm_expr.X_add_number > -0x8000
7904 && imm_expr.X_add_number < 0)
7906 imm_expr.X_add_number = -imm_expr.X_add_number;
7907 macro_build ((char *) NULL, &icnt, &imm_expr,
7908 HAVE_32BIT_GPRS ? "addiu" : "daddiu",
7909 "t,r,j", dreg, sreg, (int) BFD_RELOC_LO16);
7914 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_GPRS);
7915 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "xor",
7916 "d,v,t", dreg, sreg, AT);
7919 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sltu",
7920 "d,v,t", dreg, 0, dreg);
7928 if (imm_expr.X_op == O_constant
7929 && imm_expr.X_add_number > -0x8000
7930 && imm_expr.X_add_number <= 0x8000)
7932 imm_expr.X_add_number = -imm_expr.X_add_number;
7933 macro_build ((char *) NULL, &icnt, &imm_expr,
7934 dbl ? "daddi" : "addi",
7935 "t,r,j", dreg, sreg, (int) BFD_RELOC_LO16);
7938 load_register (&icnt, AT, &imm_expr, dbl);
7939 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7940 dbl ? "dsub" : "sub", "d,v,t", dreg, sreg, AT);
7946 if (imm_expr.X_op == O_constant
7947 && imm_expr.X_add_number > -0x8000
7948 && imm_expr.X_add_number <= 0x8000)
7950 imm_expr.X_add_number = -imm_expr.X_add_number;
7951 macro_build ((char *) NULL, &icnt, &imm_expr,
7952 dbl ? "daddiu" : "addiu",
7953 "t,r,j", dreg, sreg, (int) BFD_RELOC_LO16);
7956 load_register (&icnt, AT, &imm_expr, dbl);
7957 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7958 dbl ? "dsubu" : "subu", "d,v,t", dreg, sreg, AT);
7979 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_GPRS);
7980 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "s,t", sreg,
7986 assert (mips_opts.isa == ISA_MIPS1);
7987 sreg = (ip->insn_opcode >> 11) & 0x1f; /* floating reg */
7988 dreg = (ip->insn_opcode >> 06) & 0x1f; /* floating reg */
7991 * Is the double cfc1 instruction a bug in the mips assembler;
7992 * or is there a reason for it?
7994 mips_emit_delays (TRUE);
7995 ++mips_opts.noreorder;
7996 mips_any_noreorder = 1;
7997 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "cfc1", "t,G",
7999 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "cfc1", "t,G",
8001 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "");
8002 expr1.X_add_number = 3;
8003 macro_build ((char *) NULL, &icnt, &expr1, "ori", "t,r,i", AT, treg,
8004 (int) BFD_RELOC_LO16);
8005 expr1.X_add_number = 2;
8006 macro_build ((char *) NULL, &icnt, &expr1, "xori", "t,r,i", AT, AT,
8007 (int) BFD_RELOC_LO16);
8008 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "ctc1", "t,G",
8010 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "");
8011 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
8012 mask == M_TRUNCWD ? "cvt.w.d" : "cvt.w.s", "D,S", dreg, sreg);
8013 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "ctc1", "t,G",
8015 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "");
8016 --mips_opts.noreorder;
8025 if (offset_expr.X_add_number >= 0x7fff)
8026 as_bad (_("operand overflow"));
8027 if (! target_big_endian)
8028 ++offset_expr.X_add_number;
8029 macro_build ((char *) NULL, &icnt, &offset_expr, s, "t,o(b)", AT,
8030 (int) BFD_RELOC_LO16, breg);
8031 if (! target_big_endian)
8032 --offset_expr.X_add_number;
8034 ++offset_expr.X_add_number;
8035 macro_build ((char *) NULL, &icnt, &offset_expr, "lbu", "t,o(b)", treg,
8036 (int) BFD_RELOC_LO16, breg);
8037 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sll", "d,w,<",
8039 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or", "d,v,t",
8053 if (offset_expr.X_add_number >= 0x8000 - off)
8054 as_bad (_("operand overflow"));
8059 if (! target_big_endian)
8060 offset_expr.X_add_number += off;
8061 macro_build ((char *) NULL, &icnt, &offset_expr, s, "t,o(b)", tempreg,
8062 (int) BFD_RELOC_LO16, breg);
8063 if (! target_big_endian)
8064 offset_expr.X_add_number -= off;
8066 offset_expr.X_add_number += off;
8067 macro_build ((char *) NULL, &icnt, &offset_expr, s2, "t,o(b)", tempreg,
8068 (int) BFD_RELOC_LO16, breg);
8070 /* If necessary, move the result in tempreg the final destination. */
8071 if (treg == tempreg)
8073 /* Protect second load's delay slot. */
8074 if (!gpr_interlocks)
8075 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "");
8076 move_register (&icnt, treg, tempreg);
8090 load_address (&icnt, AT, &offset_expr, &used_at);
8092 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
8093 HAVE_32BIT_ADDRESSES ? HAVE_NEWABI
8094 ? "add" : "addu" : "daddu",
8095 "d,v,t", AT, AT, breg);
8096 if (! target_big_endian)
8097 expr1.X_add_number = off;
8099 expr1.X_add_number = 0;
8100 macro_build ((char *) NULL, &icnt, &expr1, s, "t,o(b)", treg,
8101 (int) BFD_RELOC_LO16, AT);
8102 if (! target_big_endian)
8103 expr1.X_add_number = 0;
8105 expr1.X_add_number = off;
8106 macro_build ((char *) NULL, &icnt, &expr1, s2, "t,o(b)", treg,
8107 (int) BFD_RELOC_LO16, AT);
8113 load_address (&icnt, AT, &offset_expr, &used_at);
8115 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
8116 HAVE_32BIT_ADDRESSES ? HAVE_NEWABI
8117 ? "add" : "addu" : "daddu",
8118 "d,v,t", AT, AT, breg);
8119 if (target_big_endian)
8120 expr1.X_add_number = 0;
8121 macro_build ((char *) NULL, &icnt, &expr1,
8122 mask == M_ULH_A ? "lb" : "lbu", "t,o(b)", treg,
8123 (int) BFD_RELOC_LO16, AT);
8124 if (target_big_endian)
8125 expr1.X_add_number = 1;
8127 expr1.X_add_number = 0;
8128 macro_build ((char *) NULL, &icnt, &expr1, "lbu", "t,o(b)", AT,
8129 (int) BFD_RELOC_LO16, AT);
8130 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sll", "d,w,<",
8132 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or", "d,v,t",
8137 if (offset_expr.X_add_number >= 0x7fff)
8138 as_bad (_("operand overflow"));
8139 if (target_big_endian)
8140 ++offset_expr.X_add_number;
8141 macro_build ((char *) NULL, &icnt, &offset_expr, "sb", "t,o(b)", treg,
8142 (int) BFD_RELOC_LO16, breg);
8143 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "srl", "d,w,<",
8145 if (target_big_endian)
8146 --offset_expr.X_add_number;
8148 ++offset_expr.X_add_number;
8149 macro_build ((char *) NULL, &icnt, &offset_expr, "sb", "t,o(b)", AT,
8150 (int) BFD_RELOC_LO16, breg);
8163 if (offset_expr.X_add_number >= 0x8000 - off)
8164 as_bad (_("operand overflow"));
8165 if (! target_big_endian)
8166 offset_expr.X_add_number += off;
8167 macro_build ((char *) NULL, &icnt, &offset_expr, s, "t,o(b)", treg,
8168 (int) BFD_RELOC_LO16, breg);
8169 if (! target_big_endian)
8170 offset_expr.X_add_number -= off;
8172 offset_expr.X_add_number += off;
8173 macro_build ((char *) NULL, &icnt, &offset_expr, s2, "t,o(b)", treg,
8174 (int) BFD_RELOC_LO16, breg);
8188 load_address (&icnt, AT, &offset_expr, &used_at);
8190 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
8191 HAVE_32BIT_ADDRESSES ? HAVE_NEWABI
8192 ? "add" : "addu" : "daddu",
8193 "d,v,t", AT, AT, breg);
8194 if (! target_big_endian)
8195 expr1.X_add_number = off;
8197 expr1.X_add_number = 0;
8198 macro_build ((char *) NULL, &icnt, &expr1, s, "t,o(b)", treg,
8199 (int) BFD_RELOC_LO16, AT);
8200 if (! target_big_endian)
8201 expr1.X_add_number = 0;
8203 expr1.X_add_number = off;
8204 macro_build ((char *) NULL, &icnt, &expr1, s2, "t,o(b)", treg,
8205 (int) BFD_RELOC_LO16, AT);
8210 load_address (&icnt, AT, &offset_expr, &used_at);
8212 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
8213 HAVE_32BIT_ADDRESSES ? HAVE_NEWABI
8214 ? "add" : "addu" : "daddu",
8215 "d,v,t", AT, AT, breg);
8216 if (! target_big_endian)
8217 expr1.X_add_number = 0;
8218 macro_build ((char *) NULL, &icnt, &expr1, "sb", "t,o(b)", treg,
8219 (int) BFD_RELOC_LO16, AT);
8220 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "srl", "d,w,<",
8222 if (! target_big_endian)
8223 expr1.X_add_number = 1;
8225 expr1.X_add_number = 0;
8226 macro_build ((char *) NULL, &icnt, &expr1, "sb", "t,o(b)", treg,
8227 (int) BFD_RELOC_LO16, AT);
8228 if (! target_big_endian)
8229 expr1.X_add_number = 0;
8231 expr1.X_add_number = 1;
8232 macro_build ((char *) NULL, &icnt, &expr1, "lbu", "t,o(b)", AT,
8233 (int) BFD_RELOC_LO16, AT);
8234 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sll", "d,w,<",
8236 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or", "d,v,t",
8241 /* FIXME: Check if this is one of the itbl macros, since they
8242 are added dynamically. */
8243 as_bad (_("Macro %s not implemented yet"), ip->insn_mo->name);
8247 as_warn (_("Macro used $at after \".set noat\""));
8250 /* Implement macros in mips16 mode. */
8254 struct mips_cl_insn *ip;
8257 int xreg, yreg, zreg, tmp;
8261 const char *s, *s2, *s3;
8263 mask = ip->insn_mo->mask;
8265 xreg = (ip->insn_opcode >> MIPS16OP_SH_RX) & MIPS16OP_MASK_RX;
8266 yreg = (ip->insn_opcode >> MIPS16OP_SH_RY) & MIPS16OP_MASK_RY;
8267 zreg = (ip->insn_opcode >> MIPS16OP_SH_RZ) & MIPS16OP_MASK_RZ;
8271 expr1.X_op = O_constant;
8272 expr1.X_op_symbol = NULL;
8273 expr1.X_add_symbol = NULL;
8274 expr1.X_add_number = 1;
8293 mips_emit_delays (TRUE);
8294 ++mips_opts.noreorder;
8295 mips_any_noreorder = 1;
8296 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
8297 dbl ? "ddiv" : "div",
8298 "0,x,y", xreg, yreg);
8299 expr1.X_add_number = 2;
8300 macro_build ((char *) NULL, &icnt, &expr1, "bnez", "x,p", yreg);
8301 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "break", "6",
8304 /* FIXME: The normal code checks for of -1 / -0x80000000 here,
8305 since that causes an overflow. We should do that as well,
8306 but I don't see how to do the comparisons without a temporary
8308 --mips_opts.noreorder;
8309 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "x", zreg);
8328 mips_emit_delays (TRUE);
8329 ++mips_opts.noreorder;
8330 mips_any_noreorder = 1;
8331 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "0,x,y",
8333 expr1.X_add_number = 2;
8334 macro_build ((char *) NULL, &icnt, &expr1, "bnez", "x,p", yreg);
8335 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "break",
8337 --mips_opts.noreorder;
8338 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s2, "x", zreg);
8344 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
8345 dbl ? "dmultu" : "multu", "x,y", xreg, yreg);
8346 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "mflo", "x",
8355 if (imm_expr.X_op != O_constant)
8356 as_bad (_("Unsupported large constant"));
8357 imm_expr.X_add_number = -imm_expr.X_add_number;
8358 macro_build ((char *) NULL, &icnt, &imm_expr,
8359 dbl ? "daddiu" : "addiu", "y,x,4", yreg, xreg);
8363 if (imm_expr.X_op != O_constant)
8364 as_bad (_("Unsupported large constant"));
8365 imm_expr.X_add_number = -imm_expr.X_add_number;
8366 macro_build ((char *) NULL, &icnt, &imm_expr, "addiu",
8371 if (imm_expr.X_op != O_constant)
8372 as_bad (_("Unsupported large constant"));
8373 imm_expr.X_add_number = -imm_expr.X_add_number;
8374 macro_build ((char *) NULL, &icnt, &imm_expr, "daddiu",
8397 goto do_reverse_branch;
8401 goto do_reverse_branch;
8413 goto do_reverse_branch;
8424 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "x,y",
8426 macro_build ((char *) NULL, &icnt, &offset_expr, s2, "p");
8453 goto do_addone_branch_i;
8458 goto do_addone_branch_i;
8473 goto do_addone_branch_i;
8480 if (imm_expr.X_op != O_constant)
8481 as_bad (_("Unsupported large constant"));
8482 ++imm_expr.X_add_number;
8485 macro_build ((char *) NULL, &icnt, &imm_expr, s, s3, xreg);
8486 macro_build ((char *) NULL, &icnt, &offset_expr, s2, "p");
8490 expr1.X_add_number = 0;
8491 macro_build ((char *) NULL, &icnt, &expr1, "slti", "x,8", yreg);
8493 move_register (&icnt, xreg, yreg);
8494 expr1.X_add_number = 2;
8495 macro_build ((char *) NULL, &icnt, &expr1, "bteqz", "p");
8496 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
8497 "neg", "x,w", xreg, xreg);
8501 /* For consistency checking, verify that all bits are specified either
8502 by the match/mask part of the instruction definition, or by the
8505 validate_mips_insn (opc)
8506 const struct mips_opcode *opc;
8508 const char *p = opc->args;
8510 unsigned long used_bits = opc->mask;
8512 if ((used_bits & opc->match) != opc->match)
8514 as_bad (_("internal: bad mips opcode (mask error): %s %s"),
8515 opc->name, opc->args);
8518 #define USE_BITS(mask,shift) (used_bits |= ((mask) << (shift)))
8528 case 'A': USE_BITS (OP_MASK_SHAMT, OP_SH_SHAMT); break;
8529 case 'B': USE_BITS (OP_MASK_INSMSB, OP_SH_INSMSB); break;
8530 case 'C': USE_BITS (OP_MASK_EXTMSBD, OP_SH_EXTMSBD); break;
8531 case 'D': USE_BITS (OP_MASK_RD, OP_SH_RD);
8532 USE_BITS (OP_MASK_SEL, OP_SH_SEL); break;
8534 as_bad (_("internal: bad mips opcode (unknown extension operand type `+%c'): %s %s"),
8535 c, opc->name, opc->args);
8539 case '<': USE_BITS (OP_MASK_SHAMT, OP_SH_SHAMT); break;
8540 case '>': USE_BITS (OP_MASK_SHAMT, OP_SH_SHAMT); break;
8542 case 'B': USE_BITS (OP_MASK_CODE20, OP_SH_CODE20); break;
8543 case 'C': USE_BITS (OP_MASK_COPZ, OP_SH_COPZ); break;
8544 case 'D': USE_BITS (OP_MASK_FD, OP_SH_FD); break;
8545 case 'E': USE_BITS (OP_MASK_RT, OP_SH_RT); break;
8547 case 'G': USE_BITS (OP_MASK_RD, OP_SH_RD); break;
8548 case 'H': USE_BITS (OP_MASK_SEL, OP_SH_SEL); break;
8550 case 'J': USE_BITS (OP_MASK_CODE19, OP_SH_CODE19); break;
8551 case 'K': USE_BITS (OP_MASK_RD, OP_SH_RD); break;
8553 case 'M': USE_BITS (OP_MASK_CCC, OP_SH_CCC); break;
8554 case 'N': USE_BITS (OP_MASK_BCC, OP_SH_BCC); break;
8555 case 'O': USE_BITS (OP_MASK_ALN, OP_SH_ALN); break;
8556 case 'Q': USE_BITS (OP_MASK_VSEL, OP_SH_VSEL);
8557 USE_BITS (OP_MASK_FT, OP_SH_FT); break;
8558 case 'R': USE_BITS (OP_MASK_FR, OP_SH_FR); break;
8559 case 'S': USE_BITS (OP_MASK_FS, OP_SH_FS); break;
8560 case 'T': USE_BITS (OP_MASK_FT, OP_SH_FT); break;
8561 case 'V': USE_BITS (OP_MASK_FS, OP_SH_FS); break;
8562 case 'W': USE_BITS (OP_MASK_FT, OP_SH_FT); break;
8563 case 'X': USE_BITS (OP_MASK_FD, OP_SH_FD); break;
8564 case 'Y': USE_BITS (OP_MASK_FS, OP_SH_FS); break;
8565 case 'Z': USE_BITS (OP_MASK_FT, OP_SH_FT); break;
8566 case 'a': USE_BITS (OP_MASK_TARGET, OP_SH_TARGET); break;
8567 case 'b': USE_BITS (OP_MASK_RS, OP_SH_RS); break;
8568 case 'c': USE_BITS (OP_MASK_CODE, OP_SH_CODE); break;
8569 case 'd': USE_BITS (OP_MASK_RD, OP_SH_RD); break;
8571 case 'h': USE_BITS (OP_MASK_PREFX, OP_SH_PREFX); break;
8572 case 'i': USE_BITS (OP_MASK_IMMEDIATE, OP_SH_IMMEDIATE); break;
8573 case 'j': USE_BITS (OP_MASK_DELTA, OP_SH_DELTA); break;
8574 case 'k': USE_BITS (OP_MASK_CACHE, OP_SH_CACHE); break;
8576 case 'o': USE_BITS (OP_MASK_DELTA, OP_SH_DELTA); break;
8577 case 'p': USE_BITS (OP_MASK_DELTA, OP_SH_DELTA); break;
8578 case 'q': USE_BITS (OP_MASK_CODE2, OP_SH_CODE2); break;
8579 case 'r': USE_BITS (OP_MASK_RS, OP_SH_RS); break;
8580 case 's': USE_BITS (OP_MASK_RS, OP_SH_RS); break;
8581 case 't': USE_BITS (OP_MASK_RT, OP_SH_RT); break;
8582 case 'u': USE_BITS (OP_MASK_IMMEDIATE, OP_SH_IMMEDIATE); break;
8583 case 'v': USE_BITS (OP_MASK_RS, OP_SH_RS); break;
8584 case 'w': USE_BITS (OP_MASK_RT, OP_SH_RT); break;
8587 case 'P': USE_BITS (OP_MASK_PERFREG, OP_SH_PERFREG); break;
8588 case 'U': USE_BITS (OP_MASK_RD, OP_SH_RD);
8589 USE_BITS (OP_MASK_RT, OP_SH_RT); break;
8590 case 'e': USE_BITS (OP_MASK_VECBYTE, OP_SH_VECBYTE); break;
8591 case '%': USE_BITS (OP_MASK_VECALIGN, OP_SH_VECALIGN); break;
8595 as_bad (_("internal: bad mips opcode (unknown operand type `%c'): %s %s"),
8596 c, opc->name, opc->args);
8600 if (used_bits != 0xffffffff)
8602 as_bad (_("internal: bad mips opcode (bits 0x%lx undefined): %s %s"),
8603 ~used_bits & 0xffffffff, opc->name, opc->args);
8609 /* This routine assembles an instruction into its binary format. As a
8610 side effect, it sets one of the global variables imm_reloc or
8611 offset_reloc to the type of relocation to do if one of the operands
8612 is an address expression. */
8617 struct mips_cl_insn *ip;
8622 struct mips_opcode *insn;
8625 unsigned int lastregno = 0;
8626 unsigned int lastpos = 0;
8627 unsigned int limlo, limhi;
8633 /* If the instruction contains a '.', we first try to match an instruction
8634 including the '.'. Then we try again without the '.'. */
8636 for (s = str; *s != '\0' && !ISSPACE (*s); ++s)
8639 /* If we stopped on whitespace, then replace the whitespace with null for
8640 the call to hash_find. Save the character we replaced just in case we
8641 have to re-parse the instruction. */
8648 insn = (struct mips_opcode *) hash_find (op_hash, str);
8650 /* If we didn't find the instruction in the opcode table, try again, but
8651 this time with just the instruction up to, but not including the
8655 /* Restore the character we overwrite above (if any). */
8659 /* Scan up to the first '.' or whitespace. */
8661 *s != '\0' && *s != '.' && !ISSPACE (*s);
8665 /* If we did not find a '.', then we can quit now. */
8668 insn_error = "unrecognized opcode";
8672 /* Lookup the instruction in the hash table. */
8674 if ((insn = (struct mips_opcode *) hash_find (op_hash, str)) == NULL)
8676 insn_error = "unrecognized opcode";
8686 assert (strcmp (insn->name, str) == 0);
8688 if (OPCODE_IS_MEMBER (insn,
8690 | (file_ase_mips16 ? INSN_MIPS16 : 0)
8691 | (mips_opts.ase_mdmx ? INSN_MDMX : 0)
8692 | (mips_opts.ase_mips3d ? INSN_MIPS3D : 0)),
8698 if (insn->pinfo != INSN_MACRO)
8700 if (mips_arch == CPU_R4650 && (insn->pinfo & FP_D) != 0)
8706 if (insn + 1 < &mips_opcodes[NUMOPCODES]
8707 && strcmp (insn->name, insn[1].name) == 0)
8716 static char buf[100];
8717 if (mips_arch_info->is_isa)
8719 _("opcode not supported at this ISA level (%s)"),
8720 mips_cpu_info_from_isa (mips_opts.isa)->name);
8723 _("opcode not supported on this processor: %s (%s)"),
8724 mips_arch_info->name,
8725 mips_cpu_info_from_isa (mips_opts.isa)->name);
8735 ip->insn_opcode = insn->match;
8737 for (args = insn->args;; ++args)
8741 s += strspn (s, " \t");
8745 case '\0': /* end of args */
8758 ip->insn_opcode |= lastregno << OP_SH_RS;
8762 ip->insn_opcode |= lastregno << OP_SH_RT;
8766 ip->insn_opcode |= lastregno << OP_SH_FT;
8770 ip->insn_opcode |= lastregno << OP_SH_FS;
8776 /* Handle optional base register.
8777 Either the base register is omitted or
8778 we must have a left paren. */
8779 /* This is dependent on the next operand specifier
8780 is a base register specification. */
8781 assert (args[1] == 'b' || args[1] == '5'
8782 || args[1] == '-' || args[1] == '4');
8786 case ')': /* these must match exactly */
8793 case '+': /* Opcode extension character. */
8796 case 'A': /* ins/ext position, becomes LSB. */
8799 my_getExpression (&imm_expr, s);
8800 check_absolute_expr (ip, &imm_expr);
8801 if ((unsigned long) imm_expr.X_add_number < limlo
8802 || (unsigned long) imm_expr.X_add_number > limhi)
8804 as_bad (_("Improper position (%lu)"),
8805 (unsigned long) imm_expr.X_add_number);
8806 imm_expr.X_add_number = limlo;
8808 lastpos = imm_expr.X_add_number;
8809 ip->insn_opcode |= (imm_expr.X_add_number
8810 & OP_MASK_SHAMT) << OP_SH_SHAMT;
8811 imm_expr.X_op = O_absent;
8815 case 'B': /* ins size, becomes MSB. */
8818 my_getExpression (&imm_expr, s);
8819 check_absolute_expr (ip, &imm_expr);
8820 /* Check for negative input so that small negative numbers
8821 will not succeed incorrectly. The checks against
8822 (pos+size) transitively check "size" itself,
8823 assuming that "pos" is reasonable. */
8824 if ((long) imm_expr.X_add_number < 0
8825 || ((unsigned long) imm_expr.X_add_number
8827 || ((unsigned long) imm_expr.X_add_number
8830 as_bad (_("Improper insert size (%lu, position %lu)"),
8831 (unsigned long) imm_expr.X_add_number,
8832 (unsigned long) lastpos);
8833 imm_expr.X_add_number = limlo - lastpos;
8835 ip->insn_opcode |= ((lastpos + imm_expr.X_add_number - 1)
8836 & OP_MASK_INSMSB) << OP_SH_INSMSB;
8837 imm_expr.X_op = O_absent;
8841 case 'C': /* ext size, becomes MSBD. */
8844 my_getExpression (&imm_expr, s);
8845 check_absolute_expr (ip, &imm_expr);
8846 /* Check for negative input so that small negative numbers
8847 will not succeed incorrectly. The checks against
8848 (pos+size) transitively check "size" itself,
8849 assuming that "pos" is reasonable. */
8850 if ((long) imm_expr.X_add_number < 0
8851 || ((unsigned long) imm_expr.X_add_number
8853 || ((unsigned long) imm_expr.X_add_number
8856 as_bad (_("Improper extract size (%lu, position %lu)"),
8857 (unsigned long) imm_expr.X_add_number,
8858 (unsigned long) lastpos);
8859 imm_expr.X_add_number = limlo - lastpos;
8861 ip->insn_opcode |= ((imm_expr.X_add_number - 1)
8862 & OP_MASK_EXTMSBD) << OP_SH_EXTMSBD;
8863 imm_expr.X_op = O_absent;
8868 /* +D is for disassembly only; never match. */
8872 as_bad (_("internal: bad mips opcode (unknown extension operand type `+%c'): %s %s"),
8873 *args, insn->name, insn->args);
8874 /* Further processing is fruitless. */
8879 case '<': /* must be at least one digit */
8881 * According to the manual, if the shift amount is greater
8882 * than 31 or less than 0, then the shift amount should be
8883 * mod 32. In reality the mips assembler issues an error.
8884 * We issue a warning and mask out all but the low 5 bits.
8886 my_getExpression (&imm_expr, s);
8887 check_absolute_expr (ip, &imm_expr);
8888 if ((unsigned long) imm_expr.X_add_number > 31)
8890 as_warn (_("Improper shift amount (%lu)"),
8891 (unsigned long) imm_expr.X_add_number);
8892 imm_expr.X_add_number &= OP_MASK_SHAMT;
8894 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_SHAMT;
8895 imm_expr.X_op = O_absent;
8899 case '>': /* shift amount minus 32 */
8900 my_getExpression (&imm_expr, s);
8901 check_absolute_expr (ip, &imm_expr);
8902 if ((unsigned long) imm_expr.X_add_number < 32
8903 || (unsigned long) imm_expr.X_add_number > 63)
8905 ip->insn_opcode |= (imm_expr.X_add_number - 32) << OP_SH_SHAMT;
8906 imm_expr.X_op = O_absent;
8910 case 'k': /* cache code */
8911 case 'h': /* prefx code */
8912 my_getExpression (&imm_expr, s);
8913 check_absolute_expr (ip, &imm_expr);
8914 if ((unsigned long) imm_expr.X_add_number > 31)
8916 as_warn (_("Invalid value for `%s' (%lu)"),
8918 (unsigned long) imm_expr.X_add_number);
8919 imm_expr.X_add_number &= 0x1f;
8922 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_CACHE;
8924 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_PREFX;
8925 imm_expr.X_op = O_absent;
8929 case 'c': /* break code */
8930 my_getExpression (&imm_expr, s);
8931 check_absolute_expr (ip, &imm_expr);
8932 if ((unsigned long) imm_expr.X_add_number > 1023)
8934 as_warn (_("Illegal break code (%lu)"),
8935 (unsigned long) imm_expr.X_add_number);
8936 imm_expr.X_add_number &= OP_MASK_CODE;
8938 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_CODE;
8939 imm_expr.X_op = O_absent;
8943 case 'q': /* lower break code */
8944 my_getExpression (&imm_expr, s);
8945 check_absolute_expr (ip, &imm_expr);
8946 if ((unsigned long) imm_expr.X_add_number > 1023)
8948 as_warn (_("Illegal lower break code (%lu)"),
8949 (unsigned long) imm_expr.X_add_number);
8950 imm_expr.X_add_number &= OP_MASK_CODE2;
8952 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_CODE2;
8953 imm_expr.X_op = O_absent;
8957 case 'B': /* 20-bit syscall/break code. */
8958 my_getExpression (&imm_expr, s);
8959 check_absolute_expr (ip, &imm_expr);
8960 if ((unsigned long) imm_expr.X_add_number > OP_MASK_CODE20)
8961 as_warn (_("Illegal 20-bit code (%lu)"),
8962 (unsigned long) imm_expr.X_add_number);
8963 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_CODE20;
8964 imm_expr.X_op = O_absent;
8968 case 'C': /* Coprocessor code */
8969 my_getExpression (&imm_expr, s);
8970 check_absolute_expr (ip, &imm_expr);
8971 if ((unsigned long) imm_expr.X_add_number >= (1 << 25))
8973 as_warn (_("Coproccesor code > 25 bits (%lu)"),
8974 (unsigned long) imm_expr.X_add_number);
8975 imm_expr.X_add_number &= ((1 << 25) - 1);
8977 ip->insn_opcode |= imm_expr.X_add_number;
8978 imm_expr.X_op = O_absent;
8982 case 'J': /* 19-bit wait code. */
8983 my_getExpression (&imm_expr, s);
8984 check_absolute_expr (ip, &imm_expr);
8985 if ((unsigned long) imm_expr.X_add_number > OP_MASK_CODE19)
8986 as_warn (_("Illegal 19-bit code (%lu)"),
8987 (unsigned long) imm_expr.X_add_number);
8988 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_CODE19;
8989 imm_expr.X_op = O_absent;
8993 case 'P': /* Performance register */
8994 my_getExpression (&imm_expr, s);
8995 check_absolute_expr (ip, &imm_expr);
8996 if (imm_expr.X_add_number != 0 && imm_expr.X_add_number != 1)
8998 as_warn (_("Invalid performance register (%lu)"),
8999 (unsigned long) imm_expr.X_add_number);
9000 imm_expr.X_add_number &= OP_MASK_PERFREG;
9002 ip->insn_opcode |= (imm_expr.X_add_number << OP_SH_PERFREG);
9003 imm_expr.X_op = O_absent;
9007 case 'b': /* base register */
9008 case 'd': /* destination register */
9009 case 's': /* source register */
9010 case 't': /* target register */
9011 case 'r': /* both target and source */
9012 case 'v': /* both dest and source */
9013 case 'w': /* both dest and target */
9014 case 'E': /* coprocessor target register */
9015 case 'G': /* coprocessor destination register */
9016 case 'K': /* 'rdhwr' destination register */
9017 case 'x': /* ignore register name */
9018 case 'z': /* must be zero register */
9019 case 'U': /* destination register (clo/clz). */
9034 while (ISDIGIT (*s));
9036 as_bad (_("Invalid register number (%d)"), regno);
9038 else if (*args == 'E' || *args == 'G' || *args == 'K')
9042 if (s[1] == 'r' && s[2] == 'a')
9047 else if (s[1] == 'f' && s[2] == 'p')
9052 else if (s[1] == 's' && s[2] == 'p')
9057 else if (s[1] == 'g' && s[2] == 'p')
9062 else if (s[1] == 'a' && s[2] == 't')
9067 else if (s[1] == 'k' && s[2] == 't' && s[3] == '0')
9072 else if (s[1] == 'k' && s[2] == 't' && s[3] == '1')
9077 else if (s[1] == 'z' && s[2] == 'e' && s[3] == 'r' && s[4] == 'o')
9082 else if (itbl_have_entries)
9087 p = s + 1; /* advance past '$' */
9088 n = itbl_get_field (&p); /* n is name */
9090 /* See if this is a register defined in an
9092 if (itbl_get_reg_val (n, &r))
9094 /* Get_field advances to the start of
9095 the next field, so we need to back
9096 rack to the end of the last field. */
9100 s = strchr (s, '\0');
9114 as_warn (_("Used $at without \".set noat\""));
9120 if (c == 'r' || c == 'v' || c == 'w')
9127 /* 'z' only matches $0. */
9128 if (c == 'z' && regno != 0)
9131 /* Now that we have assembled one operand, we use the args string
9132 * to figure out where it goes in the instruction. */
9139 ip->insn_opcode |= regno << OP_SH_RS;
9144 ip->insn_opcode |= regno << OP_SH_RD;
9147 ip->insn_opcode |= regno << OP_SH_RD;
9148 ip->insn_opcode |= regno << OP_SH_RT;
9153 ip->insn_opcode |= regno << OP_SH_RT;
9156 /* This case exists because on the r3000 trunc
9157 expands into a macro which requires a gp
9158 register. On the r6000 or r4000 it is
9159 assembled into a single instruction which
9160 ignores the register. Thus the insn version
9161 is MIPS_ISA2 and uses 'x', and the macro
9162 version is MIPS_ISA1 and uses 't'. */
9165 /* This case is for the div instruction, which
9166 acts differently if the destination argument
9167 is $0. This only matches $0, and is checked
9168 outside the switch. */
9171 /* Itbl operand; not yet implemented. FIXME ?? */
9173 /* What about all other operands like 'i', which
9174 can be specified in the opcode table? */
9184 ip->insn_opcode |= lastregno << OP_SH_RS;
9187 ip->insn_opcode |= lastregno << OP_SH_RT;
9192 case 'O': /* MDMX alignment immediate constant. */
9193 my_getExpression (&imm_expr, s);
9194 check_absolute_expr (ip, &imm_expr);
9195 if ((unsigned long) imm_expr.X_add_number > OP_MASK_ALN)
9197 as_warn ("Improper align amount (%ld), using low bits",
9198 (long) imm_expr.X_add_number);
9199 imm_expr.X_add_number &= OP_MASK_ALN;
9201 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_ALN;
9202 imm_expr.X_op = O_absent;
9206 case 'Q': /* MDMX vector, element sel, or const. */
9209 /* MDMX Immediate. */
9210 my_getExpression (&imm_expr, s);
9211 check_absolute_expr (ip, &imm_expr);
9212 if ((unsigned long) imm_expr.X_add_number > OP_MASK_FT)
9214 as_warn (_("Invalid MDMX Immediate (%ld)"),
9215 (long) imm_expr.X_add_number);
9216 imm_expr.X_add_number &= OP_MASK_FT;
9218 imm_expr.X_add_number &= OP_MASK_FT;
9219 if (ip->insn_opcode & (OP_MASK_VSEL << OP_SH_VSEL))
9220 ip->insn_opcode |= MDMX_FMTSEL_IMM_QH << OP_SH_VSEL;
9222 ip->insn_opcode |= MDMX_FMTSEL_IMM_OB << OP_SH_VSEL;
9223 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_FT;
9224 imm_expr.X_op = O_absent;
9228 /* Not MDMX Immediate. Fall through. */
9229 case 'X': /* MDMX destination register. */
9230 case 'Y': /* MDMX source register. */
9231 case 'Z': /* MDMX target register. */
9233 case 'D': /* floating point destination register */
9234 case 'S': /* floating point source register */
9235 case 'T': /* floating point target register */
9236 case 'R': /* floating point source register */
9240 /* Accept $fN for FP and MDMX register numbers, and in
9241 addition accept $vN for MDMX register numbers. */
9242 if ((s[0] == '$' && s[1] == 'f' && ISDIGIT (s[2]))
9243 || (is_mdmx != 0 && s[0] == '$' && s[1] == 'v'
9254 while (ISDIGIT (*s));
9257 as_bad (_("Invalid float register number (%d)"), regno);
9259 if ((regno & 1) != 0
9261 && ! (strcmp (str, "mtc1") == 0
9262 || strcmp (str, "mfc1") == 0
9263 || strcmp (str, "lwc1") == 0
9264 || strcmp (str, "swc1") == 0
9265 || strcmp (str, "l.s") == 0
9266 || strcmp (str, "s.s") == 0))
9267 as_warn (_("Float register should be even, was %d"),
9275 if (c == 'V' || c == 'W')
9286 ip->insn_opcode |= regno << OP_SH_FD;
9291 ip->insn_opcode |= regno << OP_SH_FS;
9294 /* This is like 'Z', but also needs to fix the MDMX
9295 vector/scalar select bits. Note that the
9296 scalar immediate case is handled above. */
9299 int is_qh = (ip->insn_opcode & (1 << OP_SH_VSEL));
9300 int max_el = (is_qh ? 3 : 7);
9302 my_getExpression(&imm_expr, s);
9303 check_absolute_expr (ip, &imm_expr);
9305 if (imm_expr.X_add_number > max_el)
9306 as_bad(_("Bad element selector %ld"),
9307 (long) imm_expr.X_add_number);
9308 imm_expr.X_add_number &= max_el;
9309 ip->insn_opcode |= (imm_expr.X_add_number
9313 as_warn(_("Expecting ']' found '%s'"), s);
9319 if (ip->insn_opcode & (OP_MASK_VSEL << OP_SH_VSEL))
9320 ip->insn_opcode |= (MDMX_FMTSEL_VEC_QH
9323 ip->insn_opcode |= (MDMX_FMTSEL_VEC_OB <<
9330 ip->insn_opcode |= regno << OP_SH_FT;
9333 ip->insn_opcode |= regno << OP_SH_FR;
9343 ip->insn_opcode |= lastregno << OP_SH_FS;
9346 ip->insn_opcode |= lastregno << OP_SH_FT;
9352 my_getExpression (&imm_expr, s);
9353 if (imm_expr.X_op != O_big
9354 && imm_expr.X_op != O_constant)
9355 insn_error = _("absolute expression required");
9360 my_getExpression (&offset_expr, s);
9361 *imm_reloc = BFD_RELOC_32;
9374 unsigned char temp[8];
9376 unsigned int length;
9381 /* These only appear as the last operand in an
9382 instruction, and every instruction that accepts
9383 them in any variant accepts them in all variants.
9384 This means we don't have to worry about backing out
9385 any changes if the instruction does not match.
9387 The difference between them is the size of the
9388 floating point constant and where it goes. For 'F'
9389 and 'L' the constant is 64 bits; for 'f' and 'l' it
9390 is 32 bits. Where the constant is placed is based
9391 on how the MIPS assembler does things:
9394 f -- immediate value
9397 The .lit4 and .lit8 sections are only used if
9398 permitted by the -G argument.
9400 When generating embedded PIC code, we use the
9401 .lit8 section but not the .lit4 section (we can do
9402 .lit4 inline easily; we need to put .lit8
9403 somewhere in the data segment, and using .lit8
9404 permits the linker to eventually combine identical
9407 The code below needs to know whether the target register
9408 is 32 or 64 bits wide. It relies on the fact 'f' and
9409 'F' are used with GPR-based instructions and 'l' and
9410 'L' are used with FPR-based instructions. */
9412 f64 = *args == 'F' || *args == 'L';
9413 using_gprs = *args == 'F' || *args == 'f';
9415 save_in = input_line_pointer;
9416 input_line_pointer = s;
9417 err = md_atof (f64 ? 'd' : 'f', (char *) temp, &len);
9419 s = input_line_pointer;
9420 input_line_pointer = save_in;
9421 if (err != NULL && *err != '\0')
9423 as_bad (_("Bad floating point constant: %s"), err);
9424 memset (temp, '\0', sizeof temp);
9425 length = f64 ? 8 : 4;
9428 assert (length == (unsigned) (f64 ? 8 : 4));
9432 && (! USE_GLOBAL_POINTER_OPT
9433 || mips_pic == EMBEDDED_PIC
9434 || g_switch_value < 4
9435 || (temp[0] == 0 && temp[1] == 0)
9436 || (temp[2] == 0 && temp[3] == 0))))
9438 imm_expr.X_op = O_constant;
9439 if (! target_big_endian)
9440 imm_expr.X_add_number = bfd_getl32 (temp);
9442 imm_expr.X_add_number = bfd_getb32 (temp);
9445 && ! mips_disable_float_construction
9446 /* Constants can only be constructed in GPRs and
9447 copied to FPRs if the GPRs are at least as wide
9448 as the FPRs. Force the constant into memory if
9449 we are using 64-bit FPRs but the GPRs are only
9452 || ! (HAVE_64BIT_FPRS && HAVE_32BIT_GPRS))
9453 && ((temp[0] == 0 && temp[1] == 0)
9454 || (temp[2] == 0 && temp[3] == 0))
9455 && ((temp[4] == 0 && temp[5] == 0)
9456 || (temp[6] == 0 && temp[7] == 0)))
9458 /* The value is simple enough to load with a couple of
9459 instructions. If using 32-bit registers, set
9460 imm_expr to the high order 32 bits and offset_expr to
9461 the low order 32 bits. Otherwise, set imm_expr to
9462 the entire 64 bit constant. */
9463 if (using_gprs ? HAVE_32BIT_GPRS : HAVE_32BIT_FPRS)
9465 imm_expr.X_op = O_constant;
9466 offset_expr.X_op = O_constant;
9467 if (! target_big_endian)
9469 imm_expr.X_add_number = bfd_getl32 (temp + 4);
9470 offset_expr.X_add_number = bfd_getl32 (temp);
9474 imm_expr.X_add_number = bfd_getb32 (temp);
9475 offset_expr.X_add_number = bfd_getb32 (temp + 4);
9477 if (offset_expr.X_add_number == 0)
9478 offset_expr.X_op = O_absent;
9480 else if (sizeof (imm_expr.X_add_number) > 4)
9482 imm_expr.X_op = O_constant;
9483 if (! target_big_endian)
9484 imm_expr.X_add_number = bfd_getl64 (temp);
9486 imm_expr.X_add_number = bfd_getb64 (temp);
9490 imm_expr.X_op = O_big;
9491 imm_expr.X_add_number = 4;
9492 if (! target_big_endian)
9494 generic_bignum[0] = bfd_getl16 (temp);
9495 generic_bignum[1] = bfd_getl16 (temp + 2);
9496 generic_bignum[2] = bfd_getl16 (temp + 4);
9497 generic_bignum[3] = bfd_getl16 (temp + 6);
9501 generic_bignum[0] = bfd_getb16 (temp + 6);
9502 generic_bignum[1] = bfd_getb16 (temp + 4);
9503 generic_bignum[2] = bfd_getb16 (temp + 2);
9504 generic_bignum[3] = bfd_getb16 (temp);
9510 const char *newname;
9513 /* Switch to the right section. */
9515 subseg = now_subseg;
9518 default: /* unused default case avoids warnings. */
9520 newname = RDATA_SECTION_NAME;
9521 if ((USE_GLOBAL_POINTER_OPT && g_switch_value >= 8)
9522 || mips_pic == EMBEDDED_PIC)
9526 if (mips_pic == EMBEDDED_PIC)
9529 newname = RDATA_SECTION_NAME;
9532 assert (!USE_GLOBAL_POINTER_OPT
9533 || g_switch_value >= 4);
9537 new_seg = subseg_new (newname, (subsegT) 0);
9538 if (OUTPUT_FLAVOR == bfd_target_elf_flavour)
9539 bfd_set_section_flags (stdoutput, new_seg,
9544 frag_align (*args == 'l' ? 2 : 3, 0, 0);
9545 if (OUTPUT_FLAVOR == bfd_target_elf_flavour
9546 && strcmp (TARGET_OS, "elf") != 0)
9547 record_alignment (new_seg, 4);
9549 record_alignment (new_seg, *args == 'l' ? 2 : 3);
9551 as_bad (_("Can't use floating point insn in this section"));
9553 /* Set the argument to the current address in the
9555 offset_expr.X_op = O_symbol;
9556 offset_expr.X_add_symbol =
9557 symbol_new ("L0\001", now_seg,
9558 (valueT) frag_now_fix (), frag_now);
9559 offset_expr.X_add_number = 0;
9561 /* Put the floating point number into the section. */
9562 p = frag_more ((int) length);
9563 memcpy (p, temp, length);
9565 /* Switch back to the original section. */
9566 subseg_set (seg, subseg);
9571 case 'i': /* 16 bit unsigned immediate */
9572 case 'j': /* 16 bit signed immediate */
9573 *imm_reloc = BFD_RELOC_LO16;
9574 if (my_getSmallExpression (&imm_expr, imm_reloc, s) == 0)
9577 offsetT minval, maxval;
9579 more = (insn + 1 < &mips_opcodes[NUMOPCODES]
9580 && strcmp (insn->name, insn[1].name) == 0);
9582 /* If the expression was written as an unsigned number,
9583 only treat it as signed if there are no more
9587 && sizeof (imm_expr.X_add_number) <= 4
9588 && imm_expr.X_op == O_constant
9589 && imm_expr.X_add_number < 0
9590 && imm_expr.X_unsigned
9594 /* For compatibility with older assemblers, we accept
9595 0x8000-0xffff as signed 16-bit numbers when only
9596 signed numbers are allowed. */
9598 minval = 0, maxval = 0xffff;
9600 minval = -0x8000, maxval = 0x7fff;
9602 minval = -0x8000, maxval = 0xffff;
9604 if (imm_expr.X_op != O_constant
9605 || imm_expr.X_add_number < minval
9606 || imm_expr.X_add_number > maxval)
9610 if (imm_expr.X_op == O_constant
9611 || imm_expr.X_op == O_big)
9612 as_bad (_("expression out of range"));
9618 case 'o': /* 16 bit offset */
9619 /* Check whether there is only a single bracketed expression
9620 left. If so, it must be the base register and the
9621 constant must be zero. */
9622 if (*s == '(' && strchr (s + 1, '(') == 0)
9624 offset_expr.X_op = O_constant;
9625 offset_expr.X_add_number = 0;
9629 /* If this value won't fit into a 16 bit offset, then go
9630 find a macro that will generate the 32 bit offset
9632 if (my_getSmallExpression (&offset_expr, offset_reloc, s) == 0
9633 && (offset_expr.X_op != O_constant
9634 || offset_expr.X_add_number >= 0x8000
9635 || offset_expr.X_add_number < -0x8000))
9641 case 'p': /* pc relative offset */
9642 *offset_reloc = BFD_RELOC_16_PCREL_S2;
9643 my_getExpression (&offset_expr, s);
9647 case 'u': /* upper 16 bits */
9648 if (my_getSmallExpression (&imm_expr, imm_reloc, s) == 0
9649 && imm_expr.X_op == O_constant
9650 && (imm_expr.X_add_number < 0
9651 || imm_expr.X_add_number >= 0x10000))
9652 as_bad (_("lui expression not in range 0..65535"));
9656 case 'a': /* 26 bit address */
9657 my_getExpression (&offset_expr, s);
9659 *offset_reloc = BFD_RELOC_MIPS_JMP;
9662 case 'N': /* 3 bit branch condition code */
9663 case 'M': /* 3 bit compare condition code */
9664 if (strncmp (s, "$fcc", 4) != 0)
9674 while (ISDIGIT (*s));
9676 as_bad (_("invalid condition code register $fcc%d"), regno);
9678 ip->insn_opcode |= regno << OP_SH_BCC;
9680 ip->insn_opcode |= regno << OP_SH_CCC;
9684 if (s[0] == '0' && (s[1] == 'x' || s[1] == 'X'))
9695 while (ISDIGIT (*s));
9698 c = 8; /* Invalid sel value. */
9701 as_bad (_("invalid coprocessor sub-selection value (0-7)"));
9702 ip->insn_opcode |= c;
9706 /* Must be at least one digit. */
9707 my_getExpression (&imm_expr, s);
9708 check_absolute_expr (ip, &imm_expr);
9710 if ((unsigned long) imm_expr.X_add_number
9711 > (unsigned long) OP_MASK_VECBYTE)
9713 as_bad (_("bad byte vector index (%ld)"),
9714 (long) imm_expr.X_add_number);
9715 imm_expr.X_add_number = 0;
9718 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_VECBYTE;
9719 imm_expr.X_op = O_absent;
9724 my_getExpression (&imm_expr, s);
9725 check_absolute_expr (ip, &imm_expr);
9727 if ((unsigned long) imm_expr.X_add_number
9728 > (unsigned long) OP_MASK_VECALIGN)
9730 as_bad (_("bad byte vector index (%ld)"),
9731 (long) imm_expr.X_add_number);
9732 imm_expr.X_add_number = 0;
9735 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_VECALIGN;
9736 imm_expr.X_op = O_absent;
9741 as_bad (_("bad char = '%c'\n"), *args);
9746 /* Args don't match. */
9747 if (insn + 1 < &mips_opcodes[NUMOPCODES] &&
9748 !strcmp (insn->name, insn[1].name))
9752 insn_error = _("illegal operands");
9757 insn_error = _("illegal operands");
9762 /* This routine assembles an instruction into its binary format when
9763 assembling for the mips16. As a side effect, it sets one of the
9764 global variables imm_reloc or offset_reloc to the type of
9765 relocation to do if one of the operands is an address expression.
9766 It also sets mips16_small and mips16_ext if the user explicitly
9767 requested a small or extended instruction. */
9772 struct mips_cl_insn *ip;
9776 struct mips_opcode *insn;
9779 unsigned int lastregno = 0;
9784 mips16_small = FALSE;
9787 for (s = str; ISLOWER (*s); ++s)
9799 if (s[1] == 't' && s[2] == ' ')
9802 mips16_small = TRUE;
9806 else if (s[1] == 'e' && s[2] == ' ')
9815 insn_error = _("unknown opcode");
9819 if (mips_opts.noautoextend && ! mips16_ext)
9820 mips16_small = TRUE;
9822 if ((insn = (struct mips_opcode *) hash_find (mips16_op_hash, str)) == NULL)
9824 insn_error = _("unrecognized opcode");
9831 assert (strcmp (insn->name, str) == 0);
9834 ip->insn_opcode = insn->match;
9835 ip->use_extend = FALSE;
9836 imm_expr.X_op = O_absent;
9837 imm_reloc[0] = BFD_RELOC_UNUSED;
9838 imm_reloc[1] = BFD_RELOC_UNUSED;
9839 imm_reloc[2] = BFD_RELOC_UNUSED;
9840 offset_expr.X_op = O_absent;
9841 offset_reloc[0] = BFD_RELOC_UNUSED;
9842 offset_reloc[1] = BFD_RELOC_UNUSED;
9843 offset_reloc[2] = BFD_RELOC_UNUSED;
9844 for (args = insn->args; 1; ++args)
9851 /* In this switch statement we call break if we did not find
9852 a match, continue if we did find a match, or return if we
9861 /* Stuff the immediate value in now, if we can. */
9862 if (imm_expr.X_op == O_constant
9863 && *imm_reloc > BFD_RELOC_UNUSED
9864 && insn->pinfo != INSN_MACRO)
9866 mips16_immed (NULL, 0, *imm_reloc - BFD_RELOC_UNUSED,
9867 imm_expr.X_add_number, TRUE, mips16_small,
9868 mips16_ext, &ip->insn_opcode,
9869 &ip->use_extend, &ip->extend);
9870 imm_expr.X_op = O_absent;
9871 *imm_reloc = BFD_RELOC_UNUSED;
9885 ip->insn_opcode |= lastregno << MIPS16OP_SH_RX;
9888 ip->insn_opcode |= lastregno << MIPS16OP_SH_RY;
9904 ip->insn_opcode |= lastregno << MIPS16OP_SH_RX;
9906 ip->insn_opcode |= lastregno << MIPS16OP_SH_RY;
9933 while (ISDIGIT (*s));
9936 as_bad (_("invalid register number (%d)"), regno);
9942 if (s[1] == 'r' && s[2] == 'a')
9947 else if (s[1] == 'f' && s[2] == 'p')
9952 else if (s[1] == 's' && s[2] == 'p')
9957 else if (s[1] == 'g' && s[2] == 'p')
9962 else if (s[1] == 'a' && s[2] == 't')
9967 else if (s[1] == 'k' && s[2] == 't' && s[3] == '0')
9972 else if (s[1] == 'k' && s[2] == 't' && s[3] == '1')
9977 else if (s[1] == 'z' && s[2] == 'e' && s[3] == 'r' && s[4] == 'o')
9990 if (c == 'v' || c == 'w')
9992 regno = mips16_to_32_reg_map[lastregno];
10006 regno = mips32_to_16_reg_map[regno];
10011 regno = ILLEGAL_REG;
10016 regno = ILLEGAL_REG;
10021 regno = ILLEGAL_REG;
10026 if (regno == AT && ! mips_opts.noat)
10027 as_warn (_("used $at without \".set noat\""));
10034 if (regno == ILLEGAL_REG)
10041 ip->insn_opcode |= regno << MIPS16OP_SH_RX;
10045 ip->insn_opcode |= regno << MIPS16OP_SH_RY;
10048 ip->insn_opcode |= regno << MIPS16OP_SH_RZ;
10051 ip->insn_opcode |= regno << MIPS16OP_SH_MOVE32Z;
10057 ip->insn_opcode |= regno << MIPS16OP_SH_REGR32;
10060 regno = ((regno & 7) << 2) | ((regno & 0x18) >> 3);
10061 ip->insn_opcode |= regno << MIPS16OP_SH_REG32R;
10071 if (strncmp (s, "$pc", 3) == 0)
10095 && strncmp (s + 1, "gprel(", sizeof "gprel(" - 1) == 0)
10097 /* This is %gprel(SYMBOL). We need to read SYMBOL,
10098 and generate the appropriate reloc. If the text
10099 inside %gprel is not a symbol name with an
10100 optional offset, then we generate a normal reloc
10101 and will probably fail later. */
10102 my_getExpression (&imm_expr, s + sizeof "%gprel" - 1);
10103 if (imm_expr.X_op == O_symbol)
10106 *imm_reloc = BFD_RELOC_MIPS16_GPREL;
10108 ip->use_extend = TRUE;
10115 /* Just pick up a normal expression. */
10116 my_getExpression (&imm_expr, s);
10119 if (imm_expr.X_op == O_register)
10121 /* What we thought was an expression turned out to
10124 if (s[0] == '(' && args[1] == '(')
10126 /* It looks like the expression was omitted
10127 before a register indirection, which means
10128 that the expression is implicitly zero. We
10129 still set up imm_expr, so that we handle
10130 explicit extensions correctly. */
10131 imm_expr.X_op = O_constant;
10132 imm_expr.X_add_number = 0;
10133 *imm_reloc = (int) BFD_RELOC_UNUSED + c;
10140 /* We need to relax this instruction. */
10141 *imm_reloc = (int) BFD_RELOC_UNUSED + c;
10150 /* We use offset_reloc rather than imm_reloc for the PC
10151 relative operands. This lets macros with both
10152 immediate and address operands work correctly. */
10153 my_getExpression (&offset_expr, s);
10155 if (offset_expr.X_op == O_register)
10158 /* We need to relax this instruction. */
10159 *offset_reloc = (int) BFD_RELOC_UNUSED + c;
10163 case '6': /* break code */
10164 my_getExpression (&imm_expr, s);
10165 check_absolute_expr (ip, &imm_expr);
10166 if ((unsigned long) imm_expr.X_add_number > 63)
10168 as_warn (_("Invalid value for `%s' (%lu)"),
10170 (unsigned long) imm_expr.X_add_number);
10171 imm_expr.X_add_number &= 0x3f;
10173 ip->insn_opcode |= imm_expr.X_add_number << MIPS16OP_SH_IMM6;
10174 imm_expr.X_op = O_absent;
10178 case 'a': /* 26 bit address */
10179 my_getExpression (&offset_expr, s);
10181 *offset_reloc = BFD_RELOC_MIPS16_JMP;
10182 ip->insn_opcode <<= 16;
10185 case 'l': /* register list for entry macro */
10186 case 'L': /* register list for exit macro */
10196 int freg, reg1, reg2;
10198 while (*s == ' ' || *s == ',')
10202 as_bad (_("can't parse register list"));
10214 while (ISDIGIT (*s))
10236 as_bad (_("invalid register list"));
10241 while (ISDIGIT (*s))
10248 if (freg && reg1 == 0 && reg2 == 0 && c == 'L')
10250 mask &= ~ (7 << 3);
10253 else if (freg && reg1 == 0 && reg2 == 1 && c == 'L')
10255 mask &= ~ (7 << 3);
10258 else if (reg1 == 4 && reg2 >= 4 && reg2 <= 7 && c != 'L')
10259 mask |= (reg2 - 3) << 3;
10260 else if (reg1 == 16 && reg2 >= 16 && reg2 <= 17)
10261 mask |= (reg2 - 15) << 1;
10262 else if (reg1 == RA && reg2 == RA)
10266 as_bad (_("invalid register list"));
10270 /* The mask is filled in in the opcode table for the
10271 benefit of the disassembler. We remove it before
10272 applying the actual mask. */
10273 ip->insn_opcode &= ~ ((7 << 3) << MIPS16OP_SH_IMM6);
10274 ip->insn_opcode |= mask << MIPS16OP_SH_IMM6;
10278 case 'e': /* extend code */
10279 my_getExpression (&imm_expr, s);
10280 check_absolute_expr (ip, &imm_expr);
10281 if ((unsigned long) imm_expr.X_add_number > 0x7ff)
10283 as_warn (_("Invalid value for `%s' (%lu)"),
10285 (unsigned long) imm_expr.X_add_number);
10286 imm_expr.X_add_number &= 0x7ff;
10288 ip->insn_opcode |= imm_expr.X_add_number;
10289 imm_expr.X_op = O_absent;
10299 /* Args don't match. */
10300 if (insn + 1 < &mips16_opcodes[bfd_mips16_num_opcodes] &&
10301 strcmp (insn->name, insn[1].name) == 0)
10308 insn_error = _("illegal operands");
10314 /* This structure holds information we know about a mips16 immediate
10317 struct mips16_immed_operand
10319 /* The type code used in the argument string in the opcode table. */
10321 /* The number of bits in the short form of the opcode. */
10323 /* The number of bits in the extended form of the opcode. */
10325 /* The amount by which the short form is shifted when it is used;
10326 for example, the sw instruction has a shift count of 2. */
10328 /* The amount by which the short form is shifted when it is stored
10329 into the instruction code. */
10331 /* Non-zero if the short form is unsigned. */
10333 /* Non-zero if the extended form is unsigned. */
10335 /* Non-zero if the value is PC relative. */
10339 /* The mips16 immediate operand types. */
10341 static const struct mips16_immed_operand mips16_immed_operands[] =
10343 { '<', 3, 5, 0, MIPS16OP_SH_RZ, 1, 1, 0 },
10344 { '>', 3, 5, 0, MIPS16OP_SH_RX, 1, 1, 0 },
10345 { '[', 3, 6, 0, MIPS16OP_SH_RZ, 1, 1, 0 },
10346 { ']', 3, 6, 0, MIPS16OP_SH_RX, 1, 1, 0 },
10347 { '4', 4, 15, 0, MIPS16OP_SH_IMM4, 0, 0, 0 },
10348 { '5', 5, 16, 0, MIPS16OP_SH_IMM5, 1, 0, 0 },
10349 { 'H', 5, 16, 1, MIPS16OP_SH_IMM5, 1, 0, 0 },
10350 { 'W', 5, 16, 2, MIPS16OP_SH_IMM5, 1, 0, 0 },
10351 { 'D', 5, 16, 3, MIPS16OP_SH_IMM5, 1, 0, 0 },
10352 { 'j', 5, 16, 0, MIPS16OP_SH_IMM5, 0, 0, 0 },
10353 { '8', 8, 16, 0, MIPS16OP_SH_IMM8, 1, 0, 0 },
10354 { 'V', 8, 16, 2, MIPS16OP_SH_IMM8, 1, 0, 0 },
10355 { 'C', 8, 16, 3, MIPS16OP_SH_IMM8, 1, 0, 0 },
10356 { 'U', 8, 16, 0, MIPS16OP_SH_IMM8, 1, 1, 0 },
10357 { 'k', 8, 16, 0, MIPS16OP_SH_IMM8, 0, 0, 0 },
10358 { 'K', 8, 16, 3, MIPS16OP_SH_IMM8, 0, 0, 0 },
10359 { 'p', 8, 16, 0, MIPS16OP_SH_IMM8, 0, 0, 1 },
10360 { 'q', 11, 16, 0, MIPS16OP_SH_IMM8, 0, 0, 1 },
10361 { 'A', 8, 16, 2, MIPS16OP_SH_IMM8, 1, 0, 1 },
10362 { 'B', 5, 16, 3, MIPS16OP_SH_IMM5, 1, 0, 1 },
10363 { 'E', 5, 16, 2, MIPS16OP_SH_IMM5, 1, 0, 1 }
10366 #define MIPS16_NUM_IMMED \
10367 (sizeof mips16_immed_operands / sizeof mips16_immed_operands[0])
10369 /* Handle a mips16 instruction with an immediate value. This or's the
10370 small immediate value into *INSN. It sets *USE_EXTEND to indicate
10371 whether an extended value is needed; if one is needed, it sets
10372 *EXTEND to the value. The argument type is TYPE. The value is VAL.
10373 If SMALL is true, an unextended opcode was explicitly requested.
10374 If EXT is true, an extended opcode was explicitly requested. If
10375 WARN is true, warn if EXT does not match reality. */
10378 mips16_immed (file, line, type, val, warn, small, ext, insn, use_extend,
10387 unsigned long *insn;
10388 bfd_boolean *use_extend;
10389 unsigned short *extend;
10391 register const struct mips16_immed_operand *op;
10392 int mintiny, maxtiny;
10393 bfd_boolean needext;
10395 op = mips16_immed_operands;
10396 while (op->type != type)
10399 assert (op < mips16_immed_operands + MIPS16_NUM_IMMED);
10404 if (type == '<' || type == '>' || type == '[' || type == ']')
10407 maxtiny = 1 << op->nbits;
10412 maxtiny = (1 << op->nbits) - 1;
10417 mintiny = - (1 << (op->nbits - 1));
10418 maxtiny = (1 << (op->nbits - 1)) - 1;
10421 /* Branch offsets have an implicit 0 in the lowest bit. */
10422 if (type == 'p' || type == 'q')
10425 if ((val & ((1 << op->shift) - 1)) != 0
10426 || val < (mintiny << op->shift)
10427 || val > (maxtiny << op->shift))
10432 if (warn && ext && ! needext)
10433 as_warn_where (file, line,
10434 _("extended operand requested but not required"));
10435 if (small && needext)
10436 as_bad_where (file, line, _("invalid unextended operand value"));
10438 if (small || (! ext && ! needext))
10442 *use_extend = FALSE;
10443 insnval = ((val >> op->shift) & ((1 << op->nbits) - 1));
10444 insnval <<= op->op_shift;
10449 long minext, maxext;
10455 maxext = (1 << op->extbits) - 1;
10459 minext = - (1 << (op->extbits - 1));
10460 maxext = (1 << (op->extbits - 1)) - 1;
10462 if (val < minext || val > maxext)
10463 as_bad_where (file, line,
10464 _("operand value out of range for instruction"));
10466 *use_extend = TRUE;
10467 if (op->extbits == 16)
10469 extval = ((val >> 11) & 0x1f) | (val & 0x7e0);
10472 else if (op->extbits == 15)
10474 extval = ((val >> 11) & 0xf) | (val & 0x7f0);
10479 extval = ((val & 0x1f) << 6) | (val & 0x20);
10483 *extend = (unsigned short) extval;
10488 static const struct percent_op_match
10491 bfd_reloc_code_real_type reloc;
10494 {"%lo", BFD_RELOC_LO16},
10496 {"%call_hi", BFD_RELOC_MIPS_CALL_HI16},
10497 {"%call_lo", BFD_RELOC_MIPS_CALL_LO16},
10498 {"%call16", BFD_RELOC_MIPS_CALL16},
10499 {"%got_disp", BFD_RELOC_MIPS_GOT_DISP},
10500 {"%got_page", BFD_RELOC_MIPS_GOT_PAGE},
10501 {"%got_ofst", BFD_RELOC_MIPS_GOT_OFST},
10502 {"%got_hi", BFD_RELOC_MIPS_GOT_HI16},
10503 {"%got_lo", BFD_RELOC_MIPS_GOT_LO16},
10504 {"%got", BFD_RELOC_MIPS_GOT16},
10505 {"%gp_rel", BFD_RELOC_GPREL16},
10506 {"%half", BFD_RELOC_16},
10507 {"%highest", BFD_RELOC_MIPS_HIGHEST},
10508 {"%higher", BFD_RELOC_MIPS_HIGHER},
10509 {"%neg", BFD_RELOC_MIPS_SUB},
10511 {"%hi", BFD_RELOC_HI16_S}
10515 /* Return true if *STR points to a relocation operator. When returning true,
10516 move *STR over the operator and store its relocation code in *RELOC.
10517 Leave both *STR and *RELOC alone when returning false. */
10520 parse_relocation (str, reloc)
10522 bfd_reloc_code_real_type *reloc;
10526 for (i = 0; i < ARRAY_SIZE (percent_op); i++)
10527 if (strncasecmp (*str, percent_op[i].str, strlen (percent_op[i].str)) == 0)
10529 *str += strlen (percent_op[i].str);
10530 *reloc = percent_op[i].reloc;
10532 /* Check whether the output BFD supports this relocation.
10533 If not, issue an error and fall back on something safe. */
10534 if (!bfd_reloc_type_lookup (stdoutput, percent_op[i].reloc))
10536 as_bad ("relocation %s isn't supported by the current ABI",
10537 percent_op[i].str);
10538 *reloc = BFD_RELOC_LO16;
10546 /* Parse string STR as a 16-bit relocatable operand. Store the
10547 expression in *EP and the relocations in the array starting
10548 at RELOC. Return the number of relocation operators used.
10550 On exit, EXPR_END points to the first character after the expression.
10551 If no relocation operators are used, RELOC[0] is set to BFD_RELOC_LO16. */
10554 my_getSmallExpression (ep, reloc, str)
10556 bfd_reloc_code_real_type *reloc;
10559 bfd_reloc_code_real_type reversed_reloc[3];
10560 size_t reloc_index, i;
10561 int crux_depth, str_depth;
10564 /* Search for the start of the main expression, recoding relocations
10565 in REVERSED_RELOC. End the loop with CRUX pointing to the start
10566 of the main expression and with CRUX_DEPTH containing the number
10567 of open brackets at that point. */
10574 crux_depth = str_depth;
10576 /* Skip over whitespace and brackets, keeping count of the number
10578 while (*str == ' ' || *str == '\t' || *str == '(')
10583 && reloc_index < (HAVE_NEWABI ? 3 : 1)
10584 && parse_relocation (&str, &reversed_reloc[reloc_index]));
10586 my_getExpression (ep, crux);
10589 /* Match every open bracket. */
10590 while (crux_depth > 0 && (*str == ')' || *str == ' ' || *str == '\t'))
10594 if (crux_depth > 0)
10595 as_bad ("unclosed '('");
10599 if (reloc_index == 0)
10600 reloc[0] = BFD_RELOC_LO16;
10603 prev_reloc_op_frag = frag_now;
10604 for (i = 0; i < reloc_index; i++)
10605 reloc[i] = reversed_reloc[reloc_index - 1 - i];
10608 return reloc_index;
10612 my_getExpression (ep, str)
10619 save_in = input_line_pointer;
10620 input_line_pointer = str;
10622 expr_end = input_line_pointer;
10623 input_line_pointer = save_in;
10625 /* If we are in mips16 mode, and this is an expression based on `.',
10626 then we bump the value of the symbol by 1 since that is how other
10627 text symbols are handled. We don't bother to handle complex
10628 expressions, just `.' plus or minus a constant. */
10629 if (mips_opts.mips16
10630 && ep->X_op == O_symbol
10631 && strcmp (S_GET_NAME (ep->X_add_symbol), FAKE_LABEL_NAME) == 0
10632 && S_GET_SEGMENT (ep->X_add_symbol) == now_seg
10633 && symbol_get_frag (ep->X_add_symbol) == frag_now
10634 && symbol_constant_p (ep->X_add_symbol)
10635 && (val = S_GET_VALUE (ep->X_add_symbol)) == frag_now_fix ())
10636 S_SET_VALUE (ep->X_add_symbol, val + 1);
10639 /* Turn a string in input_line_pointer into a floating point constant
10640 of type TYPE, and store the appropriate bytes in *LITP. The number
10641 of LITTLENUMS emitted is stored in *SIZEP. An error message is
10642 returned, or NULL on OK. */
10645 md_atof (type, litP, sizeP)
10651 LITTLENUM_TYPE words[4];
10667 return _("bad call to md_atof");
10670 t = atof_ieee (input_line_pointer, type, words);
10672 input_line_pointer = t;
10676 if (! target_big_endian)
10678 for (i = prec - 1; i >= 0; i--)
10680 md_number_to_chars (litP, (valueT) words[i], 2);
10686 for (i = 0; i < prec; i++)
10688 md_number_to_chars (litP, (valueT) words[i], 2);
10697 md_number_to_chars (buf, val, n)
10702 if (target_big_endian)
10703 number_to_chars_bigendian (buf, val, n);
10705 number_to_chars_littleendian (buf, val, n);
10709 static int support_64bit_objects(void)
10711 const char **list, **l;
10714 list = bfd_target_list ();
10715 for (l = list; *l != NULL; l++)
10717 /* This is traditional mips */
10718 if (strcmp (*l, "elf64-tradbigmips") == 0
10719 || strcmp (*l, "elf64-tradlittlemips") == 0)
10721 if (strcmp (*l, "elf64-bigmips") == 0
10722 || strcmp (*l, "elf64-littlemips") == 0)
10725 yes = (*l != NULL);
10729 #endif /* OBJ_ELF */
10731 const char *md_shortopts = "nO::g::G:";
10733 struct option md_longopts[] =
10735 /* Options which specify architecture. */
10736 #define OPTION_ARCH_BASE (OPTION_MD_BASE)
10737 #define OPTION_MARCH (OPTION_ARCH_BASE + 0)
10738 {"march", required_argument, NULL, OPTION_MARCH},
10739 #define OPTION_MTUNE (OPTION_ARCH_BASE + 1)
10740 {"mtune", required_argument, NULL, OPTION_MTUNE},
10741 #define OPTION_MIPS1 (OPTION_ARCH_BASE + 2)
10742 {"mips0", no_argument, NULL, OPTION_MIPS1},
10743 {"mips1", no_argument, NULL, OPTION_MIPS1},
10744 #define OPTION_MIPS2 (OPTION_ARCH_BASE + 3)
10745 {"mips2", no_argument, NULL, OPTION_MIPS2},
10746 #define OPTION_MIPS3 (OPTION_ARCH_BASE + 4)
10747 {"mips3", no_argument, NULL, OPTION_MIPS3},
10748 #define OPTION_MIPS4 (OPTION_ARCH_BASE + 5)
10749 {"mips4", no_argument, NULL, OPTION_MIPS4},
10750 #define OPTION_MIPS5 (OPTION_ARCH_BASE + 6)
10751 {"mips5", no_argument, NULL, OPTION_MIPS5},
10752 #define OPTION_MIPS32 (OPTION_ARCH_BASE + 7)
10753 {"mips32", no_argument, NULL, OPTION_MIPS32},
10754 #define OPTION_MIPS64 (OPTION_ARCH_BASE + 8)
10755 {"mips64", no_argument, NULL, OPTION_MIPS64},
10756 #define OPTION_MIPS32R2 (OPTION_ARCH_BASE + 9)
10757 {"mips32r2", no_argument, NULL, OPTION_MIPS32R2},
10759 /* Options which specify Application Specific Extensions (ASEs). */
10760 #define OPTION_ASE_BASE (OPTION_ARCH_BASE + 10)
10761 #define OPTION_MIPS16 (OPTION_ASE_BASE + 0)
10762 {"mips16", no_argument, NULL, OPTION_MIPS16},
10763 #define OPTION_NO_MIPS16 (OPTION_ASE_BASE + 1)
10764 {"no-mips16", no_argument, NULL, OPTION_NO_MIPS16},
10765 #define OPTION_MIPS3D (OPTION_ASE_BASE + 2)
10766 {"mips3d", no_argument, NULL, OPTION_MIPS3D},
10767 #define OPTION_NO_MIPS3D (OPTION_ASE_BASE + 3)
10768 {"no-mips3d", no_argument, NULL, OPTION_NO_MIPS3D},
10769 #define OPTION_MDMX (OPTION_ASE_BASE + 4)
10770 {"mdmx", no_argument, NULL, OPTION_MDMX},
10771 #define OPTION_NO_MDMX (OPTION_ASE_BASE + 5)
10772 {"no-mdmx", no_argument, NULL, OPTION_NO_MDMX},
10774 /* Old-style architecture options. Don't add more of these. */
10775 #define OPTION_COMPAT_ARCH_BASE (OPTION_ASE_BASE + 6)
10776 #define OPTION_M4650 (OPTION_COMPAT_ARCH_BASE + 0)
10777 {"m4650", no_argument, NULL, OPTION_M4650},
10778 #define OPTION_NO_M4650 (OPTION_COMPAT_ARCH_BASE + 1)
10779 {"no-m4650", no_argument, NULL, OPTION_NO_M4650},
10780 #define OPTION_M4010 (OPTION_COMPAT_ARCH_BASE + 2)
10781 {"m4010", no_argument, NULL, OPTION_M4010},
10782 #define OPTION_NO_M4010 (OPTION_COMPAT_ARCH_BASE + 3)
10783 {"no-m4010", no_argument, NULL, OPTION_NO_M4010},
10784 #define OPTION_M4100 (OPTION_COMPAT_ARCH_BASE + 4)
10785 {"m4100", no_argument, NULL, OPTION_M4100},
10786 #define OPTION_NO_M4100 (OPTION_COMPAT_ARCH_BASE + 5)
10787 {"no-m4100", no_argument, NULL, OPTION_NO_M4100},
10788 #define OPTION_M3900 (OPTION_COMPAT_ARCH_BASE + 6)
10789 {"m3900", no_argument, NULL, OPTION_M3900},
10790 #define OPTION_NO_M3900 (OPTION_COMPAT_ARCH_BASE + 7)
10791 {"no-m3900", no_argument, NULL, OPTION_NO_M3900},
10793 /* Options which enable bug fixes. */
10794 #define OPTION_FIX_BASE (OPTION_COMPAT_ARCH_BASE + 8)
10795 #define OPTION_M7000_HILO_FIX (OPTION_FIX_BASE + 0)
10796 {"mfix7000", no_argument, NULL, OPTION_M7000_HILO_FIX},
10797 #define OPTION_MNO_7000_HILO_FIX (OPTION_FIX_BASE + 1)
10798 {"no-fix-7000", no_argument, NULL, OPTION_MNO_7000_HILO_FIX},
10799 {"mno-fix7000", no_argument, NULL, OPTION_MNO_7000_HILO_FIX},
10800 #define OPTION_FIX_VR4122 (OPTION_FIX_BASE + 2)
10801 #define OPTION_NO_FIX_VR4122 (OPTION_FIX_BASE + 3)
10802 {"mfix-vr4122-bugs", no_argument, NULL, OPTION_FIX_VR4122},
10803 {"no-mfix-vr4122-bugs", no_argument, NULL, OPTION_NO_FIX_VR4122},
10805 /* Miscellaneous options. */
10806 #define OPTION_MISC_BASE (OPTION_FIX_BASE + 4)
10807 #define OPTION_MEMBEDDED_PIC (OPTION_MISC_BASE + 0)
10808 {"membedded-pic", no_argument, NULL, OPTION_MEMBEDDED_PIC},
10809 #define OPTION_TRAP (OPTION_MISC_BASE + 1)
10810 {"trap", no_argument, NULL, OPTION_TRAP},
10811 {"no-break", no_argument, NULL, OPTION_TRAP},
10812 #define OPTION_BREAK (OPTION_MISC_BASE + 2)
10813 {"break", no_argument, NULL, OPTION_BREAK},
10814 {"no-trap", no_argument, NULL, OPTION_BREAK},
10815 #define OPTION_EB (OPTION_MISC_BASE + 3)
10816 {"EB", no_argument, NULL, OPTION_EB},
10817 #define OPTION_EL (OPTION_MISC_BASE + 4)
10818 {"EL", no_argument, NULL, OPTION_EL},
10819 #define OPTION_FP32 (OPTION_MISC_BASE + 5)
10820 {"mfp32", no_argument, NULL, OPTION_FP32},
10821 #define OPTION_GP32 (OPTION_MISC_BASE + 6)
10822 {"mgp32", no_argument, NULL, OPTION_GP32},
10823 #define OPTION_CONSTRUCT_FLOATS (OPTION_MISC_BASE + 7)
10824 {"construct-floats", no_argument, NULL, OPTION_CONSTRUCT_FLOATS},
10825 #define OPTION_NO_CONSTRUCT_FLOATS (OPTION_MISC_BASE + 8)
10826 {"no-construct-floats", no_argument, NULL, OPTION_NO_CONSTRUCT_FLOATS},
10827 #define OPTION_FP64 (OPTION_MISC_BASE + 9)
10828 {"mfp64", no_argument, NULL, OPTION_FP64},
10829 #define OPTION_GP64 (OPTION_MISC_BASE + 10)
10830 {"mgp64", no_argument, NULL, OPTION_GP64},
10831 #define OPTION_RELAX_BRANCH (OPTION_MISC_BASE + 11)
10832 #define OPTION_NO_RELAX_BRANCH (OPTION_MISC_BASE + 12)
10833 {"relax-branch", no_argument, NULL, OPTION_RELAX_BRANCH},
10834 {"no-relax-branch", no_argument, NULL, OPTION_NO_RELAX_BRANCH},
10836 /* ELF-specific options. */
10838 #define OPTION_ELF_BASE (OPTION_MISC_BASE + 13)
10839 #define OPTION_CALL_SHARED (OPTION_ELF_BASE + 0)
10840 {"KPIC", no_argument, NULL, OPTION_CALL_SHARED},
10841 {"call_shared", no_argument, NULL, OPTION_CALL_SHARED},
10842 #define OPTION_NON_SHARED (OPTION_ELF_BASE + 1)
10843 {"non_shared", no_argument, NULL, OPTION_NON_SHARED},
10844 #define OPTION_XGOT (OPTION_ELF_BASE + 2)
10845 {"xgot", no_argument, NULL, OPTION_XGOT},
10846 #define OPTION_MABI (OPTION_ELF_BASE + 3)
10847 {"mabi", required_argument, NULL, OPTION_MABI},
10848 #define OPTION_32 (OPTION_ELF_BASE + 4)
10849 {"32", no_argument, NULL, OPTION_32},
10850 #define OPTION_N32 (OPTION_ELF_BASE + 5)
10851 {"n32", no_argument, NULL, OPTION_N32},
10852 #define OPTION_64 (OPTION_ELF_BASE + 6)
10853 {"64", no_argument, NULL, OPTION_64},
10854 #define OPTION_MDEBUG (OPTION_ELF_BASE + 7)
10855 {"mdebug", no_argument, NULL, OPTION_MDEBUG},
10856 #define OPTION_NO_MDEBUG (OPTION_ELF_BASE + 8)
10857 {"no-mdebug", no_argument, NULL, OPTION_NO_MDEBUG},
10858 #endif /* OBJ_ELF */
10860 {NULL, no_argument, NULL, 0}
10862 size_t md_longopts_size = sizeof (md_longopts);
10864 /* Set STRING_PTR (either &mips_arch_string or &mips_tune_string) to
10865 NEW_VALUE. Warn if another value was already specified. Note:
10866 we have to defer parsing the -march and -mtune arguments in order
10867 to handle 'from-abi' correctly, since the ABI might be specified
10868 in a later argument. */
10871 mips_set_option_string (string_ptr, new_value)
10872 const char **string_ptr, *new_value;
10874 if (*string_ptr != 0 && strcasecmp (*string_ptr, new_value) != 0)
10875 as_warn (_("A different %s was already specified, is now %s"),
10876 string_ptr == &mips_arch_string ? "-march" : "-mtune",
10879 *string_ptr = new_value;
10883 md_parse_option (c, arg)
10889 case OPTION_CONSTRUCT_FLOATS:
10890 mips_disable_float_construction = 0;
10893 case OPTION_NO_CONSTRUCT_FLOATS:
10894 mips_disable_float_construction = 1;
10906 target_big_endian = 1;
10910 target_big_endian = 0;
10918 if (arg && arg[1] == '0')
10928 mips_debug = atoi (arg);
10929 /* When the MIPS assembler sees -g or -g2, it does not do
10930 optimizations which limit full symbolic debugging. We take
10931 that to be equivalent to -O0. */
10932 if (mips_debug == 2)
10937 file_mips_isa = ISA_MIPS1;
10941 file_mips_isa = ISA_MIPS2;
10945 file_mips_isa = ISA_MIPS3;
10949 file_mips_isa = ISA_MIPS4;
10953 file_mips_isa = ISA_MIPS5;
10956 case OPTION_MIPS32:
10957 file_mips_isa = ISA_MIPS32;
10960 case OPTION_MIPS32R2:
10961 file_mips_isa = ISA_MIPS32R2;
10964 case OPTION_MIPS64:
10965 file_mips_isa = ISA_MIPS64;
10969 mips_set_option_string (&mips_tune_string, arg);
10973 mips_set_option_string (&mips_arch_string, arg);
10977 mips_set_option_string (&mips_arch_string, "4650");
10978 mips_set_option_string (&mips_tune_string, "4650");
10981 case OPTION_NO_M4650:
10985 mips_set_option_string (&mips_arch_string, "4010");
10986 mips_set_option_string (&mips_tune_string, "4010");
10989 case OPTION_NO_M4010:
10993 mips_set_option_string (&mips_arch_string, "4100");
10994 mips_set_option_string (&mips_tune_string, "4100");
10997 case OPTION_NO_M4100:
11001 mips_set_option_string (&mips_arch_string, "3900");
11002 mips_set_option_string (&mips_tune_string, "3900");
11005 case OPTION_NO_M3900:
11009 mips_opts.ase_mdmx = 1;
11012 case OPTION_NO_MDMX:
11013 mips_opts.ase_mdmx = 0;
11016 case OPTION_MIPS16:
11017 mips_opts.mips16 = 1;
11018 mips_no_prev_insn (FALSE);
11021 case OPTION_NO_MIPS16:
11022 mips_opts.mips16 = 0;
11023 mips_no_prev_insn (FALSE);
11026 case OPTION_MIPS3D:
11027 mips_opts.ase_mips3d = 1;
11030 case OPTION_NO_MIPS3D:
11031 mips_opts.ase_mips3d = 0;
11034 case OPTION_MEMBEDDED_PIC:
11035 mips_pic = EMBEDDED_PIC;
11036 if (USE_GLOBAL_POINTER_OPT && g_switch_seen)
11038 as_bad (_("-G may not be used with embedded PIC code"));
11041 g_switch_value = 0x7fffffff;
11044 case OPTION_FIX_VR4122:
11045 mips_fix_4122_bugs = 1;
11048 case OPTION_NO_FIX_VR4122:
11049 mips_fix_4122_bugs = 0;
11052 case OPTION_RELAX_BRANCH:
11053 mips_relax_branch = 1;
11056 case OPTION_NO_RELAX_BRANCH:
11057 mips_relax_branch = 0;
11061 /* When generating ELF code, we permit -KPIC and -call_shared to
11062 select SVR4_PIC, and -non_shared to select no PIC. This is
11063 intended to be compatible with Irix 5. */
11064 case OPTION_CALL_SHARED:
11065 if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
11067 as_bad (_("-call_shared is supported only for ELF format"));
11070 mips_pic = SVR4_PIC;
11071 mips_abicalls = TRUE;
11072 if (g_switch_seen && g_switch_value != 0)
11074 as_bad (_("-G may not be used with SVR4 PIC code"));
11077 g_switch_value = 0;
11080 case OPTION_NON_SHARED:
11081 if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
11083 as_bad (_("-non_shared is supported only for ELF format"));
11087 mips_abicalls = FALSE;
11090 /* The -xgot option tells the assembler to use 32 offsets when
11091 accessing the got in SVR4_PIC mode. It is for Irix
11096 #endif /* OBJ_ELF */
11099 if (! USE_GLOBAL_POINTER_OPT)
11101 as_bad (_("-G is not supported for this configuration"));
11104 else if (mips_pic == SVR4_PIC || mips_pic == EMBEDDED_PIC)
11106 as_bad (_("-G may not be used with SVR4 or embedded PIC code"));
11110 g_switch_value = atoi (arg);
11115 /* The -32, -n32 and -64 options are shortcuts for -mabi=32, -mabi=n32
11118 if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
11120 as_bad (_("-32 is supported for ELF format only"));
11123 mips_abi = O32_ABI;
11127 if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
11129 as_bad (_("-n32 is supported for ELF format only"));
11132 mips_abi = N32_ABI;
11136 if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
11138 as_bad (_("-64 is supported for ELF format only"));
11141 mips_abi = N64_ABI;
11142 if (! support_64bit_objects())
11143 as_fatal (_("No compiled in support for 64 bit object file format"));
11145 #endif /* OBJ_ELF */
11148 file_mips_gp32 = 1;
11152 file_mips_gp32 = 0;
11156 file_mips_fp32 = 1;
11160 file_mips_fp32 = 0;
11165 if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
11167 as_bad (_("-mabi is supported for ELF format only"));
11170 if (strcmp (arg, "32") == 0)
11171 mips_abi = O32_ABI;
11172 else if (strcmp (arg, "o64") == 0)
11173 mips_abi = O64_ABI;
11174 else if (strcmp (arg, "n32") == 0)
11175 mips_abi = N32_ABI;
11176 else if (strcmp (arg, "64") == 0)
11178 mips_abi = N64_ABI;
11179 if (! support_64bit_objects())
11180 as_fatal (_("No compiled in support for 64 bit object file "
11183 else if (strcmp (arg, "eabi") == 0)
11184 mips_abi = EABI_ABI;
11187 as_fatal (_("invalid abi -mabi=%s"), arg);
11191 #endif /* OBJ_ELF */
11193 case OPTION_M7000_HILO_FIX:
11194 mips_7000_hilo_fix = TRUE;
11197 case OPTION_MNO_7000_HILO_FIX:
11198 mips_7000_hilo_fix = FALSE;
11202 case OPTION_MDEBUG:
11203 mips_flag_mdebug = TRUE;
11206 case OPTION_NO_MDEBUG:
11207 mips_flag_mdebug = FALSE;
11209 #endif /* OBJ_ELF */
11218 /* Set up globals to generate code for the ISA or processor
11219 described by INFO. */
11222 mips_set_architecture (info)
11223 const struct mips_cpu_info *info;
11227 mips_arch_info = info;
11228 mips_arch = info->cpu;
11229 mips_opts.isa = info->isa;
11234 /* Likewise for tuning. */
11237 mips_set_tune (info)
11238 const struct mips_cpu_info *info;
11242 mips_tune_info = info;
11243 mips_tune = info->cpu;
11249 mips_after_parse_args ()
11251 /* GP relative stuff not working for PE */
11252 if (strncmp (TARGET_OS, "pe", 2) == 0
11253 && g_switch_value != 0)
11256 as_bad (_("-G not supported in this configuration."));
11257 g_switch_value = 0;
11260 if (mips_abi == NO_ABI)
11261 mips_abi = MIPS_DEFAULT_ABI;
11263 /* The following code determines the architecture and register size.
11264 Similar code was added to GCC 3.3 (see override_options() in
11265 config/mips/mips.c). The GAS and GCC code should be kept in sync
11266 as much as possible. */
11268 if (mips_arch_string != 0)
11269 mips_set_architecture (mips_parse_cpu ("-march", mips_arch_string));
11271 if (mips_tune_string != 0)
11272 mips_set_tune (mips_parse_cpu ("-mtune", mips_tune_string));
11274 if (file_mips_isa != ISA_UNKNOWN)
11276 /* Handle -mipsN. At this point, file_mips_isa contains the
11277 ISA level specified by -mipsN, while mips_opts.isa contains
11278 the -march selection (if any). */
11279 if (mips_arch_info != 0)
11281 /* -march takes precedence over -mipsN, since it is more descriptive.
11282 There's no harm in specifying both as long as the ISA levels
11284 if (file_mips_isa != mips_opts.isa)
11285 as_bad (_("-%s conflicts with the other architecture options, which imply -%s"),
11286 mips_cpu_info_from_isa (file_mips_isa)->name,
11287 mips_cpu_info_from_isa (mips_opts.isa)->name);
11290 mips_set_architecture (mips_cpu_info_from_isa (file_mips_isa));
11293 if (mips_arch_info == 0)
11294 mips_set_architecture (mips_parse_cpu ("default CPU",
11295 MIPS_CPU_STRING_DEFAULT));
11297 if (ABI_NEEDS_64BIT_REGS (mips_abi) && !ISA_HAS_64BIT_REGS (mips_opts.isa))
11298 as_bad ("-march=%s is not compatible with the selected ABI",
11299 mips_arch_info->name);
11301 /* Optimize for mips_arch, unless -mtune selects a different processor. */
11302 if (mips_tune_info == 0)
11303 mips_set_tune (mips_arch_info);
11305 if (file_mips_gp32 >= 0)
11307 /* The user specified the size of the integer registers. Make sure
11308 it agrees with the ABI and ISA. */
11309 if (file_mips_gp32 == 0 && !ISA_HAS_64BIT_REGS (mips_opts.isa))
11310 as_bad (_("-mgp64 used with a 32-bit processor"));
11311 else if (file_mips_gp32 == 1 && ABI_NEEDS_64BIT_REGS (mips_abi))
11312 as_bad (_("-mgp32 used with a 64-bit ABI"));
11313 else if (file_mips_gp32 == 0 && ABI_NEEDS_32BIT_REGS (mips_abi))
11314 as_bad (_("-mgp64 used with a 32-bit ABI"));
11318 /* Infer the integer register size from the ABI and processor.
11319 Restrict ourselves to 32-bit registers if that's all the
11320 processor has, or if the ABI cannot handle 64-bit registers. */
11321 file_mips_gp32 = (ABI_NEEDS_32BIT_REGS (mips_abi)
11322 || !ISA_HAS_64BIT_REGS (mips_opts.isa));
11325 /* ??? GAS treats single-float processors as though they had 64-bit
11326 float registers (although it complains when double-precision
11327 instructions are used). As things stand, saying they have 32-bit
11328 registers would lead to spurious "register must be even" messages.
11329 So here we assume float registers are always the same size as
11330 integer ones, unless the user says otherwise. */
11331 if (file_mips_fp32 < 0)
11332 file_mips_fp32 = file_mips_gp32;
11334 /* End of GCC-shared inference code. */
11336 /* ??? When do we want this flag to be set? Who uses it? */
11337 if (file_mips_gp32 == 1
11338 && mips_abi == NO_ABI
11339 && ISA_HAS_64BIT_REGS (mips_opts.isa))
11340 mips_32bitmode = 1;
11342 if (mips_opts.isa == ISA_MIPS1 && mips_trap)
11343 as_bad (_("trap exception not supported at ISA 1"));
11345 /* If the selected architecture includes support for ASEs, enable
11346 generation of code for them. */
11347 if (mips_opts.mips16 == -1)
11348 mips_opts.mips16 = (CPU_HAS_MIPS16 (mips_arch)) ? 1 : 0;
11349 if (mips_opts.ase_mips3d == -1)
11350 mips_opts.ase_mips3d = (CPU_HAS_MIPS3D (mips_arch)) ? 1 : 0;
11351 if (mips_opts.ase_mdmx == -1)
11352 mips_opts.ase_mdmx = (CPU_HAS_MDMX (mips_arch)) ? 1 : 0;
11354 file_mips_isa = mips_opts.isa;
11355 file_ase_mips16 = mips_opts.mips16;
11356 file_ase_mips3d = mips_opts.ase_mips3d;
11357 file_ase_mdmx = mips_opts.ase_mdmx;
11358 mips_opts.gp32 = file_mips_gp32;
11359 mips_opts.fp32 = file_mips_fp32;
11361 if (mips_flag_mdebug < 0)
11363 #ifdef OBJ_MAYBE_ECOFF
11364 if (OUTPUT_FLAVOR == bfd_target_ecoff_flavour)
11365 mips_flag_mdebug = 1;
11367 #endif /* OBJ_MAYBE_ECOFF */
11368 mips_flag_mdebug = 0;
11373 mips_init_after_args ()
11375 /* initialize opcodes */
11376 bfd_mips_num_opcodes = bfd_mips_num_builtin_opcodes;
11377 mips_opcodes = (struct mips_opcode *) mips_builtin_opcodes;
11381 md_pcrel_from (fixP)
11384 if (OUTPUT_FLAVOR != bfd_target_aout_flavour
11385 && fixP->fx_addsy != (symbolS *) NULL
11386 && ! S_IS_DEFINED (fixP->fx_addsy))
11389 /* Return the address of the delay slot. */
11390 return fixP->fx_size + fixP->fx_where + fixP->fx_frag->fr_address;
11393 /* This is called before the symbol table is processed. In order to
11394 work with gcc when using mips-tfile, we must keep all local labels.
11395 However, in other cases, we want to discard them. If we were
11396 called with -g, but we didn't see any debugging information, it may
11397 mean that gcc is smuggling debugging information through to
11398 mips-tfile, in which case we must generate all local labels. */
11401 mips_frob_file_before_adjust ()
11403 #ifndef NO_ECOFF_DEBUGGING
11404 if (ECOFF_DEBUGGING
11406 && ! ecoff_debugging_seen)
11407 flag_keep_locals = 1;
11411 /* Sort any unmatched HI16_S relocs so that they immediately precede
11412 the corresponding LO reloc. This is called before md_apply_fix3 and
11413 tc_gen_reloc. Unmatched HI16_S relocs can only be generated by
11414 explicit use of the %hi modifier. */
11419 struct mips_hi_fixup *l;
11421 for (l = mips_hi_fixup_list; l != NULL; l = l->next)
11423 segment_info_type *seginfo;
11426 assert (reloc_needs_lo_p (l->fixp->fx_r_type));
11428 /* If a GOT16 relocation turns out to be against a global symbol,
11429 there isn't supposed to be a matching LO. */
11430 if (l->fixp->fx_r_type == BFD_RELOC_MIPS_GOT16
11431 && !pic_need_relax (l->fixp->fx_addsy, l->seg))
11434 /* Check quickly whether the next fixup happens to be a matching %lo. */
11435 if (fixup_has_matching_lo_p (l->fixp))
11438 /* Look through the fixups for this segment for a matching %lo.
11439 When we find one, move the %hi just in front of it. We do
11440 this in two passes. In the first pass, we try to find a
11441 unique %lo. In the second pass, we permit multiple %hi
11442 relocs for a single %lo (this is a GNU extension). */
11443 seginfo = seg_info (l->seg);
11444 for (pass = 0; pass < 2; pass++)
11449 for (f = seginfo->fix_root; f != NULL; f = f->fx_next)
11451 /* Check whether this is a %lo fixup which matches l->fixp. */
11452 if (f->fx_r_type == BFD_RELOC_LO16
11453 && f->fx_addsy == l->fixp->fx_addsy
11454 && f->fx_offset == l->fixp->fx_offset
11457 || !reloc_needs_lo_p (prev->fx_r_type)
11458 || !fixup_has_matching_lo_p (prev)))
11462 /* Move l->fixp before f. */
11463 for (pf = &seginfo->fix_root;
11465 pf = &(*pf)->fx_next)
11466 assert (*pf != NULL);
11468 *pf = l->fixp->fx_next;
11470 l->fixp->fx_next = f;
11472 seginfo->fix_root = l->fixp;
11474 prev->fx_next = l->fixp;
11485 #if 0 /* GCC code motion plus incomplete dead code elimination
11486 can leave a %hi without a %lo. */
11488 as_warn_where (l->fixp->fx_file, l->fixp->fx_line,
11489 _("Unmatched %%hi reloc"));
11495 /* When generating embedded PIC code we need to use a special
11496 relocation to represent the difference of two symbols in the .text
11497 section (switch tables use a difference of this sort). See
11498 include/coff/mips.h for details. This macro checks whether this
11499 fixup requires the special reloc. */
11500 #define SWITCH_TABLE(fixp) \
11501 ((fixp)->fx_r_type == BFD_RELOC_32 \
11502 && OUTPUT_FLAVOR != bfd_target_elf_flavour \
11503 && (fixp)->fx_addsy != NULL \
11504 && (fixp)->fx_subsy != NULL \
11505 && S_GET_SEGMENT ((fixp)->fx_addsy) == text_section \
11506 && S_GET_SEGMENT ((fixp)->fx_subsy) == text_section)
11508 /* When generating embedded PIC code we must keep all PC relative
11509 relocations, in case the linker has to relax a call. We also need
11510 to keep relocations for switch table entries.
11512 We may have combined relocations without symbols in the N32/N64 ABI.
11513 We have to prevent gas from dropping them. */
11516 mips_force_relocation (fixp)
11519 if (generic_force_reloc (fixp))
11523 && S_GET_SEGMENT (fixp->fx_addsy) == bfd_abs_section_ptr
11524 && (fixp->fx_r_type == BFD_RELOC_MIPS_SUB
11525 || fixp->fx_r_type == BFD_RELOC_HI16_S
11526 || fixp->fx_r_type == BFD_RELOC_LO16))
11529 return (mips_pic == EMBEDDED_PIC
11531 || SWITCH_TABLE (fixp)
11532 || fixp->fx_r_type == BFD_RELOC_PCREL_HI16_S
11533 || fixp->fx_r_type == BFD_RELOC_PCREL_LO16));
11536 /* This hook is called before a fix is simplified. We don't really
11537 decide whether to skip a fix here. Rather, we turn global symbols
11538 used as branch targets into local symbols, such that they undergo
11539 simplification. We can only do this if the symbol is defined and
11540 it is in the same section as the branch. If this doesn't hold, we
11541 emit a better error message than just saying the relocation is not
11542 valid for the selected object format.
11544 FIXP is the fix-up we're going to try to simplify, SEG is the
11545 segment in which the fix up occurs. The return value should be
11546 non-zero to indicate the fix-up is valid for further
11547 simplifications. */
11550 mips_validate_fix (fixP, seg)
11554 /* There's a lot of discussion on whether it should be possible to
11555 use R_MIPS_PC16 to represent branch relocations. The outcome
11556 seems to be that it can, but gas/bfd are very broken in creating
11557 RELA relocations for this, so for now we only accept branches to
11558 symbols in the same section. Anything else is of dubious value,
11559 since there's no guarantee that at link time the symbol would be
11560 in range. Even for branches to local symbols this is arguably
11561 wrong, since it we assume the symbol is not going to be
11562 overridden, which should be possible per ELF library semantics,
11563 but then, there isn't a dynamic relocation that could be used to
11564 this effect, and the target would likely be out of range as well.
11566 Unfortunately, it seems that there is too much code out there
11567 that relies on branches to symbols that are global to be resolved
11568 as if they were local, like the IRIX tools do, so we do it as
11569 well, but with a warning so that people are reminded to fix their
11570 code. If we ever get back to using R_MIPS_PC16 for branch
11571 targets, this entire block should go away (and probably the
11572 whole function). */
11574 if (fixP->fx_r_type == BFD_RELOC_16_PCREL_S2
11575 && (((OUTPUT_FLAVOR == bfd_target_ecoff_flavour
11576 || OUTPUT_FLAVOR == bfd_target_elf_flavour)
11577 && mips_pic != EMBEDDED_PIC)
11578 || bfd_reloc_type_lookup (stdoutput, BFD_RELOC_16_PCREL_S2) == NULL)
11581 if (! S_IS_DEFINED (fixP->fx_addsy))
11583 as_bad_where (fixP->fx_file, fixP->fx_line,
11584 _("Cannot branch to undefined symbol."));
11585 /* Avoid any further errors about this fixup. */
11588 else if (S_GET_SEGMENT (fixP->fx_addsy) != seg)
11590 as_bad_where (fixP->fx_file, fixP->fx_line,
11591 _("Cannot branch to symbol in another section."));
11594 else if (S_IS_EXTERNAL (fixP->fx_addsy))
11596 symbolS *sym = fixP->fx_addsy;
11598 as_warn_where (fixP->fx_file, fixP->fx_line,
11599 _("Pretending global symbol used as branch target is local."));
11601 fixP->fx_addsy = symbol_create (S_GET_NAME (sym),
11602 S_GET_SEGMENT (sym),
11604 symbol_get_frag (sym));
11605 copy_symbol_attributes (fixP->fx_addsy, sym);
11606 S_CLEAR_EXTERNAL (fixP->fx_addsy);
11607 assert (symbol_resolved_p (sym));
11608 symbol_mark_resolved (fixP->fx_addsy);
11617 mips_need_elf_addend_fixup (fixP)
11620 if (S_GET_OTHER (fixP->fx_addsy) == STO_MIPS16)
11622 if (mips_pic == EMBEDDED_PIC
11623 && S_IS_WEAK (fixP->fx_addsy))
11625 if (mips_pic != EMBEDDED_PIC
11626 && (S_IS_WEAK (fixP->fx_addsy)
11627 || S_IS_EXTERNAL (fixP->fx_addsy))
11628 && !S_IS_COMMON (fixP->fx_addsy))
11630 if (((bfd_get_section_flags (stdoutput,
11631 S_GET_SEGMENT (fixP->fx_addsy))
11632 & (SEC_LINK_ONCE | SEC_MERGE)) != 0)
11633 || !strncmp (segment_name (S_GET_SEGMENT (fixP->fx_addsy)),
11635 sizeof (".gnu.linkonce") - 1))
11641 /* Apply a fixup to the object file. */
11644 md_apply_fix3 (fixP, valP, seg)
11647 segT seg ATTRIBUTE_UNUSED;
11652 static int previous_fx_r_type = 0;
11654 /* FIXME: Maybe just return for all reloc types not listed below?
11655 Eric Christopher says: "This is stupid, please rewrite md_apply_fix3. */
11656 if (fixP->fx_r_type == BFD_RELOC_8)
11659 assert (fixP->fx_size == 4
11660 || fixP->fx_r_type == BFD_RELOC_16
11661 || fixP->fx_r_type == BFD_RELOC_32
11662 || fixP->fx_r_type == BFD_RELOC_MIPS_JMP
11663 || fixP->fx_r_type == BFD_RELOC_HI16_S
11664 || fixP->fx_r_type == BFD_RELOC_LO16
11665 || fixP->fx_r_type == BFD_RELOC_GPREL16
11666 || fixP->fx_r_type == BFD_RELOC_MIPS_LITERAL
11667 || fixP->fx_r_type == BFD_RELOC_GPREL32
11668 || fixP->fx_r_type == BFD_RELOC_64
11669 || fixP->fx_r_type == BFD_RELOC_CTOR
11670 || fixP->fx_r_type == BFD_RELOC_MIPS_SUB
11671 || fixP->fx_r_type == BFD_RELOC_MIPS_HIGHEST
11672 || fixP->fx_r_type == BFD_RELOC_MIPS_HIGHER
11673 || fixP->fx_r_type == BFD_RELOC_MIPS_SCN_DISP
11674 || fixP->fx_r_type == BFD_RELOC_MIPS_REL16
11675 || fixP->fx_r_type == BFD_RELOC_MIPS_RELGOT
11676 || fixP->fx_r_type == BFD_RELOC_VTABLE_INHERIT
11677 || fixP->fx_r_type == BFD_RELOC_VTABLE_ENTRY
11678 || fixP->fx_r_type == BFD_RELOC_MIPS_JALR);
11682 /* If we aren't adjusting this fixup to be against the section
11683 symbol, we need to adjust the value. */
11685 if (fixP->fx_addsy != NULL && OUTPUT_FLAVOR == bfd_target_elf_flavour)
11687 if (mips_need_elf_addend_fixup (fixP))
11689 reloc_howto_type *howto;
11690 valueT symval = S_GET_VALUE (fixP->fx_addsy);
11694 howto = bfd_reloc_type_lookup (stdoutput, fixP->fx_r_type);
11695 if (value != 0 && howto && howto->partial_inplace)
11697 /* In this case, the bfd_install_relocation routine will
11698 incorrectly add the symbol value back in. We just want
11699 the addend to appear in the object file.
11701 The condition above used to include
11702 "&& (! fixP->fx_pcrel || howto->pcrel_offset)".
11704 However, howto can't be trusted here, because we
11705 might change the reloc type in tc_gen_reloc. We can
11706 check howto->partial_inplace because that conversion
11707 happens to preserve howto->partial_inplace; but it
11708 does not preserve howto->pcrel_offset. I've just
11709 eliminated the check, because all MIPS PC-relative
11710 relocations are marked howto->pcrel_offset.
11712 howto->pcrel_offset was originally added for
11713 R_MIPS_PC16, which is generated for code like
11724 /* Make sure the addend is still non-zero. If it became zero
11725 after the last operation, set it to a spurious value and
11726 subtract the same value from the object file's contents. */
11731 /* The in-place addends for LO16 relocations are signed;
11732 leave the matching HI16 in-place addends as zero. */
11733 if (fixP->fx_r_type != BFD_RELOC_HI16_S)
11735 bfd_vma contents, mask, field;
11737 contents = bfd_get_bits (fixP->fx_frag->fr_literal
11740 target_big_endian);
11742 /* MASK has bits set where the relocation should go.
11743 FIELD is -value, shifted into the appropriate place
11744 for this relocation. */
11745 mask = 1 << (howto->bitsize - 1);
11746 mask = (((mask - 1) << 1) | 1) << howto->bitpos;
11747 field = (-value >> howto->rightshift) << howto->bitpos;
11749 bfd_put_bits ((field & mask) | (contents & ~mask),
11750 fixP->fx_frag->fr_literal + fixP->fx_where,
11752 target_big_endian);
11758 /* This code was generated using trial and error and so is
11759 fragile and not trustworthy. If you change it, you should
11760 rerun the elf-rel, elf-rel2, and empic testcases and ensure
11761 they still pass. */
11762 if (fixP->fx_pcrel || fixP->fx_subsy != NULL)
11764 value += fixP->fx_frag->fr_address + fixP->fx_where;
11766 /* BFD's REL handling, for MIPS, is _very_ weird.
11767 This gives the right results, but it can't possibly
11768 be the way things are supposed to work. */
11769 if (fixP->fx_r_type != BFD_RELOC_16_PCREL_S2
11770 || S_GET_SEGMENT (fixP->fx_addsy) != undefined_section)
11771 value += fixP->fx_frag->fr_address + fixP->fx_where;
11776 fixP->fx_addnumber = value; /* Remember value for tc_gen_reloc. */
11778 /* We are not done if this is a composite relocation to set up gp. */
11779 if (fixP->fx_addsy == NULL && ! fixP->fx_pcrel
11780 && !(fixP->fx_r_type == BFD_RELOC_MIPS_SUB
11781 || (fixP->fx_r_type == BFD_RELOC_64
11782 && (previous_fx_r_type == BFD_RELOC_GPREL32
11783 || previous_fx_r_type == BFD_RELOC_GPREL16))
11784 || (previous_fx_r_type == BFD_RELOC_MIPS_SUB
11785 && (fixP->fx_r_type == BFD_RELOC_HI16_S
11786 || fixP->fx_r_type == BFD_RELOC_LO16))))
11788 previous_fx_r_type = fixP->fx_r_type;
11790 switch (fixP->fx_r_type)
11792 case BFD_RELOC_MIPS_JMP:
11793 case BFD_RELOC_MIPS_SHIFT5:
11794 case BFD_RELOC_MIPS_SHIFT6:
11795 case BFD_RELOC_MIPS_GOT_DISP:
11796 case BFD_RELOC_MIPS_GOT_PAGE:
11797 case BFD_RELOC_MIPS_GOT_OFST:
11798 case BFD_RELOC_MIPS_SUB:
11799 case BFD_RELOC_MIPS_INSERT_A:
11800 case BFD_RELOC_MIPS_INSERT_B:
11801 case BFD_RELOC_MIPS_DELETE:
11802 case BFD_RELOC_MIPS_HIGHEST:
11803 case BFD_RELOC_MIPS_HIGHER:
11804 case BFD_RELOC_MIPS_SCN_DISP:
11805 case BFD_RELOC_MIPS_REL16:
11806 case BFD_RELOC_MIPS_RELGOT:
11807 case BFD_RELOC_MIPS_JALR:
11808 case BFD_RELOC_HI16:
11809 case BFD_RELOC_HI16_S:
11810 case BFD_RELOC_GPREL16:
11811 case BFD_RELOC_MIPS_LITERAL:
11812 case BFD_RELOC_MIPS_CALL16:
11813 case BFD_RELOC_MIPS_GOT16:
11814 case BFD_RELOC_GPREL32:
11815 case BFD_RELOC_MIPS_GOT_HI16:
11816 case BFD_RELOC_MIPS_GOT_LO16:
11817 case BFD_RELOC_MIPS_CALL_HI16:
11818 case BFD_RELOC_MIPS_CALL_LO16:
11819 case BFD_RELOC_MIPS16_GPREL:
11820 if (fixP->fx_pcrel)
11821 as_bad_where (fixP->fx_file, fixP->fx_line,
11822 _("Invalid PC relative reloc"));
11823 /* Nothing needed to do. The value comes from the reloc entry */
11826 case BFD_RELOC_MIPS16_JMP:
11827 /* We currently always generate a reloc against a symbol, which
11828 means that we don't want an addend even if the symbol is
11830 fixP->fx_addnumber = 0;
11833 case BFD_RELOC_PCREL_HI16_S:
11834 /* The addend for this is tricky if it is internal, so we just
11835 do everything here rather than in bfd_install_relocation. */
11836 if (OUTPUT_FLAVOR == bfd_target_elf_flavour
11841 && (symbol_get_bfdsym (fixP->fx_addsy)->flags & BSF_SECTION_SYM) == 0)
11843 /* For an external symbol adjust by the address to make it
11844 pcrel_offset. We use the address of the RELLO reloc
11845 which follows this one. */
11846 value += (fixP->fx_next->fx_frag->fr_address
11847 + fixP->fx_next->fx_where);
11849 value = ((value + 0x8000) >> 16) & 0xffff;
11850 buf = (bfd_byte *) fixP->fx_frag->fr_literal + fixP->fx_where;
11851 if (target_big_endian)
11853 md_number_to_chars ((char *) buf, value, 2);
11856 case BFD_RELOC_PCREL_LO16:
11857 /* The addend for this is tricky if it is internal, so we just
11858 do everything here rather than in bfd_install_relocation. */
11859 if (OUTPUT_FLAVOR == bfd_target_elf_flavour
11864 && (symbol_get_bfdsym (fixP->fx_addsy)->flags & BSF_SECTION_SYM) == 0)
11865 value += fixP->fx_frag->fr_address + fixP->fx_where;
11866 buf = (bfd_byte *) fixP->fx_frag->fr_literal + fixP->fx_where;
11867 if (target_big_endian)
11869 md_number_to_chars ((char *) buf, value, 2);
11873 /* This is handled like BFD_RELOC_32, but we output a sign
11874 extended value if we are only 32 bits. */
11876 || (mips_pic == EMBEDDED_PIC && SWITCH_TABLE (fixP)))
11878 if (8 <= sizeof (valueT))
11879 md_number_to_chars (fixP->fx_frag->fr_literal + fixP->fx_where,
11886 w1 = w2 = fixP->fx_where;
11887 if (target_big_endian)
11891 md_number_to_chars (fixP->fx_frag->fr_literal + w1, value, 4);
11892 if ((value & 0x80000000) != 0)
11896 md_number_to_chars (fixP->fx_frag->fr_literal + w2, hiv, 4);
11901 case BFD_RELOC_RVA:
11903 /* If we are deleting this reloc entry, we must fill in the
11904 value now. This can happen if we have a .word which is not
11905 resolved when it appears but is later defined. We also need
11906 to fill in the value if this is an embedded PIC switch table
11909 || (mips_pic == EMBEDDED_PIC && SWITCH_TABLE (fixP)))
11910 md_number_to_chars (fixP->fx_frag->fr_literal + fixP->fx_where,
11915 /* If we are deleting this reloc entry, we must fill in the
11917 assert (fixP->fx_size == 2);
11919 md_number_to_chars (fixP->fx_frag->fr_literal + fixP->fx_where,
11923 case BFD_RELOC_LO16:
11924 /* When handling an embedded PIC switch statement, we can wind
11925 up deleting a LO16 reloc. See the 'o' case in mips_ip. */
11928 if (value + 0x8000 > 0xffff)
11929 as_bad_where (fixP->fx_file, fixP->fx_line,
11930 _("relocation overflow"));
11931 buf = (bfd_byte *) fixP->fx_frag->fr_literal + fixP->fx_where;
11932 if (target_big_endian)
11934 md_number_to_chars ((char *) buf, value, 2);
11938 case BFD_RELOC_16_PCREL_S2:
11939 if ((value & 0x3) != 0)
11940 as_bad_where (fixP->fx_file, fixP->fx_line,
11941 _("Branch to odd address (%lx)"), (long) value);
11944 * We need to save the bits in the instruction since fixup_segment()
11945 * might be deleting the relocation entry (i.e., a branch within
11946 * the current segment).
11948 if (!fixP->fx_done && (value != 0 || HAVE_NEWABI))
11950 /* If 'value' is zero, the remaining reloc code won't actually
11951 do the store, so it must be done here. This is probably
11952 a bug somewhere. */
11954 && (fixP->fx_r_type != BFD_RELOC_16_PCREL_S2
11955 || fixP->fx_addsy == NULL /* ??? */
11956 || ! S_IS_DEFINED (fixP->fx_addsy)))
11957 value -= fixP->fx_frag->fr_address + fixP->fx_where;
11959 value = (offsetT) value >> 2;
11961 /* update old instruction data */
11962 buf = (bfd_byte *) (fixP->fx_where + fixP->fx_frag->fr_literal);
11963 if (target_big_endian)
11964 insn = (buf[0] << 24) | (buf[1] << 16) | (buf[2] << 8) | buf[3];
11966 insn = (buf[3] << 24) | (buf[2] << 16) | (buf[1] << 8) | buf[0];
11968 if (value + 0x8000 <= 0xffff)
11969 insn |= value & 0xffff;
11972 /* The branch offset is too large. If this is an
11973 unconditional branch, and we are not generating PIC code,
11974 we can convert it to an absolute jump instruction. */
11975 if (mips_pic == NO_PIC
11977 && fixP->fx_frag->fr_address >= text_section->vma
11978 && (fixP->fx_frag->fr_address
11979 < text_section->vma + text_section->_raw_size)
11980 && ((insn & 0xffff0000) == 0x10000000 /* beq $0,$0 */
11981 || (insn & 0xffff0000) == 0x04010000 /* bgez $0 */
11982 || (insn & 0xffff0000) == 0x04110000)) /* bgezal $0 */
11984 if ((insn & 0xffff0000) == 0x04110000) /* bgezal $0 */
11985 insn = 0x0c000000; /* jal */
11987 insn = 0x08000000; /* j */
11988 fixP->fx_r_type = BFD_RELOC_MIPS_JMP;
11990 fixP->fx_addsy = section_symbol (text_section);
11991 fixP->fx_addnumber = (value << 2) + md_pcrel_from (fixP);
11995 /* If we got here, we have branch-relaxation disabled,
11996 and there's nothing we can do to fix this instruction
11997 without turning it into a longer sequence. */
11998 as_bad_where (fixP->fx_file, fixP->fx_line,
11999 _("Branch out of range"));
12003 md_number_to_chars ((char *) buf, (valueT) insn, 4);
12006 case BFD_RELOC_VTABLE_INHERIT:
12009 && !S_IS_DEFINED (fixP->fx_addsy)
12010 && !S_IS_WEAK (fixP->fx_addsy))
12011 S_SET_WEAK (fixP->fx_addsy);
12014 case BFD_RELOC_VTABLE_ENTRY:
12028 const struct mips_opcode *p;
12029 int treg, sreg, dreg, shamt;
12034 for (i = 0; i < NUMOPCODES; ++i)
12036 p = &mips_opcodes[i];
12037 if (((oc & p->mask) == p->match) && (p->pinfo != INSN_MACRO))
12039 printf ("%08lx %s\t", oc, p->name);
12040 treg = (oc >> 16) & 0x1f;
12041 sreg = (oc >> 21) & 0x1f;
12042 dreg = (oc >> 11) & 0x1f;
12043 shamt = (oc >> 6) & 0x1f;
12045 for (args = p->args;; ++args)
12056 printf ("%c", *args);
12060 assert (treg == sreg);
12061 printf ("$%d,$%d", treg, sreg);
12066 printf ("$%d", dreg);
12071 printf ("$%d", treg);
12075 printf ("0x%x", treg);
12080 printf ("$%d", sreg);
12084 printf ("0x%08lx", oc & 0x1ffffff);
12091 printf ("%d", imm);
12096 printf ("$%d", shamt);
12107 printf (_("%08lx UNDEFINED\n"), oc);
12118 name = input_line_pointer;
12119 c = get_symbol_end ();
12120 p = (symbolS *) symbol_find_or_make (name);
12121 *input_line_pointer = c;
12125 /* Align the current frag to a given power of two. The MIPS assembler
12126 also automatically adjusts any preceding label. */
12129 mips_align (to, fill, label)
12134 mips_emit_delays (FALSE);
12135 frag_align (to, fill, 0);
12136 record_alignment (now_seg, to);
12139 assert (S_GET_SEGMENT (label) == now_seg);
12140 symbol_set_frag (label, frag_now);
12141 S_SET_VALUE (label, (valueT) frag_now_fix ());
12145 /* Align to a given power of two. .align 0 turns off the automatic
12146 alignment used by the data creating pseudo-ops. */
12150 int x ATTRIBUTE_UNUSED;
12153 register long temp_fill;
12154 long max_alignment = 15;
12158 o Note that the assembler pulls down any immediately preceeding label
12159 to the aligned address.
12160 o It's not documented but auto alignment is reinstated by
12161 a .align pseudo instruction.
12162 o Note also that after auto alignment is turned off the mips assembler
12163 issues an error on attempt to assemble an improperly aligned data item.
12168 temp = get_absolute_expression ();
12169 if (temp > max_alignment)
12170 as_bad (_("Alignment too large: %d. assumed."), temp = max_alignment);
12173 as_warn (_("Alignment negative: 0 assumed."));
12176 if (*input_line_pointer == ',')
12178 ++input_line_pointer;
12179 temp_fill = get_absolute_expression ();
12186 mips_align (temp, (int) temp_fill,
12187 insn_labels != NULL ? insn_labels->label : NULL);
12194 demand_empty_rest_of_line ();
12198 mips_flush_pending_output ()
12200 mips_emit_delays (FALSE);
12201 mips_clear_insn_labels ();
12210 /* When generating embedded PIC code, we only use the .text, .lit8,
12211 .sdata and .sbss sections. We change the .data and .rdata
12212 pseudo-ops to use .sdata. */
12213 if (mips_pic == EMBEDDED_PIC
12214 && (sec == 'd' || sec == 'r'))
12218 /* The ELF backend needs to know that we are changing sections, so
12219 that .previous works correctly. We could do something like check
12220 for an obj_section_change_hook macro, but that might be confusing
12221 as it would not be appropriate to use it in the section changing
12222 functions in read.c, since obj-elf.c intercepts those. FIXME:
12223 This should be cleaner, somehow. */
12224 obj_elf_section_change_hook ();
12227 mips_emit_delays (FALSE);
12237 subseg_set (bss_section, (subsegT) get_absolute_expression ());
12238 demand_empty_rest_of_line ();
12242 if (USE_GLOBAL_POINTER_OPT)
12244 seg = subseg_new (RDATA_SECTION_NAME,
12245 (subsegT) get_absolute_expression ());
12246 if (OUTPUT_FLAVOR == bfd_target_elf_flavour)
12248 bfd_set_section_flags (stdoutput, seg,
12254 if (strcmp (TARGET_OS, "elf") != 0)
12255 record_alignment (seg, 4);
12257 demand_empty_rest_of_line ();
12261 as_bad (_("No read only data section in this object file format"));
12262 demand_empty_rest_of_line ();
12268 if (USE_GLOBAL_POINTER_OPT)
12270 seg = subseg_new (".sdata", (subsegT) get_absolute_expression ());
12271 if (OUTPUT_FLAVOR == bfd_target_elf_flavour)
12273 bfd_set_section_flags (stdoutput, seg,
12274 SEC_ALLOC | SEC_LOAD | SEC_RELOC
12276 if (strcmp (TARGET_OS, "elf") != 0)
12277 record_alignment (seg, 4);
12279 demand_empty_rest_of_line ();
12284 as_bad (_("Global pointers not supported; recompile -G 0"));
12285 demand_empty_rest_of_line ();
12294 s_change_section (ignore)
12295 int ignore ATTRIBUTE_UNUSED;
12298 char *section_name;
12303 int section_entry_size;
12304 int section_alignment;
12306 if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
12309 section_name = input_line_pointer;
12310 c = get_symbol_end ();
12312 next_c = *(input_line_pointer + 1);
12314 /* Do we have .section Name<,"flags">? */
12315 if (c != ',' || (c == ',' && next_c == '"'))
12317 /* just after name is now '\0'. */
12318 *input_line_pointer = c;
12319 input_line_pointer = section_name;
12320 obj_elf_section (ignore);
12323 input_line_pointer++;
12325 /* Do we have .section Name<,type><,flag><,entry_size><,alignment> */
12327 section_type = get_absolute_expression ();
12330 if (*input_line_pointer++ == ',')
12331 section_flag = get_absolute_expression ();
12334 if (*input_line_pointer++ == ',')
12335 section_entry_size = get_absolute_expression ();
12337 section_entry_size = 0;
12338 if (*input_line_pointer++ == ',')
12339 section_alignment = get_absolute_expression ();
12341 section_alignment = 0;
12343 section_name = xstrdup (section_name);
12345 obj_elf_change_section (section_name, section_type, section_flag,
12346 section_entry_size, 0, 0, 0);
12348 if (now_seg->name != section_name)
12349 free (section_name);
12350 #endif /* OBJ_ELF */
12354 mips_enable_auto_align ()
12365 label = insn_labels != NULL ? insn_labels->label : NULL;
12366 mips_emit_delays (FALSE);
12367 if (log_size > 0 && auto_align)
12368 mips_align (log_size, 0, label);
12369 mips_clear_insn_labels ();
12370 cons (1 << log_size);
12374 s_float_cons (type)
12379 label = insn_labels != NULL ? insn_labels->label : NULL;
12381 mips_emit_delays (FALSE);
12386 mips_align (3, 0, label);
12388 mips_align (2, 0, label);
12391 mips_clear_insn_labels ();
12396 /* Handle .globl. We need to override it because on Irix 5 you are
12399 where foo is an undefined symbol, to mean that foo should be
12400 considered to be the address of a function. */
12404 int x ATTRIBUTE_UNUSED;
12411 name = input_line_pointer;
12412 c = get_symbol_end ();
12413 symbolP = symbol_find_or_make (name);
12414 *input_line_pointer = c;
12415 SKIP_WHITESPACE ();
12417 /* On Irix 5, every global symbol that is not explicitly labelled as
12418 being a function is apparently labelled as being an object. */
12421 if (! is_end_of_line[(unsigned char) *input_line_pointer])
12426 secname = input_line_pointer;
12427 c = get_symbol_end ();
12428 sec = bfd_get_section_by_name (stdoutput, secname);
12430 as_bad (_("%s: no such section"), secname);
12431 *input_line_pointer = c;
12433 if (sec != NULL && (sec->flags & SEC_CODE) != 0)
12434 flag = BSF_FUNCTION;
12437 symbol_get_bfdsym (symbolP)->flags |= flag;
12439 S_SET_EXTERNAL (symbolP);
12440 demand_empty_rest_of_line ();
12445 int x ATTRIBUTE_UNUSED;
12450 opt = input_line_pointer;
12451 c = get_symbol_end ();
12455 /* FIXME: What does this mean? */
12457 else if (strncmp (opt, "pic", 3) == 0)
12461 i = atoi (opt + 3);
12466 mips_pic = SVR4_PIC;
12467 mips_abicalls = TRUE;
12470 as_bad (_(".option pic%d not supported"), i);
12472 if (USE_GLOBAL_POINTER_OPT && mips_pic == SVR4_PIC)
12474 if (g_switch_seen && g_switch_value != 0)
12475 as_warn (_("-G may not be used with SVR4 PIC code"));
12476 g_switch_value = 0;
12477 bfd_set_gp_size (stdoutput, 0);
12481 as_warn (_("Unrecognized option \"%s\""), opt);
12483 *input_line_pointer = c;
12484 demand_empty_rest_of_line ();
12487 /* This structure is used to hold a stack of .set values. */
12489 struct mips_option_stack
12491 struct mips_option_stack *next;
12492 struct mips_set_options options;
12495 static struct mips_option_stack *mips_opts_stack;
12497 /* Handle the .set pseudo-op. */
12501 int x ATTRIBUTE_UNUSED;
12503 char *name = input_line_pointer, ch;
12505 while (!is_end_of_line[(unsigned char) *input_line_pointer])
12506 ++input_line_pointer;
12507 ch = *input_line_pointer;
12508 *input_line_pointer = '\0';
12510 if (strcmp (name, "reorder") == 0)
12512 if (mips_opts.noreorder && prev_nop_frag != NULL)
12514 /* If we still have pending nops, we can discard them. The
12515 usual nop handling will insert any that are still
12517 prev_nop_frag->fr_fix -= (prev_nop_frag_holds
12518 * (mips_opts.mips16 ? 2 : 4));
12519 prev_nop_frag = NULL;
12521 mips_opts.noreorder = 0;
12523 else if (strcmp (name, "noreorder") == 0)
12525 mips_emit_delays (TRUE);
12526 mips_opts.noreorder = 1;
12527 mips_any_noreorder = 1;
12529 else if (strcmp (name, "at") == 0)
12531 mips_opts.noat = 0;
12533 else if (strcmp (name, "noat") == 0)
12535 mips_opts.noat = 1;
12537 else if (strcmp (name, "macro") == 0)
12539 mips_opts.warn_about_macros = 0;
12541 else if (strcmp (name, "nomacro") == 0)
12543 if (mips_opts.noreorder == 0)
12544 as_bad (_("`noreorder' must be set before `nomacro'"));
12545 mips_opts.warn_about_macros = 1;
12547 else if (strcmp (name, "move") == 0 || strcmp (name, "novolatile") == 0)
12549 mips_opts.nomove = 0;
12551 else if (strcmp (name, "nomove") == 0 || strcmp (name, "volatile") == 0)
12553 mips_opts.nomove = 1;
12555 else if (strcmp (name, "bopt") == 0)
12557 mips_opts.nobopt = 0;
12559 else if (strcmp (name, "nobopt") == 0)
12561 mips_opts.nobopt = 1;
12563 else if (strcmp (name, "mips16") == 0
12564 || strcmp (name, "MIPS-16") == 0)
12565 mips_opts.mips16 = 1;
12566 else if (strcmp (name, "nomips16") == 0
12567 || strcmp (name, "noMIPS-16") == 0)
12568 mips_opts.mips16 = 0;
12569 else if (strcmp (name, "mips3d") == 0)
12570 mips_opts.ase_mips3d = 1;
12571 else if (strcmp (name, "nomips3d") == 0)
12572 mips_opts.ase_mips3d = 0;
12573 else if (strcmp (name, "mdmx") == 0)
12574 mips_opts.ase_mdmx = 1;
12575 else if (strcmp (name, "nomdmx") == 0)
12576 mips_opts.ase_mdmx = 0;
12577 else if (strncmp (name, "mips", 4) == 0)
12581 /* Permit the user to change the ISA on the fly. Needless to
12582 say, misuse can cause serious problems. */
12583 if (strcmp (name, "mips0") == 0)
12586 mips_opts.isa = file_mips_isa;
12588 else if (strcmp (name, "mips1") == 0)
12589 mips_opts.isa = ISA_MIPS1;
12590 else if (strcmp (name, "mips2") == 0)
12591 mips_opts.isa = ISA_MIPS2;
12592 else if (strcmp (name, "mips3") == 0)
12593 mips_opts.isa = ISA_MIPS3;
12594 else if (strcmp (name, "mips4") == 0)
12595 mips_opts.isa = ISA_MIPS4;
12596 else if (strcmp (name, "mips5") == 0)
12597 mips_opts.isa = ISA_MIPS5;
12598 else if (strcmp (name, "mips32") == 0)
12599 mips_opts.isa = ISA_MIPS32;
12600 else if (strcmp (name, "mips32r2") == 0)
12601 mips_opts.isa = ISA_MIPS32R2;
12602 else if (strcmp (name, "mips64") == 0)
12603 mips_opts.isa = ISA_MIPS64;
12605 as_bad (_("unknown ISA level %s"), name + 4);
12607 switch (mips_opts.isa)
12615 mips_opts.gp32 = 1;
12616 mips_opts.fp32 = 1;
12622 mips_opts.gp32 = 0;
12623 mips_opts.fp32 = 0;
12626 as_bad (_("unknown ISA level %s"), name + 4);
12631 mips_opts.gp32 = file_mips_gp32;
12632 mips_opts.fp32 = file_mips_fp32;
12635 else if (strcmp (name, "autoextend") == 0)
12636 mips_opts.noautoextend = 0;
12637 else if (strcmp (name, "noautoextend") == 0)
12638 mips_opts.noautoextend = 1;
12639 else if (strcmp (name, "push") == 0)
12641 struct mips_option_stack *s;
12643 s = (struct mips_option_stack *) xmalloc (sizeof *s);
12644 s->next = mips_opts_stack;
12645 s->options = mips_opts;
12646 mips_opts_stack = s;
12648 else if (strcmp (name, "pop") == 0)
12650 struct mips_option_stack *s;
12652 s = mips_opts_stack;
12654 as_bad (_(".set pop with no .set push"));
12657 /* If we're changing the reorder mode we need to handle
12658 delay slots correctly. */
12659 if (s->options.noreorder && ! mips_opts.noreorder)
12660 mips_emit_delays (TRUE);
12661 else if (! s->options.noreorder && mips_opts.noreorder)
12663 if (prev_nop_frag != NULL)
12665 prev_nop_frag->fr_fix -= (prev_nop_frag_holds
12666 * (mips_opts.mips16 ? 2 : 4));
12667 prev_nop_frag = NULL;
12671 mips_opts = s->options;
12672 mips_opts_stack = s->next;
12678 as_warn (_("Tried to set unrecognized symbol: %s\n"), name);
12680 *input_line_pointer = ch;
12681 demand_empty_rest_of_line ();
12684 /* Handle the .abicalls pseudo-op. I believe this is equivalent to
12685 .option pic2. It means to generate SVR4 PIC calls. */
12688 s_abicalls (ignore)
12689 int ignore ATTRIBUTE_UNUSED;
12691 mips_pic = SVR4_PIC;
12692 mips_abicalls = TRUE;
12693 if (USE_GLOBAL_POINTER_OPT)
12695 if (g_switch_seen && g_switch_value != 0)
12696 as_warn (_("-G may not be used with SVR4 PIC code"));
12697 g_switch_value = 0;
12699 bfd_set_gp_size (stdoutput, 0);
12700 demand_empty_rest_of_line ();
12703 /* Handle the .cpload pseudo-op. This is used when generating SVR4
12704 PIC code. It sets the $gp register for the function based on the
12705 function address, which is in the register named in the argument.
12706 This uses a relocation against _gp_disp, which is handled specially
12707 by the linker. The result is:
12708 lui $gp,%hi(_gp_disp)
12709 addiu $gp,$gp,%lo(_gp_disp)
12710 addu $gp,$gp,.cpload argument
12711 The .cpload argument is normally $25 == $t9. */
12715 int ignore ATTRIBUTE_UNUSED;
12720 /* If we are not generating SVR4 PIC code, or if this is NewABI code,
12721 .cpload is ignored. */
12722 if (mips_pic != SVR4_PIC || HAVE_NEWABI)
12728 /* .cpload should be in a .set noreorder section. */
12729 if (mips_opts.noreorder == 0)
12730 as_warn (_(".cpload not in noreorder section"));
12732 ex.X_op = O_symbol;
12733 ex.X_add_symbol = symbol_find_or_make ("_gp_disp");
12734 ex.X_op_symbol = NULL;
12735 ex.X_add_number = 0;
12737 /* In ELF, this symbol is implicitly an STT_OBJECT symbol. */
12738 symbol_get_bfdsym (ex.X_add_symbol)->flags |= BSF_OBJECT;
12740 macro_build_lui (NULL, &icnt, &ex, mips_gp_register);
12741 macro_build ((char *) NULL, &icnt, &ex, "addiu", "t,r,j",
12742 mips_gp_register, mips_gp_register, (int) BFD_RELOC_LO16);
12744 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "addu", "d,v,t",
12745 mips_gp_register, mips_gp_register, tc_get_register (0));
12747 demand_empty_rest_of_line ();
12750 /* Handle the .cpsetup pseudo-op defined for NewABI PIC code. The syntax is:
12751 .cpsetup $reg1, offset|$reg2, label
12753 If offset is given, this results in:
12754 sd $gp, offset($sp)
12755 lui $gp, %hi(%neg(%gp_rel(label)))
12756 addiu $gp, $gp, %lo(%neg(%gp_rel(label)))
12757 daddu $gp, $gp, $reg1
12759 If $reg2 is given, this results in:
12760 daddu $reg2, $gp, $0
12761 lui $gp, %hi(%neg(%gp_rel(label)))
12762 addiu $gp, $gp, %lo(%neg(%gp_rel(label)))
12763 daddu $gp, $gp, $reg1
12764 $reg1 is normally $25 == $t9. */
12767 int ignore ATTRIBUTE_UNUSED;
12769 expressionS ex_off;
12770 expressionS ex_sym;
12775 /* If we are not generating SVR4 PIC code, .cpsetup is ignored.
12776 We also need NewABI support. */
12777 if (mips_pic != SVR4_PIC || ! HAVE_NEWABI)
12783 reg1 = tc_get_register (0);
12784 SKIP_WHITESPACE ();
12785 if (*input_line_pointer != ',')
12787 as_bad (_("missing argument separator ',' for .cpsetup"));
12791 ++input_line_pointer;
12792 SKIP_WHITESPACE ();
12793 if (*input_line_pointer == '$')
12795 mips_cpreturn_register = tc_get_register (0);
12796 mips_cpreturn_offset = -1;
12800 mips_cpreturn_offset = get_absolute_expression ();
12801 mips_cpreturn_register = -1;
12803 SKIP_WHITESPACE ();
12804 if (*input_line_pointer != ',')
12806 as_bad (_("missing argument separator ',' for .cpsetup"));
12810 ++input_line_pointer;
12811 SKIP_WHITESPACE ();
12812 expression (&ex_sym);
12814 if (mips_cpreturn_register == -1)
12816 ex_off.X_op = O_constant;
12817 ex_off.X_add_symbol = NULL;
12818 ex_off.X_op_symbol = NULL;
12819 ex_off.X_add_number = mips_cpreturn_offset;
12821 macro_build ((char *) NULL, &icnt, &ex_off, "sd", "t,o(b)",
12822 mips_gp_register, (int) BFD_RELOC_LO16, SP);
12825 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "daddu",
12826 "d,v,t", mips_cpreturn_register, mips_gp_register, 0);
12828 /* Ensure there's room for the next two instructions, so that `f'
12829 doesn't end up with an address in the wrong frag. */
12832 macro_build ((char *) NULL, &icnt, &ex_sym, "lui", "t,u", mips_gp_register,
12833 (int) BFD_RELOC_GPREL16);
12834 fix_new (frag_now, f - frag_now->fr_literal,
12835 8, NULL, 0, 0, BFD_RELOC_MIPS_SUB);
12836 fix_new (frag_now, f - frag_now->fr_literal,
12837 4, NULL, 0, 0, BFD_RELOC_HI16_S);
12840 macro_build ((char *) NULL, &icnt, &ex_sym, "addiu", "t,r,j",
12841 mips_gp_register, mips_gp_register, (int) BFD_RELOC_GPREL16);
12842 fix_new (frag_now, f - frag_now->fr_literal,
12843 8, NULL, 0, 0, BFD_RELOC_MIPS_SUB);
12844 fix_new (frag_now, f - frag_now->fr_literal,
12845 4, NULL, 0, 0, BFD_RELOC_LO16);
12847 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
12848 HAVE_64BIT_ADDRESSES ? "daddu" : "add", "d,v,t",
12849 mips_gp_register, mips_gp_register, reg1);
12851 demand_empty_rest_of_line ();
12856 int ignore ATTRIBUTE_UNUSED;
12858 /* If we are not generating SVR4 PIC code, or if this is not NewABI code,
12859 .cplocal is ignored. */
12860 if (mips_pic != SVR4_PIC || ! HAVE_NEWABI)
12866 mips_gp_register = tc_get_register (0);
12867 demand_empty_rest_of_line ();
12870 /* Handle the .cprestore pseudo-op. This stores $gp into a given
12871 offset from $sp. The offset is remembered, and after making a PIC
12872 call $gp is restored from that location. */
12875 s_cprestore (ignore)
12876 int ignore ATTRIBUTE_UNUSED;
12881 /* If we are not generating SVR4 PIC code, or if this is NewABI code,
12882 .cprestore is ignored. */
12883 if (mips_pic != SVR4_PIC || HAVE_NEWABI)
12889 mips_cprestore_offset = get_absolute_expression ();
12890 mips_cprestore_valid = 1;
12892 ex.X_op = O_constant;
12893 ex.X_add_symbol = NULL;
12894 ex.X_op_symbol = NULL;
12895 ex.X_add_number = mips_cprestore_offset;
12897 macro_build_ldst_constoffset ((char *) NULL, &icnt, &ex,
12898 HAVE_32BIT_ADDRESSES ? "sw" : "sd",
12899 mips_gp_register, SP);
12901 demand_empty_rest_of_line ();
12904 /* Handle the .cpreturn pseudo-op defined for NewABI PIC code. If an offset
12905 was given in the preceeding .gpsetup, it results in:
12906 ld $gp, offset($sp)
12908 If a register $reg2 was given there, it results in:
12909 daddiu $gp, $gp, $reg2
12912 s_cpreturn (ignore)
12913 int ignore ATTRIBUTE_UNUSED;
12918 /* If we are not generating SVR4 PIC code, .cpreturn is ignored.
12919 We also need NewABI support. */
12920 if (mips_pic != SVR4_PIC || ! HAVE_NEWABI)
12926 if (mips_cpreturn_register == -1)
12928 ex.X_op = O_constant;
12929 ex.X_add_symbol = NULL;
12930 ex.X_op_symbol = NULL;
12931 ex.X_add_number = mips_cpreturn_offset;
12933 macro_build ((char *) NULL, &icnt, &ex, "ld", "t,o(b)",
12934 mips_gp_register, (int) BFD_RELOC_LO16, SP);
12937 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "daddu",
12938 "d,v,t", mips_gp_register, mips_cpreturn_register, 0);
12940 demand_empty_rest_of_line ();
12943 /* Handle the .gpvalue pseudo-op. This is used when generating NewABI PIC
12944 code. It sets the offset to use in gp_rel relocations. */
12948 int ignore ATTRIBUTE_UNUSED;
12950 /* If we are not generating SVR4 PIC code, .gpvalue is ignored.
12951 We also need NewABI support. */
12952 if (mips_pic != SVR4_PIC || ! HAVE_NEWABI)
12958 mips_gprel_offset = get_absolute_expression ();
12960 demand_empty_rest_of_line ();
12963 /* Handle the .gpword pseudo-op. This is used when generating PIC
12964 code. It generates a 32 bit GP relative reloc. */
12968 int ignore ATTRIBUTE_UNUSED;
12974 /* When not generating PIC code, this is treated as .word. */
12975 if (mips_pic != SVR4_PIC)
12981 label = insn_labels != NULL ? insn_labels->label : NULL;
12982 mips_emit_delays (TRUE);
12984 mips_align (2, 0, label);
12985 mips_clear_insn_labels ();
12989 if (ex.X_op != O_symbol || ex.X_add_number != 0)
12991 as_bad (_("Unsupported use of .gpword"));
12992 ignore_rest_of_line ();
12996 md_number_to_chars (p, (valueT) 0, 4);
12997 fix_new_exp (frag_now, p - frag_now->fr_literal, 4, &ex, FALSE,
12998 BFD_RELOC_GPREL32);
13000 demand_empty_rest_of_line ();
13005 int ignore ATTRIBUTE_UNUSED;
13011 /* When not generating PIC code, this is treated as .dword. */
13012 if (mips_pic != SVR4_PIC)
13018 label = insn_labels != NULL ? insn_labels->label : NULL;
13019 mips_emit_delays (TRUE);
13021 mips_align (3, 0, label);
13022 mips_clear_insn_labels ();
13026 if (ex.X_op != O_symbol || ex.X_add_number != 0)
13028 as_bad (_("Unsupported use of .gpdword"));
13029 ignore_rest_of_line ();
13033 md_number_to_chars (p, (valueT) 0, 8);
13034 fix_new_exp (frag_now, p - frag_now->fr_literal, 4, &ex, FALSE,
13035 BFD_RELOC_GPREL32);
13037 /* GPREL32 composed with 64 gives a 64-bit GP offset. */
13038 ex.X_op = O_absent;
13039 ex.X_add_symbol = 0;
13040 ex.X_add_number = 0;
13041 fix_new_exp (frag_now, p - frag_now->fr_literal, 8, &ex, FALSE,
13044 demand_empty_rest_of_line ();
13047 /* Handle the .cpadd pseudo-op. This is used when dealing with switch
13048 tables in SVR4 PIC code. */
13052 int ignore ATTRIBUTE_UNUSED;
13057 /* This is ignored when not generating SVR4 PIC code. */
13058 if (mips_pic != SVR4_PIC)
13064 /* Add $gp to the register named as an argument. */
13065 reg = tc_get_register (0);
13066 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
13067 HAVE_32BIT_ADDRESSES ? HAVE_NEWABI ? "add" : "addu" : "daddu",
13068 "d,v,t", reg, reg, mips_gp_register);
13070 demand_empty_rest_of_line ();
13073 /* Handle the .insn pseudo-op. This marks instruction labels in
13074 mips16 mode. This permits the linker to handle them specially,
13075 such as generating jalx instructions when needed. We also make
13076 them odd for the duration of the assembly, in order to generate the
13077 right sort of code. We will make them even in the adjust_symtab
13078 routine, while leaving them marked. This is convenient for the
13079 debugger and the disassembler. The linker knows to make them odd
13084 int ignore ATTRIBUTE_UNUSED;
13086 mips16_mark_labels ();
13088 demand_empty_rest_of_line ();
13091 /* Handle a .stabn directive. We need these in order to mark a label
13092 as being a mips16 text label correctly. Sometimes the compiler
13093 will emit a label, followed by a .stabn, and then switch sections.
13094 If the label and .stabn are in mips16 mode, then the label is
13095 really a mips16 text label. */
13102 mips16_mark_labels ();
13107 /* Handle the .weakext pseudo-op as defined in Kane and Heinrich.
13111 s_mips_weakext (ignore)
13112 int ignore ATTRIBUTE_UNUSED;
13119 name = input_line_pointer;
13120 c = get_symbol_end ();
13121 symbolP = symbol_find_or_make (name);
13122 S_SET_WEAK (symbolP);
13123 *input_line_pointer = c;
13125 SKIP_WHITESPACE ();
13127 if (! is_end_of_line[(unsigned char) *input_line_pointer])
13129 if (S_IS_DEFINED (symbolP))
13131 as_bad ("ignoring attempt to redefine symbol %s",
13132 S_GET_NAME (symbolP));
13133 ignore_rest_of_line ();
13137 if (*input_line_pointer == ',')
13139 ++input_line_pointer;
13140 SKIP_WHITESPACE ();
13144 if (exp.X_op != O_symbol)
13146 as_bad ("bad .weakext directive");
13147 ignore_rest_of_line ();
13150 symbol_set_value_expression (symbolP, &exp);
13153 demand_empty_rest_of_line ();
13156 /* Parse a register string into a number. Called from the ECOFF code
13157 to parse .frame. The argument is non-zero if this is the frame
13158 register, so that we can record it in mips_frame_reg. */
13161 tc_get_register (frame)
13166 SKIP_WHITESPACE ();
13167 if (*input_line_pointer++ != '$')
13169 as_warn (_("expected `$'"));
13172 else if (ISDIGIT (*input_line_pointer))
13174 reg = get_absolute_expression ();
13175 if (reg < 0 || reg >= 32)
13177 as_warn (_("Bad register number"));
13183 if (strncmp (input_line_pointer, "ra", 2) == 0)
13186 input_line_pointer += 2;
13188 else if (strncmp (input_line_pointer, "fp", 2) == 0)
13191 input_line_pointer += 2;
13193 else if (strncmp (input_line_pointer, "sp", 2) == 0)
13196 input_line_pointer += 2;
13198 else if (strncmp (input_line_pointer, "gp", 2) == 0)
13201 input_line_pointer += 2;
13203 else if (strncmp (input_line_pointer, "at", 2) == 0)
13206 input_line_pointer += 2;
13208 else if (strncmp (input_line_pointer, "kt0", 3) == 0)
13211 input_line_pointer += 3;
13213 else if (strncmp (input_line_pointer, "kt1", 3) == 0)
13216 input_line_pointer += 3;
13218 else if (strncmp (input_line_pointer, "zero", 4) == 0)
13221 input_line_pointer += 4;
13225 as_warn (_("Unrecognized register name"));
13227 while (ISALNUM(*input_line_pointer))
13228 input_line_pointer++;
13233 mips_frame_reg = reg != 0 ? reg : SP;
13234 mips_frame_reg_valid = 1;
13235 mips_cprestore_valid = 0;
13241 md_section_align (seg, addr)
13245 int align = bfd_get_section_alignment (stdoutput, seg);
13248 /* We don't need to align ELF sections to the full alignment.
13249 However, Irix 5 may prefer that we align them at least to a 16
13250 byte boundary. We don't bother to align the sections if we are
13251 targeted for an embedded system. */
13252 if (strcmp (TARGET_OS, "elf") == 0)
13258 return ((addr + (1 << align) - 1) & (-1 << align));
13261 /* Utility routine, called from above as well. If called while the
13262 input file is still being read, it's only an approximation. (For
13263 example, a symbol may later become defined which appeared to be
13264 undefined earlier.) */
13267 nopic_need_relax (sym, before_relaxing)
13269 int before_relaxing;
13274 if (USE_GLOBAL_POINTER_OPT && g_switch_value > 0)
13276 const char *symname;
13279 /* Find out whether this symbol can be referenced off the $gp
13280 register. It can be if it is smaller than the -G size or if
13281 it is in the .sdata or .sbss section. Certain symbols can
13282 not be referenced off the $gp, although it appears as though
13284 symname = S_GET_NAME (sym);
13285 if (symname != (const char *) NULL
13286 && (strcmp (symname, "eprol") == 0
13287 || strcmp (symname, "etext") == 0
13288 || strcmp (symname, "_gp") == 0
13289 || strcmp (symname, "edata") == 0
13290 || strcmp (symname, "_fbss") == 0
13291 || strcmp (symname, "_fdata") == 0
13292 || strcmp (symname, "_ftext") == 0
13293 || strcmp (symname, "end") == 0
13294 || strcmp (symname, "_gp_disp") == 0))
13296 else if ((! S_IS_DEFINED (sym) || S_IS_COMMON (sym))
13298 #ifndef NO_ECOFF_DEBUGGING
13299 || (symbol_get_obj (sym)->ecoff_extern_size != 0
13300 && (symbol_get_obj (sym)->ecoff_extern_size
13301 <= g_switch_value))
13303 /* We must defer this decision until after the whole
13304 file has been read, since there might be a .extern
13305 after the first use of this symbol. */
13306 || (before_relaxing
13307 #ifndef NO_ECOFF_DEBUGGING
13308 && symbol_get_obj (sym)->ecoff_extern_size == 0
13310 && S_GET_VALUE (sym) == 0)
13311 || (S_GET_VALUE (sym) != 0
13312 && S_GET_VALUE (sym) <= g_switch_value)))
13316 const char *segname;
13318 segname = segment_name (S_GET_SEGMENT (sym));
13319 assert (strcmp (segname, ".lit8") != 0
13320 && strcmp (segname, ".lit4") != 0);
13321 change = (strcmp (segname, ".sdata") != 0
13322 && strcmp (segname, ".sbss") != 0
13323 && strncmp (segname, ".sdata.", 7) != 0
13324 && strncmp (segname, ".gnu.linkonce.s.", 16) != 0);
13329 /* We are not optimizing for the $gp register. */
13334 /* Return true if the given symbol should be considered local for SVR4 PIC. */
13337 pic_need_relax (sym, segtype)
13342 bfd_boolean linkonce;
13344 /* Handle the case of a symbol equated to another symbol. */
13345 while (symbol_equated_reloc_p (sym))
13349 /* It's possible to get a loop here in a badly written
13351 n = symbol_get_value_expression (sym)->X_add_symbol;
13357 symsec = S_GET_SEGMENT (sym);
13359 /* duplicate the test for LINK_ONCE sections as in adjust_reloc_syms */
13361 if (symsec != segtype && ! S_IS_LOCAL (sym))
13363 if ((bfd_get_section_flags (stdoutput, symsec) & SEC_LINK_ONCE)
13367 /* The GNU toolchain uses an extension for ELF: a section
13368 beginning with the magic string .gnu.linkonce is a linkonce
13370 if (strncmp (segment_name (symsec), ".gnu.linkonce",
13371 sizeof ".gnu.linkonce" - 1) == 0)
13375 /* This must duplicate the test in adjust_reloc_syms. */
13376 return (symsec != &bfd_und_section
13377 && symsec != &bfd_abs_section
13378 && ! bfd_is_com_section (symsec)
13381 /* A global or weak symbol is treated as external. */
13382 && (OUTPUT_FLAVOR != bfd_target_elf_flavour
13383 || (! S_IS_WEAK (sym)
13384 && (! S_IS_EXTERNAL (sym)
13385 || mips_pic == EMBEDDED_PIC)))
13391 /* Given a mips16 variant frag FRAGP, return non-zero if it needs an
13392 extended opcode. SEC is the section the frag is in. */
13395 mips16_extended_frag (fragp, sec, stretch)
13401 register const struct mips16_immed_operand *op;
13403 int mintiny, maxtiny;
13407 if (RELAX_MIPS16_USER_SMALL (fragp->fr_subtype))
13409 if (RELAX_MIPS16_USER_EXT (fragp->fr_subtype))
13412 type = RELAX_MIPS16_TYPE (fragp->fr_subtype);
13413 op = mips16_immed_operands;
13414 while (op->type != type)
13417 assert (op < mips16_immed_operands + MIPS16_NUM_IMMED);
13422 if (type == '<' || type == '>' || type == '[' || type == ']')
13425 maxtiny = 1 << op->nbits;
13430 maxtiny = (1 << op->nbits) - 1;
13435 mintiny = - (1 << (op->nbits - 1));
13436 maxtiny = (1 << (op->nbits - 1)) - 1;
13439 sym_frag = symbol_get_frag (fragp->fr_symbol);
13440 val = S_GET_VALUE (fragp->fr_symbol);
13441 symsec = S_GET_SEGMENT (fragp->fr_symbol);
13447 /* We won't have the section when we are called from
13448 mips_relax_frag. However, we will always have been called
13449 from md_estimate_size_before_relax first. If this is a
13450 branch to a different section, we mark it as such. If SEC is
13451 NULL, and the frag is not marked, then it must be a branch to
13452 the same section. */
13455 if (RELAX_MIPS16_LONG_BRANCH (fragp->fr_subtype))
13460 /* Must have been called from md_estimate_size_before_relax. */
13463 fragp->fr_subtype =
13464 RELAX_MIPS16_MARK_LONG_BRANCH (fragp->fr_subtype);
13466 /* FIXME: We should support this, and let the linker
13467 catch branches and loads that are out of range. */
13468 as_bad_where (fragp->fr_file, fragp->fr_line,
13469 _("unsupported PC relative reference to different section"));
13473 if (fragp != sym_frag && sym_frag->fr_address == 0)
13474 /* Assume non-extended on the first relaxation pass.
13475 The address we have calculated will be bogus if this is
13476 a forward branch to another frag, as the forward frag
13477 will have fr_address == 0. */
13481 /* In this case, we know for sure that the symbol fragment is in
13482 the same section. If the relax_marker of the symbol fragment
13483 differs from the relax_marker of this fragment, we have not
13484 yet adjusted the symbol fragment fr_address. We want to add
13485 in STRETCH in order to get a better estimate of the address.
13486 This particularly matters because of the shift bits. */
13488 && sym_frag->relax_marker != fragp->relax_marker)
13492 /* Adjust stretch for any alignment frag. Note that if have
13493 been expanding the earlier code, the symbol may be
13494 defined in what appears to be an earlier frag. FIXME:
13495 This doesn't handle the fr_subtype field, which specifies
13496 a maximum number of bytes to skip when doing an
13498 for (f = fragp; f != NULL && f != sym_frag; f = f->fr_next)
13500 if (f->fr_type == rs_align || f->fr_type == rs_align_code)
13503 stretch = - ((- stretch)
13504 & ~ ((1 << (int) f->fr_offset) - 1));
13506 stretch &= ~ ((1 << (int) f->fr_offset) - 1);
13515 addr = fragp->fr_address + fragp->fr_fix;
13517 /* The base address rules are complicated. The base address of
13518 a branch is the following instruction. The base address of a
13519 PC relative load or add is the instruction itself, but if it
13520 is in a delay slot (in which case it can not be extended) use
13521 the address of the instruction whose delay slot it is in. */
13522 if (type == 'p' || type == 'q')
13526 /* If we are currently assuming that this frag should be
13527 extended, then, the current address is two bytes
13529 if (RELAX_MIPS16_EXTENDED (fragp->fr_subtype))
13532 /* Ignore the low bit in the target, since it will be set
13533 for a text label. */
13534 if ((val & 1) != 0)
13537 else if (RELAX_MIPS16_JAL_DSLOT (fragp->fr_subtype))
13539 else if (RELAX_MIPS16_DSLOT (fragp->fr_subtype))
13542 val -= addr & ~ ((1 << op->shift) - 1);
13544 /* Branch offsets have an implicit 0 in the lowest bit. */
13545 if (type == 'p' || type == 'q')
13548 /* If any of the shifted bits are set, we must use an extended
13549 opcode. If the address depends on the size of this
13550 instruction, this can lead to a loop, so we arrange to always
13551 use an extended opcode. We only check this when we are in
13552 the main relaxation loop, when SEC is NULL. */
13553 if ((val & ((1 << op->shift) - 1)) != 0 && sec == NULL)
13555 fragp->fr_subtype =
13556 RELAX_MIPS16_MARK_LONG_BRANCH (fragp->fr_subtype);
13560 /* If we are about to mark a frag as extended because the value
13561 is precisely maxtiny + 1, then there is a chance of an
13562 infinite loop as in the following code:
13567 In this case when the la is extended, foo is 0x3fc bytes
13568 away, so the la can be shrunk, but then foo is 0x400 away, so
13569 the la must be extended. To avoid this loop, we mark the
13570 frag as extended if it was small, and is about to become
13571 extended with a value of maxtiny + 1. */
13572 if (val == ((maxtiny + 1) << op->shift)
13573 && ! RELAX_MIPS16_EXTENDED (fragp->fr_subtype)
13576 fragp->fr_subtype =
13577 RELAX_MIPS16_MARK_LONG_BRANCH (fragp->fr_subtype);
13581 else if (symsec != absolute_section && sec != NULL)
13582 as_bad_where (fragp->fr_file, fragp->fr_line, _("unsupported relocation"));
13584 if ((val & ((1 << op->shift) - 1)) != 0
13585 || val < (mintiny << op->shift)
13586 || val > (maxtiny << op->shift))
13592 /* Compute the length of a branch sequence, and adjust the
13593 RELAX_BRANCH_TOOFAR bit accordingly. If FRAGP is NULL, the
13594 worst-case length is computed, with UPDATE being used to indicate
13595 whether an unconditional (-1), branch-likely (+1) or regular (0)
13596 branch is to be computed. */
13598 relaxed_branch_length (fragp, sec, update)
13603 bfd_boolean toofar;
13607 && S_IS_DEFINED (fragp->fr_symbol)
13608 && sec == S_GET_SEGMENT (fragp->fr_symbol))
13613 val = S_GET_VALUE (fragp->fr_symbol) + fragp->fr_offset;
13615 addr = fragp->fr_address + fragp->fr_fix + 4;
13619 toofar = val < - (0x8000 << 2) || val >= (0x8000 << 2);
13622 /* If the symbol is not defined or it's in a different segment,
13623 assume the user knows what's going on and emit a short
13629 if (fragp && update && toofar != RELAX_BRANCH_TOOFAR (fragp->fr_subtype))
13631 = RELAX_BRANCH_ENCODE (RELAX_BRANCH_UNCOND (fragp->fr_subtype),
13632 RELAX_BRANCH_LIKELY (fragp->fr_subtype),
13633 RELAX_BRANCH_LINK (fragp->fr_subtype),
13639 if (fragp ? RELAX_BRANCH_LIKELY (fragp->fr_subtype) : (update > 0))
13642 if (mips_pic != NO_PIC)
13644 /* Additional space for PIC loading of target address. */
13646 if (mips_opts.isa == ISA_MIPS1)
13647 /* Additional space for $at-stabilizing nop. */
13651 /* If branch is conditional. */
13652 if (fragp ? !RELAX_BRANCH_UNCOND (fragp->fr_subtype) : (update >= 0))
13659 /* Estimate the size of a frag before relaxing. Unless this is the
13660 mips16, we are not really relaxing here, and the final size is
13661 encoded in the subtype information. For the mips16, we have to
13662 decide whether we are using an extended opcode or not. */
13665 md_estimate_size_before_relax (fragp, segtype)
13671 if (RELAX_BRANCH_P (fragp->fr_subtype))
13674 fragp->fr_var = relaxed_branch_length (fragp, segtype, FALSE);
13676 return fragp->fr_var;
13679 if (RELAX_MIPS16_P (fragp->fr_subtype))
13680 /* We don't want to modify the EXTENDED bit here; it might get us
13681 into infinite loops. We change it only in mips_relax_frag(). */
13682 return (RELAX_MIPS16_EXTENDED (fragp->fr_subtype) ? 4 : 2);
13684 if (mips_pic == NO_PIC)
13685 change = nopic_need_relax (fragp->fr_symbol, 0);
13686 else if (mips_pic == SVR4_PIC)
13687 change = pic_need_relax (fragp->fr_symbol, segtype);
13693 /* Record the offset to the first reloc in the fr_opcode field.
13694 This lets md_convert_frag and tc_gen_reloc know that the code
13695 must be expanded. */
13696 fragp->fr_opcode = (fragp->fr_literal
13698 - RELAX_OLD (fragp->fr_subtype)
13699 + RELAX_RELOC1 (fragp->fr_subtype));
13700 /* FIXME: This really needs as_warn_where. */
13701 if (RELAX_WARN (fragp->fr_subtype))
13702 as_warn (_("AT used after \".set noat\" or macro used after "
13703 "\".set nomacro\""));
13705 return RELAX_NEW (fragp->fr_subtype) - RELAX_OLD (fragp->fr_subtype);
13711 /* This is called to see whether a reloc against a defined symbol
13712 should be converted into a reloc against a section. Don't adjust
13713 MIPS16 jump relocations, so we don't have to worry about the format
13714 of the offset in the .o file. Don't adjust relocations against
13715 mips16 symbols, so that the linker can find them if it needs to set
13719 mips_fix_adjustable (fixp)
13722 if (fixp->fx_r_type == BFD_RELOC_MIPS16_JMP)
13725 if (fixp->fx_r_type == BFD_RELOC_VTABLE_INHERIT
13726 || fixp->fx_r_type == BFD_RELOC_VTABLE_ENTRY)
13729 if (fixp->fx_addsy == NULL)
13733 if (OUTPUT_FLAVOR == bfd_target_elf_flavour
13734 && S_GET_OTHER (fixp->fx_addsy) == STO_MIPS16
13735 && fixp->fx_subsy == NULL)
13742 /* Translate internal representation of relocation info to BFD target
13746 tc_gen_reloc (section, fixp)
13747 asection *section ATTRIBUTE_UNUSED;
13750 static arelent *retval[4];
13752 bfd_reloc_code_real_type code;
13754 reloc = retval[0] = (arelent *) xmalloc (sizeof (arelent));
13757 reloc->sym_ptr_ptr = (asymbol **) xmalloc (sizeof (asymbol *));
13758 *reloc->sym_ptr_ptr = symbol_get_bfdsym (fixp->fx_addsy);
13759 reloc->address = fixp->fx_frag->fr_address + fixp->fx_where;
13761 if (mips_pic == EMBEDDED_PIC
13762 && SWITCH_TABLE (fixp))
13764 /* For a switch table entry we use a special reloc. The addend
13765 is actually the difference between the reloc address and the
13767 reloc->addend = reloc->address - S_GET_VALUE (fixp->fx_subsy);
13768 if (OUTPUT_FLAVOR != bfd_target_ecoff_flavour)
13769 as_fatal (_("Double check fx_r_type in tc-mips.c:tc_gen_reloc"));
13770 fixp->fx_r_type = BFD_RELOC_GPREL32;
13772 else if (fixp->fx_r_type == BFD_RELOC_PCREL_LO16)
13774 if (OUTPUT_FLAVOR == bfd_target_elf_flavour)
13775 reloc->addend = fixp->fx_addnumber;
13778 /* We use a special addend for an internal RELLO reloc. */
13779 if (symbol_section_p (fixp->fx_addsy))
13780 reloc->addend = reloc->address - S_GET_VALUE (fixp->fx_subsy);
13782 reloc->addend = fixp->fx_addnumber + reloc->address;
13785 else if (fixp->fx_r_type == BFD_RELOC_PCREL_HI16_S)
13787 assert (fixp->fx_next != NULL
13788 && fixp->fx_next->fx_r_type == BFD_RELOC_PCREL_LO16);
13790 /* The reloc is relative to the RELLO; adjust the addend
13792 if (OUTPUT_FLAVOR == bfd_target_elf_flavour)
13793 reloc->addend = fixp->fx_next->fx_addnumber;
13796 /* We use a special addend for an internal RELHI reloc. */
13797 if (symbol_section_p (fixp->fx_addsy))
13798 reloc->addend = (fixp->fx_next->fx_frag->fr_address
13799 + fixp->fx_next->fx_where
13800 - S_GET_VALUE (fixp->fx_subsy));
13802 reloc->addend = (fixp->fx_addnumber
13803 + fixp->fx_next->fx_frag->fr_address
13804 + fixp->fx_next->fx_where);
13807 else if (fixp->fx_pcrel == 0 || OUTPUT_FLAVOR == bfd_target_elf_flavour)
13808 reloc->addend = fixp->fx_addnumber;
13811 if (OUTPUT_FLAVOR != bfd_target_aout_flavour)
13812 /* A gruesome hack which is a result of the gruesome gas reloc
13814 reloc->addend = reloc->address;
13816 reloc->addend = -reloc->address;
13819 /* If this is a variant frag, we may need to adjust the existing
13820 reloc and generate a new one. */
13821 if (fixp->fx_frag->fr_opcode != NULL
13822 && ((fixp->fx_r_type == BFD_RELOC_GPREL16
13824 || (fixp->fx_r_type == BFD_RELOC_MIPS_GOT_DISP
13826 || fixp->fx_r_type == BFD_RELOC_MIPS_GOT16
13827 || fixp->fx_r_type == BFD_RELOC_MIPS_CALL16
13828 || fixp->fx_r_type == BFD_RELOC_MIPS_GOT_HI16
13829 || fixp->fx_r_type == BFD_RELOC_MIPS_GOT_LO16
13830 || fixp->fx_r_type == BFD_RELOC_MIPS_CALL_HI16
13831 || fixp->fx_r_type == BFD_RELOC_MIPS_CALL_LO16)
13836 assert (! RELAX_MIPS16_P (fixp->fx_frag->fr_subtype));
13838 /* If this is not the last reloc in this frag, then we have two
13839 GPREL relocs, or a GOT_HI16/GOT_LO16 pair, or a
13840 CALL_HI16/CALL_LO16, both of which are being replaced. Let
13841 the second one handle all of them. */
13842 if (fixp->fx_next != NULL
13843 && fixp->fx_frag == fixp->fx_next->fx_frag)
13845 assert ((fixp->fx_r_type == BFD_RELOC_GPREL16
13846 && fixp->fx_next->fx_r_type == BFD_RELOC_GPREL16)
13847 || (fixp->fx_r_type == BFD_RELOC_MIPS_GOT_HI16
13848 && (fixp->fx_next->fx_r_type
13849 == BFD_RELOC_MIPS_GOT_LO16))
13850 || (fixp->fx_r_type == BFD_RELOC_MIPS_CALL_HI16
13851 && (fixp->fx_next->fx_r_type
13852 == BFD_RELOC_MIPS_CALL_LO16)));
13857 fixp->fx_where = fixp->fx_frag->fr_opcode - fixp->fx_frag->fr_literal;
13858 reloc->address = fixp->fx_frag->fr_address + fixp->fx_where;
13859 reloc->addend += fixp->fx_frag->tc_frag_data.tc_fr_offset;
13860 reloc2 = retval[1] = (arelent *) xmalloc (sizeof (arelent));
13862 reloc2->sym_ptr_ptr = (asymbol **) xmalloc (sizeof (asymbol *));
13863 *reloc2->sym_ptr_ptr = symbol_get_bfdsym (fixp->fx_addsy);
13864 reloc2->address = (reloc->address
13865 + (RELAX_RELOC2 (fixp->fx_frag->fr_subtype)
13866 - RELAX_RELOC1 (fixp->fx_frag->fr_subtype)));
13867 reloc2->addend = fixp->fx_addnumber
13868 + fixp->fx_frag->tc_frag_data.tc_fr_offset;
13869 reloc2->howto = bfd_reloc_type_lookup (stdoutput, BFD_RELOC_LO16);
13870 assert (reloc2->howto != NULL);
13872 if (RELAX_RELOC3 (fixp->fx_frag->fr_subtype))
13876 reloc3 = retval[2] = (arelent *) xmalloc (sizeof (arelent));
13879 reloc3->address += 4;
13882 if (mips_pic == NO_PIC)
13884 assert (fixp->fx_r_type == BFD_RELOC_GPREL16);
13885 fixp->fx_r_type = BFD_RELOC_HI16_S;
13887 else if (mips_pic == SVR4_PIC)
13889 switch (fixp->fx_r_type)
13893 case BFD_RELOC_MIPS_GOT16:
13895 case BFD_RELOC_MIPS_GOT_LO16:
13896 case BFD_RELOC_MIPS_CALL_LO16:
13899 fixp->fx_r_type = BFD_RELOC_MIPS_GOT_PAGE;
13900 reloc2->howto = bfd_reloc_type_lookup
13901 (stdoutput, BFD_RELOC_MIPS_GOT_OFST);
13904 fixp->fx_r_type = BFD_RELOC_MIPS_GOT16;
13906 case BFD_RELOC_MIPS_CALL16:
13907 case BFD_RELOC_MIPS_GOT_OFST:
13908 case BFD_RELOC_MIPS_GOT_DISP:
13911 /* It may seem nonsensical to relax GOT_DISP to
13912 GOT_DISP, but we're actually turning a GOT_DISP
13913 without offset into a GOT_DISP with an offset,
13914 getting rid of the separate addition, which we can
13915 do when the symbol is found to be local. */
13916 fixp->fx_r_type = BFD_RELOC_MIPS_GOT_DISP;
13920 fixp->fx_r_type = BFD_RELOC_MIPS_GOT16;
13928 /* Since the old MIPS ELF ABI uses Rel instead of Rela, encode the vtable
13929 entry to be used in the relocation's section offset. */
13930 if (! HAVE_NEWABI && fixp->fx_r_type == BFD_RELOC_VTABLE_ENTRY)
13932 reloc->address = reloc->addend;
13936 /* Since DIFF_EXPR_OK is defined in tc-mips.h, it is possible that
13937 fixup_segment converted a non-PC relative reloc into a PC
13938 relative reloc. In such a case, we need to convert the reloc
13940 code = fixp->fx_r_type;
13941 if (fixp->fx_pcrel)
13946 code = BFD_RELOC_8_PCREL;
13949 code = BFD_RELOC_16_PCREL;
13952 code = BFD_RELOC_32_PCREL;
13955 code = BFD_RELOC_64_PCREL;
13957 case BFD_RELOC_8_PCREL:
13958 case BFD_RELOC_16_PCREL:
13959 case BFD_RELOC_32_PCREL:
13960 case BFD_RELOC_64_PCREL:
13961 case BFD_RELOC_16_PCREL_S2:
13962 case BFD_RELOC_PCREL_HI16_S:
13963 case BFD_RELOC_PCREL_LO16:
13966 as_bad_where (fixp->fx_file, fixp->fx_line,
13967 _("Cannot make %s relocation PC relative"),
13968 bfd_get_reloc_code_name (code));
13973 /* md_apply_fix3 has a double-subtraction hack to get
13974 bfd_install_relocation to behave nicely. GPREL relocations are
13975 handled correctly without this hack, so undo it here. We can't
13976 stop md_apply_fix3 from subtracting twice in the first place since
13977 the fake addend is required for variant frags above. */
13978 if (fixp->fx_addsy != NULL && OUTPUT_FLAVOR == bfd_target_elf_flavour
13979 && (code == BFD_RELOC_GPREL16 || code == BFD_RELOC_MIPS16_GPREL)
13980 && reloc->addend != 0
13981 && mips_need_elf_addend_fixup (fixp))
13983 /* If howto->partial_inplace is false, md_apply_fix3 will only
13984 subtract it once. */
13985 reloc_howto_type *howto;
13987 howto = bfd_reloc_type_lookup (stdoutput, fixp->fx_r_type);
13988 if (howto->partial_inplace)
13989 reloc->addend += S_GET_VALUE (fixp->fx_addsy);
13993 /* To support a PC relative reloc when generating embedded PIC code
13994 for ECOFF, we use a Cygnus extension. We check for that here to
13995 make sure that we don't let such a reloc escape normally. */
13996 if ((OUTPUT_FLAVOR == bfd_target_ecoff_flavour
13997 || OUTPUT_FLAVOR == bfd_target_elf_flavour)
13998 && code == BFD_RELOC_16_PCREL_S2
13999 && mips_pic != EMBEDDED_PIC)
14000 reloc->howto = NULL;
14002 reloc->howto = bfd_reloc_type_lookup (stdoutput, code);
14004 if (reloc->howto == NULL)
14006 as_bad_where (fixp->fx_file, fixp->fx_line,
14007 _("Can not represent %s relocation in this object file format"),
14008 bfd_get_reloc_code_name (code));
14015 /* Relax a machine dependent frag. This returns the amount by which
14016 the current size of the frag should change. */
14019 mips_relax_frag (sec, fragp, stretch)
14024 if (RELAX_BRANCH_P (fragp->fr_subtype))
14026 offsetT old_var = fragp->fr_var;
14028 fragp->fr_var = relaxed_branch_length (fragp, sec, TRUE);
14030 return fragp->fr_var - old_var;
14033 if (! RELAX_MIPS16_P (fragp->fr_subtype))
14036 if (mips16_extended_frag (fragp, NULL, stretch))
14038 if (RELAX_MIPS16_EXTENDED (fragp->fr_subtype))
14040 fragp->fr_subtype = RELAX_MIPS16_MARK_EXTENDED (fragp->fr_subtype);
14045 if (! RELAX_MIPS16_EXTENDED (fragp->fr_subtype))
14047 fragp->fr_subtype = RELAX_MIPS16_CLEAR_EXTENDED (fragp->fr_subtype);
14054 /* Convert a machine dependent frag. */
14057 md_convert_frag (abfd, asec, fragp)
14058 bfd *abfd ATTRIBUTE_UNUSED;
14065 if (RELAX_BRANCH_P (fragp->fr_subtype))
14068 unsigned long insn;
14072 buf = (bfd_byte *)fragp->fr_literal + fragp->fr_fix;
14074 if (target_big_endian)
14075 insn = bfd_getb32 (buf);
14077 insn = bfd_getl32 (buf);
14079 if (!RELAX_BRANCH_TOOFAR (fragp->fr_subtype))
14081 /* We generate a fixup instead of applying it right now
14082 because, if there are linker relaxations, we're going to
14083 need the relocations. */
14084 exp.X_op = O_symbol;
14085 exp.X_add_symbol = fragp->fr_symbol;
14086 exp.X_add_number = fragp->fr_offset;
14088 fixp = fix_new_exp (fragp, buf - (bfd_byte *)fragp->fr_literal,
14090 BFD_RELOC_16_PCREL_S2);
14091 fixp->fx_file = fragp->fr_file;
14092 fixp->fx_line = fragp->fr_line;
14094 md_number_to_chars ((char *)buf, insn, 4);
14101 as_warn_where (fragp->fr_file, fragp->fr_line,
14102 _("relaxed out-of-range branch into a jump"));
14104 if (RELAX_BRANCH_UNCOND (fragp->fr_subtype))
14107 if (!RELAX_BRANCH_LIKELY (fragp->fr_subtype))
14109 /* Reverse the branch. */
14110 switch ((insn >> 28) & 0xf)
14113 /* bc[0-3][tf]l? and bc1any[24][ft] instructions can
14114 have the condition reversed by tweaking a single
14115 bit, and their opcodes all have 0x4???????. */
14116 assert ((insn & 0xf1000000) == 0x41000000);
14117 insn ^= 0x00010000;
14121 /* bltz 0x04000000 bgez 0x04010000
14122 bltzal 0x04100000 bgezal 0x04110000 */
14123 assert ((insn & 0xfc0e0000) == 0x04000000);
14124 insn ^= 0x00010000;
14128 /* beq 0x10000000 bne 0x14000000
14129 blez 0x18000000 bgtz 0x1c000000 */
14130 insn ^= 0x04000000;
14138 if (RELAX_BRANCH_LINK (fragp->fr_subtype))
14140 /* Clear the and-link bit. */
14141 assert ((insn & 0xfc1c0000) == 0x04100000);
14143 /* bltzal 0x04100000 bgezal 0x04110000
14144 bltzall 0x04120000 bgezall 0x04130000 */
14145 insn &= ~0x00100000;
14148 /* Branch over the branch (if the branch was likely) or the
14149 full jump (not likely case). Compute the offset from the
14150 current instruction to branch to. */
14151 if (RELAX_BRANCH_LIKELY (fragp->fr_subtype))
14155 /* How many bytes in instructions we've already emitted? */
14156 i = buf - (bfd_byte *)fragp->fr_literal - fragp->fr_fix;
14157 /* How many bytes in instructions from here to the end? */
14158 i = fragp->fr_var - i;
14160 /* Convert to instruction count. */
14162 /* Branch counts from the next instruction. */
14165 /* Branch over the jump. */
14166 md_number_to_chars ((char *)buf, insn, 4);
14170 md_number_to_chars ((char*)buf, 0, 4);
14173 if (RELAX_BRANCH_LIKELY (fragp->fr_subtype))
14175 /* beql $0, $0, 2f */
14177 /* Compute the PC offset from the current instruction to
14178 the end of the variable frag. */
14179 /* How many bytes in instructions we've already emitted? */
14180 i = buf - (bfd_byte *)fragp->fr_literal - fragp->fr_fix;
14181 /* How many bytes in instructions from here to the end? */
14182 i = fragp->fr_var - i;
14183 /* Convert to instruction count. */
14185 /* Don't decrement i, because we want to branch over the
14189 md_number_to_chars ((char *)buf, insn, 4);
14192 md_number_to_chars ((char *)buf, 0, 4);
14197 if (mips_pic == NO_PIC)
14200 insn = (RELAX_BRANCH_LINK (fragp->fr_subtype)
14201 ? 0x0c000000 : 0x08000000);
14202 exp.X_op = O_symbol;
14203 exp.X_add_symbol = fragp->fr_symbol;
14204 exp.X_add_number = fragp->fr_offset;
14206 fixp = fix_new_exp (fragp, buf - (bfd_byte *)fragp->fr_literal,
14207 4, &exp, 0, BFD_RELOC_MIPS_JMP);
14208 fixp->fx_file = fragp->fr_file;
14209 fixp->fx_line = fragp->fr_line;
14211 md_number_to_chars ((char*)buf, insn, 4);
14216 /* lw/ld $at, <sym>($gp) R_MIPS_GOT16 */
14217 insn = HAVE_64BIT_ADDRESSES ? 0xdf810000 : 0x8f810000;
14218 exp.X_op = O_symbol;
14219 exp.X_add_symbol = fragp->fr_symbol;
14220 exp.X_add_number = fragp->fr_offset;
14222 if (fragp->fr_offset)
14224 exp.X_add_symbol = make_expr_symbol (&exp);
14225 exp.X_add_number = 0;
14228 fixp = fix_new_exp (fragp, buf - (bfd_byte *)fragp->fr_literal,
14229 4, &exp, 0, BFD_RELOC_MIPS_GOT16);
14230 fixp->fx_file = fragp->fr_file;
14231 fixp->fx_line = fragp->fr_line;
14233 md_number_to_chars ((char*)buf, insn, 4);
14236 if (mips_opts.isa == ISA_MIPS1)
14239 md_number_to_chars ((char*)buf, 0, 4);
14243 /* d/addiu $at, $at, <sym> R_MIPS_LO16 */
14244 insn = HAVE_64BIT_ADDRESSES ? 0x64210000 : 0x24210000;
14246 fixp = fix_new_exp (fragp, buf - (bfd_byte *)fragp->fr_literal,
14247 4, &exp, 0, BFD_RELOC_LO16);
14248 fixp->fx_file = fragp->fr_file;
14249 fixp->fx_line = fragp->fr_line;
14251 md_number_to_chars ((char*)buf, insn, 4);
14255 if (RELAX_BRANCH_LINK (fragp->fr_subtype))
14260 md_number_to_chars ((char*)buf, insn, 4);
14265 assert (buf == (bfd_byte *)fragp->fr_literal
14266 + fragp->fr_fix + fragp->fr_var);
14268 fragp->fr_fix += fragp->fr_var;
14273 if (RELAX_MIPS16_P (fragp->fr_subtype))
14276 register const struct mips16_immed_operand *op;
14277 bfd_boolean small, ext;
14280 unsigned long insn;
14281 bfd_boolean use_extend;
14282 unsigned short extend;
14284 type = RELAX_MIPS16_TYPE (fragp->fr_subtype);
14285 op = mips16_immed_operands;
14286 while (op->type != type)
14289 if (RELAX_MIPS16_EXTENDED (fragp->fr_subtype))
14300 resolve_symbol_value (fragp->fr_symbol);
14301 val = S_GET_VALUE (fragp->fr_symbol);
14306 addr = fragp->fr_address + fragp->fr_fix;
14308 /* The rules for the base address of a PC relative reloc are
14309 complicated; see mips16_extended_frag. */
14310 if (type == 'p' || type == 'q')
14315 /* Ignore the low bit in the target, since it will be
14316 set for a text label. */
14317 if ((val & 1) != 0)
14320 else if (RELAX_MIPS16_JAL_DSLOT (fragp->fr_subtype))
14322 else if (RELAX_MIPS16_DSLOT (fragp->fr_subtype))
14325 addr &= ~ (addressT) ((1 << op->shift) - 1);
14328 /* Make sure the section winds up with the alignment we have
14331 record_alignment (asec, op->shift);
14335 && (RELAX_MIPS16_JAL_DSLOT (fragp->fr_subtype)
14336 || RELAX_MIPS16_DSLOT (fragp->fr_subtype)))
14337 as_warn_where (fragp->fr_file, fragp->fr_line,
14338 _("extended instruction in delay slot"));
14340 buf = (bfd_byte *) (fragp->fr_literal + fragp->fr_fix);
14342 if (target_big_endian)
14343 insn = bfd_getb16 (buf);
14345 insn = bfd_getl16 (buf);
14347 mips16_immed (fragp->fr_file, fragp->fr_line, type, val,
14348 RELAX_MIPS16_USER_EXT (fragp->fr_subtype),
14349 small, ext, &insn, &use_extend, &extend);
14353 md_number_to_chars ((char *) buf, 0xf000 | extend, 2);
14354 fragp->fr_fix += 2;
14358 md_number_to_chars ((char *) buf, insn, 2);
14359 fragp->fr_fix += 2;
14364 if (fragp->fr_opcode == NULL)
14367 old = RELAX_OLD (fragp->fr_subtype);
14368 new = RELAX_NEW (fragp->fr_subtype);
14369 fixptr = fragp->fr_literal + fragp->fr_fix;
14372 memmove (fixptr - old, fixptr, new);
14374 fragp->fr_fix += new - old;
14380 /* This function is called after the relocs have been generated.
14381 We've been storing mips16 text labels as odd. Here we convert them
14382 back to even for the convenience of the debugger. */
14385 mips_frob_file_after_relocs ()
14388 unsigned int count, i;
14390 if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
14393 syms = bfd_get_outsymbols (stdoutput);
14394 count = bfd_get_symcount (stdoutput);
14395 for (i = 0; i < count; i++, syms++)
14397 if (elf_symbol (*syms)->internal_elf_sym.st_other == STO_MIPS16
14398 && ((*syms)->value & 1) != 0)
14400 (*syms)->value &= ~1;
14401 /* If the symbol has an odd size, it was probably computed
14402 incorrectly, so adjust that as well. */
14403 if ((elf_symbol (*syms)->internal_elf_sym.st_size & 1) != 0)
14404 ++elf_symbol (*syms)->internal_elf_sym.st_size;
14411 /* This function is called whenever a label is defined. It is used
14412 when handling branch delays; if a branch has a label, we assume we
14413 can not move it. */
14416 mips_define_label (sym)
14419 struct insn_label_list *l;
14421 if (free_insn_labels == NULL)
14422 l = (struct insn_label_list *) xmalloc (sizeof *l);
14425 l = free_insn_labels;
14426 free_insn_labels = l->next;
14430 l->next = insn_labels;
14434 #if defined (OBJ_ELF) || defined (OBJ_MAYBE_ELF)
14436 /* Some special processing for a MIPS ELF file. */
14439 mips_elf_final_processing ()
14441 /* Write out the register information. */
14442 if (mips_abi != N64_ABI)
14446 s.ri_gprmask = mips_gprmask;
14447 s.ri_cprmask[0] = mips_cprmask[0];
14448 s.ri_cprmask[1] = mips_cprmask[1];
14449 s.ri_cprmask[2] = mips_cprmask[2];
14450 s.ri_cprmask[3] = mips_cprmask[3];
14451 /* The gp_value field is set by the MIPS ELF backend. */
14453 bfd_mips_elf32_swap_reginfo_out (stdoutput, &s,
14454 ((Elf32_External_RegInfo *)
14455 mips_regmask_frag));
14459 Elf64_Internal_RegInfo s;
14461 s.ri_gprmask = mips_gprmask;
14463 s.ri_cprmask[0] = mips_cprmask[0];
14464 s.ri_cprmask[1] = mips_cprmask[1];
14465 s.ri_cprmask[2] = mips_cprmask[2];
14466 s.ri_cprmask[3] = mips_cprmask[3];
14467 /* The gp_value field is set by the MIPS ELF backend. */
14469 bfd_mips_elf64_swap_reginfo_out (stdoutput, &s,
14470 ((Elf64_External_RegInfo *)
14471 mips_regmask_frag));
14474 /* Set the MIPS ELF flag bits. FIXME: There should probably be some
14475 sort of BFD interface for this. */
14476 if (mips_any_noreorder)
14477 elf_elfheader (stdoutput)->e_flags |= EF_MIPS_NOREORDER;
14478 if (mips_pic != NO_PIC)
14480 elf_elfheader (stdoutput)->e_flags |= EF_MIPS_PIC;
14481 elf_elfheader (stdoutput)->e_flags |= EF_MIPS_CPIC;
14484 elf_elfheader (stdoutput)->e_flags |= EF_MIPS_CPIC;
14486 /* Set MIPS ELF flags for ASEs. */
14487 if (file_ase_mips16)
14488 elf_elfheader (stdoutput)->e_flags |= EF_MIPS_ARCH_ASE_M16;
14489 #if 0 /* XXX FIXME */
14490 if (file_ase_mips3d)
14491 elf_elfheader (stdoutput)->e_flags |= ???;
14494 elf_elfheader (stdoutput)->e_flags |= EF_MIPS_ARCH_ASE_MDMX;
14496 /* Set the MIPS ELF ABI flags. */
14497 if (mips_abi == O32_ABI && USE_E_MIPS_ABI_O32)
14498 elf_elfheader (stdoutput)->e_flags |= E_MIPS_ABI_O32;
14499 else if (mips_abi == O64_ABI)
14500 elf_elfheader (stdoutput)->e_flags |= E_MIPS_ABI_O64;
14501 else if (mips_abi == EABI_ABI)
14503 if (!file_mips_gp32)
14504 elf_elfheader (stdoutput)->e_flags |= E_MIPS_ABI_EABI64;
14506 elf_elfheader (stdoutput)->e_flags |= E_MIPS_ABI_EABI32;
14508 else if (mips_abi == N32_ABI)
14509 elf_elfheader (stdoutput)->e_flags |= EF_MIPS_ABI2;
14511 /* Nothing to do for N64_ABI. */
14513 if (mips_32bitmode)
14514 elf_elfheader (stdoutput)->e_flags |= EF_MIPS_32BITMODE;
14517 #endif /* OBJ_ELF || OBJ_MAYBE_ELF */
14519 typedef struct proc {
14521 unsigned long reg_mask;
14522 unsigned long reg_offset;
14523 unsigned long fpreg_mask;
14524 unsigned long fpreg_offset;
14525 unsigned long frame_offset;
14526 unsigned long frame_reg;
14527 unsigned long pc_reg;
14530 static procS cur_proc;
14531 static procS *cur_proc_ptr;
14532 static int numprocs;
14534 /* Fill in an rs_align_code fragment. */
14537 mips_handle_align (fragp)
14540 if (fragp->fr_type != rs_align_code)
14543 if (mips_opts.mips16)
14545 static const unsigned char be_nop[] = { 0x65, 0x00 };
14546 static const unsigned char le_nop[] = { 0x00, 0x65 };
14551 bytes = fragp->fr_next->fr_address - fragp->fr_address - fragp->fr_fix;
14552 p = fragp->fr_literal + fragp->fr_fix;
14560 memcpy (p, (target_big_endian ? be_nop : le_nop), 2);
14564 /* For mips32, a nop is a zero, which we trivially get by doing nothing. */
14575 /* check for premature end, nesting errors, etc */
14577 as_warn (_("missing .end at end of assembly"));
14586 if (*input_line_pointer == '-')
14588 ++input_line_pointer;
14591 if (!ISDIGIT (*input_line_pointer))
14592 as_bad (_("expected simple number"));
14593 if (input_line_pointer[0] == '0')
14595 if (input_line_pointer[1] == 'x')
14597 input_line_pointer += 2;
14598 while (ISXDIGIT (*input_line_pointer))
14601 val |= hex_value (*input_line_pointer++);
14603 return negative ? -val : val;
14607 ++input_line_pointer;
14608 while (ISDIGIT (*input_line_pointer))
14611 val |= *input_line_pointer++ - '0';
14613 return negative ? -val : val;
14616 if (!ISDIGIT (*input_line_pointer))
14618 printf (_(" *input_line_pointer == '%c' 0x%02x\n"),
14619 *input_line_pointer, *input_line_pointer);
14620 as_warn (_("invalid number"));
14623 while (ISDIGIT (*input_line_pointer))
14626 val += *input_line_pointer++ - '0';
14628 return negative ? -val : val;
14631 /* The .file directive; just like the usual .file directive, but there
14632 is an initial number which is the ECOFF file index. In the non-ECOFF
14633 case .file implies DWARF-2. */
14637 int x ATTRIBUTE_UNUSED;
14639 static int first_file_directive = 0;
14641 if (ECOFF_DEBUGGING)
14650 filename = dwarf2_directive_file (0);
14652 /* Versions of GCC up to 3.1 start files with a ".file"
14653 directive even for stabs output. Make sure that this
14654 ".file" is handled. Note that you need a version of GCC
14655 after 3.1 in order to support DWARF-2 on MIPS. */
14656 if (filename != NULL && ! first_file_directive)
14658 (void) new_logical_line (filename, -1);
14659 s_app_file_string (filename);
14661 first_file_directive = 1;
14665 /* The .loc directive, implying DWARF-2. */
14669 int x ATTRIBUTE_UNUSED;
14671 if (!ECOFF_DEBUGGING)
14672 dwarf2_directive_loc (0);
14675 /* The .end directive. */
14679 int x ATTRIBUTE_UNUSED;
14683 /* Following functions need their own .frame and .cprestore directives. */
14684 mips_frame_reg_valid = 0;
14685 mips_cprestore_valid = 0;
14687 if (!is_end_of_line[(unsigned char) *input_line_pointer])
14690 demand_empty_rest_of_line ();
14695 if ((bfd_get_section_flags (stdoutput, now_seg) & SEC_CODE) == 0)
14696 as_warn (_(".end not in text section"));
14700 as_warn (_(".end directive without a preceding .ent directive."));
14701 demand_empty_rest_of_line ();
14707 assert (S_GET_NAME (p));
14708 if (strcmp (S_GET_NAME (p), S_GET_NAME (cur_proc_ptr->isym)))
14709 as_warn (_(".end symbol does not match .ent symbol."));
14711 if (debug_type == DEBUG_STABS)
14712 stabs_generate_asm_endfunc (S_GET_NAME (p),
14716 as_warn (_(".end directive missing or unknown symbol"));
14719 /* Generate a .pdr section. */
14720 if (OUTPUT_FLAVOR == bfd_target_elf_flavour && ! ECOFF_DEBUGGING)
14722 segT saved_seg = now_seg;
14723 subsegT saved_subseg = now_subseg;
14728 dot = frag_now_fix ();
14730 #ifdef md_flush_pending_output
14731 md_flush_pending_output ();
14735 subseg_set (pdr_seg, 0);
14737 /* Write the symbol. */
14738 exp.X_op = O_symbol;
14739 exp.X_add_symbol = p;
14740 exp.X_add_number = 0;
14741 emit_expr (&exp, 4);
14743 fragp = frag_more (7 * 4);
14745 md_number_to_chars (fragp, (valueT) cur_proc_ptr->reg_mask, 4);
14746 md_number_to_chars (fragp + 4, (valueT) cur_proc_ptr->reg_offset, 4);
14747 md_number_to_chars (fragp + 8, (valueT) cur_proc_ptr->fpreg_mask, 4);
14748 md_number_to_chars (fragp + 12, (valueT) cur_proc_ptr->fpreg_offset, 4);
14749 md_number_to_chars (fragp + 16, (valueT) cur_proc_ptr->frame_offset, 4);
14750 md_number_to_chars (fragp + 20, (valueT) cur_proc_ptr->frame_reg, 4);
14751 md_number_to_chars (fragp + 24, (valueT) cur_proc_ptr->pc_reg, 4);
14753 subseg_set (saved_seg, saved_subseg);
14755 #endif /* OBJ_ELF */
14757 cur_proc_ptr = NULL;
14760 /* The .aent and .ent directives. */
14768 symbolP = get_symbol ();
14769 if (*input_line_pointer == ',')
14770 ++input_line_pointer;
14771 SKIP_WHITESPACE ();
14772 if (ISDIGIT (*input_line_pointer)
14773 || *input_line_pointer == '-')
14776 if ((bfd_get_section_flags (stdoutput, now_seg) & SEC_CODE) == 0)
14777 as_warn (_(".ent or .aent not in text section."));
14779 if (!aent && cur_proc_ptr)
14780 as_warn (_("missing .end"));
14784 /* This function needs its own .frame and .cprestore directives. */
14785 mips_frame_reg_valid = 0;
14786 mips_cprestore_valid = 0;
14788 cur_proc_ptr = &cur_proc;
14789 memset (cur_proc_ptr, '\0', sizeof (procS));
14791 cur_proc_ptr->isym = symbolP;
14793 symbol_get_bfdsym (symbolP)->flags |= BSF_FUNCTION;
14797 if (debug_type == DEBUG_STABS)
14798 stabs_generate_asm_func (S_GET_NAME (symbolP),
14799 S_GET_NAME (symbolP));
14802 demand_empty_rest_of_line ();
14805 /* The .frame directive. If the mdebug section is present (IRIX 5 native)
14806 then ecoff.c (ecoff_directive_frame) is used. For embedded targets,
14807 s_mips_frame is used so that we can set the PDR information correctly.
14808 We can't use the ecoff routines because they make reference to the ecoff
14809 symbol table (in the mdebug section). */
14812 s_mips_frame (ignore)
14813 int ignore ATTRIBUTE_UNUSED;
14816 if (OUTPUT_FLAVOR == bfd_target_elf_flavour && ! ECOFF_DEBUGGING)
14820 if (cur_proc_ptr == (procS *) NULL)
14822 as_warn (_(".frame outside of .ent"));
14823 demand_empty_rest_of_line ();
14827 cur_proc_ptr->frame_reg = tc_get_register (1);
14829 SKIP_WHITESPACE ();
14830 if (*input_line_pointer++ != ','
14831 || get_absolute_expression_and_terminator (&val) != ',')
14833 as_warn (_("Bad .frame directive"));
14834 --input_line_pointer;
14835 demand_empty_rest_of_line ();
14839 cur_proc_ptr->frame_offset = val;
14840 cur_proc_ptr->pc_reg = tc_get_register (0);
14842 demand_empty_rest_of_line ();
14845 #endif /* OBJ_ELF */
14849 /* The .fmask and .mask directives. If the mdebug section is present
14850 (IRIX 5 native) then ecoff.c (ecoff_directive_mask) is used. For
14851 embedded targets, s_mips_mask is used so that we can set the PDR
14852 information correctly. We can't use the ecoff routines because they
14853 make reference to the ecoff symbol table (in the mdebug section). */
14856 s_mips_mask (reg_type)
14860 if (OUTPUT_FLAVOR == bfd_target_elf_flavour && ! ECOFF_DEBUGGING)
14864 if (cur_proc_ptr == (procS *) NULL)
14866 as_warn (_(".mask/.fmask outside of .ent"));
14867 demand_empty_rest_of_line ();
14871 if (get_absolute_expression_and_terminator (&mask) != ',')
14873 as_warn (_("Bad .mask/.fmask directive"));
14874 --input_line_pointer;
14875 demand_empty_rest_of_line ();
14879 off = get_absolute_expression ();
14881 if (reg_type == 'F')
14883 cur_proc_ptr->fpreg_mask = mask;
14884 cur_proc_ptr->fpreg_offset = off;
14888 cur_proc_ptr->reg_mask = mask;
14889 cur_proc_ptr->reg_offset = off;
14892 demand_empty_rest_of_line ();
14895 #endif /* OBJ_ELF */
14896 s_ignore (reg_type);
14899 /* The .loc directive. */
14910 assert (now_seg == text_section);
14912 lineno = get_number ();
14913 addroff = frag_now_fix ();
14915 symbolP = symbol_new ("", N_SLINE, addroff, frag_now);
14916 S_SET_TYPE (symbolP, N_SLINE);
14917 S_SET_OTHER (symbolP, 0);
14918 S_SET_DESC (symbolP, lineno);
14919 symbolP->sy_segment = now_seg;
14923 /* A table describing all the processors gas knows about. Names are
14924 matched in the order listed.
14926 To ease comparison, please keep this table in the same order as
14927 gcc's mips_cpu_info_table[]. */
14928 static const struct mips_cpu_info mips_cpu_info_table[] =
14930 /* Entries for generic ISAs */
14931 { "mips1", 1, ISA_MIPS1, CPU_R3000 },
14932 { "mips2", 1, ISA_MIPS2, CPU_R6000 },
14933 { "mips3", 1, ISA_MIPS3, CPU_R4000 },
14934 { "mips4", 1, ISA_MIPS4, CPU_R8000 },
14935 { "mips5", 1, ISA_MIPS5, CPU_MIPS5 },
14936 { "mips32", 1, ISA_MIPS32, CPU_MIPS32 },
14937 { "mips32r2", 1, ISA_MIPS32R2, CPU_MIPS32R2 },
14938 { "mips64", 1, ISA_MIPS64, CPU_MIPS64 },
14941 { "r3000", 0, ISA_MIPS1, CPU_R3000 },
14942 { "r2000", 0, ISA_MIPS1, CPU_R3000 },
14943 { "r3900", 0, ISA_MIPS1, CPU_R3900 },
14946 { "r6000", 0, ISA_MIPS2, CPU_R6000 },
14949 { "r4000", 0, ISA_MIPS3, CPU_R4000 },
14950 { "r4010", 0, ISA_MIPS2, CPU_R4010 },
14951 { "vr4100", 0, ISA_MIPS3, CPU_VR4100 },
14952 { "vr4111", 0, ISA_MIPS3, CPU_R4111 },
14953 { "vr4120", 0, ISA_MIPS3, CPU_VR4120 },
14954 { "vr4130", 0, ISA_MIPS3, CPU_VR4120 },
14955 { "vr4181", 0, ISA_MIPS3, CPU_R4111 },
14956 { "vr4300", 0, ISA_MIPS3, CPU_R4300 },
14957 { "r4400", 0, ISA_MIPS3, CPU_R4400 },
14958 { "r4600", 0, ISA_MIPS3, CPU_R4600 },
14959 { "orion", 0, ISA_MIPS3, CPU_R4600 },
14960 { "r4650", 0, ISA_MIPS3, CPU_R4650 },
14963 { "r8000", 0, ISA_MIPS4, CPU_R8000 },
14964 { "r10000", 0, ISA_MIPS4, CPU_R10000 },
14965 { "r12000", 0, ISA_MIPS4, CPU_R12000 },
14966 { "vr5000", 0, ISA_MIPS4, CPU_R5000 },
14967 { "vr5400", 0, ISA_MIPS4, CPU_VR5400 },
14968 { "vr5500", 0, ISA_MIPS4, CPU_VR5500 },
14969 { "rm5200", 0, ISA_MIPS4, CPU_R5000 },
14970 { "rm5230", 0, ISA_MIPS4, CPU_R5000 },
14971 { "rm5231", 0, ISA_MIPS4, CPU_R5000 },
14972 { "rm5261", 0, ISA_MIPS4, CPU_R5000 },
14973 { "rm5721", 0, ISA_MIPS4, CPU_R5000 },
14974 { "r7000", 0, ISA_MIPS4, CPU_R5000 },
14977 { "4kc", 0, ISA_MIPS32, CPU_MIPS32, },
14978 { "4km", 0, ISA_MIPS32, CPU_MIPS32 },
14979 { "4kp", 0, ISA_MIPS32, CPU_MIPS32 },
14982 { "5kc", 0, ISA_MIPS64, CPU_MIPS64 },
14983 { "20kc", 0, ISA_MIPS64, CPU_MIPS64 },
14985 /* Broadcom SB-1 CPU core */
14986 { "sb1", 0, ISA_MIPS64, CPU_SB1 },
14993 /* Return true if GIVEN is the same as CANONICAL, or if it is CANONICAL
14994 with a final "000" replaced by "k". Ignore case.
14996 Note: this function is shared between GCC and GAS. */
14999 mips_strict_matching_cpu_name_p (canonical, given)
15000 const char *canonical, *given;
15002 while (*given != 0 && TOLOWER (*given) == TOLOWER (*canonical))
15003 given++, canonical++;
15005 return ((*given == 0 && *canonical == 0)
15006 || (strcmp (canonical, "000") == 0 && strcasecmp (given, "k") == 0));
15010 /* Return true if GIVEN matches CANONICAL, where GIVEN is a user-supplied
15011 CPU name. We've traditionally allowed a lot of variation here.
15013 Note: this function is shared between GCC and GAS. */
15016 mips_matching_cpu_name_p (canonical, given)
15017 const char *canonical, *given;
15019 /* First see if the name matches exactly, or with a final "000"
15020 turned into "k". */
15021 if (mips_strict_matching_cpu_name_p (canonical, given))
15024 /* If not, try comparing based on numerical designation alone.
15025 See if GIVEN is an unadorned number, or 'r' followed by a number. */
15026 if (TOLOWER (*given) == 'r')
15028 if (!ISDIGIT (*given))
15031 /* Skip over some well-known prefixes in the canonical name,
15032 hoping to find a number there too. */
15033 if (TOLOWER (canonical[0]) == 'v' && TOLOWER (canonical[1]) == 'r')
15035 else if (TOLOWER (canonical[0]) == 'r' && TOLOWER (canonical[1]) == 'm')
15037 else if (TOLOWER (canonical[0]) == 'r')
15040 return mips_strict_matching_cpu_name_p (canonical, given);
15044 /* Parse an option that takes the name of a processor as its argument.
15045 OPTION is the name of the option and CPU_STRING is the argument.
15046 Return the corresponding processor enumeration if the CPU_STRING is
15047 recognized, otherwise report an error and return null.
15049 A similar function exists in GCC. */
15051 static const struct mips_cpu_info *
15052 mips_parse_cpu (option, cpu_string)
15053 const char *option, *cpu_string;
15055 const struct mips_cpu_info *p;
15057 /* 'from-abi' selects the most compatible architecture for the given
15058 ABI: MIPS I for 32-bit ABIs and MIPS III for 64-bit ABIs. For the
15059 EABIs, we have to decide whether we're using the 32-bit or 64-bit
15060 version. Look first at the -mgp options, if given, otherwise base
15061 the choice on MIPS_DEFAULT_64BIT.
15063 Treat NO_ABI like the EABIs. One reason to do this is that the
15064 plain 'mips' and 'mips64' configs have 'from-abi' as their default
15065 architecture. This code picks MIPS I for 'mips' and MIPS III for
15066 'mips64', just as we did in the days before 'from-abi'. */
15067 if (strcasecmp (cpu_string, "from-abi") == 0)
15069 if (ABI_NEEDS_32BIT_REGS (mips_abi))
15070 return mips_cpu_info_from_isa (ISA_MIPS1);
15072 if (ABI_NEEDS_64BIT_REGS (mips_abi))
15073 return mips_cpu_info_from_isa (ISA_MIPS3);
15075 if (file_mips_gp32 >= 0)
15076 return mips_cpu_info_from_isa (file_mips_gp32 ? ISA_MIPS1 : ISA_MIPS3);
15078 return mips_cpu_info_from_isa (MIPS_DEFAULT_64BIT
15083 /* 'default' has traditionally been a no-op. Probably not very useful. */
15084 if (strcasecmp (cpu_string, "default") == 0)
15087 for (p = mips_cpu_info_table; p->name != 0; p++)
15088 if (mips_matching_cpu_name_p (p->name, cpu_string))
15091 as_bad ("Bad value (%s) for %s", cpu_string, option);
15095 /* Return the canonical processor information for ISA (a member of the
15096 ISA_MIPS* enumeration). */
15098 static const struct mips_cpu_info *
15099 mips_cpu_info_from_isa (isa)
15104 for (i = 0; mips_cpu_info_table[i].name != NULL; i++)
15105 if (mips_cpu_info_table[i].is_isa
15106 && isa == mips_cpu_info_table[i].isa)
15107 return (&mips_cpu_info_table[i]);
15113 show (stream, string, col_p, first_p)
15115 const char *string;
15121 fprintf (stream, "%24s", "");
15126 fprintf (stream, ", ");
15130 if (*col_p + strlen (string) > 72)
15132 fprintf (stream, "\n%24s", "");
15136 fprintf (stream, "%s", string);
15137 *col_p += strlen (string);
15143 md_show_usage (stream)
15149 fprintf (stream, _("\
15151 -membedded-pic generate embedded position independent code\n\
15152 -EB generate big endian output\n\
15153 -EL generate little endian output\n\
15154 -g, -g2 do not remove unneeded NOPs or swap branches\n\
15155 -G NUM allow referencing objects up to NUM bytes\n\
15156 implicitly with the gp register [default 8]\n"));
15157 fprintf (stream, _("\
15158 -mips1 generate MIPS ISA I instructions\n\
15159 -mips2 generate MIPS ISA II instructions\n\
15160 -mips3 generate MIPS ISA III instructions\n\
15161 -mips4 generate MIPS ISA IV instructions\n\
15162 -mips5 generate MIPS ISA V instructions\n\
15163 -mips32 generate MIPS32 ISA instructions\n\
15164 -mips32r2 generate MIPS32 release 2 ISA instructions\n\
15165 -mips64 generate MIPS64 ISA instructions\n\
15166 -march=CPU/-mtune=CPU generate code/schedule for CPU, where CPU is one of:\n"));
15170 for (i = 0; mips_cpu_info_table[i].name != NULL; i++)
15171 show (stream, mips_cpu_info_table[i].name, &column, &first);
15172 show (stream, "from-abi", &column, &first);
15173 fputc ('\n', stream);
15175 fprintf (stream, _("\
15176 -mCPU equivalent to -march=CPU -mtune=CPU. Deprecated.\n\
15177 -no-mCPU don't generate code specific to CPU.\n\
15178 For -mCPU and -no-mCPU, CPU must be one of:\n"));
15182 show (stream, "3900", &column, &first);
15183 show (stream, "4010", &column, &first);
15184 show (stream, "4100", &column, &first);
15185 show (stream, "4650", &column, &first);
15186 fputc ('\n', stream);
15188 fprintf (stream, _("\
15189 -mips16 generate mips16 instructions\n\
15190 -no-mips16 do not generate mips16 instructions\n"));
15191 fprintf (stream, _("\
15192 -mgp32 use 32-bit GPRs, regardless of the chosen ISA\n\
15193 -mfp32 use 32-bit FPRs, regardless of the chosen ISA\n\
15194 -O0 remove unneeded NOPs, do not swap branches\n\
15195 -O remove unneeded NOPs and swap branches\n\
15196 -n warn about NOPs generated from macros\n\
15197 --[no-]construct-floats [dis]allow floating point values to be constructed\n\
15198 --trap, --no-break trap exception on div by 0 and mult overflow\n\
15199 --break, --no-trap break exception on div by 0 and mult overflow\n"));
15201 fprintf (stream, _("\
15202 -KPIC, -call_shared generate SVR4 position independent code\n\
15203 -non_shared do not generate position independent code\n\
15204 -xgot assume a 32 bit GOT\n\
15205 -mabi=ABI create ABI conformant object file for:\n"));
15209 show (stream, "32", &column, &first);
15210 show (stream, "o64", &column, &first);
15211 show (stream, "n32", &column, &first);
15212 show (stream, "64", &column, &first);
15213 show (stream, "eabi", &column, &first);
15215 fputc ('\n', stream);
15217 fprintf (stream, _("\
15218 -32 create o32 ABI object file (default)\n\
15219 -n32 create n32 ABI object file\n\
15220 -64 create 64 ABI object file\n"));
15225 mips_dwarf2_format ()
15227 if (mips_abi == N64_ABI)
15230 return dwarf2_format_64bit_irix;
15232 return dwarf2_format_64bit;
15236 return dwarf2_format_32bit;