1 /* tc-mips.c -- assemble code for a MIPS chip.
2 Copyright 1993, 1994, 1995, 1996, 1997, 1998, 1999, 2000, 2001, 2002, 2003
3 Free Software Foundation, Inc.
4 Contributed by the OSF and Ralph Campbell.
5 Written by Keith Knowles and Ralph Campbell, working independently.
6 Modified for ECOFF and R4000 support by Ian Lance Taylor of Cygnus
9 This file is part of GAS.
11 GAS is free software; you can redistribute it and/or modify
12 it under the terms of the GNU General Public License as published by
13 the Free Software Foundation; either version 2, or (at your option)
16 GAS is distributed in the hope that it will be useful,
17 but WITHOUT ANY WARRANTY; without even the implied warranty of
18 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
19 GNU General Public License for more details.
21 You should have received a copy of the GNU General Public License
22 along with GAS; see the file COPYING. If not, write to the Free
23 Software Foundation, 59 Temple Place - Suite 330, Boston, MA
29 #include "safe-ctype.h"
38 #include "opcode/mips.h"
40 #include "dwarf2dbg.h"
43 #define DBG(x) printf x
49 /* Clean up namespace so we can include obj-elf.h too. */
50 static int mips_output_flavor PARAMS ((void));
51 static int mips_output_flavor () { return OUTPUT_FLAVOR; }
52 #undef OBJ_PROCESS_STAB
59 #undef obj_frob_file_after_relocs
60 #undef obj_frob_symbol
62 #undef obj_sec_sym_ok_for_reloc
63 #undef OBJ_COPY_SYMBOL_ATTRIBUTES
66 /* Fix any of them that we actually care about. */
68 #define OUTPUT_FLAVOR mips_output_flavor()
75 #ifndef ECOFF_DEBUGGING
76 #define NO_ECOFF_DEBUGGING
77 #define ECOFF_DEBUGGING 0
80 int mips_flag_mdebug = -1;
84 #if defined (OBJ_ELF) || defined (OBJ_MAYBE_ELF)
85 static char *mips_regmask_frag;
91 #define PIC_CALL_REG 25
99 #define ILLEGAL_REG (32)
101 /* Allow override of standard little-endian ECOFF format. */
103 #ifndef ECOFF_LITTLE_FORMAT
104 #define ECOFF_LITTLE_FORMAT "ecoff-littlemips"
107 extern int target_big_endian;
109 /* The name of the readonly data section. */
110 #define RDATA_SECTION_NAME (OUTPUT_FLAVOR == bfd_target_aout_flavour \
112 : OUTPUT_FLAVOR == bfd_target_ecoff_flavour \
114 : OUTPUT_FLAVOR == bfd_target_coff_flavour \
116 : OUTPUT_FLAVOR == bfd_target_elf_flavour \
120 /* The ABI to use. */
131 /* MIPS ABI we are using for this output file. */
132 static enum mips_abi_level mips_abi = NO_ABI;
134 /* This is the set of options which may be modified by the .set
135 pseudo-op. We use a struct so that .set push and .set pop are more
138 struct mips_set_options
140 /* MIPS ISA (Instruction Set Architecture) level. This is set to -1
141 if it has not been initialized. Changed by `.set mipsN', and the
142 -mipsN command line option, and the default CPU. */
144 /* Enabled Application Specific Extensions (ASEs). These are set to -1
145 if they have not been initialized. Changed by `.set <asename>', by
146 command line options, and based on the default architecture. */
149 /* Whether we are assembling for the mips16 processor. 0 if we are
150 not, 1 if we are, and -1 if the value has not been initialized.
151 Changed by `.set mips16' and `.set nomips16', and the -mips16 and
152 -nomips16 command line options, and the default CPU. */
154 /* Non-zero if we should not reorder instructions. Changed by `.set
155 reorder' and `.set noreorder'. */
157 /* Non-zero if we should not permit the $at ($1) register to be used
158 in instructions. Changed by `.set at' and `.set noat'. */
160 /* Non-zero if we should warn when a macro instruction expands into
161 more than one machine instruction. Changed by `.set nomacro' and
163 int warn_about_macros;
164 /* Non-zero if we should not move instructions. Changed by `.set
165 move', `.set volatile', `.set nomove', and `.set novolatile'. */
167 /* Non-zero if we should not optimize branches by moving the target
168 of the branch into the delay slot. Actually, we don't perform
169 this optimization anyhow. Changed by `.set bopt' and `.set
172 /* Non-zero if we should not autoextend mips16 instructions.
173 Changed by `.set autoextend' and `.set noautoextend'. */
175 /* Restrict general purpose registers and floating point registers
176 to 32 bit. This is initially determined when -mgp32 or -mfp32
177 is passed but can changed if the assembler code uses .set mipsN. */
182 /* True if -mgp32 was passed. */
183 static int file_mips_gp32 = -1;
185 /* True if -mfp32 was passed. */
186 static int file_mips_fp32 = -1;
188 /* This is the struct we use to hold the current set of options. Note
189 that we must set the isa field to ISA_UNKNOWN and the ASE fields to
190 -1 to indicate that they have not been initialized. */
192 static struct mips_set_options mips_opts =
194 ISA_UNKNOWN, -1, -1, -1, 0, 0, 0, 0, 0, 0, 0, 0
197 /* These variables are filled in with the masks of registers used.
198 The object format code reads them and puts them in the appropriate
200 unsigned long mips_gprmask;
201 unsigned long mips_cprmask[4];
203 /* MIPS ISA we are using for this output file. */
204 static int file_mips_isa = ISA_UNKNOWN;
206 /* True if -mips16 was passed or implied by arguments passed on the
207 command line (e.g., by -march). */
208 static int file_ase_mips16;
210 /* True if -mips3d was passed or implied by arguments passed on the
211 command line (e.g., by -march). */
212 static int file_ase_mips3d;
214 /* True if -mdmx was passed or implied by arguments passed on the
215 command line (e.g., by -march). */
216 static int file_ase_mdmx;
218 /* The argument of the -march= flag. The architecture we are assembling. */
219 static int mips_arch = CPU_UNKNOWN;
220 static const char *mips_arch_string;
221 static const struct mips_cpu_info *mips_arch_info;
223 /* The argument of the -mtune= flag. The architecture for which we
225 static int mips_tune = CPU_UNKNOWN;
226 static const char *mips_tune_string;
227 static const struct mips_cpu_info *mips_tune_info;
229 /* True when generating 32-bit code for a 64-bit processor. */
230 static int mips_32bitmode = 0;
232 /* Some ISA's have delay slots for instructions which read or write
233 from a coprocessor (eg. mips1-mips3); some don't (eg mips4).
234 Return true if instructions marked INSN_LOAD_COPROC_DELAY,
235 INSN_COPROC_MOVE_DELAY, or INSN_WRITE_COND_CODE actually have a
236 delay slot in this ISA. The uses of this macro assume that any
237 ISA that has delay slots for one of these, has them for all. They
238 also assume that ISAs which don't have delays for these insns, don't
239 have delays for the INSN_LOAD_MEMORY_DELAY instructions either. */
240 #define ISA_HAS_COPROC_DELAYS(ISA) ( \
242 || (ISA) == ISA_MIPS2 \
243 || (ISA) == ISA_MIPS3 \
246 /* True if the given ABI requires 32-bit registers. */
247 #define ABI_NEEDS_32BIT_REGS(ABI) ((ABI) == O32_ABI)
249 /* Likewise 64-bit registers. */
250 #define ABI_NEEDS_64BIT_REGS(ABI) \
252 || (ABI) == N64_ABI \
255 /* Return true if ISA supports 64 bit gp register instructions. */
256 #define ISA_HAS_64BIT_REGS(ISA) ( \
258 || (ISA) == ISA_MIPS4 \
259 || (ISA) == ISA_MIPS5 \
260 || (ISA) == ISA_MIPS64 \
263 /* Return true if ISA supports 64-bit right rotate (dror et al.)
265 #define ISA_HAS_DROR(ISA) ( \
269 /* Return true if ISA supports 32-bit right rotate (ror et al.)
271 #define ISA_HAS_ROR(ISA) ( \
272 (ISA) == ISA_MIPS32R2 \
275 #define HAVE_32BIT_GPRS \
276 (mips_opts.gp32 || ! ISA_HAS_64BIT_REGS (mips_opts.isa))
278 #define HAVE_32BIT_FPRS \
279 (mips_opts.fp32 || ! ISA_HAS_64BIT_REGS (mips_opts.isa))
281 #define HAVE_64BIT_GPRS (! HAVE_32BIT_GPRS)
282 #define HAVE_64BIT_FPRS (! HAVE_32BIT_FPRS)
284 #define HAVE_NEWABI (mips_abi == N32_ABI || mips_abi == N64_ABI)
286 #define HAVE_64BIT_OBJECTS (mips_abi == N64_ABI)
288 /* We can only have 64bit addresses if the object file format
290 #define HAVE_32BIT_ADDRESSES \
292 || ((bfd_arch_bits_per_address (stdoutput) == 32 \
293 || ! HAVE_64BIT_OBJECTS) \
294 && mips_pic != EMBEDDED_PIC))
296 #define HAVE_64BIT_ADDRESSES (! HAVE_32BIT_ADDRESSES)
297 #define HAVE_64BIT_ADDRESS_CONSTANTS (HAVE_64BIT_ADDRESSES \
300 /* Return true if the given CPU supports the MIPS16 ASE. */
301 #define CPU_HAS_MIPS16(cpu) \
302 (strncmp (TARGET_CPU, "mips16", sizeof ("mips16") - 1) == 0 \
303 || strncmp (TARGET_CANONICAL, "mips-lsi-elf", sizeof ("mips-lsi-elf") - 1) == 0)
305 /* Return true if the given CPU supports the MIPS3D ASE. */
306 #define CPU_HAS_MIPS3D(cpu) ((cpu) == CPU_SB1 \
309 /* Return true if the given CPU supports the MDMX ASE. */
310 #define CPU_HAS_MDMX(cpu) (FALSE \
313 /* True if CPU has a dror instruction. */
314 #define CPU_HAS_DROR(CPU) ((CPU) == CPU_VR5400 || (CPU) == CPU_VR5500)
316 /* True if CPU has a ror instruction. */
317 #define CPU_HAS_ROR(CPU) CPU_HAS_DROR (CPU)
319 /* Whether the processor uses hardware interlocks to protect
320 reads from the HI and LO registers, and thus does not
321 require nops to be inserted. */
323 #define hilo_interlocks (mips_arch == CPU_R4010 \
324 || mips_arch == CPU_VR5500 \
325 || mips_arch == CPU_SB1 \
328 /* Whether the processor uses hardware interlocks to protect reads
329 from the GPRs, and thus does not require nops to be inserted. */
330 #define gpr_interlocks \
331 (mips_opts.isa != ISA_MIPS1 \
332 || mips_arch == CPU_VR5400 \
333 || mips_arch == CPU_VR5500 \
334 || mips_arch == CPU_R3900)
336 /* As with other "interlocks" this is used by hardware that has FP
337 (co-processor) interlocks. */
338 /* Itbl support may require additional care here. */
339 #define cop_interlocks (mips_arch == CPU_R4300 \
340 || mips_arch == CPU_VR5400 \
341 || mips_arch == CPU_VR5500 \
342 || mips_arch == CPU_SB1 \
345 /* Is this a mfhi or mflo instruction? */
346 #define MF_HILO_INSN(PINFO) \
347 ((PINFO & INSN_READ_HI) || (PINFO & INSN_READ_LO))
349 /* MIPS PIC level. */
351 enum mips_pic_level mips_pic;
353 /* Warn about all NOPS that the assembler generates. */
354 static int warn_nops = 0;
356 /* 1 if we should generate 32 bit offsets from the $gp register in
357 SVR4_PIC mode. Currently has no meaning in other modes. */
358 static int mips_big_got = 0;
360 /* 1 if trap instructions should used for overflow rather than break
362 static int mips_trap = 0;
364 /* 1 if double width floating point constants should not be constructed
365 by assembling two single width halves into two single width floating
366 point registers which just happen to alias the double width destination
367 register. On some architectures this aliasing can be disabled by a bit
368 in the status register, and the setting of this bit cannot be determined
369 automatically at assemble time. */
370 static int mips_disable_float_construction;
372 /* Non-zero if any .set noreorder directives were used. */
374 static int mips_any_noreorder;
376 /* Non-zero if nops should be inserted when the register referenced in
377 an mfhi/mflo instruction is read in the next two instructions. */
378 static int mips_7000_hilo_fix;
380 /* The size of the small data section. */
381 static unsigned int g_switch_value = 8;
382 /* Whether the -G option was used. */
383 static int g_switch_seen = 0;
388 /* If we can determine in advance that GP optimization won't be
389 possible, we can skip the relaxation stuff that tries to produce
390 GP-relative references. This makes delay slot optimization work
393 This function can only provide a guess, but it seems to work for
394 gcc output. It needs to guess right for gcc, otherwise gcc
395 will put what it thinks is a GP-relative instruction in a branch
398 I don't know if a fix is needed for the SVR4_PIC mode. I've only
399 fixed it for the non-PIC mode. KR 95/04/07 */
400 static int nopic_need_relax PARAMS ((symbolS *, int));
402 /* handle of the OPCODE hash table */
403 static struct hash_control *op_hash = NULL;
405 /* The opcode hash table we use for the mips16. */
406 static struct hash_control *mips16_op_hash = NULL;
408 /* This array holds the chars that always start a comment. If the
409 pre-processor is disabled, these aren't very useful */
410 const char comment_chars[] = "#";
412 /* This array holds the chars that only start a comment at the beginning of
413 a line. If the line seems to have the form '# 123 filename'
414 .line and .file directives will appear in the pre-processed output */
415 /* Note that input_file.c hand checks for '#' at the beginning of the
416 first line of the input file. This is because the compiler outputs
417 #NO_APP at the beginning of its output. */
418 /* Also note that C style comments are always supported. */
419 const char line_comment_chars[] = "#";
421 /* This array holds machine specific line separator characters. */
422 const char line_separator_chars[] = ";";
424 /* Chars that can be used to separate mant from exp in floating point nums */
425 const char EXP_CHARS[] = "eE";
427 /* Chars that mean this number is a floating point constant */
430 const char FLT_CHARS[] = "rRsSfFdDxXpP";
432 /* Also be aware that MAXIMUM_NUMBER_OF_CHARS_FOR_FLOAT may have to be
433 changed in read.c . Ideally it shouldn't have to know about it at all,
434 but nothing is ideal around here.
437 static char *insn_error;
439 static int auto_align = 1;
441 /* When outputting SVR4 PIC code, the assembler needs to know the
442 offset in the stack frame from which to restore the $gp register.
443 This is set by the .cprestore pseudo-op, and saved in this
445 static offsetT mips_cprestore_offset = -1;
447 /* Similiar for NewABI PIC code, where $gp is callee-saved. NewABI has some
448 more optimizations, it can use a register value instead of a memory-saved
449 offset and even an other register than $gp as global pointer. */
450 static offsetT mips_cpreturn_offset = -1;
451 static int mips_cpreturn_register = -1;
452 static int mips_gp_register = GP;
453 static int mips_gprel_offset = 0;
455 /* Whether mips_cprestore_offset has been set in the current function
456 (or whether it has already been warned about, if not). */
457 static int mips_cprestore_valid = 0;
459 /* This is the register which holds the stack frame, as set by the
460 .frame pseudo-op. This is needed to implement .cprestore. */
461 static int mips_frame_reg = SP;
463 /* Whether mips_frame_reg has been set in the current function
464 (or whether it has already been warned about, if not). */
465 static int mips_frame_reg_valid = 0;
467 /* To output NOP instructions correctly, we need to keep information
468 about the previous two instructions. */
470 /* Whether we are optimizing. The default value of 2 means to remove
471 unneeded NOPs and swap branch instructions when possible. A value
472 of 1 means to not swap branches. A value of 0 means to always
474 static int mips_optimize = 2;
476 /* Debugging level. -g sets this to 2. -gN sets this to N. -g0 is
477 equivalent to seeing no -g option at all. */
478 static int mips_debug = 0;
480 /* The previous instruction. */
481 static struct mips_cl_insn prev_insn;
483 /* The instruction before prev_insn. */
484 static struct mips_cl_insn prev_prev_insn;
486 /* If we don't want information for prev_insn or prev_prev_insn, we
487 point the insn_mo field at this dummy integer. */
488 static const struct mips_opcode dummy_opcode = { NULL, NULL, 0, 0, 0, 0 };
490 /* Non-zero if prev_insn is valid. */
491 static int prev_insn_valid;
493 /* The frag for the previous instruction. */
494 static struct frag *prev_insn_frag;
496 /* The offset into prev_insn_frag for the previous instruction. */
497 static long prev_insn_where;
499 /* The reloc type for the previous instruction, if any. */
500 static bfd_reloc_code_real_type prev_insn_reloc_type[3];
502 /* The reloc for the previous instruction, if any. */
503 static fixS *prev_insn_fixp[3];
505 /* Non-zero if the previous instruction was in a delay slot. */
506 static int prev_insn_is_delay_slot;
508 /* Non-zero if the previous instruction was in a .set noreorder. */
509 static int prev_insn_unreordered;
511 /* Non-zero if the previous instruction uses an extend opcode (if
513 static int prev_insn_extended;
515 /* Non-zero if the previous previous instruction was in a .set
517 static int prev_prev_insn_unreordered;
519 /* If this is set, it points to a frag holding nop instructions which
520 were inserted before the start of a noreorder section. If those
521 nops turn out to be unnecessary, the size of the frag can be
523 static fragS *prev_nop_frag;
525 /* The number of nop instructions we created in prev_nop_frag. */
526 static int prev_nop_frag_holds;
528 /* The number of nop instructions that we know we need in
530 static int prev_nop_frag_required;
532 /* The number of instructions we've seen since prev_nop_frag. */
533 static int prev_nop_frag_since;
535 /* For ECOFF and ELF, relocations against symbols are done in two
536 parts, with a HI relocation and a LO relocation. Each relocation
537 has only 16 bits of space to store an addend. This means that in
538 order for the linker to handle carries correctly, it must be able
539 to locate both the HI and the LO relocation. This means that the
540 relocations must appear in order in the relocation table.
542 In order to implement this, we keep track of each unmatched HI
543 relocation. We then sort them so that they immediately precede the
544 corresponding LO relocation. */
549 struct mips_hi_fixup *next;
552 /* The section this fixup is in. */
556 /* The list of unmatched HI relocs. */
558 static struct mips_hi_fixup *mips_hi_fixup_list;
560 /* The frag containing the last explicit relocation operator.
561 Null if explicit relocations have not been used. */
563 static fragS *prev_reloc_op_frag;
565 /* Map normal MIPS register numbers to mips16 register numbers. */
567 #define X ILLEGAL_REG
568 static const int mips32_to_16_reg_map[] =
570 X, X, 2, 3, 4, 5, 6, 7,
571 X, X, X, X, X, X, X, X,
572 0, 1, X, X, X, X, X, X,
573 X, X, X, X, X, X, X, X
577 /* Map mips16 register numbers to normal MIPS register numbers. */
579 static const unsigned int mips16_to_32_reg_map[] =
581 16, 17, 2, 3, 4, 5, 6, 7
584 static int mips_fix_4122_bugs;
586 /* We don't relax branches by default, since this causes us to expand
587 `la .l2 - .l1' if there's a branch between .l1 and .l2, because we
588 fail to compute the offset before expanding the macro to the most
589 efficient expansion. */
591 static int mips_relax_branch;
593 /* Since the MIPS does not have multiple forms of PC relative
594 instructions, we do not have to do relaxing as is done on other
595 platforms. However, we do have to handle GP relative addressing
596 correctly, which turns out to be a similar problem.
598 Every macro that refers to a symbol can occur in (at least) two
599 forms, one with GP relative addressing and one without. For
600 example, loading a global variable into a register generally uses
601 a macro instruction like this:
603 If i can be addressed off the GP register (this is true if it is in
604 the .sbss or .sdata section, or if it is known to be smaller than
605 the -G argument) this will generate the following instruction:
607 This instruction will use a GPREL reloc. If i can not be addressed
608 off the GP register, the following instruction sequence will be used:
611 In this case the first instruction will have a HI16 reloc, and the
612 second reloc will have a LO16 reloc. Both relocs will be against
615 The issue here is that we may not know whether i is GP addressable
616 until after we see the instruction that uses it. Therefore, we
617 want to be able to choose the final instruction sequence only at
618 the end of the assembly. This is similar to the way other
619 platforms choose the size of a PC relative instruction only at the
622 When generating position independent code we do not use GP
623 addressing in quite the same way, but the issue still arises as
624 external symbols and local symbols must be handled differently.
626 We handle these issues by actually generating both possible
627 instruction sequences. The longer one is put in a frag_var with
628 type rs_machine_dependent. We encode what to do with the frag in
629 the subtype field. We encode (1) the number of existing bytes to
630 replace, (2) the number of new bytes to use, (3) the offset from
631 the start of the existing bytes to the first reloc we must generate
632 (that is, the offset is applied from the start of the existing
633 bytes after they are replaced by the new bytes, if any), (4) the
634 offset from the start of the existing bytes to the second reloc,
635 (5) whether a third reloc is needed (the third reloc is always four
636 bytes after the second reloc), and (6) whether to warn if this
637 variant is used (this is sometimes needed if .set nomacro or .set
638 noat is in effect). All these numbers are reasonably small.
640 Generating two instruction sequences must be handled carefully to
641 ensure that delay slots are handled correctly. Fortunately, there
642 are a limited number of cases. When the second instruction
643 sequence is generated, append_insn is directed to maintain the
644 existing delay slot information, so it continues to apply to any
645 code after the second instruction sequence. This means that the
646 second instruction sequence must not impose any requirements not
647 required by the first instruction sequence.
649 These variant frags are then handled in functions called by the
650 machine independent code. md_estimate_size_before_relax returns
651 the final size of the frag. md_convert_frag sets up the final form
652 of the frag. tc_gen_reloc adjust the first reloc and adds a second
654 #define RELAX_ENCODE(old, new, reloc1, reloc2, reloc3, warn) \
658 | (((reloc1) + 64) << 9) \
659 | (((reloc2) + 64) << 2) \
660 | ((reloc3) ? (1 << 1) : 0) \
662 #define RELAX_OLD(i) (((i) >> 23) & 0x7f)
663 #define RELAX_NEW(i) (((i) >> 16) & 0x7f)
664 #define RELAX_RELOC1(i) ((valueT) (((i) >> 9) & 0x7f) - 64)
665 #define RELAX_RELOC2(i) ((valueT) (((i) >> 2) & 0x7f) - 64)
666 #define RELAX_RELOC3(i) (((i) >> 1) & 1)
667 #define RELAX_WARN(i) ((i) & 1)
669 /* Branch without likely bit. If label is out of range, we turn:
671 beq reg1, reg2, label
681 with the following opcode replacements:
688 bltzal <-> bgezal (with jal label instead of j label)
690 Even though keeping the delay slot instruction in the delay slot of
691 the branch would be more efficient, it would be very tricky to do
692 correctly, because we'd have to introduce a variable frag *after*
693 the delay slot instruction, and expand that instead. Let's do it
694 the easy way for now, even if the branch-not-taken case now costs
695 one additional instruction. Out-of-range branches are not supposed
696 to be common, anyway.
698 Branch likely. If label is out of range, we turn:
700 beql reg1, reg2, label
701 delay slot (annulled if branch not taken)
710 delay slot (executed only if branch taken)
713 It would be possible to generate a shorter sequence by losing the
714 likely bit, generating something like:
719 delay slot (executed only if branch taken)
731 bltzall -> bgezal (with jal label instead of j label)
732 bgezall -> bltzal (ditto)
735 but it's not clear that it would actually improve performance. */
736 #define RELAX_BRANCH_ENCODE(uncond, likely, link, toofar) \
739 | ((toofar) ? 1 : 0) \
741 | ((likely) ? 4 : 0) \
742 | ((uncond) ? 8 : 0)))
743 #define RELAX_BRANCH_P(i) (((i) & 0xf0000000) == 0xc0000000)
744 #define RELAX_BRANCH_UNCOND(i) (((i) & 8) != 0)
745 #define RELAX_BRANCH_LIKELY(i) (((i) & 4) != 0)
746 #define RELAX_BRANCH_LINK(i) (((i) & 2) != 0)
747 #define RELAX_BRANCH_TOOFAR(i) (((i) & 1) != 0)
749 /* For mips16 code, we use an entirely different form of relaxation.
750 mips16 supports two versions of most instructions which take
751 immediate values: a small one which takes some small value, and a
752 larger one which takes a 16 bit value. Since branches also follow
753 this pattern, relaxing these values is required.
755 We can assemble both mips16 and normal MIPS code in a single
756 object. Therefore, we need to support this type of relaxation at
757 the same time that we support the relaxation described above. We
758 use the high bit of the subtype field to distinguish these cases.
760 The information we store for this type of relaxation is the
761 argument code found in the opcode file for this relocation, whether
762 the user explicitly requested a small or extended form, and whether
763 the relocation is in a jump or jal delay slot. That tells us the
764 size of the value, and how it should be stored. We also store
765 whether the fragment is considered to be extended or not. We also
766 store whether this is known to be a branch to a different section,
767 whether we have tried to relax this frag yet, and whether we have
768 ever extended a PC relative fragment because of a shift count. */
769 #define RELAX_MIPS16_ENCODE(type, small, ext, dslot, jal_dslot) \
772 | ((small) ? 0x100 : 0) \
773 | ((ext) ? 0x200 : 0) \
774 | ((dslot) ? 0x400 : 0) \
775 | ((jal_dslot) ? 0x800 : 0))
776 #define RELAX_MIPS16_P(i) (((i) & 0xc0000000) == 0x80000000)
777 #define RELAX_MIPS16_TYPE(i) ((i) & 0xff)
778 #define RELAX_MIPS16_USER_SMALL(i) (((i) & 0x100) != 0)
779 #define RELAX_MIPS16_USER_EXT(i) (((i) & 0x200) != 0)
780 #define RELAX_MIPS16_DSLOT(i) (((i) & 0x400) != 0)
781 #define RELAX_MIPS16_JAL_DSLOT(i) (((i) & 0x800) != 0)
782 #define RELAX_MIPS16_EXTENDED(i) (((i) & 0x1000) != 0)
783 #define RELAX_MIPS16_MARK_EXTENDED(i) ((i) | 0x1000)
784 #define RELAX_MIPS16_CLEAR_EXTENDED(i) ((i) &~ 0x1000)
785 #define RELAX_MIPS16_LONG_BRANCH(i) (((i) & 0x2000) != 0)
786 #define RELAX_MIPS16_MARK_LONG_BRANCH(i) ((i) | 0x2000)
787 #define RELAX_MIPS16_CLEAR_LONG_BRANCH(i) ((i) &~ 0x2000)
789 /* Is the given value a sign-extended 32-bit value? */
790 #define IS_SEXT_32BIT_NUM(x) \
791 (((x) &~ (offsetT) 0x7fffffff) == 0 \
792 || (((x) &~ (offsetT) 0x7fffffff) == ~ (offsetT) 0x7fffffff))
794 /* Is the given value a sign-extended 16-bit value? */
795 #define IS_SEXT_16BIT_NUM(x) \
796 (((x) &~ (offsetT) 0x7fff) == 0 \
797 || (((x) &~ (offsetT) 0x7fff) == ~ (offsetT) 0x7fff))
800 /* Prototypes for static functions. */
803 #define internalError() \
804 as_fatal (_("internal Error, line %d, %s"), __LINE__, __FILE__)
806 #define internalError() as_fatal (_("MIPS internal Error"));
809 enum mips_regclass { MIPS_GR_REG, MIPS_FP_REG, MIPS16_REG };
811 static inline bfd_boolean reloc_needs_lo_p
812 PARAMS ((bfd_reloc_code_real_type));
813 static inline bfd_boolean fixup_has_matching_lo_p
815 static int insn_uses_reg
816 PARAMS ((struct mips_cl_insn *ip, unsigned int reg,
817 enum mips_regclass class));
818 static int reg_needs_delay
819 PARAMS ((unsigned int));
820 static void mips16_mark_labels
822 static void append_insn
823 PARAMS ((char *place, struct mips_cl_insn * ip, expressionS * p,
824 bfd_reloc_code_real_type *r));
825 static void mips_no_prev_insn
827 static void mips_emit_delays
828 PARAMS ((bfd_boolean));
830 static void macro_build
831 PARAMS ((char *place, int *counter, expressionS * ep, const char *name,
832 const char *fmt, ...));
834 static void macro_build ();
836 static void mips16_macro_build
837 PARAMS ((char *, int *, expressionS *, const char *, const char *, va_list));
838 static void macro_build_jalr
839 PARAMS ((int, expressionS *));
840 static void macro_build_lui
841 PARAMS ((char *place, int *counter, expressionS * ep, int regnum));
842 static void macro_build_ldst_constoffset
843 PARAMS ((char *place, int *counter, expressionS * ep, const char *op,
844 int valreg, int breg));
846 PARAMS ((int *counter, int reg, int unsignedp));
847 static void check_absolute_expr
848 PARAMS ((struct mips_cl_insn * ip, expressionS *));
849 static void load_register
850 PARAMS ((int *, int, expressionS *, int));
851 static void load_address
852 PARAMS ((int *, int, expressionS *, int *));
853 static void move_register
854 PARAMS ((int *, int, int));
856 PARAMS ((struct mips_cl_insn * ip));
857 static void mips16_macro
858 PARAMS ((struct mips_cl_insn * ip));
859 #ifdef LOSING_COMPILER
861 PARAMS ((struct mips_cl_insn * ip));
864 PARAMS ((char *str, struct mips_cl_insn * ip));
865 static void mips16_ip
866 PARAMS ((char *str, struct mips_cl_insn * ip));
867 static void mips16_immed
868 PARAMS ((char *, unsigned int, int, offsetT, bfd_boolean, bfd_boolean,
869 bfd_boolean, unsigned long *, bfd_boolean *, unsigned short *));
870 static bfd_boolean parse_relocation
871 PARAMS ((char **, bfd_reloc_code_real_type *));
872 static size_t my_getSmallExpression
873 PARAMS ((expressionS *, bfd_reloc_code_real_type *, char *));
874 static void my_getExpression
875 PARAMS ((expressionS *, char *));
877 static int support_64bit_objects
880 static void mips_set_option_string
881 PARAMS ((const char **, const char *));
882 static symbolS *get_symbol
884 static void mips_align
885 PARAMS ((int to, int fill, symbolS *label));
888 static void s_change_sec
890 static void s_change_section
894 static void s_float_cons
896 static void s_mips_globl
900 static void s_mipsset
902 static void s_abicalls
906 static void s_cpsetup
908 static void s_cplocal
910 static void s_cprestore
912 static void s_cpreturn
914 static void s_gpvalue
918 static void s_gpdword
924 static void md_obj_begin
926 static void md_obj_end
928 static long get_number
930 static void s_mips_ent
932 static void s_mips_end
934 static void s_mips_frame
936 static void s_mips_mask
938 static void s_mips_stab
940 static void s_mips_weakext
942 static void s_mips_file
944 static void s_mips_loc
946 static bfd_boolean pic_need_relax
947 PARAMS ((symbolS *, asection *));
948 static int mips16_extended_frag
949 PARAMS ((fragS *, asection *, long));
950 static int relaxed_branch_length (fragS *, asection *, int);
951 static int validate_mips_insn
952 PARAMS ((const struct mips_opcode *));
954 PARAMS ((FILE *, const char *, int *, int *));
956 static int mips_need_elf_addend_fixup
960 /* Table and functions used to map between CPU/ISA names, and
961 ISA levels, and CPU numbers. */
965 const char *name; /* CPU or ISA name. */
966 int is_isa; /* Is this an ISA? (If 0, a CPU.) */
967 int isa; /* ISA level. */
968 int cpu; /* CPU number (default CPU if ISA). */
971 static void mips_set_architecture
972 PARAMS ((const struct mips_cpu_info *));
973 static void mips_set_tune
974 PARAMS ((const struct mips_cpu_info *));
975 static bfd_boolean mips_strict_matching_cpu_name_p
976 PARAMS ((const char *, const char *));
977 static bfd_boolean mips_matching_cpu_name_p
978 PARAMS ((const char *, const char *));
979 static const struct mips_cpu_info *mips_parse_cpu
980 PARAMS ((const char *, const char *));
981 static const struct mips_cpu_info *mips_cpu_info_from_isa
986 The following pseudo-ops from the Kane and Heinrich MIPS book
987 should be defined here, but are currently unsupported: .alias,
988 .galive, .gjaldef, .gjrlive, .livereg, .noalias.
990 The following pseudo-ops from the Kane and Heinrich MIPS book are
991 specific to the type of debugging information being generated, and
992 should be defined by the object format: .aent, .begin, .bend,
993 .bgnb, .end, .endb, .ent, .fmask, .frame, .loc, .mask, .verstamp,
996 The following pseudo-ops from the Kane and Heinrich MIPS book are
997 not MIPS CPU specific, but are also not specific to the object file
998 format. This file is probably the best place to define them, but
999 they are not currently supported: .asm0, .endr, .lab, .repeat,
1002 static const pseudo_typeS mips_pseudo_table[] =
1004 /* MIPS specific pseudo-ops. */
1005 {"option", s_option, 0},
1006 {"set", s_mipsset, 0},
1007 {"rdata", s_change_sec, 'r'},
1008 {"sdata", s_change_sec, 's'},
1009 {"livereg", s_ignore, 0},
1010 {"abicalls", s_abicalls, 0},
1011 {"cpload", s_cpload, 0},
1012 {"cpsetup", s_cpsetup, 0},
1013 {"cplocal", s_cplocal, 0},
1014 {"cprestore", s_cprestore, 0},
1015 {"cpreturn", s_cpreturn, 0},
1016 {"gpvalue", s_gpvalue, 0},
1017 {"gpword", s_gpword, 0},
1018 {"gpdword", s_gpdword, 0},
1019 {"cpadd", s_cpadd, 0},
1020 {"insn", s_insn, 0},
1022 /* Relatively generic pseudo-ops that happen to be used on MIPS
1024 {"asciiz", stringer, 1},
1025 {"bss", s_change_sec, 'b'},
1027 {"half", s_cons, 1},
1028 {"dword", s_cons, 3},
1029 {"weakext", s_mips_weakext, 0},
1031 /* These pseudo-ops are defined in read.c, but must be overridden
1032 here for one reason or another. */
1033 {"align", s_align, 0},
1034 {"byte", s_cons, 0},
1035 {"data", s_change_sec, 'd'},
1036 {"double", s_float_cons, 'd'},
1037 {"float", s_float_cons, 'f'},
1038 {"globl", s_mips_globl, 0},
1039 {"global", s_mips_globl, 0},
1040 {"hword", s_cons, 1},
1042 {"long", s_cons, 2},
1043 {"octa", s_cons, 4},
1044 {"quad", s_cons, 3},
1045 {"section", s_change_section, 0},
1046 {"short", s_cons, 1},
1047 {"single", s_float_cons, 'f'},
1048 {"stabn", s_mips_stab, 'n'},
1049 {"text", s_change_sec, 't'},
1050 {"word", s_cons, 2},
1052 { "extern", ecoff_directive_extern, 0},
1057 static const pseudo_typeS mips_nonecoff_pseudo_table[] =
1059 /* These pseudo-ops should be defined by the object file format.
1060 However, a.out doesn't support them, so we have versions here. */
1061 {"aent", s_mips_ent, 1},
1062 {"bgnb", s_ignore, 0},
1063 {"end", s_mips_end, 0},
1064 {"endb", s_ignore, 0},
1065 {"ent", s_mips_ent, 0},
1066 {"file", s_mips_file, 0},
1067 {"fmask", s_mips_mask, 'F'},
1068 {"frame", s_mips_frame, 0},
1069 {"loc", s_mips_loc, 0},
1070 {"mask", s_mips_mask, 'R'},
1071 {"verstamp", s_ignore, 0},
1075 extern void pop_insert PARAMS ((const pseudo_typeS *));
1080 pop_insert (mips_pseudo_table);
1081 if (! ECOFF_DEBUGGING)
1082 pop_insert (mips_nonecoff_pseudo_table);
1085 /* Symbols labelling the current insn. */
1087 struct insn_label_list
1089 struct insn_label_list *next;
1093 static struct insn_label_list *insn_labels;
1094 static struct insn_label_list *free_insn_labels;
1096 static void mips_clear_insn_labels PARAMS ((void));
1099 mips_clear_insn_labels ()
1101 register struct insn_label_list **pl;
1103 for (pl = &free_insn_labels; *pl != NULL; pl = &(*pl)->next)
1109 static char *expr_end;
1111 /* Expressions which appear in instructions. These are set by
1114 static expressionS imm_expr;
1115 static expressionS offset_expr;
1117 /* Relocs associated with imm_expr and offset_expr. */
1119 static bfd_reloc_code_real_type imm_reloc[3]
1120 = {BFD_RELOC_UNUSED, BFD_RELOC_UNUSED, BFD_RELOC_UNUSED};
1121 static bfd_reloc_code_real_type offset_reloc[3]
1122 = {BFD_RELOC_UNUSED, BFD_RELOC_UNUSED, BFD_RELOC_UNUSED};
1124 /* These are set by mips16_ip if an explicit extension is used. */
1126 static bfd_boolean mips16_small, mips16_ext;
1129 /* The pdr segment for per procedure frame/regmask info. Not used for
1132 static segT pdr_seg;
1135 /* The default target format to use. */
1138 mips_target_format ()
1140 switch (OUTPUT_FLAVOR)
1142 case bfd_target_aout_flavour:
1143 return target_big_endian ? "a.out-mips-big" : "a.out-mips-little";
1144 case bfd_target_ecoff_flavour:
1145 return target_big_endian ? "ecoff-bigmips" : ECOFF_LITTLE_FORMAT;
1146 case bfd_target_coff_flavour:
1148 case bfd_target_elf_flavour:
1150 /* This is traditional mips. */
1151 return (target_big_endian
1152 ? (HAVE_64BIT_OBJECTS
1153 ? "elf64-tradbigmips"
1155 ? "elf32-ntradbigmips" : "elf32-tradbigmips"))
1156 : (HAVE_64BIT_OBJECTS
1157 ? "elf64-tradlittlemips"
1159 ? "elf32-ntradlittlemips" : "elf32-tradlittlemips")));
1161 return (target_big_endian
1162 ? (HAVE_64BIT_OBJECTS
1165 ? "elf32-nbigmips" : "elf32-bigmips"))
1166 : (HAVE_64BIT_OBJECTS
1167 ? "elf64-littlemips"
1169 ? "elf32-nlittlemips" : "elf32-littlemips")));
1177 /* This function is called once, at assembler startup time. It should
1178 set up all the tables, etc. that the MD part of the assembler will need. */
1183 register const char *retval = NULL;
1187 if (! bfd_set_arch_mach (stdoutput, bfd_arch_mips, mips_arch))
1188 as_warn (_("Could not set architecture and machine"));
1190 op_hash = hash_new ();
1192 for (i = 0; i < NUMOPCODES;)
1194 const char *name = mips_opcodes[i].name;
1196 retval = hash_insert (op_hash, name, (PTR) &mips_opcodes[i]);
1199 fprintf (stderr, _("internal error: can't hash `%s': %s\n"),
1200 mips_opcodes[i].name, retval);
1201 /* Probably a memory allocation problem? Give up now. */
1202 as_fatal (_("Broken assembler. No assembly attempted."));
1206 if (mips_opcodes[i].pinfo != INSN_MACRO)
1208 if (!validate_mips_insn (&mips_opcodes[i]))
1213 while ((i < NUMOPCODES) && !strcmp (mips_opcodes[i].name, name));
1216 mips16_op_hash = hash_new ();
1219 while (i < bfd_mips16_num_opcodes)
1221 const char *name = mips16_opcodes[i].name;
1223 retval = hash_insert (mips16_op_hash, name, (PTR) &mips16_opcodes[i]);
1225 as_fatal (_("internal: can't hash `%s': %s"),
1226 mips16_opcodes[i].name, retval);
1229 if (mips16_opcodes[i].pinfo != INSN_MACRO
1230 && ((mips16_opcodes[i].match & mips16_opcodes[i].mask)
1231 != mips16_opcodes[i].match))
1233 fprintf (stderr, _("internal error: bad mips16 opcode: %s %s\n"),
1234 mips16_opcodes[i].name, mips16_opcodes[i].args);
1239 while (i < bfd_mips16_num_opcodes
1240 && strcmp (mips16_opcodes[i].name, name) == 0);
1244 as_fatal (_("Broken assembler. No assembly attempted."));
1246 /* We add all the general register names to the symbol table. This
1247 helps us detect invalid uses of them. */
1248 for (i = 0; i < 32; i++)
1252 sprintf (buf, "$%d", i);
1253 symbol_table_insert (symbol_new (buf, reg_section, i,
1254 &zero_address_frag));
1256 symbol_table_insert (symbol_new ("$ra", reg_section, RA,
1257 &zero_address_frag));
1258 symbol_table_insert (symbol_new ("$fp", reg_section, FP,
1259 &zero_address_frag));
1260 symbol_table_insert (symbol_new ("$sp", reg_section, SP,
1261 &zero_address_frag));
1262 symbol_table_insert (symbol_new ("$gp", reg_section, GP,
1263 &zero_address_frag));
1264 symbol_table_insert (symbol_new ("$at", reg_section, AT,
1265 &zero_address_frag));
1266 symbol_table_insert (symbol_new ("$kt0", reg_section, KT0,
1267 &zero_address_frag));
1268 symbol_table_insert (symbol_new ("$kt1", reg_section, KT1,
1269 &zero_address_frag));
1270 symbol_table_insert (symbol_new ("$zero", reg_section, ZERO,
1271 &zero_address_frag));
1272 symbol_table_insert (symbol_new ("$pc", reg_section, -1,
1273 &zero_address_frag));
1275 /* If we don't add these register names to the symbol table, they
1276 may end up being added as regular symbols by operand(), and then
1277 make it to the object file as undefined in case they're not
1278 regarded as local symbols. They're local in o32, since `$' is a
1279 local symbol prefix, but not in n32 or n64. */
1280 for (i = 0; i < 8; i++)
1284 sprintf (buf, "$fcc%i", i);
1285 symbol_table_insert (symbol_new (buf, reg_section, -1,
1286 &zero_address_frag));
1289 mips_no_prev_insn (FALSE);
1292 mips_cprmask[0] = 0;
1293 mips_cprmask[1] = 0;
1294 mips_cprmask[2] = 0;
1295 mips_cprmask[3] = 0;
1297 /* set the default alignment for the text section (2**2) */
1298 record_alignment (text_section, 2);
1300 if (USE_GLOBAL_POINTER_OPT)
1301 bfd_set_gp_size (stdoutput, g_switch_value);
1303 if (OUTPUT_FLAVOR == bfd_target_elf_flavour)
1305 /* On a native system, sections must be aligned to 16 byte
1306 boundaries. When configured for an embedded ELF target, we
1308 if (strcmp (TARGET_OS, "elf") != 0)
1310 (void) bfd_set_section_alignment (stdoutput, text_section, 4);
1311 (void) bfd_set_section_alignment (stdoutput, data_section, 4);
1312 (void) bfd_set_section_alignment (stdoutput, bss_section, 4);
1315 /* Create a .reginfo section for register masks and a .mdebug
1316 section for debugging information. */
1324 subseg = now_subseg;
1326 /* The ABI says this section should be loaded so that the
1327 running program can access it. However, we don't load it
1328 if we are configured for an embedded target */
1329 flags = SEC_READONLY | SEC_DATA;
1330 if (strcmp (TARGET_OS, "elf") != 0)
1331 flags |= SEC_ALLOC | SEC_LOAD;
1333 if (mips_abi != N64_ABI)
1335 sec = subseg_new (".reginfo", (subsegT) 0);
1337 bfd_set_section_flags (stdoutput, sec, flags);
1338 bfd_set_section_alignment (stdoutput, sec, HAVE_NEWABI ? 3 : 2);
1341 mips_regmask_frag = frag_more (sizeof (Elf32_External_RegInfo));
1346 /* The 64-bit ABI uses a .MIPS.options section rather than
1347 .reginfo section. */
1348 sec = subseg_new (".MIPS.options", (subsegT) 0);
1349 bfd_set_section_flags (stdoutput, sec, flags);
1350 bfd_set_section_alignment (stdoutput, sec, 3);
1353 /* Set up the option header. */
1355 Elf_Internal_Options opthdr;
1358 opthdr.kind = ODK_REGINFO;
1359 opthdr.size = (sizeof (Elf_External_Options)
1360 + sizeof (Elf64_External_RegInfo));
1363 f = frag_more (sizeof (Elf_External_Options));
1364 bfd_mips_elf_swap_options_out (stdoutput, &opthdr,
1365 (Elf_External_Options *) f);
1367 mips_regmask_frag = frag_more (sizeof (Elf64_External_RegInfo));
1372 if (ECOFF_DEBUGGING)
1374 sec = subseg_new (".mdebug", (subsegT) 0);
1375 (void) bfd_set_section_flags (stdoutput, sec,
1376 SEC_HAS_CONTENTS | SEC_READONLY);
1377 (void) bfd_set_section_alignment (stdoutput, sec, 2);
1380 else if (OUTPUT_FLAVOR == bfd_target_elf_flavour)
1382 pdr_seg = subseg_new (".pdr", (subsegT) 0);
1383 (void) bfd_set_section_flags (stdoutput, pdr_seg,
1384 SEC_READONLY | SEC_RELOC
1386 (void) bfd_set_section_alignment (stdoutput, pdr_seg, 2);
1390 subseg_set (seg, subseg);
1394 if (! ECOFF_DEBUGGING)
1401 if (! ECOFF_DEBUGGING)
1409 struct mips_cl_insn insn;
1410 bfd_reloc_code_real_type unused_reloc[3]
1411 = {BFD_RELOC_UNUSED, BFD_RELOC_UNUSED, BFD_RELOC_UNUSED};
1413 imm_expr.X_op = O_absent;
1414 offset_expr.X_op = O_absent;
1415 imm_reloc[0] = BFD_RELOC_UNUSED;
1416 imm_reloc[1] = BFD_RELOC_UNUSED;
1417 imm_reloc[2] = BFD_RELOC_UNUSED;
1418 offset_reloc[0] = BFD_RELOC_UNUSED;
1419 offset_reloc[1] = BFD_RELOC_UNUSED;
1420 offset_reloc[2] = BFD_RELOC_UNUSED;
1422 if (mips_opts.mips16)
1423 mips16_ip (str, &insn);
1426 mips_ip (str, &insn);
1427 DBG ((_("returned from mips_ip(%s) insn_opcode = 0x%x\n"),
1428 str, insn.insn_opcode));
1433 as_bad ("%s `%s'", insn_error, str);
1437 if (insn.insn_mo->pinfo == INSN_MACRO)
1439 if (mips_opts.mips16)
1440 mips16_macro (&insn);
1446 if (imm_expr.X_op != O_absent)
1447 append_insn (NULL, &insn, &imm_expr, imm_reloc);
1448 else if (offset_expr.X_op != O_absent)
1449 append_insn (NULL, &insn, &offset_expr, offset_reloc);
1451 append_insn (NULL, &insn, NULL, unused_reloc);
1455 /* Return true if the given relocation might need a matching %lo().
1456 Note that R_MIPS_GOT16 relocations only need a matching %lo() when
1457 applied to local symbols. */
1459 static inline bfd_boolean
1460 reloc_needs_lo_p (reloc)
1461 bfd_reloc_code_real_type reloc;
1463 return (reloc == BFD_RELOC_HI16_S
1464 || reloc == BFD_RELOC_MIPS_GOT16);
1467 /* Return true if the given fixup is followed by a matching R_MIPS_LO16
1470 static inline bfd_boolean
1471 fixup_has_matching_lo_p (fixp)
1474 return (fixp->fx_next != NULL
1475 && fixp->fx_next->fx_r_type == BFD_RELOC_LO16
1476 && fixp->fx_addsy == fixp->fx_next->fx_addsy
1477 && fixp->fx_offset == fixp->fx_next->fx_offset);
1480 /* See whether instruction IP reads register REG. CLASS is the type
1484 insn_uses_reg (ip, reg, class)
1485 struct mips_cl_insn *ip;
1487 enum mips_regclass class;
1489 if (class == MIPS16_REG)
1491 assert (mips_opts.mips16);
1492 reg = mips16_to_32_reg_map[reg];
1493 class = MIPS_GR_REG;
1496 /* Don't report on general register ZERO, since it never changes. */
1497 if (class == MIPS_GR_REG && reg == ZERO)
1500 if (class == MIPS_FP_REG)
1502 assert (! mips_opts.mips16);
1503 /* If we are called with either $f0 or $f1, we must check $f0.
1504 This is not optimal, because it will introduce an unnecessary
1505 NOP between "lwc1 $f0" and "swc1 $f1". To fix this we would
1506 need to distinguish reading both $f0 and $f1 or just one of
1507 them. Note that we don't have to check the other way,
1508 because there is no instruction that sets both $f0 and $f1
1509 and requires a delay. */
1510 if ((ip->insn_mo->pinfo & INSN_READ_FPR_S)
1511 && ((((ip->insn_opcode >> OP_SH_FS) & OP_MASK_FS) &~(unsigned)1)
1512 == (reg &~ (unsigned) 1)))
1514 if ((ip->insn_mo->pinfo & INSN_READ_FPR_T)
1515 && ((((ip->insn_opcode >> OP_SH_FT) & OP_MASK_FT) &~(unsigned)1)
1516 == (reg &~ (unsigned) 1)))
1519 else if (! mips_opts.mips16)
1521 if ((ip->insn_mo->pinfo & INSN_READ_GPR_S)
1522 && ((ip->insn_opcode >> OP_SH_RS) & OP_MASK_RS) == reg)
1524 if ((ip->insn_mo->pinfo & INSN_READ_GPR_T)
1525 && ((ip->insn_opcode >> OP_SH_RT) & OP_MASK_RT) == reg)
1530 if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_X)
1531 && (mips16_to_32_reg_map[((ip->insn_opcode >> MIPS16OP_SH_RX)
1532 & MIPS16OP_MASK_RX)]
1535 if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_Y)
1536 && (mips16_to_32_reg_map[((ip->insn_opcode >> MIPS16OP_SH_RY)
1537 & MIPS16OP_MASK_RY)]
1540 if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_Z)
1541 && (mips16_to_32_reg_map[((ip->insn_opcode >> MIPS16OP_SH_MOVE32Z)
1542 & MIPS16OP_MASK_MOVE32Z)]
1545 if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_T) && reg == TREG)
1547 if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_SP) && reg == SP)
1549 if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_31) && reg == RA)
1551 if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_GPR_X)
1552 && ((ip->insn_opcode >> MIPS16OP_SH_REGR32)
1553 & MIPS16OP_MASK_REGR32) == reg)
1560 /* This function returns true if modifying a register requires a
1564 reg_needs_delay (reg)
1567 unsigned long prev_pinfo;
1569 prev_pinfo = prev_insn.insn_mo->pinfo;
1570 if (! mips_opts.noreorder
1571 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
1572 && ((prev_pinfo & INSN_LOAD_COPROC_DELAY)
1573 || (! gpr_interlocks
1574 && (prev_pinfo & INSN_LOAD_MEMORY_DELAY))))
1576 /* A load from a coprocessor or from memory. All load
1577 delays delay the use of general register rt for one
1578 instruction on the r3000. The r6000 and r4000 use
1580 /* Itbl support may require additional care here. */
1581 know (prev_pinfo & INSN_WRITE_GPR_T);
1582 if (reg == ((prev_insn.insn_opcode >> OP_SH_RT) & OP_MASK_RT))
1589 /* Mark instruction labels in mips16 mode. This permits the linker to
1590 handle them specially, such as generating jalx instructions when
1591 needed. We also make them odd for the duration of the assembly, in
1592 order to generate the right sort of code. We will make them even
1593 in the adjust_symtab routine, while leaving them marked. This is
1594 convenient for the debugger and the disassembler. The linker knows
1595 to make them odd again. */
1598 mips16_mark_labels ()
1600 if (mips_opts.mips16)
1602 struct insn_label_list *l;
1605 for (l = insn_labels; l != NULL; l = l->next)
1608 if (OUTPUT_FLAVOR == bfd_target_elf_flavour)
1609 S_SET_OTHER (l->label, STO_MIPS16);
1611 val = S_GET_VALUE (l->label);
1613 S_SET_VALUE (l->label, val + 1);
1618 /* Output an instruction. PLACE is where to put the instruction; if
1619 it is NULL, this uses frag_more to get room. IP is the instruction
1620 information. ADDRESS_EXPR is an operand of the instruction to be
1621 used with RELOC_TYPE. */
1624 append_insn (place, ip, address_expr, reloc_type)
1626 struct mips_cl_insn *ip;
1627 expressionS *address_expr;
1628 bfd_reloc_code_real_type *reloc_type;
1630 register unsigned long prev_pinfo, pinfo;
1634 bfd_boolean force_new_frag = FALSE;
1636 /* Mark instruction labels in mips16 mode. */
1637 mips16_mark_labels ();
1639 prev_pinfo = prev_insn.insn_mo->pinfo;
1640 pinfo = ip->insn_mo->pinfo;
1642 if (place == NULL && (! mips_opts.noreorder || prev_nop_frag != NULL))
1646 /* If the previous insn required any delay slots, see if we need
1647 to insert a NOP or two. There are eight kinds of possible
1648 hazards, of which an instruction can have at most one type.
1649 (1) a load from memory delay
1650 (2) a load from a coprocessor delay
1651 (3) an unconditional branch delay
1652 (4) a conditional branch delay
1653 (5) a move to coprocessor register delay
1654 (6) a load coprocessor register from memory delay
1655 (7) a coprocessor condition code delay
1656 (8) a HI/LO special register delay
1658 There are a lot of optimizations we could do that we don't.
1659 In particular, we do not, in general, reorder instructions.
1660 If you use gcc with optimization, it will reorder
1661 instructions and generally do much more optimization then we
1662 do here; repeating all that work in the assembler would only
1663 benefit hand written assembly code, and does not seem worth
1666 /* This is how a NOP is emitted. */
1667 #define emit_nop() \
1669 ? md_number_to_chars (frag_more (2), 0x6500, 2) \
1670 : md_number_to_chars (frag_more (4), 0, 4))
1672 /* The previous insn might require a delay slot, depending upon
1673 the contents of the current insn. */
1674 if (! mips_opts.mips16
1675 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
1676 && (((prev_pinfo & INSN_LOAD_COPROC_DELAY)
1677 && ! cop_interlocks)
1678 || (! gpr_interlocks
1679 && (prev_pinfo & INSN_LOAD_MEMORY_DELAY))))
1681 /* A load from a coprocessor or from memory. All load
1682 delays delay the use of general register rt for one
1683 instruction on the r3000. The r6000 and r4000 use
1685 /* Itbl support may require additional care here. */
1686 know (prev_pinfo & INSN_WRITE_GPR_T);
1687 if (mips_optimize == 0
1688 || insn_uses_reg (ip,
1689 ((prev_insn.insn_opcode >> OP_SH_RT)
1694 else if (! mips_opts.mips16
1695 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
1696 && (((prev_pinfo & INSN_COPROC_MOVE_DELAY)
1697 && ! cop_interlocks)
1698 || (mips_opts.isa == ISA_MIPS1
1699 && (prev_pinfo & INSN_COPROC_MEMORY_DELAY))))
1701 /* A generic coprocessor delay. The previous instruction
1702 modified a coprocessor general or control register. If
1703 it modified a control register, we need to avoid any
1704 coprocessor instruction (this is probably not always
1705 required, but it sometimes is). If it modified a general
1706 register, we avoid using that register.
1708 On the r6000 and r4000 loading a coprocessor register
1709 from memory is interlocked, and does not require a delay.
1711 This case is not handled very well. There is no special
1712 knowledge of CP0 handling, and the coprocessors other
1713 than the floating point unit are not distinguished at
1715 /* Itbl support may require additional care here. FIXME!
1716 Need to modify this to include knowledge about
1717 user specified delays! */
1718 if (prev_pinfo & INSN_WRITE_FPR_T)
1720 if (mips_optimize == 0
1721 || insn_uses_reg (ip,
1722 ((prev_insn.insn_opcode >> OP_SH_FT)
1727 else if (prev_pinfo & INSN_WRITE_FPR_S)
1729 if (mips_optimize == 0
1730 || insn_uses_reg (ip,
1731 ((prev_insn.insn_opcode >> OP_SH_FS)
1738 /* We don't know exactly what the previous instruction
1739 does. If the current instruction uses a coprocessor
1740 register, we must insert a NOP. If previous
1741 instruction may set the condition codes, and the
1742 current instruction uses them, we must insert two
1744 /* Itbl support may require additional care here. */
1745 if (mips_optimize == 0
1746 || ((prev_pinfo & INSN_WRITE_COND_CODE)
1747 && (pinfo & INSN_READ_COND_CODE)))
1749 else if (pinfo & INSN_COP)
1753 else if (! mips_opts.mips16
1754 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
1755 && (prev_pinfo & INSN_WRITE_COND_CODE)
1756 && ! cop_interlocks)
1758 /* The previous instruction sets the coprocessor condition
1759 codes, but does not require a general coprocessor delay
1760 (this means it is a floating point comparison
1761 instruction). If this instruction uses the condition
1762 codes, we need to insert a single NOP. */
1763 /* Itbl support may require additional care here. */
1764 if (mips_optimize == 0
1765 || (pinfo & INSN_READ_COND_CODE))
1769 /* If we're fixing up mfhi/mflo for the r7000 and the
1770 previous insn was an mfhi/mflo and the current insn
1771 reads the register that the mfhi/mflo wrote to, then
1774 else if (mips_7000_hilo_fix
1775 && MF_HILO_INSN (prev_pinfo)
1776 && insn_uses_reg (ip, ((prev_insn.insn_opcode >> OP_SH_RD)
1783 /* If we're fixing up mfhi/mflo for the r7000 and the
1784 2nd previous insn was an mfhi/mflo and the current insn
1785 reads the register that the mfhi/mflo wrote to, then
1788 else if (mips_7000_hilo_fix
1789 && MF_HILO_INSN (prev_prev_insn.insn_opcode)
1790 && insn_uses_reg (ip, ((prev_prev_insn.insn_opcode >> OP_SH_RD)
1798 else if (prev_pinfo & INSN_READ_LO)
1800 /* The previous instruction reads the LO register; if the
1801 current instruction writes to the LO register, we must
1802 insert two NOPS. Some newer processors have interlocks.
1803 Also the tx39's multiply instructions can be exectuted
1804 immediatly after a read from HI/LO (without the delay),
1805 though the tx39's divide insns still do require the
1807 if (! (hilo_interlocks
1808 || (mips_tune == CPU_R3900 && (pinfo & INSN_MULT)))
1809 && (mips_optimize == 0
1810 || (pinfo & INSN_WRITE_LO)))
1812 /* Most mips16 branch insns don't have a delay slot.
1813 If a read from LO is immediately followed by a branch
1814 to a write to LO we have a read followed by a write
1815 less than 2 insns away. We assume the target of
1816 a branch might be a write to LO, and insert a nop
1817 between a read and an immediately following branch. */
1818 else if (mips_opts.mips16
1819 && (mips_optimize == 0
1820 || (pinfo & MIPS16_INSN_BRANCH)))
1823 else if (prev_insn.insn_mo->pinfo & INSN_READ_HI)
1825 /* The previous instruction reads the HI register; if the
1826 current instruction writes to the HI register, we must
1827 insert a NOP. Some newer processors have interlocks.
1828 Also the note tx39's multiply above. */
1829 if (! (hilo_interlocks
1830 || (mips_tune == CPU_R3900 && (pinfo & INSN_MULT)))
1831 && (mips_optimize == 0
1832 || (pinfo & INSN_WRITE_HI)))
1834 /* Most mips16 branch insns don't have a delay slot.
1835 If a read from HI is immediately followed by a branch
1836 to a write to HI we have a read followed by a write
1837 less than 2 insns away. We assume the target of
1838 a branch might be a write to HI, and insert a nop
1839 between a read and an immediately following branch. */
1840 else if (mips_opts.mips16
1841 && (mips_optimize == 0
1842 || (pinfo & MIPS16_INSN_BRANCH)))
1846 /* If the previous instruction was in a noreorder section, then
1847 we don't want to insert the nop after all. */
1848 /* Itbl support may require additional care here. */
1849 if (prev_insn_unreordered)
1852 /* There are two cases which require two intervening
1853 instructions: 1) setting the condition codes using a move to
1854 coprocessor instruction which requires a general coprocessor
1855 delay and then reading the condition codes 2) reading the HI
1856 or LO register and then writing to it (except on processors
1857 which have interlocks). If we are not already emitting a NOP
1858 instruction, we must check for these cases compared to the
1859 instruction previous to the previous instruction. */
1860 if ((! mips_opts.mips16
1861 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
1862 && (prev_prev_insn.insn_mo->pinfo & INSN_COPROC_MOVE_DELAY)
1863 && (prev_prev_insn.insn_mo->pinfo & INSN_WRITE_COND_CODE)
1864 && (pinfo & INSN_READ_COND_CODE)
1865 && ! cop_interlocks)
1866 || ((prev_prev_insn.insn_mo->pinfo & INSN_READ_LO)
1867 && (pinfo & INSN_WRITE_LO)
1868 && ! (hilo_interlocks
1869 || (mips_tune == CPU_R3900 && (pinfo & INSN_MULT))))
1870 || ((prev_prev_insn.insn_mo->pinfo & INSN_READ_HI)
1871 && (pinfo & INSN_WRITE_HI)
1872 && ! (hilo_interlocks
1873 || (mips_tune == CPU_R3900 && (pinfo & INSN_MULT)))))
1878 if (prev_prev_insn_unreordered)
1881 if (prev_prev_nop && nops == 0)
1884 if (mips_fix_4122_bugs && prev_insn.insn_mo->name)
1886 /* We're out of bits in pinfo, so we must resort to string
1887 ops here. Shortcuts are selected based on opcodes being
1888 limited to the VR4122 instruction set. */
1890 const char *pn = prev_insn.insn_mo->name;
1891 const char *tn = ip->insn_mo->name;
1892 if (strncmp(pn, "macc", 4) == 0
1893 || strncmp(pn, "dmacc", 5) == 0)
1895 /* Errata 21 - [D]DIV[U] after [D]MACC */
1896 if (strstr (tn, "div"))
1901 /* Errata 23 - Continuous DMULT[U]/DMACC instructions */
1902 if (pn[0] == 'd' /* dmacc */
1903 && (strncmp(tn, "dmult", 5) == 0
1904 || strncmp(tn, "dmacc", 5) == 0))
1909 /* Errata 24 - MT{LO,HI} after [D]MACC */
1910 if (strcmp (tn, "mtlo") == 0
1911 || strcmp (tn, "mthi") == 0)
1917 else if (strncmp(pn, "dmult", 5) == 0
1918 && (strncmp(tn, "dmult", 5) == 0
1919 || strncmp(tn, "dmacc", 5) == 0))
1921 /* Here is the rest of errata 23. */
1924 if (nops < min_nops)
1928 /* If we are being given a nop instruction, don't bother with
1929 one of the nops we would otherwise output. This will only
1930 happen when a nop instruction is used with mips_optimize set
1933 && ! mips_opts.noreorder
1934 && ip->insn_opcode == (unsigned) (mips_opts.mips16 ? 0x6500 : 0))
1937 /* Now emit the right number of NOP instructions. */
1938 if (nops > 0 && ! mips_opts.noreorder)
1941 unsigned long old_frag_offset;
1943 struct insn_label_list *l;
1945 old_frag = frag_now;
1946 old_frag_offset = frag_now_fix ();
1948 for (i = 0; i < nops; i++)
1953 listing_prev_line ();
1954 /* We may be at the start of a variant frag. In case we
1955 are, make sure there is enough space for the frag
1956 after the frags created by listing_prev_line. The
1957 argument to frag_grow here must be at least as large
1958 as the argument to all other calls to frag_grow in
1959 this file. We don't have to worry about being in the
1960 middle of a variant frag, because the variants insert
1961 all needed nop instructions themselves. */
1965 for (l = insn_labels; l != NULL; l = l->next)
1969 assert (S_GET_SEGMENT (l->label) == now_seg);
1970 symbol_set_frag (l->label, frag_now);
1971 val = (valueT) frag_now_fix ();
1972 /* mips16 text labels are stored as odd. */
1973 if (mips_opts.mips16)
1975 S_SET_VALUE (l->label, val);
1978 #ifndef NO_ECOFF_DEBUGGING
1979 if (ECOFF_DEBUGGING)
1980 ecoff_fix_loc (old_frag, old_frag_offset);
1983 else if (prev_nop_frag != NULL)
1985 /* We have a frag holding nops we may be able to remove. If
1986 we don't need any nops, we can decrease the size of
1987 prev_nop_frag by the size of one instruction. If we do
1988 need some nops, we count them in prev_nops_required. */
1989 if (prev_nop_frag_since == 0)
1993 prev_nop_frag->fr_fix -= mips_opts.mips16 ? 2 : 4;
1994 --prev_nop_frag_holds;
1997 prev_nop_frag_required += nops;
2001 if (prev_prev_nop == 0)
2003 prev_nop_frag->fr_fix -= mips_opts.mips16 ? 2 : 4;
2004 --prev_nop_frag_holds;
2007 ++prev_nop_frag_required;
2010 if (prev_nop_frag_holds <= prev_nop_frag_required)
2011 prev_nop_frag = NULL;
2013 ++prev_nop_frag_since;
2015 /* Sanity check: by the time we reach the second instruction
2016 after prev_nop_frag, we should have used up all the nops
2017 one way or another. */
2018 assert (prev_nop_frag_since <= 1 || prev_nop_frag == NULL);
2024 && *reloc_type == BFD_RELOC_16_PCREL_S2
2025 && (pinfo & INSN_UNCOND_BRANCH_DELAY || pinfo & INSN_COND_BRANCH_DELAY
2026 || pinfo & INSN_COND_BRANCH_LIKELY)
2027 && mips_relax_branch
2028 /* Don't try branch relaxation within .set nomacro, or within
2029 .set noat if we use $at for PIC computations. If it turns
2030 out that the branch was out-of-range, we'll get an error. */
2031 && !mips_opts.warn_about_macros
2032 && !(mips_opts.noat && mips_pic != NO_PIC)
2033 && !mips_opts.mips16)
2035 f = frag_var (rs_machine_dependent,
2036 relaxed_branch_length
2038 (pinfo & INSN_UNCOND_BRANCH_DELAY) ? -1
2039 : (pinfo & INSN_COND_BRANCH_LIKELY) ? 1 : 0), 4,
2041 (pinfo & INSN_UNCOND_BRANCH_DELAY,
2042 pinfo & INSN_COND_BRANCH_LIKELY,
2043 pinfo & INSN_WRITE_GPR_31,
2045 address_expr->X_add_symbol,
2046 address_expr->X_add_number,
2048 *reloc_type = BFD_RELOC_UNUSED;
2050 else if (*reloc_type > BFD_RELOC_UNUSED)
2052 /* We need to set up a variant frag. */
2053 assert (mips_opts.mips16 && address_expr != NULL);
2054 f = frag_var (rs_machine_dependent, 4, 0,
2055 RELAX_MIPS16_ENCODE (*reloc_type - BFD_RELOC_UNUSED,
2056 mips16_small, mips16_ext,
2058 & INSN_UNCOND_BRANCH_DELAY),
2059 (*prev_insn_reloc_type
2060 == BFD_RELOC_MIPS16_JMP)),
2061 make_expr_symbol (address_expr), 0, NULL);
2063 else if (place != NULL)
2065 else if (mips_opts.mips16
2067 && *reloc_type != BFD_RELOC_MIPS16_JMP)
2069 /* Make sure there is enough room to swap this instruction with
2070 a following jump instruction. */
2076 if (mips_opts.mips16
2077 && mips_opts.noreorder
2078 && (prev_pinfo & INSN_UNCOND_BRANCH_DELAY) != 0)
2079 as_warn (_("extended instruction in delay slot"));
2084 fixp[0] = fixp[1] = fixp[2] = NULL;
2085 if (address_expr != NULL && *reloc_type < BFD_RELOC_UNUSED)
2087 if (address_expr->X_op == O_constant)
2091 switch (*reloc_type)
2094 ip->insn_opcode |= address_expr->X_add_number;
2097 case BFD_RELOC_MIPS_HIGHEST:
2098 tmp = (address_expr->X_add_number + 0x800080008000) >> 16;
2100 ip->insn_opcode |= (tmp >> 16) & 0xffff;
2103 case BFD_RELOC_MIPS_HIGHER:
2104 tmp = (address_expr->X_add_number + 0x80008000) >> 16;
2105 ip->insn_opcode |= (tmp >> 16) & 0xffff;
2108 case BFD_RELOC_HI16_S:
2109 ip->insn_opcode |= ((address_expr->X_add_number + 0x8000)
2113 case BFD_RELOC_HI16:
2114 ip->insn_opcode |= (address_expr->X_add_number >> 16) & 0xffff;
2117 case BFD_RELOC_LO16:
2118 case BFD_RELOC_MIPS_GOT_DISP:
2119 ip->insn_opcode |= address_expr->X_add_number & 0xffff;
2122 case BFD_RELOC_MIPS_JMP:
2123 if ((address_expr->X_add_number & 3) != 0)
2124 as_bad (_("jump to misaligned address (0x%lx)"),
2125 (unsigned long) address_expr->X_add_number);
2126 if (address_expr->X_add_number & ~0xfffffff)
2127 as_bad (_("jump address range overflow (0x%lx)"),
2128 (unsigned long) address_expr->X_add_number);
2129 ip->insn_opcode |= (address_expr->X_add_number >> 2) & 0x3ffffff;
2132 case BFD_RELOC_MIPS16_JMP:
2133 if ((address_expr->X_add_number & 3) != 0)
2134 as_bad (_("jump to misaligned address (0x%lx)"),
2135 (unsigned long) address_expr->X_add_number);
2136 if (address_expr->X_add_number & ~0xfffffff)
2137 as_bad (_("jump address range overflow (0x%lx)"),
2138 (unsigned long) address_expr->X_add_number);
2140 (((address_expr->X_add_number & 0x7c0000) << 3)
2141 | ((address_expr->X_add_number & 0xf800000) >> 7)
2142 | ((address_expr->X_add_number & 0x3fffc) >> 2));
2145 case BFD_RELOC_16_PCREL_S2:
2155 /* Don't generate a reloc if we are writing into a variant frag. */
2158 fixp[0] = fix_new_exp (frag_now, f - frag_now->fr_literal, 4,
2160 *reloc_type == BFD_RELOC_16_PCREL_S2,
2163 /* These relocations can have an addend that won't fit in
2164 4 octets for 64bit assembly. */
2165 if (HAVE_64BIT_GPRS &&
2166 (*reloc_type == BFD_RELOC_16
2167 || *reloc_type == BFD_RELOC_32
2168 || *reloc_type == BFD_RELOC_MIPS_JMP
2169 || *reloc_type == BFD_RELOC_HI16_S
2170 || *reloc_type == BFD_RELOC_LO16
2171 || *reloc_type == BFD_RELOC_GPREL16
2172 || *reloc_type == BFD_RELOC_MIPS_LITERAL
2173 || *reloc_type == BFD_RELOC_GPREL32
2174 || *reloc_type == BFD_RELOC_64
2175 || *reloc_type == BFD_RELOC_CTOR
2176 || *reloc_type == BFD_RELOC_MIPS_SUB
2177 || *reloc_type == BFD_RELOC_MIPS_HIGHEST
2178 || *reloc_type == BFD_RELOC_MIPS_HIGHER
2179 || *reloc_type == BFD_RELOC_MIPS_SCN_DISP
2180 || *reloc_type == BFD_RELOC_MIPS_REL16
2181 || *reloc_type == BFD_RELOC_MIPS_RELGOT))
2182 fixp[0]->fx_no_overflow = 1;
2184 if (reloc_needs_lo_p (*reloc_type))
2186 struct mips_hi_fixup *hi_fixup;
2188 /* Reuse the last entry if it already has a matching %lo. */
2189 hi_fixup = mips_hi_fixup_list;
2191 || !fixup_has_matching_lo_p (hi_fixup->fixp))
2193 hi_fixup = ((struct mips_hi_fixup *)
2194 xmalloc (sizeof (struct mips_hi_fixup)));
2195 hi_fixup->next = mips_hi_fixup_list;
2196 mips_hi_fixup_list = hi_fixup;
2198 hi_fixup->fixp = fixp[0];
2199 hi_fixup->seg = now_seg;
2202 if (reloc_type[1] != BFD_RELOC_UNUSED)
2204 /* FIXME: This symbol can be one of
2205 RSS_UNDEF, RSS_GP, RSS_GP0, RSS_LOC. */
2206 address_expr->X_op = O_absent;
2207 address_expr->X_add_symbol = 0;
2208 address_expr->X_add_number = 0;
2210 fixp[1] = fix_new_exp (frag_now, f - frag_now->fr_literal,
2211 4, address_expr, FALSE,
2214 /* These relocations can have an addend that won't fit in
2215 4 octets for 64bit assembly. */
2216 if (HAVE_64BIT_GPRS &&
2217 (*reloc_type == BFD_RELOC_16
2218 || *reloc_type == BFD_RELOC_32
2219 || *reloc_type == BFD_RELOC_MIPS_JMP
2220 || *reloc_type == BFD_RELOC_HI16_S
2221 || *reloc_type == BFD_RELOC_LO16
2222 || *reloc_type == BFD_RELOC_GPREL16
2223 || *reloc_type == BFD_RELOC_MIPS_LITERAL
2224 || *reloc_type == BFD_RELOC_GPREL32
2225 || *reloc_type == BFD_RELOC_64
2226 || *reloc_type == BFD_RELOC_CTOR
2227 || *reloc_type == BFD_RELOC_MIPS_SUB
2228 || *reloc_type == BFD_RELOC_MIPS_HIGHEST
2229 || *reloc_type == BFD_RELOC_MIPS_HIGHER
2230 || *reloc_type == BFD_RELOC_MIPS_SCN_DISP
2231 || *reloc_type == BFD_RELOC_MIPS_REL16
2232 || *reloc_type == BFD_RELOC_MIPS_RELGOT))
2233 fixp[1]->fx_no_overflow = 1;
2235 if (reloc_type[2] != BFD_RELOC_UNUSED)
2237 address_expr->X_op = O_absent;
2238 address_expr->X_add_symbol = 0;
2239 address_expr->X_add_number = 0;
2241 fixp[2] = fix_new_exp (frag_now,
2242 f - frag_now->fr_literal, 4,
2243 address_expr, FALSE,
2246 /* These relocations can have an addend that won't fit in
2247 4 octets for 64bit assembly. */
2248 if (HAVE_64BIT_GPRS &&
2249 (*reloc_type == BFD_RELOC_16
2250 || *reloc_type == BFD_RELOC_32
2251 || *reloc_type == BFD_RELOC_MIPS_JMP
2252 || *reloc_type == BFD_RELOC_HI16_S
2253 || *reloc_type == BFD_RELOC_LO16
2254 || *reloc_type == BFD_RELOC_GPREL16
2255 || *reloc_type == BFD_RELOC_MIPS_LITERAL
2256 || *reloc_type == BFD_RELOC_GPREL32
2257 || *reloc_type == BFD_RELOC_64
2258 || *reloc_type == BFD_RELOC_CTOR
2259 || *reloc_type == BFD_RELOC_MIPS_SUB
2260 || *reloc_type == BFD_RELOC_MIPS_HIGHEST
2261 || *reloc_type == BFD_RELOC_MIPS_HIGHER
2262 || *reloc_type == BFD_RELOC_MIPS_SCN_DISP
2263 || *reloc_type == BFD_RELOC_MIPS_REL16
2264 || *reloc_type == BFD_RELOC_MIPS_RELGOT))
2265 fixp[2]->fx_no_overflow = 1;
2272 if (! mips_opts.mips16)
2274 md_number_to_chars (f, ip->insn_opcode, 4);
2276 dwarf2_emit_insn (4);
2279 else if (*reloc_type == BFD_RELOC_MIPS16_JMP)
2281 md_number_to_chars (f, ip->insn_opcode >> 16, 2);
2282 md_number_to_chars (f + 2, ip->insn_opcode & 0xffff, 2);
2284 dwarf2_emit_insn (4);
2291 md_number_to_chars (f, 0xf000 | ip->extend, 2);
2294 md_number_to_chars (f, ip->insn_opcode, 2);
2296 dwarf2_emit_insn (ip->use_extend ? 4 : 2);
2300 /* Update the register mask information. */
2301 if (! mips_opts.mips16)
2303 if (pinfo & INSN_WRITE_GPR_D)
2304 mips_gprmask |= 1 << ((ip->insn_opcode >> OP_SH_RD) & OP_MASK_RD);
2305 if ((pinfo & (INSN_WRITE_GPR_T | INSN_READ_GPR_T)) != 0)
2306 mips_gprmask |= 1 << ((ip->insn_opcode >> OP_SH_RT) & OP_MASK_RT);
2307 if (pinfo & INSN_READ_GPR_S)
2308 mips_gprmask |= 1 << ((ip->insn_opcode >> OP_SH_RS) & OP_MASK_RS);
2309 if (pinfo & INSN_WRITE_GPR_31)
2310 mips_gprmask |= 1 << RA;
2311 if (pinfo & INSN_WRITE_FPR_D)
2312 mips_cprmask[1] |= 1 << ((ip->insn_opcode >> OP_SH_FD) & OP_MASK_FD);
2313 if ((pinfo & (INSN_WRITE_FPR_S | INSN_READ_FPR_S)) != 0)
2314 mips_cprmask[1] |= 1 << ((ip->insn_opcode >> OP_SH_FS) & OP_MASK_FS);
2315 if ((pinfo & (INSN_WRITE_FPR_T | INSN_READ_FPR_T)) != 0)
2316 mips_cprmask[1] |= 1 << ((ip->insn_opcode >> OP_SH_FT) & OP_MASK_FT);
2317 if ((pinfo & INSN_READ_FPR_R) != 0)
2318 mips_cprmask[1] |= 1 << ((ip->insn_opcode >> OP_SH_FR) & OP_MASK_FR);
2319 if (pinfo & INSN_COP)
2321 /* We don't keep enough information to sort these cases out.
2322 The itbl support does keep this information however, although
2323 we currently don't support itbl fprmats as part of the cop
2324 instruction. May want to add this support in the future. */
2326 /* Never set the bit for $0, which is always zero. */
2327 mips_gprmask &= ~1 << 0;
2331 if (pinfo & (MIPS16_INSN_WRITE_X | MIPS16_INSN_READ_X))
2332 mips_gprmask |= 1 << ((ip->insn_opcode >> MIPS16OP_SH_RX)
2333 & MIPS16OP_MASK_RX);
2334 if (pinfo & (MIPS16_INSN_WRITE_Y | MIPS16_INSN_READ_Y))
2335 mips_gprmask |= 1 << ((ip->insn_opcode >> MIPS16OP_SH_RY)
2336 & MIPS16OP_MASK_RY);
2337 if (pinfo & MIPS16_INSN_WRITE_Z)
2338 mips_gprmask |= 1 << ((ip->insn_opcode >> MIPS16OP_SH_RZ)
2339 & MIPS16OP_MASK_RZ);
2340 if (pinfo & (MIPS16_INSN_WRITE_T | MIPS16_INSN_READ_T))
2341 mips_gprmask |= 1 << TREG;
2342 if (pinfo & (MIPS16_INSN_WRITE_SP | MIPS16_INSN_READ_SP))
2343 mips_gprmask |= 1 << SP;
2344 if (pinfo & (MIPS16_INSN_WRITE_31 | MIPS16_INSN_READ_31))
2345 mips_gprmask |= 1 << RA;
2346 if (pinfo & MIPS16_INSN_WRITE_GPR_Y)
2347 mips_gprmask |= 1 << MIPS16OP_EXTRACT_REG32R (ip->insn_opcode);
2348 if (pinfo & MIPS16_INSN_READ_Z)
2349 mips_gprmask |= 1 << ((ip->insn_opcode >> MIPS16OP_SH_MOVE32Z)
2350 & MIPS16OP_MASK_MOVE32Z);
2351 if (pinfo & MIPS16_INSN_READ_GPR_X)
2352 mips_gprmask |= 1 << ((ip->insn_opcode >> MIPS16OP_SH_REGR32)
2353 & MIPS16OP_MASK_REGR32);
2356 if (place == NULL && ! mips_opts.noreorder)
2358 /* Filling the branch delay slot is more complex. We try to
2359 switch the branch with the previous instruction, which we can
2360 do if the previous instruction does not set up a condition
2361 that the branch tests and if the branch is not itself the
2362 target of any branch. */
2363 if ((pinfo & INSN_UNCOND_BRANCH_DELAY)
2364 || (pinfo & INSN_COND_BRANCH_DELAY))
2366 if (mips_optimize < 2
2367 /* If we have seen .set volatile or .set nomove, don't
2369 || mips_opts.nomove != 0
2370 /* If we had to emit any NOP instructions, then we
2371 already know we can not swap. */
2373 /* If we don't even know the previous insn, we can not
2375 || ! prev_insn_valid
2376 /* If the previous insn is already in a branch delay
2377 slot, then we can not swap. */
2378 || prev_insn_is_delay_slot
2379 /* If the previous previous insn was in a .set
2380 noreorder, we can't swap. Actually, the MIPS
2381 assembler will swap in this situation. However, gcc
2382 configured -with-gnu-as will generate code like
2388 in which we can not swap the bne and INSN. If gcc is
2389 not configured -with-gnu-as, it does not output the
2390 .set pseudo-ops. We don't have to check
2391 prev_insn_unreordered, because prev_insn_valid will
2392 be 0 in that case. We don't want to use
2393 prev_prev_insn_valid, because we do want to be able
2394 to swap at the start of a function. */
2395 || prev_prev_insn_unreordered
2396 /* If the branch is itself the target of a branch, we
2397 can not swap. We cheat on this; all we check for is
2398 whether there is a label on this instruction. If
2399 there are any branches to anything other than a
2400 label, users must use .set noreorder. */
2401 || insn_labels != NULL
2402 /* If the previous instruction is in a variant frag, we
2403 can not do the swap. This does not apply to the
2404 mips16, which uses variant frags for different
2406 || (! mips_opts.mips16
2407 && prev_insn_frag->fr_type == rs_machine_dependent)
2408 /* If the branch reads the condition codes, we don't
2409 even try to swap, because in the sequence
2414 we can not swap, and I don't feel like handling that
2416 || (! mips_opts.mips16
2417 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
2418 && (pinfo & INSN_READ_COND_CODE))
2419 /* We can not swap with an instruction that requires a
2420 delay slot, becase the target of the branch might
2421 interfere with that instruction. */
2422 || (! mips_opts.mips16
2423 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
2425 /* Itbl support may require additional care here. */
2426 & (INSN_LOAD_COPROC_DELAY
2427 | INSN_COPROC_MOVE_DELAY
2428 | INSN_WRITE_COND_CODE)))
2429 || (! (hilo_interlocks
2430 || (mips_tune == CPU_R3900 && (pinfo & INSN_MULT)))
2434 || (! mips_opts.mips16
2436 && (prev_pinfo & INSN_LOAD_MEMORY_DELAY))
2437 || (! mips_opts.mips16
2438 && mips_opts.isa == ISA_MIPS1
2439 /* Itbl support may require additional care here. */
2440 && (prev_pinfo & INSN_COPROC_MEMORY_DELAY))
2441 /* We can not swap with a branch instruction. */
2443 & (INSN_UNCOND_BRANCH_DELAY
2444 | INSN_COND_BRANCH_DELAY
2445 | INSN_COND_BRANCH_LIKELY))
2446 /* We do not swap with a trap instruction, since it
2447 complicates trap handlers to have the trap
2448 instruction be in a delay slot. */
2449 || (prev_pinfo & INSN_TRAP)
2450 /* If the branch reads a register that the previous
2451 instruction sets, we can not swap. */
2452 || (! mips_opts.mips16
2453 && (prev_pinfo & INSN_WRITE_GPR_T)
2454 && insn_uses_reg (ip,
2455 ((prev_insn.insn_opcode >> OP_SH_RT)
2458 || (! mips_opts.mips16
2459 && (prev_pinfo & INSN_WRITE_GPR_D)
2460 && insn_uses_reg (ip,
2461 ((prev_insn.insn_opcode >> OP_SH_RD)
2464 || (mips_opts.mips16
2465 && (((prev_pinfo & MIPS16_INSN_WRITE_X)
2466 && insn_uses_reg (ip,
2467 ((prev_insn.insn_opcode
2469 & MIPS16OP_MASK_RX),
2471 || ((prev_pinfo & MIPS16_INSN_WRITE_Y)
2472 && insn_uses_reg (ip,
2473 ((prev_insn.insn_opcode
2475 & MIPS16OP_MASK_RY),
2477 || ((prev_pinfo & MIPS16_INSN_WRITE_Z)
2478 && insn_uses_reg (ip,
2479 ((prev_insn.insn_opcode
2481 & MIPS16OP_MASK_RZ),
2483 || ((prev_pinfo & MIPS16_INSN_WRITE_T)
2484 && insn_uses_reg (ip, TREG, MIPS_GR_REG))
2485 || ((prev_pinfo & MIPS16_INSN_WRITE_31)
2486 && insn_uses_reg (ip, RA, MIPS_GR_REG))
2487 || ((prev_pinfo & MIPS16_INSN_WRITE_GPR_Y)
2488 && insn_uses_reg (ip,
2489 MIPS16OP_EXTRACT_REG32R (prev_insn.
2492 /* If the branch writes a register that the previous
2493 instruction sets, we can not swap (we know that
2494 branches write only to RD or to $31). */
2495 || (! mips_opts.mips16
2496 && (prev_pinfo & INSN_WRITE_GPR_T)
2497 && (((pinfo & INSN_WRITE_GPR_D)
2498 && (((prev_insn.insn_opcode >> OP_SH_RT) & OP_MASK_RT)
2499 == ((ip->insn_opcode >> OP_SH_RD) & OP_MASK_RD)))
2500 || ((pinfo & INSN_WRITE_GPR_31)
2501 && (((prev_insn.insn_opcode >> OP_SH_RT)
2504 || (! mips_opts.mips16
2505 && (prev_pinfo & INSN_WRITE_GPR_D)
2506 && (((pinfo & INSN_WRITE_GPR_D)
2507 && (((prev_insn.insn_opcode >> OP_SH_RD) & OP_MASK_RD)
2508 == ((ip->insn_opcode >> OP_SH_RD) & OP_MASK_RD)))
2509 || ((pinfo & INSN_WRITE_GPR_31)
2510 && (((prev_insn.insn_opcode >> OP_SH_RD)
2513 || (mips_opts.mips16
2514 && (pinfo & MIPS16_INSN_WRITE_31)
2515 && ((prev_pinfo & MIPS16_INSN_WRITE_31)
2516 || ((prev_pinfo & MIPS16_INSN_WRITE_GPR_Y)
2517 && (MIPS16OP_EXTRACT_REG32R (prev_insn.insn_opcode)
2519 /* If the branch writes a register that the previous
2520 instruction reads, we can not swap (we know that
2521 branches only write to RD or to $31). */
2522 || (! mips_opts.mips16
2523 && (pinfo & INSN_WRITE_GPR_D)
2524 && insn_uses_reg (&prev_insn,
2525 ((ip->insn_opcode >> OP_SH_RD)
2528 || (! mips_opts.mips16
2529 && (pinfo & INSN_WRITE_GPR_31)
2530 && insn_uses_reg (&prev_insn, RA, MIPS_GR_REG))
2531 || (mips_opts.mips16
2532 && (pinfo & MIPS16_INSN_WRITE_31)
2533 && insn_uses_reg (&prev_insn, RA, MIPS_GR_REG))
2534 /* If we are generating embedded PIC code, the branch
2535 might be expanded into a sequence which uses $at, so
2536 we can't swap with an instruction which reads it. */
2537 || (mips_pic == EMBEDDED_PIC
2538 && insn_uses_reg (&prev_insn, AT, MIPS_GR_REG))
2539 /* If the previous previous instruction has a load
2540 delay, and sets a register that the branch reads, we
2542 || (! mips_opts.mips16
2543 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
2544 /* Itbl support may require additional care here. */
2545 && ((prev_prev_insn.insn_mo->pinfo & INSN_LOAD_COPROC_DELAY)
2546 || (! gpr_interlocks
2547 && (prev_prev_insn.insn_mo->pinfo
2548 & INSN_LOAD_MEMORY_DELAY)))
2549 && insn_uses_reg (ip,
2550 ((prev_prev_insn.insn_opcode >> OP_SH_RT)
2553 /* If one instruction sets a condition code and the
2554 other one uses a condition code, we can not swap. */
2555 || ((pinfo & INSN_READ_COND_CODE)
2556 && (prev_pinfo & INSN_WRITE_COND_CODE))
2557 || ((pinfo & INSN_WRITE_COND_CODE)
2558 && (prev_pinfo & INSN_READ_COND_CODE))
2559 /* If the previous instruction uses the PC, we can not
2561 || (mips_opts.mips16
2562 && (prev_pinfo & MIPS16_INSN_READ_PC))
2563 /* If the previous instruction was extended, we can not
2565 || (mips_opts.mips16 && prev_insn_extended)
2566 /* If the previous instruction had a fixup in mips16
2567 mode, we can not swap. This normally means that the
2568 previous instruction was a 4 byte branch anyhow. */
2569 || (mips_opts.mips16 && prev_insn_fixp[0])
2570 /* If the previous instruction is a sync, sync.l, or
2571 sync.p, we can not swap. */
2572 || (prev_pinfo & INSN_SYNC))
2574 /* We could do even better for unconditional branches to
2575 portions of this object file; we could pick up the
2576 instruction at the destination, put it in the delay
2577 slot, and bump the destination address. */
2579 /* Update the previous insn information. */
2580 prev_prev_insn = *ip;
2581 prev_insn.insn_mo = &dummy_opcode;
2585 /* It looks like we can actually do the swap. */
2586 if (! mips_opts.mips16)
2591 prev_f = prev_insn_frag->fr_literal + prev_insn_where;
2592 memcpy (temp, prev_f, 4);
2593 memcpy (prev_f, f, 4);
2594 memcpy (f, temp, 4);
2595 if (prev_insn_fixp[0])
2597 prev_insn_fixp[0]->fx_frag = frag_now;
2598 prev_insn_fixp[0]->fx_where = f - frag_now->fr_literal;
2600 if (prev_insn_fixp[1])
2602 prev_insn_fixp[1]->fx_frag = frag_now;
2603 prev_insn_fixp[1]->fx_where = f - frag_now->fr_literal;
2605 if (prev_insn_fixp[2])
2607 prev_insn_fixp[2]->fx_frag = frag_now;
2608 prev_insn_fixp[2]->fx_where = f - frag_now->fr_literal;
2610 if (prev_insn_fixp[0] && HAVE_NEWABI
2611 && prev_insn_frag != frag_now
2612 && (prev_insn_fixp[0]->fx_r_type
2613 == BFD_RELOC_MIPS_GOT_DISP
2614 || (prev_insn_fixp[0]->fx_r_type
2615 == BFD_RELOC_MIPS_CALL16)))
2617 /* To avoid confusion in tc_gen_reloc, we must
2618 ensure that this does not become a variant
2620 force_new_frag = TRUE;
2624 fixp[0]->fx_frag = prev_insn_frag;
2625 fixp[0]->fx_where = prev_insn_where;
2629 fixp[1]->fx_frag = prev_insn_frag;
2630 fixp[1]->fx_where = prev_insn_where;
2634 fixp[2]->fx_frag = prev_insn_frag;
2635 fixp[2]->fx_where = prev_insn_where;
2643 assert (prev_insn_fixp[0] == NULL);
2644 assert (prev_insn_fixp[1] == NULL);
2645 assert (prev_insn_fixp[2] == NULL);
2646 prev_f = prev_insn_frag->fr_literal + prev_insn_where;
2647 memcpy (temp, prev_f, 2);
2648 memcpy (prev_f, f, 2);
2649 if (*reloc_type != BFD_RELOC_MIPS16_JMP)
2651 assert (*reloc_type == BFD_RELOC_UNUSED);
2652 memcpy (f, temp, 2);
2656 memcpy (f, f + 2, 2);
2657 memcpy (f + 2, temp, 2);
2661 fixp[0]->fx_frag = prev_insn_frag;
2662 fixp[0]->fx_where = prev_insn_where;
2666 fixp[1]->fx_frag = prev_insn_frag;
2667 fixp[1]->fx_where = prev_insn_where;
2671 fixp[2]->fx_frag = prev_insn_frag;
2672 fixp[2]->fx_where = prev_insn_where;
2676 /* Update the previous insn information; leave prev_insn
2678 prev_prev_insn = *ip;
2680 prev_insn_is_delay_slot = 1;
2682 /* If that was an unconditional branch, forget the previous
2683 insn information. */
2684 if (pinfo & INSN_UNCOND_BRANCH_DELAY)
2686 prev_prev_insn.insn_mo = &dummy_opcode;
2687 prev_insn.insn_mo = &dummy_opcode;
2690 prev_insn_fixp[0] = NULL;
2691 prev_insn_fixp[1] = NULL;
2692 prev_insn_fixp[2] = NULL;
2693 prev_insn_reloc_type[0] = BFD_RELOC_UNUSED;
2694 prev_insn_reloc_type[1] = BFD_RELOC_UNUSED;
2695 prev_insn_reloc_type[2] = BFD_RELOC_UNUSED;
2696 prev_insn_extended = 0;
2698 else if (pinfo & INSN_COND_BRANCH_LIKELY)
2700 /* We don't yet optimize a branch likely. What we should do
2701 is look at the target, copy the instruction found there
2702 into the delay slot, and increment the branch to jump to
2703 the next instruction. */
2705 /* Update the previous insn information. */
2706 prev_prev_insn = *ip;
2707 prev_insn.insn_mo = &dummy_opcode;
2708 prev_insn_fixp[0] = NULL;
2709 prev_insn_fixp[1] = NULL;
2710 prev_insn_fixp[2] = NULL;
2711 prev_insn_reloc_type[0] = BFD_RELOC_UNUSED;
2712 prev_insn_reloc_type[1] = BFD_RELOC_UNUSED;
2713 prev_insn_reloc_type[2] = BFD_RELOC_UNUSED;
2714 prev_insn_extended = 0;
2718 /* Update the previous insn information. */
2720 prev_prev_insn.insn_mo = &dummy_opcode;
2722 prev_prev_insn = prev_insn;
2725 /* Any time we see a branch, we always fill the delay slot
2726 immediately; since this insn is not a branch, we know it
2727 is not in a delay slot. */
2728 prev_insn_is_delay_slot = 0;
2730 prev_insn_fixp[0] = fixp[0];
2731 prev_insn_fixp[1] = fixp[1];
2732 prev_insn_fixp[2] = fixp[2];
2733 prev_insn_reloc_type[0] = reloc_type[0];
2734 prev_insn_reloc_type[1] = reloc_type[1];
2735 prev_insn_reloc_type[2] = reloc_type[2];
2736 if (mips_opts.mips16)
2737 prev_insn_extended = (ip->use_extend
2738 || *reloc_type > BFD_RELOC_UNUSED);
2741 prev_prev_insn_unreordered = prev_insn_unreordered;
2742 prev_insn_unreordered = 0;
2743 prev_insn_frag = frag_now;
2744 prev_insn_where = f - frag_now->fr_literal;
2745 prev_insn_valid = 1;
2747 else if (place == NULL)
2749 /* We need to record a bit of information even when we are not
2750 reordering, in order to determine the base address for mips16
2751 PC relative relocs. */
2752 prev_prev_insn = prev_insn;
2754 prev_insn_reloc_type[0] = reloc_type[0];
2755 prev_insn_reloc_type[1] = reloc_type[1];
2756 prev_insn_reloc_type[2] = reloc_type[2];
2757 prev_prev_insn_unreordered = prev_insn_unreordered;
2758 prev_insn_unreordered = 1;
2761 /* We just output an insn, so the next one doesn't have a label. */
2762 mips_clear_insn_labels ();
2764 /* We must ensure that the frag to which an instruction that was
2765 moved from a non-variant frag doesn't become a variant frag,
2766 otherwise tc_gen_reloc may get confused. */
2769 frag_wane (frag_now);
2774 /* This function forgets that there was any previous instruction or
2775 label. If PRESERVE is non-zero, it remembers enough information to
2776 know whether nops are needed before a noreorder section. */
2779 mips_no_prev_insn (preserve)
2784 prev_insn.insn_mo = &dummy_opcode;
2785 prev_prev_insn.insn_mo = &dummy_opcode;
2786 prev_nop_frag = NULL;
2787 prev_nop_frag_holds = 0;
2788 prev_nop_frag_required = 0;
2789 prev_nop_frag_since = 0;
2791 prev_insn_valid = 0;
2792 prev_insn_is_delay_slot = 0;
2793 prev_insn_unreordered = 0;
2794 prev_insn_extended = 0;
2795 prev_insn_reloc_type[0] = BFD_RELOC_UNUSED;
2796 prev_insn_reloc_type[1] = BFD_RELOC_UNUSED;
2797 prev_insn_reloc_type[2] = BFD_RELOC_UNUSED;
2798 prev_prev_insn_unreordered = 0;
2799 mips_clear_insn_labels ();
2802 /* This function must be called whenever we turn on noreorder or emit
2803 something other than instructions. It inserts any NOPS which might
2804 be needed by the previous instruction, and clears the information
2805 kept for the previous instructions. The INSNS parameter is true if
2806 instructions are to follow. */
2809 mips_emit_delays (insns)
2812 if (! mips_opts.noreorder)
2817 if ((! mips_opts.mips16
2818 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
2819 && (! cop_interlocks
2820 && (prev_insn.insn_mo->pinfo
2821 & (INSN_LOAD_COPROC_DELAY
2822 | INSN_COPROC_MOVE_DELAY
2823 | INSN_WRITE_COND_CODE))))
2824 || (! hilo_interlocks
2825 && (prev_insn.insn_mo->pinfo
2828 || (! mips_opts.mips16
2830 && (prev_insn.insn_mo->pinfo
2831 & INSN_LOAD_MEMORY_DELAY))
2832 || (! mips_opts.mips16
2833 && mips_opts.isa == ISA_MIPS1
2834 && (prev_insn.insn_mo->pinfo
2835 & INSN_COPROC_MEMORY_DELAY)))
2837 /* Itbl support may require additional care here. */
2839 if ((! mips_opts.mips16
2840 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
2841 && (! cop_interlocks
2842 && prev_insn.insn_mo->pinfo & INSN_WRITE_COND_CODE))
2843 || (! hilo_interlocks
2844 && ((prev_insn.insn_mo->pinfo & INSN_READ_HI)
2845 || (prev_insn.insn_mo->pinfo & INSN_READ_LO))))
2848 if (prev_insn_unreordered)
2851 else if ((! mips_opts.mips16
2852 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
2853 && (! cop_interlocks
2854 && prev_prev_insn.insn_mo->pinfo & INSN_WRITE_COND_CODE))
2855 || (! hilo_interlocks
2856 && ((prev_prev_insn.insn_mo->pinfo & INSN_READ_HI)
2857 || (prev_prev_insn.insn_mo->pinfo & INSN_READ_LO))))
2859 /* Itbl support may require additional care here. */
2860 if (! prev_prev_insn_unreordered)
2864 if (mips_fix_4122_bugs && prev_insn.insn_mo->name)
2867 const char *pn = prev_insn.insn_mo->name;
2868 if (strncmp(pn, "macc", 4) == 0
2869 || strncmp(pn, "dmacc", 5) == 0
2870 || strncmp(pn, "dmult", 5) == 0)
2874 if (nops < min_nops)
2880 struct insn_label_list *l;
2884 /* Record the frag which holds the nop instructions, so
2885 that we can remove them if we don't need them. */
2886 frag_grow (mips_opts.mips16 ? nops * 2 : nops * 4);
2887 prev_nop_frag = frag_now;
2888 prev_nop_frag_holds = nops;
2889 prev_nop_frag_required = 0;
2890 prev_nop_frag_since = 0;
2893 for (; nops > 0; --nops)
2898 /* Move on to a new frag, so that it is safe to simply
2899 decrease the size of prev_nop_frag. */
2900 frag_wane (frag_now);
2904 for (l = insn_labels; l != NULL; l = l->next)
2908 assert (S_GET_SEGMENT (l->label) == now_seg);
2909 symbol_set_frag (l->label, frag_now);
2910 val = (valueT) frag_now_fix ();
2911 /* mips16 text labels are stored as odd. */
2912 if (mips_opts.mips16)
2914 S_SET_VALUE (l->label, val);
2919 /* Mark instruction labels in mips16 mode. */
2921 mips16_mark_labels ();
2923 mips_no_prev_insn (insns);
2926 /* Build an instruction created by a macro expansion. This is passed
2927 a pointer to the count of instructions created so far, an
2928 expression, the name of the instruction to build, an operand format
2929 string, and corresponding arguments. */
2933 macro_build (char *place,
2941 macro_build (place, counter, ep, name, fmt, va_alist)
2950 struct mips_cl_insn insn;
2951 bfd_reloc_code_real_type r[3];
2955 va_start (args, fmt);
2961 * If the macro is about to expand into a second instruction,
2962 * print a warning if needed. We need to pass ip as a parameter
2963 * to generate a better warning message here...
2965 if (mips_opts.warn_about_macros && place == NULL && *counter == 1)
2966 as_warn (_("Macro instruction expanded into multiple instructions"));
2969 * If the macro is about to expand into a second instruction,
2970 * and it is in a delay slot, print a warning.
2974 && mips_opts.noreorder
2975 && (prev_prev_insn.insn_mo->pinfo
2976 & (INSN_UNCOND_BRANCH_DELAY | INSN_COND_BRANCH_DELAY
2977 | INSN_COND_BRANCH_LIKELY)) != 0)
2978 as_warn (_("Macro instruction expanded into multiple instructions in a branch delay slot"));
2981 ++*counter; /* bump instruction counter */
2983 if (mips_opts.mips16)
2985 mips16_macro_build (place, counter, ep, name, fmt, args);
2990 r[0] = BFD_RELOC_UNUSED;
2991 r[1] = BFD_RELOC_UNUSED;
2992 r[2] = BFD_RELOC_UNUSED;
2993 insn.insn_mo = (struct mips_opcode *) hash_find (op_hash, name);
2994 assert (insn.insn_mo);
2995 assert (strcmp (name, insn.insn_mo->name) == 0);
2997 /* Search until we get a match for NAME. */
3000 /* It is assumed here that macros will never generate
3001 MDMX or MIPS-3D instructions. */
3002 if (strcmp (fmt, insn.insn_mo->args) == 0
3003 && insn.insn_mo->pinfo != INSN_MACRO
3004 && OPCODE_IS_MEMBER (insn.insn_mo,
3006 | (file_ase_mips16 ? INSN_MIPS16 : 0)),
3008 && (mips_arch != CPU_R4650 || (insn.insn_mo->pinfo & FP_D) == 0))
3012 assert (insn.insn_mo->name);
3013 assert (strcmp (name, insn.insn_mo->name) == 0);
3016 insn.insn_opcode = insn.insn_mo->match;
3032 insn.insn_opcode |= va_arg (args, int) << OP_SH_RT;
3036 insn.insn_opcode |= va_arg (args, int) << OP_SH_CODE;
3041 insn.insn_opcode |= va_arg (args, int) << OP_SH_FT;
3047 insn.insn_opcode |= va_arg (args, int) << OP_SH_RD;
3052 int tmp = va_arg (args, int);
3054 insn.insn_opcode |= tmp << OP_SH_RT;
3055 insn.insn_opcode |= tmp << OP_SH_RD;
3061 insn.insn_opcode |= va_arg (args, int) << OP_SH_FS;
3068 insn.insn_opcode |= va_arg (args, int) << OP_SH_SHAMT;
3072 insn.insn_opcode |= va_arg (args, int) << OP_SH_FD;
3076 insn.insn_opcode |= va_arg (args, int) << OP_SH_CODE20;
3080 insn.insn_opcode |= va_arg (args, int) << OP_SH_CODE19;
3084 insn.insn_opcode |= va_arg (args, int) << OP_SH_CODE2;
3091 insn.insn_opcode |= va_arg (args, int) << OP_SH_RS;
3097 *r = (bfd_reloc_code_real_type) va_arg (args, int);
3098 assert (*r == BFD_RELOC_GPREL16
3099 || *r == BFD_RELOC_MIPS_LITERAL
3100 || *r == BFD_RELOC_MIPS_HIGHER
3101 || *r == BFD_RELOC_HI16_S
3102 || *r == BFD_RELOC_LO16
3103 || *r == BFD_RELOC_MIPS_GOT16
3104 || *r == BFD_RELOC_MIPS_CALL16
3105 || *r == BFD_RELOC_MIPS_GOT_DISP
3106 || *r == BFD_RELOC_MIPS_GOT_PAGE
3107 || *r == BFD_RELOC_MIPS_GOT_OFST
3108 || *r == BFD_RELOC_MIPS_GOT_LO16
3109 || *r == BFD_RELOC_MIPS_CALL_LO16
3110 || (ep->X_op == O_subtract
3111 && *r == BFD_RELOC_PCREL_LO16));
3115 *r = (bfd_reloc_code_real_type) va_arg (args, int);
3117 && (ep->X_op == O_constant
3118 || (ep->X_op == O_symbol
3119 && (*r == BFD_RELOC_MIPS_HIGHEST
3120 || *r == BFD_RELOC_HI16_S
3121 || *r == BFD_RELOC_HI16
3122 || *r == BFD_RELOC_GPREL16
3123 || *r == BFD_RELOC_MIPS_GOT_HI16
3124 || *r == BFD_RELOC_MIPS_CALL_HI16))
3125 || (ep->X_op == O_subtract
3126 && *r == BFD_RELOC_PCREL_HI16_S)));
3130 assert (ep != NULL);
3132 * This allows macro() to pass an immediate expression for
3133 * creating short branches without creating a symbol.
3134 * Note that the expression still might come from the assembly
3135 * input, in which case the value is not checked for range nor
3136 * is a relocation entry generated (yuck).
3138 if (ep->X_op == O_constant)
3140 insn.insn_opcode |= (ep->X_add_number >> 2) & 0xffff;
3144 *r = BFD_RELOC_16_PCREL_S2;
3148 assert (ep != NULL);
3149 *r = BFD_RELOC_MIPS_JMP;
3153 insn.insn_opcode |= va_arg (args, unsigned long);
3162 assert (*r == BFD_RELOC_UNUSED ? ep == NULL : ep != NULL);
3164 append_insn (place, &insn, ep, r);
3168 mips16_macro_build (place, counter, ep, name, fmt, args)
3170 int *counter ATTRIBUTE_UNUSED;
3176 struct mips_cl_insn insn;
3177 bfd_reloc_code_real_type r[3]
3178 = {BFD_RELOC_UNUSED, BFD_RELOC_UNUSED, BFD_RELOC_UNUSED};
3180 insn.insn_mo = (struct mips_opcode *) hash_find (mips16_op_hash, name);
3181 assert (insn.insn_mo);
3182 assert (strcmp (name, insn.insn_mo->name) == 0);
3184 while (strcmp (fmt, insn.insn_mo->args) != 0
3185 || insn.insn_mo->pinfo == INSN_MACRO)
3188 assert (insn.insn_mo->name);
3189 assert (strcmp (name, insn.insn_mo->name) == 0);
3192 insn.insn_opcode = insn.insn_mo->match;
3193 insn.use_extend = FALSE;
3212 insn.insn_opcode |= va_arg (args, int) << MIPS16OP_SH_RY;
3217 insn.insn_opcode |= va_arg (args, int) << MIPS16OP_SH_RX;
3221 insn.insn_opcode |= va_arg (args, int) << MIPS16OP_SH_RZ;
3225 insn.insn_opcode |= va_arg (args, int) << MIPS16OP_SH_MOVE32Z;
3235 insn.insn_opcode |= va_arg (args, int) << MIPS16OP_SH_REGR32;
3242 regno = va_arg (args, int);
3243 regno = ((regno & 7) << 2) | ((regno & 0x18) >> 3);
3244 insn.insn_opcode |= regno << MIPS16OP_SH_REG32R;
3265 assert (ep != NULL);
3267 if (ep->X_op != O_constant)
3268 *r = (int) BFD_RELOC_UNUSED + c;
3271 mips16_immed (NULL, 0, c, ep->X_add_number, FALSE, FALSE,
3272 FALSE, &insn.insn_opcode, &insn.use_extend,
3275 *r = BFD_RELOC_UNUSED;
3281 insn.insn_opcode |= va_arg (args, int) << MIPS16OP_SH_IMM6;
3288 assert (*r == BFD_RELOC_UNUSED ? ep == NULL : ep != NULL);
3290 append_insn (place, &insn, ep, r);
3294 * Generate a "jalr" instruction with a relocation hint to the called
3295 * function. This occurs in NewABI PIC code.
3298 macro_build_jalr (icnt, ep)
3309 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "jalr", "d,s",
3312 fix_new_exp (frag_now, f - frag_now->fr_literal,
3313 0, ep, FALSE, BFD_RELOC_MIPS_JALR);
3317 * Generate a "lui" instruction.
3320 macro_build_lui (place, counter, ep, regnum)
3326 expressionS high_expr;
3327 struct mips_cl_insn insn;
3328 bfd_reloc_code_real_type r[3]
3329 = {BFD_RELOC_UNUSED, BFD_RELOC_UNUSED, BFD_RELOC_UNUSED};
3330 const char *name = "lui";
3331 const char *fmt = "t,u";
3333 assert (! mips_opts.mips16);
3339 high_expr.X_op = O_constant;
3340 high_expr.X_add_number = ep->X_add_number;
3343 if (high_expr.X_op == O_constant)
3345 /* we can compute the instruction now without a relocation entry */
3346 high_expr.X_add_number = ((high_expr.X_add_number + 0x8000)
3348 *r = BFD_RELOC_UNUSED;
3352 assert (ep->X_op == O_symbol);
3353 /* _gp_disp is a special case, used from s_cpload. */
3354 assert (mips_pic == NO_PIC
3356 && strcmp (S_GET_NAME (ep->X_add_symbol), "_gp_disp") == 0));
3357 *r = BFD_RELOC_HI16_S;
3361 * If the macro is about to expand into a second instruction,
3362 * print a warning if needed. We need to pass ip as a parameter
3363 * to generate a better warning message here...
3365 if (mips_opts.warn_about_macros && place == NULL && *counter == 1)
3366 as_warn (_("Macro instruction expanded into multiple instructions"));
3369 ++*counter; /* bump instruction counter */
3371 insn.insn_mo = (struct mips_opcode *) hash_find (op_hash, name);
3372 assert (insn.insn_mo);
3373 assert (strcmp (name, insn.insn_mo->name) == 0);
3374 assert (strcmp (fmt, insn.insn_mo->args) == 0);
3376 insn.insn_opcode = insn.insn_mo->match | (regnum << OP_SH_RT);
3377 if (*r == BFD_RELOC_UNUSED)
3379 insn.insn_opcode |= high_expr.X_add_number;
3380 append_insn (place, &insn, NULL, r);
3383 append_insn (place, &insn, &high_expr, r);
3386 /* Generate a sequence of instructions to do a load or store from a constant
3387 offset off of a base register (breg) into/from a target register (treg),
3388 using AT if necessary. */
3390 macro_build_ldst_constoffset (place, counter, ep, op, treg, breg)
3397 assert (ep->X_op == O_constant);
3399 /* Right now, this routine can only handle signed 32-bit contants. */
3400 if (! IS_SEXT_32BIT_NUM(ep->X_add_number))
3401 as_warn (_("operand overflow"));
3403 if (IS_SEXT_16BIT_NUM(ep->X_add_number))
3405 /* Signed 16-bit offset will fit in the op. Easy! */
3406 macro_build (place, counter, ep, op, "t,o(b)", treg,
3407 (int) BFD_RELOC_LO16, breg);
3411 /* 32-bit offset, need multiple instructions and AT, like:
3412 lui $tempreg,const_hi (BFD_RELOC_HI16_S)
3413 addu $tempreg,$tempreg,$breg
3414 <op> $treg,const_lo($tempreg) (BFD_RELOC_LO16)
3415 to handle the complete offset. */
3416 macro_build_lui (place, counter, ep, AT);
3419 macro_build (place, counter, (expressionS *) NULL,
3420 HAVE_32BIT_ADDRESSES ? HAVE_NEWABI
3421 ? "add" : "addu" : "daddu",
3422 "d,v,t", AT, AT, breg);
3425 macro_build (place, counter, ep, op, "t,o(b)", treg,
3426 (int) BFD_RELOC_LO16, AT);
3429 as_warn (_("Macro used $at after \".set noat\""));
3434 * Generates code to set the $at register to true (one)
3435 * if reg is less than the immediate expression.
3438 set_at (counter, reg, unsignedp)
3443 if (imm_expr.X_op == O_constant
3444 && imm_expr.X_add_number >= -0x8000
3445 && imm_expr.X_add_number < 0x8000)
3446 macro_build ((char *) NULL, counter, &imm_expr,
3447 unsignedp ? "sltiu" : "slti",
3448 "t,r,j", AT, reg, (int) BFD_RELOC_LO16);
3451 load_register (counter, AT, &imm_expr, HAVE_64BIT_GPRS);
3452 macro_build ((char *) NULL, counter, (expressionS *) NULL,
3453 unsignedp ? "sltu" : "slt",
3454 "d,v,t", AT, reg, AT);
3458 /* Warn if an expression is not a constant. */
3461 check_absolute_expr (ip, ex)
3462 struct mips_cl_insn *ip;
3465 if (ex->X_op == O_big)
3466 as_bad (_("unsupported large constant"));
3467 else if (ex->X_op != O_constant)
3468 as_bad (_("Instruction %s requires absolute expression"), ip->insn_mo->name);
3471 /* Count the leading zeroes by performing a binary chop. This is a
3472 bulky bit of source, but performance is a LOT better for the
3473 majority of values than a simple loop to count the bits:
3474 for (lcnt = 0; (lcnt < 32); lcnt++)
3475 if ((v) & (1 << (31 - lcnt)))
3477 However it is not code size friendly, and the gain will drop a bit
3478 on certain cached systems.
3480 #define COUNT_TOP_ZEROES(v) \
3481 (((v) & ~0xffff) == 0 \
3482 ? ((v) & ~0xff) == 0 \
3483 ? ((v) & ~0xf) == 0 \
3484 ? ((v) & ~0x3) == 0 \
3485 ? ((v) & ~0x1) == 0 \
3490 : ((v) & ~0x7) == 0 \
3493 : ((v) & ~0x3f) == 0 \
3494 ? ((v) & ~0x1f) == 0 \
3497 : ((v) & ~0x7f) == 0 \
3500 : ((v) & ~0xfff) == 0 \
3501 ? ((v) & ~0x3ff) == 0 \
3502 ? ((v) & ~0x1ff) == 0 \
3505 : ((v) & ~0x7ff) == 0 \
3508 : ((v) & ~0x3fff) == 0 \
3509 ? ((v) & ~0x1fff) == 0 \
3512 : ((v) & ~0x7fff) == 0 \
3515 : ((v) & ~0xffffff) == 0 \
3516 ? ((v) & ~0xfffff) == 0 \
3517 ? ((v) & ~0x3ffff) == 0 \
3518 ? ((v) & ~0x1ffff) == 0 \
3521 : ((v) & ~0x7ffff) == 0 \
3524 : ((v) & ~0x3fffff) == 0 \
3525 ? ((v) & ~0x1fffff) == 0 \
3528 : ((v) & ~0x7fffff) == 0 \
3531 : ((v) & ~0xfffffff) == 0 \
3532 ? ((v) & ~0x3ffffff) == 0 \
3533 ? ((v) & ~0x1ffffff) == 0 \
3536 : ((v) & ~0x7ffffff) == 0 \
3539 : ((v) & ~0x3fffffff) == 0 \
3540 ? ((v) & ~0x1fffffff) == 0 \
3543 : ((v) & ~0x7fffffff) == 0 \
3548 * This routine generates the least number of instructions neccessary to load
3549 * an absolute expression value into a register.
3552 load_register (counter, reg, ep, dbl)
3559 expressionS hi32, lo32;
3561 if (ep->X_op != O_big)
3563 assert (ep->X_op == O_constant);
3564 if (ep->X_add_number < 0x8000
3565 && (ep->X_add_number >= 0
3566 || (ep->X_add_number >= -0x8000
3569 || sizeof (ep->X_add_number) > 4))))
3571 /* We can handle 16 bit signed values with an addiu to
3572 $zero. No need to ever use daddiu here, since $zero and
3573 the result are always correct in 32 bit mode. */
3574 macro_build ((char *) NULL, counter, ep, "addiu", "t,r,j", reg, 0,
3575 (int) BFD_RELOC_LO16);
3578 else if (ep->X_add_number >= 0 && ep->X_add_number < 0x10000)
3580 /* We can handle 16 bit unsigned values with an ori to
3582 macro_build ((char *) NULL, counter, ep, "ori", "t,r,i", reg, 0,
3583 (int) BFD_RELOC_LO16);
3586 else if ((IS_SEXT_32BIT_NUM (ep->X_add_number)
3589 || sizeof (ep->X_add_number) > 4
3590 || (ep->X_add_number & 0x80000000) == 0))
3591 || ((HAVE_32BIT_GPRS || ! dbl)
3592 && (ep->X_add_number &~ (offsetT) 0xffffffff) == 0)
3595 && ((ep->X_add_number &~ (offsetT) 0xffffffff)
3596 == ~ (offsetT) 0xffffffff)))
3598 /* 32 bit values require an lui. */
3599 macro_build ((char *) NULL, counter, ep, "lui", "t,u", reg,
3600 (int) BFD_RELOC_HI16);
3601 if ((ep->X_add_number & 0xffff) != 0)
3602 macro_build ((char *) NULL, counter, ep, "ori", "t,r,i", reg, reg,
3603 (int) BFD_RELOC_LO16);
3608 /* The value is larger than 32 bits. */
3610 if (HAVE_32BIT_GPRS)
3612 as_bad (_("Number (0x%lx) larger than 32 bits"),
3613 (unsigned long) ep->X_add_number);
3614 macro_build ((char *) NULL, counter, ep, "addiu", "t,r,j", reg, 0,
3615 (int) BFD_RELOC_LO16);
3619 if (ep->X_op != O_big)
3622 hi32.X_add_number = (valueT) hi32.X_add_number >> 16;
3623 hi32.X_add_number = (valueT) hi32.X_add_number >> 16;
3624 hi32.X_add_number &= 0xffffffff;
3626 lo32.X_add_number &= 0xffffffff;
3630 assert (ep->X_add_number > 2);
3631 if (ep->X_add_number == 3)
3632 generic_bignum[3] = 0;
3633 else if (ep->X_add_number > 4)
3634 as_bad (_("Number larger than 64 bits"));
3635 lo32.X_op = O_constant;
3636 lo32.X_add_number = generic_bignum[0] + (generic_bignum[1] << 16);
3637 hi32.X_op = O_constant;
3638 hi32.X_add_number = generic_bignum[2] + (generic_bignum[3] << 16);
3641 if (hi32.X_add_number == 0)
3646 unsigned long hi, lo;
3648 if (hi32.X_add_number == (offsetT) 0xffffffff)
3650 if ((lo32.X_add_number & 0xffff8000) == 0xffff8000)
3652 macro_build ((char *) NULL, counter, &lo32, "addiu", "t,r,j",
3653 reg, 0, (int) BFD_RELOC_LO16);
3656 if (lo32.X_add_number & 0x80000000)
3658 macro_build ((char *) NULL, counter, &lo32, "lui", "t,u", reg,
3659 (int) BFD_RELOC_HI16);
3660 if (lo32.X_add_number & 0xffff)
3661 macro_build ((char *) NULL, counter, &lo32, "ori", "t,r,i",
3662 reg, reg, (int) BFD_RELOC_LO16);
3667 /* Check for 16bit shifted constant. We know that hi32 is
3668 non-zero, so start the mask on the first bit of the hi32
3673 unsigned long himask, lomask;
3677 himask = 0xffff >> (32 - shift);
3678 lomask = (0xffff << shift) & 0xffffffff;
3682 himask = 0xffff << (shift - 32);
3685 if ((hi32.X_add_number & ~(offsetT) himask) == 0
3686 && (lo32.X_add_number & ~(offsetT) lomask) == 0)
3690 tmp.X_op = O_constant;
3692 tmp.X_add_number = ((hi32.X_add_number << (32 - shift))
3693 | (lo32.X_add_number >> shift));
3695 tmp.X_add_number = hi32.X_add_number >> (shift - 32);
3696 macro_build ((char *) NULL, counter, &tmp,
3697 "ori", "t,r,i", reg, 0,
3698 (int) BFD_RELOC_LO16);
3699 macro_build ((char *) NULL, counter, (expressionS *) NULL,
3700 (shift >= 32) ? "dsll32" : "dsll",
3702 (shift >= 32) ? shift - 32 : shift);
3707 while (shift <= (64 - 16));
3709 /* Find the bit number of the lowest one bit, and store the
3710 shifted value in hi/lo. */
3711 hi = (unsigned long) (hi32.X_add_number & 0xffffffff);
3712 lo = (unsigned long) (lo32.X_add_number & 0xffffffff);
3716 while ((lo & 1) == 0)
3721 lo |= (hi & (((unsigned long) 1 << bit) - 1)) << (32 - bit);
3727 while ((hi & 1) == 0)
3736 /* Optimize if the shifted value is a (power of 2) - 1. */
3737 if ((hi == 0 && ((lo + 1) & lo) == 0)
3738 || (lo == 0xffffffff && ((hi + 1) & hi) == 0))
3740 shift = COUNT_TOP_ZEROES ((unsigned int) hi32.X_add_number);
3745 /* This instruction will set the register to be all
3747 tmp.X_op = O_constant;
3748 tmp.X_add_number = (offsetT) -1;
3749 macro_build ((char *) NULL, counter, &tmp, "addiu", "t,r,j",
3750 reg, 0, (int) BFD_RELOC_LO16);
3754 macro_build ((char *) NULL, counter, (expressionS *) NULL,
3755 (bit >= 32) ? "dsll32" : "dsll",
3757 (bit >= 32) ? bit - 32 : bit);
3759 macro_build ((char *) NULL, counter, (expressionS *) NULL,
3760 (shift >= 32) ? "dsrl32" : "dsrl",
3762 (shift >= 32) ? shift - 32 : shift);
3767 /* Sign extend hi32 before calling load_register, because we can
3768 generally get better code when we load a sign extended value. */
3769 if ((hi32.X_add_number & 0x80000000) != 0)
3770 hi32.X_add_number |= ~(offsetT) 0xffffffff;
3771 load_register (counter, reg, &hi32, 0);
3774 if ((lo32.X_add_number & 0xffff0000) == 0)
3778 macro_build ((char *) NULL, counter, (expressionS *) NULL,
3779 "dsll32", "d,w,<", reg, freg, 0);
3787 if ((freg == 0) && (lo32.X_add_number == (offsetT) 0xffffffff))
3789 macro_build ((char *) NULL, counter, &lo32, "lui", "t,u", reg,
3790 (int) BFD_RELOC_HI16);
3791 macro_build ((char *) NULL, counter, (expressionS *) NULL,
3792 "dsrl32", "d,w,<", reg, reg, 0);
3798 macro_build ((char *) NULL, counter, (expressionS *) NULL, "dsll",
3799 "d,w,<", reg, freg, 16);
3803 mid16.X_add_number >>= 16;
3804 macro_build ((char *) NULL, counter, &mid16, "ori", "t,r,i", reg,
3805 freg, (int) BFD_RELOC_LO16);
3806 macro_build ((char *) NULL, counter, (expressionS *) NULL, "dsll",
3807 "d,w,<", reg, reg, 16);
3810 if ((lo32.X_add_number & 0xffff) != 0)
3811 macro_build ((char *) NULL, counter, &lo32, "ori", "t,r,i", reg, freg,
3812 (int) BFD_RELOC_LO16);
3815 /* Load an address into a register. */
3818 load_address (counter, reg, ep, used_at)
3826 if (ep->X_op != O_constant
3827 && ep->X_op != O_symbol)
3829 as_bad (_("expression too complex"));
3830 ep->X_op = O_constant;
3833 if (ep->X_op == O_constant)
3835 load_register (counter, reg, ep, HAVE_64BIT_ADDRESSES);
3839 if (mips_pic == NO_PIC)
3841 /* If this is a reference to a GP relative symbol, we want
3842 addiu $reg,$gp,<sym> (BFD_RELOC_GPREL16)
3844 lui $reg,<sym> (BFD_RELOC_HI16_S)
3845 addiu $reg,$reg,<sym> (BFD_RELOC_LO16)
3846 If we have an addend, we always use the latter form.
3848 With 64bit address space and a usable $at we want
3849 lui $reg,<sym> (BFD_RELOC_MIPS_HIGHEST)
3850 lui $at,<sym> (BFD_RELOC_HI16_S)
3851 daddiu $reg,<sym> (BFD_RELOC_MIPS_HIGHER)
3852 daddiu $at,<sym> (BFD_RELOC_LO16)
3856 If $at is already in use, we use a path which is suboptimal
3857 on superscalar processors.
3858 lui $reg,<sym> (BFD_RELOC_MIPS_HIGHEST)
3859 daddiu $reg,<sym> (BFD_RELOC_MIPS_HIGHER)
3861 daddiu $reg,<sym> (BFD_RELOC_HI16_S)
3863 daddiu $reg,<sym> (BFD_RELOC_LO16)
3865 if (HAVE_64BIT_ADDRESSES)
3867 /* We don't do GP optimization for now because RELAX_ENCODE can't
3868 hold the data for such large chunks. */
3870 if (*used_at == 0 && ! mips_opts.noat)
3872 macro_build (p, counter, ep, "lui", "t,u",
3873 reg, (int) BFD_RELOC_MIPS_HIGHEST);
3874 macro_build (p, counter, ep, "lui", "t,u",
3875 AT, (int) BFD_RELOC_HI16_S);
3876 macro_build (p, counter, ep, "daddiu", "t,r,j",
3877 reg, reg, (int) BFD_RELOC_MIPS_HIGHER);
3878 macro_build (p, counter, ep, "daddiu", "t,r,j",
3879 AT, AT, (int) BFD_RELOC_LO16);
3880 macro_build (p, counter, (expressionS *) NULL, "dsll32",
3881 "d,w,<", reg, reg, 0);
3882 macro_build (p, counter, (expressionS *) NULL, "daddu",
3883 "d,v,t", reg, reg, AT);
3888 macro_build (p, counter, ep, "lui", "t,u",
3889 reg, (int) BFD_RELOC_MIPS_HIGHEST);
3890 macro_build (p, counter, ep, "daddiu", "t,r,j",
3891 reg, reg, (int) BFD_RELOC_MIPS_HIGHER);
3892 macro_build (p, counter, (expressionS *) NULL, "dsll",
3893 "d,w,<", reg, reg, 16);
3894 macro_build (p, counter, ep, "daddiu", "t,r,j",
3895 reg, reg, (int) BFD_RELOC_HI16_S);
3896 macro_build (p, counter, (expressionS *) NULL, "dsll",
3897 "d,w,<", reg, reg, 16);
3898 macro_build (p, counter, ep, "daddiu", "t,r,j",
3899 reg, reg, (int) BFD_RELOC_LO16);
3904 if ((valueT) ep->X_add_number <= MAX_GPREL_OFFSET
3905 && ! nopic_need_relax (ep->X_add_symbol, 1))
3908 macro_build ((char *) NULL, counter, ep,
3909 HAVE_32BIT_ADDRESSES ? HAVE_NEWABI
3910 ? "addi" : "addiu" : "daddiu", "t,r,j",
3911 reg, mips_gp_register, (int) BFD_RELOC_GPREL16);
3912 p = frag_var (rs_machine_dependent, 8, 0,
3913 RELAX_ENCODE (4, 8, 0, 4, 0,
3914 mips_opts.warn_about_macros),
3915 ep->X_add_symbol, 0, NULL);
3917 macro_build_lui (p, counter, ep, reg);
3920 macro_build (p, counter, ep,
3921 HAVE_32BIT_ADDRESSES ? HAVE_NEWABI
3922 ? "addi" : "addiu" : "daddiu",
3923 "t,r,j", reg, reg, (int) BFD_RELOC_LO16);
3926 else if (mips_pic == SVR4_PIC && ! mips_big_got)
3930 /* If this is a reference to an external symbol, we want
3931 lw $reg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
3933 lw $reg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
3935 addiu $reg,$reg,<sym> (BFD_RELOC_LO16)
3936 If there is a constant, it must be added in after.
3938 If we have NewABI, we want
3939 lw $reg,<sym+cst>($gp) (BFD_RELOC_MIPS_GOT_DISP)
3940 unless we're referencing a global symbol with a non-zero
3941 offset, in which case cst must be added separately. */
3946 if (ep->X_add_number)
3948 frag_now->tc_frag_data.tc_fr_offset =
3949 ex.X_add_number = ep->X_add_number;
3950 ep->X_add_number = 0;
3951 macro_build ((char *) NULL, counter, ep,
3952 HAVE_32BIT_ADDRESSES ? "lw" : "ld", "t,o(b)", reg,
3953 (int) BFD_RELOC_MIPS_GOT_DISP, mips_gp_register);
3954 if (ex.X_add_number < -0x8000 || ex.X_add_number >= 0x8000)
3955 as_bad (_("PIC code offset overflow (max 16 signed bits)"));
3956 ex.X_op = O_constant;
3957 macro_build ((char *) NULL, counter, &ex,
3958 HAVE_32BIT_ADDRESSES ? "addi" : "daddiu",
3959 "t,r,j", reg, reg, (int) BFD_RELOC_LO16);
3960 p = frag_var (rs_machine_dependent, 8, 0,
3961 RELAX_ENCODE (8, 4, 0, 0, 0,
3962 mips_opts.warn_about_macros),
3963 ep->X_add_symbol, 0, (char *) NULL);
3964 ep->X_add_number = ex.X_add_number;
3967 macro_build (p, counter, ep,
3968 HAVE_32BIT_ADDRESSES ? "lw" : "ld", "t,o(b)", reg,
3969 (int) BFD_RELOC_MIPS_GOT_DISP, mips_gp_register);
3973 /* To avoid confusion in tc_gen_reloc, we must ensure
3974 that this does not become a variant frag. */
3975 frag_wane (frag_now);
3981 ex.X_add_number = ep->X_add_number;
3982 ep->X_add_number = 0;
3984 macro_build ((char *) NULL, counter, ep,
3985 HAVE_32BIT_ADDRESSES ? "lw" : "ld", "t,o(b)",
3986 reg, (int) BFD_RELOC_MIPS_GOT16, mips_gp_register);
3987 macro_build ((char *) NULL, counter, (expressionS *) NULL, "nop", "");
3988 p = frag_var (rs_machine_dependent, 4, 0,
3989 RELAX_ENCODE (0, 4, -8, 0, 0, mips_opts.warn_about_macros),
3990 ep->X_add_symbol, (offsetT) 0, (char *) NULL);
3991 macro_build (p, counter, ep,
3992 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
3993 "t,r,j", reg, reg, (int) BFD_RELOC_LO16);
3995 if (ex.X_add_number != 0)
3997 if (ex.X_add_number < -0x8000 || ex.X_add_number >= 0x8000)
3998 as_bad (_("PIC code offset overflow (max 16 signed bits)"));
3999 ex.X_op = O_constant;
4000 macro_build ((char *) NULL, counter, &ex,
4001 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
4002 "t,r,j", reg, reg, (int) BFD_RELOC_LO16);
4006 else if (mips_pic == SVR4_PIC)
4011 /* This is the large GOT case. If this is a reference to an
4012 external symbol, we want
4013 lui $reg,<sym> (BFD_RELOC_MIPS_GOT_HI16)
4015 lw $reg,<sym>($reg) (BFD_RELOC_MIPS_GOT_LO16)
4017 Otherwise, for a reference to a local symbol in old ABI, we want
4018 lw $reg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
4020 addiu $reg,$reg,<sym> (BFD_RELOC_LO16)
4021 If there is a constant, it must be added in after.
4023 In the NewABI, for local symbols, with or without offsets, we want:
4024 lw $reg,<sym>($gp) (BFD_RELOC_MIPS_GOT_PAGE)
4025 addiu $reg,$reg,<sym> (BFD_RELOC_MIPS_GOT_OFST)
4031 frag_now->tc_frag_data.tc_fr_offset =
4032 ex.X_add_number = ep->X_add_number;
4033 ep->X_add_number = 0;
4034 macro_build ((char *) NULL, counter, ep, "lui", "t,u", reg,
4035 (int) BFD_RELOC_MIPS_GOT_HI16);
4036 macro_build ((char *) NULL, counter, (expressionS *) NULL,
4037 HAVE_32BIT_ADDRESSES ? "add" : "daddu", "d,v,t", reg,
4038 reg, mips_gp_register);
4039 macro_build ((char *) NULL, counter, ep,
4040 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
4041 "t,o(b)", reg, (int) BFD_RELOC_MIPS_GOT_LO16, reg);
4042 if (ex.X_add_number < -0x8000 || ex.X_add_number >= 0x8000)
4043 as_bad (_("PIC code offset overflow (max 16 signed bits)"));
4044 else if (ex.X_add_number)
4046 ex.X_op = O_constant;
4047 macro_build ((char *) NULL, counter, &ex,
4048 HAVE_32BIT_ADDRESSES ? "addi" : "daddiu",
4049 "t,r,j", reg, reg, (int) BFD_RELOC_LO16);
4052 ep->X_add_number = ex.X_add_number;
4053 p = frag_var (rs_machine_dependent, 8, 0,
4054 RELAX_ENCODE (ex.X_add_number ? 16 : 12, 8, 0, 4, 0,
4055 mips_opts.warn_about_macros),
4056 ep->X_add_symbol, 0, (char *) NULL);
4057 macro_build (p, counter, ep,
4058 HAVE_32BIT_ADDRESSES ? "lw" : "ld", "t,o(b)", reg,
4059 (int) BFD_RELOC_MIPS_GOT_PAGE, mips_gp_register);
4060 macro_build (p + 4, counter, ep,
4061 HAVE_32BIT_ADDRESSES ? "addi" : "daddiu", "t,r,j",
4062 reg, reg, (int) BFD_RELOC_MIPS_GOT_OFST);
4066 ex.X_add_number = ep->X_add_number;
4067 ep->X_add_number = 0;
4068 if (reg_needs_delay (mips_gp_register))
4073 macro_build ((char *) NULL, counter, ep, "lui", "t,u", reg,
4074 (int) BFD_RELOC_MIPS_GOT_HI16);
4075 macro_build ((char *) NULL, counter, (expressionS *) NULL,
4076 HAVE_32BIT_ADDRESSES ? "addu" : "daddu", "d,v,t", reg,
4077 reg, mips_gp_register);
4078 macro_build ((char *) NULL, counter, ep,
4079 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
4080 "t,o(b)", reg, (int) BFD_RELOC_MIPS_GOT_LO16, reg);
4081 p = frag_var (rs_machine_dependent, 12 + off, 0,
4082 RELAX_ENCODE (12, 12 + off, off, 8 + off, 0,
4083 mips_opts.warn_about_macros),
4084 ep->X_add_symbol, 0, NULL);
4087 /* We need a nop before loading from $gp. This special
4088 check is required because the lui which starts the main
4089 instruction stream does not refer to $gp, and so will not
4090 insert the nop which may be required. */
4091 macro_build (p, counter, (expressionS *) NULL, "nop", "");
4094 macro_build (p, counter, ep,
4095 HAVE_32BIT_ADDRESSES ? "lw" : "ld", "t,o(b)", reg,
4096 (int) BFD_RELOC_MIPS_GOT16, mips_gp_register);
4098 macro_build (p, counter, (expressionS *) NULL, "nop", "");
4100 macro_build (p, counter, ep,
4101 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
4102 "t,r,j", reg, reg, (int) BFD_RELOC_LO16);
4104 if (ex.X_add_number != 0)
4106 if (ex.X_add_number < -0x8000 || ex.X_add_number >= 0x8000)
4107 as_bad (_("PIC code offset overflow (max 16 signed bits)"));
4108 ex.X_op = O_constant;
4109 macro_build ((char *) NULL, counter, &ex,
4110 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
4111 "t,r,j", reg, reg, (int) BFD_RELOC_LO16);
4115 else if (mips_pic == EMBEDDED_PIC)
4118 addiu $reg,$gp,<sym> (BFD_RELOC_GPREL16)
4120 macro_build ((char *) NULL, counter, ep,
4121 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
4122 "t,r,j", reg, mips_gp_register, (int) BFD_RELOC_GPREL16);
4128 /* Move the contents of register SOURCE into register DEST. */
4131 move_register (counter, dest, source)
4136 macro_build ((char *) NULL, counter, (expressionS *) NULL,
4137 HAVE_32BIT_GPRS ? "addu" : "daddu",
4138 "d,v,t", dest, source, 0);
4143 * This routine implements the seemingly endless macro or synthesized
4144 * instructions and addressing modes in the mips assembly language. Many
4145 * of these macros are simple and are similar to each other. These could
4146 * probably be handled by some kind of table or grammer aproach instead of
4147 * this verbose method. Others are not simple macros but are more like
4148 * optimizing code generation.
4149 * One interesting optimization is when several store macros appear
4150 * consecutivly that would load AT with the upper half of the same address.
4151 * The ensuing load upper instructions are ommited. This implies some kind
4152 * of global optimization. We currently only optimize within a single macro.
4153 * For many of the load and store macros if the address is specified as a
4154 * constant expression in the first 64k of memory (ie ld $2,0x4000c) we
4155 * first load register 'at' with zero and use it as the base register. The
4156 * mips assembler simply uses register $zero. Just one tiny optimization
4161 struct mips_cl_insn *ip;
4163 register int treg, sreg, dreg, breg;
4179 bfd_reloc_code_real_type r;
4180 int hold_mips_optimize;
4182 assert (! mips_opts.mips16);
4184 treg = (ip->insn_opcode >> 16) & 0x1f;
4185 dreg = (ip->insn_opcode >> 11) & 0x1f;
4186 sreg = breg = (ip->insn_opcode >> 21) & 0x1f;
4187 mask = ip->insn_mo->mask;
4189 expr1.X_op = O_constant;
4190 expr1.X_op_symbol = NULL;
4191 expr1.X_add_symbol = NULL;
4192 expr1.X_add_number = 1;
4194 /* Umatched fixups should not be put in the same frag as a relaxable
4195 macro. For example, suppose we have:
4199 addiu $4,$4,%lo(l1) # 3
4201 If instructions 1 and 2 were put in the same frag, md_frob_file would
4202 move the fixup for #1 after the fixups for the "unrelaxed" version of
4203 #2. This would confuse tc_gen_reloc, which expects the relocations
4204 for #2 to be the last for that frag.
4206 Also, if tc_gen_reloc sees certain relocations in a variant frag,
4207 it assumes that they belong to a relaxable macro. We mustn't put
4208 other uses of such relocations into a variant frag.
4210 To avoid both problems, finish the current frag it contains a
4211 %reloc() operator. The macro then goes into a new frag. */
4212 if (prev_reloc_op_frag == frag_now)
4214 frag_wane (frag_now);
4228 mips_emit_delays (TRUE);
4229 ++mips_opts.noreorder;
4230 mips_any_noreorder = 1;
4232 expr1.X_add_number = 8;
4233 macro_build ((char *) NULL, &icnt, &expr1, "bgez", "s,p", sreg);
4235 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "",
4238 move_register (&icnt, dreg, sreg);
4239 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
4240 dbl ? "dsub" : "sub", "d,v,t", dreg, 0, sreg);
4242 --mips_opts.noreorder;
4263 if (imm_expr.X_op == O_constant
4264 && imm_expr.X_add_number >= -0x8000
4265 && imm_expr.X_add_number < 0x8000)
4267 macro_build ((char *) NULL, &icnt, &imm_expr, s, "t,r,j", treg, sreg,
4268 (int) BFD_RELOC_LO16);
4271 load_register (&icnt, AT, &imm_expr, dbl);
4272 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s2, "d,v,t",
4292 if (imm_expr.X_op == O_constant
4293 && imm_expr.X_add_number >= 0
4294 && imm_expr.X_add_number < 0x10000)
4296 if (mask != M_NOR_I)
4297 macro_build ((char *) NULL, &icnt, &imm_expr, s, "t,r,i", treg,
4298 sreg, (int) BFD_RELOC_LO16);
4301 macro_build ((char *) NULL, &icnt, &imm_expr, "ori", "t,r,i",
4302 treg, sreg, (int) BFD_RELOC_LO16);
4303 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nor",
4304 "d,v,t", treg, treg, 0);
4309 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_GPRS);
4310 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s2, "d,v,t",
4328 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
4330 macro_build ((char *) NULL, &icnt, &offset_expr, s, "s,t,p", sreg,
4334 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_GPRS);
4335 macro_build ((char *) NULL, &icnt, &offset_expr, s, "s,t,p", sreg, AT);
4343 macro_build ((char *) NULL, &icnt, &offset_expr,
4344 likely ? "bgezl" : "bgez", "s,p", sreg);
4349 macro_build ((char *) NULL, &icnt, &offset_expr,
4350 likely ? "blezl" : "blez", "s,p", treg);
4353 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "slt", "d,v,t",
4355 macro_build ((char *) NULL, &icnt, &offset_expr,
4356 likely ? "beql" : "beq", "s,t,p", AT, 0);
4362 /* check for > max integer */
4363 maxnum = 0x7fffffff;
4364 if (HAVE_64BIT_GPRS && sizeof (maxnum) > 4)
4371 if (imm_expr.X_op == O_constant
4372 && imm_expr.X_add_number >= maxnum
4373 && (HAVE_32BIT_GPRS || sizeof (maxnum) > 4))
4376 /* result is always false */
4380 as_warn (_("Branch %s is always false (nop)"),
4382 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop",
4388 as_warn (_("Branch likely %s is always false"),
4390 macro_build ((char *) NULL, &icnt, &offset_expr, "bnel",
4395 if (imm_expr.X_op != O_constant)
4396 as_bad (_("Unsupported large constant"));
4397 ++imm_expr.X_add_number;
4401 if (mask == M_BGEL_I)
4403 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
4405 macro_build ((char *) NULL, &icnt, &offset_expr,
4406 likely ? "bgezl" : "bgez", "s,p", sreg);
4409 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 1)
4411 macro_build ((char *) NULL, &icnt, &offset_expr,
4412 likely ? "bgtzl" : "bgtz", "s,p", sreg);
4415 maxnum = 0x7fffffff;
4416 if (HAVE_64BIT_GPRS && sizeof (maxnum) > 4)
4423 maxnum = - maxnum - 1;
4424 if (imm_expr.X_op == O_constant
4425 && imm_expr.X_add_number <= maxnum
4426 && (HAVE_32BIT_GPRS || sizeof (maxnum) > 4))
4429 /* result is always true */
4430 as_warn (_("Branch %s is always true"), ip->insn_mo->name);
4431 macro_build ((char *) NULL, &icnt, &offset_expr, "b", "p");
4434 set_at (&icnt, sreg, 0);
4435 macro_build ((char *) NULL, &icnt, &offset_expr,
4436 likely ? "beql" : "beq", "s,t,p", AT, 0);
4446 macro_build ((char *) NULL, &icnt, &offset_expr,
4447 likely ? "beql" : "beq", "s,t,p", 0, treg);
4450 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sltu",
4451 "d,v,t", AT, sreg, treg);
4452 macro_build ((char *) NULL, &icnt, &offset_expr,
4453 likely ? "beql" : "beq", "s,t,p", AT, 0);
4461 && imm_expr.X_op == O_constant
4462 && imm_expr.X_add_number == (offsetT) 0xffffffff))
4464 if (imm_expr.X_op != O_constant)
4465 as_bad (_("Unsupported large constant"));
4466 ++imm_expr.X_add_number;
4470 if (mask == M_BGEUL_I)
4472 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
4474 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 1)
4476 macro_build ((char *) NULL, &icnt, &offset_expr,
4477 likely ? "bnel" : "bne", "s,t,p", sreg, 0);
4480 set_at (&icnt, sreg, 1);
4481 macro_build ((char *) NULL, &icnt, &offset_expr,
4482 likely ? "beql" : "beq", "s,t,p", AT, 0);
4490 macro_build ((char *) NULL, &icnt, &offset_expr,
4491 likely ? "bgtzl" : "bgtz", "s,p", sreg);
4496 macro_build ((char *) NULL, &icnt, &offset_expr,
4497 likely ? "bltzl" : "bltz", "s,p", treg);
4500 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "slt", "d,v,t",
4502 macro_build ((char *) NULL, &icnt, &offset_expr,
4503 likely ? "bnel" : "bne", "s,t,p", AT, 0);
4511 macro_build ((char *) NULL, &icnt, &offset_expr,
4512 likely ? "bnel" : "bne", "s,t,p", sreg, 0);
4517 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sltu",
4518 "d,v,t", AT, treg, sreg);
4519 macro_build ((char *) NULL, &icnt, &offset_expr,
4520 likely ? "bnel" : "bne", "s,t,p", AT, 0);
4528 macro_build ((char *) NULL, &icnt, &offset_expr,
4529 likely ? "blezl" : "blez", "s,p", sreg);
4534 macro_build ((char *) NULL, &icnt, &offset_expr,
4535 likely ? "bgezl" : "bgez", "s,p", treg);
4538 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "slt", "d,v,t",
4540 macro_build ((char *) NULL, &icnt, &offset_expr,
4541 likely ? "beql" : "beq", "s,t,p", AT, 0);
4547 maxnum = 0x7fffffff;
4548 if (HAVE_64BIT_GPRS && sizeof (maxnum) > 4)
4555 if (imm_expr.X_op == O_constant
4556 && imm_expr.X_add_number >= maxnum
4557 && (HAVE_32BIT_GPRS || sizeof (maxnum) > 4))
4559 if (imm_expr.X_op != O_constant)
4560 as_bad (_("Unsupported large constant"));
4561 ++imm_expr.X_add_number;
4565 if (mask == M_BLTL_I)
4567 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
4569 macro_build ((char *) NULL, &icnt, &offset_expr,
4570 likely ? "bltzl" : "bltz", "s,p", sreg);
4573 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 1)
4575 macro_build ((char *) NULL, &icnt, &offset_expr,
4576 likely ? "blezl" : "blez", "s,p", sreg);
4579 set_at (&icnt, sreg, 0);
4580 macro_build ((char *) NULL, &icnt, &offset_expr,
4581 likely ? "bnel" : "bne", "s,t,p", AT, 0);
4589 macro_build ((char *) NULL, &icnt, &offset_expr,
4590 likely ? "beql" : "beq", "s,t,p", sreg, 0);
4595 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sltu",
4596 "d,v,t", AT, treg, sreg);
4597 macro_build ((char *) NULL, &icnt, &offset_expr,
4598 likely ? "beql" : "beq", "s,t,p", AT, 0);
4606 && imm_expr.X_op == O_constant
4607 && imm_expr.X_add_number == (offsetT) 0xffffffff))
4609 if (imm_expr.X_op != O_constant)
4610 as_bad (_("Unsupported large constant"));
4611 ++imm_expr.X_add_number;
4615 if (mask == M_BLTUL_I)
4617 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
4619 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 1)
4621 macro_build ((char *) NULL, &icnt, &offset_expr,
4622 likely ? "beql" : "beq",
4626 set_at (&icnt, sreg, 1);
4627 macro_build ((char *) NULL, &icnt, &offset_expr,
4628 likely ? "bnel" : "bne", "s,t,p", AT, 0);
4636 macro_build ((char *) NULL, &icnt, &offset_expr,
4637 likely ? "bltzl" : "bltz", "s,p", sreg);
4642 macro_build ((char *) NULL, &icnt, &offset_expr,
4643 likely ? "bgtzl" : "bgtz", "s,p", treg);
4646 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "slt", "d,v,t",
4648 macro_build ((char *) NULL, &icnt, &offset_expr,
4649 likely ? "bnel" : "bne", "s,t,p", AT, 0);
4659 macro_build ((char *) NULL, &icnt, &offset_expr,
4660 likely ? "bnel" : "bne", "s,t,p", 0, treg);
4663 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sltu",
4666 macro_build ((char *) NULL, &icnt, &offset_expr,
4667 likely ? "bnel" : "bne", "s,t,p", AT, 0);
4682 as_warn (_("Divide by zero."));
4684 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "teq",
4687 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "break",
4692 mips_emit_delays (TRUE);
4693 ++mips_opts.noreorder;
4694 mips_any_noreorder = 1;
4697 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "teq",
4698 "s,t,q", treg, 0, 7);
4699 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
4700 dbl ? "ddiv" : "div", "z,s,t", sreg, treg);
4704 expr1.X_add_number = 8;
4705 macro_build ((char *) NULL, &icnt, &expr1, "bne", "s,t,p", treg, 0);
4706 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
4707 dbl ? "ddiv" : "div", "z,s,t", sreg, treg);
4708 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "break",
4711 expr1.X_add_number = -1;
4712 macro_build ((char *) NULL, &icnt, &expr1,
4713 dbl ? "daddiu" : "addiu",
4714 "t,r,j", AT, 0, (int) BFD_RELOC_LO16);
4715 expr1.X_add_number = mips_trap ? (dbl ? 12 : 8) : (dbl ? 20 : 16);
4716 macro_build ((char *) NULL, &icnt, &expr1, "bne", "s,t,p", treg, AT);
4719 expr1.X_add_number = 1;
4720 macro_build ((char *) NULL, &icnt, &expr1, "daddiu", "t,r,j", AT, 0,
4721 (int) BFD_RELOC_LO16);
4722 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "dsll32",
4723 "d,w,<", AT, AT, 31);
4727 expr1.X_add_number = 0x80000000;
4728 macro_build ((char *) NULL, &icnt, &expr1, "lui", "t,u", AT,
4729 (int) BFD_RELOC_HI16);
4733 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "teq",
4734 "s,t,q", sreg, AT, 6);
4735 /* We want to close the noreorder block as soon as possible, so
4736 that later insns are available for delay slot filling. */
4737 --mips_opts.noreorder;
4741 expr1.X_add_number = 8;
4742 macro_build ((char *) NULL, &icnt, &expr1, "bne", "s,t,p", sreg, AT);
4743 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "",
4746 /* We want to close the noreorder block as soon as possible, so
4747 that later insns are available for delay slot filling. */
4748 --mips_opts.noreorder;
4750 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "break",
4753 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "d", dreg);
4792 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
4794 as_warn (_("Divide by zero."));
4796 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "teq",
4799 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "break",
4803 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 1)
4805 if (strcmp (s2, "mflo") == 0)
4806 move_register (&icnt, dreg, sreg);
4808 move_register (&icnt, dreg, 0);
4811 if (imm_expr.X_op == O_constant
4812 && imm_expr.X_add_number == -1
4813 && s[strlen (s) - 1] != 'u')
4815 if (strcmp (s2, "mflo") == 0)
4817 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
4818 dbl ? "dneg" : "neg", "d,w", dreg, sreg);
4821 move_register (&icnt, dreg, 0);
4825 load_register (&icnt, AT, &imm_expr, dbl);
4826 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "z,s,t",
4828 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s2, "d", dreg);
4847 mips_emit_delays (TRUE);
4848 ++mips_opts.noreorder;
4849 mips_any_noreorder = 1;
4852 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "teq",
4853 "s,t,q", treg, 0, 7);
4854 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "z,s,t",
4856 /* We want to close the noreorder block as soon as possible, so
4857 that later insns are available for delay slot filling. */
4858 --mips_opts.noreorder;
4862 expr1.X_add_number = 8;
4863 macro_build ((char *) NULL, &icnt, &expr1, "bne", "s,t,p", treg, 0);
4864 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "z,s,t",
4867 /* We want to close the noreorder block as soon as possible, so
4868 that later insns are available for delay slot filling. */
4869 --mips_opts.noreorder;
4870 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "break",
4873 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s2, "d", dreg);
4879 /* Load the address of a symbol into a register. If breg is not
4880 zero, we then add a base register to it. */
4882 if (dbl && HAVE_32BIT_GPRS)
4883 as_warn (_("dla used to load 32-bit register"));
4885 if (! dbl && HAVE_64BIT_OBJECTS)
4886 as_warn (_("la used to load 64-bit address"));
4888 if (offset_expr.X_op == O_constant
4889 && offset_expr.X_add_number >= -0x8000
4890 && offset_expr.X_add_number < 0x8000)
4892 macro_build ((char *) NULL, &icnt, &offset_expr,
4893 (dbl || HAVE_64BIT_ADDRESSES) ? "daddiu" :
4894 HAVE_NEWABI ? "addi" : "addiu",
4895 "t,r,j", treg, sreg, (int) BFD_RELOC_LO16);
4910 /* When generating embedded PIC code, we permit expressions of
4913 la $treg,foo-bar($breg)
4914 where bar is an address in the current section. These are used
4915 when getting the addresses of functions. We don't permit
4916 X_add_number to be non-zero, because if the symbol is
4917 external the relaxing code needs to know that any addend is
4918 purely the offset to X_op_symbol. */
4919 if (mips_pic == EMBEDDED_PIC
4920 && offset_expr.X_op == O_subtract
4921 && (symbol_constant_p (offset_expr.X_op_symbol)
4922 ? S_GET_SEGMENT (offset_expr.X_op_symbol) == now_seg
4923 : (symbol_equated_p (offset_expr.X_op_symbol)
4925 (symbol_get_value_expression (offset_expr.X_op_symbol)
4928 && (offset_expr.X_add_number == 0
4929 || OUTPUT_FLAVOR == bfd_target_elf_flavour))
4935 macro_build ((char *) NULL, &icnt, &offset_expr, "lui", "t,u",
4936 tempreg, (int) BFD_RELOC_PCREL_HI16_S);
4940 macro_build ((char *) NULL, &icnt, &offset_expr, "lui", "t,u",
4941 tempreg, (int) BFD_RELOC_PCREL_HI16_S);
4942 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
4943 (dbl || HAVE_64BIT_ADDRESSES) ? "daddu" : "addu",
4944 "d,v,t", tempreg, tempreg, breg);
4946 macro_build ((char *) NULL, &icnt, &offset_expr,
4947 (dbl || HAVE_64BIT_ADDRESSES) ? "daddiu" : "addiu",
4948 "t,r,j", treg, tempreg, (int) BFD_RELOC_PCREL_LO16);
4954 if (offset_expr.X_op != O_symbol
4955 && offset_expr.X_op != O_constant)
4957 as_bad (_("expression too complex"));
4958 offset_expr.X_op = O_constant;
4961 if (offset_expr.X_op == O_constant)
4962 load_register (&icnt, tempreg, &offset_expr,
4963 ((mips_pic == EMBEDDED_PIC || mips_pic == NO_PIC)
4964 ? (dbl || HAVE_64BIT_ADDRESSES)
4965 : HAVE_64BIT_ADDRESSES));
4966 else if (mips_pic == NO_PIC)
4968 /* If this is a reference to a GP relative symbol, we want
4969 addiu $tempreg,$gp,<sym> (BFD_RELOC_GPREL16)
4971 lui $tempreg,<sym> (BFD_RELOC_HI16_S)
4972 addiu $tempreg,$tempreg,<sym> (BFD_RELOC_LO16)
4973 If we have a constant, we need two instructions anyhow,
4974 so we may as well always use the latter form.
4976 With 64bit address space and a usable $at we want
4977 lui $tempreg,<sym> (BFD_RELOC_MIPS_HIGHEST)
4978 lui $at,<sym> (BFD_RELOC_HI16_S)
4979 daddiu $tempreg,<sym> (BFD_RELOC_MIPS_HIGHER)
4980 daddiu $at,<sym> (BFD_RELOC_LO16)
4982 daddu $tempreg,$tempreg,$at
4984 If $at is already in use, we use a path which is suboptimal
4985 on superscalar processors.
4986 lui $tempreg,<sym> (BFD_RELOC_MIPS_HIGHEST)
4987 daddiu $tempreg,<sym> (BFD_RELOC_MIPS_HIGHER)
4989 daddiu $tempreg,<sym> (BFD_RELOC_HI16_S)
4991 daddiu $tempreg,<sym> (BFD_RELOC_LO16)
4994 if (HAVE_64BIT_ADDRESSES)
4996 /* We don't do GP optimization for now because RELAX_ENCODE can't
4997 hold the data for such large chunks. */
4999 if (used_at == 0 && ! mips_opts.noat)
5001 macro_build (p, &icnt, &offset_expr, "lui", "t,u",
5002 tempreg, (int) BFD_RELOC_MIPS_HIGHEST);
5003 macro_build (p, &icnt, &offset_expr, "lui", "t,u",
5004 AT, (int) BFD_RELOC_HI16_S);
5005 macro_build (p, &icnt, &offset_expr, "daddiu", "t,r,j",
5006 tempreg, tempreg, (int) BFD_RELOC_MIPS_HIGHER);
5007 macro_build (p, &icnt, &offset_expr, "daddiu", "t,r,j",
5008 AT, AT, (int) BFD_RELOC_LO16);
5009 macro_build (p, &icnt, (expressionS *) NULL, "dsll32",
5010 "d,w,<", tempreg, tempreg, 0);
5011 macro_build (p, &icnt, (expressionS *) NULL, "daddu",
5012 "d,v,t", tempreg, tempreg, AT);
5017 macro_build (p, &icnt, &offset_expr, "lui", "t,u",
5018 tempreg, (int) BFD_RELOC_MIPS_HIGHEST);
5019 macro_build (p, &icnt, &offset_expr, "daddiu", "t,r,j",
5020 tempreg, tempreg, (int) BFD_RELOC_MIPS_HIGHER);
5021 macro_build (p, &icnt, (expressionS *) NULL, "dsll", "d,w,<",
5022 tempreg, tempreg, 16);
5023 macro_build (p, &icnt, &offset_expr, "daddiu", "t,r,j",
5024 tempreg, tempreg, (int) BFD_RELOC_HI16_S);
5025 macro_build (p, &icnt, (expressionS *) NULL, "dsll", "d,w,<",
5026 tempreg, tempreg, 16);
5027 macro_build (p, &icnt, &offset_expr, "daddiu", "t,r,j",
5028 tempreg, tempreg, (int) BFD_RELOC_LO16);
5033 if ((valueT) offset_expr.X_add_number <= MAX_GPREL_OFFSET
5034 && ! nopic_need_relax (offset_expr.X_add_symbol, 1))
5037 macro_build ((char *) NULL, &icnt, &offset_expr,
5038 HAVE_NEWABI ? "addi" : "addiu",
5039 "t,r,j", tempreg, mips_gp_register,
5040 (int) BFD_RELOC_GPREL16);
5041 p = frag_var (rs_machine_dependent, 8, 0,
5042 RELAX_ENCODE (4, 8, 0, 4, 0,
5043 mips_opts.warn_about_macros),
5044 offset_expr.X_add_symbol, 0, NULL);
5046 macro_build_lui (p, &icnt, &offset_expr, tempreg);
5049 macro_build (p, &icnt, &offset_expr,
5050 HAVE_NEWABI ? "addi" : "addiu",
5051 "t,r,j", tempreg, tempreg, (int) BFD_RELOC_LO16);
5054 else if (mips_pic == SVR4_PIC && ! mips_big_got && ! HAVE_NEWABI)
5056 int lw_reloc_type = (int) BFD_RELOC_MIPS_GOT16;
5058 /* If this is a reference to an external symbol, and there
5059 is no constant, we want
5060 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
5061 or if tempreg is PIC_CALL_REG
5062 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_CALL16)
5063 For a local symbol, we want
5064 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
5066 addiu $tempreg,$tempreg,<sym> (BFD_RELOC_LO16)
5068 If we have a small constant, and this is a reference to
5069 an external symbol, we want
5070 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
5072 addiu $tempreg,$tempreg,<constant>
5073 For a local symbol, we want the same instruction
5074 sequence, but we output a BFD_RELOC_LO16 reloc on the
5077 If we have a large constant, and this is a reference to
5078 an external symbol, we want
5079 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
5080 lui $at,<hiconstant>
5081 addiu $at,$at,<loconstant>
5082 addu $tempreg,$tempreg,$at
5083 For a local symbol, we want the same instruction
5084 sequence, but we output a BFD_RELOC_LO16 reloc on the
5088 expr1.X_add_number = offset_expr.X_add_number;
5089 offset_expr.X_add_number = 0;
5091 if (expr1.X_add_number == 0 && tempreg == PIC_CALL_REG)
5092 lw_reloc_type = (int) BFD_RELOC_MIPS_CALL16;
5093 macro_build ((char *) NULL, &icnt, &offset_expr,
5094 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
5095 "t,o(b)", tempreg, lw_reloc_type, mips_gp_register);
5096 if (expr1.X_add_number == 0)
5105 /* We're going to put in an addu instruction using
5106 tempreg, so we may as well insert the nop right
5108 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5112 p = frag_var (rs_machine_dependent, 8 - off, 0,
5113 RELAX_ENCODE (0, 8 - off, -4 - off, 4 - off, 0,
5115 ? mips_opts.warn_about_macros
5117 offset_expr.X_add_symbol, 0, NULL);
5120 macro_build (p, &icnt, (expressionS *) NULL, "nop", "");
5123 macro_build (p, &icnt, &expr1,
5124 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
5125 "t,r,j", tempreg, tempreg, (int) BFD_RELOC_LO16);
5126 /* FIXME: If breg == 0, and the next instruction uses
5127 $tempreg, then if this variant case is used an extra
5128 nop will be generated. */
5130 else if (expr1.X_add_number >= -0x8000
5131 && expr1.X_add_number < 0x8000)
5133 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5135 macro_build ((char *) NULL, &icnt, &expr1,
5136 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
5137 "t,r,j", tempreg, tempreg, (int) BFD_RELOC_LO16);
5138 frag_var (rs_machine_dependent, 0, 0,
5139 RELAX_ENCODE (0, 0, -12, -4, 0, 0),
5140 offset_expr.X_add_symbol, 0, NULL);
5146 /* If we are going to add in a base register, and the
5147 target register and the base register are the same,
5148 then we are using AT as a temporary register. Since
5149 we want to load the constant into AT, we add our
5150 current AT (from the global offset table) and the
5151 register into the register now, and pretend we were
5152 not using a base register. */
5157 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5159 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5160 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
5161 "d,v,t", treg, AT, breg);
5167 /* Set mips_optimize around the lui instruction to avoid
5168 inserting an unnecessary nop after the lw. */
5169 hold_mips_optimize = mips_optimize;
5171 macro_build_lui (NULL, &icnt, &expr1, AT);
5172 mips_optimize = hold_mips_optimize;
5174 macro_build ((char *) NULL, &icnt, &expr1,
5175 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
5176 "t,r,j", AT, AT, (int) BFD_RELOC_LO16);
5177 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5178 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
5179 "d,v,t", tempreg, tempreg, AT);
5180 frag_var (rs_machine_dependent, 0, 0,
5181 RELAX_ENCODE (0, 0, -16 + off1, -8, 0, 0),
5182 offset_expr.X_add_symbol, 0, NULL);
5186 else if (mips_pic == SVR4_PIC && ! mips_big_got && HAVE_NEWABI)
5189 int lw_reloc_type = (int) BFD_RELOC_MIPS_GOT_DISP;
5192 /* If this is a reference to an external, and there is no
5193 constant, or local symbol (*), with or without a
5195 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT_DISP)
5196 or if tempreg is PIC_CALL_REG
5197 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_CALL16)
5199 If we have a small constant, and this is a reference to
5200 an external symbol, we want
5201 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT_DISP)
5202 addiu $tempreg,$tempreg,<constant>
5204 If we have a large constant, and this is a reference to
5205 an external symbol, we want
5206 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT_DISP)
5207 lui $at,<hiconstant>
5208 addiu $at,$at,<loconstant>
5209 addu $tempreg,$tempreg,$at
5211 (*) Other assemblers seem to prefer GOT_PAGE/GOT_OFST for
5212 local symbols, even though it introduces an additional
5216 if (offset_expr.X_add_number == 0 && tempreg == PIC_CALL_REG)
5217 lw_reloc_type = (int) BFD_RELOC_MIPS_CALL16;
5218 if (offset_expr.X_add_number)
5220 frag_now->tc_frag_data.tc_fr_offset =
5221 expr1.X_add_number = offset_expr.X_add_number;
5222 offset_expr.X_add_number = 0;
5224 macro_build ((char *) NULL, &icnt, &offset_expr,
5225 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
5226 "t,o(b)", tempreg, lw_reloc_type,
5229 if (expr1.X_add_number >= -0x8000
5230 && expr1.X_add_number < 0x8000)
5232 macro_build ((char *) NULL, &icnt, &expr1,
5233 HAVE_32BIT_ADDRESSES ? "addi" : "daddiu",
5234 "t,r,j", tempreg, tempreg,
5235 (int) BFD_RELOC_LO16);
5236 p = frag_var (rs_machine_dependent, 4, 0,
5237 RELAX_ENCODE (8, 4, 0, 0, 0, 0),
5238 offset_expr.X_add_symbol, 0, NULL);
5240 else if (IS_SEXT_32BIT_NUM (expr1.X_add_number))
5244 /* If we are going to add in a base register, and the
5245 target register and the base register are the same,
5246 then we are using AT as a temporary register. Since
5247 we want to load the constant into AT, we add our
5248 current AT (from the global offset table) and the
5249 register into the register now, and pretend we were
5250 not using a base register. */
5255 assert (tempreg == AT);
5256 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5257 HAVE_32BIT_ADDRESSES ? "add" : "daddu",
5258 "d,v,t", treg, AT, breg);
5263 macro_build_lui ((char *) NULL, &icnt, &expr1, AT);
5264 macro_build ((char *) NULL, &icnt, &expr1,
5265 HAVE_32BIT_ADDRESSES ? "addi" : "daddiu",
5266 "t,r,j", AT, AT, (int) BFD_RELOC_LO16);
5267 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5268 HAVE_32BIT_ADDRESSES ? "add" : "daddu",
5269 "d,v,t", dreg, dreg, AT);
5271 p = frag_var (rs_machine_dependent, 4 + adj, 0,
5272 RELAX_ENCODE (16 + adj, 4 + adj,
5274 offset_expr.X_add_symbol, 0, NULL);
5279 as_bad (_("PIC code offset overflow (max 32 signed bits)"));
5281 offset_expr.X_add_number = expr1.X_add_number;
5283 macro_build (p, &icnt, &offset_expr,
5284 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
5285 "t,o(b)", tempreg, (int) BFD_RELOC_MIPS_GOT_DISP,
5289 macro_build (p + 4, &icnt, (expressionS *) NULL,
5290 HAVE_32BIT_ADDRESSES ? "add" : "daddu",
5291 "d,v,t", treg, tempreg, breg);
5298 macro_build ((char *) NULL, &icnt, &offset_expr,
5299 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
5300 "t,o(b)", tempreg, lw_reloc_type,
5302 if (lw_reloc_type != BFD_RELOC_MIPS_GOT_DISP)
5303 p = frag_var (rs_machine_dependent, 0, 0,
5304 RELAX_ENCODE (0, 0, -4, 0, 0, 0),
5305 offset_expr.X_add_symbol, 0, NULL);
5310 /* To avoid confusion in tc_gen_reloc, we must ensure
5311 that this does not become a variant frag. */
5312 frag_wane (frag_now);
5316 else if (mips_pic == SVR4_PIC && ! HAVE_NEWABI)
5320 int lui_reloc_type = (int) BFD_RELOC_MIPS_GOT_HI16;
5321 int lw_reloc_type = (int) BFD_RELOC_MIPS_GOT_LO16;
5322 int local_reloc_type = (int) BFD_RELOC_MIPS_GOT16;
5324 /* This is the large GOT case. If this is a reference to an
5325 external symbol, and there is no constant, we want
5326 lui $tempreg,<sym> (BFD_RELOC_MIPS_GOT_HI16)
5327 addu $tempreg,$tempreg,$gp
5328 lw $tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_LO16)
5329 or if tempreg is PIC_CALL_REG
5330 lui $tempreg,<sym> (BFD_RELOC_MIPS_CALL_HI16)
5331 addu $tempreg,$tempreg,$gp
5332 lw $tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_CALL_LO16)
5333 For a local symbol, we want
5334 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
5336 addiu $tempreg,$tempreg,<sym> (BFD_RELOC_LO16)
5338 If we have a small constant, and this is a reference to
5339 an external symbol, we want
5340 lui $tempreg,<sym> (BFD_RELOC_MIPS_GOT_HI16)
5341 addu $tempreg,$tempreg,$gp
5342 lw $tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_LO16)
5344 addiu $tempreg,$tempreg,<constant>
5345 For a local symbol, we want
5346 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
5348 addiu $tempreg,$tempreg,<constant> (BFD_RELOC_LO16)
5350 If we have a large constant, and this is a reference to
5351 an external symbol, we want
5352 lui $tempreg,<sym> (BFD_RELOC_MIPS_GOT_HI16)
5353 addu $tempreg,$tempreg,$gp
5354 lw $tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_LO16)
5355 lui $at,<hiconstant>
5356 addiu $at,$at,<loconstant>
5357 addu $tempreg,$tempreg,$at
5358 For a local symbol, we want
5359 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
5360 lui $at,<hiconstant>
5361 addiu $at,$at,<loconstant> (BFD_RELOC_LO16)
5362 addu $tempreg,$tempreg,$at
5365 expr1.X_add_number = offset_expr.X_add_number;
5366 offset_expr.X_add_number = 0;
5368 if (reg_needs_delay (mips_gp_register))
5372 if (expr1.X_add_number == 0 && tempreg == PIC_CALL_REG)
5374 lui_reloc_type = (int) BFD_RELOC_MIPS_CALL_HI16;
5375 lw_reloc_type = (int) BFD_RELOC_MIPS_CALL_LO16;
5377 macro_build ((char *) NULL, &icnt, &offset_expr, "lui", "t,u",
5378 tempreg, lui_reloc_type);
5379 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5380 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
5381 "d,v,t", tempreg, tempreg, mips_gp_register);
5382 macro_build ((char *) NULL, &icnt, &offset_expr,
5383 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
5384 "t,o(b)", tempreg, lw_reloc_type, tempreg);
5385 if (expr1.X_add_number == 0)
5393 /* We're going to put in an addu instruction using
5394 tempreg, so we may as well insert the nop right
5396 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5401 p = frag_var (rs_machine_dependent, 12 + gpdel, 0,
5402 RELAX_ENCODE (12 + off, 12 + gpdel, gpdel,
5405 ? mips_opts.warn_about_macros
5407 offset_expr.X_add_symbol, 0, NULL);
5409 else if (expr1.X_add_number >= -0x8000
5410 && expr1.X_add_number < 0x8000)
5412 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5414 macro_build ((char *) NULL, &icnt, &expr1,
5415 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
5416 "t,r,j", tempreg, tempreg, (int) BFD_RELOC_LO16);
5418 p = frag_var (rs_machine_dependent, 12 + gpdel, 0,
5419 RELAX_ENCODE (20, 12 + gpdel, gpdel, 8 + gpdel, 0,
5421 ? mips_opts.warn_about_macros
5423 offset_expr.X_add_symbol, 0, NULL);
5429 /* If we are going to add in a base register, and the
5430 target register and the base register are the same,
5431 then we are using AT as a temporary register. Since
5432 we want to load the constant into AT, we add our
5433 current AT (from the global offset table) and the
5434 register into the register now, and pretend we were
5435 not using a base register. */
5443 assert (tempreg == AT);
5444 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5446 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5447 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
5448 "d,v,t", treg, AT, breg);
5453 /* Set mips_optimize around the lui instruction to avoid
5454 inserting an unnecessary nop after the lw. */
5455 hold_mips_optimize = mips_optimize;
5457 macro_build_lui (NULL, &icnt, &expr1, AT);
5458 mips_optimize = hold_mips_optimize;
5460 macro_build ((char *) NULL, &icnt, &expr1,
5461 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
5462 "t,r,j", AT, AT, (int) BFD_RELOC_LO16);
5463 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5464 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
5465 "d,v,t", dreg, dreg, AT);
5467 p = frag_var (rs_machine_dependent, 16 + gpdel + adj, 0,
5468 RELAX_ENCODE (24 + adj, 16 + gpdel + adj, gpdel,
5471 ? mips_opts.warn_about_macros
5473 offset_expr.X_add_symbol, 0, NULL);
5480 /* This is needed because this instruction uses $gp, but
5481 the first instruction on the main stream does not. */
5482 macro_build (p, &icnt, (expressionS *) NULL, "nop", "");
5486 macro_build (p, &icnt, &offset_expr,
5487 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
5492 if (expr1.X_add_number >= -0x8000
5493 && expr1.X_add_number < 0x8000)
5495 macro_build (p, &icnt, (expressionS *) NULL, "nop", "");
5497 macro_build (p, &icnt, &expr1,
5498 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
5499 "t,r,j", tempreg, tempreg, (int) BFD_RELOC_LO16);
5500 /* FIXME: If add_number is 0, and there was no base
5501 register, the external symbol case ended with a load,
5502 so if the symbol turns out to not be external, and
5503 the next instruction uses tempreg, an unnecessary nop
5504 will be inserted. */
5510 /* We must add in the base register now, as in the
5511 external symbol case. */
5512 assert (tempreg == AT);
5513 macro_build (p, &icnt, (expressionS *) NULL, "nop", "");
5515 macro_build (p, &icnt, (expressionS *) NULL,
5516 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
5517 "d,v,t", treg, AT, breg);
5520 /* We set breg to 0 because we have arranged to add
5521 it in in both cases. */
5525 macro_build_lui (p, &icnt, &expr1, AT);
5527 macro_build (p, &icnt, &expr1,
5528 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
5529 "t,r,j", AT, AT, (int) BFD_RELOC_LO16);
5531 macro_build (p, &icnt, (expressionS *) NULL,
5532 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
5533 "d,v,t", tempreg, tempreg, AT);
5537 else if (mips_pic == SVR4_PIC && HAVE_NEWABI)
5540 int lui_reloc_type = (int) BFD_RELOC_MIPS_GOT_HI16;
5541 int lw_reloc_type = (int) BFD_RELOC_MIPS_GOT_LO16;
5544 /* This is the large GOT case. If this is a reference to an
5545 external symbol, and there is no constant, we want
5546 lui $tempreg,<sym> (BFD_RELOC_MIPS_GOT_HI16)
5547 add $tempreg,$tempreg,$gp
5548 lw $tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_LO16)
5549 or if tempreg is PIC_CALL_REG
5550 lui $tempreg,<sym> (BFD_RELOC_MIPS_CALL_HI16)
5551 add $tempreg,$tempreg,$gp
5552 lw $tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_CALL_LO16)
5554 If we have a small constant, and this is a reference to
5555 an external symbol, we want
5556 lui $tempreg,<sym> (BFD_RELOC_MIPS_GOT_HI16)
5557 add $tempreg,$tempreg,$gp
5558 lw $tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_LO16)
5559 addi $tempreg,$tempreg,<constant>
5561 If we have a large constant, and this is a reference to
5562 an external symbol, we want
5563 lui $tempreg,<sym> (BFD_RELOC_MIPS_GOT_HI16)
5564 addu $tempreg,$tempreg,$gp
5565 lw $tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_LO16)
5566 lui $at,<hiconstant>
5567 addi $at,$at,<loconstant>
5568 add $tempreg,$tempreg,$at
5570 If we have NewABI, and we know it's a local symbol, we want
5571 lw $reg,<sym>($gp) (BFD_RELOC_MIPS_GOT_PAGE)
5572 addiu $reg,$reg,<sym> (BFD_RELOC_MIPS_GOT_OFST)
5573 otherwise we have to resort to GOT_HI16/GOT_LO16. */
5577 frag_now->tc_frag_data.tc_fr_offset =
5578 expr1.X_add_number = offset_expr.X_add_number;
5579 offset_expr.X_add_number = 0;
5581 if (expr1.X_add_number == 0 && tempreg == PIC_CALL_REG)
5583 lui_reloc_type = (int) BFD_RELOC_MIPS_CALL_HI16;
5584 lw_reloc_type = (int) BFD_RELOC_MIPS_CALL_LO16;
5586 macro_build ((char *) NULL, &icnt, &offset_expr, "lui", "t,u",
5587 tempreg, lui_reloc_type);
5588 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5589 HAVE_32BIT_ADDRESSES ? "add" : "daddu",
5590 "d,v,t", tempreg, tempreg, mips_gp_register);
5591 macro_build ((char *) NULL, &icnt, &offset_expr,
5592 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
5593 "t,o(b)", tempreg, lw_reloc_type, tempreg);
5595 if (expr1.X_add_number == 0)
5597 p = frag_var (rs_machine_dependent, 8, 0,
5598 RELAX_ENCODE (12, 8, 0, 4, 0,
5599 mips_opts.warn_about_macros),
5600 offset_expr.X_add_symbol, 0, NULL);
5602 else if (expr1.X_add_number >= -0x8000
5603 && expr1.X_add_number < 0x8000)
5605 macro_build ((char *) NULL, &icnt, &expr1,
5606 HAVE_32BIT_ADDRESSES ? "addi" : "daddiu",
5607 "t,r,j", tempreg, tempreg,
5608 (int) BFD_RELOC_LO16);
5609 p = frag_var (rs_machine_dependent, 8, 0,
5610 RELAX_ENCODE (16, 8, 0, 4, 0,
5611 mips_opts.warn_about_macros),
5612 offset_expr.X_add_symbol, 0, NULL);
5614 else if (IS_SEXT_32BIT_NUM (expr1.X_add_number))
5618 /* If we are going to add in a base register, and the
5619 target register and the base register are the same,
5620 then we are using AT as a temporary register. Since
5621 we want to load the constant into AT, we add our
5622 current AT (from the global offset table) and the
5623 register into the register now, and pretend we were
5624 not using a base register. */
5629 assert (tempreg == AT);
5630 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5631 HAVE_32BIT_ADDRESSES ? "add" : "daddu",
5632 "d,v,t", treg, AT, breg);
5637 /* Set mips_optimize around the lui instruction to avoid
5638 inserting an unnecessary nop after the lw. */
5639 macro_build_lui ((char *) NULL, &icnt, &expr1, AT);
5640 macro_build ((char *) NULL, &icnt, &expr1,
5641 HAVE_32BIT_ADDRESSES ? "addi" : "daddiu",
5642 "t,r,j", AT, AT, (int) BFD_RELOC_LO16);
5643 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5644 HAVE_32BIT_ADDRESSES ? "add" : "daddu",
5645 "d,v,t", dreg, dreg, AT);
5647 p = frag_var (rs_machine_dependent, 8 + adj, 0,
5648 RELAX_ENCODE (24 + adj, 8 + adj,
5651 ? mips_opts.warn_about_macros
5653 offset_expr.X_add_symbol, 0, NULL);
5658 as_bad (_("PIC code offset overflow (max 32 signed bits)"));
5660 offset_expr.X_add_number = expr1.X_add_number;
5661 macro_build (p, &icnt, &offset_expr,
5662 HAVE_32BIT_ADDRESSES ? "lw" : "ld", "t,o(b)",
5664 (int) BFD_RELOC_MIPS_GOT_PAGE, mips_gp_register);
5665 macro_build (p + 4, &icnt, &offset_expr,
5666 HAVE_32BIT_ADDRESSES ? "addi" : "daddiu", "t,r,j",
5667 tempreg, tempreg, (int) BFD_RELOC_MIPS_GOT_OFST);
5670 macro_build (p + 8, &icnt, (expressionS *) NULL,
5671 HAVE_32BIT_ADDRESSES ? "add" : "daddu",
5672 "d,v,t", treg, tempreg, breg);
5677 else if (mips_pic == EMBEDDED_PIC)
5680 addiu $tempreg,$gp,<sym> (BFD_RELOC_GPREL16)
5682 macro_build ((char *) NULL, &icnt, &offset_expr,
5683 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu", "t,r,j",
5684 tempreg, mips_gp_register, (int) BFD_RELOC_GPREL16);
5693 if (mips_pic == EMBEDDED_PIC || mips_pic == NO_PIC)
5694 s = (dbl || HAVE_64BIT_ADDRESSES) ? "daddu" :
5695 HAVE_NEWABI ? "add" : "addu";
5697 s = HAVE_64BIT_ADDRESSES ? "daddu" : HAVE_NEWABI ? "add" : "addu";
5699 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s,
5700 "d,v,t", treg, tempreg, breg);
5709 /* The j instruction may not be used in PIC code, since it
5710 requires an absolute address. We convert it to a b
5712 if (mips_pic == NO_PIC)
5713 macro_build ((char *) NULL, &icnt, &offset_expr, "j", "a");
5715 macro_build ((char *) NULL, &icnt, &offset_expr, "b", "p");
5718 /* The jal instructions must be handled as macros because when
5719 generating PIC code they expand to multi-instruction
5720 sequences. Normally they are simple instructions. */
5725 if (mips_pic == NO_PIC
5726 || mips_pic == EMBEDDED_PIC)
5727 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "jalr",
5729 else if (mips_pic == SVR4_PIC)
5731 if (sreg != PIC_CALL_REG)
5732 as_warn (_("MIPS PIC call to register other than $25"));
5734 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "jalr",
5738 if (mips_cprestore_offset < 0)
5739 as_warn (_("No .cprestore pseudo-op used in PIC code"));
5742 if (! mips_frame_reg_valid)
5744 as_warn (_("No .frame pseudo-op used in PIC code"));
5745 /* Quiet this warning. */
5746 mips_frame_reg_valid = 1;
5748 if (! mips_cprestore_valid)
5750 as_warn (_("No .cprestore pseudo-op used in PIC code"));
5751 /* Quiet this warning. */
5752 mips_cprestore_valid = 1;
5754 expr1.X_add_number = mips_cprestore_offset;
5755 macro_build_ldst_constoffset ((char *) NULL, &icnt, &expr1,
5756 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
5757 mips_gp_register, mips_frame_reg);
5767 if (mips_pic == NO_PIC)
5768 macro_build ((char *) NULL, &icnt, &offset_expr, "jal", "a");
5769 else if (mips_pic == SVR4_PIC)
5773 /* If this is a reference to an external symbol, and we are
5774 using a small GOT, we want
5775 lw $25,<sym>($gp) (BFD_RELOC_MIPS_CALL16)
5779 lw $gp,cprestore($sp)
5780 The cprestore value is set using the .cprestore
5781 pseudo-op. If we are using a big GOT, we want
5782 lui $25,<sym> (BFD_RELOC_MIPS_CALL_HI16)
5784 lw $25,<sym>($25) (BFD_RELOC_MIPS_CALL_LO16)
5788 lw $gp,cprestore($sp)
5789 If the symbol is not external, we want
5790 lw $25,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
5792 addiu $25,$25,<sym> (BFD_RELOC_LO16)
5795 lw $gp,cprestore($sp)
5797 For NewABI, we use the same CALL16 or CALL_HI16/CALL_LO16
5798 sequences above, minus nops, unless the symbol is local,
5799 which enables us to use GOT_PAGE/GOT_OFST (big got) or
5806 macro_build ((char *) NULL, &icnt, &offset_expr,
5807 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
5808 "t,o(b)", PIC_CALL_REG,
5809 (int) BFD_RELOC_MIPS_CALL16,
5811 frag_var (rs_machine_dependent, 0, 0,
5812 RELAX_ENCODE (0, 0, -4, 0, 0, 0),
5813 offset_expr.X_add_symbol, 0, NULL);
5818 macro_build ((char *) NULL, &icnt, &offset_expr, "lui",
5819 "t,u", PIC_CALL_REG,
5820 (int) BFD_RELOC_MIPS_CALL_HI16);
5821 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5822 HAVE_32BIT_ADDRESSES ? "add" : "daddu",
5823 "d,v,t", PIC_CALL_REG, PIC_CALL_REG,
5825 macro_build ((char *) NULL, &icnt, &offset_expr,
5826 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
5827 "t,o(b)", PIC_CALL_REG,
5828 (int) BFD_RELOC_MIPS_CALL_LO16, PIC_CALL_REG);
5829 p = frag_var (rs_machine_dependent, 8, 0,
5830 RELAX_ENCODE (12, 8, 0, 4, 0, 0),
5831 offset_expr.X_add_symbol, 0, NULL);
5832 macro_build (p, &icnt, &offset_expr,
5833 HAVE_32BIT_ADDRESSES ? "lw" : "ld", "t,o(b)",
5834 tempreg, (int) BFD_RELOC_MIPS_GOT_PAGE,
5836 macro_build (p + 4, &icnt, &offset_expr,
5837 HAVE_32BIT_ADDRESSES ? "addi" : "daddiu",
5838 "t,r,j", tempreg, tempreg,
5839 (int) BFD_RELOC_MIPS_GOT_OFST);
5842 macro_build_jalr (icnt, &offset_expr);
5849 macro_build ((char *) NULL, &icnt, &offset_expr,
5850 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
5851 "t,o(b)", PIC_CALL_REG,
5852 (int) BFD_RELOC_MIPS_CALL16, mips_gp_register);
5853 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5855 p = frag_var (rs_machine_dependent, 4, 0,
5856 RELAX_ENCODE (0, 4, -8, 0, 0, 0),
5857 offset_expr.X_add_symbol, 0, NULL);
5863 if (reg_needs_delay (mips_gp_register))
5867 macro_build ((char *) NULL, &icnt, &offset_expr, "lui",
5868 "t,u", PIC_CALL_REG,
5869 (int) BFD_RELOC_MIPS_CALL_HI16);
5870 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5871 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
5872 "d,v,t", PIC_CALL_REG, PIC_CALL_REG,
5874 macro_build ((char *) NULL, &icnt, &offset_expr,
5875 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
5876 "t,o(b)", PIC_CALL_REG,
5877 (int) BFD_RELOC_MIPS_CALL_LO16, PIC_CALL_REG);
5878 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5880 p = frag_var (rs_machine_dependent, 12 + gpdel, 0,
5881 RELAX_ENCODE (16, 12 + gpdel, gpdel,
5883 offset_expr.X_add_symbol, 0, NULL);
5886 macro_build (p, &icnt, (expressionS *) NULL, "nop", "");
5889 macro_build (p, &icnt, &offset_expr,
5890 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
5891 "t,o(b)", PIC_CALL_REG,
5892 (int) BFD_RELOC_MIPS_GOT16, mips_gp_register);
5894 macro_build (p, &icnt, (expressionS *) NULL, "nop", "");
5897 macro_build (p, &icnt, &offset_expr,
5898 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
5899 "t,r,j", PIC_CALL_REG, PIC_CALL_REG,
5900 (int) BFD_RELOC_LO16);
5901 macro_build_jalr (icnt, &offset_expr);
5903 if (mips_cprestore_offset < 0)
5904 as_warn (_("No .cprestore pseudo-op used in PIC code"));
5907 if (! mips_frame_reg_valid)
5909 as_warn (_("No .frame pseudo-op used in PIC code"));
5910 /* Quiet this warning. */
5911 mips_frame_reg_valid = 1;
5913 if (! mips_cprestore_valid)
5915 as_warn (_("No .cprestore pseudo-op used in PIC code"));
5916 /* Quiet this warning. */
5917 mips_cprestore_valid = 1;
5919 if (mips_opts.noreorder)
5920 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5922 expr1.X_add_number = mips_cprestore_offset;
5923 macro_build_ldst_constoffset ((char *) NULL, &icnt, &expr1,
5924 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
5925 mips_gp_register, mips_frame_reg);
5929 else if (mips_pic == EMBEDDED_PIC)
5931 macro_build ((char *) NULL, &icnt, &offset_expr, "bal", "p");
5932 /* The linker may expand the call to a longer sequence which
5933 uses $at, so we must break rather than return. */
5958 /* Itbl support may require additional care here. */
5963 /* Itbl support may require additional care here. */
5968 /* Itbl support may require additional care here. */
5973 /* Itbl support may require additional care here. */
5985 if (mips_arch == CPU_R4650)
5987 as_bad (_("opcode not supported on this processor"));
5991 /* Itbl support may require additional care here. */
5996 /* Itbl support may require additional care here. */
6001 /* Itbl support may require additional care here. */
6021 if (breg == treg || coproc || lr)
6043 /* Itbl support may require additional care here. */
6048 /* Itbl support may require additional care here. */
6053 /* Itbl support may require additional care here. */
6058 /* Itbl support may require additional care here. */
6074 if (mips_arch == CPU_R4650)
6076 as_bad (_("opcode not supported on this processor"));
6081 /* Itbl support may require additional care here. */
6085 /* Itbl support may require additional care here. */
6090 /* Itbl support may require additional care here. */
6102 /* Itbl support may require additional care here. */
6103 if (mask == M_LWC1_AB
6104 || mask == M_SWC1_AB
6105 || mask == M_LDC1_AB
6106 || mask == M_SDC1_AB
6115 /* For embedded PIC, we allow loads where the offset is calculated
6116 by subtracting a symbol in the current segment from an unknown
6117 symbol, relative to a base register, e.g.:
6118 <op> $treg, <sym>-<localsym>($breg)
6119 This is used by the compiler for switch statements. */
6120 if (mips_pic == EMBEDDED_PIC
6121 && offset_expr.X_op == O_subtract
6122 && (symbol_constant_p (offset_expr.X_op_symbol)
6123 ? S_GET_SEGMENT (offset_expr.X_op_symbol) == now_seg
6124 : (symbol_equated_p (offset_expr.X_op_symbol)
6126 (symbol_get_value_expression (offset_expr.X_op_symbol)
6130 && (offset_expr.X_add_number == 0
6131 || OUTPUT_FLAVOR == bfd_target_elf_flavour))
6133 /* For this case, we output the instructions:
6134 lui $tempreg,<sym> (BFD_RELOC_PCREL_HI16_S)
6135 addiu $tempreg,$tempreg,$breg
6136 <op> $treg,<sym>($tempreg) (BFD_RELOC_PCREL_LO16)
6137 If the relocation would fit entirely in 16 bits, it would be
6139 <op> $treg,<sym>($breg) (BFD_RELOC_PCREL_LO16)
6140 instead, but that seems quite difficult. */
6141 macro_build ((char *) NULL, &icnt, &offset_expr, "lui", "t,u",
6142 tempreg, (int) BFD_RELOC_PCREL_HI16_S);
6143 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6144 ((bfd_arch_bits_per_address (stdoutput) == 32
6145 || ! ISA_HAS_64BIT_REGS (mips_opts.isa))
6146 ? HAVE_NEWABI ? "add" : "addu" : "daddu"),
6147 "d,v,t", tempreg, tempreg, breg);
6148 macro_build ((char *) NULL, &icnt, &offset_expr, s, fmt, treg,
6149 (int) BFD_RELOC_PCREL_LO16, tempreg);
6155 if (offset_expr.X_op != O_constant
6156 && offset_expr.X_op != O_symbol)
6158 as_bad (_("expression too complex"));
6159 offset_expr.X_op = O_constant;
6162 /* A constant expression in PIC code can be handled just as it
6163 is in non PIC code. */
6164 if (mips_pic == NO_PIC
6165 || offset_expr.X_op == O_constant)
6169 /* If this is a reference to a GP relative symbol, and there
6170 is no base register, we want
6171 <op> $treg,<sym>($gp) (BFD_RELOC_GPREL16)
6172 Otherwise, if there is no base register, we want
6173 lui $tempreg,<sym> (BFD_RELOC_HI16_S)
6174 <op> $treg,<sym>($tempreg) (BFD_RELOC_LO16)
6175 If we have a constant, we need two instructions anyhow,
6176 so we always use the latter form.
6178 If we have a base register, and this is a reference to a
6179 GP relative symbol, we want
6180 addu $tempreg,$breg,$gp
6181 <op> $treg,<sym>($tempreg) (BFD_RELOC_GPREL16)
6183 lui $tempreg,<sym> (BFD_RELOC_HI16_S)
6184 addu $tempreg,$tempreg,$breg
6185 <op> $treg,<sym>($tempreg) (BFD_RELOC_LO16)
6186 With a constant we always use the latter case.
6188 With 64bit address space and no base register and $at usable,
6190 lui $tempreg,<sym> (BFD_RELOC_MIPS_HIGHEST)
6191 lui $at,<sym> (BFD_RELOC_HI16_S)
6192 daddiu $tempreg,<sym> (BFD_RELOC_MIPS_HIGHER)
6195 <op> $treg,<sym>($tempreg) (BFD_RELOC_LO16)
6196 If we have a base register, we want
6197 lui $tempreg,<sym> (BFD_RELOC_MIPS_HIGHEST)
6198 lui $at,<sym> (BFD_RELOC_HI16_S)
6199 daddiu $tempreg,<sym> (BFD_RELOC_MIPS_HIGHER)
6203 <op> $treg,<sym>($tempreg) (BFD_RELOC_LO16)
6205 Without $at we can't generate the optimal path for superscalar
6206 processors here since this would require two temporary registers.
6207 lui $tempreg,<sym> (BFD_RELOC_MIPS_HIGHEST)
6208 daddiu $tempreg,<sym> (BFD_RELOC_MIPS_HIGHER)
6210 daddiu $tempreg,<sym> (BFD_RELOC_HI16_S)
6212 <op> $treg,<sym>($tempreg) (BFD_RELOC_LO16)
6213 If we have a base register, we want
6214 lui $tempreg,<sym> (BFD_RELOC_MIPS_HIGHEST)
6215 daddiu $tempreg,<sym> (BFD_RELOC_MIPS_HIGHER)
6217 daddiu $tempreg,<sym> (BFD_RELOC_HI16_S)
6219 daddu $tempreg,$tempreg,$breg
6220 <op> $treg,<sym>($tempreg) (BFD_RELOC_LO16)
6222 If we have 64-bit addresses, as an optimization, for
6223 addresses which are 32-bit constants (e.g. kseg0/kseg1
6224 addresses) we fall back to the 32-bit address generation
6225 mechanism since it is more efficient. Note that due to
6226 the signed offset used by memory operations, the 32-bit
6227 range is shifted down by 32768 here. This code should
6228 probably attempt to generate 64-bit constants more
6229 efficiently in general.
6231 As an extension for architectures with 64-bit registers,
6232 we don't truncate 64-bit addresses given as literal
6233 constants down to 32 bits, to support existing practice
6234 in the mips64 Linux (the kernel), that compiles source
6235 files with -mabi=64, assembling them as o32 or n32 (with
6236 -Wa,-32 or -Wa,-n32). This is not beautiful, but since
6237 the whole kernel is loaded into a memory region that is
6238 addressible with sign-extended 32-bit addresses, it is
6239 wasteful to compute the upper 32 bits of every
6240 non-literal address, that takes more space and time.
6241 Some day this should probably be implemented as an
6242 assembler option, such that the kernel doesn't have to
6243 use such ugly hacks, even though it will still have to
6244 end up converting the binary to ELF32 for a number of
6245 platforms whose boot loaders don't support ELF64
6247 if ((offset_expr.X_op != O_constant && HAVE_64BIT_ADDRESSES)
6248 || (offset_expr.X_op == O_constant
6249 && !IS_SEXT_32BIT_NUM (offset_expr.X_add_number + 0x8000)
6250 && HAVE_64BIT_ADDRESS_CONSTANTS))
6254 /* We don't do GP optimization for now because RELAX_ENCODE can't
6255 hold the data for such large chunks. */
6257 if (used_at == 0 && ! mips_opts.noat)
6259 macro_build (p, &icnt, &offset_expr, "lui", "t,u",
6260 tempreg, (int) BFD_RELOC_MIPS_HIGHEST);
6261 macro_build (p, &icnt, &offset_expr, "lui", "t,u",
6262 AT, (int) BFD_RELOC_HI16_S);
6263 macro_build (p, &icnt, &offset_expr, "daddiu", "t,r,j",
6264 tempreg, tempreg, (int) BFD_RELOC_MIPS_HIGHER);
6266 macro_build (p, &icnt, (expressionS *) NULL, "daddu",
6267 "d,v,t", AT, AT, breg);
6268 macro_build (p, &icnt, (expressionS *) NULL, "dsll32",
6269 "d,w,<", tempreg, tempreg, 0);
6270 macro_build (p, &icnt, (expressionS *) NULL, "daddu",
6271 "d,v,t", tempreg, tempreg, AT);
6272 macro_build (p, &icnt, &offset_expr, s,
6273 fmt, treg, (int) BFD_RELOC_LO16, tempreg);
6278 macro_build (p, &icnt, &offset_expr, "lui", "t,u",
6279 tempreg, (int) BFD_RELOC_MIPS_HIGHEST);
6280 macro_build (p, &icnt, &offset_expr, "daddiu", "t,r,j",
6281 tempreg, tempreg, (int) BFD_RELOC_MIPS_HIGHER);
6282 macro_build (p, &icnt, (expressionS *) NULL, "dsll",
6283 "d,w,<", tempreg, tempreg, 16);
6284 macro_build (p, &icnt, &offset_expr, "daddiu", "t,r,j",
6285 tempreg, tempreg, (int) BFD_RELOC_HI16_S);
6286 macro_build (p, &icnt, (expressionS *) NULL, "dsll",
6287 "d,w,<", tempreg, tempreg, 16);
6289 macro_build (p, &icnt, (expressionS *) NULL, "daddu",
6290 "d,v,t", tempreg, tempreg, breg);
6291 macro_build (p, &icnt, &offset_expr, s,
6292 fmt, treg, (int) BFD_RELOC_LO16, tempreg);
6297 else if (offset_expr.X_op == O_constant
6298 && !HAVE_64BIT_ADDRESS_CONSTANTS
6299 && !IS_SEXT_32BIT_NUM (offset_expr.X_add_number))
6300 as_bad (_("load/store address overflow (max 32 bits)"));
6304 if ((valueT) offset_expr.X_add_number > MAX_GPREL_OFFSET
6305 || nopic_need_relax (offset_expr.X_add_symbol, 1))
6310 macro_build ((char *) NULL, &icnt, &offset_expr, s, fmt,
6311 treg, (int) BFD_RELOC_GPREL16,
6313 p = frag_var (rs_machine_dependent, 8, 0,
6314 RELAX_ENCODE (4, 8, 0, 4, 0,
6315 (mips_opts.warn_about_macros
6317 && mips_opts.noat))),
6318 offset_expr.X_add_symbol, 0, NULL);
6321 macro_build_lui (p, &icnt, &offset_expr, tempreg);
6324 macro_build (p, &icnt, &offset_expr, s, fmt, treg,
6325 (int) BFD_RELOC_LO16, tempreg);
6329 if ((valueT) offset_expr.X_add_number > MAX_GPREL_OFFSET
6330 || nopic_need_relax (offset_expr.X_add_symbol, 1))
6335 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6336 HAVE_32BIT_ADDRESSES ? HAVE_NEWABI
6337 ? "add" : "addu" : "daddu",
6338 "d,v,t", tempreg, breg, mips_gp_register);
6339 macro_build ((char *) NULL, &icnt, &offset_expr, s, fmt,
6340 treg, (int) BFD_RELOC_GPREL16, tempreg);
6341 p = frag_var (rs_machine_dependent, 12, 0,
6342 RELAX_ENCODE (8, 12, 0, 8, 0, 0),
6343 offset_expr.X_add_symbol, 0, NULL);
6345 macro_build_lui (p, &icnt, &offset_expr, tempreg);
6348 macro_build (p, &icnt, (expressionS *) NULL,
6349 HAVE_32BIT_ADDRESSES ? HAVE_NEWABI
6350 ? "add" : "addu" : "daddu",
6351 "d,v,t", tempreg, tempreg, breg);
6354 macro_build (p, &icnt, &offset_expr, s, fmt, treg,
6355 (int) BFD_RELOC_LO16, tempreg);
6358 else if (mips_pic == SVR4_PIC && ! mips_big_got)
6361 int lw_reloc_type = (int) BFD_RELOC_MIPS_GOT16;
6363 /* If this is a reference to an external symbol, we want
6364 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
6366 <op> $treg,0($tempreg)
6368 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
6370 addiu $tempreg,$tempreg,<sym> (BFD_RELOC_LO16)
6371 <op> $treg,0($tempreg)
6374 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT_PAGE)
6375 <op> $treg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_OFST)
6377 If there is a base register, we add it to $tempreg before
6378 the <op>. If there is a constant, we stick it in the
6379 <op> instruction. We don't handle constants larger than
6380 16 bits, because we have no way to load the upper 16 bits
6381 (actually, we could handle them for the subset of cases
6382 in which we are not using $at). */
6383 assert (offset_expr.X_op == O_symbol);
6386 macro_build ((char *) NULL, &icnt, &offset_expr,
6387 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
6388 "t,o(b)", tempreg, BFD_RELOC_MIPS_GOT_PAGE,
6391 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6392 HAVE_32BIT_ADDRESSES ? "add" : "daddu",
6393 "d,v,t", tempreg, tempreg, breg);
6394 macro_build ((char *) NULL, &icnt, &offset_expr, s, fmt, treg,
6395 (int) BFD_RELOC_MIPS_GOT_OFST, tempreg);
6402 expr1.X_add_number = offset_expr.X_add_number;
6403 offset_expr.X_add_number = 0;
6404 if (expr1.X_add_number < -0x8000
6405 || expr1.X_add_number >= 0x8000)
6406 as_bad (_("PIC code offset overflow (max 16 signed bits)"));
6408 macro_build ((char *) NULL, &icnt, &offset_expr,
6409 HAVE_32BIT_ADDRESSES ? "lw" : "ld", "t,o(b)", tempreg,
6410 (int) lw_reloc_type, mips_gp_register);
6411 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "");
6412 p = frag_var (rs_machine_dependent, 4, 0,
6413 RELAX_ENCODE (0, 4, -8, 0, 0, 0),
6414 offset_expr.X_add_symbol, 0, NULL);
6415 macro_build (p, &icnt, &offset_expr,
6416 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
6417 "t,r,j", tempreg, tempreg, (int) BFD_RELOC_LO16);
6419 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6420 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
6421 "d,v,t", tempreg, tempreg, breg);
6422 macro_build ((char *) NULL, &icnt, &expr1, s, fmt, treg,
6423 (int) BFD_RELOC_LO16, tempreg);
6425 else if (mips_pic == SVR4_PIC && ! HAVE_NEWABI)
6430 /* If this is a reference to an external symbol, we want
6431 lui $tempreg,<sym> (BFD_RELOC_MIPS_GOT_HI16)
6432 addu $tempreg,$tempreg,$gp
6433 lw $tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_LO16)
6434 <op> $treg,0($tempreg)
6436 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
6438 addiu $tempreg,$tempreg,<sym> (BFD_RELOC_LO16)
6439 <op> $treg,0($tempreg)
6440 If there is a base register, we add it to $tempreg before
6441 the <op>. If there is a constant, we stick it in the
6442 <op> instruction. We don't handle constants larger than
6443 16 bits, because we have no way to load the upper 16 bits
6444 (actually, we could handle them for the subset of cases
6445 in which we are not using $at). */
6446 assert (offset_expr.X_op == O_symbol);
6447 expr1.X_add_number = offset_expr.X_add_number;
6448 offset_expr.X_add_number = 0;
6449 if (expr1.X_add_number < -0x8000
6450 || expr1.X_add_number >= 0x8000)
6451 as_bad (_("PIC code offset overflow (max 16 signed bits)"));
6452 if (reg_needs_delay (mips_gp_register))
6457 macro_build ((char *) NULL, &icnt, &offset_expr, "lui", "t,u",
6458 tempreg, (int) BFD_RELOC_MIPS_GOT_HI16);
6459 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6460 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
6461 "d,v,t", tempreg, tempreg, mips_gp_register);
6462 macro_build ((char *) NULL, &icnt, &offset_expr,
6463 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
6464 "t,o(b)", tempreg, (int) BFD_RELOC_MIPS_GOT_LO16,
6466 p = frag_var (rs_machine_dependent, 12 + gpdel, 0,
6467 RELAX_ENCODE (12, 12 + gpdel, gpdel, 8 + gpdel, 0, 0),
6468 offset_expr.X_add_symbol, 0, NULL);
6471 macro_build (p, &icnt, (expressionS *) NULL, "nop", "");
6474 macro_build (p, &icnt, &offset_expr,
6475 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
6476 "t,o(b)", tempreg, (int) BFD_RELOC_MIPS_GOT16,
6479 macro_build (p, &icnt, (expressionS *) NULL, "nop", "");
6481 macro_build (p, &icnt, &offset_expr,
6482 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
6483 "t,r,j", tempreg, tempreg, (int) BFD_RELOC_LO16);
6485 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6486 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
6487 "d,v,t", tempreg, tempreg, breg);
6488 macro_build ((char *) NULL, &icnt, &expr1, s, fmt, treg,
6489 (int) BFD_RELOC_LO16, tempreg);
6491 else if (mips_pic == SVR4_PIC && HAVE_NEWABI)
6494 int bregsz = breg != 0 ? 4 : 0;
6496 /* If this is a reference to an external symbol, we want
6497 lui $tempreg,<sym> (BFD_RELOC_MIPS_GOT_HI16)
6498 add $tempreg,$tempreg,$gp
6499 lw $tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_LO16)
6500 <op> $treg,<ofst>($tempreg)
6501 Otherwise, for local symbols, we want:
6502 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT_PAGE)
6503 <op> $treg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_OFST) */
6504 assert (offset_expr.X_op == O_symbol);
6505 frag_now->tc_frag_data.tc_fr_offset =
6506 expr1.X_add_number = offset_expr.X_add_number;
6507 offset_expr.X_add_number = 0;
6508 if (expr1.X_add_number < -0x8000
6509 || expr1.X_add_number >= 0x8000)
6510 as_bad (_("PIC code offset overflow (max 16 signed bits)"));
6512 macro_build ((char *) NULL, &icnt, &offset_expr, "lui", "t,u",
6513 tempreg, (int) BFD_RELOC_MIPS_GOT_HI16);
6514 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6515 HAVE_32BIT_ADDRESSES ? "add" : "daddu",
6516 "d,v,t", tempreg, tempreg, mips_gp_register);
6517 macro_build ((char *) NULL, &icnt, &offset_expr,
6518 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
6519 "t,o(b)", tempreg, (int) BFD_RELOC_MIPS_GOT_LO16,
6522 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6523 HAVE_32BIT_ADDRESSES ? "add" : "daddu",
6524 "d,v,t", tempreg, tempreg, breg);
6525 macro_build ((char *) NULL, &icnt, &expr1, s, fmt, treg,
6526 (int) BFD_RELOC_LO16, tempreg);
6528 offset_expr.X_add_number = expr1.X_add_number;
6529 p = frag_var (rs_machine_dependent, 12 + bregsz, 0,
6530 RELAX_ENCODE (16 + bregsz, 8 + bregsz,
6531 0, 4 + bregsz, 0, 0),
6532 offset_expr.X_add_symbol, 0, NULL);
6533 macro_build (p, &icnt, &offset_expr,
6534 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
6536 (int) BFD_RELOC_MIPS_GOT_PAGE,
6539 macro_build (p + 4, &icnt, (expressionS *) NULL,
6540 HAVE_32BIT_ADDRESSES ? "add" : "daddu",
6541 "d,v,t", tempreg, tempreg, breg);
6542 macro_build (p + 4 + bregsz, &icnt, &offset_expr, s, fmt, treg,
6543 (int) BFD_RELOC_MIPS_GOT_OFST, tempreg);
6545 else if (mips_pic == EMBEDDED_PIC)
6547 /* If there is no base register, we want
6548 <op> $treg,<sym>($gp) (BFD_RELOC_GPREL16)
6549 If there is a base register, we want
6550 addu $tempreg,$breg,$gp
6551 <op> $treg,<sym>($tempreg) (BFD_RELOC_GPREL16)
6553 assert (offset_expr.X_op == O_symbol);
6556 macro_build ((char *) NULL, &icnt, &offset_expr, s, fmt,
6557 treg, (int) BFD_RELOC_GPREL16, mips_gp_register);
6562 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6563 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
6564 "d,v,t", tempreg, breg, mips_gp_register);
6565 macro_build ((char *) NULL, &icnt, &offset_expr, s, fmt,
6566 treg, (int) BFD_RELOC_GPREL16, tempreg);
6579 load_register (&icnt, treg, &imm_expr, 0);
6583 load_register (&icnt, treg, &imm_expr, 1);
6587 if (imm_expr.X_op == O_constant)
6589 load_register (&icnt, AT, &imm_expr, 0);
6590 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6591 "mtc1", "t,G", AT, treg);
6596 assert (offset_expr.X_op == O_symbol
6597 && strcmp (segment_name (S_GET_SEGMENT
6598 (offset_expr.X_add_symbol)),
6600 && offset_expr.X_add_number == 0);
6601 macro_build ((char *) NULL, &icnt, &offset_expr, "lwc1", "T,o(b)",
6602 treg, (int) BFD_RELOC_MIPS_LITERAL, mips_gp_register);
6607 /* Check if we have a constant in IMM_EXPR. If the GPRs are 64 bits
6608 wide, IMM_EXPR is the entire value. Otherwise IMM_EXPR is the high
6609 order 32 bits of the value and the low order 32 bits are either
6610 zero or in OFFSET_EXPR. */
6611 if (imm_expr.X_op == O_constant || imm_expr.X_op == O_big)
6613 if (HAVE_64BIT_GPRS)
6614 load_register (&icnt, treg, &imm_expr, 1);
6619 if (target_big_endian)
6631 load_register (&icnt, hreg, &imm_expr, 0);
6634 if (offset_expr.X_op == O_absent)
6635 move_register (&icnt, lreg, 0);
6638 assert (offset_expr.X_op == O_constant);
6639 load_register (&icnt, lreg, &offset_expr, 0);
6646 /* We know that sym is in the .rdata section. First we get the
6647 upper 16 bits of the address. */
6648 if (mips_pic == NO_PIC)
6650 macro_build_lui (NULL, &icnt, &offset_expr, AT);
6652 else if (mips_pic == SVR4_PIC)
6654 macro_build ((char *) NULL, &icnt, &offset_expr,
6655 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
6656 "t,o(b)", AT, (int) BFD_RELOC_MIPS_GOT16,
6659 else if (mips_pic == EMBEDDED_PIC)
6661 /* For embedded PIC we pick up the entire address off $gp in
6662 a single instruction. */
6663 macro_build ((char *) NULL, &icnt, &offset_expr,
6664 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu", "t,r,j", AT,
6665 mips_gp_register, (int) BFD_RELOC_GPREL16);
6666 offset_expr.X_op = O_constant;
6667 offset_expr.X_add_number = 0;
6672 /* Now we load the register(s). */
6673 if (HAVE_64BIT_GPRS)
6674 macro_build ((char *) NULL, &icnt, &offset_expr, "ld", "t,o(b)",
6675 treg, (int) BFD_RELOC_LO16, AT);
6678 macro_build ((char *) NULL, &icnt, &offset_expr, "lw", "t,o(b)",
6679 treg, (int) BFD_RELOC_LO16, AT);
6682 /* FIXME: How in the world do we deal with the possible
6684 offset_expr.X_add_number += 4;
6685 macro_build ((char *) NULL, &icnt, &offset_expr, "lw", "t,o(b)",
6686 treg + 1, (int) BFD_RELOC_LO16, AT);
6690 /* To avoid confusion in tc_gen_reloc, we must ensure that this
6691 does not become a variant frag. */
6692 frag_wane (frag_now);
6698 /* Check if we have a constant in IMM_EXPR. If the FPRs are 64 bits
6699 wide, IMM_EXPR is the entire value and the GPRs are known to be 64
6700 bits wide as well. Otherwise IMM_EXPR is the high order 32 bits of
6701 the value and the low order 32 bits are either zero or in
6703 if (imm_expr.X_op == O_constant || imm_expr.X_op == O_big)
6705 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_FPRS);
6706 if (HAVE_64BIT_FPRS)
6708 assert (HAVE_64BIT_GPRS);
6709 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6710 "dmtc1", "t,S", AT, treg);
6714 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6715 "mtc1", "t,G", AT, treg + 1);
6716 if (offset_expr.X_op == O_absent)
6717 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6718 "mtc1", "t,G", 0, treg);
6721 assert (offset_expr.X_op == O_constant);
6722 load_register (&icnt, AT, &offset_expr, 0);
6723 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6724 "mtc1", "t,G", AT, treg);
6730 assert (offset_expr.X_op == O_symbol
6731 && offset_expr.X_add_number == 0);
6732 s = segment_name (S_GET_SEGMENT (offset_expr.X_add_symbol));
6733 if (strcmp (s, ".lit8") == 0)
6735 if (mips_opts.isa != ISA_MIPS1)
6737 macro_build ((char *) NULL, &icnt, &offset_expr, "ldc1",
6738 "T,o(b)", treg, (int) BFD_RELOC_MIPS_LITERAL,
6742 breg = mips_gp_register;
6743 r = BFD_RELOC_MIPS_LITERAL;
6748 assert (strcmp (s, RDATA_SECTION_NAME) == 0);
6749 if (mips_pic == SVR4_PIC)
6750 macro_build ((char *) NULL, &icnt, &offset_expr,
6751 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
6752 "t,o(b)", AT, (int) BFD_RELOC_MIPS_GOT16,
6756 /* FIXME: This won't work for a 64 bit address. */
6757 macro_build_lui (NULL, &icnt, &offset_expr, AT);
6760 if (mips_opts.isa != ISA_MIPS1)
6762 macro_build ((char *) NULL, &icnt, &offset_expr, "ldc1",
6763 "T,o(b)", treg, (int) BFD_RELOC_LO16, AT);
6765 /* To avoid confusion in tc_gen_reloc, we must ensure
6766 that this does not become a variant frag. */
6767 frag_wane (frag_now);
6778 if (mips_arch == CPU_R4650)
6780 as_bad (_("opcode not supported on this processor"));
6783 /* Even on a big endian machine $fn comes before $fn+1. We have
6784 to adjust when loading from memory. */
6787 assert (mips_opts.isa == ISA_MIPS1);
6788 macro_build ((char *) NULL, &icnt, &offset_expr, "lwc1", "T,o(b)",
6789 target_big_endian ? treg + 1 : treg,
6791 /* FIXME: A possible overflow which I don't know how to deal
6793 offset_expr.X_add_number += 4;
6794 macro_build ((char *) NULL, &icnt, &offset_expr, "lwc1", "T,o(b)",
6795 target_big_endian ? treg : treg + 1,
6798 /* To avoid confusion in tc_gen_reloc, we must ensure that this
6799 does not become a variant frag. */
6800 frag_wane (frag_now);
6809 * The MIPS assembler seems to check for X_add_number not
6810 * being double aligned and generating:
6813 * addiu at,at,%lo(foo+1)
6816 * But, the resulting address is the same after relocation so why
6817 * generate the extra instruction?
6819 if (mips_arch == CPU_R4650)
6821 as_bad (_("opcode not supported on this processor"));
6824 /* Itbl support may require additional care here. */
6826 if (mips_opts.isa != ISA_MIPS1)
6837 if (mips_arch == CPU_R4650)
6839 as_bad (_("opcode not supported on this processor"));
6843 if (mips_opts.isa != ISA_MIPS1)
6851 /* Itbl support may require additional care here. */
6856 if (HAVE_64BIT_GPRS)
6867 if (HAVE_64BIT_GPRS)
6877 /* We do _not_ bother to allow embedded PIC (symbol-local_symbol)
6878 loads for the case of doing a pair of loads to simulate an 'ld'.
6879 This is not currently done by the compiler, and assembly coders
6880 writing embedded-pic code can cope. */
6882 if (offset_expr.X_op != O_symbol
6883 && offset_expr.X_op != O_constant)
6885 as_bad (_("expression too complex"));
6886 offset_expr.X_op = O_constant;
6889 /* Even on a big endian machine $fn comes before $fn+1. We have
6890 to adjust when loading from memory. We set coproc if we must
6891 load $fn+1 first. */
6892 /* Itbl support may require additional care here. */
6893 if (! target_big_endian)
6896 if (mips_pic == NO_PIC
6897 || offset_expr.X_op == O_constant)
6901 /* If this is a reference to a GP relative symbol, we want
6902 <op> $treg,<sym>($gp) (BFD_RELOC_GPREL16)
6903 <op> $treg+1,<sym>+4($gp) (BFD_RELOC_GPREL16)
6904 If we have a base register, we use this
6906 <op> $treg,<sym>($at) (BFD_RELOC_GPREL16)
6907 <op> $treg+1,<sym>+4($at) (BFD_RELOC_GPREL16)
6908 If this is not a GP relative symbol, we want
6909 lui $at,<sym> (BFD_RELOC_HI16_S)
6910 <op> $treg,<sym>($at) (BFD_RELOC_LO16)
6911 <op> $treg+1,<sym>+4($at) (BFD_RELOC_LO16)
6912 If there is a base register, we add it to $at after the
6913 lui instruction. If there is a constant, we always use
6915 if ((valueT) offset_expr.X_add_number > MAX_GPREL_OFFSET
6916 || nopic_need_relax (offset_expr.X_add_symbol, 1))
6928 tempreg = mips_gp_register;
6935 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6936 HAVE_32BIT_ADDRESSES ? HAVE_NEWABI
6937 ? "add" : "addu" : "daddu",
6938 "d,v,t", AT, breg, mips_gp_register);
6944 /* Itbl support may require additional care here. */
6945 macro_build ((char *) NULL, &icnt, &offset_expr, s, fmt,
6946 coproc ? treg + 1 : treg,
6947 (int) BFD_RELOC_GPREL16, tempreg);
6948 offset_expr.X_add_number += 4;
6950 /* Set mips_optimize to 2 to avoid inserting an
6952 hold_mips_optimize = mips_optimize;
6954 /* Itbl support may require additional care here. */
6955 macro_build ((char *) NULL, &icnt, &offset_expr, s, fmt,
6956 coproc ? treg : treg + 1,
6957 (int) BFD_RELOC_GPREL16, tempreg);
6958 mips_optimize = hold_mips_optimize;
6960 p = frag_var (rs_machine_dependent, 12 + off, 0,
6961 RELAX_ENCODE (8 + off, 12 + off, 0, 4 + off, 1,
6962 used_at && mips_opts.noat),
6963 offset_expr.X_add_symbol, 0, NULL);
6965 /* We just generated two relocs. When tc_gen_reloc
6966 handles this case, it will skip the first reloc and
6967 handle the second. The second reloc already has an
6968 extra addend of 4, which we added above. We must
6969 subtract it out, and then subtract another 4 to make
6970 the first reloc come out right. The second reloc
6971 will come out right because we are going to add 4 to
6972 offset_expr when we build its instruction below.
6974 If we have a symbol, then we don't want to include
6975 the offset, because it will wind up being included
6976 when we generate the reloc. */
6978 if (offset_expr.X_op == O_constant)
6979 offset_expr.X_add_number -= 8;
6982 offset_expr.X_add_number = -4;
6983 offset_expr.X_op = O_constant;
6986 macro_build_lui (p, &icnt, &offset_expr, AT);
6991 macro_build (p, &icnt, (expressionS *) NULL,
6992 HAVE_32BIT_ADDRESSES ? HAVE_NEWABI
6993 ? "add" : "addu" : "daddu",
6994 "d,v,t", AT, breg, AT);
6998 /* Itbl support may require additional care here. */
6999 macro_build (p, &icnt, &offset_expr, s, fmt,
7000 coproc ? treg + 1 : treg,
7001 (int) BFD_RELOC_LO16, AT);
7004 /* FIXME: How do we handle overflow here? */
7005 offset_expr.X_add_number += 4;
7006 /* Itbl support may require additional care here. */
7007 macro_build (p, &icnt, &offset_expr, s, fmt,
7008 coproc ? treg : treg + 1,
7009 (int) BFD_RELOC_LO16, AT);
7011 else if (mips_pic == SVR4_PIC && ! mips_big_got)
7015 /* If this is a reference to an external symbol, we want
7016 lw $at,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
7021 lw $at,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
7023 <op> $treg,<sym>($at) (BFD_RELOC_LO16)
7024 <op> $treg+1,<sym>+4($at) (BFD_RELOC_LO16)
7025 If there is a base register we add it to $at before the
7026 lwc1 instructions. If there is a constant we include it
7027 in the lwc1 instructions. */
7029 expr1.X_add_number = offset_expr.X_add_number;
7030 offset_expr.X_add_number = 0;
7031 if (expr1.X_add_number < -0x8000
7032 || expr1.X_add_number >= 0x8000 - 4)
7033 as_bad (_("PIC code offset overflow (max 16 signed bits)"));
7038 frag_grow (24 + off);
7039 macro_build ((char *) NULL, &icnt, &offset_expr,
7040 HAVE_32BIT_ADDRESSES ? "lw" : "ld", "t,o(b)", AT,
7041 (int) BFD_RELOC_MIPS_GOT16, mips_gp_register);
7042 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "");
7044 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7045 HAVE_32BIT_ADDRESSES ? HAVE_NEWABI
7046 ? "add" : "addu" : "daddu",
7047 "d,v,t", AT, breg, AT);
7048 /* Itbl support may require additional care here. */
7049 macro_build ((char *) NULL, &icnt, &expr1, s, fmt,
7050 coproc ? treg + 1 : treg,
7051 (int) BFD_RELOC_LO16, AT);
7052 expr1.X_add_number += 4;
7054 /* Set mips_optimize to 2 to avoid inserting an undesired
7056 hold_mips_optimize = mips_optimize;
7058 /* Itbl support may require additional care here. */
7059 macro_build ((char *) NULL, &icnt, &expr1, s, fmt,
7060 coproc ? treg : treg + 1,
7061 (int) BFD_RELOC_LO16, AT);
7062 mips_optimize = hold_mips_optimize;
7064 (void) frag_var (rs_machine_dependent, 0, 0,
7065 RELAX_ENCODE (0, 0, -16 - off, -8, 1, 0),
7066 offset_expr.X_add_symbol, 0, NULL);
7068 else if (mips_pic == SVR4_PIC)
7073 /* If this is a reference to an external symbol, we want
7074 lui $at,<sym> (BFD_RELOC_MIPS_GOT_HI16)
7076 lw $at,<sym>($at) (BFD_RELOC_MIPS_GOT_LO16)
7081 lw $at,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
7083 <op> $treg,<sym>($at) (BFD_RELOC_LO16)
7084 <op> $treg+1,<sym>+4($at) (BFD_RELOC_LO16)
7085 If there is a base register we add it to $at before the
7086 lwc1 instructions. If there is a constant we include it
7087 in the lwc1 instructions. */
7089 expr1.X_add_number = offset_expr.X_add_number;
7090 offset_expr.X_add_number = 0;
7091 if (expr1.X_add_number < -0x8000
7092 || expr1.X_add_number >= 0x8000 - 4)
7093 as_bad (_("PIC code offset overflow (max 16 signed bits)"));
7094 if (reg_needs_delay (mips_gp_register))
7103 macro_build ((char *) NULL, &icnt, &offset_expr, "lui", "t,u",
7104 AT, (int) BFD_RELOC_MIPS_GOT_HI16);
7105 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7106 HAVE_32BIT_ADDRESSES ? HAVE_NEWABI
7107 ? "add" : "addu" : "daddu",
7108 "d,v,t", AT, AT, mips_gp_register);
7109 macro_build ((char *) NULL, &icnt, &offset_expr,
7110 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
7111 "t,o(b)", AT, (int) BFD_RELOC_MIPS_GOT_LO16, AT);
7112 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "");
7114 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7115 HAVE_32BIT_ADDRESSES ? HAVE_NEWABI
7116 ? "add" : "addu" : "daddu",
7117 "d,v,t", AT, breg, AT);
7118 /* Itbl support may require additional care here. */
7119 macro_build ((char *) NULL, &icnt, &expr1, s, fmt,
7120 coproc ? treg + 1 : treg,
7121 (int) BFD_RELOC_LO16, AT);
7122 expr1.X_add_number += 4;
7124 /* Set mips_optimize to 2 to avoid inserting an undesired
7126 hold_mips_optimize = mips_optimize;
7128 /* Itbl support may require additional care here. */
7129 macro_build ((char *) NULL, &icnt, &expr1, s, fmt,
7130 coproc ? treg : treg + 1,
7131 (int) BFD_RELOC_LO16, AT);
7132 mips_optimize = hold_mips_optimize;
7133 expr1.X_add_number -= 4;
7135 p = frag_var (rs_machine_dependent, 16 + gpdel + off, 0,
7136 RELAX_ENCODE (24 + off, 16 + gpdel + off, gpdel,
7137 8 + gpdel + off, 1, 0),
7138 offset_expr.X_add_symbol, 0, NULL);
7141 macro_build (p, &icnt, (expressionS *) NULL, "nop", "");
7144 macro_build (p, &icnt, &offset_expr,
7145 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
7146 "t,o(b)", AT, (int) BFD_RELOC_MIPS_GOT16,
7149 macro_build (p, &icnt, (expressionS *) NULL, "nop", "");
7153 macro_build (p, &icnt, (expressionS *) NULL,
7154 HAVE_32BIT_ADDRESSES ? HAVE_NEWABI
7155 ? "add" : "addu" : "daddu",
7156 "d,v,t", AT, breg, AT);
7159 /* Itbl support may require additional care here. */
7160 macro_build (p, &icnt, &expr1, s, fmt,
7161 coproc ? treg + 1 : treg,
7162 (int) BFD_RELOC_LO16, AT);
7164 expr1.X_add_number += 4;
7166 /* Set mips_optimize to 2 to avoid inserting an undesired
7168 hold_mips_optimize = mips_optimize;
7170 /* Itbl support may require additional care here. */
7171 macro_build (p, &icnt, &expr1, s, fmt,
7172 coproc ? treg : treg + 1,
7173 (int) BFD_RELOC_LO16, AT);
7174 mips_optimize = hold_mips_optimize;
7176 else if (mips_pic == EMBEDDED_PIC)
7178 /* If there is no base register, we use
7179 <op> $treg,<sym>($gp) (BFD_RELOC_GPREL16)
7180 <op> $treg+1,<sym>+4($gp) (BFD_RELOC_GPREL16)
7181 If we have a base register, we use
7183 <op> $treg,<sym>($at) (BFD_RELOC_GPREL16)
7184 <op> $treg+1,<sym>+4($at) (BFD_RELOC_GPREL16)
7188 tempreg = mips_gp_register;
7193 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7194 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
7195 "d,v,t", AT, breg, mips_gp_register);
7200 /* Itbl support may require additional care here. */
7201 macro_build ((char *) NULL, &icnt, &offset_expr, s, fmt,
7202 coproc ? treg + 1 : treg,
7203 (int) BFD_RELOC_GPREL16, tempreg);
7204 offset_expr.X_add_number += 4;
7205 /* Itbl support may require additional care here. */
7206 macro_build ((char *) NULL, &icnt, &offset_expr, s, fmt,
7207 coproc ? treg : treg + 1,
7208 (int) BFD_RELOC_GPREL16, tempreg);
7224 assert (HAVE_32BIT_ADDRESSES);
7225 macro_build ((char *) NULL, &icnt, &offset_expr, s, "t,o(b)", treg,
7226 (int) BFD_RELOC_LO16, breg);
7227 offset_expr.X_add_number += 4;
7228 macro_build ((char *) NULL, &icnt, &offset_expr, s, "t,o(b)", treg + 1,
7229 (int) BFD_RELOC_LO16, breg);
7232 /* New code added to support COPZ instructions.
7233 This code builds table entries out of the macros in mip_opcodes.
7234 R4000 uses interlocks to handle coproc delays.
7235 Other chips (like the R3000) require nops to be inserted for delays.
7237 FIXME: Currently, we require that the user handle delays.
7238 In order to fill delay slots for non-interlocked chips,
7239 we must have a way to specify delays based on the coprocessor.
7240 Eg. 4 cycles if load coproc reg from memory, 1 if in cache, etc.
7241 What are the side-effects of the cop instruction?
7242 What cache support might we have and what are its effects?
7243 Both coprocessor & memory require delays. how long???
7244 What registers are read/set/modified?
7246 If an itbl is provided to interpret cop instructions,
7247 this knowledge can be encoded in the itbl spec. */
7261 /* For now we just do C (same as Cz). The parameter will be
7262 stored in insn_opcode by mips_ip. */
7263 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "C",
7268 move_register (&icnt, dreg, sreg);
7271 #ifdef LOSING_COMPILER
7273 /* Try and see if this is a new itbl instruction.
7274 This code builds table entries out of the macros in mip_opcodes.
7275 FIXME: For now we just assemble the expression and pass it's
7276 value along as a 32-bit immediate.
7277 We may want to have the assembler assemble this value,
7278 so that we gain the assembler's knowledge of delay slots,
7280 Would it be more efficient to use mask (id) here? */
7281 if (itbl_have_entries
7282 && (immed_expr = itbl_assemble (ip->insn_mo->name, "")))
7284 s = ip->insn_mo->name;
7286 coproc = ITBL_DECODE_PNUM (immed_expr);;
7287 macro_build ((char *) NULL, &icnt, &immed_expr, s, "C");
7294 as_warn (_("Macro used $at after \".set noat\""));
7299 struct mips_cl_insn *ip;
7301 register int treg, sreg, dreg, breg;
7317 bfd_reloc_code_real_type r;
7320 treg = (ip->insn_opcode >> 16) & 0x1f;
7321 dreg = (ip->insn_opcode >> 11) & 0x1f;
7322 sreg = breg = (ip->insn_opcode >> 21) & 0x1f;
7323 mask = ip->insn_mo->mask;
7325 expr1.X_op = O_constant;
7326 expr1.X_op_symbol = NULL;
7327 expr1.X_add_symbol = NULL;
7328 expr1.X_add_number = 1;
7332 #endif /* LOSING_COMPILER */
7337 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7338 dbl ? "dmultu" : "multu", "s,t", sreg, treg);
7339 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "mflo", "d",
7346 /* The MIPS assembler some times generates shifts and adds. I'm
7347 not trying to be that fancy. GCC should do this for us
7349 load_register (&icnt, AT, &imm_expr, dbl);
7350 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7351 dbl ? "dmult" : "mult", "s,t", sreg, AT);
7352 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "mflo", "d",
7366 mips_emit_delays (TRUE);
7367 ++mips_opts.noreorder;
7368 mips_any_noreorder = 1;
7370 load_register (&icnt, AT, &imm_expr, dbl);
7371 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7372 dbl ? "dmult" : "mult", "s,t", sreg, imm ? AT : treg);
7373 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "mflo", "d",
7375 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7376 dbl ? "dsra32" : "sra", "d,w,<", dreg, dreg, RA);
7377 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "mfhi", "d",
7380 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "tne",
7381 "s,t,q", dreg, AT, 6);
7384 expr1.X_add_number = 8;
7385 macro_build ((char *) NULL, &icnt, &expr1, "beq", "s,t,p", dreg,
7387 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "",
7389 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "break",
7392 --mips_opts.noreorder;
7393 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "mflo", "d", dreg);
7406 mips_emit_delays (TRUE);
7407 ++mips_opts.noreorder;
7408 mips_any_noreorder = 1;
7410 load_register (&icnt, AT, &imm_expr, dbl);
7411 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7412 dbl ? "dmultu" : "multu",
7413 "s,t", sreg, imm ? AT : treg);
7414 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "mfhi", "d",
7416 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "mflo", "d",
7419 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "tne",
7423 expr1.X_add_number = 8;
7424 macro_build ((char *) NULL, &icnt, &expr1, "beq", "s,t,p", AT, 0);
7425 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "",
7427 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "break",
7430 --mips_opts.noreorder;
7434 if (ISA_HAS_DROR (mips_opts.isa) || CPU_HAS_DROR (mips_arch))
7446 macro_build ((char *) NULL, &icnt, NULL, "dnegu",
7447 "d,w", tempreg, treg);
7448 macro_build ((char *) NULL, &icnt, NULL, "drorv",
7449 "d,t,s", dreg, sreg, tempreg);
7454 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "dsubu",
7455 "d,v,t", AT, 0, treg);
7456 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "dsrlv",
7457 "d,t,s", AT, sreg, AT);
7458 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "dsllv",
7459 "d,t,s", dreg, sreg, treg);
7460 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or",
7461 "d,v,t", dreg, dreg, AT);
7465 if (ISA_HAS_ROR (mips_opts.isa) || CPU_HAS_ROR (mips_arch))
7477 macro_build ((char *) NULL, &icnt, NULL, "negu",
7478 "d,w", tempreg, treg);
7479 macro_build ((char *) NULL, &icnt, NULL, "rorv",
7480 "d,t,s", dreg, sreg, tempreg);
7485 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "subu",
7486 "d,v,t", AT, 0, treg);
7487 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "srlv",
7488 "d,t,s", AT, sreg, AT);
7489 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sllv",
7490 "d,t,s", dreg, sreg, treg);
7491 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or",
7492 "d,v,t", dreg, dreg, AT);
7500 if (imm_expr.X_op != O_constant)
7501 as_bad (_("Improper rotate count"));
7502 rot = imm_expr.X_add_number & 0x3f;
7503 if (ISA_HAS_DROR (mips_opts.isa) || CPU_HAS_DROR (mips_arch))
7505 rot = (64 - rot) & 0x3f;
7507 macro_build ((char *) NULL, &icnt, NULL, "dror32",
7508 "d,w,<", dreg, sreg, rot - 32);
7510 macro_build ((char *) NULL, &icnt, NULL, "dror",
7511 "d,w,<", dreg, sreg, rot);
7516 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "dsrl",
7517 "d,w,<", dreg, sreg, 0);
7520 l = (rot < 0x20) ? "dsll" : "dsll32";
7521 r = ((0x40 - rot) < 0x20) ? "dsrl" : "dsrl32";
7523 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, l,
7524 "d,w,<", AT, sreg, rot);
7525 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, r,
7526 "d,w,<", dreg, sreg, (0x20 - rot) & 0x1f);
7527 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or",
7528 "d,v,t", dreg, dreg, AT);
7536 if (imm_expr.X_op != O_constant)
7537 as_bad (_("Improper rotate count"));
7538 rot = imm_expr.X_add_number & 0x1f;
7539 if (ISA_HAS_ROR (mips_opts.isa) || CPU_HAS_ROR (mips_arch))
7541 macro_build ((char *) NULL, &icnt, NULL, "ror",
7542 "d,w,<", dreg, sreg, (32 - rot) & 0x1f);
7547 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "srl",
7548 "d,w,<", dreg, sreg, 0);
7551 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sll",
7552 "d,w,<", AT, sreg, rot);
7553 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "srl",
7554 "d,w,<", dreg, sreg, (0x20 - rot) & 0x1f);
7555 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or",
7556 "d,v,t", dreg, dreg, AT);
7561 if (ISA_HAS_DROR (mips_opts.isa) || CPU_HAS_DROR (mips_arch))
7563 macro_build ((char *) NULL, &icnt, NULL, "drorv",
7564 "d,t,s", dreg, sreg, treg);
7567 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "dsubu",
7568 "d,v,t", AT, 0, treg);
7569 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "dsllv",
7570 "d,t,s", AT, sreg, AT);
7571 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "dsrlv",
7572 "d,t,s", dreg, sreg, treg);
7573 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or",
7574 "d,v,t", dreg, dreg, AT);
7578 if (ISA_HAS_ROR (mips_opts.isa) || CPU_HAS_ROR (mips_arch))
7580 macro_build ((char *) NULL, &icnt, NULL, "rorv",
7581 "d,t,s", dreg, sreg, treg);
7584 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "subu",
7585 "d,v,t", AT, 0, treg);
7586 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sllv",
7587 "d,t,s", AT, sreg, AT);
7588 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "srlv",
7589 "d,t,s", dreg, sreg, treg);
7590 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or",
7591 "d,v,t", dreg, dreg, AT);
7599 if (imm_expr.X_op != O_constant)
7600 as_bad (_("Improper rotate count"));
7601 rot = imm_expr.X_add_number & 0x3f;
7602 if (ISA_HAS_DROR (mips_opts.isa) || CPU_HAS_DROR (mips_arch))
7605 macro_build ((char *) NULL, &icnt, NULL, "dror32",
7606 "d,w,<", dreg, sreg, rot - 32);
7608 macro_build ((char *) NULL, &icnt, NULL, "dror",
7609 "d,w,<", dreg, sreg, rot);
7614 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "dsrl",
7615 "d,w,<", dreg, sreg, 0);
7618 r = (rot < 0x20) ? "dsrl" : "dsrl32";
7619 l = ((0x40 - rot) < 0x20) ? "dsll" : "dsll32";
7621 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, r,
7622 "d,w,<", AT, sreg, rot);
7623 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, l,
7624 "d,w,<", dreg, sreg, (0x20 - rot) & 0x1f);
7625 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or",
7626 "d,v,t", dreg, dreg, AT);
7634 if (imm_expr.X_op != O_constant)
7635 as_bad (_("Improper rotate count"));
7636 rot = imm_expr.X_add_number & 0x1f;
7637 if (ISA_HAS_ROR (mips_opts.isa) || CPU_HAS_ROR (mips_arch))
7639 macro_build ((char *) NULL, &icnt, NULL, "ror",
7640 "d,w,<", dreg, sreg, rot);
7645 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "srl",
7646 "d,w,<", dreg, sreg, 0);
7649 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "srl",
7650 "d,w,<", AT, sreg, rot);
7651 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sll",
7652 "d,w,<", dreg, sreg, (0x20 - rot) & 0x1f);
7653 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or",
7654 "d,v,t", dreg, dreg, AT);
7659 if (mips_arch == CPU_R4650)
7661 as_bad (_("opcode not supported on this processor"));
7664 assert (mips_opts.isa == ISA_MIPS1);
7665 /* Even on a big endian machine $fn comes before $fn+1. We have
7666 to adjust when storing to memory. */
7667 macro_build ((char *) NULL, &icnt, &offset_expr, "swc1", "T,o(b)",
7668 target_big_endian ? treg + 1 : treg,
7669 (int) BFD_RELOC_LO16, breg);
7670 offset_expr.X_add_number += 4;
7671 macro_build ((char *) NULL, &icnt, &offset_expr, "swc1", "T,o(b)",
7672 target_big_endian ? treg : treg + 1,
7673 (int) BFD_RELOC_LO16, breg);
7678 macro_build ((char *) NULL, &icnt, &expr1, "sltiu", "t,r,j", dreg,
7679 treg, (int) BFD_RELOC_LO16);
7681 macro_build ((char *) NULL, &icnt, &expr1, "sltiu", "t,r,j", dreg,
7682 sreg, (int) BFD_RELOC_LO16);
7685 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "xor",
7686 "d,v,t", dreg, sreg, treg);
7687 macro_build ((char *) NULL, &icnt, &expr1, "sltiu", "t,r,j", dreg,
7688 dreg, (int) BFD_RELOC_LO16);
7693 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
7695 macro_build ((char *) NULL, &icnt, &expr1, "sltiu", "t,r,j", dreg,
7696 sreg, (int) BFD_RELOC_LO16);
7701 as_warn (_("Instruction %s: result is always false"),
7703 move_register (&icnt, dreg, 0);
7706 if (imm_expr.X_op == O_constant
7707 && imm_expr.X_add_number >= 0
7708 && imm_expr.X_add_number < 0x10000)
7710 macro_build ((char *) NULL, &icnt, &imm_expr, "xori", "t,r,i", dreg,
7711 sreg, (int) BFD_RELOC_LO16);
7714 else if (imm_expr.X_op == O_constant
7715 && imm_expr.X_add_number > -0x8000
7716 && imm_expr.X_add_number < 0)
7718 imm_expr.X_add_number = -imm_expr.X_add_number;
7719 macro_build ((char *) NULL, &icnt, &imm_expr,
7720 HAVE_32BIT_GPRS ? "addiu" : "daddiu",
7721 "t,r,j", dreg, sreg,
7722 (int) BFD_RELOC_LO16);
7727 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_GPRS);
7728 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "xor",
7729 "d,v,t", dreg, sreg, AT);
7732 macro_build ((char *) NULL, &icnt, &expr1, "sltiu", "t,r,j", dreg, dreg,
7733 (int) BFD_RELOC_LO16);
7738 case M_SGE: /* sreg >= treg <==> not (sreg < treg) */
7744 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "d,v,t",
7746 macro_build ((char *) NULL, &icnt, &expr1, "xori", "t,r,i", dreg, dreg,
7747 (int) BFD_RELOC_LO16);
7750 case M_SGE_I: /* sreg >= I <==> not (sreg < I) */
7752 if (imm_expr.X_op == O_constant
7753 && imm_expr.X_add_number >= -0x8000
7754 && imm_expr.X_add_number < 0x8000)
7756 macro_build ((char *) NULL, &icnt, &imm_expr,
7757 mask == M_SGE_I ? "slti" : "sltiu",
7758 "t,r,j", dreg, sreg, (int) BFD_RELOC_LO16);
7763 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_GPRS);
7764 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7765 mask == M_SGE_I ? "slt" : "sltu", "d,v,t", dreg, sreg,
7769 macro_build ((char *) NULL, &icnt, &expr1, "xori", "t,r,i", dreg, dreg,
7770 (int) BFD_RELOC_LO16);
7775 case M_SGT: /* sreg > treg <==> treg < sreg */
7781 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "d,v,t",
7785 case M_SGT_I: /* sreg > I <==> I < sreg */
7791 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_GPRS);
7792 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "d,v,t",
7796 case M_SLE: /* sreg <= treg <==> treg >= sreg <==> not (treg < sreg) */
7802 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "d,v,t",
7804 macro_build ((char *) NULL, &icnt, &expr1, "xori", "t,r,i", dreg, dreg,
7805 (int) BFD_RELOC_LO16);
7808 case M_SLE_I: /* sreg <= I <==> I >= sreg <==> not (I < sreg) */
7814 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_GPRS);
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);
7822 if (imm_expr.X_op == O_constant
7823 && imm_expr.X_add_number >= -0x8000
7824 && imm_expr.X_add_number < 0x8000)
7826 macro_build ((char *) NULL, &icnt, &imm_expr, "slti", "t,r,j",
7827 dreg, sreg, (int) BFD_RELOC_LO16);
7830 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_GPRS);
7831 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "slt", "d,v,t",
7836 if (imm_expr.X_op == O_constant
7837 && imm_expr.X_add_number >= -0x8000
7838 && imm_expr.X_add_number < 0x8000)
7840 macro_build ((char *) NULL, &icnt, &imm_expr, "sltiu", "t,r,j",
7841 dreg, sreg, (int) BFD_RELOC_LO16);
7844 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_GPRS);
7845 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sltu",
7846 "d,v,t", dreg, sreg, AT);
7851 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sltu",
7852 "d,v,t", dreg, 0, treg);
7854 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sltu",
7855 "d,v,t", dreg, 0, sreg);
7858 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "xor",
7859 "d,v,t", dreg, sreg, treg);
7860 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sltu",
7861 "d,v,t", dreg, 0, dreg);
7866 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
7868 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sltu",
7869 "d,v,t", dreg, 0, sreg);
7874 as_warn (_("Instruction %s: result is always true"),
7876 macro_build ((char *) NULL, &icnt, &expr1,
7877 HAVE_32BIT_GPRS ? "addiu" : "daddiu",
7878 "t,r,j", dreg, 0, (int) BFD_RELOC_LO16);
7881 if (imm_expr.X_op == O_constant
7882 && imm_expr.X_add_number >= 0
7883 && imm_expr.X_add_number < 0x10000)
7885 macro_build ((char *) NULL, &icnt, &imm_expr, "xori", "t,r,i",
7886 dreg, sreg, (int) BFD_RELOC_LO16);
7889 else if (imm_expr.X_op == O_constant
7890 && imm_expr.X_add_number > -0x8000
7891 && imm_expr.X_add_number < 0)
7893 imm_expr.X_add_number = -imm_expr.X_add_number;
7894 macro_build ((char *) NULL, &icnt, &imm_expr,
7895 HAVE_32BIT_GPRS ? "addiu" : "daddiu",
7896 "t,r,j", dreg, sreg, (int) BFD_RELOC_LO16);
7901 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_GPRS);
7902 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "xor",
7903 "d,v,t", dreg, sreg, AT);
7906 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sltu",
7907 "d,v,t", dreg, 0, dreg);
7915 if (imm_expr.X_op == O_constant
7916 && imm_expr.X_add_number > -0x8000
7917 && imm_expr.X_add_number <= 0x8000)
7919 imm_expr.X_add_number = -imm_expr.X_add_number;
7920 macro_build ((char *) NULL, &icnt, &imm_expr,
7921 dbl ? "daddi" : "addi",
7922 "t,r,j", dreg, sreg, (int) BFD_RELOC_LO16);
7925 load_register (&icnt, AT, &imm_expr, dbl);
7926 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7927 dbl ? "dsub" : "sub", "d,v,t", dreg, sreg, AT);
7933 if (imm_expr.X_op == O_constant
7934 && imm_expr.X_add_number > -0x8000
7935 && imm_expr.X_add_number <= 0x8000)
7937 imm_expr.X_add_number = -imm_expr.X_add_number;
7938 macro_build ((char *) NULL, &icnt, &imm_expr,
7939 dbl ? "daddiu" : "addiu",
7940 "t,r,j", dreg, sreg, (int) BFD_RELOC_LO16);
7943 load_register (&icnt, AT, &imm_expr, dbl);
7944 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7945 dbl ? "dsubu" : "subu", "d,v,t", dreg, sreg, AT);
7966 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_GPRS);
7967 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "s,t", sreg,
7973 assert (mips_opts.isa == ISA_MIPS1);
7974 sreg = (ip->insn_opcode >> 11) & 0x1f; /* floating reg */
7975 dreg = (ip->insn_opcode >> 06) & 0x1f; /* floating reg */
7978 * Is the double cfc1 instruction a bug in the mips assembler;
7979 * or is there a reason for it?
7981 mips_emit_delays (TRUE);
7982 ++mips_opts.noreorder;
7983 mips_any_noreorder = 1;
7984 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "cfc1", "t,G",
7986 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "cfc1", "t,G",
7988 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "");
7989 expr1.X_add_number = 3;
7990 macro_build ((char *) NULL, &icnt, &expr1, "ori", "t,r,i", AT, treg,
7991 (int) BFD_RELOC_LO16);
7992 expr1.X_add_number = 2;
7993 macro_build ((char *) NULL, &icnt, &expr1, "xori", "t,r,i", AT, AT,
7994 (int) BFD_RELOC_LO16);
7995 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "ctc1", "t,G",
7997 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "");
7998 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7999 mask == M_TRUNCWD ? "cvt.w.d" : "cvt.w.s", "D,S", dreg, sreg);
8000 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "ctc1", "t,G",
8002 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "");
8003 --mips_opts.noreorder;
8012 if (offset_expr.X_add_number >= 0x7fff)
8013 as_bad (_("operand overflow"));
8014 if (! target_big_endian)
8015 ++offset_expr.X_add_number;
8016 macro_build ((char *) NULL, &icnt, &offset_expr, s, "t,o(b)", AT,
8017 (int) BFD_RELOC_LO16, breg);
8018 if (! target_big_endian)
8019 --offset_expr.X_add_number;
8021 ++offset_expr.X_add_number;
8022 macro_build ((char *) NULL, &icnt, &offset_expr, "lbu", "t,o(b)", treg,
8023 (int) BFD_RELOC_LO16, breg);
8024 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sll", "d,w,<",
8026 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or", "d,v,t",
8040 if (offset_expr.X_add_number >= 0x8000 - off)
8041 as_bad (_("operand overflow"));
8046 if (! target_big_endian)
8047 offset_expr.X_add_number += off;
8048 macro_build ((char *) NULL, &icnt, &offset_expr, s, "t,o(b)", tempreg,
8049 (int) BFD_RELOC_LO16, breg);
8050 if (! target_big_endian)
8051 offset_expr.X_add_number -= off;
8053 offset_expr.X_add_number += off;
8054 macro_build ((char *) NULL, &icnt, &offset_expr, s2, "t,o(b)", tempreg,
8055 (int) BFD_RELOC_LO16, breg);
8057 /* If necessary, move the result in tempreg the final destination. */
8058 if (treg == tempreg)
8060 /* Protect second load's delay slot. */
8061 if (!gpr_interlocks)
8062 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "");
8063 move_register (&icnt, treg, tempreg);
8077 load_address (&icnt, AT, &offset_expr, &used_at);
8079 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
8080 HAVE_32BIT_ADDRESSES ? HAVE_NEWABI
8081 ? "add" : "addu" : "daddu",
8082 "d,v,t", AT, AT, breg);
8083 if (! target_big_endian)
8084 expr1.X_add_number = off;
8086 expr1.X_add_number = 0;
8087 macro_build ((char *) NULL, &icnt, &expr1, s, "t,o(b)", treg,
8088 (int) BFD_RELOC_LO16, AT);
8089 if (! target_big_endian)
8090 expr1.X_add_number = 0;
8092 expr1.X_add_number = off;
8093 macro_build ((char *) NULL, &icnt, &expr1, s2, "t,o(b)", treg,
8094 (int) BFD_RELOC_LO16, AT);
8100 load_address (&icnt, AT, &offset_expr, &used_at);
8102 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
8103 HAVE_32BIT_ADDRESSES ? HAVE_NEWABI
8104 ? "add" : "addu" : "daddu",
8105 "d,v,t", AT, AT, breg);
8106 if (target_big_endian)
8107 expr1.X_add_number = 0;
8108 macro_build ((char *) NULL, &icnt, &expr1,
8109 mask == M_ULH_A ? "lb" : "lbu", "t,o(b)", treg,
8110 (int) BFD_RELOC_LO16, AT);
8111 if (target_big_endian)
8112 expr1.X_add_number = 1;
8114 expr1.X_add_number = 0;
8115 macro_build ((char *) NULL, &icnt, &expr1, "lbu", "t,o(b)", AT,
8116 (int) BFD_RELOC_LO16, AT);
8117 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sll", "d,w,<",
8119 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or", "d,v,t",
8124 if (offset_expr.X_add_number >= 0x7fff)
8125 as_bad (_("operand overflow"));
8126 if (target_big_endian)
8127 ++offset_expr.X_add_number;
8128 macro_build ((char *) NULL, &icnt, &offset_expr, "sb", "t,o(b)", treg,
8129 (int) BFD_RELOC_LO16, breg);
8130 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "srl", "d,w,<",
8132 if (target_big_endian)
8133 --offset_expr.X_add_number;
8135 ++offset_expr.X_add_number;
8136 macro_build ((char *) NULL, &icnt, &offset_expr, "sb", "t,o(b)", AT,
8137 (int) BFD_RELOC_LO16, breg);
8150 if (offset_expr.X_add_number >= 0x8000 - off)
8151 as_bad (_("operand overflow"));
8152 if (! target_big_endian)
8153 offset_expr.X_add_number += off;
8154 macro_build ((char *) NULL, &icnt, &offset_expr, s, "t,o(b)", treg,
8155 (int) BFD_RELOC_LO16, breg);
8156 if (! target_big_endian)
8157 offset_expr.X_add_number -= off;
8159 offset_expr.X_add_number += off;
8160 macro_build ((char *) NULL, &icnt, &offset_expr, s2, "t,o(b)", treg,
8161 (int) BFD_RELOC_LO16, breg);
8175 load_address (&icnt, AT, &offset_expr, &used_at);
8177 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
8178 HAVE_32BIT_ADDRESSES ? HAVE_NEWABI
8179 ? "add" : "addu" : "daddu",
8180 "d,v,t", AT, AT, breg);
8181 if (! target_big_endian)
8182 expr1.X_add_number = off;
8184 expr1.X_add_number = 0;
8185 macro_build ((char *) NULL, &icnt, &expr1, s, "t,o(b)", treg,
8186 (int) BFD_RELOC_LO16, AT);
8187 if (! target_big_endian)
8188 expr1.X_add_number = 0;
8190 expr1.X_add_number = off;
8191 macro_build ((char *) NULL, &icnt, &expr1, s2, "t,o(b)", treg,
8192 (int) BFD_RELOC_LO16, AT);
8197 load_address (&icnt, AT, &offset_expr, &used_at);
8199 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
8200 HAVE_32BIT_ADDRESSES ? HAVE_NEWABI
8201 ? "add" : "addu" : "daddu",
8202 "d,v,t", AT, AT, breg);
8203 if (! target_big_endian)
8204 expr1.X_add_number = 0;
8205 macro_build ((char *) NULL, &icnt, &expr1, "sb", "t,o(b)", treg,
8206 (int) BFD_RELOC_LO16, AT);
8207 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "srl", "d,w,<",
8209 if (! target_big_endian)
8210 expr1.X_add_number = 1;
8212 expr1.X_add_number = 0;
8213 macro_build ((char *) NULL, &icnt, &expr1, "sb", "t,o(b)", treg,
8214 (int) BFD_RELOC_LO16, AT);
8215 if (! target_big_endian)
8216 expr1.X_add_number = 0;
8218 expr1.X_add_number = 1;
8219 macro_build ((char *) NULL, &icnt, &expr1, "lbu", "t,o(b)", AT,
8220 (int) BFD_RELOC_LO16, AT);
8221 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sll", "d,w,<",
8223 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or", "d,v,t",
8228 /* FIXME: Check if this is one of the itbl macros, since they
8229 are added dynamically. */
8230 as_bad (_("Macro %s not implemented yet"), ip->insn_mo->name);
8234 as_warn (_("Macro used $at after \".set noat\""));
8237 /* Implement macros in mips16 mode. */
8241 struct mips_cl_insn *ip;
8244 int xreg, yreg, zreg, tmp;
8248 const char *s, *s2, *s3;
8250 mask = ip->insn_mo->mask;
8252 xreg = (ip->insn_opcode >> MIPS16OP_SH_RX) & MIPS16OP_MASK_RX;
8253 yreg = (ip->insn_opcode >> MIPS16OP_SH_RY) & MIPS16OP_MASK_RY;
8254 zreg = (ip->insn_opcode >> MIPS16OP_SH_RZ) & MIPS16OP_MASK_RZ;
8258 expr1.X_op = O_constant;
8259 expr1.X_op_symbol = NULL;
8260 expr1.X_add_symbol = NULL;
8261 expr1.X_add_number = 1;
8280 mips_emit_delays (TRUE);
8281 ++mips_opts.noreorder;
8282 mips_any_noreorder = 1;
8283 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
8284 dbl ? "ddiv" : "div",
8285 "0,x,y", xreg, yreg);
8286 expr1.X_add_number = 2;
8287 macro_build ((char *) NULL, &icnt, &expr1, "bnez", "x,p", yreg);
8288 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "break", "6",
8291 /* FIXME: The normal code checks for of -1 / -0x80000000 here,
8292 since that causes an overflow. We should do that as well,
8293 but I don't see how to do the comparisons without a temporary
8295 --mips_opts.noreorder;
8296 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "x", zreg);
8315 mips_emit_delays (TRUE);
8316 ++mips_opts.noreorder;
8317 mips_any_noreorder = 1;
8318 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "0,x,y",
8320 expr1.X_add_number = 2;
8321 macro_build ((char *) NULL, &icnt, &expr1, "bnez", "x,p", yreg);
8322 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "break",
8324 --mips_opts.noreorder;
8325 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s2, "x", zreg);
8331 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
8332 dbl ? "dmultu" : "multu", "x,y", xreg, yreg);
8333 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "mflo", "x",
8342 if (imm_expr.X_op != O_constant)
8343 as_bad (_("Unsupported large constant"));
8344 imm_expr.X_add_number = -imm_expr.X_add_number;
8345 macro_build ((char *) NULL, &icnt, &imm_expr,
8346 dbl ? "daddiu" : "addiu", "y,x,4", yreg, xreg);
8350 if (imm_expr.X_op != O_constant)
8351 as_bad (_("Unsupported large constant"));
8352 imm_expr.X_add_number = -imm_expr.X_add_number;
8353 macro_build ((char *) NULL, &icnt, &imm_expr, "addiu",
8358 if (imm_expr.X_op != O_constant)
8359 as_bad (_("Unsupported large constant"));
8360 imm_expr.X_add_number = -imm_expr.X_add_number;
8361 macro_build ((char *) NULL, &icnt, &imm_expr, "daddiu",
8384 goto do_reverse_branch;
8388 goto do_reverse_branch;
8400 goto do_reverse_branch;
8411 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "x,y",
8413 macro_build ((char *) NULL, &icnt, &offset_expr, s2, "p");
8440 goto do_addone_branch_i;
8445 goto do_addone_branch_i;
8460 goto do_addone_branch_i;
8467 if (imm_expr.X_op != O_constant)
8468 as_bad (_("Unsupported large constant"));
8469 ++imm_expr.X_add_number;
8472 macro_build ((char *) NULL, &icnt, &imm_expr, s, s3, xreg);
8473 macro_build ((char *) NULL, &icnt, &offset_expr, s2, "p");
8477 expr1.X_add_number = 0;
8478 macro_build ((char *) NULL, &icnt, &expr1, "slti", "x,8", yreg);
8480 move_register (&icnt, xreg, yreg);
8481 expr1.X_add_number = 2;
8482 macro_build ((char *) NULL, &icnt, &expr1, "bteqz", "p");
8483 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
8484 "neg", "x,w", xreg, xreg);
8488 /* For consistency checking, verify that all bits are specified either
8489 by the match/mask part of the instruction definition, or by the
8492 validate_mips_insn (opc)
8493 const struct mips_opcode *opc;
8495 const char *p = opc->args;
8497 unsigned long used_bits = opc->mask;
8499 if ((used_bits & opc->match) != opc->match)
8501 as_bad (_("internal: bad mips opcode (mask error): %s %s"),
8502 opc->name, opc->args);
8505 #define USE_BITS(mask,shift) (used_bits |= ((mask) << (shift)))
8515 case 'A': USE_BITS (OP_MASK_SHAMT, OP_SH_SHAMT); break;
8516 case 'B': USE_BITS (OP_MASK_INSMSB, OP_SH_INSMSB); break;
8517 case 'C': USE_BITS (OP_MASK_EXTMSBD, OP_SH_EXTMSBD); break;
8518 case 'D': USE_BITS (OP_MASK_RD, OP_SH_RD);
8519 USE_BITS (OP_MASK_SEL, OP_SH_SEL); break;
8521 as_bad (_("internal: bad mips opcode (unknown extension operand type `+%c'): %s %s"),
8522 c, opc->name, opc->args);
8526 case '<': USE_BITS (OP_MASK_SHAMT, OP_SH_SHAMT); break;
8527 case '>': USE_BITS (OP_MASK_SHAMT, OP_SH_SHAMT); break;
8529 case 'B': USE_BITS (OP_MASK_CODE20, OP_SH_CODE20); break;
8530 case 'C': USE_BITS (OP_MASK_COPZ, OP_SH_COPZ); break;
8531 case 'D': USE_BITS (OP_MASK_FD, OP_SH_FD); break;
8532 case 'E': USE_BITS (OP_MASK_RT, OP_SH_RT); break;
8534 case 'G': USE_BITS (OP_MASK_RD, OP_SH_RD); break;
8535 case 'H': USE_BITS (OP_MASK_SEL, OP_SH_SEL); break;
8537 case 'J': USE_BITS (OP_MASK_CODE19, OP_SH_CODE19); break;
8538 case 'K': USE_BITS (OP_MASK_RD, OP_SH_RD); break;
8540 case 'M': USE_BITS (OP_MASK_CCC, OP_SH_CCC); break;
8541 case 'N': USE_BITS (OP_MASK_BCC, OP_SH_BCC); break;
8542 case 'O': USE_BITS (OP_MASK_ALN, OP_SH_ALN); break;
8543 case 'Q': USE_BITS (OP_MASK_VSEL, OP_SH_VSEL);
8544 USE_BITS (OP_MASK_FT, OP_SH_FT); break;
8545 case 'R': USE_BITS (OP_MASK_FR, OP_SH_FR); break;
8546 case 'S': USE_BITS (OP_MASK_FS, OP_SH_FS); break;
8547 case 'T': USE_BITS (OP_MASK_FT, OP_SH_FT); break;
8548 case 'V': USE_BITS (OP_MASK_FS, OP_SH_FS); break;
8549 case 'W': USE_BITS (OP_MASK_FT, OP_SH_FT); break;
8550 case 'X': USE_BITS (OP_MASK_FD, OP_SH_FD); break;
8551 case 'Y': USE_BITS (OP_MASK_FS, OP_SH_FS); break;
8552 case 'Z': USE_BITS (OP_MASK_FT, OP_SH_FT); break;
8553 case 'a': USE_BITS (OP_MASK_TARGET, OP_SH_TARGET); break;
8554 case 'b': USE_BITS (OP_MASK_RS, OP_SH_RS); break;
8555 case 'c': USE_BITS (OP_MASK_CODE, OP_SH_CODE); break;
8556 case 'd': USE_BITS (OP_MASK_RD, OP_SH_RD); break;
8558 case 'h': USE_BITS (OP_MASK_PREFX, OP_SH_PREFX); break;
8559 case 'i': USE_BITS (OP_MASK_IMMEDIATE, OP_SH_IMMEDIATE); break;
8560 case 'j': USE_BITS (OP_MASK_DELTA, OP_SH_DELTA); break;
8561 case 'k': USE_BITS (OP_MASK_CACHE, OP_SH_CACHE); break;
8563 case 'o': USE_BITS (OP_MASK_DELTA, OP_SH_DELTA); break;
8564 case 'p': USE_BITS (OP_MASK_DELTA, OP_SH_DELTA); break;
8565 case 'q': USE_BITS (OP_MASK_CODE2, OP_SH_CODE2); break;
8566 case 'r': USE_BITS (OP_MASK_RS, OP_SH_RS); break;
8567 case 's': USE_BITS (OP_MASK_RS, OP_SH_RS); break;
8568 case 't': USE_BITS (OP_MASK_RT, OP_SH_RT); break;
8569 case 'u': USE_BITS (OP_MASK_IMMEDIATE, OP_SH_IMMEDIATE); break;
8570 case 'v': USE_BITS (OP_MASK_RS, OP_SH_RS); break;
8571 case 'w': USE_BITS (OP_MASK_RT, OP_SH_RT); break;
8574 case 'P': USE_BITS (OP_MASK_PERFREG, OP_SH_PERFREG); break;
8575 case 'U': USE_BITS (OP_MASK_RD, OP_SH_RD);
8576 USE_BITS (OP_MASK_RT, OP_SH_RT); break;
8577 case 'e': USE_BITS (OP_MASK_VECBYTE, OP_SH_VECBYTE); break;
8578 case '%': USE_BITS (OP_MASK_VECALIGN, OP_SH_VECALIGN); break;
8582 as_bad (_("internal: bad mips opcode (unknown operand type `%c'): %s %s"),
8583 c, opc->name, opc->args);
8587 if (used_bits != 0xffffffff)
8589 as_bad (_("internal: bad mips opcode (bits 0x%lx undefined): %s %s"),
8590 ~used_bits & 0xffffffff, opc->name, opc->args);
8596 /* This routine assembles an instruction into its binary format. As a
8597 side effect, it sets one of the global variables imm_reloc or
8598 offset_reloc to the type of relocation to do if one of the operands
8599 is an address expression. */
8604 struct mips_cl_insn *ip;
8609 struct mips_opcode *insn;
8612 unsigned int lastregno = 0;
8613 unsigned int lastpos = 0;
8614 unsigned int limlo, limhi;
8620 /* If the instruction contains a '.', we first try to match an instruction
8621 including the '.'. Then we try again without the '.'. */
8623 for (s = str; *s != '\0' && !ISSPACE (*s); ++s)
8626 /* If we stopped on whitespace, then replace the whitespace with null for
8627 the call to hash_find. Save the character we replaced just in case we
8628 have to re-parse the instruction. */
8635 insn = (struct mips_opcode *) hash_find (op_hash, str);
8637 /* If we didn't find the instruction in the opcode table, try again, but
8638 this time with just the instruction up to, but not including the
8642 /* Restore the character we overwrite above (if any). */
8646 /* Scan up to the first '.' or whitespace. */
8648 *s != '\0' && *s != '.' && !ISSPACE (*s);
8652 /* If we did not find a '.', then we can quit now. */
8655 insn_error = "unrecognized opcode";
8659 /* Lookup the instruction in the hash table. */
8661 if ((insn = (struct mips_opcode *) hash_find (op_hash, str)) == NULL)
8663 insn_error = "unrecognized opcode";
8673 assert (strcmp (insn->name, str) == 0);
8675 if (OPCODE_IS_MEMBER (insn,
8677 | (file_ase_mips16 ? INSN_MIPS16 : 0)
8678 | (mips_opts.ase_mdmx ? INSN_MDMX : 0)
8679 | (mips_opts.ase_mips3d ? INSN_MIPS3D : 0)),
8685 if (insn->pinfo != INSN_MACRO)
8687 if (mips_arch == CPU_R4650 && (insn->pinfo & FP_D) != 0)
8693 if (insn + 1 < &mips_opcodes[NUMOPCODES]
8694 && strcmp (insn->name, insn[1].name) == 0)
8703 static char buf[100];
8704 if (mips_arch_info->is_isa)
8706 _("opcode not supported at this ISA level (%s)"),
8707 mips_cpu_info_from_isa (mips_opts.isa)->name);
8710 _("opcode not supported on this processor: %s (%s)"),
8711 mips_arch_info->name,
8712 mips_cpu_info_from_isa (mips_opts.isa)->name);
8722 ip->insn_opcode = insn->match;
8724 for (args = insn->args;; ++args)
8728 s += strspn (s, " \t");
8732 case '\0': /* end of args */
8745 ip->insn_opcode |= lastregno << OP_SH_RS;
8749 ip->insn_opcode |= lastregno << OP_SH_RT;
8753 ip->insn_opcode |= lastregno << OP_SH_FT;
8757 ip->insn_opcode |= lastregno << OP_SH_FS;
8763 /* Handle optional base register.
8764 Either the base register is omitted or
8765 we must have a left paren. */
8766 /* This is dependent on the next operand specifier
8767 is a base register specification. */
8768 assert (args[1] == 'b' || args[1] == '5'
8769 || args[1] == '-' || args[1] == '4');
8773 case ')': /* these must match exactly */
8780 case '+': /* Opcode extension character. */
8783 case 'A': /* ins/ext position, becomes LSB. */
8786 my_getExpression (&imm_expr, s);
8787 check_absolute_expr (ip, &imm_expr);
8788 if ((unsigned long) imm_expr.X_add_number < limlo
8789 || (unsigned long) imm_expr.X_add_number > limhi)
8791 as_bad (_("Improper position (%lu)"),
8792 (unsigned long) imm_expr.X_add_number);
8793 imm_expr.X_add_number = limlo;
8795 lastpos = imm_expr.X_add_number;
8796 ip->insn_opcode |= (imm_expr.X_add_number
8797 & OP_MASK_SHAMT) << OP_SH_SHAMT;
8798 imm_expr.X_op = O_absent;
8802 case 'B': /* ins size, becomes MSB. */
8805 my_getExpression (&imm_expr, s);
8806 check_absolute_expr (ip, &imm_expr);
8807 /* Check for negative input so that small negative numbers
8808 will not succeed incorrectly. The checks against
8809 (pos+size) transitively check "size" itself,
8810 assuming that "pos" is reasonable. */
8811 if ((long) imm_expr.X_add_number < 0
8812 || ((unsigned long) imm_expr.X_add_number
8814 || ((unsigned long) imm_expr.X_add_number
8817 as_bad (_("Improper insert size (%lu, position %lu)"),
8818 (unsigned long) imm_expr.X_add_number,
8819 (unsigned long) lastpos);
8820 imm_expr.X_add_number = limlo - lastpos;
8822 ip->insn_opcode |= ((lastpos + imm_expr.X_add_number - 1)
8823 & OP_MASK_INSMSB) << OP_SH_INSMSB;
8824 imm_expr.X_op = O_absent;
8828 case 'C': /* ext size, becomes MSBD. */
8831 my_getExpression (&imm_expr, s);
8832 check_absolute_expr (ip, &imm_expr);
8833 /* Check for negative input so that small negative numbers
8834 will not succeed incorrectly. The checks against
8835 (pos+size) transitively check "size" itself,
8836 assuming that "pos" is reasonable. */
8837 if ((long) imm_expr.X_add_number < 0
8838 || ((unsigned long) imm_expr.X_add_number
8840 || ((unsigned long) imm_expr.X_add_number
8843 as_bad (_("Improper extract size (%lu, position %lu)"),
8844 (unsigned long) imm_expr.X_add_number,
8845 (unsigned long) lastpos);
8846 imm_expr.X_add_number = limlo - lastpos;
8848 ip->insn_opcode |= ((imm_expr.X_add_number - 1)
8849 & OP_MASK_EXTMSBD) << OP_SH_EXTMSBD;
8850 imm_expr.X_op = O_absent;
8855 /* +D is for disassembly only; never match. */
8859 as_bad (_("internal: bad mips opcode (unknown extension operand type `+%c'): %s %s"),
8860 *args, insn->name, insn->args);
8861 /* Further processing is fruitless. */
8866 case '<': /* must be at least one digit */
8868 * According to the manual, if the shift amount is greater
8869 * than 31 or less than 0, then the shift amount should be
8870 * mod 32. In reality the mips assembler issues an error.
8871 * We issue a warning and mask out all but the low 5 bits.
8873 my_getExpression (&imm_expr, s);
8874 check_absolute_expr (ip, &imm_expr);
8875 if ((unsigned long) imm_expr.X_add_number > 31)
8877 as_warn (_("Improper shift amount (%lu)"),
8878 (unsigned long) imm_expr.X_add_number);
8879 imm_expr.X_add_number &= OP_MASK_SHAMT;
8881 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_SHAMT;
8882 imm_expr.X_op = O_absent;
8886 case '>': /* shift amount minus 32 */
8887 my_getExpression (&imm_expr, s);
8888 check_absolute_expr (ip, &imm_expr);
8889 if ((unsigned long) imm_expr.X_add_number < 32
8890 || (unsigned long) imm_expr.X_add_number > 63)
8892 ip->insn_opcode |= (imm_expr.X_add_number - 32) << OP_SH_SHAMT;
8893 imm_expr.X_op = O_absent;
8897 case 'k': /* cache code */
8898 case 'h': /* prefx code */
8899 my_getExpression (&imm_expr, s);
8900 check_absolute_expr (ip, &imm_expr);
8901 if ((unsigned long) imm_expr.X_add_number > 31)
8903 as_warn (_("Invalid value for `%s' (%lu)"),
8905 (unsigned long) imm_expr.X_add_number);
8906 imm_expr.X_add_number &= 0x1f;
8909 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_CACHE;
8911 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_PREFX;
8912 imm_expr.X_op = O_absent;
8916 case 'c': /* break code */
8917 my_getExpression (&imm_expr, s);
8918 check_absolute_expr (ip, &imm_expr);
8919 if ((unsigned long) imm_expr.X_add_number > 1023)
8921 as_warn (_("Illegal break code (%lu)"),
8922 (unsigned long) imm_expr.X_add_number);
8923 imm_expr.X_add_number &= OP_MASK_CODE;
8925 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_CODE;
8926 imm_expr.X_op = O_absent;
8930 case 'q': /* lower break code */
8931 my_getExpression (&imm_expr, s);
8932 check_absolute_expr (ip, &imm_expr);
8933 if ((unsigned long) imm_expr.X_add_number > 1023)
8935 as_warn (_("Illegal lower break code (%lu)"),
8936 (unsigned long) imm_expr.X_add_number);
8937 imm_expr.X_add_number &= OP_MASK_CODE2;
8939 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_CODE2;
8940 imm_expr.X_op = O_absent;
8944 case 'B': /* 20-bit syscall/break code. */
8945 my_getExpression (&imm_expr, s);
8946 check_absolute_expr (ip, &imm_expr);
8947 if ((unsigned long) imm_expr.X_add_number > OP_MASK_CODE20)
8948 as_warn (_("Illegal 20-bit code (%lu)"),
8949 (unsigned long) imm_expr.X_add_number);
8950 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_CODE20;
8951 imm_expr.X_op = O_absent;
8955 case 'C': /* Coprocessor code */
8956 my_getExpression (&imm_expr, s);
8957 check_absolute_expr (ip, &imm_expr);
8958 if ((unsigned long) imm_expr.X_add_number >= (1 << 25))
8960 as_warn (_("Coproccesor code > 25 bits (%lu)"),
8961 (unsigned long) imm_expr.X_add_number);
8962 imm_expr.X_add_number &= ((1 << 25) - 1);
8964 ip->insn_opcode |= imm_expr.X_add_number;
8965 imm_expr.X_op = O_absent;
8969 case 'J': /* 19-bit wait code. */
8970 my_getExpression (&imm_expr, s);
8971 check_absolute_expr (ip, &imm_expr);
8972 if ((unsigned long) imm_expr.X_add_number > OP_MASK_CODE19)
8973 as_warn (_("Illegal 19-bit code (%lu)"),
8974 (unsigned long) imm_expr.X_add_number);
8975 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_CODE19;
8976 imm_expr.X_op = O_absent;
8980 case 'P': /* Performance register */
8981 my_getExpression (&imm_expr, s);
8982 check_absolute_expr (ip, &imm_expr);
8983 if (imm_expr.X_add_number != 0 && imm_expr.X_add_number != 1)
8985 as_warn (_("Invalid performance register (%lu)"),
8986 (unsigned long) imm_expr.X_add_number);
8987 imm_expr.X_add_number &= OP_MASK_PERFREG;
8989 ip->insn_opcode |= (imm_expr.X_add_number << OP_SH_PERFREG);
8990 imm_expr.X_op = O_absent;
8994 case 'b': /* base register */
8995 case 'd': /* destination register */
8996 case 's': /* source register */
8997 case 't': /* target register */
8998 case 'r': /* both target and source */
8999 case 'v': /* both dest and source */
9000 case 'w': /* both dest and target */
9001 case 'E': /* coprocessor target register */
9002 case 'G': /* coprocessor destination register */
9003 case 'K': /* 'rdhwr' destination register */
9004 case 'x': /* ignore register name */
9005 case 'z': /* must be zero register */
9006 case 'U': /* destination register (clo/clz). */
9021 while (ISDIGIT (*s));
9023 as_bad (_("Invalid register number (%d)"), regno);
9025 else if (*args == 'E' || *args == 'G' || *args == 'K')
9029 if (s[1] == 'r' && s[2] == 'a')
9034 else if (s[1] == 'f' && s[2] == 'p')
9039 else if (s[1] == 's' && s[2] == 'p')
9044 else if (s[1] == 'g' && s[2] == 'p')
9049 else if (s[1] == 'a' && s[2] == 't')
9054 else if (s[1] == 'k' && s[2] == 't' && s[3] == '0')
9059 else if (s[1] == 'k' && s[2] == 't' && s[3] == '1')
9064 else if (s[1] == 'z' && s[2] == 'e' && s[3] == 'r' && s[4] == 'o')
9069 else if (itbl_have_entries)
9074 p = s + 1; /* advance past '$' */
9075 n = itbl_get_field (&p); /* n is name */
9077 /* See if this is a register defined in an
9079 if (itbl_get_reg_val (n, &r))
9081 /* Get_field advances to the start of
9082 the next field, so we need to back
9083 rack to the end of the last field. */
9087 s = strchr (s, '\0');
9101 as_warn (_("Used $at without \".set noat\""));
9107 if (c == 'r' || c == 'v' || c == 'w')
9114 /* 'z' only matches $0. */
9115 if (c == 'z' && regno != 0)
9118 /* Now that we have assembled one operand, we use the args string
9119 * to figure out where it goes in the instruction. */
9126 ip->insn_opcode |= regno << OP_SH_RS;
9131 ip->insn_opcode |= regno << OP_SH_RD;
9134 ip->insn_opcode |= regno << OP_SH_RD;
9135 ip->insn_opcode |= regno << OP_SH_RT;
9140 ip->insn_opcode |= regno << OP_SH_RT;
9143 /* This case exists because on the r3000 trunc
9144 expands into a macro which requires a gp
9145 register. On the r6000 or r4000 it is
9146 assembled into a single instruction which
9147 ignores the register. Thus the insn version
9148 is MIPS_ISA2 and uses 'x', and the macro
9149 version is MIPS_ISA1 and uses 't'. */
9152 /* This case is for the div instruction, which
9153 acts differently if the destination argument
9154 is $0. This only matches $0, and is checked
9155 outside the switch. */
9158 /* Itbl operand; not yet implemented. FIXME ?? */
9160 /* What about all other operands like 'i', which
9161 can be specified in the opcode table? */
9171 ip->insn_opcode |= lastregno << OP_SH_RS;
9174 ip->insn_opcode |= lastregno << OP_SH_RT;
9179 case 'O': /* MDMX alignment immediate constant. */
9180 my_getExpression (&imm_expr, s);
9181 check_absolute_expr (ip, &imm_expr);
9182 if ((unsigned long) imm_expr.X_add_number > OP_MASK_ALN)
9184 as_warn ("Improper align amount (%ld), using low bits",
9185 (long) imm_expr.X_add_number);
9186 imm_expr.X_add_number &= OP_MASK_ALN;
9188 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_ALN;
9189 imm_expr.X_op = O_absent;
9193 case 'Q': /* MDMX vector, element sel, or const. */
9196 /* MDMX Immediate. */
9197 my_getExpression (&imm_expr, s);
9198 check_absolute_expr (ip, &imm_expr);
9199 if ((unsigned long) imm_expr.X_add_number > OP_MASK_FT)
9201 as_warn (_("Invalid MDMX Immediate (%ld)"),
9202 (long) imm_expr.X_add_number);
9203 imm_expr.X_add_number &= OP_MASK_FT;
9205 imm_expr.X_add_number &= OP_MASK_FT;
9206 if (ip->insn_opcode & (OP_MASK_VSEL << OP_SH_VSEL))
9207 ip->insn_opcode |= MDMX_FMTSEL_IMM_QH << OP_SH_VSEL;
9209 ip->insn_opcode |= MDMX_FMTSEL_IMM_OB << OP_SH_VSEL;
9210 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_FT;
9211 imm_expr.X_op = O_absent;
9215 /* Not MDMX Immediate. Fall through. */
9216 case 'X': /* MDMX destination register. */
9217 case 'Y': /* MDMX source register. */
9218 case 'Z': /* MDMX target register. */
9220 case 'D': /* floating point destination register */
9221 case 'S': /* floating point source register */
9222 case 'T': /* floating point target register */
9223 case 'R': /* floating point source register */
9227 /* Accept $fN for FP and MDMX register numbers, and in
9228 addition accept $vN for MDMX register numbers. */
9229 if ((s[0] == '$' && s[1] == 'f' && ISDIGIT (s[2]))
9230 || (is_mdmx != 0 && s[0] == '$' && s[1] == 'v'
9241 while (ISDIGIT (*s));
9244 as_bad (_("Invalid float register number (%d)"), regno);
9246 if ((regno & 1) != 0
9248 && ! (strcmp (str, "mtc1") == 0
9249 || strcmp (str, "mfc1") == 0
9250 || strcmp (str, "lwc1") == 0
9251 || strcmp (str, "swc1") == 0
9252 || strcmp (str, "l.s") == 0
9253 || strcmp (str, "s.s") == 0))
9254 as_warn (_("Float register should be even, was %d"),
9262 if (c == 'V' || c == 'W')
9273 ip->insn_opcode |= regno << OP_SH_FD;
9278 ip->insn_opcode |= regno << OP_SH_FS;
9281 /* This is like 'Z', but also needs to fix the MDMX
9282 vector/scalar select bits. Note that the
9283 scalar immediate case is handled above. */
9286 int is_qh = (ip->insn_opcode & (1 << OP_SH_VSEL));
9287 int max_el = (is_qh ? 3 : 7);
9289 my_getExpression(&imm_expr, s);
9290 check_absolute_expr (ip, &imm_expr);
9292 if (imm_expr.X_add_number > max_el)
9293 as_bad(_("Bad element selector %ld"),
9294 (long) imm_expr.X_add_number);
9295 imm_expr.X_add_number &= max_el;
9296 ip->insn_opcode |= (imm_expr.X_add_number
9300 as_warn(_("Expecting ']' found '%s'"), s);
9306 if (ip->insn_opcode & (OP_MASK_VSEL << OP_SH_VSEL))
9307 ip->insn_opcode |= (MDMX_FMTSEL_VEC_QH
9310 ip->insn_opcode |= (MDMX_FMTSEL_VEC_OB <<
9317 ip->insn_opcode |= regno << OP_SH_FT;
9320 ip->insn_opcode |= regno << OP_SH_FR;
9330 ip->insn_opcode |= lastregno << OP_SH_FS;
9333 ip->insn_opcode |= lastregno << OP_SH_FT;
9339 my_getExpression (&imm_expr, s);
9340 if (imm_expr.X_op != O_big
9341 && imm_expr.X_op != O_constant)
9342 insn_error = _("absolute expression required");
9347 my_getExpression (&offset_expr, s);
9348 *imm_reloc = BFD_RELOC_32;
9361 unsigned char temp[8];
9363 unsigned int length;
9368 /* These only appear as the last operand in an
9369 instruction, and every instruction that accepts
9370 them in any variant accepts them in all variants.
9371 This means we don't have to worry about backing out
9372 any changes if the instruction does not match.
9374 The difference between them is the size of the
9375 floating point constant and where it goes. For 'F'
9376 and 'L' the constant is 64 bits; for 'f' and 'l' it
9377 is 32 bits. Where the constant is placed is based
9378 on how the MIPS assembler does things:
9381 f -- immediate value
9384 The .lit4 and .lit8 sections are only used if
9385 permitted by the -G argument.
9387 When generating embedded PIC code, we use the
9388 .lit8 section but not the .lit4 section (we can do
9389 .lit4 inline easily; we need to put .lit8
9390 somewhere in the data segment, and using .lit8
9391 permits the linker to eventually combine identical
9394 The code below needs to know whether the target register
9395 is 32 or 64 bits wide. It relies on the fact 'f' and
9396 'F' are used with GPR-based instructions and 'l' and
9397 'L' are used with FPR-based instructions. */
9399 f64 = *args == 'F' || *args == 'L';
9400 using_gprs = *args == 'F' || *args == 'f';
9402 save_in = input_line_pointer;
9403 input_line_pointer = s;
9404 err = md_atof (f64 ? 'd' : 'f', (char *) temp, &len);
9406 s = input_line_pointer;
9407 input_line_pointer = save_in;
9408 if (err != NULL && *err != '\0')
9410 as_bad (_("Bad floating point constant: %s"), err);
9411 memset (temp, '\0', sizeof temp);
9412 length = f64 ? 8 : 4;
9415 assert (length == (unsigned) (f64 ? 8 : 4));
9419 && (! USE_GLOBAL_POINTER_OPT
9420 || mips_pic == EMBEDDED_PIC
9421 || g_switch_value < 4
9422 || (temp[0] == 0 && temp[1] == 0)
9423 || (temp[2] == 0 && temp[3] == 0))))
9425 imm_expr.X_op = O_constant;
9426 if (! target_big_endian)
9427 imm_expr.X_add_number = bfd_getl32 (temp);
9429 imm_expr.X_add_number = bfd_getb32 (temp);
9432 && ! mips_disable_float_construction
9433 /* Constants can only be constructed in GPRs and
9434 copied to FPRs if the GPRs are at least as wide
9435 as the FPRs. Force the constant into memory if
9436 we are using 64-bit FPRs but the GPRs are only
9439 || ! (HAVE_64BIT_FPRS && HAVE_32BIT_GPRS))
9440 && ((temp[0] == 0 && temp[1] == 0)
9441 || (temp[2] == 0 && temp[3] == 0))
9442 && ((temp[4] == 0 && temp[5] == 0)
9443 || (temp[6] == 0 && temp[7] == 0)))
9445 /* The value is simple enough to load with a couple of
9446 instructions. If using 32-bit registers, set
9447 imm_expr to the high order 32 bits and offset_expr to
9448 the low order 32 bits. Otherwise, set imm_expr to
9449 the entire 64 bit constant. */
9450 if (using_gprs ? HAVE_32BIT_GPRS : HAVE_32BIT_FPRS)
9452 imm_expr.X_op = O_constant;
9453 offset_expr.X_op = O_constant;
9454 if (! target_big_endian)
9456 imm_expr.X_add_number = bfd_getl32 (temp + 4);
9457 offset_expr.X_add_number = bfd_getl32 (temp);
9461 imm_expr.X_add_number = bfd_getb32 (temp);
9462 offset_expr.X_add_number = bfd_getb32 (temp + 4);
9464 if (offset_expr.X_add_number == 0)
9465 offset_expr.X_op = O_absent;
9467 else if (sizeof (imm_expr.X_add_number) > 4)
9469 imm_expr.X_op = O_constant;
9470 if (! target_big_endian)
9471 imm_expr.X_add_number = bfd_getl64 (temp);
9473 imm_expr.X_add_number = bfd_getb64 (temp);
9477 imm_expr.X_op = O_big;
9478 imm_expr.X_add_number = 4;
9479 if (! target_big_endian)
9481 generic_bignum[0] = bfd_getl16 (temp);
9482 generic_bignum[1] = bfd_getl16 (temp + 2);
9483 generic_bignum[2] = bfd_getl16 (temp + 4);
9484 generic_bignum[3] = bfd_getl16 (temp + 6);
9488 generic_bignum[0] = bfd_getb16 (temp + 6);
9489 generic_bignum[1] = bfd_getb16 (temp + 4);
9490 generic_bignum[2] = bfd_getb16 (temp + 2);
9491 generic_bignum[3] = bfd_getb16 (temp);
9497 const char *newname;
9500 /* Switch to the right section. */
9502 subseg = now_subseg;
9505 default: /* unused default case avoids warnings. */
9507 newname = RDATA_SECTION_NAME;
9508 if ((USE_GLOBAL_POINTER_OPT && g_switch_value >= 8)
9509 || mips_pic == EMBEDDED_PIC)
9513 if (mips_pic == EMBEDDED_PIC)
9516 newname = RDATA_SECTION_NAME;
9519 assert (!USE_GLOBAL_POINTER_OPT
9520 || g_switch_value >= 4);
9524 new_seg = subseg_new (newname, (subsegT) 0);
9525 if (OUTPUT_FLAVOR == bfd_target_elf_flavour)
9526 bfd_set_section_flags (stdoutput, new_seg,
9531 frag_align (*args == 'l' ? 2 : 3, 0, 0);
9532 if (OUTPUT_FLAVOR == bfd_target_elf_flavour
9533 && strcmp (TARGET_OS, "elf") != 0)
9534 record_alignment (new_seg, 4);
9536 record_alignment (new_seg, *args == 'l' ? 2 : 3);
9538 as_bad (_("Can't use floating point insn in this section"));
9540 /* Set the argument to the current address in the
9542 offset_expr.X_op = O_symbol;
9543 offset_expr.X_add_symbol =
9544 symbol_new ("L0\001", now_seg,
9545 (valueT) frag_now_fix (), frag_now);
9546 offset_expr.X_add_number = 0;
9548 /* Put the floating point number into the section. */
9549 p = frag_more ((int) length);
9550 memcpy (p, temp, length);
9552 /* Switch back to the original section. */
9553 subseg_set (seg, subseg);
9558 case 'i': /* 16 bit unsigned immediate */
9559 case 'j': /* 16 bit signed immediate */
9560 *imm_reloc = BFD_RELOC_LO16;
9561 if (my_getSmallExpression (&imm_expr, imm_reloc, s) == 0)
9564 offsetT minval, maxval;
9566 more = (insn + 1 < &mips_opcodes[NUMOPCODES]
9567 && strcmp (insn->name, insn[1].name) == 0);
9569 /* If the expression was written as an unsigned number,
9570 only treat it as signed if there are no more
9574 && sizeof (imm_expr.X_add_number) <= 4
9575 && imm_expr.X_op == O_constant
9576 && imm_expr.X_add_number < 0
9577 && imm_expr.X_unsigned
9581 /* For compatibility with older assemblers, we accept
9582 0x8000-0xffff as signed 16-bit numbers when only
9583 signed numbers are allowed. */
9585 minval = 0, maxval = 0xffff;
9587 minval = -0x8000, maxval = 0x7fff;
9589 minval = -0x8000, maxval = 0xffff;
9591 if (imm_expr.X_op != O_constant
9592 || imm_expr.X_add_number < minval
9593 || imm_expr.X_add_number > maxval)
9597 if (imm_expr.X_op == O_constant
9598 || imm_expr.X_op == O_big)
9599 as_bad (_("expression out of range"));
9605 case 'o': /* 16 bit offset */
9606 /* Check whether there is only a single bracketed expression
9607 left. If so, it must be the base register and the
9608 constant must be zero. */
9609 if (*s == '(' && strchr (s + 1, '(') == 0)
9611 offset_expr.X_op = O_constant;
9612 offset_expr.X_add_number = 0;
9616 /* If this value won't fit into a 16 bit offset, then go
9617 find a macro that will generate the 32 bit offset
9619 if (my_getSmallExpression (&offset_expr, offset_reloc, s) == 0
9620 && (offset_expr.X_op != O_constant
9621 || offset_expr.X_add_number >= 0x8000
9622 || offset_expr.X_add_number < -0x8000))
9628 case 'p': /* pc relative offset */
9629 *offset_reloc = BFD_RELOC_16_PCREL_S2;
9630 my_getExpression (&offset_expr, s);
9634 case 'u': /* upper 16 bits */
9635 if (my_getSmallExpression (&imm_expr, imm_reloc, s) == 0
9636 && imm_expr.X_op == O_constant
9637 && (imm_expr.X_add_number < 0
9638 || imm_expr.X_add_number >= 0x10000))
9639 as_bad (_("lui expression not in range 0..65535"));
9643 case 'a': /* 26 bit address */
9644 my_getExpression (&offset_expr, s);
9646 *offset_reloc = BFD_RELOC_MIPS_JMP;
9649 case 'N': /* 3 bit branch condition code */
9650 case 'M': /* 3 bit compare condition code */
9651 if (strncmp (s, "$fcc", 4) != 0)
9661 while (ISDIGIT (*s));
9663 as_bad (_("invalid condition code register $fcc%d"), regno);
9665 ip->insn_opcode |= regno << OP_SH_BCC;
9667 ip->insn_opcode |= regno << OP_SH_CCC;
9671 if (s[0] == '0' && (s[1] == 'x' || s[1] == 'X'))
9682 while (ISDIGIT (*s));
9685 c = 8; /* Invalid sel value. */
9688 as_bad (_("invalid coprocessor sub-selection value (0-7)"));
9689 ip->insn_opcode |= c;
9693 /* Must be at least one digit. */
9694 my_getExpression (&imm_expr, s);
9695 check_absolute_expr (ip, &imm_expr);
9697 if ((unsigned long) imm_expr.X_add_number
9698 > (unsigned long) OP_MASK_VECBYTE)
9700 as_bad (_("bad byte vector index (%ld)"),
9701 (long) imm_expr.X_add_number);
9702 imm_expr.X_add_number = 0;
9705 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_VECBYTE;
9706 imm_expr.X_op = O_absent;
9711 my_getExpression (&imm_expr, s);
9712 check_absolute_expr (ip, &imm_expr);
9714 if ((unsigned long) imm_expr.X_add_number
9715 > (unsigned long) OP_MASK_VECALIGN)
9717 as_bad (_("bad byte vector index (%ld)"),
9718 (long) imm_expr.X_add_number);
9719 imm_expr.X_add_number = 0;
9722 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_VECALIGN;
9723 imm_expr.X_op = O_absent;
9728 as_bad (_("bad char = '%c'\n"), *args);
9733 /* Args don't match. */
9734 if (insn + 1 < &mips_opcodes[NUMOPCODES] &&
9735 !strcmp (insn->name, insn[1].name))
9739 insn_error = _("illegal operands");
9744 insn_error = _("illegal operands");
9749 /* This routine assembles an instruction into its binary format when
9750 assembling for the mips16. As a side effect, it sets one of the
9751 global variables imm_reloc or offset_reloc to the type of
9752 relocation to do if one of the operands is an address expression.
9753 It also sets mips16_small and mips16_ext if the user explicitly
9754 requested a small or extended instruction. */
9759 struct mips_cl_insn *ip;
9763 struct mips_opcode *insn;
9766 unsigned int lastregno = 0;
9771 mips16_small = FALSE;
9774 for (s = str; ISLOWER (*s); ++s)
9786 if (s[1] == 't' && s[2] == ' ')
9789 mips16_small = TRUE;
9793 else if (s[1] == 'e' && s[2] == ' ')
9802 insn_error = _("unknown opcode");
9806 if (mips_opts.noautoextend && ! mips16_ext)
9807 mips16_small = TRUE;
9809 if ((insn = (struct mips_opcode *) hash_find (mips16_op_hash, str)) == NULL)
9811 insn_error = _("unrecognized opcode");
9818 assert (strcmp (insn->name, str) == 0);
9821 ip->insn_opcode = insn->match;
9822 ip->use_extend = FALSE;
9823 imm_expr.X_op = O_absent;
9824 imm_reloc[0] = BFD_RELOC_UNUSED;
9825 imm_reloc[1] = BFD_RELOC_UNUSED;
9826 imm_reloc[2] = BFD_RELOC_UNUSED;
9827 offset_expr.X_op = O_absent;
9828 offset_reloc[0] = BFD_RELOC_UNUSED;
9829 offset_reloc[1] = BFD_RELOC_UNUSED;
9830 offset_reloc[2] = BFD_RELOC_UNUSED;
9831 for (args = insn->args; 1; ++args)
9838 /* In this switch statement we call break if we did not find
9839 a match, continue if we did find a match, or return if we
9848 /* Stuff the immediate value in now, if we can. */
9849 if (imm_expr.X_op == O_constant
9850 && *imm_reloc > BFD_RELOC_UNUSED
9851 && insn->pinfo != INSN_MACRO)
9853 mips16_immed (NULL, 0, *imm_reloc - BFD_RELOC_UNUSED,
9854 imm_expr.X_add_number, TRUE, mips16_small,
9855 mips16_ext, &ip->insn_opcode,
9856 &ip->use_extend, &ip->extend);
9857 imm_expr.X_op = O_absent;
9858 *imm_reloc = BFD_RELOC_UNUSED;
9872 ip->insn_opcode |= lastregno << MIPS16OP_SH_RX;
9875 ip->insn_opcode |= lastregno << MIPS16OP_SH_RY;
9891 ip->insn_opcode |= lastregno << MIPS16OP_SH_RX;
9893 ip->insn_opcode |= lastregno << MIPS16OP_SH_RY;
9920 while (ISDIGIT (*s));
9923 as_bad (_("invalid register number (%d)"), regno);
9929 if (s[1] == 'r' && s[2] == 'a')
9934 else if (s[1] == 'f' && s[2] == 'p')
9939 else if (s[1] == 's' && s[2] == 'p')
9944 else if (s[1] == 'g' && s[2] == 'p')
9949 else if (s[1] == 'a' && s[2] == 't')
9954 else if (s[1] == 'k' && s[2] == 't' && s[3] == '0')
9959 else if (s[1] == 'k' && s[2] == 't' && s[3] == '1')
9964 else if (s[1] == 'z' && s[2] == 'e' && s[3] == 'r' && s[4] == 'o')
9977 if (c == 'v' || c == 'w')
9979 regno = mips16_to_32_reg_map[lastregno];
9993 regno = mips32_to_16_reg_map[regno];
9998 regno = ILLEGAL_REG;
10003 regno = ILLEGAL_REG;
10008 regno = ILLEGAL_REG;
10013 if (regno == AT && ! mips_opts.noat)
10014 as_warn (_("used $at without \".set noat\""));
10021 if (regno == ILLEGAL_REG)
10028 ip->insn_opcode |= regno << MIPS16OP_SH_RX;
10032 ip->insn_opcode |= regno << MIPS16OP_SH_RY;
10035 ip->insn_opcode |= regno << MIPS16OP_SH_RZ;
10038 ip->insn_opcode |= regno << MIPS16OP_SH_MOVE32Z;
10044 ip->insn_opcode |= regno << MIPS16OP_SH_REGR32;
10047 regno = ((regno & 7) << 2) | ((regno & 0x18) >> 3);
10048 ip->insn_opcode |= regno << MIPS16OP_SH_REG32R;
10058 if (strncmp (s, "$pc", 3) == 0)
10082 && strncmp (s + 1, "gprel(", sizeof "gprel(" - 1) == 0)
10084 /* This is %gprel(SYMBOL). We need to read SYMBOL,
10085 and generate the appropriate reloc. If the text
10086 inside %gprel is not a symbol name with an
10087 optional offset, then we generate a normal reloc
10088 and will probably fail later. */
10089 my_getExpression (&imm_expr, s + sizeof "%gprel" - 1);
10090 if (imm_expr.X_op == O_symbol)
10093 *imm_reloc = BFD_RELOC_MIPS16_GPREL;
10095 ip->use_extend = TRUE;
10102 /* Just pick up a normal expression. */
10103 my_getExpression (&imm_expr, s);
10106 if (imm_expr.X_op == O_register)
10108 /* What we thought was an expression turned out to
10111 if (s[0] == '(' && args[1] == '(')
10113 /* It looks like the expression was omitted
10114 before a register indirection, which means
10115 that the expression is implicitly zero. We
10116 still set up imm_expr, so that we handle
10117 explicit extensions correctly. */
10118 imm_expr.X_op = O_constant;
10119 imm_expr.X_add_number = 0;
10120 *imm_reloc = (int) BFD_RELOC_UNUSED + c;
10127 /* We need to relax this instruction. */
10128 *imm_reloc = (int) BFD_RELOC_UNUSED + c;
10137 /* We use offset_reloc rather than imm_reloc for the PC
10138 relative operands. This lets macros with both
10139 immediate and address operands work correctly. */
10140 my_getExpression (&offset_expr, s);
10142 if (offset_expr.X_op == O_register)
10145 /* We need to relax this instruction. */
10146 *offset_reloc = (int) BFD_RELOC_UNUSED + c;
10150 case '6': /* break code */
10151 my_getExpression (&imm_expr, s);
10152 check_absolute_expr (ip, &imm_expr);
10153 if ((unsigned long) imm_expr.X_add_number > 63)
10155 as_warn (_("Invalid value for `%s' (%lu)"),
10157 (unsigned long) imm_expr.X_add_number);
10158 imm_expr.X_add_number &= 0x3f;
10160 ip->insn_opcode |= imm_expr.X_add_number << MIPS16OP_SH_IMM6;
10161 imm_expr.X_op = O_absent;
10165 case 'a': /* 26 bit address */
10166 my_getExpression (&offset_expr, s);
10168 *offset_reloc = BFD_RELOC_MIPS16_JMP;
10169 ip->insn_opcode <<= 16;
10172 case 'l': /* register list for entry macro */
10173 case 'L': /* register list for exit macro */
10183 int freg, reg1, reg2;
10185 while (*s == ' ' || *s == ',')
10189 as_bad (_("can't parse register list"));
10201 while (ISDIGIT (*s))
10223 as_bad (_("invalid register list"));
10228 while (ISDIGIT (*s))
10235 if (freg && reg1 == 0 && reg2 == 0 && c == 'L')
10237 mask &= ~ (7 << 3);
10240 else if (freg && reg1 == 0 && reg2 == 1 && c == 'L')
10242 mask &= ~ (7 << 3);
10245 else if (reg1 == 4 && reg2 >= 4 && reg2 <= 7 && c != 'L')
10246 mask |= (reg2 - 3) << 3;
10247 else if (reg1 == 16 && reg2 >= 16 && reg2 <= 17)
10248 mask |= (reg2 - 15) << 1;
10249 else if (reg1 == RA && reg2 == RA)
10253 as_bad (_("invalid register list"));
10257 /* The mask is filled in in the opcode table for the
10258 benefit of the disassembler. We remove it before
10259 applying the actual mask. */
10260 ip->insn_opcode &= ~ ((7 << 3) << MIPS16OP_SH_IMM6);
10261 ip->insn_opcode |= mask << MIPS16OP_SH_IMM6;
10265 case 'e': /* extend code */
10266 my_getExpression (&imm_expr, s);
10267 check_absolute_expr (ip, &imm_expr);
10268 if ((unsigned long) imm_expr.X_add_number > 0x7ff)
10270 as_warn (_("Invalid value for `%s' (%lu)"),
10272 (unsigned long) imm_expr.X_add_number);
10273 imm_expr.X_add_number &= 0x7ff;
10275 ip->insn_opcode |= imm_expr.X_add_number;
10276 imm_expr.X_op = O_absent;
10286 /* Args don't match. */
10287 if (insn + 1 < &mips16_opcodes[bfd_mips16_num_opcodes] &&
10288 strcmp (insn->name, insn[1].name) == 0)
10295 insn_error = _("illegal operands");
10301 /* This structure holds information we know about a mips16 immediate
10304 struct mips16_immed_operand
10306 /* The type code used in the argument string in the opcode table. */
10308 /* The number of bits in the short form of the opcode. */
10310 /* The number of bits in the extended form of the opcode. */
10312 /* The amount by which the short form is shifted when it is used;
10313 for example, the sw instruction has a shift count of 2. */
10315 /* The amount by which the short form is shifted when it is stored
10316 into the instruction code. */
10318 /* Non-zero if the short form is unsigned. */
10320 /* Non-zero if the extended form is unsigned. */
10322 /* Non-zero if the value is PC relative. */
10326 /* The mips16 immediate operand types. */
10328 static const struct mips16_immed_operand mips16_immed_operands[] =
10330 { '<', 3, 5, 0, MIPS16OP_SH_RZ, 1, 1, 0 },
10331 { '>', 3, 5, 0, MIPS16OP_SH_RX, 1, 1, 0 },
10332 { '[', 3, 6, 0, MIPS16OP_SH_RZ, 1, 1, 0 },
10333 { ']', 3, 6, 0, MIPS16OP_SH_RX, 1, 1, 0 },
10334 { '4', 4, 15, 0, MIPS16OP_SH_IMM4, 0, 0, 0 },
10335 { '5', 5, 16, 0, MIPS16OP_SH_IMM5, 1, 0, 0 },
10336 { 'H', 5, 16, 1, MIPS16OP_SH_IMM5, 1, 0, 0 },
10337 { 'W', 5, 16, 2, MIPS16OP_SH_IMM5, 1, 0, 0 },
10338 { 'D', 5, 16, 3, MIPS16OP_SH_IMM5, 1, 0, 0 },
10339 { 'j', 5, 16, 0, MIPS16OP_SH_IMM5, 0, 0, 0 },
10340 { '8', 8, 16, 0, MIPS16OP_SH_IMM8, 1, 0, 0 },
10341 { 'V', 8, 16, 2, MIPS16OP_SH_IMM8, 1, 0, 0 },
10342 { 'C', 8, 16, 3, MIPS16OP_SH_IMM8, 1, 0, 0 },
10343 { 'U', 8, 16, 0, MIPS16OP_SH_IMM8, 1, 1, 0 },
10344 { 'k', 8, 16, 0, MIPS16OP_SH_IMM8, 0, 0, 0 },
10345 { 'K', 8, 16, 3, MIPS16OP_SH_IMM8, 0, 0, 0 },
10346 { 'p', 8, 16, 0, MIPS16OP_SH_IMM8, 0, 0, 1 },
10347 { 'q', 11, 16, 0, MIPS16OP_SH_IMM8, 0, 0, 1 },
10348 { 'A', 8, 16, 2, MIPS16OP_SH_IMM8, 1, 0, 1 },
10349 { 'B', 5, 16, 3, MIPS16OP_SH_IMM5, 1, 0, 1 },
10350 { 'E', 5, 16, 2, MIPS16OP_SH_IMM5, 1, 0, 1 }
10353 #define MIPS16_NUM_IMMED \
10354 (sizeof mips16_immed_operands / sizeof mips16_immed_operands[0])
10356 /* Handle a mips16 instruction with an immediate value. This or's the
10357 small immediate value into *INSN. It sets *USE_EXTEND to indicate
10358 whether an extended value is needed; if one is needed, it sets
10359 *EXTEND to the value. The argument type is TYPE. The value is VAL.
10360 If SMALL is true, an unextended opcode was explicitly requested.
10361 If EXT is true, an extended opcode was explicitly requested. If
10362 WARN is true, warn if EXT does not match reality. */
10365 mips16_immed (file, line, type, val, warn, small, ext, insn, use_extend,
10374 unsigned long *insn;
10375 bfd_boolean *use_extend;
10376 unsigned short *extend;
10378 register const struct mips16_immed_operand *op;
10379 int mintiny, maxtiny;
10380 bfd_boolean needext;
10382 op = mips16_immed_operands;
10383 while (op->type != type)
10386 assert (op < mips16_immed_operands + MIPS16_NUM_IMMED);
10391 if (type == '<' || type == '>' || type == '[' || type == ']')
10394 maxtiny = 1 << op->nbits;
10399 maxtiny = (1 << op->nbits) - 1;
10404 mintiny = - (1 << (op->nbits - 1));
10405 maxtiny = (1 << (op->nbits - 1)) - 1;
10408 /* Branch offsets have an implicit 0 in the lowest bit. */
10409 if (type == 'p' || type == 'q')
10412 if ((val & ((1 << op->shift) - 1)) != 0
10413 || val < (mintiny << op->shift)
10414 || val > (maxtiny << op->shift))
10419 if (warn && ext && ! needext)
10420 as_warn_where (file, line,
10421 _("extended operand requested but not required"));
10422 if (small && needext)
10423 as_bad_where (file, line, _("invalid unextended operand value"));
10425 if (small || (! ext && ! needext))
10429 *use_extend = FALSE;
10430 insnval = ((val >> op->shift) & ((1 << op->nbits) - 1));
10431 insnval <<= op->op_shift;
10436 long minext, maxext;
10442 maxext = (1 << op->extbits) - 1;
10446 minext = - (1 << (op->extbits - 1));
10447 maxext = (1 << (op->extbits - 1)) - 1;
10449 if (val < minext || val > maxext)
10450 as_bad_where (file, line,
10451 _("operand value out of range for instruction"));
10453 *use_extend = TRUE;
10454 if (op->extbits == 16)
10456 extval = ((val >> 11) & 0x1f) | (val & 0x7e0);
10459 else if (op->extbits == 15)
10461 extval = ((val >> 11) & 0xf) | (val & 0x7f0);
10466 extval = ((val & 0x1f) << 6) | (val & 0x20);
10470 *extend = (unsigned short) extval;
10475 static const struct percent_op_match
10478 bfd_reloc_code_real_type reloc;
10481 {"%lo", BFD_RELOC_LO16},
10483 {"%call_hi", BFD_RELOC_MIPS_CALL_HI16},
10484 {"%call_lo", BFD_RELOC_MIPS_CALL_LO16},
10485 {"%call16", BFD_RELOC_MIPS_CALL16},
10486 {"%got_disp", BFD_RELOC_MIPS_GOT_DISP},
10487 {"%got_page", BFD_RELOC_MIPS_GOT_PAGE},
10488 {"%got_ofst", BFD_RELOC_MIPS_GOT_OFST},
10489 {"%got_hi", BFD_RELOC_MIPS_GOT_HI16},
10490 {"%got_lo", BFD_RELOC_MIPS_GOT_LO16},
10491 {"%got", BFD_RELOC_MIPS_GOT16},
10492 {"%gp_rel", BFD_RELOC_GPREL16},
10493 {"%half", BFD_RELOC_16},
10494 {"%highest", BFD_RELOC_MIPS_HIGHEST},
10495 {"%higher", BFD_RELOC_MIPS_HIGHER},
10496 {"%neg", BFD_RELOC_MIPS_SUB},
10498 {"%hi", BFD_RELOC_HI16_S}
10502 /* Return true if *STR points to a relocation operator. When returning true,
10503 move *STR over the operator and store its relocation code in *RELOC.
10504 Leave both *STR and *RELOC alone when returning false. */
10507 parse_relocation (str, reloc)
10509 bfd_reloc_code_real_type *reloc;
10513 for (i = 0; i < ARRAY_SIZE (percent_op); i++)
10514 if (strncasecmp (*str, percent_op[i].str, strlen (percent_op[i].str)) == 0)
10516 *str += strlen (percent_op[i].str);
10517 *reloc = percent_op[i].reloc;
10519 /* Check whether the output BFD supports this relocation.
10520 If not, issue an error and fall back on something safe. */
10521 if (!bfd_reloc_type_lookup (stdoutput, percent_op[i].reloc))
10523 as_bad ("relocation %s isn't supported by the current ABI",
10524 percent_op[i].str);
10525 *reloc = BFD_RELOC_LO16;
10533 /* Parse string STR as a 16-bit relocatable operand. Store the
10534 expression in *EP and the relocations in the array starting
10535 at RELOC. Return the number of relocation operators used.
10537 On exit, EXPR_END points to the first character after the expression.
10538 If no relocation operators are used, RELOC[0] is set to BFD_RELOC_LO16. */
10541 my_getSmallExpression (ep, reloc, str)
10543 bfd_reloc_code_real_type *reloc;
10546 bfd_reloc_code_real_type reversed_reloc[3];
10547 size_t reloc_index, i;
10548 int crux_depth, str_depth;
10551 /* Search for the start of the main expression, recoding relocations
10552 in REVERSED_RELOC. End the loop with CRUX pointing to the start
10553 of the main expression and with CRUX_DEPTH containing the number
10554 of open brackets at that point. */
10561 crux_depth = str_depth;
10563 /* Skip over whitespace and brackets, keeping count of the number
10565 while (*str == ' ' || *str == '\t' || *str == '(')
10570 && reloc_index < (HAVE_NEWABI ? 3 : 1)
10571 && parse_relocation (&str, &reversed_reloc[reloc_index]));
10573 my_getExpression (ep, crux);
10576 /* Match every open bracket. */
10577 while (crux_depth > 0 && (*str == ')' || *str == ' ' || *str == '\t'))
10581 if (crux_depth > 0)
10582 as_bad ("unclosed '('");
10586 if (reloc_index == 0)
10587 reloc[0] = BFD_RELOC_LO16;
10590 prev_reloc_op_frag = frag_now;
10591 for (i = 0; i < reloc_index; i++)
10592 reloc[i] = reversed_reloc[reloc_index - 1 - i];
10595 return reloc_index;
10599 my_getExpression (ep, str)
10606 save_in = input_line_pointer;
10607 input_line_pointer = str;
10609 expr_end = input_line_pointer;
10610 input_line_pointer = save_in;
10612 /* If we are in mips16 mode, and this is an expression based on `.',
10613 then we bump the value of the symbol by 1 since that is how other
10614 text symbols are handled. We don't bother to handle complex
10615 expressions, just `.' plus or minus a constant. */
10616 if (mips_opts.mips16
10617 && ep->X_op == O_symbol
10618 && strcmp (S_GET_NAME (ep->X_add_symbol), FAKE_LABEL_NAME) == 0
10619 && S_GET_SEGMENT (ep->X_add_symbol) == now_seg
10620 && symbol_get_frag (ep->X_add_symbol) == frag_now
10621 && symbol_constant_p (ep->X_add_symbol)
10622 && (val = S_GET_VALUE (ep->X_add_symbol)) == frag_now_fix ())
10623 S_SET_VALUE (ep->X_add_symbol, val + 1);
10626 /* Turn a string in input_line_pointer into a floating point constant
10627 of type TYPE, and store the appropriate bytes in *LITP. The number
10628 of LITTLENUMS emitted is stored in *SIZEP. An error message is
10629 returned, or NULL on OK. */
10632 md_atof (type, litP, sizeP)
10638 LITTLENUM_TYPE words[4];
10654 return _("bad call to md_atof");
10657 t = atof_ieee (input_line_pointer, type, words);
10659 input_line_pointer = t;
10663 if (! target_big_endian)
10665 for (i = prec - 1; i >= 0; i--)
10667 md_number_to_chars (litP, (valueT) words[i], 2);
10673 for (i = 0; i < prec; i++)
10675 md_number_to_chars (litP, (valueT) words[i], 2);
10684 md_number_to_chars (buf, val, n)
10689 if (target_big_endian)
10690 number_to_chars_bigendian (buf, val, n);
10692 number_to_chars_littleendian (buf, val, n);
10696 static int support_64bit_objects(void)
10698 const char **list, **l;
10701 list = bfd_target_list ();
10702 for (l = list; *l != NULL; l++)
10704 /* This is traditional mips */
10705 if (strcmp (*l, "elf64-tradbigmips") == 0
10706 || strcmp (*l, "elf64-tradlittlemips") == 0)
10708 if (strcmp (*l, "elf64-bigmips") == 0
10709 || strcmp (*l, "elf64-littlemips") == 0)
10712 yes = (*l != NULL);
10716 #endif /* OBJ_ELF */
10718 const char *md_shortopts = "nO::g::G:";
10720 struct option md_longopts[] =
10722 #define OPTION_MIPS1 (OPTION_MD_BASE + 1)
10723 {"mips0", no_argument, NULL, OPTION_MIPS1},
10724 {"mips1", no_argument, NULL, OPTION_MIPS1},
10725 #define OPTION_MIPS2 (OPTION_MD_BASE + 2)
10726 {"mips2", no_argument, NULL, OPTION_MIPS2},
10727 #define OPTION_MIPS3 (OPTION_MD_BASE + 3)
10728 {"mips3", no_argument, NULL, OPTION_MIPS3},
10729 #define OPTION_MIPS4 (OPTION_MD_BASE + 4)
10730 {"mips4", no_argument, NULL, OPTION_MIPS4},
10731 #define OPTION_MIPS5 (OPTION_MD_BASE + 5)
10732 {"mips5", no_argument, NULL, OPTION_MIPS5},
10733 #define OPTION_MIPS32 (OPTION_MD_BASE + 6)
10734 {"mips32", no_argument, NULL, OPTION_MIPS32},
10735 #define OPTION_MIPS64 (OPTION_MD_BASE + 7)
10736 {"mips64", no_argument, NULL, OPTION_MIPS64},
10737 #define OPTION_MEMBEDDED_PIC (OPTION_MD_BASE + 8)
10738 {"membedded-pic", no_argument, NULL, OPTION_MEMBEDDED_PIC},
10739 #define OPTION_TRAP (OPTION_MD_BASE + 9)
10740 {"trap", no_argument, NULL, OPTION_TRAP},
10741 {"no-break", no_argument, NULL, OPTION_TRAP},
10742 #define OPTION_BREAK (OPTION_MD_BASE + 10)
10743 {"break", no_argument, NULL, OPTION_BREAK},
10744 {"no-trap", no_argument, NULL, OPTION_BREAK},
10745 #define OPTION_EB (OPTION_MD_BASE + 11)
10746 {"EB", no_argument, NULL, OPTION_EB},
10747 #define OPTION_EL (OPTION_MD_BASE + 12)
10748 {"EL", no_argument, NULL, OPTION_EL},
10749 #define OPTION_MIPS16 (OPTION_MD_BASE + 13)
10750 {"mips16", no_argument, NULL, OPTION_MIPS16},
10751 #define OPTION_NO_MIPS16 (OPTION_MD_BASE + 14)
10752 {"no-mips16", no_argument, NULL, OPTION_NO_MIPS16},
10753 #define OPTION_M7000_HILO_FIX (OPTION_MD_BASE + 15)
10754 {"mfix7000", no_argument, NULL, OPTION_M7000_HILO_FIX},
10755 #define OPTION_MNO_7000_HILO_FIX (OPTION_MD_BASE + 16)
10756 {"no-fix-7000", no_argument, NULL, OPTION_MNO_7000_HILO_FIX},
10757 {"mno-fix7000", no_argument, NULL, OPTION_MNO_7000_HILO_FIX},
10758 #define OPTION_FP32 (OPTION_MD_BASE + 17)
10759 {"mfp32", no_argument, NULL, OPTION_FP32},
10760 #define OPTION_GP32 (OPTION_MD_BASE + 18)
10761 {"mgp32", no_argument, NULL, OPTION_GP32},
10762 #define OPTION_CONSTRUCT_FLOATS (OPTION_MD_BASE + 19)
10763 {"construct-floats", no_argument, NULL, OPTION_CONSTRUCT_FLOATS},
10764 #define OPTION_NO_CONSTRUCT_FLOATS (OPTION_MD_BASE + 20)
10765 {"no-construct-floats", no_argument, NULL, OPTION_NO_CONSTRUCT_FLOATS},
10766 #define OPTION_MARCH (OPTION_MD_BASE + 21)
10767 {"march", required_argument, NULL, OPTION_MARCH},
10768 #define OPTION_MTUNE (OPTION_MD_BASE + 22)
10769 {"mtune", required_argument, NULL, OPTION_MTUNE},
10770 #define OPTION_FP64 (OPTION_MD_BASE + 23)
10771 {"mfp64", no_argument, NULL, OPTION_FP64},
10772 #define OPTION_M4650 (OPTION_MD_BASE + 24)
10773 {"m4650", no_argument, NULL, OPTION_M4650},
10774 #define OPTION_NO_M4650 (OPTION_MD_BASE + 25)
10775 {"no-m4650", no_argument, NULL, OPTION_NO_M4650},
10776 #define OPTION_M4010 (OPTION_MD_BASE + 26)
10777 {"m4010", no_argument, NULL, OPTION_M4010},
10778 #define OPTION_NO_M4010 (OPTION_MD_BASE + 27)
10779 {"no-m4010", no_argument, NULL, OPTION_NO_M4010},
10780 #define OPTION_M4100 (OPTION_MD_BASE + 28)
10781 {"m4100", no_argument, NULL, OPTION_M4100},
10782 #define OPTION_NO_M4100 (OPTION_MD_BASE + 29)
10783 {"no-m4100", no_argument, NULL, OPTION_NO_M4100},
10784 #define OPTION_M3900 (OPTION_MD_BASE + 30)
10785 {"m3900", no_argument, NULL, OPTION_M3900},
10786 #define OPTION_NO_M3900 (OPTION_MD_BASE + 31)
10787 {"no-m3900", no_argument, NULL, OPTION_NO_M3900},
10788 #define OPTION_GP64 (OPTION_MD_BASE + 32)
10789 {"mgp64", no_argument, NULL, OPTION_GP64},
10790 #define OPTION_MIPS3D (OPTION_MD_BASE + 33)
10791 {"mips3d", no_argument, NULL, OPTION_MIPS3D},
10792 #define OPTION_NO_MIPS3D (OPTION_MD_BASE + 34)
10793 {"no-mips3d", no_argument, NULL, OPTION_NO_MIPS3D},
10794 #define OPTION_MDMX (OPTION_MD_BASE + 35)
10795 {"mdmx", no_argument, NULL, OPTION_MDMX},
10796 #define OPTION_NO_MDMX (OPTION_MD_BASE + 36)
10797 {"no-mdmx", no_argument, NULL, OPTION_NO_MDMX},
10798 #define OPTION_FIX_VR4122 (OPTION_MD_BASE + 37)
10799 #define OPTION_NO_FIX_VR4122 (OPTION_MD_BASE + 38)
10800 {"mfix-vr4122-bugs", no_argument, NULL, OPTION_FIX_VR4122},
10801 {"no-mfix-vr4122-bugs", no_argument, NULL, OPTION_NO_FIX_VR4122},
10802 #define OPTION_RELAX_BRANCH (OPTION_MD_BASE + 39)
10803 #define OPTION_NO_RELAX_BRANCH (OPTION_MD_BASE + 40)
10804 {"relax-branch", no_argument, NULL, OPTION_RELAX_BRANCH},
10805 {"no-relax-branch", no_argument, NULL, OPTION_NO_RELAX_BRANCH},
10806 #define OPTION_MIPS32R2 (OPTION_MD_BASE + 41)
10807 {"mips32r2", no_argument, NULL, OPTION_MIPS32R2},
10809 #define OPTION_ELF_BASE (OPTION_MD_BASE + 42)
10810 #define OPTION_CALL_SHARED (OPTION_ELF_BASE + 0)
10811 {"KPIC", no_argument, NULL, OPTION_CALL_SHARED},
10812 {"call_shared", no_argument, NULL, OPTION_CALL_SHARED},
10813 #define OPTION_NON_SHARED (OPTION_ELF_BASE + 1)
10814 {"non_shared", no_argument, NULL, OPTION_NON_SHARED},
10815 #define OPTION_XGOT (OPTION_ELF_BASE + 2)
10816 {"xgot", no_argument, NULL, OPTION_XGOT},
10817 #define OPTION_MABI (OPTION_ELF_BASE + 3)
10818 {"mabi", required_argument, NULL, OPTION_MABI},
10819 #define OPTION_32 (OPTION_ELF_BASE + 4)
10820 {"32", no_argument, NULL, OPTION_32},
10821 #define OPTION_N32 (OPTION_ELF_BASE + 5)
10822 {"n32", no_argument, NULL, OPTION_N32},
10823 #define OPTION_64 (OPTION_ELF_BASE + 6)
10824 {"64", no_argument, NULL, OPTION_64},
10825 #define OPTION_MDEBUG (OPTION_ELF_BASE + 7)
10826 {"mdebug", no_argument, NULL, OPTION_MDEBUG},
10827 #define OPTION_NO_MDEBUG (OPTION_ELF_BASE + 8)
10828 {"no-mdebug", no_argument, NULL, OPTION_NO_MDEBUG},
10829 #endif /* OBJ_ELF */
10830 {NULL, no_argument, NULL, 0}
10832 size_t md_longopts_size = sizeof (md_longopts);
10834 /* Set STRING_PTR (either &mips_arch_string or &mips_tune_string) to
10835 NEW_VALUE. Warn if another value was already specified. Note:
10836 we have to defer parsing the -march and -mtune arguments in order
10837 to handle 'from-abi' correctly, since the ABI might be specified
10838 in a later argument. */
10841 mips_set_option_string (string_ptr, new_value)
10842 const char **string_ptr, *new_value;
10844 if (*string_ptr != 0 && strcasecmp (*string_ptr, new_value) != 0)
10845 as_warn (_("A different %s was already specified, is now %s"),
10846 string_ptr == &mips_arch_string ? "-march" : "-mtune",
10849 *string_ptr = new_value;
10853 md_parse_option (c, arg)
10859 case OPTION_CONSTRUCT_FLOATS:
10860 mips_disable_float_construction = 0;
10863 case OPTION_NO_CONSTRUCT_FLOATS:
10864 mips_disable_float_construction = 1;
10876 target_big_endian = 1;
10880 target_big_endian = 0;
10888 if (arg && arg[1] == '0')
10898 mips_debug = atoi (arg);
10899 /* When the MIPS assembler sees -g or -g2, it does not do
10900 optimizations which limit full symbolic debugging. We take
10901 that to be equivalent to -O0. */
10902 if (mips_debug == 2)
10907 file_mips_isa = ISA_MIPS1;
10911 file_mips_isa = ISA_MIPS2;
10915 file_mips_isa = ISA_MIPS3;
10919 file_mips_isa = ISA_MIPS4;
10923 file_mips_isa = ISA_MIPS5;
10926 case OPTION_MIPS32:
10927 file_mips_isa = ISA_MIPS32;
10930 case OPTION_MIPS32R2:
10931 file_mips_isa = ISA_MIPS32R2;
10934 case OPTION_MIPS64:
10935 file_mips_isa = ISA_MIPS64;
10939 mips_set_option_string (&mips_tune_string, arg);
10943 mips_set_option_string (&mips_arch_string, arg);
10947 mips_set_option_string (&mips_arch_string, "4650");
10948 mips_set_option_string (&mips_tune_string, "4650");
10951 case OPTION_NO_M4650:
10955 mips_set_option_string (&mips_arch_string, "4010");
10956 mips_set_option_string (&mips_tune_string, "4010");
10959 case OPTION_NO_M4010:
10963 mips_set_option_string (&mips_arch_string, "4100");
10964 mips_set_option_string (&mips_tune_string, "4100");
10967 case OPTION_NO_M4100:
10971 mips_set_option_string (&mips_arch_string, "3900");
10972 mips_set_option_string (&mips_tune_string, "3900");
10975 case OPTION_NO_M3900:
10979 mips_opts.ase_mdmx = 1;
10982 case OPTION_NO_MDMX:
10983 mips_opts.ase_mdmx = 0;
10986 case OPTION_MIPS16:
10987 mips_opts.mips16 = 1;
10988 mips_no_prev_insn (FALSE);
10991 case OPTION_NO_MIPS16:
10992 mips_opts.mips16 = 0;
10993 mips_no_prev_insn (FALSE);
10996 case OPTION_MIPS3D:
10997 mips_opts.ase_mips3d = 1;
11000 case OPTION_NO_MIPS3D:
11001 mips_opts.ase_mips3d = 0;
11004 case OPTION_MEMBEDDED_PIC:
11005 mips_pic = EMBEDDED_PIC;
11006 if (USE_GLOBAL_POINTER_OPT && g_switch_seen)
11008 as_bad (_("-G may not be used with embedded PIC code"));
11011 g_switch_value = 0x7fffffff;
11014 case OPTION_FIX_VR4122:
11015 mips_fix_4122_bugs = 1;
11018 case OPTION_NO_FIX_VR4122:
11019 mips_fix_4122_bugs = 0;
11022 case OPTION_RELAX_BRANCH:
11023 mips_relax_branch = 1;
11026 case OPTION_NO_RELAX_BRANCH:
11027 mips_relax_branch = 0;
11031 /* When generating ELF code, we permit -KPIC and -call_shared to
11032 select SVR4_PIC, and -non_shared to select no PIC. This is
11033 intended to be compatible with Irix 5. */
11034 case OPTION_CALL_SHARED:
11035 if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
11037 as_bad (_("-call_shared is supported only for ELF format"));
11040 mips_pic = SVR4_PIC;
11041 if (g_switch_seen && g_switch_value != 0)
11043 as_bad (_("-G may not be used with SVR4 PIC code"));
11046 g_switch_value = 0;
11049 case OPTION_NON_SHARED:
11050 if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
11052 as_bad (_("-non_shared is supported only for ELF format"));
11058 /* The -xgot option tells the assembler to use 32 offsets when
11059 accessing the got in SVR4_PIC mode. It is for Irix
11064 #endif /* OBJ_ELF */
11067 if (! USE_GLOBAL_POINTER_OPT)
11069 as_bad (_("-G is not supported for this configuration"));
11072 else if (mips_pic == SVR4_PIC || mips_pic == EMBEDDED_PIC)
11074 as_bad (_("-G may not be used with SVR4 or embedded PIC code"));
11078 g_switch_value = atoi (arg);
11083 /* The -32, -n32 and -64 options are shortcuts for -mabi=32, -mabi=n32
11086 if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
11088 as_bad (_("-32 is supported for ELF format only"));
11091 mips_abi = O32_ABI;
11095 if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
11097 as_bad (_("-n32 is supported for ELF format only"));
11100 mips_abi = N32_ABI;
11104 if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
11106 as_bad (_("-64 is supported for ELF format only"));
11109 mips_abi = N64_ABI;
11110 if (! support_64bit_objects())
11111 as_fatal (_("No compiled in support for 64 bit object file format"));
11113 #endif /* OBJ_ELF */
11116 file_mips_gp32 = 1;
11120 file_mips_gp32 = 0;
11124 file_mips_fp32 = 1;
11128 file_mips_fp32 = 0;
11133 if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
11135 as_bad (_("-mabi is supported for ELF format only"));
11138 if (strcmp (arg, "32") == 0)
11139 mips_abi = O32_ABI;
11140 else if (strcmp (arg, "o64") == 0)
11141 mips_abi = O64_ABI;
11142 else if (strcmp (arg, "n32") == 0)
11143 mips_abi = N32_ABI;
11144 else if (strcmp (arg, "64") == 0)
11146 mips_abi = N64_ABI;
11147 if (! support_64bit_objects())
11148 as_fatal (_("No compiled in support for 64 bit object file "
11151 else if (strcmp (arg, "eabi") == 0)
11152 mips_abi = EABI_ABI;
11155 as_fatal (_("invalid abi -mabi=%s"), arg);
11159 #endif /* OBJ_ELF */
11161 case OPTION_M7000_HILO_FIX:
11162 mips_7000_hilo_fix = TRUE;
11165 case OPTION_MNO_7000_HILO_FIX:
11166 mips_7000_hilo_fix = FALSE;
11170 case OPTION_MDEBUG:
11171 mips_flag_mdebug = TRUE;
11174 case OPTION_NO_MDEBUG:
11175 mips_flag_mdebug = FALSE;
11177 #endif /* OBJ_ELF */
11186 /* Set up globals to generate code for the ISA or processor
11187 described by INFO. */
11190 mips_set_architecture (info)
11191 const struct mips_cpu_info *info;
11195 mips_arch_info = info;
11196 mips_arch = info->cpu;
11197 mips_opts.isa = info->isa;
11202 /* Likewise for tuning. */
11205 mips_set_tune (info)
11206 const struct mips_cpu_info *info;
11210 mips_tune_info = info;
11211 mips_tune = info->cpu;
11217 mips_after_parse_args ()
11219 /* GP relative stuff not working for PE */
11220 if (strncmp (TARGET_OS, "pe", 2) == 0
11221 && g_switch_value != 0)
11224 as_bad (_("-G not supported in this configuration."));
11225 g_switch_value = 0;
11228 /* The following code determines the architecture and register size.
11229 Similar code was added to GCC 3.3 (see override_options() in
11230 config/mips/mips.c). The GAS and GCC code should be kept in sync
11231 as much as possible. */
11233 if (mips_arch_string != 0)
11234 mips_set_architecture (mips_parse_cpu ("-march", mips_arch_string));
11236 if (mips_tune_string != 0)
11237 mips_set_tune (mips_parse_cpu ("-mtune", mips_tune_string));
11239 if (file_mips_isa != ISA_UNKNOWN)
11241 /* Handle -mipsN. At this point, file_mips_isa contains the
11242 ISA level specified by -mipsN, while mips_opts.isa contains
11243 the -march selection (if any). */
11244 if (mips_arch_info != 0)
11246 /* -march takes precedence over -mipsN, since it is more descriptive.
11247 There's no harm in specifying both as long as the ISA levels
11249 if (file_mips_isa != mips_opts.isa)
11250 as_bad (_("-%s conflicts with the other architecture options, which imply -%s"),
11251 mips_cpu_info_from_isa (file_mips_isa)->name,
11252 mips_cpu_info_from_isa (mips_opts.isa)->name);
11255 mips_set_architecture (mips_cpu_info_from_isa (file_mips_isa));
11258 if (mips_arch_info == 0)
11259 mips_set_architecture (mips_parse_cpu ("default CPU",
11260 MIPS_CPU_STRING_DEFAULT));
11262 if (ABI_NEEDS_64BIT_REGS (mips_abi) && !ISA_HAS_64BIT_REGS (mips_opts.isa))
11263 as_bad ("-march=%s is not compatible with the selected ABI",
11264 mips_arch_info->name);
11266 /* Optimize for mips_arch, unless -mtune selects a different processor. */
11267 if (mips_tune_info == 0)
11268 mips_set_tune (mips_arch_info);
11270 if (file_mips_gp32 >= 0)
11272 /* The user specified the size of the integer registers. Make sure
11273 it agrees with the ABI and ISA. */
11274 if (file_mips_gp32 == 0 && !ISA_HAS_64BIT_REGS (mips_opts.isa))
11275 as_bad (_("-mgp64 used with a 32-bit processor"));
11276 else if (file_mips_gp32 == 1 && ABI_NEEDS_64BIT_REGS (mips_abi))
11277 as_bad (_("-mgp32 used with a 64-bit ABI"));
11278 else if (file_mips_gp32 == 0 && ABI_NEEDS_32BIT_REGS (mips_abi))
11279 as_bad (_("-mgp64 used with a 32-bit ABI"));
11283 /* Infer the integer register size from the ABI and processor.
11284 Restrict ourselves to 32-bit registers if that's all the
11285 processor has, or if the ABI cannot handle 64-bit registers. */
11286 file_mips_gp32 = (ABI_NEEDS_32BIT_REGS (mips_abi)
11287 || !ISA_HAS_64BIT_REGS (mips_opts.isa));
11290 /* ??? GAS treats single-float processors as though they had 64-bit
11291 float registers (although it complains when double-precision
11292 instructions are used). As things stand, saying they have 32-bit
11293 registers would lead to spurious "register must be even" messages.
11294 So here we assume float registers are always the same size as
11295 integer ones, unless the user says otherwise. */
11296 if (file_mips_fp32 < 0)
11297 file_mips_fp32 = file_mips_gp32;
11299 /* End of GCC-shared inference code. */
11301 /* ??? When do we want this flag to be set? Who uses it? */
11302 if (file_mips_gp32 == 1
11303 && mips_abi == NO_ABI
11304 && ISA_HAS_64BIT_REGS (mips_opts.isa))
11305 mips_32bitmode = 1;
11307 if (mips_opts.isa == ISA_MIPS1 && mips_trap)
11308 as_bad (_("trap exception not supported at ISA 1"));
11310 /* If the selected architecture includes support for ASEs, enable
11311 generation of code for them. */
11312 if (mips_opts.mips16 == -1)
11313 mips_opts.mips16 = (CPU_HAS_MIPS16 (mips_arch)) ? 1 : 0;
11314 if (mips_opts.ase_mips3d == -1)
11315 mips_opts.ase_mips3d = (CPU_HAS_MIPS3D (mips_arch)) ? 1 : 0;
11316 if (mips_opts.ase_mdmx == -1)
11317 mips_opts.ase_mdmx = (CPU_HAS_MDMX (mips_arch)) ? 1 : 0;
11319 file_mips_isa = mips_opts.isa;
11320 file_ase_mips16 = mips_opts.mips16;
11321 file_ase_mips3d = mips_opts.ase_mips3d;
11322 file_ase_mdmx = mips_opts.ase_mdmx;
11323 mips_opts.gp32 = file_mips_gp32;
11324 mips_opts.fp32 = file_mips_fp32;
11326 if (mips_flag_mdebug < 0)
11328 #ifdef OBJ_MAYBE_ECOFF
11329 if (OUTPUT_FLAVOR == bfd_target_ecoff_flavour)
11330 mips_flag_mdebug = 1;
11332 #endif /* OBJ_MAYBE_ECOFF */
11333 mips_flag_mdebug = 0;
11338 mips_init_after_args ()
11340 /* initialize opcodes */
11341 bfd_mips_num_opcodes = bfd_mips_num_builtin_opcodes;
11342 mips_opcodes = (struct mips_opcode *) mips_builtin_opcodes;
11346 md_pcrel_from (fixP)
11349 if (OUTPUT_FLAVOR != bfd_target_aout_flavour
11350 && fixP->fx_addsy != (symbolS *) NULL
11351 && ! S_IS_DEFINED (fixP->fx_addsy))
11354 /* Return the address of the delay slot. */
11355 return fixP->fx_size + fixP->fx_where + fixP->fx_frag->fr_address;
11358 /* This is called before the symbol table is processed. In order to
11359 work with gcc when using mips-tfile, we must keep all local labels.
11360 However, in other cases, we want to discard them. If we were
11361 called with -g, but we didn't see any debugging information, it may
11362 mean that gcc is smuggling debugging information through to
11363 mips-tfile, in which case we must generate all local labels. */
11366 mips_frob_file_before_adjust ()
11368 #ifndef NO_ECOFF_DEBUGGING
11369 if (ECOFF_DEBUGGING
11371 && ! ecoff_debugging_seen)
11372 flag_keep_locals = 1;
11376 /* Sort any unmatched HI16_S relocs so that they immediately precede
11377 the corresponding LO reloc. This is called before md_apply_fix3 and
11378 tc_gen_reloc. Unmatched HI16_S relocs can only be generated by
11379 explicit use of the %hi modifier. */
11384 struct mips_hi_fixup *l;
11386 for (l = mips_hi_fixup_list; l != NULL; l = l->next)
11388 segment_info_type *seginfo;
11391 assert (reloc_needs_lo_p (l->fixp->fx_r_type));
11393 /* If a GOT16 relocation turns out to be against a global symbol,
11394 there isn't supposed to be a matching LO. */
11395 if (l->fixp->fx_r_type == BFD_RELOC_MIPS_GOT16
11396 && !pic_need_relax (l->fixp->fx_addsy, l->seg))
11399 /* Check quickly whether the next fixup happens to be a matching %lo. */
11400 if (fixup_has_matching_lo_p (l->fixp))
11403 /* Look through the fixups for this segment for a matching %lo.
11404 When we find one, move the %hi just in front of it. We do
11405 this in two passes. In the first pass, we try to find a
11406 unique %lo. In the second pass, we permit multiple %hi
11407 relocs for a single %lo (this is a GNU extension). */
11408 seginfo = seg_info (l->seg);
11409 for (pass = 0; pass < 2; pass++)
11414 for (f = seginfo->fix_root; f != NULL; f = f->fx_next)
11416 /* Check whether this is a %lo fixup which matches l->fixp. */
11417 if (f->fx_r_type == BFD_RELOC_LO16
11418 && f->fx_addsy == l->fixp->fx_addsy
11419 && f->fx_offset == l->fixp->fx_offset
11422 || !reloc_needs_lo_p (prev->fx_r_type)
11423 || !fixup_has_matching_lo_p (prev)))
11427 /* Move l->fixp before f. */
11428 for (pf = &seginfo->fix_root;
11430 pf = &(*pf)->fx_next)
11431 assert (*pf != NULL);
11433 *pf = l->fixp->fx_next;
11435 l->fixp->fx_next = f;
11437 seginfo->fix_root = l->fixp;
11439 prev->fx_next = l->fixp;
11450 #if 0 /* GCC code motion plus incomplete dead code elimination
11451 can leave a %hi without a %lo. */
11453 as_warn_where (l->fixp->fx_file, l->fixp->fx_line,
11454 _("Unmatched %%hi reloc"));
11460 /* When generating embedded PIC code we need to use a special
11461 relocation to represent the difference of two symbols in the .text
11462 section (switch tables use a difference of this sort). See
11463 include/coff/mips.h for details. This macro checks whether this
11464 fixup requires the special reloc. */
11465 #define SWITCH_TABLE(fixp) \
11466 ((fixp)->fx_r_type == BFD_RELOC_32 \
11467 && OUTPUT_FLAVOR != bfd_target_elf_flavour \
11468 && (fixp)->fx_addsy != NULL \
11469 && (fixp)->fx_subsy != NULL \
11470 && S_GET_SEGMENT ((fixp)->fx_addsy) == text_section \
11471 && S_GET_SEGMENT ((fixp)->fx_subsy) == text_section)
11473 /* When generating embedded PIC code we must keep all PC relative
11474 relocations, in case the linker has to relax a call. We also need
11475 to keep relocations for switch table entries.
11477 We may have combined relocations without symbols in the N32/N64 ABI.
11478 We have to prevent gas from dropping them. */
11481 mips_force_relocation (fixp)
11484 if (generic_force_reloc (fixp))
11488 && S_GET_SEGMENT (fixp->fx_addsy) == bfd_abs_section_ptr
11489 && (fixp->fx_r_type == BFD_RELOC_MIPS_SUB
11490 || fixp->fx_r_type == BFD_RELOC_HI16_S
11491 || fixp->fx_r_type == BFD_RELOC_LO16))
11494 return (mips_pic == EMBEDDED_PIC
11496 || SWITCH_TABLE (fixp)
11497 || fixp->fx_r_type == BFD_RELOC_PCREL_HI16_S
11498 || fixp->fx_r_type == BFD_RELOC_PCREL_LO16));
11501 /* This hook is called before a fix is simplified. We don't really
11502 decide whether to skip a fix here. Rather, we turn global symbols
11503 used as branch targets into local symbols, such that they undergo
11504 simplification. We can only do this if the symbol is defined and
11505 it is in the same section as the branch. If this doesn't hold, we
11506 emit a better error message than just saying the relocation is not
11507 valid for the selected object format.
11509 FIXP is the fix-up we're going to try to simplify, SEG is the
11510 segment in which the fix up occurs. The return value should be
11511 non-zero to indicate the fix-up is valid for further
11512 simplifications. */
11515 mips_validate_fix (fixP, seg)
11519 /* There's a lot of discussion on whether it should be possible to
11520 use R_MIPS_PC16 to represent branch relocations. The outcome
11521 seems to be that it can, but gas/bfd are very broken in creating
11522 RELA relocations for this, so for now we only accept branches to
11523 symbols in the same section. Anything else is of dubious value,
11524 since there's no guarantee that at link time the symbol would be
11525 in range. Even for branches to local symbols this is arguably
11526 wrong, since it we assume the symbol is not going to be
11527 overridden, which should be possible per ELF library semantics,
11528 but then, there isn't a dynamic relocation that could be used to
11529 this effect, and the target would likely be out of range as well.
11531 Unfortunately, it seems that there is too much code out there
11532 that relies on branches to symbols that are global to be resolved
11533 as if they were local, like the IRIX tools do, so we do it as
11534 well, but with a warning so that people are reminded to fix their
11535 code. If we ever get back to using R_MIPS_PC16 for branch
11536 targets, this entire block should go away (and probably the
11537 whole function). */
11539 if (fixP->fx_r_type == BFD_RELOC_16_PCREL_S2
11540 && (((OUTPUT_FLAVOR == bfd_target_ecoff_flavour
11541 || OUTPUT_FLAVOR == bfd_target_elf_flavour)
11542 && mips_pic != EMBEDDED_PIC)
11543 || bfd_reloc_type_lookup (stdoutput, BFD_RELOC_16_PCREL_S2) == NULL)
11546 if (! S_IS_DEFINED (fixP->fx_addsy))
11548 as_bad_where (fixP->fx_file, fixP->fx_line,
11549 _("Cannot branch to undefined symbol."));
11550 /* Avoid any further errors about this fixup. */
11553 else if (S_GET_SEGMENT (fixP->fx_addsy) != seg)
11555 as_bad_where (fixP->fx_file, fixP->fx_line,
11556 _("Cannot branch to symbol in another section."));
11559 else if (S_IS_EXTERNAL (fixP->fx_addsy))
11561 symbolS *sym = fixP->fx_addsy;
11563 as_warn_where (fixP->fx_file, fixP->fx_line,
11564 _("Pretending global symbol used as branch target is local."));
11566 fixP->fx_addsy = symbol_create (S_GET_NAME (sym),
11567 S_GET_SEGMENT (sym),
11569 symbol_get_frag (sym));
11570 copy_symbol_attributes (fixP->fx_addsy, sym);
11571 S_CLEAR_EXTERNAL (fixP->fx_addsy);
11572 assert (symbol_resolved_p (sym));
11573 symbol_mark_resolved (fixP->fx_addsy);
11582 mips_need_elf_addend_fixup (fixP)
11585 if (S_GET_OTHER (fixP->fx_addsy) == STO_MIPS16)
11587 if (mips_pic == EMBEDDED_PIC
11588 && S_IS_WEAK (fixP->fx_addsy))
11590 if (mips_pic != EMBEDDED_PIC
11591 && (S_IS_WEAK (fixP->fx_addsy)
11592 || S_IS_EXTERNAL (fixP->fx_addsy))
11593 && !S_IS_COMMON (fixP->fx_addsy))
11595 if (symbol_used_in_reloc_p (fixP->fx_addsy)
11596 && (((bfd_get_section_flags (stdoutput,
11597 S_GET_SEGMENT (fixP->fx_addsy))
11598 & (SEC_LINK_ONCE | SEC_MERGE)) != 0)
11599 || !strncmp (segment_name (S_GET_SEGMENT (fixP->fx_addsy)),
11601 sizeof (".gnu.linkonce") - 1)))
11607 /* Apply a fixup to the object file. */
11610 md_apply_fix3 (fixP, valP, seg)
11613 segT seg ATTRIBUTE_UNUSED;
11618 static int previous_fx_r_type = 0;
11620 /* FIXME: Maybe just return for all reloc types not listed below?
11621 Eric Christopher says: "This is stupid, please rewrite md_apply_fix3. */
11622 if (fixP->fx_r_type == BFD_RELOC_8)
11625 assert (fixP->fx_size == 4
11626 || fixP->fx_r_type == BFD_RELOC_16
11627 || fixP->fx_r_type == BFD_RELOC_32
11628 || fixP->fx_r_type == BFD_RELOC_MIPS_JMP
11629 || fixP->fx_r_type == BFD_RELOC_HI16_S
11630 || fixP->fx_r_type == BFD_RELOC_LO16
11631 || fixP->fx_r_type == BFD_RELOC_GPREL16
11632 || fixP->fx_r_type == BFD_RELOC_MIPS_LITERAL
11633 || fixP->fx_r_type == BFD_RELOC_GPREL32
11634 || fixP->fx_r_type == BFD_RELOC_64
11635 || fixP->fx_r_type == BFD_RELOC_CTOR
11636 || fixP->fx_r_type == BFD_RELOC_MIPS_SUB
11637 || fixP->fx_r_type == BFD_RELOC_MIPS_HIGHEST
11638 || fixP->fx_r_type == BFD_RELOC_MIPS_HIGHER
11639 || fixP->fx_r_type == BFD_RELOC_MIPS_SCN_DISP
11640 || fixP->fx_r_type == BFD_RELOC_MIPS_REL16
11641 || fixP->fx_r_type == BFD_RELOC_MIPS_RELGOT
11642 || fixP->fx_r_type == BFD_RELOC_VTABLE_INHERIT
11643 || fixP->fx_r_type == BFD_RELOC_VTABLE_ENTRY
11644 || fixP->fx_r_type == BFD_RELOC_MIPS_JALR);
11648 /* If we aren't adjusting this fixup to be against the section
11649 symbol, we need to adjust the value. */
11651 if (fixP->fx_addsy != NULL && OUTPUT_FLAVOR == bfd_target_elf_flavour)
11653 if (mips_need_elf_addend_fixup (fixP))
11655 reloc_howto_type *howto;
11656 valueT symval = S_GET_VALUE (fixP->fx_addsy);
11660 howto = bfd_reloc_type_lookup (stdoutput, fixP->fx_r_type);
11661 if (value != 0 && howto && howto->partial_inplace
11662 && (! fixP->fx_pcrel || howto->pcrel_offset))
11664 /* In this case, the bfd_install_relocation routine will
11665 incorrectly add the symbol value back in. We just want
11666 the addend to appear in the object file.
11668 howto->pcrel_offset is added for R_MIPS_PC16, which is
11669 generated for code like
11680 /* Make sure the addend is still non-zero. If it became zero
11681 after the last operation, set it to a spurious value and
11682 subtract the same value from the object file's contents. */
11687 /* The in-place addends for LO16 relocations are signed;
11688 leave the matching HI16 in-place addends as zero. */
11689 if (fixP->fx_r_type != BFD_RELOC_HI16_S)
11691 bfd_vma contents, mask, field;
11693 contents = bfd_get_bits (fixP->fx_frag->fr_literal
11696 target_big_endian);
11698 /* MASK has bits set where the relocation should go.
11699 FIELD is -value, shifted into the appropriate place
11700 for this relocation. */
11701 mask = 1 << (howto->bitsize - 1);
11702 mask = (((mask - 1) << 1) | 1) << howto->bitpos;
11703 field = (-value >> howto->rightshift) << howto->bitpos;
11705 bfd_put_bits ((field & mask) | (contents & ~mask),
11706 fixP->fx_frag->fr_literal + fixP->fx_where,
11708 target_big_endian);
11714 /* This code was generated using trial and error and so is
11715 fragile and not trustworthy. If you change it, you should
11716 rerun the elf-rel, elf-rel2, and empic testcases and ensure
11717 they still pass. */
11718 if (fixP->fx_pcrel || fixP->fx_subsy != NULL)
11720 value += fixP->fx_frag->fr_address + fixP->fx_where;
11722 /* BFD's REL handling, for MIPS, is _very_ weird.
11723 This gives the right results, but it can't possibly
11724 be the way things are supposed to work. */
11725 if (fixP->fx_r_type != BFD_RELOC_16_PCREL_S2
11726 || S_GET_SEGMENT (fixP->fx_addsy) != undefined_section)
11727 value += fixP->fx_frag->fr_address + fixP->fx_where;
11732 fixP->fx_addnumber = value; /* Remember value for tc_gen_reloc. */
11734 /* We are not done if this is a composite relocation to set up gp. */
11735 if (fixP->fx_addsy == NULL && ! fixP->fx_pcrel
11736 && !(fixP->fx_r_type == BFD_RELOC_MIPS_SUB
11737 || (fixP->fx_r_type == BFD_RELOC_64
11738 && (previous_fx_r_type == BFD_RELOC_GPREL32
11739 || previous_fx_r_type == BFD_RELOC_GPREL16))
11740 || (previous_fx_r_type == BFD_RELOC_MIPS_SUB
11741 && (fixP->fx_r_type == BFD_RELOC_HI16_S
11742 || fixP->fx_r_type == BFD_RELOC_LO16))))
11744 previous_fx_r_type = fixP->fx_r_type;
11746 switch (fixP->fx_r_type)
11748 case BFD_RELOC_MIPS_JMP:
11749 case BFD_RELOC_MIPS_SHIFT5:
11750 case BFD_RELOC_MIPS_SHIFT6:
11751 case BFD_RELOC_MIPS_GOT_DISP:
11752 case BFD_RELOC_MIPS_GOT_PAGE:
11753 case BFD_RELOC_MIPS_GOT_OFST:
11754 case BFD_RELOC_MIPS_SUB:
11755 case BFD_RELOC_MIPS_INSERT_A:
11756 case BFD_RELOC_MIPS_INSERT_B:
11757 case BFD_RELOC_MIPS_DELETE:
11758 case BFD_RELOC_MIPS_HIGHEST:
11759 case BFD_RELOC_MIPS_HIGHER:
11760 case BFD_RELOC_MIPS_SCN_DISP:
11761 case BFD_RELOC_MIPS_REL16:
11762 case BFD_RELOC_MIPS_RELGOT:
11763 case BFD_RELOC_MIPS_JALR:
11764 case BFD_RELOC_HI16:
11765 case BFD_RELOC_HI16_S:
11766 case BFD_RELOC_GPREL16:
11767 case BFD_RELOC_MIPS_LITERAL:
11768 case BFD_RELOC_MIPS_CALL16:
11769 case BFD_RELOC_MIPS_GOT16:
11770 case BFD_RELOC_GPREL32:
11771 case BFD_RELOC_MIPS_GOT_HI16:
11772 case BFD_RELOC_MIPS_GOT_LO16:
11773 case BFD_RELOC_MIPS_CALL_HI16:
11774 case BFD_RELOC_MIPS_CALL_LO16:
11775 case BFD_RELOC_MIPS16_GPREL:
11776 if (fixP->fx_pcrel)
11777 as_bad_where (fixP->fx_file, fixP->fx_line,
11778 _("Invalid PC relative reloc"));
11779 /* Nothing needed to do. The value comes from the reloc entry */
11782 case BFD_RELOC_MIPS16_JMP:
11783 /* We currently always generate a reloc against a symbol, which
11784 means that we don't want an addend even if the symbol is
11786 fixP->fx_addnumber = 0;
11789 case BFD_RELOC_PCREL_HI16_S:
11790 /* The addend for this is tricky if it is internal, so we just
11791 do everything here rather than in bfd_install_relocation. */
11792 if (OUTPUT_FLAVOR == bfd_target_elf_flavour
11797 && (symbol_get_bfdsym (fixP->fx_addsy)->flags & BSF_SECTION_SYM) == 0)
11799 /* For an external symbol adjust by the address to make it
11800 pcrel_offset. We use the address of the RELLO reloc
11801 which follows this one. */
11802 value += (fixP->fx_next->fx_frag->fr_address
11803 + fixP->fx_next->fx_where);
11805 value = ((value + 0x8000) >> 16) & 0xffff;
11806 buf = (bfd_byte *) fixP->fx_frag->fr_literal + fixP->fx_where;
11807 if (target_big_endian)
11809 md_number_to_chars ((char *) buf, value, 2);
11812 case BFD_RELOC_PCREL_LO16:
11813 /* The addend for this is tricky if it is internal, so we just
11814 do everything here rather than in bfd_install_relocation. */
11815 if (OUTPUT_FLAVOR == bfd_target_elf_flavour
11820 && (symbol_get_bfdsym (fixP->fx_addsy)->flags & BSF_SECTION_SYM) == 0)
11821 value += fixP->fx_frag->fr_address + fixP->fx_where;
11822 buf = (bfd_byte *) fixP->fx_frag->fr_literal + fixP->fx_where;
11823 if (target_big_endian)
11825 md_number_to_chars ((char *) buf, value, 2);
11829 /* This is handled like BFD_RELOC_32, but we output a sign
11830 extended value if we are only 32 bits. */
11832 || (mips_pic == EMBEDDED_PIC && SWITCH_TABLE (fixP)))
11834 if (8 <= sizeof (valueT))
11835 md_number_to_chars (fixP->fx_frag->fr_literal + fixP->fx_where,
11842 w1 = w2 = fixP->fx_where;
11843 if (target_big_endian)
11847 md_number_to_chars (fixP->fx_frag->fr_literal + w1, value, 4);
11848 if ((value & 0x80000000) != 0)
11852 md_number_to_chars (fixP->fx_frag->fr_literal + w2, hiv, 4);
11857 case BFD_RELOC_RVA:
11859 /* If we are deleting this reloc entry, we must fill in the
11860 value now. This can happen if we have a .word which is not
11861 resolved when it appears but is later defined. We also need
11862 to fill in the value if this is an embedded PIC switch table
11865 || (mips_pic == EMBEDDED_PIC && SWITCH_TABLE (fixP)))
11866 md_number_to_chars (fixP->fx_frag->fr_literal + fixP->fx_where,
11871 /* If we are deleting this reloc entry, we must fill in the
11873 assert (fixP->fx_size == 2);
11875 md_number_to_chars (fixP->fx_frag->fr_literal + fixP->fx_where,
11879 case BFD_RELOC_LO16:
11880 /* When handling an embedded PIC switch statement, we can wind
11881 up deleting a LO16 reloc. See the 'o' case in mips_ip. */
11884 if (value + 0x8000 > 0xffff)
11885 as_bad_where (fixP->fx_file, fixP->fx_line,
11886 _("relocation overflow"));
11887 buf = (bfd_byte *) fixP->fx_frag->fr_literal + fixP->fx_where;
11888 if (target_big_endian)
11890 md_number_to_chars ((char *) buf, value, 2);
11894 case BFD_RELOC_16_PCREL_S2:
11895 if ((value & 0x3) != 0)
11896 as_bad_where (fixP->fx_file, fixP->fx_line,
11897 _("Branch to odd address (%lx)"), (long) value);
11900 * We need to save the bits in the instruction since fixup_segment()
11901 * might be deleting the relocation entry (i.e., a branch within
11902 * the current segment).
11904 if (!fixP->fx_done && (value != 0 || HAVE_NEWABI))
11906 /* If 'value' is zero, the remaining reloc code won't actually
11907 do the store, so it must be done here. This is probably
11908 a bug somewhere. */
11910 && (fixP->fx_r_type != BFD_RELOC_16_PCREL_S2
11911 || fixP->fx_addsy == NULL /* ??? */
11912 || ! S_IS_DEFINED (fixP->fx_addsy)))
11913 value -= fixP->fx_frag->fr_address + fixP->fx_where;
11915 value = (offsetT) value >> 2;
11917 /* update old instruction data */
11918 buf = (bfd_byte *) (fixP->fx_where + fixP->fx_frag->fr_literal);
11919 if (target_big_endian)
11920 insn = (buf[0] << 24) | (buf[1] << 16) | (buf[2] << 8) | buf[3];
11922 insn = (buf[3] << 24) | (buf[2] << 16) | (buf[1] << 8) | buf[0];
11924 if (value + 0x8000 <= 0xffff)
11925 insn |= value & 0xffff;
11928 /* The branch offset is too large. If this is an
11929 unconditional branch, and we are not generating PIC code,
11930 we can convert it to an absolute jump instruction. */
11931 if (mips_pic == NO_PIC
11933 && fixP->fx_frag->fr_address >= text_section->vma
11934 && (fixP->fx_frag->fr_address
11935 < text_section->vma + text_section->_raw_size)
11936 && ((insn & 0xffff0000) == 0x10000000 /* beq $0,$0 */
11937 || (insn & 0xffff0000) == 0x04010000 /* bgez $0 */
11938 || (insn & 0xffff0000) == 0x04110000)) /* bgezal $0 */
11940 if ((insn & 0xffff0000) == 0x04110000) /* bgezal $0 */
11941 insn = 0x0c000000; /* jal */
11943 insn = 0x08000000; /* j */
11944 fixP->fx_r_type = BFD_RELOC_MIPS_JMP;
11946 fixP->fx_addsy = section_symbol (text_section);
11947 fixP->fx_addnumber = (value << 2) + md_pcrel_from (fixP);
11951 /* If we got here, we have branch-relaxation disabled,
11952 and there's nothing we can do to fix this instruction
11953 without turning it into a longer sequence. */
11954 as_bad_where (fixP->fx_file, fixP->fx_line,
11955 _("Branch out of range"));
11959 md_number_to_chars ((char *) buf, (valueT) insn, 4);
11962 case BFD_RELOC_VTABLE_INHERIT:
11965 && !S_IS_DEFINED (fixP->fx_addsy)
11966 && !S_IS_WEAK (fixP->fx_addsy))
11967 S_SET_WEAK (fixP->fx_addsy);
11970 case BFD_RELOC_VTABLE_ENTRY:
11984 const struct mips_opcode *p;
11985 int treg, sreg, dreg, shamt;
11990 for (i = 0; i < NUMOPCODES; ++i)
11992 p = &mips_opcodes[i];
11993 if (((oc & p->mask) == p->match) && (p->pinfo != INSN_MACRO))
11995 printf ("%08lx %s\t", oc, p->name);
11996 treg = (oc >> 16) & 0x1f;
11997 sreg = (oc >> 21) & 0x1f;
11998 dreg = (oc >> 11) & 0x1f;
11999 shamt = (oc >> 6) & 0x1f;
12001 for (args = p->args;; ++args)
12012 printf ("%c", *args);
12016 assert (treg == sreg);
12017 printf ("$%d,$%d", treg, sreg);
12022 printf ("$%d", dreg);
12027 printf ("$%d", treg);
12031 printf ("0x%x", treg);
12036 printf ("$%d", sreg);
12040 printf ("0x%08lx", oc & 0x1ffffff);
12047 printf ("%d", imm);
12052 printf ("$%d", shamt);
12063 printf (_("%08lx UNDEFINED\n"), oc);
12074 name = input_line_pointer;
12075 c = get_symbol_end ();
12076 p = (symbolS *) symbol_find_or_make (name);
12077 *input_line_pointer = c;
12081 /* Align the current frag to a given power of two. The MIPS assembler
12082 also automatically adjusts any preceding label. */
12085 mips_align (to, fill, label)
12090 mips_emit_delays (FALSE);
12091 frag_align (to, fill, 0);
12092 record_alignment (now_seg, to);
12095 assert (S_GET_SEGMENT (label) == now_seg);
12096 symbol_set_frag (label, frag_now);
12097 S_SET_VALUE (label, (valueT) frag_now_fix ());
12101 /* Align to a given power of two. .align 0 turns off the automatic
12102 alignment used by the data creating pseudo-ops. */
12106 int x ATTRIBUTE_UNUSED;
12109 register long temp_fill;
12110 long max_alignment = 15;
12114 o Note that the assembler pulls down any immediately preceeding label
12115 to the aligned address.
12116 o It's not documented but auto alignment is reinstated by
12117 a .align pseudo instruction.
12118 o Note also that after auto alignment is turned off the mips assembler
12119 issues an error on attempt to assemble an improperly aligned data item.
12124 temp = get_absolute_expression ();
12125 if (temp > max_alignment)
12126 as_bad (_("Alignment too large: %d. assumed."), temp = max_alignment);
12129 as_warn (_("Alignment negative: 0 assumed."));
12132 if (*input_line_pointer == ',')
12134 ++input_line_pointer;
12135 temp_fill = get_absolute_expression ();
12142 mips_align (temp, (int) temp_fill,
12143 insn_labels != NULL ? insn_labels->label : NULL);
12150 demand_empty_rest_of_line ();
12154 mips_flush_pending_output ()
12156 mips_emit_delays (FALSE);
12157 mips_clear_insn_labels ();
12166 /* When generating embedded PIC code, we only use the .text, .lit8,
12167 .sdata and .sbss sections. We change the .data and .rdata
12168 pseudo-ops to use .sdata. */
12169 if (mips_pic == EMBEDDED_PIC
12170 && (sec == 'd' || sec == 'r'))
12174 /* The ELF backend needs to know that we are changing sections, so
12175 that .previous works correctly. We could do something like check
12176 for an obj_section_change_hook macro, but that might be confusing
12177 as it would not be appropriate to use it in the section changing
12178 functions in read.c, since obj-elf.c intercepts those. FIXME:
12179 This should be cleaner, somehow. */
12180 obj_elf_section_change_hook ();
12183 mips_emit_delays (FALSE);
12193 subseg_set (bss_section, (subsegT) get_absolute_expression ());
12194 demand_empty_rest_of_line ();
12198 if (USE_GLOBAL_POINTER_OPT)
12200 seg = subseg_new (RDATA_SECTION_NAME,
12201 (subsegT) get_absolute_expression ());
12202 if (OUTPUT_FLAVOR == bfd_target_elf_flavour)
12204 bfd_set_section_flags (stdoutput, seg,
12210 if (strcmp (TARGET_OS, "elf") != 0)
12211 record_alignment (seg, 4);
12213 demand_empty_rest_of_line ();
12217 as_bad (_("No read only data section in this object file format"));
12218 demand_empty_rest_of_line ();
12224 if (USE_GLOBAL_POINTER_OPT)
12226 seg = subseg_new (".sdata", (subsegT) get_absolute_expression ());
12227 if (OUTPUT_FLAVOR == bfd_target_elf_flavour)
12229 bfd_set_section_flags (stdoutput, seg,
12230 SEC_ALLOC | SEC_LOAD | SEC_RELOC
12232 if (strcmp (TARGET_OS, "elf") != 0)
12233 record_alignment (seg, 4);
12235 demand_empty_rest_of_line ();
12240 as_bad (_("Global pointers not supported; recompile -G 0"));
12241 demand_empty_rest_of_line ();
12250 s_change_section (ignore)
12251 int ignore ATTRIBUTE_UNUSED;
12254 char *section_name;
12259 int section_entry_size;
12260 int section_alignment;
12262 if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
12265 section_name = input_line_pointer;
12266 c = get_symbol_end ();
12268 next_c = *(input_line_pointer + 1);
12270 /* Do we have .section Name<,"flags">? */
12271 if (c != ',' || (c == ',' && next_c == '"'))
12273 /* just after name is now '\0'. */
12274 *input_line_pointer = c;
12275 input_line_pointer = section_name;
12276 obj_elf_section (ignore);
12279 input_line_pointer++;
12281 /* Do we have .section Name<,type><,flag><,entry_size><,alignment> */
12283 section_type = get_absolute_expression ();
12286 if (*input_line_pointer++ == ',')
12287 section_flag = get_absolute_expression ();
12290 if (*input_line_pointer++ == ',')
12291 section_entry_size = get_absolute_expression ();
12293 section_entry_size = 0;
12294 if (*input_line_pointer++ == ',')
12295 section_alignment = get_absolute_expression ();
12297 section_alignment = 0;
12299 section_name = xstrdup (section_name);
12301 obj_elf_change_section (section_name, section_type, section_flag,
12302 section_entry_size, 0, 0, 0);
12304 if (now_seg->name != section_name)
12305 free (section_name);
12306 #endif /* OBJ_ELF */
12310 mips_enable_auto_align ()
12321 label = insn_labels != NULL ? insn_labels->label : NULL;
12322 mips_emit_delays (FALSE);
12323 if (log_size > 0 && auto_align)
12324 mips_align (log_size, 0, label);
12325 mips_clear_insn_labels ();
12326 cons (1 << log_size);
12330 s_float_cons (type)
12335 label = insn_labels != NULL ? insn_labels->label : NULL;
12337 mips_emit_delays (FALSE);
12342 mips_align (3, 0, label);
12344 mips_align (2, 0, label);
12347 mips_clear_insn_labels ();
12352 /* Handle .globl. We need to override it because on Irix 5 you are
12355 where foo is an undefined symbol, to mean that foo should be
12356 considered to be the address of a function. */
12360 int x ATTRIBUTE_UNUSED;
12367 name = input_line_pointer;
12368 c = get_symbol_end ();
12369 symbolP = symbol_find_or_make (name);
12370 *input_line_pointer = c;
12371 SKIP_WHITESPACE ();
12373 /* On Irix 5, every global symbol that is not explicitly labelled as
12374 being a function is apparently labelled as being an object. */
12377 if (! is_end_of_line[(unsigned char) *input_line_pointer])
12382 secname = input_line_pointer;
12383 c = get_symbol_end ();
12384 sec = bfd_get_section_by_name (stdoutput, secname);
12386 as_bad (_("%s: no such section"), secname);
12387 *input_line_pointer = c;
12389 if (sec != NULL && (sec->flags & SEC_CODE) != 0)
12390 flag = BSF_FUNCTION;
12393 symbol_get_bfdsym (symbolP)->flags |= flag;
12395 S_SET_EXTERNAL (symbolP);
12396 demand_empty_rest_of_line ();
12401 int x ATTRIBUTE_UNUSED;
12406 opt = input_line_pointer;
12407 c = get_symbol_end ();
12411 /* FIXME: What does this mean? */
12413 else if (strncmp (opt, "pic", 3) == 0)
12417 i = atoi (opt + 3);
12421 mips_pic = SVR4_PIC;
12423 as_bad (_(".option pic%d not supported"), i);
12425 if (USE_GLOBAL_POINTER_OPT && mips_pic == SVR4_PIC)
12427 if (g_switch_seen && g_switch_value != 0)
12428 as_warn (_("-G may not be used with SVR4 PIC code"));
12429 g_switch_value = 0;
12430 bfd_set_gp_size (stdoutput, 0);
12434 as_warn (_("Unrecognized option \"%s\""), opt);
12436 *input_line_pointer = c;
12437 demand_empty_rest_of_line ();
12440 /* This structure is used to hold a stack of .set values. */
12442 struct mips_option_stack
12444 struct mips_option_stack *next;
12445 struct mips_set_options options;
12448 static struct mips_option_stack *mips_opts_stack;
12450 /* Handle the .set pseudo-op. */
12454 int x ATTRIBUTE_UNUSED;
12456 char *name = input_line_pointer, ch;
12458 while (!is_end_of_line[(unsigned char) *input_line_pointer])
12459 ++input_line_pointer;
12460 ch = *input_line_pointer;
12461 *input_line_pointer = '\0';
12463 if (strcmp (name, "reorder") == 0)
12465 if (mips_opts.noreorder && prev_nop_frag != NULL)
12467 /* If we still have pending nops, we can discard them. The
12468 usual nop handling will insert any that are still
12470 prev_nop_frag->fr_fix -= (prev_nop_frag_holds
12471 * (mips_opts.mips16 ? 2 : 4));
12472 prev_nop_frag = NULL;
12474 mips_opts.noreorder = 0;
12476 else if (strcmp (name, "noreorder") == 0)
12478 mips_emit_delays (TRUE);
12479 mips_opts.noreorder = 1;
12480 mips_any_noreorder = 1;
12482 else if (strcmp (name, "at") == 0)
12484 mips_opts.noat = 0;
12486 else if (strcmp (name, "noat") == 0)
12488 mips_opts.noat = 1;
12490 else if (strcmp (name, "macro") == 0)
12492 mips_opts.warn_about_macros = 0;
12494 else if (strcmp (name, "nomacro") == 0)
12496 if (mips_opts.noreorder == 0)
12497 as_bad (_("`noreorder' must be set before `nomacro'"));
12498 mips_opts.warn_about_macros = 1;
12500 else if (strcmp (name, "move") == 0 || strcmp (name, "novolatile") == 0)
12502 mips_opts.nomove = 0;
12504 else if (strcmp (name, "nomove") == 0 || strcmp (name, "volatile") == 0)
12506 mips_opts.nomove = 1;
12508 else if (strcmp (name, "bopt") == 0)
12510 mips_opts.nobopt = 0;
12512 else if (strcmp (name, "nobopt") == 0)
12514 mips_opts.nobopt = 1;
12516 else if (strcmp (name, "mips16") == 0
12517 || strcmp (name, "MIPS-16") == 0)
12518 mips_opts.mips16 = 1;
12519 else if (strcmp (name, "nomips16") == 0
12520 || strcmp (name, "noMIPS-16") == 0)
12521 mips_opts.mips16 = 0;
12522 else if (strcmp (name, "mips3d") == 0)
12523 mips_opts.ase_mips3d = 1;
12524 else if (strcmp (name, "nomips3d") == 0)
12525 mips_opts.ase_mips3d = 0;
12526 else if (strcmp (name, "mdmx") == 0)
12527 mips_opts.ase_mdmx = 1;
12528 else if (strcmp (name, "nomdmx") == 0)
12529 mips_opts.ase_mdmx = 0;
12530 else if (strncmp (name, "mips", 4) == 0)
12534 /* Permit the user to change the ISA on the fly. Needless to
12535 say, misuse can cause serious problems. */
12536 if (strcmp (name, "mips0") == 0)
12539 mips_opts.isa = file_mips_isa;
12541 else if (strcmp (name, "mips1") == 0)
12542 mips_opts.isa = ISA_MIPS1;
12543 else if (strcmp (name, "mips2") == 0)
12544 mips_opts.isa = ISA_MIPS2;
12545 else if (strcmp (name, "mips3") == 0)
12546 mips_opts.isa = ISA_MIPS3;
12547 else if (strcmp (name, "mips4") == 0)
12548 mips_opts.isa = ISA_MIPS4;
12549 else if (strcmp (name, "mips5") == 0)
12550 mips_opts.isa = ISA_MIPS5;
12551 else if (strcmp (name, "mips32") == 0)
12552 mips_opts.isa = ISA_MIPS32;
12553 else if (strcmp (name, "mips32r2") == 0)
12554 mips_opts.isa = ISA_MIPS32R2;
12555 else if (strcmp (name, "mips64") == 0)
12556 mips_opts.isa = ISA_MIPS64;
12558 as_bad (_("unknown ISA level %s"), name + 4);
12560 switch (mips_opts.isa)
12568 mips_opts.gp32 = 1;
12569 mips_opts.fp32 = 1;
12575 mips_opts.gp32 = 0;
12576 mips_opts.fp32 = 0;
12579 as_bad (_("unknown ISA level %s"), name + 4);
12584 mips_opts.gp32 = file_mips_gp32;
12585 mips_opts.fp32 = file_mips_fp32;
12588 else if (strcmp (name, "autoextend") == 0)
12589 mips_opts.noautoextend = 0;
12590 else if (strcmp (name, "noautoextend") == 0)
12591 mips_opts.noautoextend = 1;
12592 else if (strcmp (name, "push") == 0)
12594 struct mips_option_stack *s;
12596 s = (struct mips_option_stack *) xmalloc (sizeof *s);
12597 s->next = mips_opts_stack;
12598 s->options = mips_opts;
12599 mips_opts_stack = s;
12601 else if (strcmp (name, "pop") == 0)
12603 struct mips_option_stack *s;
12605 s = mips_opts_stack;
12607 as_bad (_(".set pop with no .set push"));
12610 /* If we're changing the reorder mode we need to handle
12611 delay slots correctly. */
12612 if (s->options.noreorder && ! mips_opts.noreorder)
12613 mips_emit_delays (TRUE);
12614 else if (! s->options.noreorder && mips_opts.noreorder)
12616 if (prev_nop_frag != NULL)
12618 prev_nop_frag->fr_fix -= (prev_nop_frag_holds
12619 * (mips_opts.mips16 ? 2 : 4));
12620 prev_nop_frag = NULL;
12624 mips_opts = s->options;
12625 mips_opts_stack = s->next;
12631 as_warn (_("Tried to set unrecognized symbol: %s\n"), name);
12633 *input_line_pointer = ch;
12634 demand_empty_rest_of_line ();
12637 /* Handle the .abicalls pseudo-op. I believe this is equivalent to
12638 .option pic2. It means to generate SVR4 PIC calls. */
12641 s_abicalls (ignore)
12642 int ignore ATTRIBUTE_UNUSED;
12644 mips_pic = SVR4_PIC;
12645 if (USE_GLOBAL_POINTER_OPT)
12647 if (g_switch_seen && g_switch_value != 0)
12648 as_warn (_("-G may not be used with SVR4 PIC code"));
12649 g_switch_value = 0;
12651 bfd_set_gp_size (stdoutput, 0);
12652 demand_empty_rest_of_line ();
12655 /* Handle the .cpload pseudo-op. This is used when generating SVR4
12656 PIC code. It sets the $gp register for the function based on the
12657 function address, which is in the register named in the argument.
12658 This uses a relocation against _gp_disp, which is handled specially
12659 by the linker. The result is:
12660 lui $gp,%hi(_gp_disp)
12661 addiu $gp,$gp,%lo(_gp_disp)
12662 addu $gp,$gp,.cpload argument
12663 The .cpload argument is normally $25 == $t9. */
12667 int ignore ATTRIBUTE_UNUSED;
12672 /* If we are not generating SVR4 PIC code, or if this is NewABI code,
12673 .cpload is ignored. */
12674 if (mips_pic != SVR4_PIC || HAVE_NEWABI)
12680 /* .cpload should be in a .set noreorder section. */
12681 if (mips_opts.noreorder == 0)
12682 as_warn (_(".cpload not in noreorder section"));
12684 ex.X_op = O_symbol;
12685 ex.X_add_symbol = symbol_find_or_make ("_gp_disp");
12686 ex.X_op_symbol = NULL;
12687 ex.X_add_number = 0;
12689 /* In ELF, this symbol is implicitly an STT_OBJECT symbol. */
12690 symbol_get_bfdsym (ex.X_add_symbol)->flags |= BSF_OBJECT;
12692 macro_build_lui (NULL, &icnt, &ex, mips_gp_register);
12693 macro_build ((char *) NULL, &icnt, &ex, "addiu", "t,r,j",
12694 mips_gp_register, mips_gp_register, (int) BFD_RELOC_LO16);
12696 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "addu", "d,v,t",
12697 mips_gp_register, mips_gp_register, tc_get_register (0));
12699 demand_empty_rest_of_line ();
12702 /* Handle the .cpsetup pseudo-op defined for NewABI PIC code. The syntax is:
12703 .cpsetup $reg1, offset|$reg2, label
12705 If offset is given, this results in:
12706 sd $gp, offset($sp)
12707 lui $gp, %hi(%neg(%gp_rel(label)))
12708 addiu $gp, $gp, %lo(%neg(%gp_rel(label)))
12709 daddu $gp, $gp, $reg1
12711 If $reg2 is given, this results in:
12712 daddu $reg2, $gp, $0
12713 lui $gp, %hi(%neg(%gp_rel(label)))
12714 addiu $gp, $gp, %lo(%neg(%gp_rel(label)))
12715 daddu $gp, $gp, $reg1
12716 $reg1 is normally $25 == $t9. */
12719 int ignore ATTRIBUTE_UNUSED;
12721 expressionS ex_off;
12722 expressionS ex_sym;
12727 /* If we are not generating SVR4 PIC code, .cpsetup is ignored.
12728 We also need NewABI support. */
12729 if (mips_pic != SVR4_PIC || ! HAVE_NEWABI)
12735 reg1 = tc_get_register (0);
12736 SKIP_WHITESPACE ();
12737 if (*input_line_pointer != ',')
12739 as_bad (_("missing argument separator ',' for .cpsetup"));
12743 ++input_line_pointer;
12744 SKIP_WHITESPACE ();
12745 if (*input_line_pointer == '$')
12747 mips_cpreturn_register = tc_get_register (0);
12748 mips_cpreturn_offset = -1;
12752 mips_cpreturn_offset = get_absolute_expression ();
12753 mips_cpreturn_register = -1;
12755 SKIP_WHITESPACE ();
12756 if (*input_line_pointer != ',')
12758 as_bad (_("missing argument separator ',' for .cpsetup"));
12762 ++input_line_pointer;
12763 SKIP_WHITESPACE ();
12764 expression (&ex_sym);
12766 if (mips_cpreturn_register == -1)
12768 ex_off.X_op = O_constant;
12769 ex_off.X_add_symbol = NULL;
12770 ex_off.X_op_symbol = NULL;
12771 ex_off.X_add_number = mips_cpreturn_offset;
12773 macro_build ((char *) NULL, &icnt, &ex_off, "sd", "t,o(b)",
12774 mips_gp_register, (int) BFD_RELOC_LO16, SP);
12777 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "daddu",
12778 "d,v,t", mips_cpreturn_register, mips_gp_register, 0);
12780 /* Ensure there's room for the next two instructions, so that `f'
12781 doesn't end up with an address in the wrong frag. */
12784 macro_build ((char *) NULL, &icnt, &ex_sym, "lui", "t,u", mips_gp_register,
12785 (int) BFD_RELOC_GPREL16);
12786 fix_new (frag_now, f - frag_now->fr_literal,
12787 0, NULL, 0, 0, BFD_RELOC_MIPS_SUB);
12788 fix_new (frag_now, f - frag_now->fr_literal,
12789 0, NULL, 0, 0, BFD_RELOC_HI16_S);
12792 macro_build ((char *) NULL, &icnt, &ex_sym, "addiu", "t,r,j",
12793 mips_gp_register, mips_gp_register, (int) BFD_RELOC_GPREL16);
12794 fix_new (frag_now, f - frag_now->fr_literal,
12795 0, NULL, 0, 0, BFD_RELOC_MIPS_SUB);
12796 fix_new (frag_now, f - frag_now->fr_literal,
12797 0, NULL, 0, 0, BFD_RELOC_LO16);
12799 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
12800 HAVE_64BIT_ADDRESSES ? "daddu" : "add", "d,v,t",
12801 mips_gp_register, mips_gp_register, reg1);
12803 demand_empty_rest_of_line ();
12808 int ignore ATTRIBUTE_UNUSED;
12810 /* If we are not generating SVR4 PIC code, or if this is not NewABI code,
12811 .cplocal is ignored. */
12812 if (mips_pic != SVR4_PIC || ! HAVE_NEWABI)
12818 mips_gp_register = tc_get_register (0);
12819 demand_empty_rest_of_line ();
12822 /* Handle the .cprestore pseudo-op. This stores $gp into a given
12823 offset from $sp. The offset is remembered, and after making a PIC
12824 call $gp is restored from that location. */
12827 s_cprestore (ignore)
12828 int ignore ATTRIBUTE_UNUSED;
12833 /* If we are not generating SVR4 PIC code, or if this is NewABI code,
12834 .cprestore is ignored. */
12835 if (mips_pic != SVR4_PIC || HAVE_NEWABI)
12841 mips_cprestore_offset = get_absolute_expression ();
12842 mips_cprestore_valid = 1;
12844 ex.X_op = O_constant;
12845 ex.X_add_symbol = NULL;
12846 ex.X_op_symbol = NULL;
12847 ex.X_add_number = mips_cprestore_offset;
12849 macro_build_ldst_constoffset ((char *) NULL, &icnt, &ex,
12850 HAVE_32BIT_ADDRESSES ? "sw" : "sd",
12851 mips_gp_register, SP);
12853 demand_empty_rest_of_line ();
12856 /* Handle the .cpreturn pseudo-op defined for NewABI PIC code. If an offset
12857 was given in the preceeding .gpsetup, it results in:
12858 ld $gp, offset($sp)
12860 If a register $reg2 was given there, it results in:
12861 daddiu $gp, $gp, $reg2
12864 s_cpreturn (ignore)
12865 int ignore ATTRIBUTE_UNUSED;
12870 /* If we are not generating SVR4 PIC code, .cpreturn is ignored.
12871 We also need NewABI support. */
12872 if (mips_pic != SVR4_PIC || ! HAVE_NEWABI)
12878 if (mips_cpreturn_register == -1)
12880 ex.X_op = O_constant;
12881 ex.X_add_symbol = NULL;
12882 ex.X_op_symbol = NULL;
12883 ex.X_add_number = mips_cpreturn_offset;
12885 macro_build ((char *) NULL, &icnt, &ex, "ld", "t,o(b)",
12886 mips_gp_register, (int) BFD_RELOC_LO16, SP);
12889 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "daddu",
12890 "d,v,t", mips_gp_register, mips_cpreturn_register, 0);
12892 demand_empty_rest_of_line ();
12895 /* Handle the .gpvalue pseudo-op. This is used when generating NewABI PIC
12896 code. It sets the offset to use in gp_rel relocations. */
12900 int ignore ATTRIBUTE_UNUSED;
12902 /* If we are not generating SVR4 PIC code, .gpvalue is ignored.
12903 We also need NewABI support. */
12904 if (mips_pic != SVR4_PIC || ! HAVE_NEWABI)
12910 mips_gprel_offset = get_absolute_expression ();
12912 demand_empty_rest_of_line ();
12915 /* Handle the .gpword pseudo-op. This is used when generating PIC
12916 code. It generates a 32 bit GP relative reloc. */
12920 int ignore ATTRIBUTE_UNUSED;
12926 /* When not generating PIC code, this is treated as .word. */
12927 if (mips_pic != SVR4_PIC)
12933 label = insn_labels != NULL ? insn_labels->label : NULL;
12934 mips_emit_delays (TRUE);
12936 mips_align (2, 0, label);
12937 mips_clear_insn_labels ();
12941 if (ex.X_op != O_symbol || ex.X_add_number != 0)
12943 as_bad (_("Unsupported use of .gpword"));
12944 ignore_rest_of_line ();
12948 md_number_to_chars (p, (valueT) 0, 4);
12949 fix_new_exp (frag_now, p - frag_now->fr_literal, 4, &ex, FALSE,
12950 BFD_RELOC_GPREL32);
12952 demand_empty_rest_of_line ();
12957 int ignore ATTRIBUTE_UNUSED;
12963 /* When not generating PIC code, this is treated as .dword. */
12964 if (mips_pic != SVR4_PIC)
12970 label = insn_labels != NULL ? insn_labels->label : NULL;
12971 mips_emit_delays (TRUE);
12973 mips_align (3, 0, label);
12974 mips_clear_insn_labels ();
12978 if (ex.X_op != O_symbol || ex.X_add_number != 0)
12980 as_bad (_("Unsupported use of .gpdword"));
12981 ignore_rest_of_line ();
12985 md_number_to_chars (p, (valueT) 0, 8);
12986 fix_new_exp (frag_now, p - frag_now->fr_literal, 8, &ex, FALSE,
12987 BFD_RELOC_GPREL32);
12989 /* GPREL32 composed with 64 gives a 64-bit GP offset. */
12990 ex.X_op = O_absent;
12991 ex.X_add_symbol = 0;
12992 ex.X_add_number = 0;
12993 fix_new_exp (frag_now, p - frag_now->fr_literal, 8, &ex, FALSE,
12996 demand_empty_rest_of_line ();
12999 /* Handle the .cpadd pseudo-op. This is used when dealing with switch
13000 tables in SVR4 PIC code. */
13004 int ignore ATTRIBUTE_UNUSED;
13009 /* This is ignored when not generating SVR4 PIC code. */
13010 if (mips_pic != SVR4_PIC)
13016 /* Add $gp to the register named as an argument. */
13017 reg = tc_get_register (0);
13018 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
13019 HAVE_32BIT_ADDRESSES ? HAVE_NEWABI ? "add" : "addu" : "daddu",
13020 "d,v,t", reg, reg, mips_gp_register);
13022 demand_empty_rest_of_line ();
13025 /* Handle the .insn pseudo-op. This marks instruction labels in
13026 mips16 mode. This permits the linker to handle them specially,
13027 such as generating jalx instructions when needed. We also make
13028 them odd for the duration of the assembly, in order to generate the
13029 right sort of code. We will make them even in the adjust_symtab
13030 routine, while leaving them marked. This is convenient for the
13031 debugger and the disassembler. The linker knows to make them odd
13036 int ignore ATTRIBUTE_UNUSED;
13038 mips16_mark_labels ();
13040 demand_empty_rest_of_line ();
13043 /* Handle a .stabn directive. We need these in order to mark a label
13044 as being a mips16 text label correctly. Sometimes the compiler
13045 will emit a label, followed by a .stabn, and then switch sections.
13046 If the label and .stabn are in mips16 mode, then the label is
13047 really a mips16 text label. */
13054 mips16_mark_labels ();
13059 /* Handle the .weakext pseudo-op as defined in Kane and Heinrich.
13063 s_mips_weakext (ignore)
13064 int ignore ATTRIBUTE_UNUSED;
13071 name = input_line_pointer;
13072 c = get_symbol_end ();
13073 symbolP = symbol_find_or_make (name);
13074 S_SET_WEAK (symbolP);
13075 *input_line_pointer = c;
13077 SKIP_WHITESPACE ();
13079 if (! is_end_of_line[(unsigned char) *input_line_pointer])
13081 if (S_IS_DEFINED (symbolP))
13083 as_bad ("ignoring attempt to redefine symbol %s",
13084 S_GET_NAME (symbolP));
13085 ignore_rest_of_line ();
13089 if (*input_line_pointer == ',')
13091 ++input_line_pointer;
13092 SKIP_WHITESPACE ();
13096 if (exp.X_op != O_symbol)
13098 as_bad ("bad .weakext directive");
13099 ignore_rest_of_line ();
13102 symbol_set_value_expression (symbolP, &exp);
13105 demand_empty_rest_of_line ();
13108 /* Parse a register string into a number. Called from the ECOFF code
13109 to parse .frame. The argument is non-zero if this is the frame
13110 register, so that we can record it in mips_frame_reg. */
13113 tc_get_register (frame)
13118 SKIP_WHITESPACE ();
13119 if (*input_line_pointer++ != '$')
13121 as_warn (_("expected `$'"));
13124 else if (ISDIGIT (*input_line_pointer))
13126 reg = get_absolute_expression ();
13127 if (reg < 0 || reg >= 32)
13129 as_warn (_("Bad register number"));
13135 if (strncmp (input_line_pointer, "ra", 2) == 0)
13138 input_line_pointer += 2;
13140 else if (strncmp (input_line_pointer, "fp", 2) == 0)
13143 input_line_pointer += 2;
13145 else if (strncmp (input_line_pointer, "sp", 2) == 0)
13148 input_line_pointer += 2;
13150 else if (strncmp (input_line_pointer, "gp", 2) == 0)
13153 input_line_pointer += 2;
13155 else if (strncmp (input_line_pointer, "at", 2) == 0)
13158 input_line_pointer += 2;
13160 else if (strncmp (input_line_pointer, "kt0", 3) == 0)
13163 input_line_pointer += 3;
13165 else if (strncmp (input_line_pointer, "kt1", 3) == 0)
13168 input_line_pointer += 3;
13170 else if (strncmp (input_line_pointer, "zero", 4) == 0)
13173 input_line_pointer += 4;
13177 as_warn (_("Unrecognized register name"));
13179 while (ISALNUM(*input_line_pointer))
13180 input_line_pointer++;
13185 mips_frame_reg = reg != 0 ? reg : SP;
13186 mips_frame_reg_valid = 1;
13187 mips_cprestore_valid = 0;
13193 md_section_align (seg, addr)
13197 int align = bfd_get_section_alignment (stdoutput, seg);
13200 /* We don't need to align ELF sections to the full alignment.
13201 However, Irix 5 may prefer that we align them at least to a 16
13202 byte boundary. We don't bother to align the sections if we are
13203 targeted for an embedded system. */
13204 if (strcmp (TARGET_OS, "elf") == 0)
13210 return ((addr + (1 << align) - 1) & (-1 << align));
13213 /* Utility routine, called from above as well. If called while the
13214 input file is still being read, it's only an approximation. (For
13215 example, a symbol may later become defined which appeared to be
13216 undefined earlier.) */
13219 nopic_need_relax (sym, before_relaxing)
13221 int before_relaxing;
13226 if (USE_GLOBAL_POINTER_OPT && g_switch_value > 0)
13228 const char *symname;
13231 /* Find out whether this symbol can be referenced off the $gp
13232 register. It can be if it is smaller than the -G size or if
13233 it is in the .sdata or .sbss section. Certain symbols can
13234 not be referenced off the $gp, although it appears as though
13236 symname = S_GET_NAME (sym);
13237 if (symname != (const char *) NULL
13238 && (strcmp (symname, "eprol") == 0
13239 || strcmp (symname, "etext") == 0
13240 || strcmp (symname, "_gp") == 0
13241 || strcmp (symname, "edata") == 0
13242 || strcmp (symname, "_fbss") == 0
13243 || strcmp (symname, "_fdata") == 0
13244 || strcmp (symname, "_ftext") == 0
13245 || strcmp (symname, "end") == 0
13246 || strcmp (symname, "_gp_disp") == 0))
13248 else if ((! S_IS_DEFINED (sym) || S_IS_COMMON (sym))
13249 && !S_IS_EXTERN (sym)
13251 #ifndef NO_ECOFF_DEBUGGING
13252 || (symbol_get_obj (sym)->ecoff_extern_size != 0
13253 && (symbol_get_obj (sym)->ecoff_extern_size
13254 <= g_switch_value))
13256 /* We must defer this decision until after the whole
13257 file has been read, since there might be a .extern
13258 after the first use of this symbol. */
13259 || (before_relaxing
13260 #ifndef NO_ECOFF_DEBUGGING
13261 && symbol_get_obj (sym)->ecoff_extern_size == 0
13263 && S_GET_VALUE (sym) == 0)
13264 || (S_GET_VALUE (sym) != 0
13265 && S_GET_VALUE (sym) <= g_switch_value)))
13269 const char *segname;
13271 segname = segment_name (S_GET_SEGMENT (sym));
13272 assert (strcmp (segname, ".lit8") != 0
13273 && strcmp (segname, ".lit4") != 0);
13274 change = (strcmp (segname, ".sdata") != 0
13275 && strcmp (segname, ".sbss") != 0
13276 && strncmp (segname, ".sdata.", 7) != 0
13277 && strncmp (segname, ".gnu.linkonce.s.", 16) != 0);
13282 /* We are not optimizing for the $gp register. */
13287 /* Return true if the given symbol should be considered local for SVR4 PIC. */
13290 pic_need_relax (sym, segtype)
13295 bfd_boolean linkonce;
13297 /* Handle the case of a symbol equated to another symbol. */
13298 while (symbol_equated_reloc_p (sym))
13302 /* It's possible to get a loop here in a badly written
13304 n = symbol_get_value_expression (sym)->X_add_symbol;
13310 symsec = S_GET_SEGMENT (sym);
13312 /* duplicate the test for LINK_ONCE sections as in adjust_reloc_syms */
13314 if (symsec != segtype && ! S_IS_LOCAL (sym))
13316 if ((bfd_get_section_flags (stdoutput, symsec) & SEC_LINK_ONCE)
13320 /* The GNU toolchain uses an extension for ELF: a section
13321 beginning with the magic string .gnu.linkonce is a linkonce
13323 if (strncmp (segment_name (symsec), ".gnu.linkonce",
13324 sizeof ".gnu.linkonce" - 1) == 0)
13328 /* This must duplicate the test in adjust_reloc_syms. */
13329 return (symsec != &bfd_und_section
13330 && symsec != &bfd_abs_section
13331 && ! bfd_is_com_section (symsec)
13334 /* A global or weak symbol is treated as external. */
13335 && (OUTPUT_FLAVOR != bfd_target_elf_flavour
13336 || (! S_IS_WEAK (sym)
13337 && (! S_IS_EXTERNAL (sym)
13338 || mips_pic == EMBEDDED_PIC)))
13344 /* Given a mips16 variant frag FRAGP, return non-zero if it needs an
13345 extended opcode. SEC is the section the frag is in. */
13348 mips16_extended_frag (fragp, sec, stretch)
13354 register const struct mips16_immed_operand *op;
13356 int mintiny, maxtiny;
13360 if (RELAX_MIPS16_USER_SMALL (fragp->fr_subtype))
13362 if (RELAX_MIPS16_USER_EXT (fragp->fr_subtype))
13365 type = RELAX_MIPS16_TYPE (fragp->fr_subtype);
13366 op = mips16_immed_operands;
13367 while (op->type != type)
13370 assert (op < mips16_immed_operands + MIPS16_NUM_IMMED);
13375 if (type == '<' || type == '>' || type == '[' || type == ']')
13378 maxtiny = 1 << op->nbits;
13383 maxtiny = (1 << op->nbits) - 1;
13388 mintiny = - (1 << (op->nbits - 1));
13389 maxtiny = (1 << (op->nbits - 1)) - 1;
13392 sym_frag = symbol_get_frag (fragp->fr_symbol);
13393 val = S_GET_VALUE (fragp->fr_symbol);
13394 symsec = S_GET_SEGMENT (fragp->fr_symbol);
13400 /* We won't have the section when we are called from
13401 mips_relax_frag. However, we will always have been called
13402 from md_estimate_size_before_relax first. If this is a
13403 branch to a different section, we mark it as such. If SEC is
13404 NULL, and the frag is not marked, then it must be a branch to
13405 the same section. */
13408 if (RELAX_MIPS16_LONG_BRANCH (fragp->fr_subtype))
13413 /* Must have been called from md_estimate_size_before_relax. */
13416 fragp->fr_subtype =
13417 RELAX_MIPS16_MARK_LONG_BRANCH (fragp->fr_subtype);
13419 /* FIXME: We should support this, and let the linker
13420 catch branches and loads that are out of range. */
13421 as_bad_where (fragp->fr_file, fragp->fr_line,
13422 _("unsupported PC relative reference to different section"));
13426 if (fragp != sym_frag && sym_frag->fr_address == 0)
13427 /* Assume non-extended on the first relaxation pass.
13428 The address we have calculated will be bogus if this is
13429 a forward branch to another frag, as the forward frag
13430 will have fr_address == 0. */
13434 /* In this case, we know for sure that the symbol fragment is in
13435 the same section. If the relax_marker of the symbol fragment
13436 differs from the relax_marker of this fragment, we have not
13437 yet adjusted the symbol fragment fr_address. We want to add
13438 in STRETCH in order to get a better estimate of the address.
13439 This particularly matters because of the shift bits. */
13441 && sym_frag->relax_marker != fragp->relax_marker)
13445 /* Adjust stretch for any alignment frag. Note that if have
13446 been expanding the earlier code, the symbol may be
13447 defined in what appears to be an earlier frag. FIXME:
13448 This doesn't handle the fr_subtype field, which specifies
13449 a maximum number of bytes to skip when doing an
13451 for (f = fragp; f != NULL && f != sym_frag; f = f->fr_next)
13453 if (f->fr_type == rs_align || f->fr_type == rs_align_code)
13456 stretch = - ((- stretch)
13457 & ~ ((1 << (int) f->fr_offset) - 1));
13459 stretch &= ~ ((1 << (int) f->fr_offset) - 1);
13468 addr = fragp->fr_address + fragp->fr_fix;
13470 /* The base address rules are complicated. The base address of
13471 a branch is the following instruction. The base address of a
13472 PC relative load or add is the instruction itself, but if it
13473 is in a delay slot (in which case it can not be extended) use
13474 the address of the instruction whose delay slot it is in. */
13475 if (type == 'p' || type == 'q')
13479 /* If we are currently assuming that this frag should be
13480 extended, then, the current address is two bytes
13482 if (RELAX_MIPS16_EXTENDED (fragp->fr_subtype))
13485 /* Ignore the low bit in the target, since it will be set
13486 for a text label. */
13487 if ((val & 1) != 0)
13490 else if (RELAX_MIPS16_JAL_DSLOT (fragp->fr_subtype))
13492 else if (RELAX_MIPS16_DSLOT (fragp->fr_subtype))
13495 val -= addr & ~ ((1 << op->shift) - 1);
13497 /* Branch offsets have an implicit 0 in the lowest bit. */
13498 if (type == 'p' || type == 'q')
13501 /* If any of the shifted bits are set, we must use an extended
13502 opcode. If the address depends on the size of this
13503 instruction, this can lead to a loop, so we arrange to always
13504 use an extended opcode. We only check this when we are in
13505 the main relaxation loop, when SEC is NULL. */
13506 if ((val & ((1 << op->shift) - 1)) != 0 && sec == NULL)
13508 fragp->fr_subtype =
13509 RELAX_MIPS16_MARK_LONG_BRANCH (fragp->fr_subtype);
13513 /* If we are about to mark a frag as extended because the value
13514 is precisely maxtiny + 1, then there is a chance of an
13515 infinite loop as in the following code:
13520 In this case when the la is extended, foo is 0x3fc bytes
13521 away, so the la can be shrunk, but then foo is 0x400 away, so
13522 the la must be extended. To avoid this loop, we mark the
13523 frag as extended if it was small, and is about to become
13524 extended with a value of maxtiny + 1. */
13525 if (val == ((maxtiny + 1) << op->shift)
13526 && ! RELAX_MIPS16_EXTENDED (fragp->fr_subtype)
13529 fragp->fr_subtype =
13530 RELAX_MIPS16_MARK_LONG_BRANCH (fragp->fr_subtype);
13534 else if (symsec != absolute_section && sec != NULL)
13535 as_bad_where (fragp->fr_file, fragp->fr_line, _("unsupported relocation"));
13537 if ((val & ((1 << op->shift) - 1)) != 0
13538 || val < (mintiny << op->shift)
13539 || val > (maxtiny << op->shift))
13545 /* Compute the length of a branch sequence, and adjust the
13546 RELAX_BRANCH_TOOFAR bit accordingly. If FRAGP is NULL, the
13547 worst-case length is computed, with UPDATE being used to indicate
13548 whether an unconditional (-1), branch-likely (+1) or regular (0)
13549 branch is to be computed. */
13551 relaxed_branch_length (fragp, sec, update)
13556 bfd_boolean toofar;
13560 && S_IS_DEFINED (fragp->fr_symbol)
13561 && sec == S_GET_SEGMENT (fragp->fr_symbol))
13566 val = S_GET_VALUE (fragp->fr_symbol) + fragp->fr_offset;
13568 addr = fragp->fr_address + fragp->fr_fix + 4;
13572 toofar = val < - (0x8000 << 2) || val >= (0x8000 << 2);
13575 /* If the symbol is not defined or it's in a different segment,
13576 assume the user knows what's going on and emit a short
13582 if (fragp && update && toofar != RELAX_BRANCH_TOOFAR (fragp->fr_subtype))
13584 = RELAX_BRANCH_ENCODE (RELAX_BRANCH_UNCOND (fragp->fr_subtype),
13585 RELAX_BRANCH_LIKELY (fragp->fr_subtype),
13586 RELAX_BRANCH_LINK (fragp->fr_subtype),
13592 if (fragp ? RELAX_BRANCH_LIKELY (fragp->fr_subtype) : (update > 0))
13595 if (mips_pic != NO_PIC)
13597 /* Additional space for PIC loading of target address. */
13599 if (mips_opts.isa == ISA_MIPS1)
13600 /* Additional space for $at-stabilizing nop. */
13604 /* If branch is conditional. */
13605 if (fragp ? !RELAX_BRANCH_UNCOND (fragp->fr_subtype) : (update >= 0))
13612 /* Estimate the size of a frag before relaxing. Unless this is the
13613 mips16, we are not really relaxing here, and the final size is
13614 encoded in the subtype information. For the mips16, we have to
13615 decide whether we are using an extended opcode or not. */
13618 md_estimate_size_before_relax (fragp, segtype)
13624 if (RELAX_BRANCH_P (fragp->fr_subtype))
13627 fragp->fr_var = relaxed_branch_length (fragp, segtype, FALSE);
13629 return fragp->fr_var;
13632 if (RELAX_MIPS16_P (fragp->fr_subtype))
13633 /* We don't want to modify the EXTENDED bit here; it might get us
13634 into infinite loops. We change it only in mips_relax_frag(). */
13635 return (RELAX_MIPS16_EXTENDED (fragp->fr_subtype) ? 4 : 2);
13637 if (mips_pic == NO_PIC)
13638 change = nopic_need_relax (fragp->fr_symbol, 0);
13639 else if (mips_pic == SVR4_PIC)
13640 change = pic_need_relax (fragp->fr_symbol, segtype);
13646 /* Record the offset to the first reloc in the fr_opcode field.
13647 This lets md_convert_frag and tc_gen_reloc know that the code
13648 must be expanded. */
13649 fragp->fr_opcode = (fragp->fr_literal
13651 - RELAX_OLD (fragp->fr_subtype)
13652 + RELAX_RELOC1 (fragp->fr_subtype));
13653 /* FIXME: This really needs as_warn_where. */
13654 if (RELAX_WARN (fragp->fr_subtype))
13655 as_warn (_("AT used after \".set noat\" or macro used after "
13656 "\".set nomacro\""));
13658 return RELAX_NEW (fragp->fr_subtype) - RELAX_OLD (fragp->fr_subtype);
13664 /* This is called to see whether a reloc against a defined symbol
13665 should be converted into a reloc against a section. Don't adjust
13666 MIPS16 jump relocations, so we don't have to worry about the format
13667 of the offset in the .o file. Don't adjust relocations against
13668 mips16 symbols, so that the linker can find them if it needs to set
13672 mips_fix_adjustable (fixp)
13675 if (fixp->fx_r_type == BFD_RELOC_MIPS16_JMP)
13678 if (fixp->fx_r_type == BFD_RELOC_VTABLE_INHERIT
13679 || fixp->fx_r_type == BFD_RELOC_VTABLE_ENTRY)
13682 if (fixp->fx_addsy == NULL)
13686 if (OUTPUT_FLAVOR == bfd_target_elf_flavour
13687 && S_GET_OTHER (fixp->fx_addsy) == STO_MIPS16
13688 && fixp->fx_subsy == NULL)
13695 /* Translate internal representation of relocation info to BFD target
13699 tc_gen_reloc (section, fixp)
13700 asection *section ATTRIBUTE_UNUSED;
13703 static arelent *retval[4];
13705 bfd_reloc_code_real_type code;
13707 reloc = retval[0] = (arelent *) xmalloc (sizeof (arelent));
13710 reloc->sym_ptr_ptr = (asymbol **) xmalloc (sizeof (asymbol *));
13711 *reloc->sym_ptr_ptr = symbol_get_bfdsym (fixp->fx_addsy);
13712 reloc->address = fixp->fx_frag->fr_address + fixp->fx_where;
13714 if (mips_pic == EMBEDDED_PIC
13715 && SWITCH_TABLE (fixp))
13717 /* For a switch table entry we use a special reloc. The addend
13718 is actually the difference between the reloc address and the
13720 reloc->addend = reloc->address - S_GET_VALUE (fixp->fx_subsy);
13721 if (OUTPUT_FLAVOR != bfd_target_ecoff_flavour)
13722 as_fatal (_("Double check fx_r_type in tc-mips.c:tc_gen_reloc"));
13723 fixp->fx_r_type = BFD_RELOC_GPREL32;
13725 else if (fixp->fx_r_type == BFD_RELOC_PCREL_LO16)
13727 if (OUTPUT_FLAVOR == bfd_target_elf_flavour)
13728 reloc->addend = fixp->fx_addnumber;
13731 /* We use a special addend for an internal RELLO reloc. */
13732 if (symbol_section_p (fixp->fx_addsy))
13733 reloc->addend = reloc->address - S_GET_VALUE (fixp->fx_subsy);
13735 reloc->addend = fixp->fx_addnumber + reloc->address;
13738 else if (fixp->fx_r_type == BFD_RELOC_PCREL_HI16_S)
13740 assert (fixp->fx_next != NULL
13741 && fixp->fx_next->fx_r_type == BFD_RELOC_PCREL_LO16);
13743 /* The reloc is relative to the RELLO; adjust the addend
13745 if (OUTPUT_FLAVOR == bfd_target_elf_flavour)
13746 reloc->addend = fixp->fx_next->fx_addnumber;
13749 /* We use a special addend for an internal RELHI reloc. */
13750 if (symbol_section_p (fixp->fx_addsy))
13751 reloc->addend = (fixp->fx_next->fx_frag->fr_address
13752 + fixp->fx_next->fx_where
13753 - S_GET_VALUE (fixp->fx_subsy));
13755 reloc->addend = (fixp->fx_addnumber
13756 + fixp->fx_next->fx_frag->fr_address
13757 + fixp->fx_next->fx_where);
13760 else if (fixp->fx_pcrel == 0 || OUTPUT_FLAVOR == bfd_target_elf_flavour)
13761 reloc->addend = fixp->fx_addnumber;
13764 if (OUTPUT_FLAVOR != bfd_target_aout_flavour)
13765 /* A gruesome hack which is a result of the gruesome gas reloc
13767 reloc->addend = reloc->address;
13769 reloc->addend = -reloc->address;
13772 /* If this is a variant frag, we may need to adjust the existing
13773 reloc and generate a new one. */
13774 if (fixp->fx_frag->fr_opcode != NULL
13775 && ((fixp->fx_r_type == BFD_RELOC_GPREL16
13777 || (fixp->fx_r_type == BFD_RELOC_MIPS_GOT_DISP
13779 || fixp->fx_r_type == BFD_RELOC_MIPS_GOT16
13780 || fixp->fx_r_type == BFD_RELOC_MIPS_CALL16
13781 || fixp->fx_r_type == BFD_RELOC_MIPS_GOT_HI16
13782 || fixp->fx_r_type == BFD_RELOC_MIPS_GOT_LO16
13783 || fixp->fx_r_type == BFD_RELOC_MIPS_CALL_HI16
13784 || fixp->fx_r_type == BFD_RELOC_MIPS_CALL_LO16)
13789 assert (! RELAX_MIPS16_P (fixp->fx_frag->fr_subtype));
13791 /* If this is not the last reloc in this frag, then we have two
13792 GPREL relocs, or a GOT_HI16/GOT_LO16 pair, or a
13793 CALL_HI16/CALL_LO16, both of which are being replaced. Let
13794 the second one handle all of them. */
13795 if (fixp->fx_next != NULL
13796 && fixp->fx_frag == fixp->fx_next->fx_frag)
13798 assert ((fixp->fx_r_type == BFD_RELOC_GPREL16
13799 && fixp->fx_next->fx_r_type == BFD_RELOC_GPREL16)
13800 || (fixp->fx_r_type == BFD_RELOC_MIPS_GOT_HI16
13801 && (fixp->fx_next->fx_r_type
13802 == BFD_RELOC_MIPS_GOT_LO16))
13803 || (fixp->fx_r_type == BFD_RELOC_MIPS_CALL_HI16
13804 && (fixp->fx_next->fx_r_type
13805 == BFD_RELOC_MIPS_CALL_LO16)));
13810 fixp->fx_where = fixp->fx_frag->fr_opcode - fixp->fx_frag->fr_literal;
13811 reloc->address = fixp->fx_frag->fr_address + fixp->fx_where;
13812 reloc->addend += fixp->fx_frag->tc_frag_data.tc_fr_offset;
13813 reloc2 = retval[1] = (arelent *) xmalloc (sizeof (arelent));
13815 reloc2->sym_ptr_ptr = (asymbol **) xmalloc (sizeof (asymbol *));
13816 *reloc2->sym_ptr_ptr = symbol_get_bfdsym (fixp->fx_addsy);
13817 reloc2->address = (reloc->address
13818 + (RELAX_RELOC2 (fixp->fx_frag->fr_subtype)
13819 - RELAX_RELOC1 (fixp->fx_frag->fr_subtype)));
13820 reloc2->addend = fixp->fx_addnumber
13821 + fixp->fx_frag->tc_frag_data.tc_fr_offset;
13822 reloc2->howto = bfd_reloc_type_lookup (stdoutput, BFD_RELOC_LO16);
13823 assert (reloc2->howto != NULL);
13825 if (RELAX_RELOC3 (fixp->fx_frag->fr_subtype))
13829 reloc3 = retval[2] = (arelent *) xmalloc (sizeof (arelent));
13832 reloc3->address += 4;
13835 if (mips_pic == NO_PIC)
13837 assert (fixp->fx_r_type == BFD_RELOC_GPREL16);
13838 fixp->fx_r_type = BFD_RELOC_HI16_S;
13840 else if (mips_pic == SVR4_PIC)
13842 switch (fixp->fx_r_type)
13846 case BFD_RELOC_MIPS_GOT16:
13848 case BFD_RELOC_MIPS_GOT_LO16:
13849 case BFD_RELOC_MIPS_CALL_LO16:
13852 fixp->fx_r_type = BFD_RELOC_MIPS_GOT_PAGE;
13853 reloc2->howto = bfd_reloc_type_lookup
13854 (stdoutput, BFD_RELOC_MIPS_GOT_OFST);
13857 fixp->fx_r_type = BFD_RELOC_MIPS_GOT16;
13859 case BFD_RELOC_MIPS_CALL16:
13860 case BFD_RELOC_MIPS_GOT_OFST:
13861 case BFD_RELOC_MIPS_GOT_DISP:
13864 /* It may seem nonsensical to relax GOT_DISP to
13865 GOT_DISP, but we're actually turning a GOT_DISP
13866 without offset into a GOT_DISP with an offset,
13867 getting rid of the separate addition, which we can
13868 do when the symbol is found to be local. */
13869 fixp->fx_r_type = BFD_RELOC_MIPS_GOT_DISP;
13873 fixp->fx_r_type = BFD_RELOC_MIPS_GOT16;
13881 /* Since the old MIPS ELF ABI uses Rel instead of Rela, encode the vtable
13882 entry to be used in the relocation's section offset. */
13883 if (! HAVE_NEWABI && fixp->fx_r_type == BFD_RELOC_VTABLE_ENTRY)
13885 reloc->address = reloc->addend;
13889 /* Since DIFF_EXPR_OK is defined in tc-mips.h, it is possible that
13890 fixup_segment converted a non-PC relative reloc into a PC
13891 relative reloc. In such a case, we need to convert the reloc
13893 code = fixp->fx_r_type;
13894 if (fixp->fx_pcrel)
13899 code = BFD_RELOC_8_PCREL;
13902 code = BFD_RELOC_16_PCREL;
13905 code = BFD_RELOC_32_PCREL;
13908 code = BFD_RELOC_64_PCREL;
13910 case BFD_RELOC_8_PCREL:
13911 case BFD_RELOC_16_PCREL:
13912 case BFD_RELOC_32_PCREL:
13913 case BFD_RELOC_64_PCREL:
13914 case BFD_RELOC_16_PCREL_S2:
13915 case BFD_RELOC_PCREL_HI16_S:
13916 case BFD_RELOC_PCREL_LO16:
13919 as_bad_where (fixp->fx_file, fixp->fx_line,
13920 _("Cannot make %s relocation PC relative"),
13921 bfd_get_reloc_code_name (code));
13926 /* md_apply_fix3 has a double-subtraction hack to get
13927 bfd_install_relocation to behave nicely. GPREL relocations are
13928 handled correctly without this hack, so undo it here. We can't
13929 stop md_apply_fix3 from subtracting twice in the first place since
13930 the fake addend is required for variant frags above. */
13931 if (fixp->fx_addsy != NULL && OUTPUT_FLAVOR == bfd_target_elf_flavour
13932 && (code == BFD_RELOC_GPREL16 || code == BFD_RELOC_MIPS16_GPREL)
13933 && reloc->addend != 0
13934 && mips_need_elf_addend_fixup (fixp))
13935 reloc->addend += S_GET_VALUE (fixp->fx_addsy);
13938 /* To support a PC relative reloc when generating embedded PIC code
13939 for ECOFF, we use a Cygnus extension. We check for that here to
13940 make sure that we don't let such a reloc escape normally. */
13941 if ((OUTPUT_FLAVOR == bfd_target_ecoff_flavour
13942 || OUTPUT_FLAVOR == bfd_target_elf_flavour)
13943 && code == BFD_RELOC_16_PCREL_S2
13944 && mips_pic != EMBEDDED_PIC)
13945 reloc->howto = NULL;
13947 reloc->howto = bfd_reloc_type_lookup (stdoutput, code);
13949 if (reloc->howto == NULL)
13951 as_bad_where (fixp->fx_file, fixp->fx_line,
13952 _("Can not represent %s relocation in this object file format"),
13953 bfd_get_reloc_code_name (code));
13960 /* Relax a machine dependent frag. This returns the amount by which
13961 the current size of the frag should change. */
13964 mips_relax_frag (sec, fragp, stretch)
13969 if (RELAX_BRANCH_P (fragp->fr_subtype))
13971 offsetT old_var = fragp->fr_var;
13973 fragp->fr_var = relaxed_branch_length (fragp, sec, TRUE);
13975 return fragp->fr_var - old_var;
13978 if (! RELAX_MIPS16_P (fragp->fr_subtype))
13981 if (mips16_extended_frag (fragp, NULL, stretch))
13983 if (RELAX_MIPS16_EXTENDED (fragp->fr_subtype))
13985 fragp->fr_subtype = RELAX_MIPS16_MARK_EXTENDED (fragp->fr_subtype);
13990 if (! RELAX_MIPS16_EXTENDED (fragp->fr_subtype))
13992 fragp->fr_subtype = RELAX_MIPS16_CLEAR_EXTENDED (fragp->fr_subtype);
13999 /* Convert a machine dependent frag. */
14002 md_convert_frag (abfd, asec, fragp)
14003 bfd *abfd ATTRIBUTE_UNUSED;
14010 if (RELAX_BRANCH_P (fragp->fr_subtype))
14013 unsigned long insn;
14017 buf = (bfd_byte *)fragp->fr_literal + fragp->fr_fix;
14019 if (target_big_endian)
14020 insn = bfd_getb32 (buf);
14022 insn = bfd_getl32 (buf);
14024 if (!RELAX_BRANCH_TOOFAR (fragp->fr_subtype))
14026 /* We generate a fixup instead of applying it right now
14027 because, if there are linker relaxations, we're going to
14028 need the relocations. */
14029 exp.X_op = O_symbol;
14030 exp.X_add_symbol = fragp->fr_symbol;
14031 exp.X_add_number = fragp->fr_offset;
14033 fixp = fix_new_exp (fragp, buf - (bfd_byte *)fragp->fr_literal,
14035 BFD_RELOC_16_PCREL_S2);
14036 fixp->fx_file = fragp->fr_file;
14037 fixp->fx_line = fragp->fr_line;
14039 md_number_to_chars ((char *)buf, insn, 4);
14046 as_warn_where (fragp->fr_file, fragp->fr_line,
14047 _("relaxed out-of-range branch into a jump"));
14049 if (RELAX_BRANCH_UNCOND (fragp->fr_subtype))
14052 if (!RELAX_BRANCH_LIKELY (fragp->fr_subtype))
14054 /* Reverse the branch. */
14055 switch ((insn >> 28) & 0xf)
14058 /* bc[0-3][tf]l? and bc1any[24][ft] instructions can
14059 have the condition reversed by tweaking a single
14060 bit, and their opcodes all have 0x4???????. */
14061 assert ((insn & 0xf1000000) == 0x41000000);
14062 insn ^= 0x00010000;
14066 /* bltz 0x04000000 bgez 0x04010000
14067 bltzal 0x04100000 bgezal 0x04110000 */
14068 assert ((insn & 0xfc0e0000) == 0x04000000);
14069 insn ^= 0x00010000;
14073 /* beq 0x10000000 bne 0x14000000
14074 blez 0x18000000 bgtz 0x1c000000 */
14075 insn ^= 0x04000000;
14083 if (RELAX_BRANCH_LINK (fragp->fr_subtype))
14085 /* Clear the and-link bit. */
14086 assert ((insn & 0xfc1c0000) == 0x04100000);
14088 /* bltzal 0x04100000 bgezal 0x04110000
14089 bltzall 0x04120000 bgezall 0x04130000 */
14090 insn &= ~0x00100000;
14093 /* Branch over the branch (if the branch was likely) or the
14094 full jump (not likely case). Compute the offset from the
14095 current instruction to branch to. */
14096 if (RELAX_BRANCH_LIKELY (fragp->fr_subtype))
14100 /* How many bytes in instructions we've already emitted? */
14101 i = buf - (bfd_byte *)fragp->fr_literal - fragp->fr_fix;
14102 /* How many bytes in instructions from here to the end? */
14103 i = fragp->fr_var - i;
14105 /* Convert to instruction count. */
14107 /* Branch counts from the next instruction. */
14110 /* Branch over the jump. */
14111 md_number_to_chars ((char *)buf, insn, 4);
14115 md_number_to_chars ((char*)buf, 0, 4);
14118 if (RELAX_BRANCH_LIKELY (fragp->fr_subtype))
14120 /* beql $0, $0, 2f */
14122 /* Compute the PC offset from the current instruction to
14123 the end of the variable frag. */
14124 /* How many bytes in instructions we've already emitted? */
14125 i = buf - (bfd_byte *)fragp->fr_literal - fragp->fr_fix;
14126 /* How many bytes in instructions from here to the end? */
14127 i = fragp->fr_var - i;
14128 /* Convert to instruction count. */
14130 /* Don't decrement i, because we want to branch over the
14134 md_number_to_chars ((char *)buf, insn, 4);
14137 md_number_to_chars ((char *)buf, 0, 4);
14142 if (mips_pic == NO_PIC)
14145 insn = (RELAX_BRANCH_LINK (fragp->fr_subtype)
14146 ? 0x0c000000 : 0x08000000);
14147 exp.X_op = O_symbol;
14148 exp.X_add_symbol = fragp->fr_symbol;
14149 exp.X_add_number = fragp->fr_offset;
14151 fixp = fix_new_exp (fragp, buf - (bfd_byte *)fragp->fr_literal,
14152 4, &exp, 0, BFD_RELOC_MIPS_JMP);
14153 fixp->fx_file = fragp->fr_file;
14154 fixp->fx_line = fragp->fr_line;
14156 md_number_to_chars ((char*)buf, insn, 4);
14161 /* lw/ld $at, <sym>($gp) R_MIPS_GOT16 */
14162 insn = HAVE_64BIT_ADDRESSES ? 0xdf810000 : 0x8f810000;
14163 exp.X_op = O_symbol;
14164 exp.X_add_symbol = fragp->fr_symbol;
14165 exp.X_add_number = fragp->fr_offset;
14167 if (fragp->fr_offset)
14169 exp.X_add_symbol = make_expr_symbol (&exp);
14170 exp.X_add_number = 0;
14173 fixp = fix_new_exp (fragp, buf - (bfd_byte *)fragp->fr_literal,
14174 4, &exp, 0, BFD_RELOC_MIPS_GOT16);
14175 fixp->fx_file = fragp->fr_file;
14176 fixp->fx_line = fragp->fr_line;
14178 md_number_to_chars ((char*)buf, insn, 4);
14181 if (mips_opts.isa == ISA_MIPS1)
14184 md_number_to_chars ((char*)buf, 0, 4);
14188 /* d/addiu $at, $at, <sym> R_MIPS_LO16 */
14189 insn = HAVE_64BIT_ADDRESSES ? 0x64210000 : 0x24210000;
14191 fixp = fix_new_exp (fragp, buf - (bfd_byte *)fragp->fr_literal,
14192 4, &exp, 0, BFD_RELOC_LO16);
14193 fixp->fx_file = fragp->fr_file;
14194 fixp->fx_line = fragp->fr_line;
14196 md_number_to_chars ((char*)buf, insn, 4);
14200 if (RELAX_BRANCH_LINK (fragp->fr_subtype))
14205 md_number_to_chars ((char*)buf, insn, 4);
14210 assert (buf == (bfd_byte *)fragp->fr_literal
14211 + fragp->fr_fix + fragp->fr_var);
14213 fragp->fr_fix += fragp->fr_var;
14218 if (RELAX_MIPS16_P (fragp->fr_subtype))
14221 register const struct mips16_immed_operand *op;
14222 bfd_boolean small, ext;
14225 unsigned long insn;
14226 bfd_boolean use_extend;
14227 unsigned short extend;
14229 type = RELAX_MIPS16_TYPE (fragp->fr_subtype);
14230 op = mips16_immed_operands;
14231 while (op->type != type)
14234 if (RELAX_MIPS16_EXTENDED (fragp->fr_subtype))
14245 resolve_symbol_value (fragp->fr_symbol);
14246 val = S_GET_VALUE (fragp->fr_symbol);
14251 addr = fragp->fr_address + fragp->fr_fix;
14253 /* The rules for the base address of a PC relative reloc are
14254 complicated; see mips16_extended_frag. */
14255 if (type == 'p' || type == 'q')
14260 /* Ignore the low bit in the target, since it will be
14261 set for a text label. */
14262 if ((val & 1) != 0)
14265 else if (RELAX_MIPS16_JAL_DSLOT (fragp->fr_subtype))
14267 else if (RELAX_MIPS16_DSLOT (fragp->fr_subtype))
14270 addr &= ~ (addressT) ((1 << op->shift) - 1);
14273 /* Make sure the section winds up with the alignment we have
14276 record_alignment (asec, op->shift);
14280 && (RELAX_MIPS16_JAL_DSLOT (fragp->fr_subtype)
14281 || RELAX_MIPS16_DSLOT (fragp->fr_subtype)))
14282 as_warn_where (fragp->fr_file, fragp->fr_line,
14283 _("extended instruction in delay slot"));
14285 buf = (bfd_byte *) (fragp->fr_literal + fragp->fr_fix);
14287 if (target_big_endian)
14288 insn = bfd_getb16 (buf);
14290 insn = bfd_getl16 (buf);
14292 mips16_immed (fragp->fr_file, fragp->fr_line, type, val,
14293 RELAX_MIPS16_USER_EXT (fragp->fr_subtype),
14294 small, ext, &insn, &use_extend, &extend);
14298 md_number_to_chars ((char *) buf, 0xf000 | extend, 2);
14299 fragp->fr_fix += 2;
14303 md_number_to_chars ((char *) buf, insn, 2);
14304 fragp->fr_fix += 2;
14309 if (fragp->fr_opcode == NULL)
14312 old = RELAX_OLD (fragp->fr_subtype);
14313 new = RELAX_NEW (fragp->fr_subtype);
14314 fixptr = fragp->fr_literal + fragp->fr_fix;
14317 memmove (fixptr - old, fixptr, new);
14319 fragp->fr_fix += new - old;
14325 /* This function is called after the relocs have been generated.
14326 We've been storing mips16 text labels as odd. Here we convert them
14327 back to even for the convenience of the debugger. */
14330 mips_frob_file_after_relocs ()
14333 unsigned int count, i;
14335 if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
14338 syms = bfd_get_outsymbols (stdoutput);
14339 count = bfd_get_symcount (stdoutput);
14340 for (i = 0; i < count; i++, syms++)
14342 if (elf_symbol (*syms)->internal_elf_sym.st_other == STO_MIPS16
14343 && ((*syms)->value & 1) != 0)
14345 (*syms)->value &= ~1;
14346 /* If the symbol has an odd size, it was probably computed
14347 incorrectly, so adjust that as well. */
14348 if ((elf_symbol (*syms)->internal_elf_sym.st_size & 1) != 0)
14349 ++elf_symbol (*syms)->internal_elf_sym.st_size;
14356 /* This function is called whenever a label is defined. It is used
14357 when handling branch delays; if a branch has a label, we assume we
14358 can not move it. */
14361 mips_define_label (sym)
14364 struct insn_label_list *l;
14366 if (free_insn_labels == NULL)
14367 l = (struct insn_label_list *) xmalloc (sizeof *l);
14370 l = free_insn_labels;
14371 free_insn_labels = l->next;
14375 l->next = insn_labels;
14379 #if defined (OBJ_ELF) || defined (OBJ_MAYBE_ELF)
14381 /* Some special processing for a MIPS ELF file. */
14384 mips_elf_final_processing ()
14386 /* Write out the register information. */
14387 if (mips_abi != N64_ABI)
14391 s.ri_gprmask = mips_gprmask;
14392 s.ri_cprmask[0] = mips_cprmask[0];
14393 s.ri_cprmask[1] = mips_cprmask[1];
14394 s.ri_cprmask[2] = mips_cprmask[2];
14395 s.ri_cprmask[3] = mips_cprmask[3];
14396 /* The gp_value field is set by the MIPS ELF backend. */
14398 bfd_mips_elf32_swap_reginfo_out (stdoutput, &s,
14399 ((Elf32_External_RegInfo *)
14400 mips_regmask_frag));
14404 Elf64_Internal_RegInfo s;
14406 s.ri_gprmask = mips_gprmask;
14408 s.ri_cprmask[0] = mips_cprmask[0];
14409 s.ri_cprmask[1] = mips_cprmask[1];
14410 s.ri_cprmask[2] = mips_cprmask[2];
14411 s.ri_cprmask[3] = mips_cprmask[3];
14412 /* The gp_value field is set by the MIPS ELF backend. */
14414 bfd_mips_elf64_swap_reginfo_out (stdoutput, &s,
14415 ((Elf64_External_RegInfo *)
14416 mips_regmask_frag));
14419 /* Set the MIPS ELF flag bits. FIXME: There should probably be some
14420 sort of BFD interface for this. */
14421 if (mips_any_noreorder)
14422 elf_elfheader (stdoutput)->e_flags |= EF_MIPS_NOREORDER;
14423 if (mips_pic != NO_PIC)
14424 elf_elfheader (stdoutput)->e_flags |= EF_MIPS_PIC;
14426 /* Set MIPS ELF flags for ASEs. */
14427 if (file_ase_mips16)
14428 elf_elfheader (stdoutput)->e_flags |= EF_MIPS_ARCH_ASE_M16;
14429 #if 0 /* XXX FIXME */
14430 if (file_ase_mips3d)
14431 elf_elfheader (stdoutput)->e_flags |= ???;
14434 elf_elfheader (stdoutput)->e_flags |= EF_MIPS_ARCH_ASE_MDMX;
14436 /* Set the MIPS ELF ABI flags. */
14437 if (mips_abi == O32_ABI && USE_E_MIPS_ABI_O32)
14438 elf_elfheader (stdoutput)->e_flags |= E_MIPS_ABI_O32;
14439 else if (mips_abi == O64_ABI)
14440 elf_elfheader (stdoutput)->e_flags |= E_MIPS_ABI_O64;
14441 else if (mips_abi == EABI_ABI)
14443 if (!file_mips_gp32)
14444 elf_elfheader (stdoutput)->e_flags |= E_MIPS_ABI_EABI64;
14446 elf_elfheader (stdoutput)->e_flags |= E_MIPS_ABI_EABI32;
14448 else if (mips_abi == N32_ABI)
14449 elf_elfheader (stdoutput)->e_flags |= EF_MIPS_ABI2;
14451 /* Nothing to do for N64_ABI. */
14453 if (mips_32bitmode)
14454 elf_elfheader (stdoutput)->e_flags |= EF_MIPS_32BITMODE;
14457 #endif /* OBJ_ELF || OBJ_MAYBE_ELF */
14459 typedef struct proc {
14461 unsigned long reg_mask;
14462 unsigned long reg_offset;
14463 unsigned long fpreg_mask;
14464 unsigned long fpreg_offset;
14465 unsigned long frame_offset;
14466 unsigned long frame_reg;
14467 unsigned long pc_reg;
14470 static procS cur_proc;
14471 static procS *cur_proc_ptr;
14472 static int numprocs;
14474 /* Fill in an rs_align_code fragment. */
14477 mips_handle_align (fragp)
14480 if (fragp->fr_type != rs_align_code)
14483 if (mips_opts.mips16)
14485 static const unsigned char be_nop[] = { 0x65, 0x00 };
14486 static const unsigned char le_nop[] = { 0x00, 0x65 };
14491 bytes = fragp->fr_next->fr_address - fragp->fr_address - fragp->fr_fix;
14492 p = fragp->fr_literal + fragp->fr_fix;
14500 memcpy (p, (target_big_endian ? be_nop : le_nop), 2);
14504 /* For mips32, a nop is a zero, which we trivially get by doing nothing. */
14515 /* check for premature end, nesting errors, etc */
14517 as_warn (_("missing .end at end of assembly"));
14526 if (*input_line_pointer == '-')
14528 ++input_line_pointer;
14531 if (!ISDIGIT (*input_line_pointer))
14532 as_bad (_("expected simple number"));
14533 if (input_line_pointer[0] == '0')
14535 if (input_line_pointer[1] == 'x')
14537 input_line_pointer += 2;
14538 while (ISXDIGIT (*input_line_pointer))
14541 val |= hex_value (*input_line_pointer++);
14543 return negative ? -val : val;
14547 ++input_line_pointer;
14548 while (ISDIGIT (*input_line_pointer))
14551 val |= *input_line_pointer++ - '0';
14553 return negative ? -val : val;
14556 if (!ISDIGIT (*input_line_pointer))
14558 printf (_(" *input_line_pointer == '%c' 0x%02x\n"),
14559 *input_line_pointer, *input_line_pointer);
14560 as_warn (_("invalid number"));
14563 while (ISDIGIT (*input_line_pointer))
14566 val += *input_line_pointer++ - '0';
14568 return negative ? -val : val;
14571 /* The .file directive; just like the usual .file directive, but there
14572 is an initial number which is the ECOFF file index. In the non-ECOFF
14573 case .file implies DWARF-2. */
14577 int x ATTRIBUTE_UNUSED;
14579 static int first_file_directive = 0;
14581 if (ECOFF_DEBUGGING)
14590 filename = dwarf2_directive_file (0);
14592 /* Versions of GCC up to 3.1 start files with a ".file"
14593 directive even for stabs output. Make sure that this
14594 ".file" is handled. Note that you need a version of GCC
14595 after 3.1 in order to support DWARF-2 on MIPS. */
14596 if (filename != NULL && ! first_file_directive)
14598 (void) new_logical_line (filename, -1);
14599 s_app_file_string (filename);
14601 first_file_directive = 1;
14605 /* The .loc directive, implying DWARF-2. */
14609 int x ATTRIBUTE_UNUSED;
14611 if (!ECOFF_DEBUGGING)
14612 dwarf2_directive_loc (0);
14615 /* The .end directive. */
14619 int x ATTRIBUTE_UNUSED;
14623 /* Following functions need their own .frame and .cprestore directives. */
14624 mips_frame_reg_valid = 0;
14625 mips_cprestore_valid = 0;
14627 if (!is_end_of_line[(unsigned char) *input_line_pointer])
14630 demand_empty_rest_of_line ();
14635 if ((bfd_get_section_flags (stdoutput, now_seg) & SEC_CODE) == 0)
14636 as_warn (_(".end not in text section"));
14640 as_warn (_(".end directive without a preceding .ent directive."));
14641 demand_empty_rest_of_line ();
14647 assert (S_GET_NAME (p));
14648 if (strcmp (S_GET_NAME (p), S_GET_NAME (cur_proc_ptr->isym)))
14649 as_warn (_(".end symbol does not match .ent symbol."));
14651 if (debug_type == DEBUG_STABS)
14652 stabs_generate_asm_endfunc (S_GET_NAME (p),
14656 as_warn (_(".end directive missing or unknown symbol"));
14659 /* Generate a .pdr section. */
14660 if (OUTPUT_FLAVOR == bfd_target_elf_flavour && ! ECOFF_DEBUGGING)
14662 segT saved_seg = now_seg;
14663 subsegT saved_subseg = now_subseg;
14668 dot = frag_now_fix ();
14670 #ifdef md_flush_pending_output
14671 md_flush_pending_output ();
14675 subseg_set (pdr_seg, 0);
14677 /* Write the symbol. */
14678 exp.X_op = O_symbol;
14679 exp.X_add_symbol = p;
14680 exp.X_add_number = 0;
14681 emit_expr (&exp, 4);
14683 fragp = frag_more (7 * 4);
14685 md_number_to_chars (fragp, (valueT) cur_proc_ptr->reg_mask, 4);
14686 md_number_to_chars (fragp + 4, (valueT) cur_proc_ptr->reg_offset, 4);
14687 md_number_to_chars (fragp + 8, (valueT) cur_proc_ptr->fpreg_mask, 4);
14688 md_number_to_chars (fragp + 12, (valueT) cur_proc_ptr->fpreg_offset, 4);
14689 md_number_to_chars (fragp + 16, (valueT) cur_proc_ptr->frame_offset, 4);
14690 md_number_to_chars (fragp + 20, (valueT) cur_proc_ptr->frame_reg, 4);
14691 md_number_to_chars (fragp + 24, (valueT) cur_proc_ptr->pc_reg, 4);
14693 subseg_set (saved_seg, saved_subseg);
14695 #endif /* OBJ_ELF */
14697 cur_proc_ptr = NULL;
14700 /* The .aent and .ent directives. */
14708 symbolP = get_symbol ();
14709 if (*input_line_pointer == ',')
14710 ++input_line_pointer;
14711 SKIP_WHITESPACE ();
14712 if (ISDIGIT (*input_line_pointer)
14713 || *input_line_pointer == '-')
14716 if ((bfd_get_section_flags (stdoutput, now_seg) & SEC_CODE) == 0)
14717 as_warn (_(".ent or .aent not in text section."));
14719 if (!aent && cur_proc_ptr)
14720 as_warn (_("missing .end"));
14724 /* This function needs its own .frame and .cprestore directives. */
14725 mips_frame_reg_valid = 0;
14726 mips_cprestore_valid = 0;
14728 cur_proc_ptr = &cur_proc;
14729 memset (cur_proc_ptr, '\0', sizeof (procS));
14731 cur_proc_ptr->isym = symbolP;
14733 symbol_get_bfdsym (symbolP)->flags |= BSF_FUNCTION;
14737 if (debug_type == DEBUG_STABS)
14738 stabs_generate_asm_func (S_GET_NAME (symbolP),
14739 S_GET_NAME (symbolP));
14742 demand_empty_rest_of_line ();
14745 /* The .frame directive. If the mdebug section is present (IRIX 5 native)
14746 then ecoff.c (ecoff_directive_frame) is used. For embedded targets,
14747 s_mips_frame is used so that we can set the PDR information correctly.
14748 We can't use the ecoff routines because they make reference to the ecoff
14749 symbol table (in the mdebug section). */
14752 s_mips_frame (ignore)
14753 int ignore ATTRIBUTE_UNUSED;
14756 if (OUTPUT_FLAVOR == bfd_target_elf_flavour && ! ECOFF_DEBUGGING)
14760 if (cur_proc_ptr == (procS *) NULL)
14762 as_warn (_(".frame outside of .ent"));
14763 demand_empty_rest_of_line ();
14767 cur_proc_ptr->frame_reg = tc_get_register (1);
14769 SKIP_WHITESPACE ();
14770 if (*input_line_pointer++ != ','
14771 || get_absolute_expression_and_terminator (&val) != ',')
14773 as_warn (_("Bad .frame directive"));
14774 --input_line_pointer;
14775 demand_empty_rest_of_line ();
14779 cur_proc_ptr->frame_offset = val;
14780 cur_proc_ptr->pc_reg = tc_get_register (0);
14782 demand_empty_rest_of_line ();
14785 #endif /* OBJ_ELF */
14789 /* The .fmask and .mask directives. If the mdebug section is present
14790 (IRIX 5 native) then ecoff.c (ecoff_directive_mask) is used. For
14791 embedded targets, s_mips_mask is used so that we can set the PDR
14792 information correctly. We can't use the ecoff routines because they
14793 make reference to the ecoff symbol table (in the mdebug section). */
14796 s_mips_mask (reg_type)
14800 if (OUTPUT_FLAVOR == bfd_target_elf_flavour && ! ECOFF_DEBUGGING)
14804 if (cur_proc_ptr == (procS *) NULL)
14806 as_warn (_(".mask/.fmask outside of .ent"));
14807 demand_empty_rest_of_line ();
14811 if (get_absolute_expression_and_terminator (&mask) != ',')
14813 as_warn (_("Bad .mask/.fmask directive"));
14814 --input_line_pointer;
14815 demand_empty_rest_of_line ();
14819 off = get_absolute_expression ();
14821 if (reg_type == 'F')
14823 cur_proc_ptr->fpreg_mask = mask;
14824 cur_proc_ptr->fpreg_offset = off;
14828 cur_proc_ptr->reg_mask = mask;
14829 cur_proc_ptr->reg_offset = off;
14832 demand_empty_rest_of_line ();
14835 #endif /* OBJ_ELF */
14836 s_ignore (reg_type);
14839 /* The .loc directive. */
14850 assert (now_seg == text_section);
14852 lineno = get_number ();
14853 addroff = frag_now_fix ();
14855 symbolP = symbol_new ("", N_SLINE, addroff, frag_now);
14856 S_SET_TYPE (symbolP, N_SLINE);
14857 S_SET_OTHER (symbolP, 0);
14858 S_SET_DESC (symbolP, lineno);
14859 symbolP->sy_segment = now_seg;
14863 /* A table describing all the processors gas knows about. Names are
14864 matched in the order listed.
14866 To ease comparison, please keep this table in the same order as
14867 gcc's mips_cpu_info_table[]. */
14868 static const struct mips_cpu_info mips_cpu_info_table[] =
14870 /* Entries for generic ISAs */
14871 { "mips1", 1, ISA_MIPS1, CPU_R3000 },
14872 { "mips2", 1, ISA_MIPS2, CPU_R6000 },
14873 { "mips3", 1, ISA_MIPS3, CPU_R4000 },
14874 { "mips4", 1, ISA_MIPS4, CPU_R8000 },
14875 { "mips5", 1, ISA_MIPS5, CPU_MIPS5 },
14876 { "mips32", 1, ISA_MIPS32, CPU_MIPS32 },
14877 { "mips32r2", 1, ISA_MIPS32R2, CPU_MIPS32R2 },
14878 { "mips64", 1, ISA_MIPS64, CPU_MIPS64 },
14881 { "r3000", 0, ISA_MIPS1, CPU_R3000 },
14882 { "r2000", 0, ISA_MIPS1, CPU_R3000 },
14883 { "r3900", 0, ISA_MIPS1, CPU_R3900 },
14886 { "r6000", 0, ISA_MIPS2, CPU_R6000 },
14889 { "r4000", 0, ISA_MIPS3, CPU_R4000 },
14890 { "r4010", 0, ISA_MIPS2, CPU_R4010 },
14891 { "vr4100", 0, ISA_MIPS3, CPU_VR4100 },
14892 { "vr4111", 0, ISA_MIPS3, CPU_R4111 },
14893 { "vr4120", 0, ISA_MIPS3, CPU_VR4120 },
14894 { "vr4130", 0, ISA_MIPS3, CPU_VR4120 },
14895 { "vr4181", 0, ISA_MIPS3, CPU_R4111 },
14896 { "vr4300", 0, ISA_MIPS3, CPU_R4300 },
14897 { "r4400", 0, ISA_MIPS3, CPU_R4400 },
14898 { "r4600", 0, ISA_MIPS3, CPU_R4600 },
14899 { "orion", 0, ISA_MIPS3, CPU_R4600 },
14900 { "r4650", 0, ISA_MIPS3, CPU_R4650 },
14903 { "r8000", 0, ISA_MIPS4, CPU_R8000 },
14904 { "r10000", 0, ISA_MIPS4, CPU_R10000 },
14905 { "r12000", 0, ISA_MIPS4, CPU_R12000 },
14906 { "vr5000", 0, ISA_MIPS4, CPU_R5000 },
14907 { "vr5400", 0, ISA_MIPS4, CPU_VR5400 },
14908 { "vr5500", 0, ISA_MIPS4, CPU_VR5500 },
14909 { "rm5200", 0, ISA_MIPS4, CPU_R5000 },
14910 { "rm5230", 0, ISA_MIPS4, CPU_R5000 },
14911 { "rm5231", 0, ISA_MIPS4, CPU_R5000 },
14912 { "rm5261", 0, ISA_MIPS4, CPU_R5000 },
14913 { "rm5721", 0, ISA_MIPS4, CPU_R5000 },
14914 { "r7000", 0, ISA_MIPS4, CPU_R5000 },
14917 { "4kc", 0, ISA_MIPS32, CPU_MIPS32, },
14918 { "4km", 0, ISA_MIPS32, CPU_MIPS32 },
14919 { "4kp", 0, ISA_MIPS32, CPU_MIPS32 },
14922 { "5kc", 0, ISA_MIPS64, CPU_MIPS64 },
14923 { "20kc", 0, ISA_MIPS64, CPU_MIPS64 },
14925 /* Broadcom SB-1 CPU core */
14926 { "sb1", 0, ISA_MIPS64, CPU_SB1 },
14933 /* Return true if GIVEN is the same as CANONICAL, or if it is CANONICAL
14934 with a final "000" replaced by "k". Ignore case.
14936 Note: this function is shared between GCC and GAS. */
14939 mips_strict_matching_cpu_name_p (canonical, given)
14940 const char *canonical, *given;
14942 while (*given != 0 && TOLOWER (*given) == TOLOWER (*canonical))
14943 given++, canonical++;
14945 return ((*given == 0 && *canonical == 0)
14946 || (strcmp (canonical, "000") == 0 && strcasecmp (given, "k") == 0));
14950 /* Return true if GIVEN matches CANONICAL, where GIVEN is a user-supplied
14951 CPU name. We've traditionally allowed a lot of variation here.
14953 Note: this function is shared between GCC and GAS. */
14956 mips_matching_cpu_name_p (canonical, given)
14957 const char *canonical, *given;
14959 /* First see if the name matches exactly, or with a final "000"
14960 turned into "k". */
14961 if (mips_strict_matching_cpu_name_p (canonical, given))
14964 /* If not, try comparing based on numerical designation alone.
14965 See if GIVEN is an unadorned number, or 'r' followed by a number. */
14966 if (TOLOWER (*given) == 'r')
14968 if (!ISDIGIT (*given))
14971 /* Skip over some well-known prefixes in the canonical name,
14972 hoping to find a number there too. */
14973 if (TOLOWER (canonical[0]) == 'v' && TOLOWER (canonical[1]) == 'r')
14975 else if (TOLOWER (canonical[0]) == 'r' && TOLOWER (canonical[1]) == 'm')
14977 else if (TOLOWER (canonical[0]) == 'r')
14980 return mips_strict_matching_cpu_name_p (canonical, given);
14984 /* Parse an option that takes the name of a processor as its argument.
14985 OPTION is the name of the option and CPU_STRING is the argument.
14986 Return the corresponding processor enumeration if the CPU_STRING is
14987 recognized, otherwise report an error and return null.
14989 A similar function exists in GCC. */
14991 static const struct mips_cpu_info *
14992 mips_parse_cpu (option, cpu_string)
14993 const char *option, *cpu_string;
14995 const struct mips_cpu_info *p;
14997 /* 'from-abi' selects the most compatible architecture for the given
14998 ABI: MIPS I for 32-bit ABIs and MIPS III for 64-bit ABIs. For the
14999 EABIs, we have to decide whether we're using the 32-bit or 64-bit
15000 version. Look first at the -mgp options, if given, otherwise base
15001 the choice on MIPS_DEFAULT_64BIT.
15003 Treat NO_ABI like the EABIs. One reason to do this is that the
15004 plain 'mips' and 'mips64' configs have 'from-abi' as their default
15005 architecture. This code picks MIPS I for 'mips' and MIPS III for
15006 'mips64', just as we did in the days before 'from-abi'. */
15007 if (strcasecmp (cpu_string, "from-abi") == 0)
15009 if (ABI_NEEDS_32BIT_REGS (mips_abi))
15010 return mips_cpu_info_from_isa (ISA_MIPS1);
15012 if (ABI_NEEDS_64BIT_REGS (mips_abi))
15013 return mips_cpu_info_from_isa (ISA_MIPS3);
15015 if (file_mips_gp32 >= 0)
15016 return mips_cpu_info_from_isa (file_mips_gp32 ? ISA_MIPS1 : ISA_MIPS3);
15018 return mips_cpu_info_from_isa (MIPS_DEFAULT_64BIT
15023 /* 'default' has traditionally been a no-op. Probably not very useful. */
15024 if (strcasecmp (cpu_string, "default") == 0)
15027 for (p = mips_cpu_info_table; p->name != 0; p++)
15028 if (mips_matching_cpu_name_p (p->name, cpu_string))
15031 as_bad ("Bad value (%s) for %s", cpu_string, option);
15035 /* Return the canonical processor information for ISA (a member of the
15036 ISA_MIPS* enumeration). */
15038 static const struct mips_cpu_info *
15039 mips_cpu_info_from_isa (isa)
15044 for (i = 0; mips_cpu_info_table[i].name != NULL; i++)
15045 if (mips_cpu_info_table[i].is_isa
15046 && isa == mips_cpu_info_table[i].isa)
15047 return (&mips_cpu_info_table[i]);
15053 show (stream, string, col_p, first_p)
15055 const char *string;
15061 fprintf (stream, "%24s", "");
15066 fprintf (stream, ", ");
15070 if (*col_p + strlen (string) > 72)
15072 fprintf (stream, "\n%24s", "");
15076 fprintf (stream, "%s", string);
15077 *col_p += strlen (string);
15083 md_show_usage (stream)
15089 fprintf (stream, _("\
15091 -membedded-pic generate embedded position independent code\n\
15092 -EB generate big endian output\n\
15093 -EL generate little endian output\n\
15094 -g, -g2 do not remove unneeded NOPs or swap branches\n\
15095 -G NUM allow referencing objects up to NUM bytes\n\
15096 implicitly with the gp register [default 8]\n"));
15097 fprintf (stream, _("\
15098 -mips1 generate MIPS ISA I instructions\n\
15099 -mips2 generate MIPS ISA II instructions\n\
15100 -mips3 generate MIPS ISA III instructions\n\
15101 -mips4 generate MIPS ISA IV instructions\n\
15102 -mips5 generate MIPS ISA V instructions\n\
15103 -mips32 generate MIPS32 ISA instructions\n\
15104 -mips32r2 generate MIPS32 release 2 ISA instructions\n\
15105 -mips64 generate MIPS64 ISA instructions\n\
15106 -march=CPU/-mtune=CPU generate code/schedule for CPU, where CPU is one of:\n"));
15110 for (i = 0; mips_cpu_info_table[i].name != NULL; i++)
15111 show (stream, mips_cpu_info_table[i].name, &column, &first);
15112 show (stream, "from-abi", &column, &first);
15113 fputc ('\n', stream);
15115 fprintf (stream, _("\
15116 -mCPU equivalent to -march=CPU -mtune=CPU. Deprecated.\n\
15117 -no-mCPU don't generate code specific to CPU.\n\
15118 For -mCPU and -no-mCPU, CPU must be one of:\n"));
15122 show (stream, "3900", &column, &first);
15123 show (stream, "4010", &column, &first);
15124 show (stream, "4100", &column, &first);
15125 show (stream, "4650", &column, &first);
15126 fputc ('\n', stream);
15128 fprintf (stream, _("\
15129 -mips16 generate mips16 instructions\n\
15130 -no-mips16 do not generate mips16 instructions\n"));
15131 fprintf (stream, _("\
15132 -mgp32 use 32-bit GPRs, regardless of the chosen ISA\n\
15133 -mfp32 use 32-bit FPRs, regardless of the chosen ISA\n\
15134 -O0 remove unneeded NOPs, do not swap branches\n\
15135 -O remove unneeded NOPs and swap branches\n\
15136 -n warn about NOPs generated from macros\n\
15137 --[no-]construct-floats [dis]allow floating point values to be constructed\n\
15138 --trap, --no-break trap exception on div by 0 and mult overflow\n\
15139 --break, --no-trap break exception on div by 0 and mult overflow\n"));
15141 fprintf (stream, _("\
15142 -KPIC, -call_shared generate SVR4 position independent code\n\
15143 -non_shared do not generate position independent code\n\
15144 -xgot assume a 32 bit GOT\n\
15145 -mabi=ABI create ABI conformant object file for:\n"));
15149 show (stream, "32", &column, &first);
15150 show (stream, "o64", &column, &first);
15151 show (stream, "n32", &column, &first);
15152 show (stream, "64", &column, &first);
15153 show (stream, "eabi", &column, &first);
15155 fputc ('\n', stream);
15157 fprintf (stream, _("\
15158 -32 create o32 ABI object file (default)\n\
15159 -n32 create n32 ABI object file\n\
15160 -64 create 64 ABI object file\n"));
15165 mips_dwarf2_format ()
15167 if (mips_abi == N64_ABI)
15170 return dwarf2_format_64bit_irix;
15172 return dwarf2_format_64bit;
15176 return dwarf2_format_32bit;