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)
298 /* Return true if the given CPU supports the MIPS16 ASE. */
299 #define CPU_HAS_MIPS16(cpu) \
300 (strncmp (TARGET_CPU, "mips16", sizeof ("mips16") - 1) == 0 \
301 || strncmp (TARGET_CANONICAL, "mips-lsi-elf", sizeof ("mips-lsi-elf") - 1) == 0)
303 /* Return true if the given CPU supports the MIPS3D ASE. */
304 #define CPU_HAS_MIPS3D(cpu) ((cpu) == CPU_SB1 \
307 /* Return true if the given CPU supports the MDMX ASE. */
308 #define CPU_HAS_MDMX(cpu) (FALSE \
311 /* True if CPU has a dror instruction. */
312 #define CPU_HAS_DROR(CPU) ((CPU) == CPU_VR5400 || (CPU) == CPU_VR5500)
314 /* True if CPU has a ror instruction. */
315 #define CPU_HAS_ROR(CPU) CPU_HAS_DROR (CPU)
317 /* Whether the processor uses hardware interlocks to protect
318 reads from the HI and LO registers, and thus does not
319 require nops to be inserted. */
321 #define hilo_interlocks (mips_arch == CPU_R4010 \
322 || mips_arch == CPU_VR5500 \
323 || mips_arch == CPU_SB1 \
326 /* Whether the processor uses hardware interlocks to protect reads
327 from the GPRs, and thus does not require nops to be inserted. */
328 #define gpr_interlocks \
329 (mips_opts.isa != ISA_MIPS1 \
330 || mips_arch == CPU_VR5400 \
331 || mips_arch == CPU_VR5500 \
332 || mips_arch == CPU_R3900)
334 /* As with other "interlocks" this is used by hardware that has FP
335 (co-processor) interlocks. */
336 /* Itbl support may require additional care here. */
337 #define cop_interlocks (mips_arch == CPU_R4300 \
338 || mips_arch == CPU_VR5400 \
339 || mips_arch == CPU_VR5500 \
340 || mips_arch == CPU_SB1 \
343 /* Is this a mfhi or mflo instruction? */
344 #define MF_HILO_INSN(PINFO) \
345 ((PINFO & INSN_READ_HI) || (PINFO & INSN_READ_LO))
347 /* MIPS PIC level. */
349 enum mips_pic_level mips_pic;
351 /* Warn about all NOPS that the assembler generates. */
352 static int warn_nops = 0;
354 /* 1 if we should generate 32 bit offsets from the $gp register in
355 SVR4_PIC mode. Currently has no meaning in other modes. */
356 static int mips_big_got = 0;
358 /* 1 if trap instructions should used for overflow rather than break
360 static int mips_trap = 0;
362 /* 1 if double width floating point constants should not be constructed
363 by assembling two single width halves into two single width floating
364 point registers which just happen to alias the double width destination
365 register. On some architectures this aliasing can be disabled by a bit
366 in the status register, and the setting of this bit cannot be determined
367 automatically at assemble time. */
368 static int mips_disable_float_construction;
370 /* Non-zero if any .set noreorder directives were used. */
372 static int mips_any_noreorder;
374 /* Non-zero if nops should be inserted when the register referenced in
375 an mfhi/mflo instruction is read in the next two instructions. */
376 static int mips_7000_hilo_fix;
378 /* The size of the small data section. */
379 static unsigned int g_switch_value = 8;
380 /* Whether the -G option was used. */
381 static int g_switch_seen = 0;
386 /* If we can determine in advance that GP optimization won't be
387 possible, we can skip the relaxation stuff that tries to produce
388 GP-relative references. This makes delay slot optimization work
391 This function can only provide a guess, but it seems to work for
392 gcc output. It needs to guess right for gcc, otherwise gcc
393 will put what it thinks is a GP-relative instruction in a branch
396 I don't know if a fix is needed for the SVR4_PIC mode. I've only
397 fixed it for the non-PIC mode. KR 95/04/07 */
398 static int nopic_need_relax PARAMS ((symbolS *, int));
400 /* handle of the OPCODE hash table */
401 static struct hash_control *op_hash = NULL;
403 /* The opcode hash table we use for the mips16. */
404 static struct hash_control *mips16_op_hash = NULL;
406 /* This array holds the chars that always start a comment. If the
407 pre-processor is disabled, these aren't very useful */
408 const char comment_chars[] = "#";
410 /* This array holds the chars that only start a comment at the beginning of
411 a line. If the line seems to have the form '# 123 filename'
412 .line and .file directives will appear in the pre-processed output */
413 /* Note that input_file.c hand checks for '#' at the beginning of the
414 first line of the input file. This is because the compiler outputs
415 #NO_APP at the beginning of its output. */
416 /* Also note that C style comments are always supported. */
417 const char line_comment_chars[] = "#";
419 /* This array holds machine specific line separator characters. */
420 const char line_separator_chars[] = ";";
422 /* Chars that can be used to separate mant from exp in floating point nums */
423 const char EXP_CHARS[] = "eE";
425 /* Chars that mean this number is a floating point constant */
428 const char FLT_CHARS[] = "rRsSfFdDxXpP";
430 /* Also be aware that MAXIMUM_NUMBER_OF_CHARS_FOR_FLOAT may have to be
431 changed in read.c . Ideally it shouldn't have to know about it at all,
432 but nothing is ideal around here.
435 static char *insn_error;
437 static int auto_align = 1;
439 /* When outputting SVR4 PIC code, the assembler needs to know the
440 offset in the stack frame from which to restore the $gp register.
441 This is set by the .cprestore pseudo-op, and saved in this
443 static offsetT mips_cprestore_offset = -1;
445 /* Similiar for NewABI PIC code, where $gp is callee-saved. NewABI has some
446 more optimizations, it can use a register value instead of a memory-saved
447 offset and even an other register than $gp as global pointer. */
448 static offsetT mips_cpreturn_offset = -1;
449 static int mips_cpreturn_register = -1;
450 static int mips_gp_register = GP;
451 static int mips_gprel_offset = 0;
453 /* Whether mips_cprestore_offset has been set in the current function
454 (or whether it has already been warned about, if not). */
455 static int mips_cprestore_valid = 0;
457 /* This is the register which holds the stack frame, as set by the
458 .frame pseudo-op. This is needed to implement .cprestore. */
459 static int mips_frame_reg = SP;
461 /* Whether mips_frame_reg has been set in the current function
462 (or whether it has already been warned about, if not). */
463 static int mips_frame_reg_valid = 0;
465 /* To output NOP instructions correctly, we need to keep information
466 about the previous two instructions. */
468 /* Whether we are optimizing. The default value of 2 means to remove
469 unneeded NOPs and swap branch instructions when possible. A value
470 of 1 means to not swap branches. A value of 0 means to always
472 static int mips_optimize = 2;
474 /* Debugging level. -g sets this to 2. -gN sets this to N. -g0 is
475 equivalent to seeing no -g option at all. */
476 static int mips_debug = 0;
478 /* The previous instruction. */
479 static struct mips_cl_insn prev_insn;
481 /* The instruction before prev_insn. */
482 static struct mips_cl_insn prev_prev_insn;
484 /* If we don't want information for prev_insn or prev_prev_insn, we
485 point the insn_mo field at this dummy integer. */
486 static const struct mips_opcode dummy_opcode = { NULL, NULL, 0, 0, 0, 0 };
488 /* Non-zero if prev_insn is valid. */
489 static int prev_insn_valid;
491 /* The frag for the previous instruction. */
492 static struct frag *prev_insn_frag;
494 /* The offset into prev_insn_frag for the previous instruction. */
495 static long prev_insn_where;
497 /* The reloc type for the previous instruction, if any. */
498 static bfd_reloc_code_real_type prev_insn_reloc_type[3];
500 /* The reloc for the previous instruction, if any. */
501 static fixS *prev_insn_fixp[3];
503 /* Non-zero if the previous instruction was in a delay slot. */
504 static int prev_insn_is_delay_slot;
506 /* Non-zero if the previous instruction was in a .set noreorder. */
507 static int prev_insn_unreordered;
509 /* Non-zero if the previous instruction uses an extend opcode (if
511 static int prev_insn_extended;
513 /* Non-zero if the previous previous instruction was in a .set
515 static int prev_prev_insn_unreordered;
517 /* If this is set, it points to a frag holding nop instructions which
518 were inserted before the start of a noreorder section. If those
519 nops turn out to be unnecessary, the size of the frag can be
521 static fragS *prev_nop_frag;
523 /* The number of nop instructions we created in prev_nop_frag. */
524 static int prev_nop_frag_holds;
526 /* The number of nop instructions that we know we need in
528 static int prev_nop_frag_required;
530 /* The number of instructions we've seen since prev_nop_frag. */
531 static int prev_nop_frag_since;
533 /* For ECOFF and ELF, relocations against symbols are done in two
534 parts, with a HI relocation and a LO relocation. Each relocation
535 has only 16 bits of space to store an addend. This means that in
536 order for the linker to handle carries correctly, it must be able
537 to locate both the HI and the LO relocation. This means that the
538 relocations must appear in order in the relocation table.
540 In order to implement this, we keep track of each unmatched HI
541 relocation. We then sort them so that they immediately precede the
542 corresponding LO relocation. */
547 struct mips_hi_fixup *next;
550 /* The section this fixup is in. */
554 /* The list of unmatched HI relocs. */
556 static struct mips_hi_fixup *mips_hi_fixup_list;
558 /* The frag containing the last explicit relocation operator.
559 Null if explicit relocations have not been used. */
561 static fragS *prev_reloc_op_frag;
563 /* Map normal MIPS register numbers to mips16 register numbers. */
565 #define X ILLEGAL_REG
566 static const int mips32_to_16_reg_map[] =
568 X, X, 2, 3, 4, 5, 6, 7,
569 X, X, X, X, X, X, X, X,
570 0, 1, X, X, X, X, X, X,
571 X, X, X, X, X, X, X, X
575 /* Map mips16 register numbers to normal MIPS register numbers. */
577 static const unsigned int mips16_to_32_reg_map[] =
579 16, 17, 2, 3, 4, 5, 6, 7
582 static int mips_fix_4122_bugs;
584 /* We don't relax branches by default, since this causes us to expand
585 `la .l2 - .l1' if there's a branch between .l1 and .l2, because we
586 fail to compute the offset before expanding the macro to the most
587 efficient expansion. */
589 static int mips_relax_branch;
591 /* Since the MIPS does not have multiple forms of PC relative
592 instructions, we do not have to do relaxing as is done on other
593 platforms. However, we do have to handle GP relative addressing
594 correctly, which turns out to be a similar problem.
596 Every macro that refers to a symbol can occur in (at least) two
597 forms, one with GP relative addressing and one without. For
598 example, loading a global variable into a register generally uses
599 a macro instruction like this:
601 If i can be addressed off the GP register (this is true if it is in
602 the .sbss or .sdata section, or if it is known to be smaller than
603 the -G argument) this will generate the following instruction:
605 This instruction will use a GPREL reloc. If i can not be addressed
606 off the GP register, the following instruction sequence will be used:
609 In this case the first instruction will have a HI16 reloc, and the
610 second reloc will have a LO16 reloc. Both relocs will be against
613 The issue here is that we may not know whether i is GP addressable
614 until after we see the instruction that uses it. Therefore, we
615 want to be able to choose the final instruction sequence only at
616 the end of the assembly. This is similar to the way other
617 platforms choose the size of a PC relative instruction only at the
620 When generating position independent code we do not use GP
621 addressing in quite the same way, but the issue still arises as
622 external symbols and local symbols must be handled differently.
624 We handle these issues by actually generating both possible
625 instruction sequences. The longer one is put in a frag_var with
626 type rs_machine_dependent. We encode what to do with the frag in
627 the subtype field. We encode (1) the number of existing bytes to
628 replace, (2) the number of new bytes to use, (3) the offset from
629 the start of the existing bytes to the first reloc we must generate
630 (that is, the offset is applied from the start of the existing
631 bytes after they are replaced by the new bytes, if any), (4) the
632 offset from the start of the existing bytes to the second reloc,
633 (5) whether a third reloc is needed (the third reloc is always four
634 bytes after the second reloc), and (6) whether to warn if this
635 variant is used (this is sometimes needed if .set nomacro or .set
636 noat is in effect). All these numbers are reasonably small.
638 Generating two instruction sequences must be handled carefully to
639 ensure that delay slots are handled correctly. Fortunately, there
640 are a limited number of cases. When the second instruction
641 sequence is generated, append_insn is directed to maintain the
642 existing delay slot information, so it continues to apply to any
643 code after the second instruction sequence. This means that the
644 second instruction sequence must not impose any requirements not
645 required by the first instruction sequence.
647 These variant frags are then handled in functions called by the
648 machine independent code. md_estimate_size_before_relax returns
649 the final size of the frag. md_convert_frag sets up the final form
650 of the frag. tc_gen_reloc adjust the first reloc and adds a second
652 #define RELAX_ENCODE(old, new, reloc1, reloc2, reloc3, warn) \
656 | (((reloc1) + 64) << 9) \
657 | (((reloc2) + 64) << 2) \
658 | ((reloc3) ? (1 << 1) : 0) \
660 #define RELAX_OLD(i) (((i) >> 23) & 0x7f)
661 #define RELAX_NEW(i) (((i) >> 16) & 0x7f)
662 #define RELAX_RELOC1(i) ((valueT) (((i) >> 9) & 0x7f) - 64)
663 #define RELAX_RELOC2(i) ((valueT) (((i) >> 2) & 0x7f) - 64)
664 #define RELAX_RELOC3(i) (((i) >> 1) & 1)
665 #define RELAX_WARN(i) ((i) & 1)
667 /* Branch without likely bit. If label is out of range, we turn:
669 beq reg1, reg2, label
679 with the following opcode replacements:
686 bltzal <-> bgezal (with jal label instead of j label)
688 Even though keeping the delay slot instruction in the delay slot of
689 the branch would be more efficient, it would be very tricky to do
690 correctly, because we'd have to introduce a variable frag *after*
691 the delay slot instruction, and expand that instead. Let's do it
692 the easy way for now, even if the branch-not-taken case now costs
693 one additional instruction. Out-of-range branches are not supposed
694 to be common, anyway.
696 Branch likely. If label is out of range, we turn:
698 beql reg1, reg2, label
699 delay slot (annulled if branch not taken)
708 delay slot (executed only if branch taken)
711 It would be possible to generate a shorter sequence by losing the
712 likely bit, generating something like:
717 delay slot (executed only if branch taken)
729 bltzall -> bgezal (with jal label instead of j label)
730 bgezall -> bltzal (ditto)
733 but it's not clear that it would actually improve performance. */
734 #define RELAX_BRANCH_ENCODE(uncond, likely, link, toofar) \
737 | ((toofar) ? 1 : 0) \
739 | ((likely) ? 4 : 0) \
740 | ((uncond) ? 8 : 0)))
741 #define RELAX_BRANCH_P(i) (((i) & 0xf0000000) == 0xc0000000)
742 #define RELAX_BRANCH_UNCOND(i) (((i) & 8) != 0)
743 #define RELAX_BRANCH_LIKELY(i) (((i) & 4) != 0)
744 #define RELAX_BRANCH_LINK(i) (((i) & 2) != 0)
745 #define RELAX_BRANCH_TOOFAR(i) (((i) & 1) != 0)
747 /* For mips16 code, we use an entirely different form of relaxation.
748 mips16 supports two versions of most instructions which take
749 immediate values: a small one which takes some small value, and a
750 larger one which takes a 16 bit value. Since branches also follow
751 this pattern, relaxing these values is required.
753 We can assemble both mips16 and normal MIPS code in a single
754 object. Therefore, we need to support this type of relaxation at
755 the same time that we support the relaxation described above. We
756 use the high bit of the subtype field to distinguish these cases.
758 The information we store for this type of relaxation is the
759 argument code found in the opcode file for this relocation, whether
760 the user explicitly requested a small or extended form, and whether
761 the relocation is in a jump or jal delay slot. That tells us the
762 size of the value, and how it should be stored. We also store
763 whether the fragment is considered to be extended or not. We also
764 store whether this is known to be a branch to a different section,
765 whether we have tried to relax this frag yet, and whether we have
766 ever extended a PC relative fragment because of a shift count. */
767 #define RELAX_MIPS16_ENCODE(type, small, ext, dslot, jal_dslot) \
770 | ((small) ? 0x100 : 0) \
771 | ((ext) ? 0x200 : 0) \
772 | ((dslot) ? 0x400 : 0) \
773 | ((jal_dslot) ? 0x800 : 0))
774 #define RELAX_MIPS16_P(i) (((i) & 0xc0000000) == 0x80000000)
775 #define RELAX_MIPS16_TYPE(i) ((i) & 0xff)
776 #define RELAX_MIPS16_USER_SMALL(i) (((i) & 0x100) != 0)
777 #define RELAX_MIPS16_USER_EXT(i) (((i) & 0x200) != 0)
778 #define RELAX_MIPS16_DSLOT(i) (((i) & 0x400) != 0)
779 #define RELAX_MIPS16_JAL_DSLOT(i) (((i) & 0x800) != 0)
780 #define RELAX_MIPS16_EXTENDED(i) (((i) & 0x1000) != 0)
781 #define RELAX_MIPS16_MARK_EXTENDED(i) ((i) | 0x1000)
782 #define RELAX_MIPS16_CLEAR_EXTENDED(i) ((i) &~ 0x1000)
783 #define RELAX_MIPS16_LONG_BRANCH(i) (((i) & 0x2000) != 0)
784 #define RELAX_MIPS16_MARK_LONG_BRANCH(i) ((i) | 0x2000)
785 #define RELAX_MIPS16_CLEAR_LONG_BRANCH(i) ((i) &~ 0x2000)
787 /* Is the given value a sign-extended 32-bit value? */
788 #define IS_SEXT_32BIT_NUM(x) \
789 (((x) &~ (offsetT) 0x7fffffff) == 0 \
790 || (((x) &~ (offsetT) 0x7fffffff) == ~ (offsetT) 0x7fffffff))
792 /* Is the given value a sign-extended 16-bit value? */
793 #define IS_SEXT_16BIT_NUM(x) \
794 (((x) &~ (offsetT) 0x7fff) == 0 \
795 || (((x) &~ (offsetT) 0x7fff) == ~ (offsetT) 0x7fff))
798 /* Prototypes for static functions. */
801 #define internalError() \
802 as_fatal (_("internal Error, line %d, %s"), __LINE__, __FILE__)
804 #define internalError() as_fatal (_("MIPS internal Error"));
807 enum mips_regclass { MIPS_GR_REG, MIPS_FP_REG, MIPS16_REG };
809 static inline bfd_boolean reloc_needs_lo_p
810 PARAMS ((bfd_reloc_code_real_type));
811 static inline bfd_boolean fixup_has_matching_lo_p
813 static int insn_uses_reg
814 PARAMS ((struct mips_cl_insn *ip, unsigned int reg,
815 enum mips_regclass class));
816 static int reg_needs_delay
817 PARAMS ((unsigned int));
818 static void mips16_mark_labels
820 static void append_insn
821 PARAMS ((char *place, struct mips_cl_insn * ip, expressionS * p,
822 bfd_reloc_code_real_type *r));
823 static void mips_no_prev_insn
825 static void mips_emit_delays
826 PARAMS ((bfd_boolean));
828 static void macro_build
829 PARAMS ((char *place, int *counter, expressionS * ep, const char *name,
830 const char *fmt, ...));
832 static void macro_build ();
834 static void mips16_macro_build
835 PARAMS ((char *, int *, expressionS *, const char *, const char *, va_list));
836 static void macro_build_jalr
837 PARAMS ((int, expressionS *));
838 static void macro_build_lui
839 PARAMS ((char *place, int *counter, expressionS * ep, int regnum));
840 static void macro_build_ldst_constoffset
841 PARAMS ((char *place, int *counter, expressionS * ep, const char *op,
842 int valreg, int breg));
844 PARAMS ((int *counter, int reg, int unsignedp));
845 static void check_absolute_expr
846 PARAMS ((struct mips_cl_insn * ip, expressionS *));
847 static void load_register
848 PARAMS ((int *, int, expressionS *, int));
849 static void load_address
850 PARAMS ((int *, int, expressionS *, int *));
851 static void move_register
852 PARAMS ((int *, int, int));
854 PARAMS ((struct mips_cl_insn * ip));
855 static void mips16_macro
856 PARAMS ((struct mips_cl_insn * ip));
857 #ifdef LOSING_COMPILER
859 PARAMS ((struct mips_cl_insn * ip));
862 PARAMS ((char *str, struct mips_cl_insn * ip));
863 static void mips16_ip
864 PARAMS ((char *str, struct mips_cl_insn * ip));
865 static void mips16_immed
866 PARAMS ((char *, unsigned int, int, offsetT, bfd_boolean, bfd_boolean,
867 bfd_boolean, unsigned long *, bfd_boolean *, unsigned short *));
868 static bfd_boolean parse_relocation
869 PARAMS ((char **, bfd_reloc_code_real_type *));
870 static size_t my_getSmallExpression
871 PARAMS ((expressionS *, bfd_reloc_code_real_type *, char *));
872 static void my_getExpression
873 PARAMS ((expressionS *, char *));
875 static int support_64bit_objects
878 static void mips_set_option_string
879 PARAMS ((const char **, const char *));
880 static symbolS *get_symbol
882 static void mips_align
883 PARAMS ((int to, int fill, symbolS *label));
886 static void s_change_sec
888 static void s_change_section
892 static void s_float_cons
894 static void s_mips_globl
898 static void s_mipsset
900 static void s_abicalls
904 static void s_cpsetup
906 static void s_cplocal
908 static void s_cprestore
910 static void s_cpreturn
912 static void s_gpvalue
916 static void s_gpdword
922 static void md_obj_begin
924 static void md_obj_end
926 static long get_number
928 static void s_mips_ent
930 static void s_mips_end
932 static void s_mips_frame
934 static void s_mips_mask
936 static void s_mips_stab
938 static void s_mips_weakext
940 static void s_mips_file
942 static void s_mips_loc
944 static bfd_boolean pic_need_relax
945 PARAMS ((symbolS *, asection *));
946 static int mips16_extended_frag
947 PARAMS ((fragS *, asection *, long));
948 static int relaxed_branch_length (fragS *, asection *, int);
949 static int validate_mips_insn
950 PARAMS ((const struct mips_opcode *));
952 PARAMS ((FILE *, const char *, int *, int *));
954 static int mips_need_elf_addend_fixup
958 /* Table and functions used to map between CPU/ISA names, and
959 ISA levels, and CPU numbers. */
963 const char *name; /* CPU or ISA name. */
964 int is_isa; /* Is this an ISA? (If 0, a CPU.) */
965 int isa; /* ISA level. */
966 int cpu; /* CPU number (default CPU if ISA). */
969 static void mips_set_architecture
970 PARAMS ((const struct mips_cpu_info *));
971 static void mips_set_tune
972 PARAMS ((const struct mips_cpu_info *));
973 static bfd_boolean mips_strict_matching_cpu_name_p
974 PARAMS ((const char *, const char *));
975 static bfd_boolean mips_matching_cpu_name_p
976 PARAMS ((const char *, const char *));
977 static const struct mips_cpu_info *mips_parse_cpu
978 PARAMS ((const char *, const char *));
979 static const struct mips_cpu_info *mips_cpu_info_from_isa
984 The following pseudo-ops from the Kane and Heinrich MIPS book
985 should be defined here, but are currently unsupported: .alias,
986 .galive, .gjaldef, .gjrlive, .livereg, .noalias.
988 The following pseudo-ops from the Kane and Heinrich MIPS book are
989 specific to the type of debugging information being generated, and
990 should be defined by the object format: .aent, .begin, .bend,
991 .bgnb, .end, .endb, .ent, .fmask, .frame, .loc, .mask, .verstamp,
994 The following pseudo-ops from the Kane and Heinrich MIPS book are
995 not MIPS CPU specific, but are also not specific to the object file
996 format. This file is probably the best place to define them, but
997 they are not currently supported: .asm0, .endr, .lab, .repeat,
1000 static const pseudo_typeS mips_pseudo_table[] =
1002 /* MIPS specific pseudo-ops. */
1003 {"option", s_option, 0},
1004 {"set", s_mipsset, 0},
1005 {"rdata", s_change_sec, 'r'},
1006 {"sdata", s_change_sec, 's'},
1007 {"livereg", s_ignore, 0},
1008 {"abicalls", s_abicalls, 0},
1009 {"cpload", s_cpload, 0},
1010 {"cpsetup", s_cpsetup, 0},
1011 {"cplocal", s_cplocal, 0},
1012 {"cprestore", s_cprestore, 0},
1013 {"cpreturn", s_cpreturn, 0},
1014 {"gpvalue", s_gpvalue, 0},
1015 {"gpword", s_gpword, 0},
1016 {"gpdword", s_gpdword, 0},
1017 {"cpadd", s_cpadd, 0},
1018 {"insn", s_insn, 0},
1020 /* Relatively generic pseudo-ops that happen to be used on MIPS
1022 {"asciiz", stringer, 1},
1023 {"bss", s_change_sec, 'b'},
1025 {"half", s_cons, 1},
1026 {"dword", s_cons, 3},
1027 {"weakext", s_mips_weakext, 0},
1029 /* These pseudo-ops are defined in read.c, but must be overridden
1030 here for one reason or another. */
1031 {"align", s_align, 0},
1032 {"byte", s_cons, 0},
1033 {"data", s_change_sec, 'd'},
1034 {"double", s_float_cons, 'd'},
1035 {"float", s_float_cons, 'f'},
1036 {"globl", s_mips_globl, 0},
1037 {"global", s_mips_globl, 0},
1038 {"hword", s_cons, 1},
1040 {"long", s_cons, 2},
1041 {"octa", s_cons, 4},
1042 {"quad", s_cons, 3},
1043 {"section", s_change_section, 0},
1044 {"short", s_cons, 1},
1045 {"single", s_float_cons, 'f'},
1046 {"stabn", s_mips_stab, 'n'},
1047 {"text", s_change_sec, 't'},
1048 {"word", s_cons, 2},
1050 { "extern", ecoff_directive_extern, 0},
1055 static const pseudo_typeS mips_nonecoff_pseudo_table[] =
1057 /* These pseudo-ops should be defined by the object file format.
1058 However, a.out doesn't support them, so we have versions here. */
1059 {"aent", s_mips_ent, 1},
1060 {"bgnb", s_ignore, 0},
1061 {"end", s_mips_end, 0},
1062 {"endb", s_ignore, 0},
1063 {"ent", s_mips_ent, 0},
1064 {"file", s_mips_file, 0},
1065 {"fmask", s_mips_mask, 'F'},
1066 {"frame", s_mips_frame, 0},
1067 {"loc", s_mips_loc, 0},
1068 {"mask", s_mips_mask, 'R'},
1069 {"verstamp", s_ignore, 0},
1073 extern void pop_insert PARAMS ((const pseudo_typeS *));
1078 pop_insert (mips_pseudo_table);
1079 if (! ECOFF_DEBUGGING)
1080 pop_insert (mips_nonecoff_pseudo_table);
1083 /* Symbols labelling the current insn. */
1085 struct insn_label_list
1087 struct insn_label_list *next;
1091 static struct insn_label_list *insn_labels;
1092 static struct insn_label_list *free_insn_labels;
1094 static void mips_clear_insn_labels PARAMS ((void));
1097 mips_clear_insn_labels ()
1099 register struct insn_label_list **pl;
1101 for (pl = &free_insn_labels; *pl != NULL; pl = &(*pl)->next)
1107 static char *expr_end;
1109 /* Expressions which appear in instructions. These are set by
1112 static expressionS imm_expr;
1113 static expressionS offset_expr;
1115 /* Relocs associated with imm_expr and offset_expr. */
1117 static bfd_reloc_code_real_type imm_reloc[3]
1118 = {BFD_RELOC_UNUSED, BFD_RELOC_UNUSED, BFD_RELOC_UNUSED};
1119 static bfd_reloc_code_real_type offset_reloc[3]
1120 = {BFD_RELOC_UNUSED, BFD_RELOC_UNUSED, BFD_RELOC_UNUSED};
1122 /* These are set by mips16_ip if an explicit extension is used. */
1124 static bfd_boolean mips16_small, mips16_ext;
1127 /* The pdr segment for per procedure frame/regmask info. Not used for
1130 static segT pdr_seg;
1133 /* The default target format to use. */
1136 mips_target_format ()
1138 switch (OUTPUT_FLAVOR)
1140 case bfd_target_aout_flavour:
1141 return target_big_endian ? "a.out-mips-big" : "a.out-mips-little";
1142 case bfd_target_ecoff_flavour:
1143 return target_big_endian ? "ecoff-bigmips" : ECOFF_LITTLE_FORMAT;
1144 case bfd_target_coff_flavour:
1146 case bfd_target_elf_flavour:
1148 /* This is traditional mips. */
1149 return (target_big_endian
1150 ? (HAVE_64BIT_OBJECTS
1151 ? "elf64-tradbigmips"
1153 ? "elf32-ntradbigmips" : "elf32-tradbigmips"))
1154 : (HAVE_64BIT_OBJECTS
1155 ? "elf64-tradlittlemips"
1157 ? "elf32-ntradlittlemips" : "elf32-tradlittlemips")));
1159 return (target_big_endian
1160 ? (HAVE_64BIT_OBJECTS
1163 ? "elf32-nbigmips" : "elf32-bigmips"))
1164 : (HAVE_64BIT_OBJECTS
1165 ? "elf64-littlemips"
1167 ? "elf32-nlittlemips" : "elf32-littlemips")));
1175 /* This function is called once, at assembler startup time. It should
1176 set up all the tables, etc. that the MD part of the assembler will need. */
1181 register const char *retval = NULL;
1185 if (! bfd_set_arch_mach (stdoutput, bfd_arch_mips, mips_arch))
1186 as_warn (_("Could not set architecture and machine"));
1188 op_hash = hash_new ();
1190 for (i = 0; i < NUMOPCODES;)
1192 const char *name = mips_opcodes[i].name;
1194 retval = hash_insert (op_hash, name, (PTR) &mips_opcodes[i]);
1197 fprintf (stderr, _("internal error: can't hash `%s': %s\n"),
1198 mips_opcodes[i].name, retval);
1199 /* Probably a memory allocation problem? Give up now. */
1200 as_fatal (_("Broken assembler. No assembly attempted."));
1204 if (mips_opcodes[i].pinfo != INSN_MACRO)
1206 if (!validate_mips_insn (&mips_opcodes[i]))
1211 while ((i < NUMOPCODES) && !strcmp (mips_opcodes[i].name, name));
1214 mips16_op_hash = hash_new ();
1217 while (i < bfd_mips16_num_opcodes)
1219 const char *name = mips16_opcodes[i].name;
1221 retval = hash_insert (mips16_op_hash, name, (PTR) &mips16_opcodes[i]);
1223 as_fatal (_("internal: can't hash `%s': %s"),
1224 mips16_opcodes[i].name, retval);
1227 if (mips16_opcodes[i].pinfo != INSN_MACRO
1228 && ((mips16_opcodes[i].match & mips16_opcodes[i].mask)
1229 != mips16_opcodes[i].match))
1231 fprintf (stderr, _("internal error: bad mips16 opcode: %s %s\n"),
1232 mips16_opcodes[i].name, mips16_opcodes[i].args);
1237 while (i < bfd_mips16_num_opcodes
1238 && strcmp (mips16_opcodes[i].name, name) == 0);
1242 as_fatal (_("Broken assembler. No assembly attempted."));
1244 /* We add all the general register names to the symbol table. This
1245 helps us detect invalid uses of them. */
1246 for (i = 0; i < 32; i++)
1250 sprintf (buf, "$%d", i);
1251 symbol_table_insert (symbol_new (buf, reg_section, i,
1252 &zero_address_frag));
1254 symbol_table_insert (symbol_new ("$ra", reg_section, RA,
1255 &zero_address_frag));
1256 symbol_table_insert (symbol_new ("$fp", reg_section, FP,
1257 &zero_address_frag));
1258 symbol_table_insert (symbol_new ("$sp", reg_section, SP,
1259 &zero_address_frag));
1260 symbol_table_insert (symbol_new ("$gp", reg_section, GP,
1261 &zero_address_frag));
1262 symbol_table_insert (symbol_new ("$at", reg_section, AT,
1263 &zero_address_frag));
1264 symbol_table_insert (symbol_new ("$kt0", reg_section, KT0,
1265 &zero_address_frag));
1266 symbol_table_insert (symbol_new ("$kt1", reg_section, KT1,
1267 &zero_address_frag));
1268 symbol_table_insert (symbol_new ("$zero", reg_section, ZERO,
1269 &zero_address_frag));
1270 symbol_table_insert (symbol_new ("$pc", reg_section, -1,
1271 &zero_address_frag));
1273 /* If we don't add these register names to the symbol table, they
1274 may end up being added as regular symbols by operand(), and then
1275 make it to the object file as undefined in case they're not
1276 regarded as local symbols. They're local in o32, since `$' is a
1277 local symbol prefix, but not in n32 or n64. */
1278 for (i = 0; i < 8; i++)
1282 sprintf (buf, "$fcc%i", i);
1283 symbol_table_insert (symbol_new (buf, reg_section, -1,
1284 &zero_address_frag));
1287 mips_no_prev_insn (FALSE);
1290 mips_cprmask[0] = 0;
1291 mips_cprmask[1] = 0;
1292 mips_cprmask[2] = 0;
1293 mips_cprmask[3] = 0;
1295 /* set the default alignment for the text section (2**2) */
1296 record_alignment (text_section, 2);
1298 if (USE_GLOBAL_POINTER_OPT)
1299 bfd_set_gp_size (stdoutput, g_switch_value);
1301 if (OUTPUT_FLAVOR == bfd_target_elf_flavour)
1303 /* On a native system, sections must be aligned to 16 byte
1304 boundaries. When configured for an embedded ELF target, we
1306 if (strcmp (TARGET_OS, "elf") != 0)
1308 (void) bfd_set_section_alignment (stdoutput, text_section, 4);
1309 (void) bfd_set_section_alignment (stdoutput, data_section, 4);
1310 (void) bfd_set_section_alignment (stdoutput, bss_section, 4);
1313 /* Create a .reginfo section for register masks and a .mdebug
1314 section for debugging information. */
1322 subseg = now_subseg;
1324 /* The ABI says this section should be loaded so that the
1325 running program can access it. However, we don't load it
1326 if we are configured for an embedded target */
1327 flags = SEC_READONLY | SEC_DATA;
1328 if (strcmp (TARGET_OS, "elf") != 0)
1329 flags |= SEC_ALLOC | SEC_LOAD;
1331 if (mips_abi != N64_ABI)
1333 sec = subseg_new (".reginfo", (subsegT) 0);
1335 bfd_set_section_flags (stdoutput, sec, flags);
1336 bfd_set_section_alignment (stdoutput, sec, HAVE_NEWABI ? 3 : 2);
1339 mips_regmask_frag = frag_more (sizeof (Elf32_External_RegInfo));
1344 /* The 64-bit ABI uses a .MIPS.options section rather than
1345 .reginfo section. */
1346 sec = subseg_new (".MIPS.options", (subsegT) 0);
1347 bfd_set_section_flags (stdoutput, sec, flags);
1348 bfd_set_section_alignment (stdoutput, sec, 3);
1351 /* Set up the option header. */
1353 Elf_Internal_Options opthdr;
1356 opthdr.kind = ODK_REGINFO;
1357 opthdr.size = (sizeof (Elf_External_Options)
1358 + sizeof (Elf64_External_RegInfo));
1361 f = frag_more (sizeof (Elf_External_Options));
1362 bfd_mips_elf_swap_options_out (stdoutput, &opthdr,
1363 (Elf_External_Options *) f);
1365 mips_regmask_frag = frag_more (sizeof (Elf64_External_RegInfo));
1370 if (ECOFF_DEBUGGING)
1372 sec = subseg_new (".mdebug", (subsegT) 0);
1373 (void) bfd_set_section_flags (stdoutput, sec,
1374 SEC_HAS_CONTENTS | SEC_READONLY);
1375 (void) bfd_set_section_alignment (stdoutput, sec, 2);
1378 else if (OUTPUT_FLAVOR == bfd_target_elf_flavour)
1380 pdr_seg = subseg_new (".pdr", (subsegT) 0);
1381 (void) bfd_set_section_flags (stdoutput, pdr_seg,
1382 SEC_READONLY | SEC_RELOC
1384 (void) bfd_set_section_alignment (stdoutput, pdr_seg, 2);
1388 subseg_set (seg, subseg);
1392 if (! ECOFF_DEBUGGING)
1399 if (! ECOFF_DEBUGGING)
1407 struct mips_cl_insn insn;
1408 bfd_reloc_code_real_type unused_reloc[3]
1409 = {BFD_RELOC_UNUSED, BFD_RELOC_UNUSED, BFD_RELOC_UNUSED};
1411 imm_expr.X_op = O_absent;
1412 offset_expr.X_op = O_absent;
1413 imm_reloc[0] = BFD_RELOC_UNUSED;
1414 imm_reloc[1] = BFD_RELOC_UNUSED;
1415 imm_reloc[2] = BFD_RELOC_UNUSED;
1416 offset_reloc[0] = BFD_RELOC_UNUSED;
1417 offset_reloc[1] = BFD_RELOC_UNUSED;
1418 offset_reloc[2] = BFD_RELOC_UNUSED;
1420 if (mips_opts.mips16)
1421 mips16_ip (str, &insn);
1424 mips_ip (str, &insn);
1425 DBG ((_("returned from mips_ip(%s) insn_opcode = 0x%x\n"),
1426 str, insn.insn_opcode));
1431 as_bad ("%s `%s'", insn_error, str);
1435 if (insn.insn_mo->pinfo == INSN_MACRO)
1437 if (mips_opts.mips16)
1438 mips16_macro (&insn);
1444 if (imm_expr.X_op != O_absent)
1445 append_insn (NULL, &insn, &imm_expr, imm_reloc);
1446 else if (offset_expr.X_op != O_absent)
1447 append_insn (NULL, &insn, &offset_expr, offset_reloc);
1449 append_insn (NULL, &insn, NULL, unused_reloc);
1453 /* Return true if the given relocation might need a matching %lo().
1454 Note that R_MIPS_GOT16 relocations only need a matching %lo() when
1455 applied to local symbols. */
1457 static inline bfd_boolean
1458 reloc_needs_lo_p (reloc)
1459 bfd_reloc_code_real_type reloc;
1461 return (reloc == BFD_RELOC_HI16_S
1462 || reloc == BFD_RELOC_MIPS_GOT16);
1465 /* Return true if the given fixup is followed by a matching R_MIPS_LO16
1468 static inline bfd_boolean
1469 fixup_has_matching_lo_p (fixp)
1472 return (fixp->fx_next != NULL
1473 && fixp->fx_next->fx_r_type == BFD_RELOC_LO16
1474 && fixp->fx_addsy == fixp->fx_next->fx_addsy
1475 && fixp->fx_offset == fixp->fx_next->fx_offset);
1478 /* See whether instruction IP reads register REG. CLASS is the type
1482 insn_uses_reg (ip, reg, class)
1483 struct mips_cl_insn *ip;
1485 enum mips_regclass class;
1487 if (class == MIPS16_REG)
1489 assert (mips_opts.mips16);
1490 reg = mips16_to_32_reg_map[reg];
1491 class = MIPS_GR_REG;
1494 /* Don't report on general register ZERO, since it never changes. */
1495 if (class == MIPS_GR_REG && reg == ZERO)
1498 if (class == MIPS_FP_REG)
1500 assert (! mips_opts.mips16);
1501 /* If we are called with either $f0 or $f1, we must check $f0.
1502 This is not optimal, because it will introduce an unnecessary
1503 NOP between "lwc1 $f0" and "swc1 $f1". To fix this we would
1504 need to distinguish reading both $f0 and $f1 or just one of
1505 them. Note that we don't have to check the other way,
1506 because there is no instruction that sets both $f0 and $f1
1507 and requires a delay. */
1508 if ((ip->insn_mo->pinfo & INSN_READ_FPR_S)
1509 && ((((ip->insn_opcode >> OP_SH_FS) & OP_MASK_FS) &~(unsigned)1)
1510 == (reg &~ (unsigned) 1)))
1512 if ((ip->insn_mo->pinfo & INSN_READ_FPR_T)
1513 && ((((ip->insn_opcode >> OP_SH_FT) & OP_MASK_FT) &~(unsigned)1)
1514 == (reg &~ (unsigned) 1)))
1517 else if (! mips_opts.mips16)
1519 if ((ip->insn_mo->pinfo & INSN_READ_GPR_S)
1520 && ((ip->insn_opcode >> OP_SH_RS) & OP_MASK_RS) == reg)
1522 if ((ip->insn_mo->pinfo & INSN_READ_GPR_T)
1523 && ((ip->insn_opcode >> OP_SH_RT) & OP_MASK_RT) == reg)
1528 if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_X)
1529 && (mips16_to_32_reg_map[((ip->insn_opcode >> MIPS16OP_SH_RX)
1530 & MIPS16OP_MASK_RX)]
1533 if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_Y)
1534 && (mips16_to_32_reg_map[((ip->insn_opcode >> MIPS16OP_SH_RY)
1535 & MIPS16OP_MASK_RY)]
1538 if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_Z)
1539 && (mips16_to_32_reg_map[((ip->insn_opcode >> MIPS16OP_SH_MOVE32Z)
1540 & MIPS16OP_MASK_MOVE32Z)]
1543 if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_T) && reg == TREG)
1545 if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_SP) && reg == SP)
1547 if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_31) && reg == RA)
1549 if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_GPR_X)
1550 && ((ip->insn_opcode >> MIPS16OP_SH_REGR32)
1551 & MIPS16OP_MASK_REGR32) == reg)
1558 /* This function returns true if modifying a register requires a
1562 reg_needs_delay (reg)
1565 unsigned long prev_pinfo;
1567 prev_pinfo = prev_insn.insn_mo->pinfo;
1568 if (! mips_opts.noreorder
1569 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
1570 && ((prev_pinfo & INSN_LOAD_COPROC_DELAY)
1571 || (! gpr_interlocks
1572 && (prev_pinfo & INSN_LOAD_MEMORY_DELAY))))
1574 /* A load from a coprocessor or from memory. All load
1575 delays delay the use of general register rt for one
1576 instruction on the r3000. The r6000 and r4000 use
1578 /* Itbl support may require additional care here. */
1579 know (prev_pinfo & INSN_WRITE_GPR_T);
1580 if (reg == ((prev_insn.insn_opcode >> OP_SH_RT) & OP_MASK_RT))
1587 /* Mark instruction labels in mips16 mode. This permits the linker to
1588 handle them specially, such as generating jalx instructions when
1589 needed. We also make them odd for the duration of the assembly, in
1590 order to generate the right sort of code. We will make them even
1591 in the adjust_symtab routine, while leaving them marked. This is
1592 convenient for the debugger and the disassembler. The linker knows
1593 to make them odd again. */
1596 mips16_mark_labels ()
1598 if (mips_opts.mips16)
1600 struct insn_label_list *l;
1603 for (l = insn_labels; l != NULL; l = l->next)
1606 if (OUTPUT_FLAVOR == bfd_target_elf_flavour)
1607 S_SET_OTHER (l->label, STO_MIPS16);
1609 val = S_GET_VALUE (l->label);
1611 S_SET_VALUE (l->label, val + 1);
1616 /* Output an instruction. PLACE is where to put the instruction; if
1617 it is NULL, this uses frag_more to get room. IP is the instruction
1618 information. ADDRESS_EXPR is an operand of the instruction to be
1619 used with RELOC_TYPE. */
1622 append_insn (place, ip, address_expr, reloc_type)
1624 struct mips_cl_insn *ip;
1625 expressionS *address_expr;
1626 bfd_reloc_code_real_type *reloc_type;
1628 register unsigned long prev_pinfo, pinfo;
1633 /* Mark instruction labels in mips16 mode. */
1634 mips16_mark_labels ();
1636 prev_pinfo = prev_insn.insn_mo->pinfo;
1637 pinfo = ip->insn_mo->pinfo;
1639 if (place == NULL && (! mips_opts.noreorder || prev_nop_frag != NULL))
1643 /* If the previous insn required any delay slots, see if we need
1644 to insert a NOP or two. There are eight kinds of possible
1645 hazards, of which an instruction can have at most one type.
1646 (1) a load from memory delay
1647 (2) a load from a coprocessor delay
1648 (3) an unconditional branch delay
1649 (4) a conditional branch delay
1650 (5) a move to coprocessor register delay
1651 (6) a load coprocessor register from memory delay
1652 (7) a coprocessor condition code delay
1653 (8) a HI/LO special register delay
1655 There are a lot of optimizations we could do that we don't.
1656 In particular, we do not, in general, reorder instructions.
1657 If you use gcc with optimization, it will reorder
1658 instructions and generally do much more optimization then we
1659 do here; repeating all that work in the assembler would only
1660 benefit hand written assembly code, and does not seem worth
1663 /* This is how a NOP is emitted. */
1664 #define emit_nop() \
1666 ? md_number_to_chars (frag_more (2), 0x6500, 2) \
1667 : md_number_to_chars (frag_more (4), 0, 4))
1669 /* The previous insn might require a delay slot, depending upon
1670 the contents of the current insn. */
1671 if (! mips_opts.mips16
1672 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
1673 && (((prev_pinfo & INSN_LOAD_COPROC_DELAY)
1674 && ! cop_interlocks)
1675 || (! gpr_interlocks
1676 && (prev_pinfo & INSN_LOAD_MEMORY_DELAY))))
1678 /* A load from a coprocessor or from memory. All load
1679 delays delay the use of general register rt for one
1680 instruction on the r3000. The r6000 and r4000 use
1682 /* Itbl support may require additional care here. */
1683 know (prev_pinfo & INSN_WRITE_GPR_T);
1684 if (mips_optimize == 0
1685 || insn_uses_reg (ip,
1686 ((prev_insn.insn_opcode >> OP_SH_RT)
1691 else if (! mips_opts.mips16
1692 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
1693 && (((prev_pinfo & INSN_COPROC_MOVE_DELAY)
1694 && ! cop_interlocks)
1695 || (mips_opts.isa == ISA_MIPS1
1696 && (prev_pinfo & INSN_COPROC_MEMORY_DELAY))))
1698 /* A generic coprocessor delay. The previous instruction
1699 modified a coprocessor general or control register. If
1700 it modified a control register, we need to avoid any
1701 coprocessor instruction (this is probably not always
1702 required, but it sometimes is). If it modified a general
1703 register, we avoid using that register.
1705 On the r6000 and r4000 loading a coprocessor register
1706 from memory is interlocked, and does not require a delay.
1708 This case is not handled very well. There is no special
1709 knowledge of CP0 handling, and the coprocessors other
1710 than the floating point unit are not distinguished at
1712 /* Itbl support may require additional care here. FIXME!
1713 Need to modify this to include knowledge about
1714 user specified delays! */
1715 if (prev_pinfo & INSN_WRITE_FPR_T)
1717 if (mips_optimize == 0
1718 || insn_uses_reg (ip,
1719 ((prev_insn.insn_opcode >> OP_SH_FT)
1724 else if (prev_pinfo & INSN_WRITE_FPR_S)
1726 if (mips_optimize == 0
1727 || insn_uses_reg (ip,
1728 ((prev_insn.insn_opcode >> OP_SH_FS)
1735 /* We don't know exactly what the previous instruction
1736 does. If the current instruction uses a coprocessor
1737 register, we must insert a NOP. If previous
1738 instruction may set the condition codes, and the
1739 current instruction uses them, we must insert two
1741 /* Itbl support may require additional care here. */
1742 if (mips_optimize == 0
1743 || ((prev_pinfo & INSN_WRITE_COND_CODE)
1744 && (pinfo & INSN_READ_COND_CODE)))
1746 else if (pinfo & INSN_COP)
1750 else if (! mips_opts.mips16
1751 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
1752 && (prev_pinfo & INSN_WRITE_COND_CODE)
1753 && ! cop_interlocks)
1755 /* The previous instruction sets the coprocessor condition
1756 codes, but does not require a general coprocessor delay
1757 (this means it is a floating point comparison
1758 instruction). If this instruction uses the condition
1759 codes, we need to insert a single NOP. */
1760 /* Itbl support may require additional care here. */
1761 if (mips_optimize == 0
1762 || (pinfo & INSN_READ_COND_CODE))
1766 /* If we're fixing up mfhi/mflo for the r7000 and the
1767 previous insn was an mfhi/mflo and the current insn
1768 reads the register that the mfhi/mflo wrote to, then
1771 else if (mips_7000_hilo_fix
1772 && MF_HILO_INSN (prev_pinfo)
1773 && insn_uses_reg (ip, ((prev_insn.insn_opcode >> OP_SH_RD)
1780 /* If we're fixing up mfhi/mflo for the r7000 and the
1781 2nd previous insn was an mfhi/mflo and the current insn
1782 reads the register that the mfhi/mflo wrote to, then
1785 else if (mips_7000_hilo_fix
1786 && MF_HILO_INSN (prev_prev_insn.insn_opcode)
1787 && insn_uses_reg (ip, ((prev_prev_insn.insn_opcode >> OP_SH_RD)
1795 else if (prev_pinfo & INSN_READ_LO)
1797 /* The previous instruction reads the LO register; if the
1798 current instruction writes to the LO register, we must
1799 insert two NOPS. Some newer processors have interlocks.
1800 Also the tx39's multiply instructions can be exectuted
1801 immediatly after a read from HI/LO (without the delay),
1802 though the tx39's divide insns still do require the
1804 if (! (hilo_interlocks
1805 || (mips_tune == CPU_R3900 && (pinfo & INSN_MULT)))
1806 && (mips_optimize == 0
1807 || (pinfo & INSN_WRITE_LO)))
1809 /* Most mips16 branch insns don't have a delay slot.
1810 If a read from LO is immediately followed by a branch
1811 to a write to LO we have a read followed by a write
1812 less than 2 insns away. We assume the target of
1813 a branch might be a write to LO, and insert a nop
1814 between a read and an immediately following branch. */
1815 else if (mips_opts.mips16
1816 && (mips_optimize == 0
1817 || (pinfo & MIPS16_INSN_BRANCH)))
1820 else if (prev_insn.insn_mo->pinfo & INSN_READ_HI)
1822 /* The previous instruction reads the HI register; if the
1823 current instruction writes to the HI register, we must
1824 insert a NOP. Some newer processors have interlocks.
1825 Also the note tx39's multiply above. */
1826 if (! (hilo_interlocks
1827 || (mips_tune == CPU_R3900 && (pinfo & INSN_MULT)))
1828 && (mips_optimize == 0
1829 || (pinfo & INSN_WRITE_HI)))
1831 /* Most mips16 branch insns don't have a delay slot.
1832 If a read from HI is immediately followed by a branch
1833 to a write to HI we have a read followed by a write
1834 less than 2 insns away. We assume the target of
1835 a branch might be a write to HI, and insert a nop
1836 between a read and an immediately following branch. */
1837 else if (mips_opts.mips16
1838 && (mips_optimize == 0
1839 || (pinfo & MIPS16_INSN_BRANCH)))
1843 /* If the previous instruction was in a noreorder section, then
1844 we don't want to insert the nop after all. */
1845 /* Itbl support may require additional care here. */
1846 if (prev_insn_unreordered)
1849 /* There are two cases which require two intervening
1850 instructions: 1) setting the condition codes using a move to
1851 coprocessor instruction which requires a general coprocessor
1852 delay and then reading the condition codes 2) reading the HI
1853 or LO register and then writing to it (except on processors
1854 which have interlocks). If we are not already emitting a NOP
1855 instruction, we must check for these cases compared to the
1856 instruction previous to the previous instruction. */
1857 if ((! mips_opts.mips16
1858 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
1859 && (prev_prev_insn.insn_mo->pinfo & INSN_COPROC_MOVE_DELAY)
1860 && (prev_prev_insn.insn_mo->pinfo & INSN_WRITE_COND_CODE)
1861 && (pinfo & INSN_READ_COND_CODE)
1862 && ! cop_interlocks)
1863 || ((prev_prev_insn.insn_mo->pinfo & INSN_READ_LO)
1864 && (pinfo & INSN_WRITE_LO)
1865 && ! (hilo_interlocks
1866 || (mips_tune == CPU_R3900 && (pinfo & INSN_MULT))))
1867 || ((prev_prev_insn.insn_mo->pinfo & INSN_READ_HI)
1868 && (pinfo & INSN_WRITE_HI)
1869 && ! (hilo_interlocks
1870 || (mips_tune == CPU_R3900 && (pinfo & INSN_MULT)))))
1875 if (prev_prev_insn_unreordered)
1878 if (prev_prev_nop && nops == 0)
1881 if (mips_fix_4122_bugs && prev_insn.insn_mo->name)
1883 /* We're out of bits in pinfo, so we must resort to string
1884 ops here. Shortcuts are selected based on opcodes being
1885 limited to the VR4122 instruction set. */
1887 const char *pn = prev_insn.insn_mo->name;
1888 const char *tn = ip->insn_mo->name;
1889 if (strncmp(pn, "macc", 4) == 0
1890 || strncmp(pn, "dmacc", 5) == 0)
1892 /* Errata 21 - [D]DIV[U] after [D]MACC */
1893 if (strstr (tn, "div"))
1898 /* Errata 23 - Continuous DMULT[U]/DMACC instructions */
1899 if (pn[0] == 'd' /* dmacc */
1900 && (strncmp(tn, "dmult", 5) == 0
1901 || strncmp(tn, "dmacc", 5) == 0))
1906 /* Errata 24 - MT{LO,HI} after [D]MACC */
1907 if (strcmp (tn, "mtlo") == 0
1908 || strcmp (tn, "mthi") == 0)
1914 else if (strncmp(pn, "dmult", 5) == 0
1915 && (strncmp(tn, "dmult", 5) == 0
1916 || strncmp(tn, "dmacc", 5) == 0))
1918 /* Here is the rest of errata 23. */
1921 if (nops < min_nops)
1925 /* If we are being given a nop instruction, don't bother with
1926 one of the nops we would otherwise output. This will only
1927 happen when a nop instruction is used with mips_optimize set
1930 && ! mips_opts.noreorder
1931 && ip->insn_opcode == (unsigned) (mips_opts.mips16 ? 0x6500 : 0))
1934 /* Now emit the right number of NOP instructions. */
1935 if (nops > 0 && ! mips_opts.noreorder)
1938 unsigned long old_frag_offset;
1940 struct insn_label_list *l;
1942 old_frag = frag_now;
1943 old_frag_offset = frag_now_fix ();
1945 for (i = 0; i < nops; i++)
1950 listing_prev_line ();
1951 /* We may be at the start of a variant frag. In case we
1952 are, make sure there is enough space for the frag
1953 after the frags created by listing_prev_line. The
1954 argument to frag_grow here must be at least as large
1955 as the argument to all other calls to frag_grow in
1956 this file. We don't have to worry about being in the
1957 middle of a variant frag, because the variants insert
1958 all needed nop instructions themselves. */
1962 for (l = insn_labels; l != NULL; l = l->next)
1966 assert (S_GET_SEGMENT (l->label) == now_seg);
1967 symbol_set_frag (l->label, frag_now);
1968 val = (valueT) frag_now_fix ();
1969 /* mips16 text labels are stored as odd. */
1970 if (mips_opts.mips16)
1972 S_SET_VALUE (l->label, val);
1975 #ifndef NO_ECOFF_DEBUGGING
1976 if (ECOFF_DEBUGGING)
1977 ecoff_fix_loc (old_frag, old_frag_offset);
1980 else if (prev_nop_frag != NULL)
1982 /* We have a frag holding nops we may be able to remove. If
1983 we don't need any nops, we can decrease the size of
1984 prev_nop_frag by the size of one instruction. If we do
1985 need some nops, we count them in prev_nops_required. */
1986 if (prev_nop_frag_since == 0)
1990 prev_nop_frag->fr_fix -= mips_opts.mips16 ? 2 : 4;
1991 --prev_nop_frag_holds;
1994 prev_nop_frag_required += nops;
1998 if (prev_prev_nop == 0)
2000 prev_nop_frag->fr_fix -= mips_opts.mips16 ? 2 : 4;
2001 --prev_nop_frag_holds;
2004 ++prev_nop_frag_required;
2007 if (prev_nop_frag_holds <= prev_nop_frag_required)
2008 prev_nop_frag = NULL;
2010 ++prev_nop_frag_since;
2012 /* Sanity check: by the time we reach the second instruction
2013 after prev_nop_frag, we should have used up all the nops
2014 one way or another. */
2015 assert (prev_nop_frag_since <= 1 || prev_nop_frag == NULL);
2021 && *reloc_type == BFD_RELOC_16_PCREL_S2
2022 && (pinfo & INSN_UNCOND_BRANCH_DELAY || pinfo & INSN_COND_BRANCH_DELAY
2023 || pinfo & INSN_COND_BRANCH_LIKELY)
2024 && mips_relax_branch
2025 /* Don't try branch relaxation within .set nomacro, or within
2026 .set noat if we use $at for PIC computations. If it turns
2027 out that the branch was out-of-range, we'll get an error. */
2028 && !mips_opts.warn_about_macros
2029 && !(mips_opts.noat && mips_pic != NO_PIC)
2030 && !mips_opts.mips16)
2032 f = frag_var (rs_machine_dependent,
2033 relaxed_branch_length
2035 (pinfo & INSN_UNCOND_BRANCH_DELAY) ? -1
2036 : (pinfo & INSN_COND_BRANCH_LIKELY) ? 1 : 0), 4,
2038 (pinfo & INSN_UNCOND_BRANCH_DELAY,
2039 pinfo & INSN_COND_BRANCH_LIKELY,
2040 pinfo & INSN_WRITE_GPR_31,
2042 address_expr->X_add_symbol,
2043 address_expr->X_add_number,
2045 *reloc_type = BFD_RELOC_UNUSED;
2047 else if (*reloc_type > BFD_RELOC_UNUSED)
2049 /* We need to set up a variant frag. */
2050 assert (mips_opts.mips16 && address_expr != NULL);
2051 f = frag_var (rs_machine_dependent, 4, 0,
2052 RELAX_MIPS16_ENCODE (*reloc_type - BFD_RELOC_UNUSED,
2053 mips16_small, mips16_ext,
2055 & INSN_UNCOND_BRANCH_DELAY),
2056 (*prev_insn_reloc_type
2057 == BFD_RELOC_MIPS16_JMP)),
2058 make_expr_symbol (address_expr), 0, NULL);
2060 else if (place != NULL)
2062 else if (mips_opts.mips16
2064 && *reloc_type != BFD_RELOC_MIPS16_JMP)
2066 /* Make sure there is enough room to swap this instruction with
2067 a following jump instruction. */
2073 if (mips_opts.mips16
2074 && mips_opts.noreorder
2075 && (prev_pinfo & INSN_UNCOND_BRANCH_DELAY) != 0)
2076 as_warn (_("extended instruction in delay slot"));
2081 fixp[0] = fixp[1] = fixp[2] = NULL;
2082 if (address_expr != NULL && *reloc_type < BFD_RELOC_UNUSED)
2084 if (address_expr->X_op == O_constant)
2088 switch (*reloc_type)
2091 ip->insn_opcode |= address_expr->X_add_number;
2094 case BFD_RELOC_MIPS_HIGHEST:
2095 tmp = (address_expr->X_add_number + 0x800080008000) >> 16;
2097 ip->insn_opcode |= (tmp >> 16) & 0xffff;
2100 case BFD_RELOC_MIPS_HIGHER:
2101 tmp = (address_expr->X_add_number + 0x80008000) >> 16;
2102 ip->insn_opcode |= (tmp >> 16) & 0xffff;
2105 case BFD_RELOC_HI16_S:
2106 ip->insn_opcode |= ((address_expr->X_add_number + 0x8000)
2110 case BFD_RELOC_HI16:
2111 ip->insn_opcode |= (address_expr->X_add_number >> 16) & 0xffff;
2114 case BFD_RELOC_LO16:
2115 case BFD_RELOC_MIPS_GOT_DISP:
2116 ip->insn_opcode |= address_expr->X_add_number & 0xffff;
2119 case BFD_RELOC_MIPS_JMP:
2120 if ((address_expr->X_add_number & 3) != 0)
2121 as_bad (_("jump to misaligned address (0x%lx)"),
2122 (unsigned long) address_expr->X_add_number);
2123 if (address_expr->X_add_number & ~0xfffffff)
2124 as_bad (_("jump address range overflow (0x%lx)"),
2125 (unsigned long) address_expr->X_add_number);
2126 ip->insn_opcode |= (address_expr->X_add_number >> 2) & 0x3ffffff;
2129 case BFD_RELOC_MIPS16_JMP:
2130 if ((address_expr->X_add_number & 3) != 0)
2131 as_bad (_("jump to misaligned address (0x%lx)"),
2132 (unsigned long) address_expr->X_add_number);
2133 if (address_expr->X_add_number & ~0xfffffff)
2134 as_bad (_("jump address range overflow (0x%lx)"),
2135 (unsigned long) address_expr->X_add_number);
2137 (((address_expr->X_add_number & 0x7c0000) << 3)
2138 | ((address_expr->X_add_number & 0xf800000) >> 7)
2139 | ((address_expr->X_add_number & 0x3fffc) >> 2));
2142 case BFD_RELOC_16_PCREL_S2:
2152 /* Don't generate a reloc if we are writing into a variant frag. */
2155 fixp[0] = fix_new_exp (frag_now, f - frag_now->fr_literal, 4,
2157 *reloc_type == BFD_RELOC_16_PCREL_S2,
2160 /* These relocations can have an addend that won't fit in
2161 4 octets for 64bit assembly. */
2162 if (HAVE_64BIT_GPRS &&
2163 (*reloc_type == BFD_RELOC_16
2164 || *reloc_type == BFD_RELOC_32
2165 || *reloc_type == BFD_RELOC_MIPS_JMP
2166 || *reloc_type == BFD_RELOC_HI16_S
2167 || *reloc_type == BFD_RELOC_LO16
2168 || *reloc_type == BFD_RELOC_GPREL16
2169 || *reloc_type == BFD_RELOC_MIPS_LITERAL
2170 || *reloc_type == BFD_RELOC_GPREL32
2171 || *reloc_type == BFD_RELOC_64
2172 || *reloc_type == BFD_RELOC_CTOR
2173 || *reloc_type == BFD_RELOC_MIPS_SUB
2174 || *reloc_type == BFD_RELOC_MIPS_HIGHEST
2175 || *reloc_type == BFD_RELOC_MIPS_HIGHER
2176 || *reloc_type == BFD_RELOC_MIPS_SCN_DISP
2177 || *reloc_type == BFD_RELOC_MIPS_REL16
2178 || *reloc_type == BFD_RELOC_MIPS_RELGOT))
2179 fixp[0]->fx_no_overflow = 1;
2181 if (reloc_needs_lo_p (*reloc_type))
2183 struct mips_hi_fixup *hi_fixup;
2185 /* Reuse the last entry if it already has a matching %lo. */
2186 hi_fixup = mips_hi_fixup_list;
2188 || !fixup_has_matching_lo_p (hi_fixup->fixp))
2190 hi_fixup = ((struct mips_hi_fixup *)
2191 xmalloc (sizeof (struct mips_hi_fixup)));
2192 hi_fixup->next = mips_hi_fixup_list;
2193 mips_hi_fixup_list = hi_fixup;
2195 hi_fixup->fixp = fixp[0];
2196 hi_fixup->seg = now_seg;
2199 if (reloc_type[1] != BFD_RELOC_UNUSED)
2201 /* FIXME: This symbol can be one of
2202 RSS_UNDEF, RSS_GP, RSS_GP0, RSS_LOC. */
2203 address_expr->X_op = O_absent;
2204 address_expr->X_add_symbol = 0;
2205 address_expr->X_add_number = 0;
2207 fixp[1] = fix_new_exp (frag_now, f - frag_now->fr_literal,
2208 4, address_expr, FALSE,
2211 /* These relocations can have an addend that won't fit in
2212 4 octets for 64bit assembly. */
2213 if (HAVE_64BIT_GPRS &&
2214 (*reloc_type == BFD_RELOC_16
2215 || *reloc_type == BFD_RELOC_32
2216 || *reloc_type == BFD_RELOC_MIPS_JMP
2217 || *reloc_type == BFD_RELOC_HI16_S
2218 || *reloc_type == BFD_RELOC_LO16
2219 || *reloc_type == BFD_RELOC_GPREL16
2220 || *reloc_type == BFD_RELOC_MIPS_LITERAL
2221 || *reloc_type == BFD_RELOC_GPREL32
2222 || *reloc_type == BFD_RELOC_64
2223 || *reloc_type == BFD_RELOC_CTOR
2224 || *reloc_type == BFD_RELOC_MIPS_SUB
2225 || *reloc_type == BFD_RELOC_MIPS_HIGHEST
2226 || *reloc_type == BFD_RELOC_MIPS_HIGHER
2227 || *reloc_type == BFD_RELOC_MIPS_SCN_DISP
2228 || *reloc_type == BFD_RELOC_MIPS_REL16
2229 || *reloc_type == BFD_RELOC_MIPS_RELGOT))
2230 fixp[1]->fx_no_overflow = 1;
2232 if (reloc_type[2] != BFD_RELOC_UNUSED)
2234 address_expr->X_op = O_absent;
2235 address_expr->X_add_symbol = 0;
2236 address_expr->X_add_number = 0;
2238 fixp[2] = fix_new_exp (frag_now,
2239 f - frag_now->fr_literal, 4,
2240 address_expr, FALSE,
2243 /* These relocations can have an addend that won't fit in
2244 4 octets for 64bit assembly. */
2245 if (HAVE_64BIT_GPRS &&
2246 (*reloc_type == BFD_RELOC_16
2247 || *reloc_type == BFD_RELOC_32
2248 || *reloc_type == BFD_RELOC_MIPS_JMP
2249 || *reloc_type == BFD_RELOC_HI16_S
2250 || *reloc_type == BFD_RELOC_LO16
2251 || *reloc_type == BFD_RELOC_GPREL16
2252 || *reloc_type == BFD_RELOC_MIPS_LITERAL
2253 || *reloc_type == BFD_RELOC_GPREL32
2254 || *reloc_type == BFD_RELOC_64
2255 || *reloc_type == BFD_RELOC_CTOR
2256 || *reloc_type == BFD_RELOC_MIPS_SUB
2257 || *reloc_type == BFD_RELOC_MIPS_HIGHEST
2258 || *reloc_type == BFD_RELOC_MIPS_HIGHER
2259 || *reloc_type == BFD_RELOC_MIPS_SCN_DISP
2260 || *reloc_type == BFD_RELOC_MIPS_REL16
2261 || *reloc_type == BFD_RELOC_MIPS_RELGOT))
2262 fixp[2]->fx_no_overflow = 1;
2269 if (! mips_opts.mips16)
2271 md_number_to_chars (f, ip->insn_opcode, 4);
2273 dwarf2_emit_insn (4);
2276 else if (*reloc_type == BFD_RELOC_MIPS16_JMP)
2278 md_number_to_chars (f, ip->insn_opcode >> 16, 2);
2279 md_number_to_chars (f + 2, ip->insn_opcode & 0xffff, 2);
2281 dwarf2_emit_insn (4);
2288 md_number_to_chars (f, 0xf000 | ip->extend, 2);
2291 md_number_to_chars (f, ip->insn_opcode, 2);
2293 dwarf2_emit_insn (ip->use_extend ? 4 : 2);
2297 /* Update the register mask information. */
2298 if (! mips_opts.mips16)
2300 if (pinfo & INSN_WRITE_GPR_D)
2301 mips_gprmask |= 1 << ((ip->insn_opcode >> OP_SH_RD) & OP_MASK_RD);
2302 if ((pinfo & (INSN_WRITE_GPR_T | INSN_READ_GPR_T)) != 0)
2303 mips_gprmask |= 1 << ((ip->insn_opcode >> OP_SH_RT) & OP_MASK_RT);
2304 if (pinfo & INSN_READ_GPR_S)
2305 mips_gprmask |= 1 << ((ip->insn_opcode >> OP_SH_RS) & OP_MASK_RS);
2306 if (pinfo & INSN_WRITE_GPR_31)
2307 mips_gprmask |= 1 << RA;
2308 if (pinfo & INSN_WRITE_FPR_D)
2309 mips_cprmask[1] |= 1 << ((ip->insn_opcode >> OP_SH_FD) & OP_MASK_FD);
2310 if ((pinfo & (INSN_WRITE_FPR_S | INSN_READ_FPR_S)) != 0)
2311 mips_cprmask[1] |= 1 << ((ip->insn_opcode >> OP_SH_FS) & OP_MASK_FS);
2312 if ((pinfo & (INSN_WRITE_FPR_T | INSN_READ_FPR_T)) != 0)
2313 mips_cprmask[1] |= 1 << ((ip->insn_opcode >> OP_SH_FT) & OP_MASK_FT);
2314 if ((pinfo & INSN_READ_FPR_R) != 0)
2315 mips_cprmask[1] |= 1 << ((ip->insn_opcode >> OP_SH_FR) & OP_MASK_FR);
2316 if (pinfo & INSN_COP)
2318 /* We don't keep enough information to sort these cases out.
2319 The itbl support does keep this information however, although
2320 we currently don't support itbl fprmats as part of the cop
2321 instruction. May want to add this support in the future. */
2323 /* Never set the bit for $0, which is always zero. */
2324 mips_gprmask &= ~1 << 0;
2328 if (pinfo & (MIPS16_INSN_WRITE_X | MIPS16_INSN_READ_X))
2329 mips_gprmask |= 1 << ((ip->insn_opcode >> MIPS16OP_SH_RX)
2330 & MIPS16OP_MASK_RX);
2331 if (pinfo & (MIPS16_INSN_WRITE_Y | MIPS16_INSN_READ_Y))
2332 mips_gprmask |= 1 << ((ip->insn_opcode >> MIPS16OP_SH_RY)
2333 & MIPS16OP_MASK_RY);
2334 if (pinfo & MIPS16_INSN_WRITE_Z)
2335 mips_gprmask |= 1 << ((ip->insn_opcode >> MIPS16OP_SH_RZ)
2336 & MIPS16OP_MASK_RZ);
2337 if (pinfo & (MIPS16_INSN_WRITE_T | MIPS16_INSN_READ_T))
2338 mips_gprmask |= 1 << TREG;
2339 if (pinfo & (MIPS16_INSN_WRITE_SP | MIPS16_INSN_READ_SP))
2340 mips_gprmask |= 1 << SP;
2341 if (pinfo & (MIPS16_INSN_WRITE_31 | MIPS16_INSN_READ_31))
2342 mips_gprmask |= 1 << RA;
2343 if (pinfo & MIPS16_INSN_WRITE_GPR_Y)
2344 mips_gprmask |= 1 << MIPS16OP_EXTRACT_REG32R (ip->insn_opcode);
2345 if (pinfo & MIPS16_INSN_READ_Z)
2346 mips_gprmask |= 1 << ((ip->insn_opcode >> MIPS16OP_SH_MOVE32Z)
2347 & MIPS16OP_MASK_MOVE32Z);
2348 if (pinfo & MIPS16_INSN_READ_GPR_X)
2349 mips_gprmask |= 1 << ((ip->insn_opcode >> MIPS16OP_SH_REGR32)
2350 & MIPS16OP_MASK_REGR32);
2353 if (place == NULL && ! mips_opts.noreorder)
2355 /* Filling the branch delay slot is more complex. We try to
2356 switch the branch with the previous instruction, which we can
2357 do if the previous instruction does not set up a condition
2358 that the branch tests and if the branch is not itself the
2359 target of any branch. */
2360 if ((pinfo & INSN_UNCOND_BRANCH_DELAY)
2361 || (pinfo & INSN_COND_BRANCH_DELAY))
2363 if (mips_optimize < 2
2364 /* If we have seen .set volatile or .set nomove, don't
2366 || mips_opts.nomove != 0
2367 /* If we had to emit any NOP instructions, then we
2368 already know we can not swap. */
2370 /* If we don't even know the previous insn, we can not
2372 || ! prev_insn_valid
2373 /* If the previous insn is already in a branch delay
2374 slot, then we can not swap. */
2375 || prev_insn_is_delay_slot
2376 /* If the previous previous insn was in a .set
2377 noreorder, we can't swap. Actually, the MIPS
2378 assembler will swap in this situation. However, gcc
2379 configured -with-gnu-as will generate code like
2385 in which we can not swap the bne and INSN. If gcc is
2386 not configured -with-gnu-as, it does not output the
2387 .set pseudo-ops. We don't have to check
2388 prev_insn_unreordered, because prev_insn_valid will
2389 be 0 in that case. We don't want to use
2390 prev_prev_insn_valid, because we do want to be able
2391 to swap at the start of a function. */
2392 || prev_prev_insn_unreordered
2393 /* If the branch is itself the target of a branch, we
2394 can not swap. We cheat on this; all we check for is
2395 whether there is a label on this instruction. If
2396 there are any branches to anything other than a
2397 label, users must use .set noreorder. */
2398 || insn_labels != NULL
2399 /* If the previous instruction is in a variant frag, we
2400 can not do the swap. This does not apply to the
2401 mips16, which uses variant frags for different
2403 || (! mips_opts.mips16
2404 && prev_insn_frag->fr_type == rs_machine_dependent)
2405 /* If the branch reads the condition codes, we don't
2406 even try to swap, because in the sequence
2411 we can not swap, and I don't feel like handling that
2413 || (! mips_opts.mips16
2414 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
2415 && (pinfo & INSN_READ_COND_CODE))
2416 /* We can not swap with an instruction that requires a
2417 delay slot, becase the target of the branch might
2418 interfere with that instruction. */
2419 || (! mips_opts.mips16
2420 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
2422 /* Itbl support may require additional care here. */
2423 & (INSN_LOAD_COPROC_DELAY
2424 | INSN_COPROC_MOVE_DELAY
2425 | INSN_WRITE_COND_CODE)))
2426 || (! (hilo_interlocks
2427 || (mips_tune == CPU_R3900 && (pinfo & INSN_MULT)))
2431 || (! mips_opts.mips16
2433 && (prev_pinfo & INSN_LOAD_MEMORY_DELAY))
2434 || (! mips_opts.mips16
2435 && mips_opts.isa == ISA_MIPS1
2436 /* Itbl support may require additional care here. */
2437 && (prev_pinfo & INSN_COPROC_MEMORY_DELAY))
2438 /* We can not swap with a branch instruction. */
2440 & (INSN_UNCOND_BRANCH_DELAY
2441 | INSN_COND_BRANCH_DELAY
2442 | INSN_COND_BRANCH_LIKELY))
2443 /* We do not swap with a trap instruction, since it
2444 complicates trap handlers to have the trap
2445 instruction be in a delay slot. */
2446 || (prev_pinfo & INSN_TRAP)
2447 /* If the branch reads a register that the previous
2448 instruction sets, we can not swap. */
2449 || (! mips_opts.mips16
2450 && (prev_pinfo & INSN_WRITE_GPR_T)
2451 && insn_uses_reg (ip,
2452 ((prev_insn.insn_opcode >> OP_SH_RT)
2455 || (! mips_opts.mips16
2456 && (prev_pinfo & INSN_WRITE_GPR_D)
2457 && insn_uses_reg (ip,
2458 ((prev_insn.insn_opcode >> OP_SH_RD)
2461 || (mips_opts.mips16
2462 && (((prev_pinfo & MIPS16_INSN_WRITE_X)
2463 && insn_uses_reg (ip,
2464 ((prev_insn.insn_opcode
2466 & MIPS16OP_MASK_RX),
2468 || ((prev_pinfo & MIPS16_INSN_WRITE_Y)
2469 && insn_uses_reg (ip,
2470 ((prev_insn.insn_opcode
2472 & MIPS16OP_MASK_RY),
2474 || ((prev_pinfo & MIPS16_INSN_WRITE_Z)
2475 && insn_uses_reg (ip,
2476 ((prev_insn.insn_opcode
2478 & MIPS16OP_MASK_RZ),
2480 || ((prev_pinfo & MIPS16_INSN_WRITE_T)
2481 && insn_uses_reg (ip, TREG, MIPS_GR_REG))
2482 || ((prev_pinfo & MIPS16_INSN_WRITE_31)
2483 && insn_uses_reg (ip, RA, MIPS_GR_REG))
2484 || ((prev_pinfo & MIPS16_INSN_WRITE_GPR_Y)
2485 && insn_uses_reg (ip,
2486 MIPS16OP_EXTRACT_REG32R (prev_insn.
2489 /* If the branch writes a register that the previous
2490 instruction sets, we can not swap (we know that
2491 branches write only to RD or to $31). */
2492 || (! mips_opts.mips16
2493 && (prev_pinfo & INSN_WRITE_GPR_T)
2494 && (((pinfo & INSN_WRITE_GPR_D)
2495 && (((prev_insn.insn_opcode >> OP_SH_RT) & OP_MASK_RT)
2496 == ((ip->insn_opcode >> OP_SH_RD) & OP_MASK_RD)))
2497 || ((pinfo & INSN_WRITE_GPR_31)
2498 && (((prev_insn.insn_opcode >> OP_SH_RT)
2501 || (! mips_opts.mips16
2502 && (prev_pinfo & INSN_WRITE_GPR_D)
2503 && (((pinfo & INSN_WRITE_GPR_D)
2504 && (((prev_insn.insn_opcode >> OP_SH_RD) & OP_MASK_RD)
2505 == ((ip->insn_opcode >> OP_SH_RD) & OP_MASK_RD)))
2506 || ((pinfo & INSN_WRITE_GPR_31)
2507 && (((prev_insn.insn_opcode >> OP_SH_RD)
2510 || (mips_opts.mips16
2511 && (pinfo & MIPS16_INSN_WRITE_31)
2512 && ((prev_pinfo & MIPS16_INSN_WRITE_31)
2513 || ((prev_pinfo & MIPS16_INSN_WRITE_GPR_Y)
2514 && (MIPS16OP_EXTRACT_REG32R (prev_insn.insn_opcode)
2516 /* If the branch writes a register that the previous
2517 instruction reads, we can not swap (we know that
2518 branches only write to RD or to $31). */
2519 || (! mips_opts.mips16
2520 && (pinfo & INSN_WRITE_GPR_D)
2521 && insn_uses_reg (&prev_insn,
2522 ((ip->insn_opcode >> OP_SH_RD)
2525 || (! mips_opts.mips16
2526 && (pinfo & INSN_WRITE_GPR_31)
2527 && insn_uses_reg (&prev_insn, RA, MIPS_GR_REG))
2528 || (mips_opts.mips16
2529 && (pinfo & MIPS16_INSN_WRITE_31)
2530 && insn_uses_reg (&prev_insn, RA, MIPS_GR_REG))
2531 /* If we are generating embedded PIC code, the branch
2532 might be expanded into a sequence which uses $at, so
2533 we can't swap with an instruction which reads it. */
2534 || (mips_pic == EMBEDDED_PIC
2535 && insn_uses_reg (&prev_insn, AT, MIPS_GR_REG))
2536 /* If the previous previous instruction has a load
2537 delay, and sets a register that the branch reads, we
2539 || (! mips_opts.mips16
2540 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
2541 /* Itbl support may require additional care here. */
2542 && ((prev_prev_insn.insn_mo->pinfo & INSN_LOAD_COPROC_DELAY)
2543 || (! gpr_interlocks
2544 && (prev_prev_insn.insn_mo->pinfo
2545 & INSN_LOAD_MEMORY_DELAY)))
2546 && insn_uses_reg (ip,
2547 ((prev_prev_insn.insn_opcode >> OP_SH_RT)
2550 /* If one instruction sets a condition code and the
2551 other one uses a condition code, we can not swap. */
2552 || ((pinfo & INSN_READ_COND_CODE)
2553 && (prev_pinfo & INSN_WRITE_COND_CODE))
2554 || ((pinfo & INSN_WRITE_COND_CODE)
2555 && (prev_pinfo & INSN_READ_COND_CODE))
2556 /* If the previous instruction uses the PC, we can not
2558 || (mips_opts.mips16
2559 && (prev_pinfo & MIPS16_INSN_READ_PC))
2560 /* If the previous instruction was extended, we can not
2562 || (mips_opts.mips16 && prev_insn_extended)
2563 /* If the previous instruction had a fixup in mips16
2564 mode, we can not swap. This normally means that the
2565 previous instruction was a 4 byte branch anyhow. */
2566 || (mips_opts.mips16 && prev_insn_fixp[0])
2567 /* If the previous instruction is a sync, sync.l, or
2568 sync.p, we can not swap. */
2569 || (prev_pinfo & INSN_SYNC))
2571 /* We could do even better for unconditional branches to
2572 portions of this object file; we could pick up the
2573 instruction at the destination, put it in the delay
2574 slot, and bump the destination address. */
2576 /* Update the previous insn information. */
2577 prev_prev_insn = *ip;
2578 prev_insn.insn_mo = &dummy_opcode;
2582 /* It looks like we can actually do the swap. */
2583 if (! mips_opts.mips16)
2588 prev_f = prev_insn_frag->fr_literal + prev_insn_where;
2589 memcpy (temp, prev_f, 4);
2590 memcpy (prev_f, f, 4);
2591 memcpy (f, temp, 4);
2592 if (prev_insn_fixp[0])
2594 prev_insn_fixp[0]->fx_frag = frag_now;
2595 prev_insn_fixp[0]->fx_where = f - frag_now->fr_literal;
2597 if (prev_insn_fixp[1])
2599 prev_insn_fixp[1]->fx_frag = frag_now;
2600 prev_insn_fixp[1]->fx_where = f - frag_now->fr_literal;
2602 if (prev_insn_fixp[2])
2604 prev_insn_fixp[2]->fx_frag = frag_now;
2605 prev_insn_fixp[2]->fx_where = f - frag_now->fr_literal;
2609 fixp[0]->fx_frag = prev_insn_frag;
2610 fixp[0]->fx_where = prev_insn_where;
2614 fixp[1]->fx_frag = prev_insn_frag;
2615 fixp[1]->fx_where = prev_insn_where;
2619 fixp[2]->fx_frag = prev_insn_frag;
2620 fixp[2]->fx_where = prev_insn_where;
2628 assert (prev_insn_fixp[0] == NULL);
2629 assert (prev_insn_fixp[1] == NULL);
2630 assert (prev_insn_fixp[2] == NULL);
2631 prev_f = prev_insn_frag->fr_literal + prev_insn_where;
2632 memcpy (temp, prev_f, 2);
2633 memcpy (prev_f, f, 2);
2634 if (*reloc_type != BFD_RELOC_MIPS16_JMP)
2636 assert (*reloc_type == BFD_RELOC_UNUSED);
2637 memcpy (f, temp, 2);
2641 memcpy (f, f + 2, 2);
2642 memcpy (f + 2, temp, 2);
2646 fixp[0]->fx_frag = prev_insn_frag;
2647 fixp[0]->fx_where = prev_insn_where;
2651 fixp[1]->fx_frag = prev_insn_frag;
2652 fixp[1]->fx_where = prev_insn_where;
2656 fixp[2]->fx_frag = prev_insn_frag;
2657 fixp[2]->fx_where = prev_insn_where;
2661 /* Update the previous insn information; leave prev_insn
2663 prev_prev_insn = *ip;
2665 prev_insn_is_delay_slot = 1;
2667 /* If that was an unconditional branch, forget the previous
2668 insn information. */
2669 if (pinfo & INSN_UNCOND_BRANCH_DELAY)
2671 prev_prev_insn.insn_mo = &dummy_opcode;
2672 prev_insn.insn_mo = &dummy_opcode;
2675 prev_insn_fixp[0] = NULL;
2676 prev_insn_fixp[1] = NULL;
2677 prev_insn_fixp[2] = NULL;
2678 prev_insn_reloc_type[0] = BFD_RELOC_UNUSED;
2679 prev_insn_reloc_type[1] = BFD_RELOC_UNUSED;
2680 prev_insn_reloc_type[2] = BFD_RELOC_UNUSED;
2681 prev_insn_extended = 0;
2683 else if (pinfo & INSN_COND_BRANCH_LIKELY)
2685 /* We don't yet optimize a branch likely. What we should do
2686 is look at the target, copy the instruction found there
2687 into the delay slot, and increment the branch to jump to
2688 the next instruction. */
2690 /* Update the previous insn information. */
2691 prev_prev_insn = *ip;
2692 prev_insn.insn_mo = &dummy_opcode;
2693 prev_insn_fixp[0] = NULL;
2694 prev_insn_fixp[1] = NULL;
2695 prev_insn_fixp[2] = NULL;
2696 prev_insn_reloc_type[0] = BFD_RELOC_UNUSED;
2697 prev_insn_reloc_type[1] = BFD_RELOC_UNUSED;
2698 prev_insn_reloc_type[2] = BFD_RELOC_UNUSED;
2699 prev_insn_extended = 0;
2703 /* Update the previous insn information. */
2705 prev_prev_insn.insn_mo = &dummy_opcode;
2707 prev_prev_insn = prev_insn;
2710 /* Any time we see a branch, we always fill the delay slot
2711 immediately; since this insn is not a branch, we know it
2712 is not in a delay slot. */
2713 prev_insn_is_delay_slot = 0;
2715 prev_insn_fixp[0] = fixp[0];
2716 prev_insn_fixp[1] = fixp[1];
2717 prev_insn_fixp[2] = fixp[2];
2718 prev_insn_reloc_type[0] = reloc_type[0];
2719 prev_insn_reloc_type[1] = reloc_type[1];
2720 prev_insn_reloc_type[2] = reloc_type[2];
2721 if (mips_opts.mips16)
2722 prev_insn_extended = (ip->use_extend
2723 || *reloc_type > BFD_RELOC_UNUSED);
2726 prev_prev_insn_unreordered = prev_insn_unreordered;
2727 prev_insn_unreordered = 0;
2728 prev_insn_frag = frag_now;
2729 prev_insn_where = f - frag_now->fr_literal;
2730 prev_insn_valid = 1;
2732 else if (place == NULL)
2734 /* We need to record a bit of information even when we are not
2735 reordering, in order to determine the base address for mips16
2736 PC relative relocs. */
2737 prev_prev_insn = prev_insn;
2739 prev_insn_reloc_type[0] = reloc_type[0];
2740 prev_insn_reloc_type[1] = reloc_type[1];
2741 prev_insn_reloc_type[2] = reloc_type[2];
2742 prev_prev_insn_unreordered = prev_insn_unreordered;
2743 prev_insn_unreordered = 1;
2746 /* We just output an insn, so the next one doesn't have a label. */
2747 mips_clear_insn_labels ();
2750 /* This function forgets that there was any previous instruction or
2751 label. If PRESERVE is non-zero, it remembers enough information to
2752 know whether nops are needed before a noreorder section. */
2755 mips_no_prev_insn (preserve)
2760 prev_insn.insn_mo = &dummy_opcode;
2761 prev_prev_insn.insn_mo = &dummy_opcode;
2762 prev_nop_frag = NULL;
2763 prev_nop_frag_holds = 0;
2764 prev_nop_frag_required = 0;
2765 prev_nop_frag_since = 0;
2767 prev_insn_valid = 0;
2768 prev_insn_is_delay_slot = 0;
2769 prev_insn_unreordered = 0;
2770 prev_insn_extended = 0;
2771 prev_insn_reloc_type[0] = BFD_RELOC_UNUSED;
2772 prev_insn_reloc_type[1] = BFD_RELOC_UNUSED;
2773 prev_insn_reloc_type[2] = BFD_RELOC_UNUSED;
2774 prev_prev_insn_unreordered = 0;
2775 mips_clear_insn_labels ();
2778 /* This function must be called whenever we turn on noreorder or emit
2779 something other than instructions. It inserts any NOPS which might
2780 be needed by the previous instruction, and clears the information
2781 kept for the previous instructions. The INSNS parameter is true if
2782 instructions are to follow. */
2785 mips_emit_delays (insns)
2788 if (! mips_opts.noreorder)
2793 if ((! mips_opts.mips16
2794 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
2795 && (! cop_interlocks
2796 && (prev_insn.insn_mo->pinfo
2797 & (INSN_LOAD_COPROC_DELAY
2798 | INSN_COPROC_MOVE_DELAY
2799 | INSN_WRITE_COND_CODE))))
2800 || (! hilo_interlocks
2801 && (prev_insn.insn_mo->pinfo
2804 || (! mips_opts.mips16
2806 && (prev_insn.insn_mo->pinfo
2807 & INSN_LOAD_MEMORY_DELAY))
2808 || (! mips_opts.mips16
2809 && mips_opts.isa == ISA_MIPS1
2810 && (prev_insn.insn_mo->pinfo
2811 & INSN_COPROC_MEMORY_DELAY)))
2813 /* Itbl support may require additional care here. */
2815 if ((! mips_opts.mips16
2816 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
2817 && (! cop_interlocks
2818 && prev_insn.insn_mo->pinfo & INSN_WRITE_COND_CODE))
2819 || (! hilo_interlocks
2820 && ((prev_insn.insn_mo->pinfo & INSN_READ_HI)
2821 || (prev_insn.insn_mo->pinfo & INSN_READ_LO))))
2824 if (prev_insn_unreordered)
2827 else if ((! mips_opts.mips16
2828 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
2829 && (! cop_interlocks
2830 && prev_prev_insn.insn_mo->pinfo & INSN_WRITE_COND_CODE))
2831 || (! hilo_interlocks
2832 && ((prev_prev_insn.insn_mo->pinfo & INSN_READ_HI)
2833 || (prev_prev_insn.insn_mo->pinfo & INSN_READ_LO))))
2835 /* Itbl support may require additional care here. */
2836 if (! prev_prev_insn_unreordered)
2840 if (mips_fix_4122_bugs && prev_insn.insn_mo->name)
2843 const char *pn = prev_insn.insn_mo->name;
2844 if (strncmp(pn, "macc", 4) == 0
2845 || strncmp(pn, "dmacc", 5) == 0
2846 || strncmp(pn, "dmult", 5) == 0)
2850 if (nops < min_nops)
2856 struct insn_label_list *l;
2860 /* Record the frag which holds the nop instructions, so
2861 that we can remove them if we don't need them. */
2862 frag_grow (mips_opts.mips16 ? nops * 2 : nops * 4);
2863 prev_nop_frag = frag_now;
2864 prev_nop_frag_holds = nops;
2865 prev_nop_frag_required = 0;
2866 prev_nop_frag_since = 0;
2869 for (; nops > 0; --nops)
2874 /* Move on to a new frag, so that it is safe to simply
2875 decrease the size of prev_nop_frag. */
2876 frag_wane (frag_now);
2880 for (l = insn_labels; l != NULL; l = l->next)
2884 assert (S_GET_SEGMENT (l->label) == now_seg);
2885 symbol_set_frag (l->label, frag_now);
2886 val = (valueT) frag_now_fix ();
2887 /* mips16 text labels are stored as odd. */
2888 if (mips_opts.mips16)
2890 S_SET_VALUE (l->label, val);
2895 /* Mark instruction labels in mips16 mode. */
2897 mips16_mark_labels ();
2899 mips_no_prev_insn (insns);
2902 /* Build an instruction created by a macro expansion. This is passed
2903 a pointer to the count of instructions created so far, an
2904 expression, the name of the instruction to build, an operand format
2905 string, and corresponding arguments. */
2909 macro_build (char *place,
2917 macro_build (place, counter, ep, name, fmt, va_alist)
2926 struct mips_cl_insn insn;
2927 bfd_reloc_code_real_type r[3];
2931 va_start (args, fmt);
2937 * If the macro is about to expand into a second instruction,
2938 * print a warning if needed. We need to pass ip as a parameter
2939 * to generate a better warning message here...
2941 if (mips_opts.warn_about_macros && place == NULL && *counter == 1)
2942 as_warn (_("Macro instruction expanded into multiple instructions"));
2945 * If the macro is about to expand into a second instruction,
2946 * and it is in a delay slot, print a warning.
2950 && mips_opts.noreorder
2951 && (prev_prev_insn.insn_mo->pinfo
2952 & (INSN_UNCOND_BRANCH_DELAY | INSN_COND_BRANCH_DELAY
2953 | INSN_COND_BRANCH_LIKELY)) != 0)
2954 as_warn (_("Macro instruction expanded into multiple instructions in a branch delay slot"));
2957 ++*counter; /* bump instruction counter */
2959 if (mips_opts.mips16)
2961 mips16_macro_build (place, counter, ep, name, fmt, args);
2966 r[0] = BFD_RELOC_UNUSED;
2967 r[1] = BFD_RELOC_UNUSED;
2968 r[2] = BFD_RELOC_UNUSED;
2969 insn.insn_mo = (struct mips_opcode *) hash_find (op_hash, name);
2970 assert (insn.insn_mo);
2971 assert (strcmp (name, insn.insn_mo->name) == 0);
2973 /* Search until we get a match for NAME. */
2976 /* It is assumed here that macros will never generate
2977 MDMX or MIPS-3D instructions. */
2978 if (strcmp (fmt, insn.insn_mo->args) == 0
2979 && insn.insn_mo->pinfo != INSN_MACRO
2980 && OPCODE_IS_MEMBER (insn.insn_mo,
2982 | (file_ase_mips16 ? INSN_MIPS16 : 0)),
2984 && (mips_arch != CPU_R4650 || (insn.insn_mo->pinfo & FP_D) == 0))
2988 assert (insn.insn_mo->name);
2989 assert (strcmp (name, insn.insn_mo->name) == 0);
2992 insn.insn_opcode = insn.insn_mo->match;
3008 insn.insn_opcode |= va_arg (args, int) << OP_SH_RT;
3012 insn.insn_opcode |= va_arg (args, int) << OP_SH_CODE;
3017 insn.insn_opcode |= va_arg (args, int) << OP_SH_FT;
3023 insn.insn_opcode |= va_arg (args, int) << OP_SH_RD;
3028 int tmp = va_arg (args, int);
3030 insn.insn_opcode |= tmp << OP_SH_RT;
3031 insn.insn_opcode |= tmp << OP_SH_RD;
3037 insn.insn_opcode |= va_arg (args, int) << OP_SH_FS;
3044 insn.insn_opcode |= va_arg (args, int) << OP_SH_SHAMT;
3048 insn.insn_opcode |= va_arg (args, int) << OP_SH_FD;
3052 insn.insn_opcode |= va_arg (args, int) << OP_SH_CODE20;
3056 insn.insn_opcode |= va_arg (args, int) << OP_SH_CODE19;
3060 insn.insn_opcode |= va_arg (args, int) << OP_SH_CODE2;
3067 insn.insn_opcode |= va_arg (args, int) << OP_SH_RS;
3073 *r = (bfd_reloc_code_real_type) va_arg (args, int);
3074 assert (*r == BFD_RELOC_GPREL16
3075 || *r == BFD_RELOC_MIPS_LITERAL
3076 || *r == BFD_RELOC_MIPS_HIGHER
3077 || *r == BFD_RELOC_HI16_S
3078 || *r == BFD_RELOC_LO16
3079 || *r == BFD_RELOC_MIPS_GOT16
3080 || *r == BFD_RELOC_MIPS_CALL16
3081 || *r == BFD_RELOC_MIPS_GOT_DISP
3082 || *r == BFD_RELOC_MIPS_GOT_PAGE
3083 || *r == BFD_RELOC_MIPS_GOT_OFST
3084 || *r == BFD_RELOC_MIPS_GOT_LO16
3085 || *r == BFD_RELOC_MIPS_CALL_LO16
3086 || (ep->X_op == O_subtract
3087 && *r == BFD_RELOC_PCREL_LO16));
3091 *r = (bfd_reloc_code_real_type) va_arg (args, int);
3093 && (ep->X_op == O_constant
3094 || (ep->X_op == O_symbol
3095 && (*r == BFD_RELOC_MIPS_HIGHEST
3096 || *r == BFD_RELOC_HI16_S
3097 || *r == BFD_RELOC_HI16
3098 || *r == BFD_RELOC_GPREL16
3099 || *r == BFD_RELOC_MIPS_GOT_HI16
3100 || *r == BFD_RELOC_MIPS_CALL_HI16))
3101 || (ep->X_op == O_subtract
3102 && *r == BFD_RELOC_PCREL_HI16_S)));
3106 assert (ep != NULL);
3108 * This allows macro() to pass an immediate expression for
3109 * creating short branches without creating a symbol.
3110 * Note that the expression still might come from the assembly
3111 * input, in which case the value is not checked for range nor
3112 * is a relocation entry generated (yuck).
3114 if (ep->X_op == O_constant)
3116 insn.insn_opcode |= (ep->X_add_number >> 2) & 0xffff;
3120 *r = BFD_RELOC_16_PCREL_S2;
3124 assert (ep != NULL);
3125 *r = BFD_RELOC_MIPS_JMP;
3129 insn.insn_opcode |= va_arg (args, unsigned long);
3138 assert (*r == BFD_RELOC_UNUSED ? ep == NULL : ep != NULL);
3140 append_insn (place, &insn, ep, r);
3144 mips16_macro_build (place, counter, ep, name, fmt, args)
3146 int *counter ATTRIBUTE_UNUSED;
3152 struct mips_cl_insn insn;
3153 bfd_reloc_code_real_type r[3]
3154 = {BFD_RELOC_UNUSED, BFD_RELOC_UNUSED, BFD_RELOC_UNUSED};
3156 insn.insn_mo = (struct mips_opcode *) hash_find (mips16_op_hash, name);
3157 assert (insn.insn_mo);
3158 assert (strcmp (name, insn.insn_mo->name) == 0);
3160 while (strcmp (fmt, insn.insn_mo->args) != 0
3161 || insn.insn_mo->pinfo == INSN_MACRO)
3164 assert (insn.insn_mo->name);
3165 assert (strcmp (name, insn.insn_mo->name) == 0);
3168 insn.insn_opcode = insn.insn_mo->match;
3169 insn.use_extend = FALSE;
3188 insn.insn_opcode |= va_arg (args, int) << MIPS16OP_SH_RY;
3193 insn.insn_opcode |= va_arg (args, int) << MIPS16OP_SH_RX;
3197 insn.insn_opcode |= va_arg (args, int) << MIPS16OP_SH_RZ;
3201 insn.insn_opcode |= va_arg (args, int) << MIPS16OP_SH_MOVE32Z;
3211 insn.insn_opcode |= va_arg (args, int) << MIPS16OP_SH_REGR32;
3218 regno = va_arg (args, int);
3219 regno = ((regno & 7) << 2) | ((regno & 0x18) >> 3);
3220 insn.insn_opcode |= regno << MIPS16OP_SH_REG32R;
3241 assert (ep != NULL);
3243 if (ep->X_op != O_constant)
3244 *r = (int) BFD_RELOC_UNUSED + c;
3247 mips16_immed (NULL, 0, c, ep->X_add_number, FALSE, FALSE,
3248 FALSE, &insn.insn_opcode, &insn.use_extend,
3251 *r = BFD_RELOC_UNUSED;
3257 insn.insn_opcode |= va_arg (args, int) << MIPS16OP_SH_IMM6;
3264 assert (*r == BFD_RELOC_UNUSED ? ep == NULL : ep != NULL);
3266 append_insn (place, &insn, ep, r);
3270 * Generate a "jalr" instruction with a relocation hint to the called
3271 * function. This occurs in NewABI PIC code.
3274 macro_build_jalr (icnt, ep)
3285 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "jalr", "d,s",
3288 fix_new_exp (frag_now, f - frag_now->fr_literal,
3289 0, ep, FALSE, BFD_RELOC_MIPS_JALR);
3293 * Generate a "lui" instruction.
3296 macro_build_lui (place, counter, ep, regnum)
3302 expressionS high_expr;
3303 struct mips_cl_insn insn;
3304 bfd_reloc_code_real_type r[3]
3305 = {BFD_RELOC_UNUSED, BFD_RELOC_UNUSED, BFD_RELOC_UNUSED};
3306 const char *name = "lui";
3307 const char *fmt = "t,u";
3309 assert (! mips_opts.mips16);
3315 high_expr.X_op = O_constant;
3316 high_expr.X_add_number = ep->X_add_number;
3319 if (high_expr.X_op == O_constant)
3321 /* we can compute the instruction now without a relocation entry */
3322 high_expr.X_add_number = ((high_expr.X_add_number + 0x8000)
3324 *r = BFD_RELOC_UNUSED;
3328 assert (ep->X_op == O_symbol);
3329 /* _gp_disp is a special case, used from s_cpload. */
3330 assert (mips_pic == NO_PIC
3332 && strcmp (S_GET_NAME (ep->X_add_symbol), "_gp_disp") == 0));
3333 *r = BFD_RELOC_HI16_S;
3337 * If the macro is about to expand into a second instruction,
3338 * print a warning if needed. We need to pass ip as a parameter
3339 * to generate a better warning message here...
3341 if (mips_opts.warn_about_macros && place == NULL && *counter == 1)
3342 as_warn (_("Macro instruction expanded into multiple instructions"));
3345 ++*counter; /* bump instruction counter */
3347 insn.insn_mo = (struct mips_opcode *) hash_find (op_hash, name);
3348 assert (insn.insn_mo);
3349 assert (strcmp (name, insn.insn_mo->name) == 0);
3350 assert (strcmp (fmt, insn.insn_mo->args) == 0);
3352 insn.insn_opcode = insn.insn_mo->match | (regnum << OP_SH_RT);
3353 if (*r == BFD_RELOC_UNUSED)
3355 insn.insn_opcode |= high_expr.X_add_number;
3356 append_insn (place, &insn, NULL, r);
3359 append_insn (place, &insn, &high_expr, r);
3362 /* Generate a sequence of instructions to do a load or store from a constant
3363 offset off of a base register (breg) into/from a target register (treg),
3364 using AT if necessary. */
3366 macro_build_ldst_constoffset (place, counter, ep, op, treg, breg)
3373 assert (ep->X_op == O_constant);
3375 /* Right now, this routine can only handle signed 32-bit contants. */
3376 if (! IS_SEXT_32BIT_NUM(ep->X_add_number))
3377 as_warn (_("operand overflow"));
3379 if (IS_SEXT_16BIT_NUM(ep->X_add_number))
3381 /* Signed 16-bit offset will fit in the op. Easy! */
3382 macro_build (place, counter, ep, op, "t,o(b)", treg,
3383 (int) BFD_RELOC_LO16, breg);
3387 /* 32-bit offset, need multiple instructions and AT, like:
3388 lui $tempreg,const_hi (BFD_RELOC_HI16_S)
3389 addu $tempreg,$tempreg,$breg
3390 <op> $treg,const_lo($tempreg) (BFD_RELOC_LO16)
3391 to handle the complete offset. */
3392 macro_build_lui (place, counter, ep, AT);
3395 macro_build (place, counter, (expressionS *) NULL,
3396 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
3397 "d,v,t", AT, AT, breg);
3400 macro_build (place, counter, ep, op, "t,o(b)", treg,
3401 (int) BFD_RELOC_LO16, AT);
3404 as_warn (_("Macro used $at after \".set noat\""));
3409 * Generates code to set the $at register to true (one)
3410 * if reg is less than the immediate expression.
3413 set_at (counter, reg, unsignedp)
3418 if (imm_expr.X_op == O_constant
3419 && imm_expr.X_add_number >= -0x8000
3420 && imm_expr.X_add_number < 0x8000)
3421 macro_build ((char *) NULL, counter, &imm_expr,
3422 unsignedp ? "sltiu" : "slti",
3423 "t,r,j", AT, reg, (int) BFD_RELOC_LO16);
3426 load_register (counter, AT, &imm_expr, HAVE_64BIT_GPRS);
3427 macro_build ((char *) NULL, counter, (expressionS *) NULL,
3428 unsignedp ? "sltu" : "slt",
3429 "d,v,t", AT, reg, AT);
3433 /* Warn if an expression is not a constant. */
3436 check_absolute_expr (ip, ex)
3437 struct mips_cl_insn *ip;
3440 if (ex->X_op == O_big)
3441 as_bad (_("unsupported large constant"));
3442 else if (ex->X_op != O_constant)
3443 as_bad (_("Instruction %s requires absolute expression"), ip->insn_mo->name);
3446 /* Count the leading zeroes by performing a binary chop. This is a
3447 bulky bit of source, but performance is a LOT better for the
3448 majority of values than a simple loop to count the bits:
3449 for (lcnt = 0; (lcnt < 32); lcnt++)
3450 if ((v) & (1 << (31 - lcnt)))
3452 However it is not code size friendly, and the gain will drop a bit
3453 on certain cached systems.
3455 #define COUNT_TOP_ZEROES(v) \
3456 (((v) & ~0xffff) == 0 \
3457 ? ((v) & ~0xff) == 0 \
3458 ? ((v) & ~0xf) == 0 \
3459 ? ((v) & ~0x3) == 0 \
3460 ? ((v) & ~0x1) == 0 \
3465 : ((v) & ~0x7) == 0 \
3468 : ((v) & ~0x3f) == 0 \
3469 ? ((v) & ~0x1f) == 0 \
3472 : ((v) & ~0x7f) == 0 \
3475 : ((v) & ~0xfff) == 0 \
3476 ? ((v) & ~0x3ff) == 0 \
3477 ? ((v) & ~0x1ff) == 0 \
3480 : ((v) & ~0x7ff) == 0 \
3483 : ((v) & ~0x3fff) == 0 \
3484 ? ((v) & ~0x1fff) == 0 \
3487 : ((v) & ~0x7fff) == 0 \
3490 : ((v) & ~0xffffff) == 0 \
3491 ? ((v) & ~0xfffff) == 0 \
3492 ? ((v) & ~0x3ffff) == 0 \
3493 ? ((v) & ~0x1ffff) == 0 \
3496 : ((v) & ~0x7ffff) == 0 \
3499 : ((v) & ~0x3fffff) == 0 \
3500 ? ((v) & ~0x1fffff) == 0 \
3503 : ((v) & ~0x7fffff) == 0 \
3506 : ((v) & ~0xfffffff) == 0 \
3507 ? ((v) & ~0x3ffffff) == 0 \
3508 ? ((v) & ~0x1ffffff) == 0 \
3511 : ((v) & ~0x7ffffff) == 0 \
3514 : ((v) & ~0x3fffffff) == 0 \
3515 ? ((v) & ~0x1fffffff) == 0 \
3518 : ((v) & ~0x7fffffff) == 0 \
3523 * This routine generates the least number of instructions neccessary to load
3524 * an absolute expression value into a register.
3527 load_register (counter, reg, ep, dbl)
3534 expressionS hi32, lo32;
3536 if (ep->X_op != O_big)
3538 assert (ep->X_op == O_constant);
3539 if (ep->X_add_number < 0x8000
3540 && (ep->X_add_number >= 0
3541 || (ep->X_add_number >= -0x8000
3544 || sizeof (ep->X_add_number) > 4))))
3546 /* We can handle 16 bit signed values with an addiu to
3547 $zero. No need to ever use daddiu here, since $zero and
3548 the result are always correct in 32 bit mode. */
3549 macro_build ((char *) NULL, counter, ep, "addiu", "t,r,j", reg, 0,
3550 (int) BFD_RELOC_LO16);
3553 else if (ep->X_add_number >= 0 && ep->X_add_number < 0x10000)
3555 /* We can handle 16 bit unsigned values with an ori to
3557 macro_build ((char *) NULL, counter, ep, "ori", "t,r,i", reg, 0,
3558 (int) BFD_RELOC_LO16);
3561 else if ((IS_SEXT_32BIT_NUM (ep->X_add_number)
3564 || sizeof (ep->X_add_number) > 4
3565 || (ep->X_add_number & 0x80000000) == 0))
3566 || ((HAVE_32BIT_GPRS || ! dbl)
3567 && (ep->X_add_number &~ (offsetT) 0xffffffff) == 0)
3570 && ((ep->X_add_number &~ (offsetT) 0xffffffff)
3571 == ~ (offsetT) 0xffffffff)))
3573 /* 32 bit values require an lui. */
3574 macro_build ((char *) NULL, counter, ep, "lui", "t,u", reg,
3575 (int) BFD_RELOC_HI16);
3576 if ((ep->X_add_number & 0xffff) != 0)
3577 macro_build ((char *) NULL, counter, ep, "ori", "t,r,i", reg, reg,
3578 (int) BFD_RELOC_LO16);
3583 /* The value is larger than 32 bits. */
3585 if (HAVE_32BIT_GPRS)
3587 as_bad (_("Number (0x%lx) larger than 32 bits"),
3588 (unsigned long) ep->X_add_number);
3589 macro_build ((char *) NULL, counter, ep, "addiu", "t,r,j", reg, 0,
3590 (int) BFD_RELOC_LO16);
3594 if (ep->X_op != O_big)
3597 hi32.X_add_number = (valueT) hi32.X_add_number >> 16;
3598 hi32.X_add_number = (valueT) hi32.X_add_number >> 16;
3599 hi32.X_add_number &= 0xffffffff;
3601 lo32.X_add_number &= 0xffffffff;
3605 assert (ep->X_add_number > 2);
3606 if (ep->X_add_number == 3)
3607 generic_bignum[3] = 0;
3608 else if (ep->X_add_number > 4)
3609 as_bad (_("Number larger than 64 bits"));
3610 lo32.X_op = O_constant;
3611 lo32.X_add_number = generic_bignum[0] + (generic_bignum[1] << 16);
3612 hi32.X_op = O_constant;
3613 hi32.X_add_number = generic_bignum[2] + (generic_bignum[3] << 16);
3616 if (hi32.X_add_number == 0)
3621 unsigned long hi, lo;
3623 if (hi32.X_add_number == (offsetT) 0xffffffff)
3625 if ((lo32.X_add_number & 0xffff8000) == 0xffff8000)
3627 macro_build ((char *) NULL, counter, &lo32, "addiu", "t,r,j",
3628 reg, 0, (int) BFD_RELOC_LO16);
3631 if (lo32.X_add_number & 0x80000000)
3633 macro_build ((char *) NULL, counter, &lo32, "lui", "t,u", reg,
3634 (int) BFD_RELOC_HI16);
3635 if (lo32.X_add_number & 0xffff)
3636 macro_build ((char *) NULL, counter, &lo32, "ori", "t,r,i",
3637 reg, reg, (int) BFD_RELOC_LO16);
3642 /* Check for 16bit shifted constant. We know that hi32 is
3643 non-zero, so start the mask on the first bit of the hi32
3648 unsigned long himask, lomask;
3652 himask = 0xffff >> (32 - shift);
3653 lomask = (0xffff << shift) & 0xffffffff;
3657 himask = 0xffff << (shift - 32);
3660 if ((hi32.X_add_number & ~(offsetT) himask) == 0
3661 && (lo32.X_add_number & ~(offsetT) lomask) == 0)
3665 tmp.X_op = O_constant;
3667 tmp.X_add_number = ((hi32.X_add_number << (32 - shift))
3668 | (lo32.X_add_number >> shift));
3670 tmp.X_add_number = hi32.X_add_number >> (shift - 32);
3671 macro_build ((char *) NULL, counter, &tmp,
3672 "ori", "t,r,i", reg, 0,
3673 (int) BFD_RELOC_LO16);
3674 macro_build ((char *) NULL, counter, (expressionS *) NULL,
3675 (shift >= 32) ? "dsll32" : "dsll",
3677 (shift >= 32) ? shift - 32 : shift);
3682 while (shift <= (64 - 16));
3684 /* Find the bit number of the lowest one bit, and store the
3685 shifted value in hi/lo. */
3686 hi = (unsigned long) (hi32.X_add_number & 0xffffffff);
3687 lo = (unsigned long) (lo32.X_add_number & 0xffffffff);
3691 while ((lo & 1) == 0)
3696 lo |= (hi & (((unsigned long) 1 << bit) - 1)) << (32 - bit);
3702 while ((hi & 1) == 0)
3711 /* Optimize if the shifted value is a (power of 2) - 1. */
3712 if ((hi == 0 && ((lo + 1) & lo) == 0)
3713 || (lo == 0xffffffff && ((hi + 1) & hi) == 0))
3715 shift = COUNT_TOP_ZEROES ((unsigned int) hi32.X_add_number);
3720 /* This instruction will set the register to be all
3722 tmp.X_op = O_constant;
3723 tmp.X_add_number = (offsetT) -1;
3724 macro_build ((char *) NULL, counter, &tmp, "addiu", "t,r,j",
3725 reg, 0, (int) BFD_RELOC_LO16);
3729 macro_build ((char *) NULL, counter, (expressionS *) NULL,
3730 (bit >= 32) ? "dsll32" : "dsll",
3732 (bit >= 32) ? bit - 32 : bit);
3734 macro_build ((char *) NULL, counter, (expressionS *) NULL,
3735 (shift >= 32) ? "dsrl32" : "dsrl",
3737 (shift >= 32) ? shift - 32 : shift);
3742 /* Sign extend hi32 before calling load_register, because we can
3743 generally get better code when we load a sign extended value. */
3744 if ((hi32.X_add_number & 0x80000000) != 0)
3745 hi32.X_add_number |= ~(offsetT) 0xffffffff;
3746 load_register (counter, reg, &hi32, 0);
3749 if ((lo32.X_add_number & 0xffff0000) == 0)
3753 macro_build ((char *) NULL, counter, (expressionS *) NULL,
3754 "dsll32", "d,w,<", reg, freg, 0);
3762 if ((freg == 0) && (lo32.X_add_number == (offsetT) 0xffffffff))
3764 macro_build ((char *) NULL, counter, &lo32, "lui", "t,u", reg,
3765 (int) BFD_RELOC_HI16);
3766 macro_build ((char *) NULL, counter, (expressionS *) NULL,
3767 "dsrl32", "d,w,<", reg, reg, 0);
3773 macro_build ((char *) NULL, counter, (expressionS *) NULL, "dsll",
3774 "d,w,<", reg, freg, 16);
3778 mid16.X_add_number >>= 16;
3779 macro_build ((char *) NULL, counter, &mid16, "ori", "t,r,i", reg,
3780 freg, (int) BFD_RELOC_LO16);
3781 macro_build ((char *) NULL, counter, (expressionS *) NULL, "dsll",
3782 "d,w,<", reg, reg, 16);
3785 if ((lo32.X_add_number & 0xffff) != 0)
3786 macro_build ((char *) NULL, counter, &lo32, "ori", "t,r,i", reg, freg,
3787 (int) BFD_RELOC_LO16);
3790 /* Load an address into a register. */
3793 load_address (counter, reg, ep, used_at)
3801 if (ep->X_op != O_constant
3802 && ep->X_op != O_symbol)
3804 as_bad (_("expression too complex"));
3805 ep->X_op = O_constant;
3808 if (ep->X_op == O_constant)
3810 load_register (counter, reg, ep, HAVE_64BIT_ADDRESSES);
3814 if (mips_pic == NO_PIC)
3816 /* If this is a reference to a GP relative symbol, we want
3817 addiu $reg,$gp,<sym> (BFD_RELOC_GPREL16)
3819 lui $reg,<sym> (BFD_RELOC_HI16_S)
3820 addiu $reg,$reg,<sym> (BFD_RELOC_LO16)
3821 If we have an addend, we always use the latter form.
3823 With 64bit address space and a usable $at we want
3824 lui $reg,<sym> (BFD_RELOC_MIPS_HIGHEST)
3825 lui $at,<sym> (BFD_RELOC_HI16_S)
3826 daddiu $reg,<sym> (BFD_RELOC_MIPS_HIGHER)
3827 daddiu $at,<sym> (BFD_RELOC_LO16)
3831 If $at is already in use, we use a path which is suboptimal
3832 on superscalar processors.
3833 lui $reg,<sym> (BFD_RELOC_MIPS_HIGHEST)
3834 daddiu $reg,<sym> (BFD_RELOC_MIPS_HIGHER)
3836 daddiu $reg,<sym> (BFD_RELOC_HI16_S)
3838 daddiu $reg,<sym> (BFD_RELOC_LO16)
3840 if (HAVE_64BIT_ADDRESSES)
3842 /* We don't do GP optimization for now because RELAX_ENCODE can't
3843 hold the data for such large chunks. */
3845 if (*used_at == 0 && ! mips_opts.noat)
3847 macro_build (p, counter, ep, "lui", "t,u",
3848 reg, (int) BFD_RELOC_MIPS_HIGHEST);
3849 macro_build (p, counter, ep, "lui", "t,u",
3850 AT, (int) BFD_RELOC_HI16_S);
3851 macro_build (p, counter, ep, "daddiu", "t,r,j",
3852 reg, reg, (int) BFD_RELOC_MIPS_HIGHER);
3853 macro_build (p, counter, ep, "daddiu", "t,r,j",
3854 AT, AT, (int) BFD_RELOC_LO16);
3855 macro_build (p, counter, (expressionS *) NULL, "dsll32",
3856 "d,w,<", reg, reg, 0);
3857 macro_build (p, counter, (expressionS *) NULL, "daddu",
3858 "d,v,t", reg, reg, AT);
3863 macro_build (p, counter, ep, "lui", "t,u",
3864 reg, (int) BFD_RELOC_MIPS_HIGHEST);
3865 macro_build (p, counter, ep, "daddiu", "t,r,j",
3866 reg, reg, (int) BFD_RELOC_MIPS_HIGHER);
3867 macro_build (p, counter, (expressionS *) NULL, "dsll",
3868 "d,w,<", reg, reg, 16);
3869 macro_build (p, counter, ep, "daddiu", "t,r,j",
3870 reg, reg, (int) BFD_RELOC_HI16_S);
3871 macro_build (p, counter, (expressionS *) NULL, "dsll",
3872 "d,w,<", reg, reg, 16);
3873 macro_build (p, counter, ep, "daddiu", "t,r,j",
3874 reg, reg, (int) BFD_RELOC_LO16);
3879 if ((valueT) ep->X_add_number <= MAX_GPREL_OFFSET
3880 && ! nopic_need_relax (ep->X_add_symbol, 1))
3883 macro_build ((char *) NULL, counter, ep,
3884 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu", "t,r,j",
3885 reg, mips_gp_register, (int) BFD_RELOC_GPREL16);
3886 p = frag_var (rs_machine_dependent, 8, 0,
3887 RELAX_ENCODE (4, 8, 0, 4, 0,
3888 mips_opts.warn_about_macros),
3889 ep->X_add_symbol, 0, NULL);
3891 macro_build_lui (p, counter, ep, reg);
3894 macro_build (p, counter, ep,
3895 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
3896 "t,r,j", reg, reg, (int) BFD_RELOC_LO16);
3899 else if (mips_pic == SVR4_PIC && ! mips_big_got)
3903 /* If this is a reference to an external symbol, we want
3904 lw $reg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
3906 lw $reg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
3908 addiu $reg,$reg,<sym> (BFD_RELOC_LO16)
3909 If we have NewABI, we want
3910 lw $reg,<sym>($gp) (BFD_RELOC_MIPS_GOT_DISP)
3911 If there is a constant, it must be added in after. */
3912 ex.X_add_number = ep->X_add_number;
3913 ep->X_add_number = 0;
3917 macro_build ((char *) NULL, counter, ep,
3918 HAVE_32BIT_ADDRESSES ? "lw" : "ld", "t,o(b)", reg,
3919 (int) BFD_RELOC_MIPS_GOT_DISP, mips_gp_register);
3923 macro_build ((char *) NULL, counter, ep,
3924 HAVE_32BIT_ADDRESSES ? "lw" : "ld", "t,o(b)",
3925 reg, (int) BFD_RELOC_MIPS_GOT16, mips_gp_register);
3926 macro_build ((char *) NULL, counter, (expressionS *) NULL, "nop", "");
3927 p = frag_var (rs_machine_dependent, 4, 0,
3928 RELAX_ENCODE (0, 4, -8, 0, 0, mips_opts.warn_about_macros),
3929 ep->X_add_symbol, (offsetT) 0, (char *) NULL);
3930 macro_build (p, counter, ep,
3931 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
3932 "t,r,j", reg, reg, (int) BFD_RELOC_LO16);
3935 if (ex.X_add_number != 0)
3937 if (ex.X_add_number < -0x8000 || ex.X_add_number >= 0x8000)
3938 as_bad (_("PIC code offset overflow (max 16 signed bits)"));
3939 ex.X_op = O_constant;
3940 macro_build ((char *) NULL, counter, &ex,
3941 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
3942 "t,r,j", reg, reg, (int) BFD_RELOC_LO16);
3945 else if (mips_pic == SVR4_PIC)
3950 /* This is the large GOT case. If this is a reference to an
3951 external symbol, we want
3952 lui $reg,<sym> (BFD_RELOC_MIPS_GOT_HI16)
3954 lw $reg,<sym>($reg) (BFD_RELOC_MIPS_GOT_LO16)
3955 Otherwise, for a reference to a local symbol, we want
3956 lw $reg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
3958 addiu $reg,$reg,<sym> (BFD_RELOC_LO16)
3959 If we have NewABI, we want
3960 lw $reg,<sym>($gp) (BFD_RELOC_MIPS_GOT_PAGE)
3961 addiu $reg,$reg,<sym> (BFD_RELOC_MIPS_GOT_OFST)
3962 If there is a constant, it must be added in after. */
3963 ex.X_add_number = ep->X_add_number;
3964 ep->X_add_number = 0;
3967 macro_build ((char *) NULL, counter, ep,
3968 HAVE_32BIT_ADDRESSES ? "lw" : "ld", "t,o(b)", reg,
3969 (int) BFD_RELOC_MIPS_GOT_PAGE, mips_gp_register);
3970 macro_build (p, counter, ep,
3971 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu", "t,r,j",
3972 reg, reg, (int) BFD_RELOC_MIPS_GOT_OFST);
3976 if (reg_needs_delay (mips_gp_register))
3981 macro_build ((char *) NULL, counter, ep, "lui", "t,u", reg,
3982 (int) BFD_RELOC_MIPS_GOT_HI16);
3983 macro_build ((char *) NULL, counter, (expressionS *) NULL,
3984 HAVE_32BIT_ADDRESSES ? "addu" : "daddu", "d,v,t", reg,
3985 reg, mips_gp_register);
3986 macro_build ((char *) NULL, counter, ep,
3987 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
3988 "t,o(b)", reg, (int) BFD_RELOC_MIPS_GOT_LO16, reg);
3989 p = frag_var (rs_machine_dependent, 12 + off, 0,
3990 RELAX_ENCODE (12, 12 + off, off, 8 + off, 0,
3991 mips_opts.warn_about_macros),
3992 ep->X_add_symbol, 0, NULL);
3995 /* We need a nop before loading from $gp. This special
3996 check is required because the lui which starts the main
3997 instruction stream does not refer to $gp, and so will not
3998 insert the nop which may be required. */
3999 macro_build (p, counter, (expressionS *) NULL, "nop", "");
4002 macro_build (p, counter, ep,
4003 HAVE_32BIT_ADDRESSES ? "lw" : "ld", "t,o(b)", reg,
4004 (int) BFD_RELOC_MIPS_GOT16, mips_gp_register);
4006 macro_build (p, counter, (expressionS *) NULL, "nop", "");
4008 macro_build (p, counter, ep,
4009 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
4010 "t,r,j", reg, reg, (int) BFD_RELOC_LO16);
4013 if (ex.X_add_number != 0)
4015 if (ex.X_add_number < -0x8000 || ex.X_add_number >= 0x8000)
4016 as_bad (_("PIC code offset overflow (max 16 signed bits)"));
4017 ex.X_op = O_constant;
4018 macro_build ((char *) NULL, counter, &ex,
4019 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
4020 "t,r,j", reg, reg, (int) BFD_RELOC_LO16);
4023 else if (mips_pic == EMBEDDED_PIC)
4026 addiu $reg,$gp,<sym> (BFD_RELOC_GPREL16)
4028 macro_build ((char *) NULL, counter, ep,
4029 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
4030 "t,r,j", reg, mips_gp_register, (int) BFD_RELOC_GPREL16);
4036 /* Move the contents of register SOURCE into register DEST. */
4039 move_register (counter, dest, source)
4044 macro_build ((char *) NULL, counter, (expressionS *) NULL,
4045 HAVE_32BIT_GPRS ? "addu" : "daddu",
4046 "d,v,t", dest, source, 0);
4051 * This routine implements the seemingly endless macro or synthesized
4052 * instructions and addressing modes in the mips assembly language. Many
4053 * of these macros are simple and are similar to each other. These could
4054 * probably be handled by some kind of table or grammer aproach instead of
4055 * this verbose method. Others are not simple macros but are more like
4056 * optimizing code generation.
4057 * One interesting optimization is when several store macros appear
4058 * consecutivly that would load AT with the upper half of the same address.
4059 * The ensuing load upper instructions are ommited. This implies some kind
4060 * of global optimization. We currently only optimize within a single macro.
4061 * For many of the load and store macros if the address is specified as a
4062 * constant expression in the first 64k of memory (ie ld $2,0x4000c) we
4063 * first load register 'at' with zero and use it as the base register. The
4064 * mips assembler simply uses register $zero. Just one tiny optimization
4069 struct mips_cl_insn *ip;
4071 register int treg, sreg, dreg, breg;
4087 bfd_reloc_code_real_type r;
4088 int hold_mips_optimize;
4090 assert (! mips_opts.mips16);
4092 treg = (ip->insn_opcode >> 16) & 0x1f;
4093 dreg = (ip->insn_opcode >> 11) & 0x1f;
4094 sreg = breg = (ip->insn_opcode >> 21) & 0x1f;
4095 mask = ip->insn_mo->mask;
4097 expr1.X_op = O_constant;
4098 expr1.X_op_symbol = NULL;
4099 expr1.X_add_symbol = NULL;
4100 expr1.X_add_number = 1;
4102 /* Umatched fixups should not be put in the same frag as a relaxable
4103 macro. For example, suppose we have:
4107 addiu $4,$4,%lo(l1) # 3
4109 If instructions 1 and 2 were put in the same frag, md_frob_file would
4110 move the fixup for #1 after the fixups for the "unrelaxed" version of
4111 #2. This would confuse tc_gen_reloc, which expects the relocations
4112 for #2 to be the last for that frag.
4114 Also, if tc_gen_reloc sees certain relocations in a variant frag,
4115 it assumes that they belong to a relaxable macro. We mustn't put
4116 other uses of such relocations into a variant frag.
4118 To avoid both problems, finish the current frag it contains a
4119 %reloc() operator. The macro then goes into a new frag. */
4120 if (prev_reloc_op_frag == frag_now)
4122 frag_wane (frag_now);
4136 mips_emit_delays (TRUE);
4137 ++mips_opts.noreorder;
4138 mips_any_noreorder = 1;
4140 expr1.X_add_number = 8;
4141 macro_build ((char *) NULL, &icnt, &expr1, "bgez", "s,p", sreg);
4143 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "",
4146 move_register (&icnt, dreg, sreg);
4147 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
4148 dbl ? "dsub" : "sub", "d,v,t", dreg, 0, sreg);
4150 --mips_opts.noreorder;
4171 if (imm_expr.X_op == O_constant
4172 && imm_expr.X_add_number >= -0x8000
4173 && imm_expr.X_add_number < 0x8000)
4175 macro_build ((char *) NULL, &icnt, &imm_expr, s, "t,r,j", treg, sreg,
4176 (int) BFD_RELOC_LO16);
4179 load_register (&icnt, AT, &imm_expr, dbl);
4180 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s2, "d,v,t",
4200 if (imm_expr.X_op == O_constant
4201 && imm_expr.X_add_number >= 0
4202 && imm_expr.X_add_number < 0x10000)
4204 if (mask != M_NOR_I)
4205 macro_build ((char *) NULL, &icnt, &imm_expr, s, "t,r,i", treg,
4206 sreg, (int) BFD_RELOC_LO16);
4209 macro_build ((char *) NULL, &icnt, &imm_expr, "ori", "t,r,i",
4210 treg, sreg, (int) BFD_RELOC_LO16);
4211 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nor",
4212 "d,v,t", treg, treg, 0);
4217 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_GPRS);
4218 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s2, "d,v,t",
4236 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
4238 macro_build ((char *) NULL, &icnt, &offset_expr, s, "s,t,p", sreg,
4242 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_GPRS);
4243 macro_build ((char *) NULL, &icnt, &offset_expr, s, "s,t,p", sreg, AT);
4251 macro_build ((char *) NULL, &icnt, &offset_expr,
4252 likely ? "bgezl" : "bgez", "s,p", sreg);
4257 macro_build ((char *) NULL, &icnt, &offset_expr,
4258 likely ? "blezl" : "blez", "s,p", treg);
4261 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "slt", "d,v,t",
4263 macro_build ((char *) NULL, &icnt, &offset_expr,
4264 likely ? "beql" : "beq", "s,t,p", AT, 0);
4270 /* check for > max integer */
4271 maxnum = 0x7fffffff;
4272 if (HAVE_64BIT_GPRS && sizeof (maxnum) > 4)
4279 if (imm_expr.X_op == O_constant
4280 && imm_expr.X_add_number >= maxnum
4281 && (HAVE_32BIT_GPRS || sizeof (maxnum) > 4))
4284 /* result is always false */
4288 as_warn (_("Branch %s is always false (nop)"),
4290 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop",
4296 as_warn (_("Branch likely %s is always false"),
4298 macro_build ((char *) NULL, &icnt, &offset_expr, "bnel",
4303 if (imm_expr.X_op != O_constant)
4304 as_bad (_("Unsupported large constant"));
4305 ++imm_expr.X_add_number;
4309 if (mask == M_BGEL_I)
4311 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
4313 macro_build ((char *) NULL, &icnt, &offset_expr,
4314 likely ? "bgezl" : "bgez", "s,p", sreg);
4317 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 1)
4319 macro_build ((char *) NULL, &icnt, &offset_expr,
4320 likely ? "bgtzl" : "bgtz", "s,p", sreg);
4323 maxnum = 0x7fffffff;
4324 if (HAVE_64BIT_GPRS && sizeof (maxnum) > 4)
4331 maxnum = - maxnum - 1;
4332 if (imm_expr.X_op == O_constant
4333 && imm_expr.X_add_number <= maxnum
4334 && (HAVE_32BIT_GPRS || sizeof (maxnum) > 4))
4337 /* result is always true */
4338 as_warn (_("Branch %s is always true"), ip->insn_mo->name);
4339 macro_build ((char *) NULL, &icnt, &offset_expr, "b", "p");
4342 set_at (&icnt, sreg, 0);
4343 macro_build ((char *) NULL, &icnt, &offset_expr,
4344 likely ? "beql" : "beq", "s,t,p", AT, 0);
4354 macro_build ((char *) NULL, &icnt, &offset_expr,
4355 likely ? "beql" : "beq", "s,t,p", 0, treg);
4358 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sltu",
4359 "d,v,t", AT, sreg, treg);
4360 macro_build ((char *) NULL, &icnt, &offset_expr,
4361 likely ? "beql" : "beq", "s,t,p", AT, 0);
4369 && imm_expr.X_op == O_constant
4370 && imm_expr.X_add_number == (offsetT) 0xffffffff))
4372 if (imm_expr.X_op != O_constant)
4373 as_bad (_("Unsupported large constant"));
4374 ++imm_expr.X_add_number;
4378 if (mask == M_BGEUL_I)
4380 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
4382 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 1)
4384 macro_build ((char *) NULL, &icnt, &offset_expr,
4385 likely ? "bnel" : "bne", "s,t,p", sreg, 0);
4388 set_at (&icnt, sreg, 1);
4389 macro_build ((char *) NULL, &icnt, &offset_expr,
4390 likely ? "beql" : "beq", "s,t,p", AT, 0);
4398 macro_build ((char *) NULL, &icnt, &offset_expr,
4399 likely ? "bgtzl" : "bgtz", "s,p", sreg);
4404 macro_build ((char *) NULL, &icnt, &offset_expr,
4405 likely ? "bltzl" : "bltz", "s,p", treg);
4408 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "slt", "d,v,t",
4410 macro_build ((char *) NULL, &icnt, &offset_expr,
4411 likely ? "bnel" : "bne", "s,t,p", AT, 0);
4419 macro_build ((char *) NULL, &icnt, &offset_expr,
4420 likely ? "bnel" : "bne", "s,t,p", sreg, 0);
4425 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sltu",
4426 "d,v,t", AT, treg, sreg);
4427 macro_build ((char *) NULL, &icnt, &offset_expr,
4428 likely ? "bnel" : "bne", "s,t,p", AT, 0);
4436 macro_build ((char *) NULL, &icnt, &offset_expr,
4437 likely ? "blezl" : "blez", "s,p", sreg);
4442 macro_build ((char *) NULL, &icnt, &offset_expr,
4443 likely ? "bgezl" : "bgez", "s,p", treg);
4446 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "slt", "d,v,t",
4448 macro_build ((char *) NULL, &icnt, &offset_expr,
4449 likely ? "beql" : "beq", "s,t,p", AT, 0);
4455 maxnum = 0x7fffffff;
4456 if (HAVE_64BIT_GPRS && sizeof (maxnum) > 4)
4463 if (imm_expr.X_op == O_constant
4464 && imm_expr.X_add_number >= maxnum
4465 && (HAVE_32BIT_GPRS || sizeof (maxnum) > 4))
4467 if (imm_expr.X_op != O_constant)
4468 as_bad (_("Unsupported large constant"));
4469 ++imm_expr.X_add_number;
4473 if (mask == M_BLTL_I)
4475 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
4477 macro_build ((char *) NULL, &icnt, &offset_expr,
4478 likely ? "bltzl" : "bltz", "s,p", sreg);
4481 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 1)
4483 macro_build ((char *) NULL, &icnt, &offset_expr,
4484 likely ? "blezl" : "blez", "s,p", sreg);
4487 set_at (&icnt, sreg, 0);
4488 macro_build ((char *) NULL, &icnt, &offset_expr,
4489 likely ? "bnel" : "bne", "s,t,p", AT, 0);
4497 macro_build ((char *) NULL, &icnt, &offset_expr,
4498 likely ? "beql" : "beq", "s,t,p", sreg, 0);
4503 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sltu",
4504 "d,v,t", AT, treg, sreg);
4505 macro_build ((char *) NULL, &icnt, &offset_expr,
4506 likely ? "beql" : "beq", "s,t,p", AT, 0);
4514 && imm_expr.X_op == O_constant
4515 && imm_expr.X_add_number == (offsetT) 0xffffffff))
4517 if (imm_expr.X_op != O_constant)
4518 as_bad (_("Unsupported large constant"));
4519 ++imm_expr.X_add_number;
4523 if (mask == M_BLTUL_I)
4525 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
4527 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 1)
4529 macro_build ((char *) NULL, &icnt, &offset_expr,
4530 likely ? "beql" : "beq",
4534 set_at (&icnt, sreg, 1);
4535 macro_build ((char *) NULL, &icnt, &offset_expr,
4536 likely ? "bnel" : "bne", "s,t,p", AT, 0);
4544 macro_build ((char *) NULL, &icnt, &offset_expr,
4545 likely ? "bltzl" : "bltz", "s,p", sreg);
4550 macro_build ((char *) NULL, &icnt, &offset_expr,
4551 likely ? "bgtzl" : "bgtz", "s,p", treg);
4554 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "slt", "d,v,t",
4556 macro_build ((char *) NULL, &icnt, &offset_expr,
4557 likely ? "bnel" : "bne", "s,t,p", AT, 0);
4567 macro_build ((char *) NULL, &icnt, &offset_expr,
4568 likely ? "bnel" : "bne", "s,t,p", 0, treg);
4571 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sltu",
4574 macro_build ((char *) NULL, &icnt, &offset_expr,
4575 likely ? "bnel" : "bne", "s,t,p", AT, 0);
4590 as_warn (_("Divide by zero."));
4592 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "teq",
4595 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "break",
4600 mips_emit_delays (TRUE);
4601 ++mips_opts.noreorder;
4602 mips_any_noreorder = 1;
4605 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "teq",
4606 "s,t,q", treg, 0, 7);
4607 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
4608 dbl ? "ddiv" : "div", "z,s,t", sreg, treg);
4612 expr1.X_add_number = 8;
4613 macro_build ((char *) NULL, &icnt, &expr1, "bne", "s,t,p", treg, 0);
4614 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
4615 dbl ? "ddiv" : "div", "z,s,t", sreg, treg);
4616 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "break",
4619 expr1.X_add_number = -1;
4620 macro_build ((char *) NULL, &icnt, &expr1,
4621 dbl ? "daddiu" : "addiu",
4622 "t,r,j", AT, 0, (int) BFD_RELOC_LO16);
4623 expr1.X_add_number = mips_trap ? (dbl ? 12 : 8) : (dbl ? 20 : 16);
4624 macro_build ((char *) NULL, &icnt, &expr1, "bne", "s,t,p", treg, AT);
4627 expr1.X_add_number = 1;
4628 macro_build ((char *) NULL, &icnt, &expr1, "daddiu", "t,r,j", AT, 0,
4629 (int) BFD_RELOC_LO16);
4630 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "dsll32",
4631 "d,w,<", AT, AT, 31);
4635 expr1.X_add_number = 0x80000000;
4636 macro_build ((char *) NULL, &icnt, &expr1, "lui", "t,u", AT,
4637 (int) BFD_RELOC_HI16);
4641 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "teq",
4642 "s,t,q", sreg, AT, 6);
4643 /* We want to close the noreorder block as soon as possible, so
4644 that later insns are available for delay slot filling. */
4645 --mips_opts.noreorder;
4649 expr1.X_add_number = 8;
4650 macro_build ((char *) NULL, &icnt, &expr1, "bne", "s,t,p", sreg, AT);
4651 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "",
4654 /* We want to close the noreorder block as soon as possible, so
4655 that later insns are available for delay slot filling. */
4656 --mips_opts.noreorder;
4658 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "break",
4661 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "d", dreg);
4700 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
4702 as_warn (_("Divide by zero."));
4704 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "teq",
4707 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "break",
4711 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 1)
4713 if (strcmp (s2, "mflo") == 0)
4714 move_register (&icnt, dreg, sreg);
4716 move_register (&icnt, dreg, 0);
4719 if (imm_expr.X_op == O_constant
4720 && imm_expr.X_add_number == -1
4721 && s[strlen (s) - 1] != 'u')
4723 if (strcmp (s2, "mflo") == 0)
4725 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
4726 dbl ? "dneg" : "neg", "d,w", dreg, sreg);
4729 move_register (&icnt, dreg, 0);
4733 load_register (&icnt, AT, &imm_expr, dbl);
4734 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "z,s,t",
4736 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s2, "d", dreg);
4755 mips_emit_delays (TRUE);
4756 ++mips_opts.noreorder;
4757 mips_any_noreorder = 1;
4760 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "teq",
4761 "s,t,q", treg, 0, 7);
4762 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "z,s,t",
4764 /* We want to close the noreorder block as soon as possible, so
4765 that later insns are available for delay slot filling. */
4766 --mips_opts.noreorder;
4770 expr1.X_add_number = 8;
4771 macro_build ((char *) NULL, &icnt, &expr1, "bne", "s,t,p", treg, 0);
4772 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "z,s,t",
4775 /* We want to close the noreorder block as soon as possible, so
4776 that later insns are available for delay slot filling. */
4777 --mips_opts.noreorder;
4778 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "break",
4781 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s2, "d", dreg);
4787 /* Load the address of a symbol into a register. If breg is not
4788 zero, we then add a base register to it. */
4790 if (dbl && HAVE_32BIT_GPRS)
4791 as_warn (_("dla used to load 32-bit register"));
4793 if (! dbl && HAVE_64BIT_OBJECTS)
4794 as_warn (_("la used to load 64-bit address"));
4796 if (offset_expr.X_op == O_constant
4797 && offset_expr.X_add_number >= -0x8000
4798 && offset_expr.X_add_number < 0x8000)
4800 macro_build ((char *) NULL, &icnt, &offset_expr,
4801 (dbl || HAVE_64BIT_ADDRESSES) ? "daddiu" : "addiu",
4802 "t,r,j", treg, sreg, (int) BFD_RELOC_LO16);
4817 /* When generating embedded PIC code, we permit expressions of
4820 la $treg,foo-bar($breg)
4821 where bar is an address in the current section. These are used
4822 when getting the addresses of functions. We don't permit
4823 X_add_number to be non-zero, because if the symbol is
4824 external the relaxing code needs to know that any addend is
4825 purely the offset to X_op_symbol. */
4826 if (mips_pic == EMBEDDED_PIC
4827 && offset_expr.X_op == O_subtract
4828 && (symbol_constant_p (offset_expr.X_op_symbol)
4829 ? S_GET_SEGMENT (offset_expr.X_op_symbol) == now_seg
4830 : (symbol_equated_p (offset_expr.X_op_symbol)
4832 (symbol_get_value_expression (offset_expr.X_op_symbol)
4835 && (offset_expr.X_add_number == 0
4836 || OUTPUT_FLAVOR == bfd_target_elf_flavour))
4842 macro_build ((char *) NULL, &icnt, &offset_expr, "lui", "t,u",
4843 tempreg, (int) BFD_RELOC_PCREL_HI16_S);
4847 macro_build ((char *) NULL, &icnt, &offset_expr, "lui", "t,u",
4848 tempreg, (int) BFD_RELOC_PCREL_HI16_S);
4849 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
4850 (dbl || HAVE_64BIT_ADDRESSES) ? "daddu" : "addu",
4851 "d,v,t", tempreg, tempreg, breg);
4853 macro_build ((char *) NULL, &icnt, &offset_expr,
4854 (dbl || HAVE_64BIT_ADDRESSES) ? "daddiu" : "addiu",
4855 "t,r,j", treg, tempreg, (int) BFD_RELOC_PCREL_LO16);
4861 if (offset_expr.X_op != O_symbol
4862 && offset_expr.X_op != O_constant)
4864 as_bad (_("expression too complex"));
4865 offset_expr.X_op = O_constant;
4868 if (offset_expr.X_op == O_constant)
4869 load_register (&icnt, tempreg, &offset_expr,
4870 ((mips_pic == EMBEDDED_PIC || mips_pic == NO_PIC)
4871 ? (dbl || HAVE_64BIT_ADDRESSES)
4872 : HAVE_64BIT_ADDRESSES));
4873 else if (mips_pic == NO_PIC)
4875 /* If this is a reference to a GP relative symbol, we want
4876 addiu $tempreg,$gp,<sym> (BFD_RELOC_GPREL16)
4878 lui $tempreg,<sym> (BFD_RELOC_HI16_S)
4879 addiu $tempreg,$tempreg,<sym> (BFD_RELOC_LO16)
4880 If we have a constant, we need two instructions anyhow,
4881 so we may as well always use the latter form.
4883 With 64bit address space and a usable $at we want
4884 lui $tempreg,<sym> (BFD_RELOC_MIPS_HIGHEST)
4885 lui $at,<sym> (BFD_RELOC_HI16_S)
4886 daddiu $tempreg,<sym> (BFD_RELOC_MIPS_HIGHER)
4887 daddiu $at,<sym> (BFD_RELOC_LO16)
4889 daddu $tempreg,$tempreg,$at
4891 If $at is already in use, we use a path which is suboptimal
4892 on superscalar processors.
4893 lui $tempreg,<sym> (BFD_RELOC_MIPS_HIGHEST)
4894 daddiu $tempreg,<sym> (BFD_RELOC_MIPS_HIGHER)
4896 daddiu $tempreg,<sym> (BFD_RELOC_HI16_S)
4898 daddiu $tempreg,<sym> (BFD_RELOC_LO16)
4901 if (HAVE_64BIT_ADDRESSES)
4903 /* We don't do GP optimization for now because RELAX_ENCODE can't
4904 hold the data for such large chunks. */
4906 if (used_at == 0 && ! mips_opts.noat)
4908 macro_build (p, &icnt, &offset_expr, "lui", "t,u",
4909 tempreg, (int) BFD_RELOC_MIPS_HIGHEST);
4910 macro_build (p, &icnt, &offset_expr, "lui", "t,u",
4911 AT, (int) BFD_RELOC_HI16_S);
4912 macro_build (p, &icnt, &offset_expr, "daddiu", "t,r,j",
4913 tempreg, tempreg, (int) BFD_RELOC_MIPS_HIGHER);
4914 macro_build (p, &icnt, &offset_expr, "daddiu", "t,r,j",
4915 AT, AT, (int) BFD_RELOC_LO16);
4916 macro_build (p, &icnt, (expressionS *) NULL, "dsll32",
4917 "d,w,<", tempreg, tempreg, 0);
4918 macro_build (p, &icnt, (expressionS *) NULL, "daddu",
4919 "d,v,t", tempreg, tempreg, AT);
4924 macro_build (p, &icnt, &offset_expr, "lui", "t,u",
4925 tempreg, (int) BFD_RELOC_MIPS_HIGHEST);
4926 macro_build (p, &icnt, &offset_expr, "daddiu", "t,r,j",
4927 tempreg, tempreg, (int) BFD_RELOC_MIPS_HIGHER);
4928 macro_build (p, &icnt, (expressionS *) NULL, "dsll", "d,w,<",
4929 tempreg, tempreg, 16);
4930 macro_build (p, &icnt, &offset_expr, "daddiu", "t,r,j",
4931 tempreg, tempreg, (int) BFD_RELOC_HI16_S);
4932 macro_build (p, &icnt, (expressionS *) NULL, "dsll", "d,w,<",
4933 tempreg, tempreg, 16);
4934 macro_build (p, &icnt, &offset_expr, "daddiu", "t,r,j",
4935 tempreg, tempreg, (int) BFD_RELOC_LO16);
4940 if ((valueT) offset_expr.X_add_number <= MAX_GPREL_OFFSET
4941 && ! nopic_need_relax (offset_expr.X_add_symbol, 1))
4944 macro_build ((char *) NULL, &icnt, &offset_expr, "addiu",
4945 "t,r,j", tempreg, mips_gp_register,
4946 (int) BFD_RELOC_GPREL16);
4947 p = frag_var (rs_machine_dependent, 8, 0,
4948 RELAX_ENCODE (4, 8, 0, 4, 0,
4949 mips_opts.warn_about_macros),
4950 offset_expr.X_add_symbol, 0, NULL);
4952 macro_build_lui (p, &icnt, &offset_expr, tempreg);
4955 macro_build (p, &icnt, &offset_expr, "addiu",
4956 "t,r,j", tempreg, tempreg, (int) BFD_RELOC_LO16);
4959 else if (mips_pic == SVR4_PIC && ! mips_big_got)
4961 int lw_reloc_type = (int) BFD_RELOC_MIPS_GOT16;
4963 /* If this is a reference to an external symbol, and there
4964 is no constant, we want
4965 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
4966 or if tempreg is PIC_CALL_REG
4967 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_CALL16)
4968 For a local symbol, we want
4969 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
4971 addiu $tempreg,$tempreg,<sym> (BFD_RELOC_LO16)
4973 If we have a small constant, and this is a reference to
4974 an external symbol, we want
4975 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
4977 addiu $tempreg,$tempreg,<constant>
4978 For a local symbol, we want the same instruction
4979 sequence, but we output a BFD_RELOC_LO16 reloc on the
4982 If we have a large constant, and this is a reference to
4983 an external symbol, we want
4984 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
4985 lui $at,<hiconstant>
4986 addiu $at,$at,<loconstant>
4987 addu $tempreg,$tempreg,$at
4988 For a local symbol, we want the same instruction
4989 sequence, but we output a BFD_RELOC_LO16 reloc on the
4992 For NewABI, we want for local or external data addresses
4993 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT_DISP)
4994 For a local function symbol, we want
4995 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT_PAGE)
4997 addiu $tempreg,$tempreg,<sym> (BFD_RELOC_MIPS_GOT_OFST)
5000 expr1.X_add_number = offset_expr.X_add_number;
5001 offset_expr.X_add_number = 0;
5003 if (expr1.X_add_number == 0 && tempreg == PIC_CALL_REG)
5004 lw_reloc_type = (int) BFD_RELOC_MIPS_CALL16;
5005 else if (HAVE_NEWABI)
5006 lw_reloc_type = (int) BFD_RELOC_MIPS_GOT_DISP;
5007 macro_build ((char *) NULL, &icnt, &offset_expr,
5008 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
5009 "t,o(b)", tempreg, lw_reloc_type, mips_gp_register);
5010 if (expr1.X_add_number == 0)
5019 /* We're going to put in an addu instruction using
5020 tempreg, so we may as well insert the nop right
5022 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5026 p = frag_var (rs_machine_dependent, 8 - off, 0,
5027 RELAX_ENCODE (0, 8 - off, -4 - off, 4 - off, 0,
5029 ? mips_opts.warn_about_macros
5031 offset_expr.X_add_symbol, 0, NULL);
5034 macro_build (p, &icnt, (expressionS *) NULL, "nop", "");
5037 macro_build (p, &icnt, &expr1,
5038 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
5039 "t,r,j", tempreg, tempreg, (int) BFD_RELOC_LO16);
5040 /* FIXME: If breg == 0, and the next instruction uses
5041 $tempreg, then if this variant case is used an extra
5042 nop will be generated. */
5044 else if (expr1.X_add_number >= -0x8000
5045 && expr1.X_add_number < 0x8000)
5047 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5049 macro_build ((char *) NULL, &icnt, &expr1,
5050 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
5051 "t,r,j", tempreg, tempreg, (int) BFD_RELOC_LO16);
5052 frag_var (rs_machine_dependent, 0, 0,
5053 RELAX_ENCODE (0, 0, -12, -4, 0, 0),
5054 offset_expr.X_add_symbol, 0, NULL);
5060 /* If we are going to add in a base register, and the
5061 target register and the base register are the same,
5062 then we are using AT as a temporary register. Since
5063 we want to load the constant into AT, we add our
5064 current AT (from the global offset table) and the
5065 register into the register now, and pretend we were
5066 not using a base register. */
5071 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5073 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5074 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
5075 "d,v,t", treg, AT, breg);
5081 /* Set mips_optimize around the lui instruction to avoid
5082 inserting an unnecessary nop after the lw. */
5083 hold_mips_optimize = mips_optimize;
5085 macro_build_lui (NULL, &icnt, &expr1, AT);
5086 mips_optimize = hold_mips_optimize;
5088 macro_build ((char *) NULL, &icnt, &expr1,
5089 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
5090 "t,r,j", AT, AT, (int) BFD_RELOC_LO16);
5091 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5092 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
5093 "d,v,t", tempreg, tempreg, AT);
5094 frag_var (rs_machine_dependent, 0, 0,
5095 RELAX_ENCODE (0, 0, -16 + off1, -8, 0, 0),
5096 offset_expr.X_add_symbol, 0, NULL);
5100 else if (mips_pic == SVR4_PIC)
5104 int lui_reloc_type = (int) BFD_RELOC_MIPS_GOT_HI16;
5105 int lw_reloc_type = (int) BFD_RELOC_MIPS_GOT_LO16;
5106 int local_reloc_type = (int) BFD_RELOC_MIPS_GOT16;
5108 /* This is the large GOT case. If this is a reference to an
5109 external symbol, and there is no constant, we want
5110 lui $tempreg,<sym> (BFD_RELOC_MIPS_GOT_HI16)
5111 addu $tempreg,$tempreg,$gp
5112 lw $tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_LO16)
5113 or if tempreg is PIC_CALL_REG
5114 lui $tempreg,<sym> (BFD_RELOC_MIPS_CALL_HI16)
5115 addu $tempreg,$tempreg,$gp
5116 lw $tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_CALL_LO16)
5117 For a local symbol, we want
5118 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
5120 addiu $tempreg,$tempreg,<sym> (BFD_RELOC_LO16)
5122 If we have a small constant, and this is a reference to
5123 an external symbol, we want
5124 lui $tempreg,<sym> (BFD_RELOC_MIPS_GOT_HI16)
5125 addu $tempreg,$tempreg,$gp
5126 lw $tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_LO16)
5128 addiu $tempreg,$tempreg,<constant>
5129 For a local symbol, we want
5130 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
5132 addiu $tempreg,$tempreg,<constant> (BFD_RELOC_LO16)
5134 If we have a large constant, and this is a reference to
5135 an external symbol, we want
5136 lui $tempreg,<sym> (BFD_RELOC_MIPS_GOT_HI16)
5137 addu $tempreg,$tempreg,$gp
5138 lw $tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_LO16)
5139 lui $at,<hiconstant>
5140 addiu $at,$at,<loconstant>
5141 addu $tempreg,$tempreg,$at
5142 For a local symbol, we want
5143 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
5144 lui $at,<hiconstant>
5145 addiu $at,$at,<loconstant> (BFD_RELOC_LO16)
5146 addu $tempreg,$tempreg,$at
5148 For NewABI, we want for local data addresses
5149 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT_DISP)
5152 expr1.X_add_number = offset_expr.X_add_number;
5153 offset_expr.X_add_number = 0;
5155 if (reg_needs_delay (mips_gp_register))
5159 if (expr1.X_add_number == 0 && tempreg == PIC_CALL_REG)
5161 lui_reloc_type = (int) BFD_RELOC_MIPS_CALL_HI16;
5162 lw_reloc_type = (int) BFD_RELOC_MIPS_CALL_LO16;
5164 macro_build ((char *) NULL, &icnt, &offset_expr, "lui", "t,u",
5165 tempreg, lui_reloc_type);
5166 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5167 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
5168 "d,v,t", tempreg, tempreg, mips_gp_register);
5169 macro_build ((char *) NULL, &icnt, &offset_expr,
5170 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
5171 "t,o(b)", tempreg, lw_reloc_type, tempreg);
5172 if (expr1.X_add_number == 0)
5180 /* We're going to put in an addu instruction using
5181 tempreg, so we may as well insert the nop right
5183 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5188 p = frag_var (rs_machine_dependent, 12 + gpdel, 0,
5189 RELAX_ENCODE (12 + off, 12 + gpdel, gpdel,
5192 ? mips_opts.warn_about_macros
5194 offset_expr.X_add_symbol, 0, NULL);
5196 else if (expr1.X_add_number >= -0x8000
5197 && expr1.X_add_number < 0x8000)
5199 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5201 macro_build ((char *) NULL, &icnt, &expr1,
5202 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
5203 "t,r,j", tempreg, tempreg, (int) BFD_RELOC_LO16);
5205 p = frag_var (rs_machine_dependent, 12 + gpdel, 0,
5206 RELAX_ENCODE (20, 12 + gpdel, gpdel, 8 + gpdel, 0,
5208 ? mips_opts.warn_about_macros
5210 offset_expr.X_add_symbol, 0, NULL);
5216 /* If we are going to add in a base register, and the
5217 target register and the base register are the same,
5218 then we are using AT as a temporary register. Since
5219 we want to load the constant into AT, we add our
5220 current AT (from the global offset table) and the
5221 register into the register now, and pretend we were
5222 not using a base register. */
5230 assert (tempreg == AT);
5231 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5233 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5234 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
5235 "d,v,t", treg, AT, breg);
5240 /* Set mips_optimize around the lui instruction to avoid
5241 inserting an unnecessary nop after the lw. */
5242 hold_mips_optimize = mips_optimize;
5244 macro_build_lui (NULL, &icnt, &expr1, AT);
5245 mips_optimize = hold_mips_optimize;
5247 macro_build ((char *) NULL, &icnt, &expr1,
5248 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
5249 "t,r,j", AT, AT, (int) BFD_RELOC_LO16);
5250 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5251 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
5252 "d,v,t", dreg, dreg, AT);
5254 p = frag_var (rs_machine_dependent, 16 + gpdel + adj, 0,
5255 RELAX_ENCODE (24 + adj, 16 + gpdel + adj, gpdel,
5258 ? mips_opts.warn_about_macros
5260 offset_expr.X_add_symbol, 0, NULL);
5267 /* This is needed because this instruction uses $gp, but
5268 the first instruction on the main stream does not. */
5269 macro_build (p, &icnt, (expressionS *) NULL, "nop", "");
5274 local_reloc_type = (int) BFD_RELOC_MIPS_GOT_DISP;
5275 macro_build (p, &icnt, &offset_expr,
5276 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
5281 if (expr1.X_add_number == 0 && HAVE_NEWABI)
5283 /* BFD_RELOC_MIPS_GOT_DISP is sufficient for newabi */
5286 if (expr1.X_add_number >= -0x8000
5287 && expr1.X_add_number < 0x8000)
5289 macro_build (p, &icnt, (expressionS *) NULL, "nop", "");
5291 macro_build (p, &icnt, &expr1,
5292 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
5293 "t,r,j", tempreg, tempreg, (int) BFD_RELOC_LO16);
5294 /* FIXME: If add_number is 0, and there was no base
5295 register, the external symbol case ended with a load,
5296 so if the symbol turns out to not be external, and
5297 the next instruction uses tempreg, an unnecessary nop
5298 will be inserted. */
5304 /* We must add in the base register now, as in the
5305 external symbol case. */
5306 assert (tempreg == AT);
5307 macro_build (p, &icnt, (expressionS *) NULL, "nop", "");
5309 macro_build (p, &icnt, (expressionS *) NULL,
5310 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
5311 "d,v,t", treg, AT, breg);
5314 /* We set breg to 0 because we have arranged to add
5315 it in in both cases. */
5319 macro_build_lui (p, &icnt, &expr1, AT);
5321 macro_build (p, &icnt, &expr1,
5322 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
5323 "t,r,j", AT, AT, (int) BFD_RELOC_LO16);
5325 macro_build (p, &icnt, (expressionS *) NULL,
5326 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
5327 "d,v,t", tempreg, tempreg, AT);
5331 else if (mips_pic == EMBEDDED_PIC)
5334 addiu $tempreg,$gp,<sym> (BFD_RELOC_GPREL16)
5336 macro_build ((char *) NULL, &icnt, &offset_expr,
5337 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu", "t,r,j",
5338 tempreg, mips_gp_register, (int) BFD_RELOC_GPREL16);
5347 if (mips_pic == EMBEDDED_PIC || mips_pic == NO_PIC)
5348 s = (dbl || HAVE_64BIT_ADDRESSES) ? "daddu" : "addu";
5350 s = HAVE_64BIT_ADDRESSES ? "daddu" : "addu";
5352 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s,
5353 "d,v,t", treg, tempreg, breg);
5362 /* The j instruction may not be used in PIC code, since it
5363 requires an absolute address. We convert it to a b
5365 if (mips_pic == NO_PIC)
5366 macro_build ((char *) NULL, &icnt, &offset_expr, "j", "a");
5368 macro_build ((char *) NULL, &icnt, &offset_expr, "b", "p");
5371 /* The jal instructions must be handled as macros because when
5372 generating PIC code they expand to multi-instruction
5373 sequences. Normally they are simple instructions. */
5378 if (mips_pic == NO_PIC
5379 || mips_pic == EMBEDDED_PIC)
5380 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "jalr",
5382 else if (mips_pic == SVR4_PIC)
5384 if (sreg != PIC_CALL_REG)
5385 as_warn (_("MIPS PIC call to register other than $25"));
5387 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "jalr",
5391 if (mips_cprestore_offset < 0)
5392 as_warn (_("No .cprestore pseudo-op used in PIC code"));
5395 if (! mips_frame_reg_valid)
5397 as_warn (_("No .frame pseudo-op used in PIC code"));
5398 /* Quiet this warning. */
5399 mips_frame_reg_valid = 1;
5401 if (! mips_cprestore_valid)
5403 as_warn (_("No .cprestore pseudo-op used in PIC code"));
5404 /* Quiet this warning. */
5405 mips_cprestore_valid = 1;
5407 expr1.X_add_number = mips_cprestore_offset;
5408 macro_build_ldst_constoffset ((char *) NULL, &icnt, &expr1,
5409 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
5410 mips_gp_register, mips_frame_reg);
5420 if (mips_pic == NO_PIC)
5421 macro_build ((char *) NULL, &icnt, &offset_expr, "jal", "a");
5422 else if (mips_pic == SVR4_PIC)
5426 /* If this is a reference to an external symbol, and we are
5427 using a small GOT, we want
5428 lw $25,<sym>($gp) (BFD_RELOC_MIPS_CALL16)
5432 lw $gp,cprestore($sp)
5433 The cprestore value is set using the .cprestore
5434 pseudo-op. If we are using a big GOT, we want
5435 lui $25,<sym> (BFD_RELOC_MIPS_CALL_HI16)
5437 lw $25,<sym>($25) (BFD_RELOC_MIPS_CALL_LO16)
5441 lw $gp,cprestore($sp)
5442 If the symbol is not external, we want
5443 lw $25,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
5445 addiu $25,$25,<sym> (BFD_RELOC_LO16)
5448 lw $gp,cprestore($sp)
5450 lw $25,<sym>($gp) (BFD_RELOC_MIPS_GOT_DISP)
5451 jalr $ra,$25 (BFD_RELOC_MIPS_JALR)
5455 macro_build ((char *) NULL, &icnt, &offset_expr,
5456 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
5457 "t,o(b)", PIC_CALL_REG,
5458 (int) BFD_RELOC_MIPS_GOT_DISP, mips_gp_register);
5459 macro_build_jalr (icnt, &offset_expr);
5466 macro_build ((char *) NULL, &icnt, &offset_expr,
5467 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
5468 "t,o(b)", PIC_CALL_REG,
5469 (int) BFD_RELOC_MIPS_CALL16, mips_gp_register);
5470 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5472 p = frag_var (rs_machine_dependent, 4, 0,
5473 RELAX_ENCODE (0, 4, -8, 0, 0, 0),
5474 offset_expr.X_add_symbol, 0, NULL);
5480 if (reg_needs_delay (mips_gp_register))
5484 macro_build ((char *) NULL, &icnt, &offset_expr, "lui",
5485 "t,u", PIC_CALL_REG,
5486 (int) BFD_RELOC_MIPS_CALL_HI16);
5487 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5488 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
5489 "d,v,t", PIC_CALL_REG, PIC_CALL_REG,
5491 macro_build ((char *) NULL, &icnt, &offset_expr,
5492 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
5493 "t,o(b)", PIC_CALL_REG,
5494 (int) BFD_RELOC_MIPS_CALL_LO16, PIC_CALL_REG);
5495 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5497 p = frag_var (rs_machine_dependent, 12 + gpdel, 0,
5498 RELAX_ENCODE (16, 12 + gpdel, gpdel,
5500 offset_expr.X_add_symbol, 0, NULL);
5503 macro_build (p, &icnt, (expressionS *) NULL, "nop", "");
5506 macro_build (p, &icnt, &offset_expr,
5507 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
5508 "t,o(b)", PIC_CALL_REG,
5509 (int) BFD_RELOC_MIPS_GOT16, mips_gp_register);
5511 macro_build (p, &icnt, (expressionS *) NULL, "nop", "");
5514 macro_build (p, &icnt, &offset_expr,
5515 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
5516 "t,r,j", PIC_CALL_REG, PIC_CALL_REG,
5517 (int) BFD_RELOC_LO16);
5518 macro_build_jalr (icnt, &offset_expr);
5520 if (mips_cprestore_offset < 0)
5521 as_warn (_("No .cprestore pseudo-op used in PIC code"));
5524 if (! mips_frame_reg_valid)
5526 as_warn (_("No .frame pseudo-op used in PIC code"));
5527 /* Quiet this warning. */
5528 mips_frame_reg_valid = 1;
5530 if (! mips_cprestore_valid)
5532 as_warn (_("No .cprestore pseudo-op used in PIC code"));
5533 /* Quiet this warning. */
5534 mips_cprestore_valid = 1;
5536 if (mips_opts.noreorder)
5537 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5539 expr1.X_add_number = mips_cprestore_offset;
5540 macro_build_ldst_constoffset ((char *) NULL, &icnt, &expr1,
5541 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
5542 mips_gp_register, mips_frame_reg);
5546 else if (mips_pic == EMBEDDED_PIC)
5548 macro_build ((char *) NULL, &icnt, &offset_expr, "bal", "p");
5549 /* The linker may expand the call to a longer sequence which
5550 uses $at, so we must break rather than return. */
5575 /* Itbl support may require additional care here. */
5580 /* Itbl support may require additional care here. */
5585 /* Itbl support may require additional care here. */
5590 /* Itbl support may require additional care here. */
5602 if (mips_arch == CPU_R4650)
5604 as_bad (_("opcode not supported on this processor"));
5608 /* Itbl support may require additional care here. */
5613 /* Itbl support may require additional care here. */
5618 /* Itbl support may require additional care here. */
5638 if (breg == treg || coproc || lr)
5660 /* Itbl support may require additional care here. */
5665 /* Itbl support may require additional care here. */
5670 /* Itbl support may require additional care here. */
5675 /* Itbl support may require additional care here. */
5691 if (mips_arch == CPU_R4650)
5693 as_bad (_("opcode not supported on this processor"));
5698 /* Itbl support may require additional care here. */
5702 /* Itbl support may require additional care here. */
5707 /* Itbl support may require additional care here. */
5719 /* Itbl support may require additional care here. */
5720 if (mask == M_LWC1_AB
5721 || mask == M_SWC1_AB
5722 || mask == M_LDC1_AB
5723 || mask == M_SDC1_AB
5732 /* For embedded PIC, we allow loads where the offset is calculated
5733 by subtracting a symbol in the current segment from an unknown
5734 symbol, relative to a base register, e.g.:
5735 <op> $treg, <sym>-<localsym>($breg)
5736 This is used by the compiler for switch statements. */
5737 if (mips_pic == EMBEDDED_PIC
5738 && offset_expr.X_op == O_subtract
5739 && (symbol_constant_p (offset_expr.X_op_symbol)
5740 ? S_GET_SEGMENT (offset_expr.X_op_symbol) == now_seg
5741 : (symbol_equated_p (offset_expr.X_op_symbol)
5743 (symbol_get_value_expression (offset_expr.X_op_symbol)
5747 && (offset_expr.X_add_number == 0
5748 || OUTPUT_FLAVOR == bfd_target_elf_flavour))
5750 /* For this case, we output the instructions:
5751 lui $tempreg,<sym> (BFD_RELOC_PCREL_HI16_S)
5752 addiu $tempreg,$tempreg,$breg
5753 <op> $treg,<sym>($tempreg) (BFD_RELOC_PCREL_LO16)
5754 If the relocation would fit entirely in 16 bits, it would be
5756 <op> $treg,<sym>($breg) (BFD_RELOC_PCREL_LO16)
5757 instead, but that seems quite difficult. */
5758 macro_build ((char *) NULL, &icnt, &offset_expr, "lui", "t,u",
5759 tempreg, (int) BFD_RELOC_PCREL_HI16_S);
5760 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5761 ((bfd_arch_bits_per_address (stdoutput) == 32
5762 || ! ISA_HAS_64BIT_REGS (mips_opts.isa))
5763 ? "addu" : "daddu"),
5764 "d,v,t", tempreg, tempreg, breg);
5765 macro_build ((char *) NULL, &icnt, &offset_expr, s, fmt, treg,
5766 (int) BFD_RELOC_PCREL_LO16, tempreg);
5772 if (offset_expr.X_op != O_constant
5773 && offset_expr.X_op != O_symbol)
5775 as_bad (_("expression too complex"));
5776 offset_expr.X_op = O_constant;
5779 /* A constant expression in PIC code can be handled just as it
5780 is in non PIC code. */
5781 if (mips_pic == NO_PIC
5782 || offset_expr.X_op == O_constant)
5786 /* If this is a reference to a GP relative symbol, and there
5787 is no base register, we want
5788 <op> $treg,<sym>($gp) (BFD_RELOC_GPREL16)
5789 Otherwise, if there is no base register, we want
5790 lui $tempreg,<sym> (BFD_RELOC_HI16_S)
5791 <op> $treg,<sym>($tempreg) (BFD_RELOC_LO16)
5792 If we have a constant, we need two instructions anyhow,
5793 so we always use the latter form.
5795 If we have a base register, and this is a reference to a
5796 GP relative symbol, we want
5797 addu $tempreg,$breg,$gp
5798 <op> $treg,<sym>($tempreg) (BFD_RELOC_GPREL16)
5800 lui $tempreg,<sym> (BFD_RELOC_HI16_S)
5801 addu $tempreg,$tempreg,$breg
5802 <op> $treg,<sym>($tempreg) (BFD_RELOC_LO16)
5803 With a constant we always use the latter case.
5805 With 64bit address space and no base register and $at usable,
5807 lui $tempreg,<sym> (BFD_RELOC_MIPS_HIGHEST)
5808 lui $at,<sym> (BFD_RELOC_HI16_S)
5809 daddiu $tempreg,<sym> (BFD_RELOC_MIPS_HIGHER)
5812 <op> $treg,<sym>($tempreg) (BFD_RELOC_LO16)
5813 If we have a base register, we want
5814 lui $tempreg,<sym> (BFD_RELOC_MIPS_HIGHEST)
5815 lui $at,<sym> (BFD_RELOC_HI16_S)
5816 daddiu $tempreg,<sym> (BFD_RELOC_MIPS_HIGHER)
5820 <op> $treg,<sym>($tempreg) (BFD_RELOC_LO16)
5822 Without $at we can't generate the optimal path for superscalar
5823 processors here since this would require two temporary registers.
5824 lui $tempreg,<sym> (BFD_RELOC_MIPS_HIGHEST)
5825 daddiu $tempreg,<sym> (BFD_RELOC_MIPS_HIGHER)
5827 daddiu $tempreg,<sym> (BFD_RELOC_HI16_S)
5829 <op> $treg,<sym>($tempreg) (BFD_RELOC_LO16)
5830 If we have a base register, we want
5831 lui $tempreg,<sym> (BFD_RELOC_MIPS_HIGHEST)
5832 daddiu $tempreg,<sym> (BFD_RELOC_MIPS_HIGHER)
5834 daddiu $tempreg,<sym> (BFD_RELOC_HI16_S)
5836 daddu $tempreg,$tempreg,$breg
5837 <op> $treg,<sym>($tempreg) (BFD_RELOC_LO16)
5839 If we have 64-bit addresses, as an optimization, for
5840 addresses which are 32-bit constants (e.g. kseg0/kseg1
5841 addresses) we fall back to the 32-bit address generation
5842 mechanism since it is more efficient. Note that due to
5843 the signed offset used by memory operations, the 32-bit
5844 range is shifted down by 32768 here. This code should
5845 probably attempt to generate 64-bit constants more
5846 efficiently in general.
5848 if (HAVE_64BIT_ADDRESSES
5849 && !(offset_expr.X_op == O_constant
5850 && IS_SEXT_32BIT_NUM (offset_expr.X_add_number + 0x8000)))
5854 /* We don't do GP optimization for now because RELAX_ENCODE can't
5855 hold the data for such large chunks. */
5857 if (used_at == 0 && ! mips_opts.noat)
5859 macro_build (p, &icnt, &offset_expr, "lui", "t,u",
5860 tempreg, (int) BFD_RELOC_MIPS_HIGHEST);
5861 macro_build (p, &icnt, &offset_expr, "lui", "t,u",
5862 AT, (int) BFD_RELOC_HI16_S);
5863 macro_build (p, &icnt, &offset_expr, "daddiu", "t,r,j",
5864 tempreg, tempreg, (int) BFD_RELOC_MIPS_HIGHER);
5866 macro_build (p, &icnt, (expressionS *) NULL, "daddu",
5867 "d,v,t", AT, AT, breg);
5868 macro_build (p, &icnt, (expressionS *) NULL, "dsll32",
5869 "d,w,<", tempreg, tempreg, 0);
5870 macro_build (p, &icnt, (expressionS *) NULL, "daddu",
5871 "d,v,t", tempreg, tempreg, AT);
5872 macro_build (p, &icnt, &offset_expr, s,
5873 fmt, treg, (int) BFD_RELOC_LO16, tempreg);
5878 macro_build (p, &icnt, &offset_expr, "lui", "t,u",
5879 tempreg, (int) BFD_RELOC_MIPS_HIGHEST);
5880 macro_build (p, &icnt, &offset_expr, "daddiu", "t,r,j",
5881 tempreg, tempreg, (int) BFD_RELOC_MIPS_HIGHER);
5882 macro_build (p, &icnt, (expressionS *) NULL, "dsll",
5883 "d,w,<", tempreg, tempreg, 16);
5884 macro_build (p, &icnt, &offset_expr, "daddiu", "t,r,j",
5885 tempreg, tempreg, (int) BFD_RELOC_HI16_S);
5886 macro_build (p, &icnt, (expressionS *) NULL, "dsll",
5887 "d,w,<", tempreg, tempreg, 16);
5889 macro_build (p, &icnt, (expressionS *) NULL, "daddu",
5890 "d,v,t", tempreg, tempreg, breg);
5891 macro_build (p, &icnt, &offset_expr, s,
5892 fmt, treg, (int) BFD_RELOC_LO16, tempreg);
5900 if ((valueT) offset_expr.X_add_number > MAX_GPREL_OFFSET
5901 || nopic_need_relax (offset_expr.X_add_symbol, 1))
5906 macro_build ((char *) NULL, &icnt, &offset_expr, s, fmt,
5907 treg, (int) BFD_RELOC_GPREL16,
5909 p = frag_var (rs_machine_dependent, 8, 0,
5910 RELAX_ENCODE (4, 8, 0, 4, 0,
5911 (mips_opts.warn_about_macros
5913 && mips_opts.noat))),
5914 offset_expr.X_add_symbol, 0, NULL);
5917 macro_build_lui (p, &icnt, &offset_expr, tempreg);
5920 macro_build (p, &icnt, &offset_expr, s, fmt, treg,
5921 (int) BFD_RELOC_LO16, tempreg);
5925 if ((valueT) offset_expr.X_add_number > MAX_GPREL_OFFSET
5926 || nopic_need_relax (offset_expr.X_add_symbol, 1))
5931 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5932 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
5933 "d,v,t", tempreg, breg, mips_gp_register);
5934 macro_build ((char *) NULL, &icnt, &offset_expr, s, fmt,
5935 treg, (int) BFD_RELOC_GPREL16, tempreg);
5936 p = frag_var (rs_machine_dependent, 12, 0,
5937 RELAX_ENCODE (8, 12, 0, 8, 0, 0),
5938 offset_expr.X_add_symbol, 0, NULL);
5940 macro_build_lui (p, &icnt, &offset_expr, tempreg);
5943 macro_build (p, &icnt, (expressionS *) NULL,
5944 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
5945 "d,v,t", tempreg, tempreg, breg);
5948 macro_build (p, &icnt, &offset_expr, s, fmt, treg,
5949 (int) BFD_RELOC_LO16, tempreg);
5952 else if (mips_pic == SVR4_PIC && ! mips_big_got)
5955 int lw_reloc_type = (int) BFD_RELOC_MIPS_GOT16;
5957 /* If this is a reference to an external symbol, we want
5958 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
5960 <op> $treg,0($tempreg)
5962 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
5964 addiu $tempreg,$tempreg,<sym> (BFD_RELOC_LO16)
5965 <op> $treg,0($tempreg)
5966 If we have NewABI, we want
5967 lw $reg,<sym>($gp) (BFD_RELOC_MIPS_GOT_DISP)
5968 If there is a base register, we add it to $tempreg before
5969 the <op>. If there is a constant, we stick it in the
5970 <op> instruction. We don't handle constants larger than
5971 16 bits, because we have no way to load the upper 16 bits
5972 (actually, we could handle them for the subset of cases
5973 in which we are not using $at). */
5974 assert (offset_expr.X_op == O_symbol);
5975 expr1.X_add_number = offset_expr.X_add_number;
5976 offset_expr.X_add_number = 0;
5978 lw_reloc_type = (int) BFD_RELOC_MIPS_GOT_DISP;
5979 if (expr1.X_add_number < -0x8000
5980 || expr1.X_add_number >= 0x8000)
5981 as_bad (_("PIC code offset overflow (max 16 signed bits)"));
5983 macro_build ((char *) NULL, &icnt, &offset_expr,
5984 HAVE_32BIT_ADDRESSES ? "lw" : "ld", "t,o(b)", tempreg,
5985 (int) lw_reloc_type, mips_gp_register);
5986 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "");
5987 p = frag_var (rs_machine_dependent, 4, 0,
5988 RELAX_ENCODE (0, 4, -8, 0, 0, 0),
5989 offset_expr.X_add_symbol, 0, NULL);
5990 macro_build (p, &icnt, &offset_expr,
5991 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
5992 "t,r,j", tempreg, tempreg, (int) BFD_RELOC_LO16);
5994 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5995 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
5996 "d,v,t", tempreg, tempreg, breg);
5997 macro_build ((char *) NULL, &icnt, &expr1, s, fmt, treg,
5998 (int) BFD_RELOC_LO16, tempreg);
6000 else if (mips_pic == SVR4_PIC)
6005 /* If this is a reference to an external symbol, we want
6006 lui $tempreg,<sym> (BFD_RELOC_MIPS_GOT_HI16)
6007 addu $tempreg,$tempreg,$gp
6008 lw $tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_LO16)
6009 <op> $treg,0($tempreg)
6011 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
6013 addiu $tempreg,$tempreg,<sym> (BFD_RELOC_LO16)
6014 <op> $treg,0($tempreg)
6015 If there is a base register, we add it to $tempreg before
6016 the <op>. If there is a constant, we stick it in the
6017 <op> instruction. We don't handle constants larger than
6018 16 bits, because we have no way to load the upper 16 bits
6019 (actually, we could handle them for the subset of cases
6020 in which we are not using $at).
6023 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT_PAGE)
6024 addiu $tempreg,$tempreg,<sym> (BFD_RELOC_MIPS_GOT_OFST)
6025 <op> $treg,0($tempreg)
6027 assert (offset_expr.X_op == O_symbol);
6028 expr1.X_add_number = offset_expr.X_add_number;
6029 offset_expr.X_add_number = 0;
6030 if (expr1.X_add_number < -0x8000
6031 || expr1.X_add_number >= 0x8000)
6032 as_bad (_("PIC code offset overflow (max 16 signed bits)"));
6035 macro_build ((char *) NULL, &icnt, &offset_expr,
6036 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
6037 "t,o(b)", tempreg, BFD_RELOC_MIPS_GOT_PAGE,
6039 macro_build ((char *) NULL, &icnt, &offset_expr,
6040 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
6041 "t,r,j", tempreg, tempreg,
6042 BFD_RELOC_MIPS_GOT_OFST);
6044 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6045 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
6046 "d,v,t", tempreg, tempreg, breg);
6047 macro_build ((char *) NULL, &icnt, &expr1, s, fmt, treg,
6048 (int) BFD_RELOC_LO16, tempreg);
6055 if (reg_needs_delay (mips_gp_register))
6060 macro_build ((char *) NULL, &icnt, &offset_expr, "lui", "t,u",
6061 tempreg, (int) BFD_RELOC_MIPS_GOT_HI16);
6062 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6063 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
6064 "d,v,t", tempreg, tempreg, mips_gp_register);
6065 macro_build ((char *) NULL, &icnt, &offset_expr,
6066 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
6067 "t,o(b)", tempreg, (int) BFD_RELOC_MIPS_GOT_LO16,
6069 p = frag_var (rs_machine_dependent, 12 + gpdel, 0,
6070 RELAX_ENCODE (12, 12 + gpdel, gpdel, 8 + gpdel, 0, 0),
6071 offset_expr.X_add_symbol, 0, NULL);
6074 macro_build (p, &icnt, (expressionS *) NULL, "nop", "");
6077 macro_build (p, &icnt, &offset_expr,
6078 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
6079 "t,o(b)", tempreg, (int) BFD_RELOC_MIPS_GOT16,
6082 macro_build (p, &icnt, (expressionS *) NULL, "nop", "");
6084 macro_build (p, &icnt, &offset_expr,
6085 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
6086 "t,r,j", tempreg, tempreg, (int) BFD_RELOC_LO16);
6088 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6089 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
6090 "d,v,t", tempreg, tempreg, breg);
6091 macro_build ((char *) NULL, &icnt, &expr1, s, fmt, treg,
6092 (int) BFD_RELOC_LO16, tempreg);
6094 else if (mips_pic == EMBEDDED_PIC)
6096 /* If there is no base register, we want
6097 <op> $treg,<sym>($gp) (BFD_RELOC_GPREL16)
6098 If there is a base register, we want
6099 addu $tempreg,$breg,$gp
6100 <op> $treg,<sym>($tempreg) (BFD_RELOC_GPREL16)
6102 assert (offset_expr.X_op == O_symbol);
6105 macro_build ((char *) NULL, &icnt, &offset_expr, s, fmt,
6106 treg, (int) BFD_RELOC_GPREL16, mips_gp_register);
6111 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6112 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
6113 "d,v,t", tempreg, breg, mips_gp_register);
6114 macro_build ((char *) NULL, &icnt, &offset_expr, s, fmt,
6115 treg, (int) BFD_RELOC_GPREL16, tempreg);
6128 load_register (&icnt, treg, &imm_expr, 0);
6132 load_register (&icnt, treg, &imm_expr, 1);
6136 if (imm_expr.X_op == O_constant)
6138 load_register (&icnt, AT, &imm_expr, 0);
6139 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6140 "mtc1", "t,G", AT, treg);
6145 assert (offset_expr.X_op == O_symbol
6146 && strcmp (segment_name (S_GET_SEGMENT
6147 (offset_expr.X_add_symbol)),
6149 && offset_expr.X_add_number == 0);
6150 macro_build ((char *) NULL, &icnt, &offset_expr, "lwc1", "T,o(b)",
6151 treg, (int) BFD_RELOC_MIPS_LITERAL, mips_gp_register);
6156 /* Check if we have a constant in IMM_EXPR. If the GPRs are 64 bits
6157 wide, IMM_EXPR is the entire value. Otherwise IMM_EXPR is the high
6158 order 32 bits of the value and the low order 32 bits are either
6159 zero or in OFFSET_EXPR. */
6160 if (imm_expr.X_op == O_constant || imm_expr.X_op == O_big)
6162 if (HAVE_64BIT_GPRS)
6163 load_register (&icnt, treg, &imm_expr, 1);
6168 if (target_big_endian)
6180 load_register (&icnt, hreg, &imm_expr, 0);
6183 if (offset_expr.X_op == O_absent)
6184 move_register (&icnt, lreg, 0);
6187 assert (offset_expr.X_op == O_constant);
6188 load_register (&icnt, lreg, &offset_expr, 0);
6195 /* We know that sym is in the .rdata section. First we get the
6196 upper 16 bits of the address. */
6197 if (mips_pic == NO_PIC)
6199 macro_build_lui (NULL, &icnt, &offset_expr, AT);
6201 else if (mips_pic == SVR4_PIC)
6203 macro_build ((char *) NULL, &icnt, &offset_expr,
6204 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
6205 "t,o(b)", AT, (int) BFD_RELOC_MIPS_GOT16,
6208 else if (mips_pic == EMBEDDED_PIC)
6210 /* For embedded PIC we pick up the entire address off $gp in
6211 a single instruction. */
6212 macro_build ((char *) NULL, &icnt, &offset_expr,
6213 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu", "t,r,j", AT,
6214 mips_gp_register, (int) BFD_RELOC_GPREL16);
6215 offset_expr.X_op = O_constant;
6216 offset_expr.X_add_number = 0;
6221 /* Now we load the register(s). */
6222 if (HAVE_64BIT_GPRS)
6223 macro_build ((char *) NULL, &icnt, &offset_expr, "ld", "t,o(b)",
6224 treg, (int) BFD_RELOC_LO16, AT);
6227 macro_build ((char *) NULL, &icnt, &offset_expr, "lw", "t,o(b)",
6228 treg, (int) BFD_RELOC_LO16, AT);
6231 /* FIXME: How in the world do we deal with the possible
6233 offset_expr.X_add_number += 4;
6234 macro_build ((char *) NULL, &icnt, &offset_expr, "lw", "t,o(b)",
6235 treg + 1, (int) BFD_RELOC_LO16, AT);
6239 /* To avoid confusion in tc_gen_reloc, we must ensure that this
6240 does not become a variant frag. */
6241 frag_wane (frag_now);
6247 /* Check if we have a constant in IMM_EXPR. If the FPRs are 64 bits
6248 wide, IMM_EXPR is the entire value and the GPRs are known to be 64
6249 bits wide as well. Otherwise IMM_EXPR is the high order 32 bits of
6250 the value and the low order 32 bits are either zero or in
6252 if (imm_expr.X_op == O_constant || imm_expr.X_op == O_big)
6254 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_FPRS);
6255 if (HAVE_64BIT_FPRS)
6257 assert (HAVE_64BIT_GPRS);
6258 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6259 "dmtc1", "t,S", AT, treg);
6263 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6264 "mtc1", "t,G", AT, treg + 1);
6265 if (offset_expr.X_op == O_absent)
6266 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6267 "mtc1", "t,G", 0, treg);
6270 assert (offset_expr.X_op == O_constant);
6271 load_register (&icnt, AT, &offset_expr, 0);
6272 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6273 "mtc1", "t,G", AT, treg);
6279 assert (offset_expr.X_op == O_symbol
6280 && offset_expr.X_add_number == 0);
6281 s = segment_name (S_GET_SEGMENT (offset_expr.X_add_symbol));
6282 if (strcmp (s, ".lit8") == 0)
6284 if (mips_opts.isa != ISA_MIPS1)
6286 macro_build ((char *) NULL, &icnt, &offset_expr, "ldc1",
6287 "T,o(b)", treg, (int) BFD_RELOC_MIPS_LITERAL,
6291 breg = mips_gp_register;
6292 r = BFD_RELOC_MIPS_LITERAL;
6297 assert (strcmp (s, RDATA_SECTION_NAME) == 0);
6298 if (mips_pic == SVR4_PIC)
6299 macro_build ((char *) NULL, &icnt, &offset_expr,
6300 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
6301 "t,o(b)", AT, (int) BFD_RELOC_MIPS_GOT16,
6305 /* FIXME: This won't work for a 64 bit address. */
6306 macro_build_lui (NULL, &icnt, &offset_expr, AT);
6309 if (mips_opts.isa != ISA_MIPS1)
6311 macro_build ((char *) NULL, &icnt, &offset_expr, "ldc1",
6312 "T,o(b)", treg, (int) BFD_RELOC_LO16, AT);
6314 /* To avoid confusion in tc_gen_reloc, we must ensure
6315 that this does not become a variant frag. */
6316 frag_wane (frag_now);
6327 if (mips_arch == CPU_R4650)
6329 as_bad (_("opcode not supported on this processor"));
6332 /* Even on a big endian machine $fn comes before $fn+1. We have
6333 to adjust when loading from memory. */
6336 assert (mips_opts.isa == ISA_MIPS1);
6337 macro_build ((char *) NULL, &icnt, &offset_expr, "lwc1", "T,o(b)",
6338 target_big_endian ? treg + 1 : treg,
6340 /* FIXME: A possible overflow which I don't know how to deal
6342 offset_expr.X_add_number += 4;
6343 macro_build ((char *) NULL, &icnt, &offset_expr, "lwc1", "T,o(b)",
6344 target_big_endian ? treg : treg + 1,
6347 /* To avoid confusion in tc_gen_reloc, we must ensure that this
6348 does not become a variant frag. */
6349 frag_wane (frag_now);
6358 * The MIPS assembler seems to check for X_add_number not
6359 * being double aligned and generating:
6362 * addiu at,at,%lo(foo+1)
6365 * But, the resulting address is the same after relocation so why
6366 * generate the extra instruction?
6368 if (mips_arch == CPU_R4650)
6370 as_bad (_("opcode not supported on this processor"));
6373 /* Itbl support may require additional care here. */
6375 if (mips_opts.isa != ISA_MIPS1)
6386 if (mips_arch == CPU_R4650)
6388 as_bad (_("opcode not supported on this processor"));
6392 if (mips_opts.isa != ISA_MIPS1)
6400 /* Itbl support may require additional care here. */
6405 if (HAVE_64BIT_GPRS)
6416 if (HAVE_64BIT_GPRS)
6426 /* We do _not_ bother to allow embedded PIC (symbol-local_symbol)
6427 loads for the case of doing a pair of loads to simulate an 'ld'.
6428 This is not currently done by the compiler, and assembly coders
6429 writing embedded-pic code can cope. */
6431 if (offset_expr.X_op != O_symbol
6432 && offset_expr.X_op != O_constant)
6434 as_bad (_("expression too complex"));
6435 offset_expr.X_op = O_constant;
6438 /* Even on a big endian machine $fn comes before $fn+1. We have
6439 to adjust when loading from memory. We set coproc if we must
6440 load $fn+1 first. */
6441 /* Itbl support may require additional care here. */
6442 if (! target_big_endian)
6445 if (mips_pic == NO_PIC
6446 || offset_expr.X_op == O_constant)
6450 /* If this is a reference to a GP relative symbol, we want
6451 <op> $treg,<sym>($gp) (BFD_RELOC_GPREL16)
6452 <op> $treg+1,<sym>+4($gp) (BFD_RELOC_GPREL16)
6453 If we have a base register, we use this
6455 <op> $treg,<sym>($at) (BFD_RELOC_GPREL16)
6456 <op> $treg+1,<sym>+4($at) (BFD_RELOC_GPREL16)
6457 If this is not a GP relative symbol, we want
6458 lui $at,<sym> (BFD_RELOC_HI16_S)
6459 <op> $treg,<sym>($at) (BFD_RELOC_LO16)
6460 <op> $treg+1,<sym>+4($at) (BFD_RELOC_LO16)
6461 If there is a base register, we add it to $at after the
6462 lui instruction. If there is a constant, we always use
6464 if ((valueT) offset_expr.X_add_number > MAX_GPREL_OFFSET
6465 || nopic_need_relax (offset_expr.X_add_symbol, 1))
6477 tempreg = mips_gp_register;
6484 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6485 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
6486 "d,v,t", AT, breg, mips_gp_register);
6492 /* Itbl support may require additional care here. */
6493 macro_build ((char *) NULL, &icnt, &offset_expr, s, fmt,
6494 coproc ? treg + 1 : treg,
6495 (int) BFD_RELOC_GPREL16, tempreg);
6496 offset_expr.X_add_number += 4;
6498 /* Set mips_optimize to 2 to avoid inserting an
6500 hold_mips_optimize = mips_optimize;
6502 /* Itbl support may require additional care here. */
6503 macro_build ((char *) NULL, &icnt, &offset_expr, s, fmt,
6504 coproc ? treg : treg + 1,
6505 (int) BFD_RELOC_GPREL16, tempreg);
6506 mips_optimize = hold_mips_optimize;
6508 p = frag_var (rs_machine_dependent, 12 + off, 0,
6509 RELAX_ENCODE (8 + off, 12 + off, 0, 4 + off, 1,
6510 used_at && mips_opts.noat),
6511 offset_expr.X_add_symbol, 0, NULL);
6513 /* We just generated two relocs. When tc_gen_reloc
6514 handles this case, it will skip the first reloc and
6515 handle the second. The second reloc already has an
6516 extra addend of 4, which we added above. We must
6517 subtract it out, and then subtract another 4 to make
6518 the first reloc come out right. The second reloc
6519 will come out right because we are going to add 4 to
6520 offset_expr when we build its instruction below.
6522 If we have a symbol, then we don't want to include
6523 the offset, because it will wind up being included
6524 when we generate the reloc. */
6526 if (offset_expr.X_op == O_constant)
6527 offset_expr.X_add_number -= 8;
6530 offset_expr.X_add_number = -4;
6531 offset_expr.X_op = O_constant;
6534 macro_build_lui (p, &icnt, &offset_expr, AT);
6539 macro_build (p, &icnt, (expressionS *) NULL,
6540 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
6541 "d,v,t", AT, breg, AT);
6545 /* Itbl support may require additional care here. */
6546 macro_build (p, &icnt, &offset_expr, s, fmt,
6547 coproc ? treg + 1 : treg,
6548 (int) BFD_RELOC_LO16, AT);
6551 /* FIXME: How do we handle overflow here? */
6552 offset_expr.X_add_number += 4;
6553 /* Itbl support may require additional care here. */
6554 macro_build (p, &icnt, &offset_expr, s, fmt,
6555 coproc ? treg : treg + 1,
6556 (int) BFD_RELOC_LO16, AT);
6558 else if (mips_pic == SVR4_PIC && ! mips_big_got)
6562 /* If this is a reference to an external symbol, we want
6563 lw $at,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
6568 lw $at,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
6570 <op> $treg,<sym>($at) (BFD_RELOC_LO16)
6571 <op> $treg+1,<sym>+4($at) (BFD_RELOC_LO16)
6572 If there is a base register we add it to $at before the
6573 lwc1 instructions. If there is a constant we include it
6574 in the lwc1 instructions. */
6576 expr1.X_add_number = offset_expr.X_add_number;
6577 offset_expr.X_add_number = 0;
6578 if (expr1.X_add_number < -0x8000
6579 || expr1.X_add_number >= 0x8000 - 4)
6580 as_bad (_("PIC code offset overflow (max 16 signed bits)"));
6585 frag_grow (24 + off);
6586 macro_build ((char *) NULL, &icnt, &offset_expr,
6587 HAVE_32BIT_ADDRESSES ? "lw" : "ld", "t,o(b)", AT,
6588 (int) BFD_RELOC_MIPS_GOT16, mips_gp_register);
6589 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "");
6591 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6592 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
6593 "d,v,t", AT, breg, AT);
6594 /* Itbl support may require additional care here. */
6595 macro_build ((char *) NULL, &icnt, &expr1, s, fmt,
6596 coproc ? treg + 1 : treg,
6597 (int) BFD_RELOC_LO16, AT);
6598 expr1.X_add_number += 4;
6600 /* Set mips_optimize to 2 to avoid inserting an undesired
6602 hold_mips_optimize = mips_optimize;
6604 /* Itbl support may require additional care here. */
6605 macro_build ((char *) NULL, &icnt, &expr1, s, fmt,
6606 coproc ? treg : treg + 1,
6607 (int) BFD_RELOC_LO16, AT);
6608 mips_optimize = hold_mips_optimize;
6610 (void) frag_var (rs_machine_dependent, 0, 0,
6611 RELAX_ENCODE (0, 0, -16 - off, -8, 1, 0),
6612 offset_expr.X_add_symbol, 0, NULL);
6614 else if (mips_pic == SVR4_PIC)
6619 /* If this is a reference to an external symbol, we want
6620 lui $at,<sym> (BFD_RELOC_MIPS_GOT_HI16)
6622 lw $at,<sym>($at) (BFD_RELOC_MIPS_GOT_LO16)
6627 lw $at,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
6629 <op> $treg,<sym>($at) (BFD_RELOC_LO16)
6630 <op> $treg+1,<sym>+4($at) (BFD_RELOC_LO16)
6631 If there is a base register we add it to $at before the
6632 lwc1 instructions. If there is a constant we include it
6633 in the lwc1 instructions. */
6635 expr1.X_add_number = offset_expr.X_add_number;
6636 offset_expr.X_add_number = 0;
6637 if (expr1.X_add_number < -0x8000
6638 || expr1.X_add_number >= 0x8000 - 4)
6639 as_bad (_("PIC code offset overflow (max 16 signed bits)"));
6640 if (reg_needs_delay (mips_gp_register))
6649 macro_build ((char *) NULL, &icnt, &offset_expr, "lui", "t,u",
6650 AT, (int) BFD_RELOC_MIPS_GOT_HI16);
6651 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6652 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
6653 "d,v,t", AT, AT, mips_gp_register);
6654 macro_build ((char *) NULL, &icnt, &offset_expr,
6655 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
6656 "t,o(b)", AT, (int) BFD_RELOC_MIPS_GOT_LO16, AT);
6657 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "");
6659 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6660 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
6661 "d,v,t", AT, breg, AT);
6662 /* Itbl support may require additional care here. */
6663 macro_build ((char *) NULL, &icnt, &expr1, s, fmt,
6664 coproc ? treg + 1 : treg,
6665 (int) BFD_RELOC_LO16, AT);
6666 expr1.X_add_number += 4;
6668 /* Set mips_optimize to 2 to avoid inserting an undesired
6670 hold_mips_optimize = mips_optimize;
6672 /* Itbl support may require additional care here. */
6673 macro_build ((char *) NULL, &icnt, &expr1, s, fmt,
6674 coproc ? treg : treg + 1,
6675 (int) BFD_RELOC_LO16, AT);
6676 mips_optimize = hold_mips_optimize;
6677 expr1.X_add_number -= 4;
6679 p = frag_var (rs_machine_dependent, 16 + gpdel + off, 0,
6680 RELAX_ENCODE (24 + off, 16 + gpdel + off, gpdel,
6681 8 + gpdel + off, 1, 0),
6682 offset_expr.X_add_symbol, 0, NULL);
6685 macro_build (p, &icnt, (expressionS *) NULL, "nop", "");
6688 macro_build (p, &icnt, &offset_expr,
6689 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
6690 "t,o(b)", AT, (int) BFD_RELOC_MIPS_GOT16,
6693 macro_build (p, &icnt, (expressionS *) NULL, "nop", "");
6697 macro_build (p, &icnt, (expressionS *) NULL,
6698 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
6699 "d,v,t", AT, breg, AT);
6702 /* Itbl support may require additional care here. */
6703 macro_build (p, &icnt, &expr1, s, fmt,
6704 coproc ? treg + 1 : treg,
6705 (int) BFD_RELOC_LO16, AT);
6707 expr1.X_add_number += 4;
6709 /* Set mips_optimize to 2 to avoid inserting an undesired
6711 hold_mips_optimize = mips_optimize;
6713 /* Itbl support may require additional care here. */
6714 macro_build (p, &icnt, &expr1, s, fmt,
6715 coproc ? treg : treg + 1,
6716 (int) BFD_RELOC_LO16, AT);
6717 mips_optimize = hold_mips_optimize;
6719 else if (mips_pic == EMBEDDED_PIC)
6721 /* If there is no base register, we use
6722 <op> $treg,<sym>($gp) (BFD_RELOC_GPREL16)
6723 <op> $treg+1,<sym>+4($gp) (BFD_RELOC_GPREL16)
6724 If we have a base register, we use
6726 <op> $treg,<sym>($at) (BFD_RELOC_GPREL16)
6727 <op> $treg+1,<sym>+4($at) (BFD_RELOC_GPREL16)
6731 tempreg = mips_gp_register;
6736 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6737 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
6738 "d,v,t", AT, breg, mips_gp_register);
6743 /* Itbl support may require additional care here. */
6744 macro_build ((char *) NULL, &icnt, &offset_expr, s, fmt,
6745 coproc ? treg + 1 : treg,
6746 (int) BFD_RELOC_GPREL16, tempreg);
6747 offset_expr.X_add_number += 4;
6748 /* Itbl support may require additional care here. */
6749 macro_build ((char *) NULL, &icnt, &offset_expr, s, fmt,
6750 coproc ? treg : treg + 1,
6751 (int) BFD_RELOC_GPREL16, tempreg);
6767 assert (HAVE_32BIT_ADDRESSES);
6768 macro_build ((char *) NULL, &icnt, &offset_expr, s, "t,o(b)", treg,
6769 (int) BFD_RELOC_LO16, breg);
6770 offset_expr.X_add_number += 4;
6771 macro_build ((char *) NULL, &icnt, &offset_expr, s, "t,o(b)", treg + 1,
6772 (int) BFD_RELOC_LO16, breg);
6775 /* New code added to support COPZ instructions.
6776 This code builds table entries out of the macros in mip_opcodes.
6777 R4000 uses interlocks to handle coproc delays.
6778 Other chips (like the R3000) require nops to be inserted for delays.
6780 FIXME: Currently, we require that the user handle delays.
6781 In order to fill delay slots for non-interlocked chips,
6782 we must have a way to specify delays based on the coprocessor.
6783 Eg. 4 cycles if load coproc reg from memory, 1 if in cache, etc.
6784 What are the side-effects of the cop instruction?
6785 What cache support might we have and what are its effects?
6786 Both coprocessor & memory require delays. how long???
6787 What registers are read/set/modified?
6789 If an itbl is provided to interpret cop instructions,
6790 this knowledge can be encoded in the itbl spec. */
6804 /* For now we just do C (same as Cz). The parameter will be
6805 stored in insn_opcode by mips_ip. */
6806 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "C",
6811 move_register (&icnt, dreg, sreg);
6814 #ifdef LOSING_COMPILER
6816 /* Try and see if this is a new itbl instruction.
6817 This code builds table entries out of the macros in mip_opcodes.
6818 FIXME: For now we just assemble the expression and pass it's
6819 value along as a 32-bit immediate.
6820 We may want to have the assembler assemble this value,
6821 so that we gain the assembler's knowledge of delay slots,
6823 Would it be more efficient to use mask (id) here? */
6824 if (itbl_have_entries
6825 && (immed_expr = itbl_assemble (ip->insn_mo->name, "")))
6827 s = ip->insn_mo->name;
6829 coproc = ITBL_DECODE_PNUM (immed_expr);;
6830 macro_build ((char *) NULL, &icnt, &immed_expr, s, "C");
6837 as_warn (_("Macro used $at after \".set noat\""));
6842 struct mips_cl_insn *ip;
6844 register int treg, sreg, dreg, breg;
6860 bfd_reloc_code_real_type r;
6863 treg = (ip->insn_opcode >> 16) & 0x1f;
6864 dreg = (ip->insn_opcode >> 11) & 0x1f;
6865 sreg = breg = (ip->insn_opcode >> 21) & 0x1f;
6866 mask = ip->insn_mo->mask;
6868 expr1.X_op = O_constant;
6869 expr1.X_op_symbol = NULL;
6870 expr1.X_add_symbol = NULL;
6871 expr1.X_add_number = 1;
6875 #endif /* LOSING_COMPILER */
6880 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6881 dbl ? "dmultu" : "multu", "s,t", sreg, treg);
6882 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "mflo", "d",
6889 /* The MIPS assembler some times generates shifts and adds. I'm
6890 not trying to be that fancy. GCC should do this for us
6892 load_register (&icnt, AT, &imm_expr, dbl);
6893 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6894 dbl ? "dmult" : "mult", "s,t", sreg, AT);
6895 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "mflo", "d",
6909 mips_emit_delays (TRUE);
6910 ++mips_opts.noreorder;
6911 mips_any_noreorder = 1;
6913 load_register (&icnt, AT, &imm_expr, dbl);
6914 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6915 dbl ? "dmult" : "mult", "s,t", sreg, imm ? AT : treg);
6916 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "mflo", "d",
6918 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6919 dbl ? "dsra32" : "sra", "d,w,<", dreg, dreg, RA);
6920 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "mfhi", "d",
6923 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "tne",
6924 "s,t,q", dreg, AT, 6);
6927 expr1.X_add_number = 8;
6928 macro_build ((char *) NULL, &icnt, &expr1, "beq", "s,t,p", dreg,
6930 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "",
6932 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "break",
6935 --mips_opts.noreorder;
6936 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "mflo", "d", dreg);
6949 mips_emit_delays (TRUE);
6950 ++mips_opts.noreorder;
6951 mips_any_noreorder = 1;
6953 load_register (&icnt, AT, &imm_expr, dbl);
6954 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6955 dbl ? "dmultu" : "multu",
6956 "s,t", sreg, imm ? AT : treg);
6957 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "mfhi", "d",
6959 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "mflo", "d",
6962 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "tne",
6966 expr1.X_add_number = 8;
6967 macro_build ((char *) NULL, &icnt, &expr1, "beq", "s,t,p", AT, 0);
6968 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "",
6970 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "break",
6973 --mips_opts.noreorder;
6977 if (ISA_HAS_DROR (mips_opts.isa) || CPU_HAS_DROR (mips_arch))
6989 macro_build ((char *) NULL, &icnt, NULL, "dnegu",
6990 "d,w", tempreg, treg);
6991 macro_build ((char *) NULL, &icnt, NULL, "drorv",
6992 "d,t,s", dreg, sreg, tempreg);
6997 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "dsubu",
6998 "d,v,t", AT, 0, treg);
6999 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "dsrlv",
7000 "d,t,s", AT, sreg, AT);
7001 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "dsllv",
7002 "d,t,s", dreg, sreg, treg);
7003 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or",
7004 "d,v,t", dreg, dreg, AT);
7008 if (ISA_HAS_ROR (mips_opts.isa) || CPU_HAS_ROR (mips_arch))
7020 macro_build ((char *) NULL, &icnt, NULL, "negu",
7021 "d,w", tempreg, treg);
7022 macro_build ((char *) NULL, &icnt, NULL, "rorv",
7023 "d,t,s", dreg, sreg, tempreg);
7028 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "subu",
7029 "d,v,t", AT, 0, treg);
7030 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "srlv",
7031 "d,t,s", AT, sreg, AT);
7032 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sllv",
7033 "d,t,s", dreg, sreg, treg);
7034 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or",
7035 "d,v,t", dreg, dreg, AT);
7043 if (imm_expr.X_op != O_constant)
7044 as_bad (_("Improper rotate count"));
7045 rot = imm_expr.X_add_number & 0x3f;
7046 if (ISA_HAS_DROR (mips_opts.isa) || CPU_HAS_DROR (mips_arch))
7048 rot = (64 - rot) & 0x3f;
7050 macro_build ((char *) NULL, &icnt, NULL, "dror32",
7051 "d,w,<", dreg, sreg, rot - 32);
7053 macro_build ((char *) NULL, &icnt, NULL, "dror",
7054 "d,w,<", dreg, sreg, rot);
7059 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "dsrl",
7060 "d,w,<", dreg, sreg, 0);
7063 l = (rot < 0x20) ? "dsll" : "dsll32";
7064 r = ((0x40 - rot) < 0x20) ? "dsrl" : "dsrl32";
7066 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, l,
7067 "d,w,<", AT, sreg, rot);
7068 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, r,
7069 "d,w,<", dreg, sreg, (0x20 - rot) & 0x1f);
7070 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or",
7071 "d,v,t", dreg, dreg, AT);
7079 if (imm_expr.X_op != O_constant)
7080 as_bad (_("Improper rotate count"));
7081 rot = imm_expr.X_add_number & 0x1f;
7082 if (ISA_HAS_ROR (mips_opts.isa) || CPU_HAS_ROR (mips_arch))
7084 macro_build ((char *) NULL, &icnt, NULL, "ror",
7085 "d,w,<", dreg, sreg, (32 - rot) & 0x1f);
7090 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "srl",
7091 "d,w,<", dreg, sreg, 0);
7094 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sll",
7095 "d,w,<", AT, sreg, rot);
7096 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "srl",
7097 "d,w,<", dreg, sreg, (0x20 - rot) & 0x1f);
7098 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or",
7099 "d,v,t", dreg, dreg, AT);
7104 if (ISA_HAS_DROR (mips_opts.isa) || CPU_HAS_DROR (mips_arch))
7106 macro_build ((char *) NULL, &icnt, NULL, "drorv",
7107 "d,t,s", dreg, sreg, treg);
7110 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "dsubu",
7111 "d,v,t", AT, 0, treg);
7112 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "dsllv",
7113 "d,t,s", AT, sreg, AT);
7114 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "dsrlv",
7115 "d,t,s", dreg, sreg, treg);
7116 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or",
7117 "d,v,t", dreg, dreg, AT);
7121 if (ISA_HAS_ROR (mips_opts.isa) || CPU_HAS_ROR (mips_arch))
7123 macro_build ((char *) NULL, &icnt, NULL, "rorv",
7124 "d,t,s", dreg, sreg, treg);
7127 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "subu",
7128 "d,v,t", AT, 0, treg);
7129 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sllv",
7130 "d,t,s", AT, sreg, AT);
7131 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "srlv",
7132 "d,t,s", dreg, sreg, treg);
7133 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or",
7134 "d,v,t", dreg, dreg, AT);
7142 if (imm_expr.X_op != O_constant)
7143 as_bad (_("Improper rotate count"));
7144 rot = imm_expr.X_add_number & 0x3f;
7145 if (ISA_HAS_DROR (mips_opts.isa) || CPU_HAS_DROR (mips_arch))
7148 macro_build ((char *) NULL, &icnt, NULL, "dror32",
7149 "d,w,<", dreg, sreg, rot - 32);
7151 macro_build ((char *) NULL, &icnt, NULL, "dror",
7152 "d,w,<", dreg, sreg, rot);
7157 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "dsrl",
7158 "d,w,<", dreg, sreg, 0);
7161 r = (rot < 0x20) ? "dsrl" : "dsrl32";
7162 l = ((0x40 - rot) < 0x20) ? "dsll" : "dsll32";
7164 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, r,
7165 "d,w,<", AT, sreg, rot);
7166 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, l,
7167 "d,w,<", dreg, sreg, (0x20 - rot) & 0x1f);
7168 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or",
7169 "d,v,t", dreg, dreg, AT);
7177 if (imm_expr.X_op != O_constant)
7178 as_bad (_("Improper rotate count"));
7179 rot = imm_expr.X_add_number & 0x1f;
7180 if (ISA_HAS_ROR (mips_opts.isa) || CPU_HAS_ROR (mips_arch))
7182 macro_build ((char *) NULL, &icnt, NULL, "ror",
7183 "d,w,<", dreg, sreg, rot);
7188 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "srl",
7189 "d,w,<", dreg, sreg, 0);
7192 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "srl",
7193 "d,w,<", AT, sreg, rot);
7194 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sll",
7195 "d,w,<", dreg, sreg, (0x20 - rot) & 0x1f);
7196 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or",
7197 "d,v,t", dreg, dreg, AT);
7202 if (mips_arch == CPU_R4650)
7204 as_bad (_("opcode not supported on this processor"));
7207 assert (mips_opts.isa == ISA_MIPS1);
7208 /* Even on a big endian machine $fn comes before $fn+1. We have
7209 to adjust when storing to memory. */
7210 macro_build ((char *) NULL, &icnt, &offset_expr, "swc1", "T,o(b)",
7211 target_big_endian ? treg + 1 : treg,
7212 (int) BFD_RELOC_LO16, breg);
7213 offset_expr.X_add_number += 4;
7214 macro_build ((char *) NULL, &icnt, &offset_expr, "swc1", "T,o(b)",
7215 target_big_endian ? treg : treg + 1,
7216 (int) BFD_RELOC_LO16, breg);
7221 macro_build ((char *) NULL, &icnt, &expr1, "sltiu", "t,r,j", dreg,
7222 treg, (int) BFD_RELOC_LO16);
7224 macro_build ((char *) NULL, &icnt, &expr1, "sltiu", "t,r,j", dreg,
7225 sreg, (int) BFD_RELOC_LO16);
7228 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "xor",
7229 "d,v,t", dreg, sreg, treg);
7230 macro_build ((char *) NULL, &icnt, &expr1, "sltiu", "t,r,j", dreg,
7231 dreg, (int) BFD_RELOC_LO16);
7236 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
7238 macro_build ((char *) NULL, &icnt, &expr1, "sltiu", "t,r,j", dreg,
7239 sreg, (int) BFD_RELOC_LO16);
7244 as_warn (_("Instruction %s: result is always false"),
7246 move_register (&icnt, dreg, 0);
7249 if (imm_expr.X_op == O_constant
7250 && imm_expr.X_add_number >= 0
7251 && imm_expr.X_add_number < 0x10000)
7253 macro_build ((char *) NULL, &icnt, &imm_expr, "xori", "t,r,i", dreg,
7254 sreg, (int) BFD_RELOC_LO16);
7257 else if (imm_expr.X_op == O_constant
7258 && imm_expr.X_add_number > -0x8000
7259 && imm_expr.X_add_number < 0)
7261 imm_expr.X_add_number = -imm_expr.X_add_number;
7262 macro_build ((char *) NULL, &icnt, &imm_expr,
7263 HAVE_32BIT_GPRS ? "addiu" : "daddiu",
7264 "t,r,j", dreg, sreg,
7265 (int) BFD_RELOC_LO16);
7270 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_GPRS);
7271 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "xor",
7272 "d,v,t", dreg, sreg, AT);
7275 macro_build ((char *) NULL, &icnt, &expr1, "sltiu", "t,r,j", dreg, dreg,
7276 (int) BFD_RELOC_LO16);
7281 case M_SGE: /* sreg >= treg <==> not (sreg < treg) */
7287 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "d,v,t",
7289 macro_build ((char *) NULL, &icnt, &expr1, "xori", "t,r,i", dreg, dreg,
7290 (int) BFD_RELOC_LO16);
7293 case M_SGE_I: /* sreg >= I <==> not (sreg < I) */
7295 if (imm_expr.X_op == O_constant
7296 && imm_expr.X_add_number >= -0x8000
7297 && imm_expr.X_add_number < 0x8000)
7299 macro_build ((char *) NULL, &icnt, &imm_expr,
7300 mask == M_SGE_I ? "slti" : "sltiu",
7301 "t,r,j", dreg, sreg, (int) BFD_RELOC_LO16);
7306 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_GPRS);
7307 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7308 mask == M_SGE_I ? "slt" : "sltu", "d,v,t", dreg, sreg,
7312 macro_build ((char *) NULL, &icnt, &expr1, "xori", "t,r,i", dreg, dreg,
7313 (int) BFD_RELOC_LO16);
7318 case M_SGT: /* sreg > treg <==> treg < sreg */
7324 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "d,v,t",
7328 case M_SGT_I: /* sreg > I <==> I < sreg */
7334 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_GPRS);
7335 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "d,v,t",
7339 case M_SLE: /* sreg <= treg <==> treg >= sreg <==> not (treg < sreg) */
7345 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "d,v,t",
7347 macro_build ((char *) NULL, &icnt, &expr1, "xori", "t,r,i", dreg, dreg,
7348 (int) BFD_RELOC_LO16);
7351 case M_SLE_I: /* sreg <= I <==> I >= sreg <==> not (I < sreg) */
7357 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_GPRS);
7358 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "d,v,t",
7360 macro_build ((char *) NULL, &icnt, &expr1, "xori", "t,r,i", dreg, dreg,
7361 (int) BFD_RELOC_LO16);
7365 if (imm_expr.X_op == O_constant
7366 && imm_expr.X_add_number >= -0x8000
7367 && imm_expr.X_add_number < 0x8000)
7369 macro_build ((char *) NULL, &icnt, &imm_expr, "slti", "t,r,j",
7370 dreg, sreg, (int) BFD_RELOC_LO16);
7373 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_GPRS);
7374 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "slt", "d,v,t",
7379 if (imm_expr.X_op == O_constant
7380 && imm_expr.X_add_number >= -0x8000
7381 && imm_expr.X_add_number < 0x8000)
7383 macro_build ((char *) NULL, &icnt, &imm_expr, "sltiu", "t,r,j",
7384 dreg, sreg, (int) BFD_RELOC_LO16);
7387 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_GPRS);
7388 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sltu",
7389 "d,v,t", dreg, sreg, AT);
7394 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sltu",
7395 "d,v,t", dreg, 0, treg);
7397 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sltu",
7398 "d,v,t", dreg, 0, sreg);
7401 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "xor",
7402 "d,v,t", dreg, sreg, treg);
7403 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sltu",
7404 "d,v,t", dreg, 0, dreg);
7409 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
7411 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sltu",
7412 "d,v,t", dreg, 0, sreg);
7417 as_warn (_("Instruction %s: result is always true"),
7419 macro_build ((char *) NULL, &icnt, &expr1,
7420 HAVE_32BIT_GPRS ? "addiu" : "daddiu",
7421 "t,r,j", dreg, 0, (int) BFD_RELOC_LO16);
7424 if (imm_expr.X_op == O_constant
7425 && imm_expr.X_add_number >= 0
7426 && imm_expr.X_add_number < 0x10000)
7428 macro_build ((char *) NULL, &icnt, &imm_expr, "xori", "t,r,i",
7429 dreg, sreg, (int) BFD_RELOC_LO16);
7432 else if (imm_expr.X_op == O_constant
7433 && imm_expr.X_add_number > -0x8000
7434 && imm_expr.X_add_number < 0)
7436 imm_expr.X_add_number = -imm_expr.X_add_number;
7437 macro_build ((char *) NULL, &icnt, &imm_expr,
7438 HAVE_32BIT_GPRS ? "addiu" : "daddiu",
7439 "t,r,j", dreg, sreg, (int) BFD_RELOC_LO16);
7444 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_GPRS);
7445 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "xor",
7446 "d,v,t", dreg, sreg, AT);
7449 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sltu",
7450 "d,v,t", dreg, 0, dreg);
7458 if (imm_expr.X_op == O_constant
7459 && imm_expr.X_add_number > -0x8000
7460 && imm_expr.X_add_number <= 0x8000)
7462 imm_expr.X_add_number = -imm_expr.X_add_number;
7463 macro_build ((char *) NULL, &icnt, &imm_expr,
7464 dbl ? "daddi" : "addi",
7465 "t,r,j", dreg, sreg, (int) BFD_RELOC_LO16);
7468 load_register (&icnt, AT, &imm_expr, dbl);
7469 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7470 dbl ? "dsub" : "sub", "d,v,t", dreg, sreg, AT);
7476 if (imm_expr.X_op == O_constant
7477 && imm_expr.X_add_number > -0x8000
7478 && imm_expr.X_add_number <= 0x8000)
7480 imm_expr.X_add_number = -imm_expr.X_add_number;
7481 macro_build ((char *) NULL, &icnt, &imm_expr,
7482 dbl ? "daddiu" : "addiu",
7483 "t,r,j", dreg, sreg, (int) BFD_RELOC_LO16);
7486 load_register (&icnt, AT, &imm_expr, dbl);
7487 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7488 dbl ? "dsubu" : "subu", "d,v,t", dreg, sreg, AT);
7509 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_GPRS);
7510 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "s,t", sreg,
7516 assert (mips_opts.isa == ISA_MIPS1);
7517 sreg = (ip->insn_opcode >> 11) & 0x1f; /* floating reg */
7518 dreg = (ip->insn_opcode >> 06) & 0x1f; /* floating reg */
7521 * Is the double cfc1 instruction a bug in the mips assembler;
7522 * or is there a reason for it?
7524 mips_emit_delays (TRUE);
7525 ++mips_opts.noreorder;
7526 mips_any_noreorder = 1;
7527 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "cfc1", "t,G",
7529 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "cfc1", "t,G",
7531 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "");
7532 expr1.X_add_number = 3;
7533 macro_build ((char *) NULL, &icnt, &expr1, "ori", "t,r,i", AT, treg,
7534 (int) BFD_RELOC_LO16);
7535 expr1.X_add_number = 2;
7536 macro_build ((char *) NULL, &icnt, &expr1, "xori", "t,r,i", AT, AT,
7537 (int) BFD_RELOC_LO16);
7538 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "ctc1", "t,G",
7540 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "");
7541 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7542 mask == M_TRUNCWD ? "cvt.w.d" : "cvt.w.s", "D,S", dreg, sreg);
7543 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "ctc1", "t,G",
7545 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "");
7546 --mips_opts.noreorder;
7555 if (offset_expr.X_add_number >= 0x7fff)
7556 as_bad (_("operand overflow"));
7557 /* avoid load delay */
7558 if (! target_big_endian)
7559 ++offset_expr.X_add_number;
7560 macro_build ((char *) NULL, &icnt, &offset_expr, s, "t,o(b)", treg,
7561 (int) BFD_RELOC_LO16, breg);
7562 if (! target_big_endian)
7563 --offset_expr.X_add_number;
7565 ++offset_expr.X_add_number;
7566 macro_build ((char *) NULL, &icnt, &offset_expr, "lbu", "t,o(b)", AT,
7567 (int) BFD_RELOC_LO16, breg);
7568 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sll", "d,w,<",
7570 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or", "d,v,t",
7584 if (offset_expr.X_add_number >= 0x8000 - off)
7585 as_bad (_("operand overflow"));
7586 if (! target_big_endian)
7587 offset_expr.X_add_number += off;
7588 macro_build ((char *) NULL, &icnt, &offset_expr, s, "t,o(b)", treg,
7589 (int) BFD_RELOC_LO16, breg);
7590 if (! target_big_endian)
7591 offset_expr.X_add_number -= off;
7593 offset_expr.X_add_number += off;
7594 macro_build ((char *) NULL, &icnt, &offset_expr, s2, "t,o(b)", treg,
7595 (int) BFD_RELOC_LO16, breg);
7609 load_address (&icnt, AT, &offset_expr, &used_at);
7611 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7612 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
7613 "d,v,t", AT, AT, breg);
7614 if (! target_big_endian)
7615 expr1.X_add_number = off;
7617 expr1.X_add_number = 0;
7618 macro_build ((char *) NULL, &icnt, &expr1, s, "t,o(b)", treg,
7619 (int) BFD_RELOC_LO16, AT);
7620 if (! target_big_endian)
7621 expr1.X_add_number = 0;
7623 expr1.X_add_number = off;
7624 macro_build ((char *) NULL, &icnt, &expr1, s2, "t,o(b)", treg,
7625 (int) BFD_RELOC_LO16, AT);
7631 load_address (&icnt, AT, &offset_expr, &used_at);
7633 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7634 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
7635 "d,v,t", AT, AT, breg);
7636 if (target_big_endian)
7637 expr1.X_add_number = 0;
7638 macro_build ((char *) NULL, &icnt, &expr1,
7639 mask == M_ULH_A ? "lb" : "lbu", "t,o(b)", treg,
7640 (int) BFD_RELOC_LO16, AT);
7641 if (target_big_endian)
7642 expr1.X_add_number = 1;
7644 expr1.X_add_number = 0;
7645 macro_build ((char *) NULL, &icnt, &expr1, "lbu", "t,o(b)", AT,
7646 (int) BFD_RELOC_LO16, AT);
7647 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sll", "d,w,<",
7649 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or", "d,v,t",
7654 if (offset_expr.X_add_number >= 0x7fff)
7655 as_bad (_("operand overflow"));
7656 if (target_big_endian)
7657 ++offset_expr.X_add_number;
7658 macro_build ((char *) NULL, &icnt, &offset_expr, "sb", "t,o(b)", treg,
7659 (int) BFD_RELOC_LO16, breg);
7660 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "srl", "d,w,<",
7662 if (target_big_endian)
7663 --offset_expr.X_add_number;
7665 ++offset_expr.X_add_number;
7666 macro_build ((char *) NULL, &icnt, &offset_expr, "sb", "t,o(b)", AT,
7667 (int) BFD_RELOC_LO16, breg);
7680 if (offset_expr.X_add_number >= 0x8000 - off)
7681 as_bad (_("operand overflow"));
7682 if (! target_big_endian)
7683 offset_expr.X_add_number += off;
7684 macro_build ((char *) NULL, &icnt, &offset_expr, s, "t,o(b)", treg,
7685 (int) BFD_RELOC_LO16, breg);
7686 if (! target_big_endian)
7687 offset_expr.X_add_number -= off;
7689 offset_expr.X_add_number += off;
7690 macro_build ((char *) NULL, &icnt, &offset_expr, s2, "t,o(b)", treg,
7691 (int) BFD_RELOC_LO16, breg);
7705 load_address (&icnt, AT, &offset_expr, &used_at);
7707 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7708 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
7709 "d,v,t", AT, AT, breg);
7710 if (! target_big_endian)
7711 expr1.X_add_number = off;
7713 expr1.X_add_number = 0;
7714 macro_build ((char *) NULL, &icnt, &expr1, s, "t,o(b)", treg,
7715 (int) BFD_RELOC_LO16, AT);
7716 if (! target_big_endian)
7717 expr1.X_add_number = 0;
7719 expr1.X_add_number = off;
7720 macro_build ((char *) NULL, &icnt, &expr1, s2, "t,o(b)", treg,
7721 (int) BFD_RELOC_LO16, AT);
7726 load_address (&icnt, AT, &offset_expr, &used_at);
7728 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7729 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
7730 "d,v,t", AT, AT, breg);
7731 if (! target_big_endian)
7732 expr1.X_add_number = 0;
7733 macro_build ((char *) NULL, &icnt, &expr1, "sb", "t,o(b)", treg,
7734 (int) BFD_RELOC_LO16, AT);
7735 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "srl", "d,w,<",
7737 if (! target_big_endian)
7738 expr1.X_add_number = 1;
7740 expr1.X_add_number = 0;
7741 macro_build ((char *) NULL, &icnt, &expr1, "sb", "t,o(b)", treg,
7742 (int) BFD_RELOC_LO16, AT);
7743 if (! target_big_endian)
7744 expr1.X_add_number = 0;
7746 expr1.X_add_number = 1;
7747 macro_build ((char *) NULL, &icnt, &expr1, "lbu", "t,o(b)", AT,
7748 (int) BFD_RELOC_LO16, AT);
7749 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sll", "d,w,<",
7751 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or", "d,v,t",
7756 /* FIXME: Check if this is one of the itbl macros, since they
7757 are added dynamically. */
7758 as_bad (_("Macro %s not implemented yet"), ip->insn_mo->name);
7762 as_warn (_("Macro used $at after \".set noat\""));
7765 /* Implement macros in mips16 mode. */
7769 struct mips_cl_insn *ip;
7772 int xreg, yreg, zreg, tmp;
7776 const char *s, *s2, *s3;
7778 mask = ip->insn_mo->mask;
7780 xreg = (ip->insn_opcode >> MIPS16OP_SH_RX) & MIPS16OP_MASK_RX;
7781 yreg = (ip->insn_opcode >> MIPS16OP_SH_RY) & MIPS16OP_MASK_RY;
7782 zreg = (ip->insn_opcode >> MIPS16OP_SH_RZ) & MIPS16OP_MASK_RZ;
7786 expr1.X_op = O_constant;
7787 expr1.X_op_symbol = NULL;
7788 expr1.X_add_symbol = NULL;
7789 expr1.X_add_number = 1;
7808 mips_emit_delays (TRUE);
7809 ++mips_opts.noreorder;
7810 mips_any_noreorder = 1;
7811 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7812 dbl ? "ddiv" : "div",
7813 "0,x,y", xreg, yreg);
7814 expr1.X_add_number = 2;
7815 macro_build ((char *) NULL, &icnt, &expr1, "bnez", "x,p", yreg);
7816 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "break", "6",
7819 /* FIXME: The normal code checks for of -1 / -0x80000000 here,
7820 since that causes an overflow. We should do that as well,
7821 but I don't see how to do the comparisons without a temporary
7823 --mips_opts.noreorder;
7824 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "x", zreg);
7843 mips_emit_delays (TRUE);
7844 ++mips_opts.noreorder;
7845 mips_any_noreorder = 1;
7846 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "0,x,y",
7848 expr1.X_add_number = 2;
7849 macro_build ((char *) NULL, &icnt, &expr1, "bnez", "x,p", yreg);
7850 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "break",
7852 --mips_opts.noreorder;
7853 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s2, "x", zreg);
7859 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7860 dbl ? "dmultu" : "multu", "x,y", xreg, yreg);
7861 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "mflo", "x",
7870 if (imm_expr.X_op != O_constant)
7871 as_bad (_("Unsupported large constant"));
7872 imm_expr.X_add_number = -imm_expr.X_add_number;
7873 macro_build ((char *) NULL, &icnt, &imm_expr,
7874 dbl ? "daddiu" : "addiu", "y,x,4", yreg, xreg);
7878 if (imm_expr.X_op != O_constant)
7879 as_bad (_("Unsupported large constant"));
7880 imm_expr.X_add_number = -imm_expr.X_add_number;
7881 macro_build ((char *) NULL, &icnt, &imm_expr, "addiu",
7886 if (imm_expr.X_op != O_constant)
7887 as_bad (_("Unsupported large constant"));
7888 imm_expr.X_add_number = -imm_expr.X_add_number;
7889 macro_build ((char *) NULL, &icnt, &imm_expr, "daddiu",
7912 goto do_reverse_branch;
7916 goto do_reverse_branch;
7928 goto do_reverse_branch;
7939 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "x,y",
7941 macro_build ((char *) NULL, &icnt, &offset_expr, s2, "p");
7968 goto do_addone_branch_i;
7973 goto do_addone_branch_i;
7988 goto do_addone_branch_i;
7995 if (imm_expr.X_op != O_constant)
7996 as_bad (_("Unsupported large constant"));
7997 ++imm_expr.X_add_number;
8000 macro_build ((char *) NULL, &icnt, &imm_expr, s, s3, xreg);
8001 macro_build ((char *) NULL, &icnt, &offset_expr, s2, "p");
8005 expr1.X_add_number = 0;
8006 macro_build ((char *) NULL, &icnt, &expr1, "slti", "x,8", yreg);
8008 move_register (&icnt, xreg, yreg);
8009 expr1.X_add_number = 2;
8010 macro_build ((char *) NULL, &icnt, &expr1, "bteqz", "p");
8011 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
8012 "neg", "x,w", xreg, xreg);
8016 /* For consistency checking, verify that all bits are specified either
8017 by the match/mask part of the instruction definition, or by the
8020 validate_mips_insn (opc)
8021 const struct mips_opcode *opc;
8023 const char *p = opc->args;
8025 unsigned long used_bits = opc->mask;
8027 if ((used_bits & opc->match) != opc->match)
8029 as_bad (_("internal: bad mips opcode (mask error): %s %s"),
8030 opc->name, opc->args);
8033 #define USE_BITS(mask,shift) (used_bits |= ((mask) << (shift)))
8043 case 'A': USE_BITS (OP_MASK_SHAMT, OP_SH_SHAMT); break;
8044 case 'B': USE_BITS (OP_MASK_INSMSB, OP_SH_INSMSB); break;
8045 case 'C': USE_BITS (OP_MASK_EXTMSBD, OP_SH_EXTMSBD); break;
8046 case 'D': USE_BITS (OP_MASK_RD, OP_SH_RD);
8047 USE_BITS (OP_MASK_SEL, OP_SH_SEL); break;
8049 as_bad (_("internal: bad mips opcode (unknown extension operand type `+%c'): %s %s"),
8050 c, opc->name, opc->args);
8054 case '<': USE_BITS (OP_MASK_SHAMT, OP_SH_SHAMT); break;
8055 case '>': USE_BITS (OP_MASK_SHAMT, OP_SH_SHAMT); break;
8057 case 'B': USE_BITS (OP_MASK_CODE20, OP_SH_CODE20); break;
8058 case 'C': USE_BITS (OP_MASK_COPZ, OP_SH_COPZ); break;
8059 case 'D': USE_BITS (OP_MASK_FD, OP_SH_FD); break;
8060 case 'E': USE_BITS (OP_MASK_RT, OP_SH_RT); break;
8062 case 'G': USE_BITS (OP_MASK_RD, OP_SH_RD); break;
8063 case 'H': USE_BITS (OP_MASK_SEL, OP_SH_SEL); break;
8065 case 'J': USE_BITS (OP_MASK_CODE19, OP_SH_CODE19); break;
8066 case 'K': USE_BITS (OP_MASK_RD, OP_SH_RD); break;
8068 case 'M': USE_BITS (OP_MASK_CCC, OP_SH_CCC); break;
8069 case 'N': USE_BITS (OP_MASK_BCC, OP_SH_BCC); break;
8070 case 'O': USE_BITS (OP_MASK_ALN, OP_SH_ALN); break;
8071 case 'Q': USE_BITS (OP_MASK_VSEL, OP_SH_VSEL);
8072 USE_BITS (OP_MASK_FT, OP_SH_FT); break;
8073 case 'R': USE_BITS (OP_MASK_FR, OP_SH_FR); break;
8074 case 'S': USE_BITS (OP_MASK_FS, OP_SH_FS); break;
8075 case 'T': USE_BITS (OP_MASK_FT, OP_SH_FT); break;
8076 case 'V': USE_BITS (OP_MASK_FS, OP_SH_FS); break;
8077 case 'W': USE_BITS (OP_MASK_FT, OP_SH_FT); break;
8078 case 'X': USE_BITS (OP_MASK_FD, OP_SH_FD); break;
8079 case 'Y': USE_BITS (OP_MASK_FS, OP_SH_FS); break;
8080 case 'Z': USE_BITS (OP_MASK_FT, OP_SH_FT); break;
8081 case 'a': USE_BITS (OP_MASK_TARGET, OP_SH_TARGET); break;
8082 case 'b': USE_BITS (OP_MASK_RS, OP_SH_RS); break;
8083 case 'c': USE_BITS (OP_MASK_CODE, OP_SH_CODE); break;
8084 case 'd': USE_BITS (OP_MASK_RD, OP_SH_RD); break;
8086 case 'h': USE_BITS (OP_MASK_PREFX, OP_SH_PREFX); break;
8087 case 'i': USE_BITS (OP_MASK_IMMEDIATE, OP_SH_IMMEDIATE); break;
8088 case 'j': USE_BITS (OP_MASK_DELTA, OP_SH_DELTA); break;
8089 case 'k': USE_BITS (OP_MASK_CACHE, OP_SH_CACHE); break;
8091 case 'o': USE_BITS (OP_MASK_DELTA, OP_SH_DELTA); break;
8092 case 'p': USE_BITS (OP_MASK_DELTA, OP_SH_DELTA); break;
8093 case 'q': USE_BITS (OP_MASK_CODE2, OP_SH_CODE2); break;
8094 case 'r': USE_BITS (OP_MASK_RS, OP_SH_RS); break;
8095 case 's': USE_BITS (OP_MASK_RS, OP_SH_RS); break;
8096 case 't': USE_BITS (OP_MASK_RT, OP_SH_RT); break;
8097 case 'u': USE_BITS (OP_MASK_IMMEDIATE, OP_SH_IMMEDIATE); break;
8098 case 'v': USE_BITS (OP_MASK_RS, OP_SH_RS); break;
8099 case 'w': USE_BITS (OP_MASK_RT, OP_SH_RT); break;
8102 case 'P': USE_BITS (OP_MASK_PERFREG, OP_SH_PERFREG); break;
8103 case 'U': USE_BITS (OP_MASK_RD, OP_SH_RD);
8104 USE_BITS (OP_MASK_RT, OP_SH_RT); break;
8105 case 'e': USE_BITS (OP_MASK_VECBYTE, OP_SH_VECBYTE); break;
8106 case '%': USE_BITS (OP_MASK_VECALIGN, OP_SH_VECALIGN); break;
8110 as_bad (_("internal: bad mips opcode (unknown operand type `%c'): %s %s"),
8111 c, opc->name, opc->args);
8115 if (used_bits != 0xffffffff)
8117 as_bad (_("internal: bad mips opcode (bits 0x%lx undefined): %s %s"),
8118 ~used_bits & 0xffffffff, opc->name, opc->args);
8124 /* This routine assembles an instruction into its binary format. As a
8125 side effect, it sets one of the global variables imm_reloc or
8126 offset_reloc to the type of relocation to do if one of the operands
8127 is an address expression. */
8132 struct mips_cl_insn *ip;
8137 struct mips_opcode *insn;
8140 unsigned int lastregno = 0;
8141 unsigned int lastpos = 0;
8142 unsigned int limlo, limhi;
8148 /* If the instruction contains a '.', we first try to match an instruction
8149 including the '.'. Then we try again without the '.'. */
8151 for (s = str; *s != '\0' && !ISSPACE (*s); ++s)
8154 /* If we stopped on whitespace, then replace the whitespace with null for
8155 the call to hash_find. Save the character we replaced just in case we
8156 have to re-parse the instruction. */
8163 insn = (struct mips_opcode *) hash_find (op_hash, str);
8165 /* If we didn't find the instruction in the opcode table, try again, but
8166 this time with just the instruction up to, but not including the
8170 /* Restore the character we overwrite above (if any). */
8174 /* Scan up to the first '.' or whitespace. */
8176 *s != '\0' && *s != '.' && !ISSPACE (*s);
8180 /* If we did not find a '.', then we can quit now. */
8183 insn_error = "unrecognized opcode";
8187 /* Lookup the instruction in the hash table. */
8189 if ((insn = (struct mips_opcode *) hash_find (op_hash, str)) == NULL)
8191 insn_error = "unrecognized opcode";
8201 assert (strcmp (insn->name, str) == 0);
8203 if (OPCODE_IS_MEMBER (insn,
8205 | (file_ase_mips16 ? INSN_MIPS16 : 0)
8206 | (mips_opts.ase_mdmx ? INSN_MDMX : 0)
8207 | (mips_opts.ase_mips3d ? INSN_MIPS3D : 0)),
8213 if (insn->pinfo != INSN_MACRO)
8215 if (mips_arch == CPU_R4650 && (insn->pinfo & FP_D) != 0)
8221 if (insn + 1 < &mips_opcodes[NUMOPCODES]
8222 && strcmp (insn->name, insn[1].name) == 0)
8231 static char buf[100];
8232 if (mips_arch_info->is_isa)
8234 _("opcode not supported at this ISA level (%s)"),
8235 mips_cpu_info_from_isa (mips_opts.isa)->name);
8238 _("opcode not supported on this processor: %s (%s)"),
8239 mips_arch_info->name,
8240 mips_cpu_info_from_isa (mips_opts.isa)->name);
8250 ip->insn_opcode = insn->match;
8252 for (args = insn->args;; ++args)
8256 s += strspn (s, " \t");
8260 case '\0': /* end of args */
8273 ip->insn_opcode |= lastregno << OP_SH_RS;
8277 ip->insn_opcode |= lastregno << OP_SH_RT;
8281 ip->insn_opcode |= lastregno << OP_SH_FT;
8285 ip->insn_opcode |= lastregno << OP_SH_FS;
8291 /* Handle optional base register.
8292 Either the base register is omitted or
8293 we must have a left paren. */
8294 /* This is dependent on the next operand specifier
8295 is a base register specification. */
8296 assert (args[1] == 'b' || args[1] == '5'
8297 || args[1] == '-' || args[1] == '4');
8301 case ')': /* these must match exactly */
8308 case '+': /* Opcode extension character. */
8311 case 'A': /* ins/ext position, becomes LSB. */
8314 my_getExpression (&imm_expr, s);
8315 check_absolute_expr (ip, &imm_expr);
8316 if ((unsigned long) imm_expr.X_add_number < limlo
8317 || (unsigned long) imm_expr.X_add_number > limhi)
8319 as_bad (_("Improper position (%lu)"),
8320 (unsigned long) imm_expr.X_add_number);
8321 imm_expr.X_add_number = limlo;
8323 lastpos = imm_expr.X_add_number;
8324 ip->insn_opcode |= (imm_expr.X_add_number
8325 & OP_MASK_SHAMT) << OP_SH_SHAMT;
8326 imm_expr.X_op = O_absent;
8330 case 'B': /* ins size, becomes MSB. */
8333 my_getExpression (&imm_expr, s);
8334 check_absolute_expr (ip, &imm_expr);
8335 /* Check for negative input so that small negative numbers
8336 will not succeed incorrectly. The checks against
8337 (pos+size) transitively check "size" itself,
8338 assuming that "pos" is reasonable. */
8339 if ((long) imm_expr.X_add_number < 0
8340 || ((unsigned long) imm_expr.X_add_number
8342 || ((unsigned long) imm_expr.X_add_number
8345 as_bad (_("Improper insert size (%lu, position %lu)"),
8346 (unsigned long) imm_expr.X_add_number,
8347 (unsigned long) lastpos);
8348 imm_expr.X_add_number = limlo - lastpos;
8350 ip->insn_opcode |= ((lastpos + imm_expr.X_add_number - 1)
8351 & OP_MASK_INSMSB) << OP_SH_INSMSB;
8352 imm_expr.X_op = O_absent;
8356 case 'C': /* ext size, becomes MSBD. */
8359 my_getExpression (&imm_expr, s);
8360 check_absolute_expr (ip, &imm_expr);
8361 /* Check for negative input so that small negative numbers
8362 will not succeed incorrectly. The checks against
8363 (pos+size) transitively check "size" itself,
8364 assuming that "pos" is reasonable. */
8365 if ((long) imm_expr.X_add_number < 0
8366 || ((unsigned long) imm_expr.X_add_number
8368 || ((unsigned long) imm_expr.X_add_number
8371 as_bad (_("Improper extract size (%lu, position %lu)"),
8372 (unsigned long) imm_expr.X_add_number,
8373 (unsigned long) lastpos);
8374 imm_expr.X_add_number = limlo - lastpos;
8376 ip->insn_opcode |= ((imm_expr.X_add_number - 1)
8377 & OP_MASK_EXTMSBD) << OP_SH_EXTMSBD;
8378 imm_expr.X_op = O_absent;
8383 /* +D is for disassembly only; never match. */
8387 as_bad (_("internal: bad mips opcode (unknown extension operand type `+%c'): %s %s"),
8388 *args, insn->name, insn->args);
8389 /* Further processing is fruitless. */
8394 case '<': /* must be at least one digit */
8396 * According to the manual, if the shift amount is greater
8397 * than 31 or less than 0, then the shift amount should be
8398 * mod 32. In reality the mips assembler issues an error.
8399 * We issue a warning and mask out all but the low 5 bits.
8401 my_getExpression (&imm_expr, s);
8402 check_absolute_expr (ip, &imm_expr);
8403 if ((unsigned long) imm_expr.X_add_number > 31)
8405 as_warn (_("Improper shift amount (%lu)"),
8406 (unsigned long) imm_expr.X_add_number);
8407 imm_expr.X_add_number &= OP_MASK_SHAMT;
8409 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_SHAMT;
8410 imm_expr.X_op = O_absent;
8414 case '>': /* shift amount minus 32 */
8415 my_getExpression (&imm_expr, s);
8416 check_absolute_expr (ip, &imm_expr);
8417 if ((unsigned long) imm_expr.X_add_number < 32
8418 || (unsigned long) imm_expr.X_add_number > 63)
8420 ip->insn_opcode |= (imm_expr.X_add_number - 32) << OP_SH_SHAMT;
8421 imm_expr.X_op = O_absent;
8425 case 'k': /* cache code */
8426 case 'h': /* prefx code */
8427 my_getExpression (&imm_expr, s);
8428 check_absolute_expr (ip, &imm_expr);
8429 if ((unsigned long) imm_expr.X_add_number > 31)
8431 as_warn (_("Invalid value for `%s' (%lu)"),
8433 (unsigned long) imm_expr.X_add_number);
8434 imm_expr.X_add_number &= 0x1f;
8437 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_CACHE;
8439 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_PREFX;
8440 imm_expr.X_op = O_absent;
8444 case 'c': /* break code */
8445 my_getExpression (&imm_expr, s);
8446 check_absolute_expr (ip, &imm_expr);
8447 if ((unsigned long) imm_expr.X_add_number > 1023)
8449 as_warn (_("Illegal break code (%lu)"),
8450 (unsigned long) imm_expr.X_add_number);
8451 imm_expr.X_add_number &= OP_MASK_CODE;
8453 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_CODE;
8454 imm_expr.X_op = O_absent;
8458 case 'q': /* lower break code */
8459 my_getExpression (&imm_expr, s);
8460 check_absolute_expr (ip, &imm_expr);
8461 if ((unsigned long) imm_expr.X_add_number > 1023)
8463 as_warn (_("Illegal lower break code (%lu)"),
8464 (unsigned long) imm_expr.X_add_number);
8465 imm_expr.X_add_number &= OP_MASK_CODE2;
8467 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_CODE2;
8468 imm_expr.X_op = O_absent;
8472 case 'B': /* 20-bit syscall/break code. */
8473 my_getExpression (&imm_expr, s);
8474 check_absolute_expr (ip, &imm_expr);
8475 if ((unsigned long) imm_expr.X_add_number > OP_MASK_CODE20)
8476 as_warn (_("Illegal 20-bit code (%lu)"),
8477 (unsigned long) imm_expr.X_add_number);
8478 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_CODE20;
8479 imm_expr.X_op = O_absent;
8483 case 'C': /* Coprocessor code */
8484 my_getExpression (&imm_expr, s);
8485 check_absolute_expr (ip, &imm_expr);
8486 if ((unsigned long) imm_expr.X_add_number >= (1 << 25))
8488 as_warn (_("Coproccesor code > 25 bits (%lu)"),
8489 (unsigned long) imm_expr.X_add_number);
8490 imm_expr.X_add_number &= ((1 << 25) - 1);
8492 ip->insn_opcode |= imm_expr.X_add_number;
8493 imm_expr.X_op = O_absent;
8497 case 'J': /* 19-bit wait code. */
8498 my_getExpression (&imm_expr, s);
8499 check_absolute_expr (ip, &imm_expr);
8500 if ((unsigned long) imm_expr.X_add_number > OP_MASK_CODE19)
8501 as_warn (_("Illegal 19-bit code (%lu)"),
8502 (unsigned long) imm_expr.X_add_number);
8503 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_CODE19;
8504 imm_expr.X_op = O_absent;
8508 case 'P': /* Performance register */
8509 my_getExpression (&imm_expr, s);
8510 check_absolute_expr (ip, &imm_expr);
8511 if (imm_expr.X_add_number != 0 && imm_expr.X_add_number != 1)
8513 as_warn (_("Invalid performance register (%lu)"),
8514 (unsigned long) imm_expr.X_add_number);
8515 imm_expr.X_add_number &= OP_MASK_PERFREG;
8517 ip->insn_opcode |= (imm_expr.X_add_number << OP_SH_PERFREG);
8518 imm_expr.X_op = O_absent;
8522 case 'b': /* base register */
8523 case 'd': /* destination register */
8524 case 's': /* source register */
8525 case 't': /* target register */
8526 case 'r': /* both target and source */
8527 case 'v': /* both dest and source */
8528 case 'w': /* both dest and target */
8529 case 'E': /* coprocessor target register */
8530 case 'G': /* coprocessor destination register */
8531 case 'K': /* 'rdhwr' destination register */
8532 case 'x': /* ignore register name */
8533 case 'z': /* must be zero register */
8534 case 'U': /* destination register (clo/clz). */
8549 while (ISDIGIT (*s));
8551 as_bad (_("Invalid register number (%d)"), regno);
8553 else if (*args == 'E' || *args == 'G' || *args == 'K')
8557 if (s[1] == 'r' && s[2] == 'a')
8562 else if (s[1] == 'f' && s[2] == 'p')
8567 else if (s[1] == 's' && s[2] == 'p')
8572 else if (s[1] == 'g' && s[2] == 'p')
8577 else if (s[1] == 'a' && s[2] == 't')
8582 else if (s[1] == 'k' && s[2] == 't' && s[3] == '0')
8587 else if (s[1] == 'k' && s[2] == 't' && s[3] == '1')
8592 else if (s[1] == 'z' && s[2] == 'e' && s[3] == 'r' && s[4] == 'o')
8597 else if (itbl_have_entries)
8602 p = s + 1; /* advance past '$' */
8603 n = itbl_get_field (&p); /* n is name */
8605 /* See if this is a register defined in an
8607 if (itbl_get_reg_val (n, &r))
8609 /* Get_field advances to the start of
8610 the next field, so we need to back
8611 rack to the end of the last field. */
8615 s = strchr (s, '\0');
8629 as_warn (_("Used $at without \".set noat\""));
8635 if (c == 'r' || c == 'v' || c == 'w')
8642 /* 'z' only matches $0. */
8643 if (c == 'z' && regno != 0)
8646 /* Now that we have assembled one operand, we use the args string
8647 * to figure out where it goes in the instruction. */
8654 ip->insn_opcode |= regno << OP_SH_RS;
8659 ip->insn_opcode |= regno << OP_SH_RD;
8662 ip->insn_opcode |= regno << OP_SH_RD;
8663 ip->insn_opcode |= regno << OP_SH_RT;
8668 ip->insn_opcode |= regno << OP_SH_RT;
8671 /* This case exists because on the r3000 trunc
8672 expands into a macro which requires a gp
8673 register. On the r6000 or r4000 it is
8674 assembled into a single instruction which
8675 ignores the register. Thus the insn version
8676 is MIPS_ISA2 and uses 'x', and the macro
8677 version is MIPS_ISA1 and uses 't'. */
8680 /* This case is for the div instruction, which
8681 acts differently if the destination argument
8682 is $0. This only matches $0, and is checked
8683 outside the switch. */
8686 /* Itbl operand; not yet implemented. FIXME ?? */
8688 /* What about all other operands like 'i', which
8689 can be specified in the opcode table? */
8699 ip->insn_opcode |= lastregno << OP_SH_RS;
8702 ip->insn_opcode |= lastregno << OP_SH_RT;
8707 case 'O': /* MDMX alignment immediate constant. */
8708 my_getExpression (&imm_expr, s);
8709 check_absolute_expr (ip, &imm_expr);
8710 if ((unsigned long) imm_expr.X_add_number > OP_MASK_ALN)
8712 as_warn ("Improper align amount (%ld), using low bits",
8713 (long) imm_expr.X_add_number);
8714 imm_expr.X_add_number &= OP_MASK_ALN;
8716 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_ALN;
8717 imm_expr.X_op = O_absent;
8721 case 'Q': /* MDMX vector, element sel, or const. */
8724 /* MDMX Immediate. */
8725 my_getExpression (&imm_expr, s);
8726 check_absolute_expr (ip, &imm_expr);
8727 if ((unsigned long) imm_expr.X_add_number > OP_MASK_FT)
8729 as_warn (_("Invalid MDMX Immediate (%ld)"),
8730 (long) imm_expr.X_add_number);
8731 imm_expr.X_add_number &= OP_MASK_FT;
8733 imm_expr.X_add_number &= OP_MASK_FT;
8734 if (ip->insn_opcode & (OP_MASK_VSEL << OP_SH_VSEL))
8735 ip->insn_opcode |= MDMX_FMTSEL_IMM_QH << OP_SH_VSEL;
8737 ip->insn_opcode |= MDMX_FMTSEL_IMM_OB << OP_SH_VSEL;
8738 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_FT;
8739 imm_expr.X_op = O_absent;
8743 /* Not MDMX Immediate. Fall through. */
8744 case 'X': /* MDMX destination register. */
8745 case 'Y': /* MDMX source register. */
8746 case 'Z': /* MDMX target register. */
8748 case 'D': /* floating point destination register */
8749 case 'S': /* floating point source register */
8750 case 'T': /* floating point target register */
8751 case 'R': /* floating point source register */
8755 /* Accept $fN for FP and MDMX register numbers, and in
8756 addition accept $vN for MDMX register numbers. */
8757 if ((s[0] == '$' && s[1] == 'f' && ISDIGIT (s[2]))
8758 || (is_mdmx != 0 && s[0] == '$' && s[1] == 'v'
8769 while (ISDIGIT (*s));
8772 as_bad (_("Invalid float register number (%d)"), regno);
8774 if ((regno & 1) != 0
8776 && ! (strcmp (str, "mtc1") == 0
8777 || strcmp (str, "mfc1") == 0
8778 || strcmp (str, "lwc1") == 0
8779 || strcmp (str, "swc1") == 0
8780 || strcmp (str, "l.s") == 0
8781 || strcmp (str, "s.s") == 0))
8782 as_warn (_("Float register should be even, was %d"),
8790 if (c == 'V' || c == 'W')
8801 ip->insn_opcode |= regno << OP_SH_FD;
8806 ip->insn_opcode |= regno << OP_SH_FS;
8809 /* This is like 'Z', but also needs to fix the MDMX
8810 vector/scalar select bits. Note that the
8811 scalar immediate case is handled above. */
8814 int is_qh = (ip->insn_opcode & (1 << OP_SH_VSEL));
8815 int max_el = (is_qh ? 3 : 7);
8817 my_getExpression(&imm_expr, s);
8818 check_absolute_expr (ip, &imm_expr);
8820 if (imm_expr.X_add_number > max_el)
8821 as_bad(_("Bad element selector %ld"),
8822 (long) imm_expr.X_add_number);
8823 imm_expr.X_add_number &= max_el;
8824 ip->insn_opcode |= (imm_expr.X_add_number
8828 as_warn(_("Expecting ']' found '%s'"), s);
8834 if (ip->insn_opcode & (OP_MASK_VSEL << OP_SH_VSEL))
8835 ip->insn_opcode |= (MDMX_FMTSEL_VEC_QH
8838 ip->insn_opcode |= (MDMX_FMTSEL_VEC_OB <<
8845 ip->insn_opcode |= regno << OP_SH_FT;
8848 ip->insn_opcode |= regno << OP_SH_FR;
8858 ip->insn_opcode |= lastregno << OP_SH_FS;
8861 ip->insn_opcode |= lastregno << OP_SH_FT;
8867 my_getExpression (&imm_expr, s);
8868 if (imm_expr.X_op != O_big
8869 && imm_expr.X_op != O_constant)
8870 insn_error = _("absolute expression required");
8875 my_getExpression (&offset_expr, s);
8876 *imm_reloc = BFD_RELOC_32;
8889 unsigned char temp[8];
8891 unsigned int length;
8896 /* These only appear as the last operand in an
8897 instruction, and every instruction that accepts
8898 them in any variant accepts them in all variants.
8899 This means we don't have to worry about backing out
8900 any changes if the instruction does not match.
8902 The difference between them is the size of the
8903 floating point constant and where it goes. For 'F'
8904 and 'L' the constant is 64 bits; for 'f' and 'l' it
8905 is 32 bits. Where the constant is placed is based
8906 on how the MIPS assembler does things:
8909 f -- immediate value
8912 The .lit4 and .lit8 sections are only used if
8913 permitted by the -G argument.
8915 When generating embedded PIC code, we use the
8916 .lit8 section but not the .lit4 section (we can do
8917 .lit4 inline easily; we need to put .lit8
8918 somewhere in the data segment, and using .lit8
8919 permits the linker to eventually combine identical
8922 The code below needs to know whether the target register
8923 is 32 or 64 bits wide. It relies on the fact 'f' and
8924 'F' are used with GPR-based instructions and 'l' and
8925 'L' are used with FPR-based instructions. */
8927 f64 = *args == 'F' || *args == 'L';
8928 using_gprs = *args == 'F' || *args == 'f';
8930 save_in = input_line_pointer;
8931 input_line_pointer = s;
8932 err = md_atof (f64 ? 'd' : 'f', (char *) temp, &len);
8934 s = input_line_pointer;
8935 input_line_pointer = save_in;
8936 if (err != NULL && *err != '\0')
8938 as_bad (_("Bad floating point constant: %s"), err);
8939 memset (temp, '\0', sizeof temp);
8940 length = f64 ? 8 : 4;
8943 assert (length == (unsigned) (f64 ? 8 : 4));
8947 && (! USE_GLOBAL_POINTER_OPT
8948 || mips_pic == EMBEDDED_PIC
8949 || g_switch_value < 4
8950 || (temp[0] == 0 && temp[1] == 0)
8951 || (temp[2] == 0 && temp[3] == 0))))
8953 imm_expr.X_op = O_constant;
8954 if (! target_big_endian)
8955 imm_expr.X_add_number = bfd_getl32 (temp);
8957 imm_expr.X_add_number = bfd_getb32 (temp);
8960 && ! mips_disable_float_construction
8961 /* Constants can only be constructed in GPRs and
8962 copied to FPRs if the GPRs are at least as wide
8963 as the FPRs. Force the constant into memory if
8964 we are using 64-bit FPRs but the GPRs are only
8967 || ! (HAVE_64BIT_FPRS && HAVE_32BIT_GPRS))
8968 && ((temp[0] == 0 && temp[1] == 0)
8969 || (temp[2] == 0 && temp[3] == 0))
8970 && ((temp[4] == 0 && temp[5] == 0)
8971 || (temp[6] == 0 && temp[7] == 0)))
8973 /* The value is simple enough to load with a couple of
8974 instructions. If using 32-bit registers, set
8975 imm_expr to the high order 32 bits and offset_expr to
8976 the low order 32 bits. Otherwise, set imm_expr to
8977 the entire 64 bit constant. */
8978 if (using_gprs ? HAVE_32BIT_GPRS : HAVE_32BIT_FPRS)
8980 imm_expr.X_op = O_constant;
8981 offset_expr.X_op = O_constant;
8982 if (! target_big_endian)
8984 imm_expr.X_add_number = bfd_getl32 (temp + 4);
8985 offset_expr.X_add_number = bfd_getl32 (temp);
8989 imm_expr.X_add_number = bfd_getb32 (temp);
8990 offset_expr.X_add_number = bfd_getb32 (temp + 4);
8992 if (offset_expr.X_add_number == 0)
8993 offset_expr.X_op = O_absent;
8995 else if (sizeof (imm_expr.X_add_number) > 4)
8997 imm_expr.X_op = O_constant;
8998 if (! target_big_endian)
8999 imm_expr.X_add_number = bfd_getl64 (temp);
9001 imm_expr.X_add_number = bfd_getb64 (temp);
9005 imm_expr.X_op = O_big;
9006 imm_expr.X_add_number = 4;
9007 if (! target_big_endian)
9009 generic_bignum[0] = bfd_getl16 (temp);
9010 generic_bignum[1] = bfd_getl16 (temp + 2);
9011 generic_bignum[2] = bfd_getl16 (temp + 4);
9012 generic_bignum[3] = bfd_getl16 (temp + 6);
9016 generic_bignum[0] = bfd_getb16 (temp + 6);
9017 generic_bignum[1] = bfd_getb16 (temp + 4);
9018 generic_bignum[2] = bfd_getb16 (temp + 2);
9019 generic_bignum[3] = bfd_getb16 (temp);
9025 const char *newname;
9028 /* Switch to the right section. */
9030 subseg = now_subseg;
9033 default: /* unused default case avoids warnings. */
9035 newname = RDATA_SECTION_NAME;
9036 if ((USE_GLOBAL_POINTER_OPT && g_switch_value >= 8)
9037 || mips_pic == EMBEDDED_PIC)
9041 if (mips_pic == EMBEDDED_PIC)
9044 newname = RDATA_SECTION_NAME;
9047 assert (!USE_GLOBAL_POINTER_OPT
9048 || g_switch_value >= 4);
9052 new_seg = subseg_new (newname, (subsegT) 0);
9053 if (OUTPUT_FLAVOR == bfd_target_elf_flavour)
9054 bfd_set_section_flags (stdoutput, new_seg,
9059 frag_align (*args == 'l' ? 2 : 3, 0, 0);
9060 if (OUTPUT_FLAVOR == bfd_target_elf_flavour
9061 && strcmp (TARGET_OS, "elf") != 0)
9062 record_alignment (new_seg, 4);
9064 record_alignment (new_seg, *args == 'l' ? 2 : 3);
9066 as_bad (_("Can't use floating point insn in this section"));
9068 /* Set the argument to the current address in the
9070 offset_expr.X_op = O_symbol;
9071 offset_expr.X_add_symbol =
9072 symbol_new ("L0\001", now_seg,
9073 (valueT) frag_now_fix (), frag_now);
9074 offset_expr.X_add_number = 0;
9076 /* Put the floating point number into the section. */
9077 p = frag_more ((int) length);
9078 memcpy (p, temp, length);
9080 /* Switch back to the original section. */
9081 subseg_set (seg, subseg);
9086 case 'i': /* 16 bit unsigned immediate */
9087 case 'j': /* 16 bit signed immediate */
9088 *imm_reloc = BFD_RELOC_LO16;
9089 if (my_getSmallExpression (&imm_expr, imm_reloc, s) == 0)
9092 offsetT minval, maxval;
9094 more = (insn + 1 < &mips_opcodes[NUMOPCODES]
9095 && strcmp (insn->name, insn[1].name) == 0);
9097 /* If the expression was written as an unsigned number,
9098 only treat it as signed if there are no more
9102 && sizeof (imm_expr.X_add_number) <= 4
9103 && imm_expr.X_op == O_constant
9104 && imm_expr.X_add_number < 0
9105 && imm_expr.X_unsigned
9109 /* For compatibility with older assemblers, we accept
9110 0x8000-0xffff as signed 16-bit numbers when only
9111 signed numbers are allowed. */
9113 minval = 0, maxval = 0xffff;
9115 minval = -0x8000, maxval = 0x7fff;
9117 minval = -0x8000, maxval = 0xffff;
9119 if (imm_expr.X_op != O_constant
9120 || imm_expr.X_add_number < minval
9121 || imm_expr.X_add_number > maxval)
9125 if (imm_expr.X_op == O_constant
9126 || imm_expr.X_op == O_big)
9127 as_bad (_("expression out of range"));
9133 case 'o': /* 16 bit offset */
9134 /* Check whether there is only a single bracketed expression
9135 left. If so, it must be the base register and the
9136 constant must be zero. */
9137 if (*s == '(' && strchr (s + 1, '(') == 0)
9139 offset_expr.X_op = O_constant;
9140 offset_expr.X_add_number = 0;
9144 /* If this value won't fit into a 16 bit offset, then go
9145 find a macro that will generate the 32 bit offset
9147 if (my_getSmallExpression (&offset_expr, offset_reloc, s) == 0
9148 && (offset_expr.X_op != O_constant
9149 || offset_expr.X_add_number >= 0x8000
9150 || offset_expr.X_add_number < -0x8000))
9156 case 'p': /* pc relative offset */
9157 *offset_reloc = BFD_RELOC_16_PCREL_S2;
9158 my_getExpression (&offset_expr, s);
9162 case 'u': /* upper 16 bits */
9163 if (my_getSmallExpression (&imm_expr, imm_reloc, s) == 0
9164 && imm_expr.X_op == O_constant
9165 && (imm_expr.X_add_number < 0
9166 || imm_expr.X_add_number >= 0x10000))
9167 as_bad (_("lui expression not in range 0..65535"));
9171 case 'a': /* 26 bit address */
9172 my_getExpression (&offset_expr, s);
9174 *offset_reloc = BFD_RELOC_MIPS_JMP;
9177 case 'N': /* 3 bit branch condition code */
9178 case 'M': /* 3 bit compare condition code */
9179 if (strncmp (s, "$fcc", 4) != 0)
9189 while (ISDIGIT (*s));
9191 as_bad (_("invalid condition code register $fcc%d"), regno);
9193 ip->insn_opcode |= regno << OP_SH_BCC;
9195 ip->insn_opcode |= regno << OP_SH_CCC;
9199 if (s[0] == '0' && (s[1] == 'x' || s[1] == 'X'))
9210 while (ISDIGIT (*s));
9213 c = 8; /* Invalid sel value. */
9216 as_bad (_("invalid coprocessor sub-selection value (0-7)"));
9217 ip->insn_opcode |= c;
9221 /* Must be at least one digit. */
9222 my_getExpression (&imm_expr, s);
9223 check_absolute_expr (ip, &imm_expr);
9225 if ((unsigned long) imm_expr.X_add_number
9226 > (unsigned long) OP_MASK_VECBYTE)
9228 as_bad (_("bad byte vector index (%ld)"),
9229 (long) imm_expr.X_add_number);
9230 imm_expr.X_add_number = 0;
9233 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_VECBYTE;
9234 imm_expr.X_op = O_absent;
9239 my_getExpression (&imm_expr, s);
9240 check_absolute_expr (ip, &imm_expr);
9242 if ((unsigned long) imm_expr.X_add_number
9243 > (unsigned long) OP_MASK_VECALIGN)
9245 as_bad (_("bad byte vector index (%ld)"),
9246 (long) imm_expr.X_add_number);
9247 imm_expr.X_add_number = 0;
9250 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_VECALIGN;
9251 imm_expr.X_op = O_absent;
9256 as_bad (_("bad char = '%c'\n"), *args);
9261 /* Args don't match. */
9262 if (insn + 1 < &mips_opcodes[NUMOPCODES] &&
9263 !strcmp (insn->name, insn[1].name))
9267 insn_error = _("illegal operands");
9272 insn_error = _("illegal operands");
9277 /* This routine assembles an instruction into its binary format when
9278 assembling for the mips16. As a side effect, it sets one of the
9279 global variables imm_reloc or offset_reloc to the type of
9280 relocation to do if one of the operands is an address expression.
9281 It also sets mips16_small and mips16_ext if the user explicitly
9282 requested a small or extended instruction. */
9287 struct mips_cl_insn *ip;
9291 struct mips_opcode *insn;
9294 unsigned int lastregno = 0;
9299 mips16_small = FALSE;
9302 for (s = str; ISLOWER (*s); ++s)
9314 if (s[1] == 't' && s[2] == ' ')
9317 mips16_small = TRUE;
9321 else if (s[1] == 'e' && s[2] == ' ')
9330 insn_error = _("unknown opcode");
9334 if (mips_opts.noautoextend && ! mips16_ext)
9335 mips16_small = TRUE;
9337 if ((insn = (struct mips_opcode *) hash_find (mips16_op_hash, str)) == NULL)
9339 insn_error = _("unrecognized opcode");
9346 assert (strcmp (insn->name, str) == 0);
9349 ip->insn_opcode = insn->match;
9350 ip->use_extend = FALSE;
9351 imm_expr.X_op = O_absent;
9352 imm_reloc[0] = BFD_RELOC_UNUSED;
9353 imm_reloc[1] = BFD_RELOC_UNUSED;
9354 imm_reloc[2] = BFD_RELOC_UNUSED;
9355 offset_expr.X_op = O_absent;
9356 offset_reloc[0] = BFD_RELOC_UNUSED;
9357 offset_reloc[1] = BFD_RELOC_UNUSED;
9358 offset_reloc[2] = BFD_RELOC_UNUSED;
9359 for (args = insn->args; 1; ++args)
9366 /* In this switch statement we call break if we did not find
9367 a match, continue if we did find a match, or return if we
9376 /* Stuff the immediate value in now, if we can. */
9377 if (imm_expr.X_op == O_constant
9378 && *imm_reloc > BFD_RELOC_UNUSED
9379 && insn->pinfo != INSN_MACRO)
9381 mips16_immed (NULL, 0, *imm_reloc - BFD_RELOC_UNUSED,
9382 imm_expr.X_add_number, TRUE, mips16_small,
9383 mips16_ext, &ip->insn_opcode,
9384 &ip->use_extend, &ip->extend);
9385 imm_expr.X_op = O_absent;
9386 *imm_reloc = BFD_RELOC_UNUSED;
9400 ip->insn_opcode |= lastregno << MIPS16OP_SH_RX;
9403 ip->insn_opcode |= lastregno << MIPS16OP_SH_RY;
9419 ip->insn_opcode |= lastregno << MIPS16OP_SH_RX;
9421 ip->insn_opcode |= lastregno << MIPS16OP_SH_RY;
9448 while (ISDIGIT (*s));
9451 as_bad (_("invalid register number (%d)"), regno);
9457 if (s[1] == 'r' && s[2] == 'a')
9462 else if (s[1] == 'f' && s[2] == 'p')
9467 else if (s[1] == 's' && s[2] == 'p')
9472 else if (s[1] == 'g' && s[2] == 'p')
9477 else if (s[1] == 'a' && s[2] == 't')
9482 else if (s[1] == 'k' && s[2] == 't' && s[3] == '0')
9487 else if (s[1] == 'k' && s[2] == 't' && s[3] == '1')
9492 else if (s[1] == 'z' && s[2] == 'e' && s[3] == 'r' && s[4] == 'o')
9505 if (c == 'v' || c == 'w')
9507 regno = mips16_to_32_reg_map[lastregno];
9521 regno = mips32_to_16_reg_map[regno];
9526 regno = ILLEGAL_REG;
9531 regno = ILLEGAL_REG;
9536 regno = ILLEGAL_REG;
9541 if (regno == AT && ! mips_opts.noat)
9542 as_warn (_("used $at without \".set noat\""));
9549 if (regno == ILLEGAL_REG)
9556 ip->insn_opcode |= regno << MIPS16OP_SH_RX;
9560 ip->insn_opcode |= regno << MIPS16OP_SH_RY;
9563 ip->insn_opcode |= regno << MIPS16OP_SH_RZ;
9566 ip->insn_opcode |= regno << MIPS16OP_SH_MOVE32Z;
9572 ip->insn_opcode |= regno << MIPS16OP_SH_REGR32;
9575 regno = ((regno & 7) << 2) | ((regno & 0x18) >> 3);
9576 ip->insn_opcode |= regno << MIPS16OP_SH_REG32R;
9586 if (strncmp (s, "$pc", 3) == 0)
9610 && strncmp (s + 1, "gprel(", sizeof "gprel(" - 1) == 0)
9612 /* This is %gprel(SYMBOL). We need to read SYMBOL,
9613 and generate the appropriate reloc. If the text
9614 inside %gprel is not a symbol name with an
9615 optional offset, then we generate a normal reloc
9616 and will probably fail later. */
9617 my_getExpression (&imm_expr, s + sizeof "%gprel" - 1);
9618 if (imm_expr.X_op == O_symbol)
9621 *imm_reloc = BFD_RELOC_MIPS16_GPREL;
9623 ip->use_extend = TRUE;
9630 /* Just pick up a normal expression. */
9631 my_getExpression (&imm_expr, s);
9634 if (imm_expr.X_op == O_register)
9636 /* What we thought was an expression turned out to
9639 if (s[0] == '(' && args[1] == '(')
9641 /* It looks like the expression was omitted
9642 before a register indirection, which means
9643 that the expression is implicitly zero. We
9644 still set up imm_expr, so that we handle
9645 explicit extensions correctly. */
9646 imm_expr.X_op = O_constant;
9647 imm_expr.X_add_number = 0;
9648 *imm_reloc = (int) BFD_RELOC_UNUSED + c;
9655 /* We need to relax this instruction. */
9656 *imm_reloc = (int) BFD_RELOC_UNUSED + c;
9665 /* We use offset_reloc rather than imm_reloc for the PC
9666 relative operands. This lets macros with both
9667 immediate and address operands work correctly. */
9668 my_getExpression (&offset_expr, s);
9670 if (offset_expr.X_op == O_register)
9673 /* We need to relax this instruction. */
9674 *offset_reloc = (int) BFD_RELOC_UNUSED + c;
9678 case '6': /* break code */
9679 my_getExpression (&imm_expr, s);
9680 check_absolute_expr (ip, &imm_expr);
9681 if ((unsigned long) imm_expr.X_add_number > 63)
9683 as_warn (_("Invalid value for `%s' (%lu)"),
9685 (unsigned long) imm_expr.X_add_number);
9686 imm_expr.X_add_number &= 0x3f;
9688 ip->insn_opcode |= imm_expr.X_add_number << MIPS16OP_SH_IMM6;
9689 imm_expr.X_op = O_absent;
9693 case 'a': /* 26 bit address */
9694 my_getExpression (&offset_expr, s);
9696 *offset_reloc = BFD_RELOC_MIPS16_JMP;
9697 ip->insn_opcode <<= 16;
9700 case 'l': /* register list for entry macro */
9701 case 'L': /* register list for exit macro */
9711 int freg, reg1, reg2;
9713 while (*s == ' ' || *s == ',')
9717 as_bad (_("can't parse register list"));
9729 while (ISDIGIT (*s))
9751 as_bad (_("invalid register list"));
9756 while (ISDIGIT (*s))
9763 if (freg && reg1 == 0 && reg2 == 0 && c == 'L')
9768 else if (freg && reg1 == 0 && reg2 == 1 && c == 'L')
9773 else if (reg1 == 4 && reg2 >= 4 && reg2 <= 7 && c != 'L')
9774 mask |= (reg2 - 3) << 3;
9775 else if (reg1 == 16 && reg2 >= 16 && reg2 <= 17)
9776 mask |= (reg2 - 15) << 1;
9777 else if (reg1 == RA && reg2 == RA)
9781 as_bad (_("invalid register list"));
9785 /* The mask is filled in in the opcode table for the
9786 benefit of the disassembler. We remove it before
9787 applying the actual mask. */
9788 ip->insn_opcode &= ~ ((7 << 3) << MIPS16OP_SH_IMM6);
9789 ip->insn_opcode |= mask << MIPS16OP_SH_IMM6;
9793 case 'e': /* extend code */
9794 my_getExpression (&imm_expr, s);
9795 check_absolute_expr (ip, &imm_expr);
9796 if ((unsigned long) imm_expr.X_add_number > 0x7ff)
9798 as_warn (_("Invalid value for `%s' (%lu)"),
9800 (unsigned long) imm_expr.X_add_number);
9801 imm_expr.X_add_number &= 0x7ff;
9803 ip->insn_opcode |= imm_expr.X_add_number;
9804 imm_expr.X_op = O_absent;
9814 /* Args don't match. */
9815 if (insn + 1 < &mips16_opcodes[bfd_mips16_num_opcodes] &&
9816 strcmp (insn->name, insn[1].name) == 0)
9823 insn_error = _("illegal operands");
9829 /* This structure holds information we know about a mips16 immediate
9832 struct mips16_immed_operand
9834 /* The type code used in the argument string in the opcode table. */
9836 /* The number of bits in the short form of the opcode. */
9838 /* The number of bits in the extended form of the opcode. */
9840 /* The amount by which the short form is shifted when it is used;
9841 for example, the sw instruction has a shift count of 2. */
9843 /* The amount by which the short form is shifted when it is stored
9844 into the instruction code. */
9846 /* Non-zero if the short form is unsigned. */
9848 /* Non-zero if the extended form is unsigned. */
9850 /* Non-zero if the value is PC relative. */
9854 /* The mips16 immediate operand types. */
9856 static const struct mips16_immed_operand mips16_immed_operands[] =
9858 { '<', 3, 5, 0, MIPS16OP_SH_RZ, 1, 1, 0 },
9859 { '>', 3, 5, 0, MIPS16OP_SH_RX, 1, 1, 0 },
9860 { '[', 3, 6, 0, MIPS16OP_SH_RZ, 1, 1, 0 },
9861 { ']', 3, 6, 0, MIPS16OP_SH_RX, 1, 1, 0 },
9862 { '4', 4, 15, 0, MIPS16OP_SH_IMM4, 0, 0, 0 },
9863 { '5', 5, 16, 0, MIPS16OP_SH_IMM5, 1, 0, 0 },
9864 { 'H', 5, 16, 1, MIPS16OP_SH_IMM5, 1, 0, 0 },
9865 { 'W', 5, 16, 2, MIPS16OP_SH_IMM5, 1, 0, 0 },
9866 { 'D', 5, 16, 3, MIPS16OP_SH_IMM5, 1, 0, 0 },
9867 { 'j', 5, 16, 0, MIPS16OP_SH_IMM5, 0, 0, 0 },
9868 { '8', 8, 16, 0, MIPS16OP_SH_IMM8, 1, 0, 0 },
9869 { 'V', 8, 16, 2, MIPS16OP_SH_IMM8, 1, 0, 0 },
9870 { 'C', 8, 16, 3, MIPS16OP_SH_IMM8, 1, 0, 0 },
9871 { 'U', 8, 16, 0, MIPS16OP_SH_IMM8, 1, 1, 0 },
9872 { 'k', 8, 16, 0, MIPS16OP_SH_IMM8, 0, 0, 0 },
9873 { 'K', 8, 16, 3, MIPS16OP_SH_IMM8, 0, 0, 0 },
9874 { 'p', 8, 16, 0, MIPS16OP_SH_IMM8, 0, 0, 1 },
9875 { 'q', 11, 16, 0, MIPS16OP_SH_IMM8, 0, 0, 1 },
9876 { 'A', 8, 16, 2, MIPS16OP_SH_IMM8, 1, 0, 1 },
9877 { 'B', 5, 16, 3, MIPS16OP_SH_IMM5, 1, 0, 1 },
9878 { 'E', 5, 16, 2, MIPS16OP_SH_IMM5, 1, 0, 1 }
9881 #define MIPS16_NUM_IMMED \
9882 (sizeof mips16_immed_operands / sizeof mips16_immed_operands[0])
9884 /* Handle a mips16 instruction with an immediate value. This or's the
9885 small immediate value into *INSN. It sets *USE_EXTEND to indicate
9886 whether an extended value is needed; if one is needed, it sets
9887 *EXTEND to the value. The argument type is TYPE. The value is VAL.
9888 If SMALL is true, an unextended opcode was explicitly requested.
9889 If EXT is true, an extended opcode was explicitly requested. If
9890 WARN is true, warn if EXT does not match reality. */
9893 mips16_immed (file, line, type, val, warn, small, ext, insn, use_extend,
9902 unsigned long *insn;
9903 bfd_boolean *use_extend;
9904 unsigned short *extend;
9906 register const struct mips16_immed_operand *op;
9907 int mintiny, maxtiny;
9908 bfd_boolean needext;
9910 op = mips16_immed_operands;
9911 while (op->type != type)
9914 assert (op < mips16_immed_operands + MIPS16_NUM_IMMED);
9919 if (type == '<' || type == '>' || type == '[' || type == ']')
9922 maxtiny = 1 << op->nbits;
9927 maxtiny = (1 << op->nbits) - 1;
9932 mintiny = - (1 << (op->nbits - 1));
9933 maxtiny = (1 << (op->nbits - 1)) - 1;
9936 /* Branch offsets have an implicit 0 in the lowest bit. */
9937 if (type == 'p' || type == 'q')
9940 if ((val & ((1 << op->shift) - 1)) != 0
9941 || val < (mintiny << op->shift)
9942 || val > (maxtiny << op->shift))
9947 if (warn && ext && ! needext)
9948 as_warn_where (file, line,
9949 _("extended operand requested but not required"));
9950 if (small && needext)
9951 as_bad_where (file, line, _("invalid unextended operand value"));
9953 if (small || (! ext && ! needext))
9957 *use_extend = FALSE;
9958 insnval = ((val >> op->shift) & ((1 << op->nbits) - 1));
9959 insnval <<= op->op_shift;
9964 long minext, maxext;
9970 maxext = (1 << op->extbits) - 1;
9974 minext = - (1 << (op->extbits - 1));
9975 maxext = (1 << (op->extbits - 1)) - 1;
9977 if (val < minext || val > maxext)
9978 as_bad_where (file, line,
9979 _("operand value out of range for instruction"));
9982 if (op->extbits == 16)
9984 extval = ((val >> 11) & 0x1f) | (val & 0x7e0);
9987 else if (op->extbits == 15)
9989 extval = ((val >> 11) & 0xf) | (val & 0x7f0);
9994 extval = ((val & 0x1f) << 6) | (val & 0x20);
9998 *extend = (unsigned short) extval;
10003 static const struct percent_op_match
10006 bfd_reloc_code_real_type reloc;
10009 {"%lo", BFD_RELOC_LO16},
10011 {"%call_hi", BFD_RELOC_MIPS_CALL_HI16},
10012 {"%call_lo", BFD_RELOC_MIPS_CALL_LO16},
10013 {"%call16", BFD_RELOC_MIPS_CALL16},
10014 {"%got_disp", BFD_RELOC_MIPS_GOT_DISP},
10015 {"%got_page", BFD_RELOC_MIPS_GOT_PAGE},
10016 {"%got_ofst", BFD_RELOC_MIPS_GOT_OFST},
10017 {"%got_hi", BFD_RELOC_MIPS_GOT_HI16},
10018 {"%got_lo", BFD_RELOC_MIPS_GOT_LO16},
10019 {"%got", BFD_RELOC_MIPS_GOT16},
10020 {"%gp_rel", BFD_RELOC_GPREL16},
10021 {"%half", BFD_RELOC_16},
10022 {"%highest", BFD_RELOC_MIPS_HIGHEST},
10023 {"%higher", BFD_RELOC_MIPS_HIGHER},
10024 {"%neg", BFD_RELOC_MIPS_SUB},
10026 {"%hi", BFD_RELOC_HI16_S}
10030 /* Return true if *STR points to a relocation operator. When returning true,
10031 move *STR over the operator and store its relocation code in *RELOC.
10032 Leave both *STR and *RELOC alone when returning false. */
10035 parse_relocation (str, reloc)
10037 bfd_reloc_code_real_type *reloc;
10041 for (i = 0; i < ARRAY_SIZE (percent_op); i++)
10042 if (strncasecmp (*str, percent_op[i].str, strlen (percent_op[i].str)) == 0)
10044 *str += strlen (percent_op[i].str);
10045 *reloc = percent_op[i].reloc;
10047 /* Check whether the output BFD supports this relocation.
10048 If not, issue an error and fall back on something safe. */
10049 if (!bfd_reloc_type_lookup (stdoutput, percent_op[i].reloc))
10051 as_bad ("relocation %s isn't supported by the current ABI",
10052 percent_op[i].str);
10053 *reloc = BFD_RELOC_LO16;
10061 /* Parse string STR as a 16-bit relocatable operand. Store the
10062 expression in *EP and the relocations in the array starting
10063 at RELOC. Return the number of relocation operators used.
10065 On exit, EXPR_END points to the first character after the expression.
10066 If no relocation operators are used, RELOC[0] is set to BFD_RELOC_LO16. */
10069 my_getSmallExpression (ep, reloc, str)
10071 bfd_reloc_code_real_type *reloc;
10074 bfd_reloc_code_real_type reversed_reloc[3];
10075 size_t reloc_index, i;
10076 int crux_depth, str_depth;
10079 /* Search for the start of the main expression, recoding relocations
10080 in REVERSED_RELOC. End the loop with CRUX pointing to the start
10081 of the main expression and with CRUX_DEPTH containing the number
10082 of open brackets at that point. */
10089 crux_depth = str_depth;
10091 /* Skip over whitespace and brackets, keeping count of the number
10093 while (*str == ' ' || *str == '\t' || *str == '(')
10098 && reloc_index < (HAVE_NEWABI ? 3 : 1)
10099 && parse_relocation (&str, &reversed_reloc[reloc_index]));
10101 my_getExpression (ep, crux);
10104 /* Match every open bracket. */
10105 while (crux_depth > 0 && (*str == ')' || *str == ' ' || *str == '\t'))
10109 if (crux_depth > 0)
10110 as_bad ("unclosed '('");
10114 if (reloc_index == 0)
10115 reloc[0] = BFD_RELOC_LO16;
10118 prev_reloc_op_frag = frag_now;
10119 for (i = 0; i < reloc_index; i++)
10120 reloc[i] = reversed_reloc[reloc_index - 1 - i];
10123 return reloc_index;
10127 my_getExpression (ep, str)
10134 save_in = input_line_pointer;
10135 input_line_pointer = str;
10137 expr_end = input_line_pointer;
10138 input_line_pointer = save_in;
10140 /* If we are in mips16 mode, and this is an expression based on `.',
10141 then we bump the value of the symbol by 1 since that is how other
10142 text symbols are handled. We don't bother to handle complex
10143 expressions, just `.' plus or minus a constant. */
10144 if (mips_opts.mips16
10145 && ep->X_op == O_symbol
10146 && strcmp (S_GET_NAME (ep->X_add_symbol), FAKE_LABEL_NAME) == 0
10147 && S_GET_SEGMENT (ep->X_add_symbol) == now_seg
10148 && symbol_get_frag (ep->X_add_symbol) == frag_now
10149 && symbol_constant_p (ep->X_add_symbol)
10150 && (val = S_GET_VALUE (ep->X_add_symbol)) == frag_now_fix ())
10151 S_SET_VALUE (ep->X_add_symbol, val + 1);
10154 /* Turn a string in input_line_pointer into a floating point constant
10155 of type TYPE, and store the appropriate bytes in *LITP. The number
10156 of LITTLENUMS emitted is stored in *SIZEP. An error message is
10157 returned, or NULL on OK. */
10160 md_atof (type, litP, sizeP)
10166 LITTLENUM_TYPE words[4];
10182 return _("bad call to md_atof");
10185 t = atof_ieee (input_line_pointer, type, words);
10187 input_line_pointer = t;
10191 if (! target_big_endian)
10193 for (i = prec - 1; i >= 0; i--)
10195 md_number_to_chars (litP, (valueT) words[i], 2);
10201 for (i = 0; i < prec; i++)
10203 md_number_to_chars (litP, (valueT) words[i], 2);
10212 md_number_to_chars (buf, val, n)
10217 if (target_big_endian)
10218 number_to_chars_bigendian (buf, val, n);
10220 number_to_chars_littleendian (buf, val, n);
10224 static int support_64bit_objects(void)
10226 const char **list, **l;
10229 list = bfd_target_list ();
10230 for (l = list; *l != NULL; l++)
10232 /* This is traditional mips */
10233 if (strcmp (*l, "elf64-tradbigmips") == 0
10234 || strcmp (*l, "elf64-tradlittlemips") == 0)
10236 if (strcmp (*l, "elf64-bigmips") == 0
10237 || strcmp (*l, "elf64-littlemips") == 0)
10240 yes = (*l != NULL);
10244 #endif /* OBJ_ELF */
10246 const char *md_shortopts = "nO::g::G:";
10248 struct option md_longopts[] =
10250 #define OPTION_MIPS1 (OPTION_MD_BASE + 1)
10251 {"mips0", no_argument, NULL, OPTION_MIPS1},
10252 {"mips1", no_argument, NULL, OPTION_MIPS1},
10253 #define OPTION_MIPS2 (OPTION_MD_BASE + 2)
10254 {"mips2", no_argument, NULL, OPTION_MIPS2},
10255 #define OPTION_MIPS3 (OPTION_MD_BASE + 3)
10256 {"mips3", no_argument, NULL, OPTION_MIPS3},
10257 #define OPTION_MIPS4 (OPTION_MD_BASE + 4)
10258 {"mips4", no_argument, NULL, OPTION_MIPS4},
10259 #define OPTION_MIPS5 (OPTION_MD_BASE + 5)
10260 {"mips5", no_argument, NULL, OPTION_MIPS5},
10261 #define OPTION_MIPS32 (OPTION_MD_BASE + 6)
10262 {"mips32", no_argument, NULL, OPTION_MIPS32},
10263 #define OPTION_MIPS64 (OPTION_MD_BASE + 7)
10264 {"mips64", no_argument, NULL, OPTION_MIPS64},
10265 #define OPTION_MEMBEDDED_PIC (OPTION_MD_BASE + 8)
10266 {"membedded-pic", no_argument, NULL, OPTION_MEMBEDDED_PIC},
10267 #define OPTION_TRAP (OPTION_MD_BASE + 9)
10268 {"trap", no_argument, NULL, OPTION_TRAP},
10269 {"no-break", no_argument, NULL, OPTION_TRAP},
10270 #define OPTION_BREAK (OPTION_MD_BASE + 10)
10271 {"break", no_argument, NULL, OPTION_BREAK},
10272 {"no-trap", no_argument, NULL, OPTION_BREAK},
10273 #define OPTION_EB (OPTION_MD_BASE + 11)
10274 {"EB", no_argument, NULL, OPTION_EB},
10275 #define OPTION_EL (OPTION_MD_BASE + 12)
10276 {"EL", no_argument, NULL, OPTION_EL},
10277 #define OPTION_MIPS16 (OPTION_MD_BASE + 13)
10278 {"mips16", no_argument, NULL, OPTION_MIPS16},
10279 #define OPTION_NO_MIPS16 (OPTION_MD_BASE + 14)
10280 {"no-mips16", no_argument, NULL, OPTION_NO_MIPS16},
10281 #define OPTION_M7000_HILO_FIX (OPTION_MD_BASE + 15)
10282 {"mfix7000", no_argument, NULL, OPTION_M7000_HILO_FIX},
10283 #define OPTION_MNO_7000_HILO_FIX (OPTION_MD_BASE + 16)
10284 {"no-fix-7000", no_argument, NULL, OPTION_MNO_7000_HILO_FIX},
10285 {"mno-fix7000", no_argument, NULL, OPTION_MNO_7000_HILO_FIX},
10286 #define OPTION_FP32 (OPTION_MD_BASE + 17)
10287 {"mfp32", no_argument, NULL, OPTION_FP32},
10288 #define OPTION_GP32 (OPTION_MD_BASE + 18)
10289 {"mgp32", no_argument, NULL, OPTION_GP32},
10290 #define OPTION_CONSTRUCT_FLOATS (OPTION_MD_BASE + 19)
10291 {"construct-floats", no_argument, NULL, OPTION_CONSTRUCT_FLOATS},
10292 #define OPTION_NO_CONSTRUCT_FLOATS (OPTION_MD_BASE + 20)
10293 {"no-construct-floats", no_argument, NULL, OPTION_NO_CONSTRUCT_FLOATS},
10294 #define OPTION_MARCH (OPTION_MD_BASE + 21)
10295 {"march", required_argument, NULL, OPTION_MARCH},
10296 #define OPTION_MTUNE (OPTION_MD_BASE + 22)
10297 {"mtune", required_argument, NULL, OPTION_MTUNE},
10298 #define OPTION_FP64 (OPTION_MD_BASE + 23)
10299 {"mfp64", no_argument, NULL, OPTION_FP64},
10300 #define OPTION_M4650 (OPTION_MD_BASE + 24)
10301 {"m4650", no_argument, NULL, OPTION_M4650},
10302 #define OPTION_NO_M4650 (OPTION_MD_BASE + 25)
10303 {"no-m4650", no_argument, NULL, OPTION_NO_M4650},
10304 #define OPTION_M4010 (OPTION_MD_BASE + 26)
10305 {"m4010", no_argument, NULL, OPTION_M4010},
10306 #define OPTION_NO_M4010 (OPTION_MD_BASE + 27)
10307 {"no-m4010", no_argument, NULL, OPTION_NO_M4010},
10308 #define OPTION_M4100 (OPTION_MD_BASE + 28)
10309 {"m4100", no_argument, NULL, OPTION_M4100},
10310 #define OPTION_NO_M4100 (OPTION_MD_BASE + 29)
10311 {"no-m4100", no_argument, NULL, OPTION_NO_M4100},
10312 #define OPTION_M3900 (OPTION_MD_BASE + 30)
10313 {"m3900", no_argument, NULL, OPTION_M3900},
10314 #define OPTION_NO_M3900 (OPTION_MD_BASE + 31)
10315 {"no-m3900", no_argument, NULL, OPTION_NO_M3900},
10316 #define OPTION_GP64 (OPTION_MD_BASE + 32)
10317 {"mgp64", no_argument, NULL, OPTION_GP64},
10318 #define OPTION_MIPS3D (OPTION_MD_BASE + 33)
10319 {"mips3d", no_argument, NULL, OPTION_MIPS3D},
10320 #define OPTION_NO_MIPS3D (OPTION_MD_BASE + 34)
10321 {"no-mips3d", no_argument, NULL, OPTION_NO_MIPS3D},
10322 #define OPTION_MDMX (OPTION_MD_BASE + 35)
10323 {"mdmx", no_argument, NULL, OPTION_MDMX},
10324 #define OPTION_NO_MDMX (OPTION_MD_BASE + 36)
10325 {"no-mdmx", no_argument, NULL, OPTION_NO_MDMX},
10326 #define OPTION_FIX_VR4122 (OPTION_MD_BASE + 37)
10327 #define OPTION_NO_FIX_VR4122 (OPTION_MD_BASE + 38)
10328 {"mfix-vr4122-bugs", no_argument, NULL, OPTION_FIX_VR4122},
10329 {"no-mfix-vr4122-bugs", no_argument, NULL, OPTION_NO_FIX_VR4122},
10330 #define OPTION_RELAX_BRANCH (OPTION_MD_BASE + 39)
10331 #define OPTION_NO_RELAX_BRANCH (OPTION_MD_BASE + 40)
10332 {"relax-branch", no_argument, NULL, OPTION_RELAX_BRANCH},
10333 {"no-relax-branch", no_argument, NULL, OPTION_NO_RELAX_BRANCH},
10334 #define OPTION_MIPS32R2 (OPTION_MD_BASE + 41)
10335 {"mips32r2", no_argument, NULL, OPTION_MIPS32R2},
10337 #define OPTION_ELF_BASE (OPTION_MD_BASE + 42)
10338 #define OPTION_CALL_SHARED (OPTION_ELF_BASE + 0)
10339 {"KPIC", no_argument, NULL, OPTION_CALL_SHARED},
10340 {"call_shared", no_argument, NULL, OPTION_CALL_SHARED},
10341 #define OPTION_NON_SHARED (OPTION_ELF_BASE + 1)
10342 {"non_shared", no_argument, NULL, OPTION_NON_SHARED},
10343 #define OPTION_XGOT (OPTION_ELF_BASE + 2)
10344 {"xgot", no_argument, NULL, OPTION_XGOT},
10345 #define OPTION_MABI (OPTION_ELF_BASE + 3)
10346 {"mabi", required_argument, NULL, OPTION_MABI},
10347 #define OPTION_32 (OPTION_ELF_BASE + 4)
10348 {"32", no_argument, NULL, OPTION_32},
10349 #define OPTION_N32 (OPTION_ELF_BASE + 5)
10350 {"n32", no_argument, NULL, OPTION_N32},
10351 #define OPTION_64 (OPTION_ELF_BASE + 6)
10352 {"64", no_argument, NULL, OPTION_64},
10353 #define OPTION_MDEBUG (OPTION_ELF_BASE + 7)
10354 {"mdebug", no_argument, NULL, OPTION_MDEBUG},
10355 #define OPTION_NO_MDEBUG (OPTION_ELF_BASE + 8)
10356 {"no-mdebug", no_argument, NULL, OPTION_NO_MDEBUG},
10357 #endif /* OBJ_ELF */
10358 {NULL, no_argument, NULL, 0}
10360 size_t md_longopts_size = sizeof (md_longopts);
10362 /* Set STRING_PTR (either &mips_arch_string or &mips_tune_string) to
10363 NEW_VALUE. Warn if another value was already specified. Note:
10364 we have to defer parsing the -march and -mtune arguments in order
10365 to handle 'from-abi' correctly, since the ABI might be specified
10366 in a later argument. */
10369 mips_set_option_string (string_ptr, new_value)
10370 const char **string_ptr, *new_value;
10372 if (*string_ptr != 0 && strcasecmp (*string_ptr, new_value) != 0)
10373 as_warn (_("A different %s was already specified, is now %s"),
10374 string_ptr == &mips_arch_string ? "-march" : "-mtune",
10377 *string_ptr = new_value;
10381 md_parse_option (c, arg)
10387 case OPTION_CONSTRUCT_FLOATS:
10388 mips_disable_float_construction = 0;
10391 case OPTION_NO_CONSTRUCT_FLOATS:
10392 mips_disable_float_construction = 1;
10404 target_big_endian = 1;
10408 target_big_endian = 0;
10416 if (arg && arg[1] == '0')
10426 mips_debug = atoi (arg);
10427 /* When the MIPS assembler sees -g or -g2, it does not do
10428 optimizations which limit full symbolic debugging. We take
10429 that to be equivalent to -O0. */
10430 if (mips_debug == 2)
10435 file_mips_isa = ISA_MIPS1;
10439 file_mips_isa = ISA_MIPS2;
10443 file_mips_isa = ISA_MIPS3;
10447 file_mips_isa = ISA_MIPS4;
10451 file_mips_isa = ISA_MIPS5;
10454 case OPTION_MIPS32:
10455 file_mips_isa = ISA_MIPS32;
10458 case OPTION_MIPS32R2:
10459 file_mips_isa = ISA_MIPS32R2;
10462 case OPTION_MIPS64:
10463 file_mips_isa = ISA_MIPS64;
10467 mips_set_option_string (&mips_tune_string, arg);
10471 mips_set_option_string (&mips_arch_string, arg);
10475 mips_set_option_string (&mips_arch_string, "4650");
10476 mips_set_option_string (&mips_tune_string, "4650");
10479 case OPTION_NO_M4650:
10483 mips_set_option_string (&mips_arch_string, "4010");
10484 mips_set_option_string (&mips_tune_string, "4010");
10487 case OPTION_NO_M4010:
10491 mips_set_option_string (&mips_arch_string, "4100");
10492 mips_set_option_string (&mips_tune_string, "4100");
10495 case OPTION_NO_M4100:
10499 mips_set_option_string (&mips_arch_string, "3900");
10500 mips_set_option_string (&mips_tune_string, "3900");
10503 case OPTION_NO_M3900:
10507 mips_opts.ase_mdmx = 1;
10510 case OPTION_NO_MDMX:
10511 mips_opts.ase_mdmx = 0;
10514 case OPTION_MIPS16:
10515 mips_opts.mips16 = 1;
10516 mips_no_prev_insn (FALSE);
10519 case OPTION_NO_MIPS16:
10520 mips_opts.mips16 = 0;
10521 mips_no_prev_insn (FALSE);
10524 case OPTION_MIPS3D:
10525 mips_opts.ase_mips3d = 1;
10528 case OPTION_NO_MIPS3D:
10529 mips_opts.ase_mips3d = 0;
10532 case OPTION_MEMBEDDED_PIC:
10533 mips_pic = EMBEDDED_PIC;
10534 if (USE_GLOBAL_POINTER_OPT && g_switch_seen)
10536 as_bad (_("-G may not be used with embedded PIC code"));
10539 g_switch_value = 0x7fffffff;
10542 case OPTION_FIX_VR4122:
10543 mips_fix_4122_bugs = 1;
10546 case OPTION_NO_FIX_VR4122:
10547 mips_fix_4122_bugs = 0;
10550 case OPTION_RELAX_BRANCH:
10551 mips_relax_branch = 1;
10554 case OPTION_NO_RELAX_BRANCH:
10555 mips_relax_branch = 0;
10559 /* When generating ELF code, we permit -KPIC and -call_shared to
10560 select SVR4_PIC, and -non_shared to select no PIC. This is
10561 intended to be compatible with Irix 5. */
10562 case OPTION_CALL_SHARED:
10563 if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
10565 as_bad (_("-call_shared is supported only for ELF format"));
10568 mips_pic = SVR4_PIC;
10569 if (g_switch_seen && g_switch_value != 0)
10571 as_bad (_("-G may not be used with SVR4 PIC code"));
10574 g_switch_value = 0;
10577 case OPTION_NON_SHARED:
10578 if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
10580 as_bad (_("-non_shared is supported only for ELF format"));
10586 /* The -xgot option tells the assembler to use 32 offsets when
10587 accessing the got in SVR4_PIC mode. It is for Irix
10592 #endif /* OBJ_ELF */
10595 if (! USE_GLOBAL_POINTER_OPT)
10597 as_bad (_("-G is not supported for this configuration"));
10600 else if (mips_pic == SVR4_PIC || mips_pic == EMBEDDED_PIC)
10602 as_bad (_("-G may not be used with SVR4 or embedded PIC code"));
10606 g_switch_value = atoi (arg);
10611 /* The -32, -n32 and -64 options are shortcuts for -mabi=32, -mabi=n32
10614 if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
10616 as_bad (_("-32 is supported for ELF format only"));
10619 mips_abi = O32_ABI;
10623 if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
10625 as_bad (_("-n32 is supported for ELF format only"));
10628 mips_abi = N32_ABI;
10632 if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
10634 as_bad (_("-64 is supported for ELF format only"));
10637 mips_abi = N64_ABI;
10638 if (! support_64bit_objects())
10639 as_fatal (_("No compiled in support for 64 bit object file format"));
10641 #endif /* OBJ_ELF */
10644 file_mips_gp32 = 1;
10648 file_mips_gp32 = 0;
10652 file_mips_fp32 = 1;
10656 file_mips_fp32 = 0;
10661 if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
10663 as_bad (_("-mabi is supported for ELF format only"));
10666 if (strcmp (arg, "32") == 0)
10667 mips_abi = O32_ABI;
10668 else if (strcmp (arg, "o64") == 0)
10669 mips_abi = O64_ABI;
10670 else if (strcmp (arg, "n32") == 0)
10671 mips_abi = N32_ABI;
10672 else if (strcmp (arg, "64") == 0)
10674 mips_abi = N64_ABI;
10675 if (! support_64bit_objects())
10676 as_fatal (_("No compiled in support for 64 bit object file "
10679 else if (strcmp (arg, "eabi") == 0)
10680 mips_abi = EABI_ABI;
10683 as_fatal (_("invalid abi -mabi=%s"), arg);
10687 #endif /* OBJ_ELF */
10689 case OPTION_M7000_HILO_FIX:
10690 mips_7000_hilo_fix = TRUE;
10693 case OPTION_MNO_7000_HILO_FIX:
10694 mips_7000_hilo_fix = FALSE;
10698 case OPTION_MDEBUG:
10699 mips_flag_mdebug = TRUE;
10702 case OPTION_NO_MDEBUG:
10703 mips_flag_mdebug = FALSE;
10705 #endif /* OBJ_ELF */
10714 /* Set up globals to generate code for the ISA or processor
10715 described by INFO. */
10718 mips_set_architecture (info)
10719 const struct mips_cpu_info *info;
10723 mips_arch_info = info;
10724 mips_arch = info->cpu;
10725 mips_opts.isa = info->isa;
10730 /* Likewise for tuning. */
10733 mips_set_tune (info)
10734 const struct mips_cpu_info *info;
10738 mips_tune_info = info;
10739 mips_tune = info->cpu;
10745 mips_after_parse_args ()
10747 /* GP relative stuff not working for PE */
10748 if (strncmp (TARGET_OS, "pe", 2) == 0
10749 && g_switch_value != 0)
10752 as_bad (_("-G not supported in this configuration."));
10753 g_switch_value = 0;
10756 /* The following code determines the architecture and register size.
10757 Similar code was added to GCC 3.3 (see override_options() in
10758 config/mips/mips.c). The GAS and GCC code should be kept in sync
10759 as much as possible. */
10761 if (mips_arch_string != 0)
10762 mips_set_architecture (mips_parse_cpu ("-march", mips_arch_string));
10764 if (mips_tune_string != 0)
10765 mips_set_tune (mips_parse_cpu ("-mtune", mips_tune_string));
10767 if (file_mips_isa != ISA_UNKNOWN)
10769 /* Handle -mipsN. At this point, file_mips_isa contains the
10770 ISA level specified by -mipsN, while mips_opts.isa contains
10771 the -march selection (if any). */
10772 if (mips_arch_info != 0)
10774 /* -march takes precedence over -mipsN, since it is more descriptive.
10775 There's no harm in specifying both as long as the ISA levels
10777 if (file_mips_isa != mips_opts.isa)
10778 as_bad (_("-%s conflicts with the other architecture options, which imply -%s"),
10779 mips_cpu_info_from_isa (file_mips_isa)->name,
10780 mips_cpu_info_from_isa (mips_opts.isa)->name);
10783 mips_set_architecture (mips_cpu_info_from_isa (file_mips_isa));
10786 if (mips_arch_info == 0)
10787 mips_set_architecture (mips_parse_cpu ("default CPU",
10788 MIPS_CPU_STRING_DEFAULT));
10790 if (ABI_NEEDS_64BIT_REGS (mips_abi) && !ISA_HAS_64BIT_REGS (mips_opts.isa))
10791 as_bad ("-march=%s is not compatible with the selected ABI",
10792 mips_arch_info->name);
10794 /* Optimize for mips_arch, unless -mtune selects a different processor. */
10795 if (mips_tune_info == 0)
10796 mips_set_tune (mips_arch_info);
10798 if (file_mips_gp32 >= 0)
10800 /* The user specified the size of the integer registers. Make sure
10801 it agrees with the ABI and ISA. */
10802 if (file_mips_gp32 == 0 && !ISA_HAS_64BIT_REGS (mips_opts.isa))
10803 as_bad (_("-mgp64 used with a 32-bit processor"));
10804 else if (file_mips_gp32 == 1 && ABI_NEEDS_64BIT_REGS (mips_abi))
10805 as_bad (_("-mgp32 used with a 64-bit ABI"));
10806 else if (file_mips_gp32 == 0 && ABI_NEEDS_32BIT_REGS (mips_abi))
10807 as_bad (_("-mgp64 used with a 32-bit ABI"));
10811 /* Infer the integer register size from the ABI and processor.
10812 Restrict ourselves to 32-bit registers if that's all the
10813 processor has, or if the ABI cannot handle 64-bit registers. */
10814 file_mips_gp32 = (ABI_NEEDS_32BIT_REGS (mips_abi)
10815 || !ISA_HAS_64BIT_REGS (mips_opts.isa));
10818 /* ??? GAS treats single-float processors as though they had 64-bit
10819 float registers (although it complains when double-precision
10820 instructions are used). As things stand, saying they have 32-bit
10821 registers would lead to spurious "register must be even" messages.
10822 So here we assume float registers are always the same size as
10823 integer ones, unless the user says otherwise. */
10824 if (file_mips_fp32 < 0)
10825 file_mips_fp32 = file_mips_gp32;
10827 /* End of GCC-shared inference code. */
10829 /* ??? When do we want this flag to be set? Who uses it? */
10830 if (file_mips_gp32 == 1
10831 && mips_abi == NO_ABI
10832 && ISA_HAS_64BIT_REGS (mips_opts.isa))
10833 mips_32bitmode = 1;
10835 if (mips_opts.isa == ISA_MIPS1 && mips_trap)
10836 as_bad (_("trap exception not supported at ISA 1"));
10838 /* If the selected architecture includes support for ASEs, enable
10839 generation of code for them. */
10840 if (mips_opts.mips16 == -1)
10841 mips_opts.mips16 = (CPU_HAS_MIPS16 (mips_arch)) ? 1 : 0;
10842 if (mips_opts.ase_mips3d == -1)
10843 mips_opts.ase_mips3d = (CPU_HAS_MIPS3D (mips_arch)) ? 1 : 0;
10844 if (mips_opts.ase_mdmx == -1)
10845 mips_opts.ase_mdmx = (CPU_HAS_MDMX (mips_arch)) ? 1 : 0;
10847 file_mips_isa = mips_opts.isa;
10848 file_ase_mips16 = mips_opts.mips16;
10849 file_ase_mips3d = mips_opts.ase_mips3d;
10850 file_ase_mdmx = mips_opts.ase_mdmx;
10851 mips_opts.gp32 = file_mips_gp32;
10852 mips_opts.fp32 = file_mips_fp32;
10854 if (mips_flag_mdebug < 0)
10856 #ifdef OBJ_MAYBE_ECOFF
10857 if (OUTPUT_FLAVOR == bfd_target_ecoff_flavour)
10858 mips_flag_mdebug = 1;
10860 #endif /* OBJ_MAYBE_ECOFF */
10861 mips_flag_mdebug = 0;
10866 mips_init_after_args ()
10868 /* initialize opcodes */
10869 bfd_mips_num_opcodes = bfd_mips_num_builtin_opcodes;
10870 mips_opcodes = (struct mips_opcode *) mips_builtin_opcodes;
10874 md_pcrel_from (fixP)
10877 if (OUTPUT_FLAVOR != bfd_target_aout_flavour
10878 && fixP->fx_addsy != (symbolS *) NULL
10879 && ! S_IS_DEFINED (fixP->fx_addsy))
10882 /* Return the address of the delay slot. */
10883 return fixP->fx_size + fixP->fx_where + fixP->fx_frag->fr_address;
10886 /* This is called before the symbol table is processed. In order to
10887 work with gcc when using mips-tfile, we must keep all local labels.
10888 However, in other cases, we want to discard them. If we were
10889 called with -g, but we didn't see any debugging information, it may
10890 mean that gcc is smuggling debugging information through to
10891 mips-tfile, in which case we must generate all local labels. */
10894 mips_frob_file_before_adjust ()
10896 #ifndef NO_ECOFF_DEBUGGING
10897 if (ECOFF_DEBUGGING
10899 && ! ecoff_debugging_seen)
10900 flag_keep_locals = 1;
10904 /* Sort any unmatched HI16_S relocs so that they immediately precede
10905 the corresponding LO reloc. This is called before md_apply_fix3 and
10906 tc_gen_reloc. Unmatched HI16_S relocs can only be generated by
10907 explicit use of the %hi modifier. */
10912 struct mips_hi_fixup *l;
10914 for (l = mips_hi_fixup_list; l != NULL; l = l->next)
10916 segment_info_type *seginfo;
10919 assert (reloc_needs_lo_p (l->fixp->fx_r_type));
10921 /* If a GOT16 relocation turns out to be against a global symbol,
10922 there isn't supposed to be a matching LO. */
10923 if (l->fixp->fx_r_type == BFD_RELOC_MIPS_GOT16
10924 && !pic_need_relax (l->fixp->fx_addsy, l->seg))
10927 /* Check quickly whether the next fixup happens to be a matching %lo. */
10928 if (fixup_has_matching_lo_p (l->fixp))
10931 /* Look through the fixups for this segment for a matching %lo.
10932 When we find one, move the %hi just in front of it. We do
10933 this in two passes. In the first pass, we try to find a
10934 unique %lo. In the second pass, we permit multiple %hi
10935 relocs for a single %lo (this is a GNU extension). */
10936 seginfo = seg_info (l->seg);
10937 for (pass = 0; pass < 2; pass++)
10942 for (f = seginfo->fix_root; f != NULL; f = f->fx_next)
10944 /* Check whether this is a %lo fixup which matches l->fixp. */
10945 if (f->fx_r_type == BFD_RELOC_LO16
10946 && f->fx_addsy == l->fixp->fx_addsy
10947 && f->fx_offset == l->fixp->fx_offset
10950 || !reloc_needs_lo_p (prev->fx_r_type)
10951 || !fixup_has_matching_lo_p (prev)))
10955 /* Move l->fixp before f. */
10956 for (pf = &seginfo->fix_root;
10958 pf = &(*pf)->fx_next)
10959 assert (*pf != NULL);
10961 *pf = l->fixp->fx_next;
10963 l->fixp->fx_next = f;
10965 seginfo->fix_root = l->fixp;
10967 prev->fx_next = l->fixp;
10978 #if 0 /* GCC code motion plus incomplete dead code elimination
10979 can leave a %hi without a %lo. */
10981 as_warn_where (l->fixp->fx_file, l->fixp->fx_line,
10982 _("Unmatched %%hi reloc"));
10988 /* When generating embedded PIC code we need to use a special
10989 relocation to represent the difference of two symbols in the .text
10990 section (switch tables use a difference of this sort). See
10991 include/coff/mips.h for details. This macro checks whether this
10992 fixup requires the special reloc. */
10993 #define SWITCH_TABLE(fixp) \
10994 ((fixp)->fx_r_type == BFD_RELOC_32 \
10995 && OUTPUT_FLAVOR != bfd_target_elf_flavour \
10996 && (fixp)->fx_addsy != NULL \
10997 && (fixp)->fx_subsy != NULL \
10998 && S_GET_SEGMENT ((fixp)->fx_addsy) == text_section \
10999 && S_GET_SEGMENT ((fixp)->fx_subsy) == text_section)
11001 /* When generating embedded PIC code we must keep all PC relative
11002 relocations, in case the linker has to relax a call. We also need
11003 to keep relocations for switch table entries.
11005 We may have combined relocations without symbols in the N32/N64 ABI.
11006 We have to prevent gas from dropping them. */
11009 mips_force_relocation (fixp)
11012 if (generic_force_reloc (fixp))
11016 && S_GET_SEGMENT (fixp->fx_addsy) == bfd_abs_section_ptr
11017 && (fixp->fx_r_type == BFD_RELOC_MIPS_SUB
11018 || fixp->fx_r_type == BFD_RELOC_HI16_S
11019 || fixp->fx_r_type == BFD_RELOC_LO16))
11022 return (mips_pic == EMBEDDED_PIC
11024 || SWITCH_TABLE (fixp)
11025 || fixp->fx_r_type == BFD_RELOC_PCREL_HI16_S
11026 || fixp->fx_r_type == BFD_RELOC_PCREL_LO16));
11031 mips_need_elf_addend_fixup (fixP)
11034 if (S_GET_OTHER (fixP->fx_addsy) == STO_MIPS16)
11036 if (mips_pic == EMBEDDED_PIC
11037 && S_IS_WEAK (fixP->fx_addsy))
11039 if (mips_pic != EMBEDDED_PIC
11040 && (S_IS_WEAK (fixP->fx_addsy)
11041 || S_IS_EXTERNAL (fixP->fx_addsy))
11042 && !S_IS_COMMON (fixP->fx_addsy))
11044 if (symbol_used_in_reloc_p (fixP->fx_addsy)
11045 && (((bfd_get_section_flags (stdoutput,
11046 S_GET_SEGMENT (fixP->fx_addsy))
11047 & (SEC_LINK_ONCE | SEC_MERGE)) != 0)
11048 || !strncmp (segment_name (S_GET_SEGMENT (fixP->fx_addsy)),
11050 sizeof (".gnu.linkonce") - 1)))
11056 /* Apply a fixup to the object file. */
11059 md_apply_fix3 (fixP, valP, seg)
11062 segT seg ATTRIBUTE_UNUSED;
11067 static int previous_fx_r_type = 0;
11069 /* FIXME: Maybe just return for all reloc types not listed below?
11070 Eric Christopher says: "This is stupid, please rewrite md_apply_fix3. */
11071 if (fixP->fx_r_type == BFD_RELOC_8)
11074 assert (fixP->fx_size == 4
11075 || fixP->fx_r_type == BFD_RELOC_16
11076 || fixP->fx_r_type == BFD_RELOC_32
11077 || fixP->fx_r_type == BFD_RELOC_MIPS_JMP
11078 || fixP->fx_r_type == BFD_RELOC_HI16_S
11079 || fixP->fx_r_type == BFD_RELOC_LO16
11080 || fixP->fx_r_type == BFD_RELOC_GPREL16
11081 || fixP->fx_r_type == BFD_RELOC_MIPS_LITERAL
11082 || fixP->fx_r_type == BFD_RELOC_GPREL32
11083 || fixP->fx_r_type == BFD_RELOC_64
11084 || fixP->fx_r_type == BFD_RELOC_CTOR
11085 || fixP->fx_r_type == BFD_RELOC_MIPS_SUB
11086 || fixP->fx_r_type == BFD_RELOC_MIPS_HIGHEST
11087 || fixP->fx_r_type == BFD_RELOC_MIPS_HIGHER
11088 || fixP->fx_r_type == BFD_RELOC_MIPS_SCN_DISP
11089 || fixP->fx_r_type == BFD_RELOC_MIPS_REL16
11090 || fixP->fx_r_type == BFD_RELOC_MIPS_RELGOT
11091 || fixP->fx_r_type == BFD_RELOC_VTABLE_INHERIT
11092 || fixP->fx_r_type == BFD_RELOC_VTABLE_ENTRY
11093 || fixP->fx_r_type == BFD_RELOC_MIPS_JALR);
11097 /* If we aren't adjusting this fixup to be against the section
11098 symbol, we need to adjust the value. */
11100 if (fixP->fx_addsy != NULL && OUTPUT_FLAVOR == bfd_target_elf_flavour)
11102 if (mips_need_elf_addend_fixup (fixP))
11104 reloc_howto_type *howto;
11105 valueT symval = S_GET_VALUE (fixP->fx_addsy);
11109 howto = bfd_reloc_type_lookup (stdoutput, fixP->fx_r_type);
11110 if (value != 0 && howto && howto->partial_inplace
11111 && (! fixP->fx_pcrel || howto->pcrel_offset))
11113 /* In this case, the bfd_install_relocation routine will
11114 incorrectly add the symbol value back in. We just want
11115 the addend to appear in the object file.
11117 howto->pcrel_offset is added for R_MIPS_PC16, which is
11118 generated for code like
11129 /* Make sure the addend is still non-zero. If it became zero
11130 after the last operation, set it to a spurious value and
11131 subtract the same value from the object file's contents. */
11136 /* The in-place addends for LO16 relocations are signed;
11137 leave the matching HI16 in-place addends as zero. */
11138 if (fixP->fx_r_type != BFD_RELOC_HI16_S)
11140 bfd_vma contents, mask, field;
11142 contents = bfd_get_bits (fixP->fx_frag->fr_literal
11145 target_big_endian);
11147 /* MASK has bits set where the relocation should go.
11148 FIELD is -value, shifted into the appropriate place
11149 for this relocation. */
11150 mask = 1 << (howto->bitsize - 1);
11151 mask = (((mask - 1) << 1) | 1) << howto->bitpos;
11152 field = (-value >> howto->rightshift) << howto->bitpos;
11154 bfd_put_bits ((field & mask) | (contents & ~mask),
11155 fixP->fx_frag->fr_literal + fixP->fx_where,
11157 target_big_endian);
11163 /* This code was generated using trial and error and so is
11164 fragile and not trustworthy. If you change it, you should
11165 rerun the elf-rel, elf-rel2, and empic testcases and ensure
11166 they still pass. */
11167 if (fixP->fx_pcrel || fixP->fx_subsy != NULL)
11169 value += fixP->fx_frag->fr_address + fixP->fx_where;
11171 /* BFD's REL handling, for MIPS, is _very_ weird.
11172 This gives the right results, but it can't possibly
11173 be the way things are supposed to work. */
11174 if (fixP->fx_r_type != BFD_RELOC_16_PCREL_S2
11175 || S_GET_SEGMENT (fixP->fx_addsy) != undefined_section)
11176 value += fixP->fx_frag->fr_address + fixP->fx_where;
11181 fixP->fx_addnumber = value; /* Remember value for tc_gen_reloc. */
11183 /* We are not done if this is a composite relocation to set up gp. */
11184 if (fixP->fx_addsy == NULL && ! fixP->fx_pcrel
11185 && !(fixP->fx_r_type == BFD_RELOC_MIPS_SUB
11186 || (fixP->fx_r_type == BFD_RELOC_64
11187 && (previous_fx_r_type == BFD_RELOC_GPREL32
11188 || previous_fx_r_type == BFD_RELOC_GPREL16))
11189 || (previous_fx_r_type == BFD_RELOC_MIPS_SUB
11190 && (fixP->fx_r_type == BFD_RELOC_HI16_S
11191 || fixP->fx_r_type == BFD_RELOC_LO16))))
11193 previous_fx_r_type = fixP->fx_r_type;
11195 switch (fixP->fx_r_type)
11197 case BFD_RELOC_MIPS_JMP:
11198 case BFD_RELOC_MIPS_SHIFT5:
11199 case BFD_RELOC_MIPS_SHIFT6:
11200 case BFD_RELOC_MIPS_GOT_DISP:
11201 case BFD_RELOC_MIPS_GOT_PAGE:
11202 case BFD_RELOC_MIPS_GOT_OFST:
11203 case BFD_RELOC_MIPS_SUB:
11204 case BFD_RELOC_MIPS_INSERT_A:
11205 case BFD_RELOC_MIPS_INSERT_B:
11206 case BFD_RELOC_MIPS_DELETE:
11207 case BFD_RELOC_MIPS_HIGHEST:
11208 case BFD_RELOC_MIPS_HIGHER:
11209 case BFD_RELOC_MIPS_SCN_DISP:
11210 case BFD_RELOC_MIPS_REL16:
11211 case BFD_RELOC_MIPS_RELGOT:
11212 case BFD_RELOC_MIPS_JALR:
11213 case BFD_RELOC_HI16:
11214 case BFD_RELOC_HI16_S:
11215 case BFD_RELOC_GPREL16:
11216 case BFD_RELOC_MIPS_LITERAL:
11217 case BFD_RELOC_MIPS_CALL16:
11218 case BFD_RELOC_MIPS_GOT16:
11219 case BFD_RELOC_GPREL32:
11220 case BFD_RELOC_MIPS_GOT_HI16:
11221 case BFD_RELOC_MIPS_GOT_LO16:
11222 case BFD_RELOC_MIPS_CALL_HI16:
11223 case BFD_RELOC_MIPS_CALL_LO16:
11224 case BFD_RELOC_MIPS16_GPREL:
11225 if (fixP->fx_pcrel)
11226 as_bad_where (fixP->fx_file, fixP->fx_line,
11227 _("Invalid PC relative reloc"));
11228 /* Nothing needed to do. The value comes from the reloc entry */
11231 case BFD_RELOC_MIPS16_JMP:
11232 /* We currently always generate a reloc against a symbol, which
11233 means that we don't want an addend even if the symbol is
11235 fixP->fx_addnumber = 0;
11238 case BFD_RELOC_PCREL_HI16_S:
11239 /* The addend for this is tricky if it is internal, so we just
11240 do everything here rather than in bfd_install_relocation. */
11241 if (OUTPUT_FLAVOR == bfd_target_elf_flavour
11246 && (symbol_get_bfdsym (fixP->fx_addsy)->flags & BSF_SECTION_SYM) == 0)
11248 /* For an external symbol adjust by the address to make it
11249 pcrel_offset. We use the address of the RELLO reloc
11250 which follows this one. */
11251 value += (fixP->fx_next->fx_frag->fr_address
11252 + fixP->fx_next->fx_where);
11254 value = ((value + 0x8000) >> 16) & 0xffff;
11255 buf = (bfd_byte *) fixP->fx_frag->fr_literal + fixP->fx_where;
11256 if (target_big_endian)
11258 md_number_to_chars ((char *) buf, value, 2);
11261 case BFD_RELOC_PCREL_LO16:
11262 /* The addend for this is tricky if it is internal, so we just
11263 do everything here rather than in bfd_install_relocation. */
11264 if (OUTPUT_FLAVOR == bfd_target_elf_flavour
11269 && (symbol_get_bfdsym (fixP->fx_addsy)->flags & BSF_SECTION_SYM) == 0)
11270 value += fixP->fx_frag->fr_address + fixP->fx_where;
11271 buf = (bfd_byte *) fixP->fx_frag->fr_literal + fixP->fx_where;
11272 if (target_big_endian)
11274 md_number_to_chars ((char *) buf, value, 2);
11278 /* This is handled like BFD_RELOC_32, but we output a sign
11279 extended value if we are only 32 bits. */
11281 || (mips_pic == EMBEDDED_PIC && SWITCH_TABLE (fixP)))
11283 if (8 <= sizeof (valueT))
11284 md_number_to_chars (fixP->fx_frag->fr_literal + fixP->fx_where,
11291 w1 = w2 = fixP->fx_where;
11292 if (target_big_endian)
11296 md_number_to_chars (fixP->fx_frag->fr_literal + w1, value, 4);
11297 if ((value & 0x80000000) != 0)
11301 md_number_to_chars (fixP->fx_frag->fr_literal + w2, hiv, 4);
11306 case BFD_RELOC_RVA:
11308 /* If we are deleting this reloc entry, we must fill in the
11309 value now. This can happen if we have a .word which is not
11310 resolved when it appears but is later defined. We also need
11311 to fill in the value if this is an embedded PIC switch table
11314 || (mips_pic == EMBEDDED_PIC && SWITCH_TABLE (fixP)))
11315 md_number_to_chars (fixP->fx_frag->fr_literal + fixP->fx_where,
11320 /* If we are deleting this reloc entry, we must fill in the
11322 assert (fixP->fx_size == 2);
11324 md_number_to_chars (fixP->fx_frag->fr_literal + fixP->fx_where,
11328 case BFD_RELOC_LO16:
11329 /* When handling an embedded PIC switch statement, we can wind
11330 up deleting a LO16 reloc. See the 'o' case in mips_ip. */
11333 if (value + 0x8000 > 0xffff)
11334 as_bad_where (fixP->fx_file, fixP->fx_line,
11335 _("relocation overflow"));
11336 buf = (bfd_byte *) fixP->fx_frag->fr_literal + fixP->fx_where;
11337 if (target_big_endian)
11339 md_number_to_chars ((char *) buf, value, 2);
11343 case BFD_RELOC_16_PCREL_S2:
11344 if ((value & 0x3) != 0)
11345 as_bad_where (fixP->fx_file, fixP->fx_line,
11346 _("Branch to odd address (%lx)"), (long) value);
11349 * We need to save the bits in the instruction since fixup_segment()
11350 * might be deleting the relocation entry (i.e., a branch within
11351 * the current segment).
11353 if (!fixP->fx_done && (value != 0 || HAVE_NEWABI))
11355 /* If 'value' is zero, the remaining reloc code won't actually
11356 do the store, so it must be done here. This is probably
11357 a bug somewhere. */
11359 && (fixP->fx_r_type != BFD_RELOC_16_PCREL_S2
11360 || fixP->fx_addsy == NULL /* ??? */
11361 || ! S_IS_DEFINED (fixP->fx_addsy)))
11362 value -= fixP->fx_frag->fr_address + fixP->fx_where;
11364 value = (offsetT) value >> 2;
11366 /* update old instruction data */
11367 buf = (bfd_byte *) (fixP->fx_where + fixP->fx_frag->fr_literal);
11368 if (target_big_endian)
11369 insn = (buf[0] << 24) | (buf[1] << 16) | (buf[2] << 8) | buf[3];
11371 insn = (buf[3] << 24) | (buf[2] << 16) | (buf[1] << 8) | buf[0];
11373 if (value + 0x8000 <= 0xffff)
11374 insn |= value & 0xffff;
11377 /* The branch offset is too large. If this is an
11378 unconditional branch, and we are not generating PIC code,
11379 we can convert it to an absolute jump instruction. */
11380 if (mips_pic == NO_PIC
11382 && fixP->fx_frag->fr_address >= text_section->vma
11383 && (fixP->fx_frag->fr_address
11384 < text_section->vma + text_section->_raw_size)
11385 && ((insn & 0xffff0000) == 0x10000000 /* beq $0,$0 */
11386 || (insn & 0xffff0000) == 0x04010000 /* bgez $0 */
11387 || (insn & 0xffff0000) == 0x04110000)) /* bgezal $0 */
11389 if ((insn & 0xffff0000) == 0x04110000) /* bgezal $0 */
11390 insn = 0x0c000000; /* jal */
11392 insn = 0x08000000; /* j */
11393 fixP->fx_r_type = BFD_RELOC_MIPS_JMP;
11395 fixP->fx_addsy = section_symbol (text_section);
11396 fixP->fx_addnumber = (value << 2) + md_pcrel_from (fixP);
11400 /* If we got here, we have branch-relaxation disabled,
11401 and there's nothing we can do to fix this instruction
11402 without turning it into a longer sequence. */
11403 as_bad_where (fixP->fx_file, fixP->fx_line,
11404 _("Branch out of range"));
11408 md_number_to_chars ((char *) buf, (valueT) insn, 4);
11411 case BFD_RELOC_VTABLE_INHERIT:
11414 && !S_IS_DEFINED (fixP->fx_addsy)
11415 && !S_IS_WEAK (fixP->fx_addsy))
11416 S_SET_WEAK (fixP->fx_addsy);
11419 case BFD_RELOC_VTABLE_ENTRY:
11433 const struct mips_opcode *p;
11434 int treg, sreg, dreg, shamt;
11439 for (i = 0; i < NUMOPCODES; ++i)
11441 p = &mips_opcodes[i];
11442 if (((oc & p->mask) == p->match) && (p->pinfo != INSN_MACRO))
11444 printf ("%08lx %s\t", oc, p->name);
11445 treg = (oc >> 16) & 0x1f;
11446 sreg = (oc >> 21) & 0x1f;
11447 dreg = (oc >> 11) & 0x1f;
11448 shamt = (oc >> 6) & 0x1f;
11450 for (args = p->args;; ++args)
11461 printf ("%c", *args);
11465 assert (treg == sreg);
11466 printf ("$%d,$%d", treg, sreg);
11471 printf ("$%d", dreg);
11476 printf ("$%d", treg);
11480 printf ("0x%x", treg);
11485 printf ("$%d", sreg);
11489 printf ("0x%08lx", oc & 0x1ffffff);
11496 printf ("%d", imm);
11501 printf ("$%d", shamt);
11512 printf (_("%08lx UNDEFINED\n"), oc);
11523 name = input_line_pointer;
11524 c = get_symbol_end ();
11525 p = (symbolS *) symbol_find_or_make (name);
11526 *input_line_pointer = c;
11530 /* Align the current frag to a given power of two. The MIPS assembler
11531 also automatically adjusts any preceding label. */
11534 mips_align (to, fill, label)
11539 mips_emit_delays (FALSE);
11540 frag_align (to, fill, 0);
11541 record_alignment (now_seg, to);
11544 assert (S_GET_SEGMENT (label) == now_seg);
11545 symbol_set_frag (label, frag_now);
11546 S_SET_VALUE (label, (valueT) frag_now_fix ());
11550 /* Align to a given power of two. .align 0 turns off the automatic
11551 alignment used by the data creating pseudo-ops. */
11555 int x ATTRIBUTE_UNUSED;
11558 register long temp_fill;
11559 long max_alignment = 15;
11563 o Note that the assembler pulls down any immediately preceeding label
11564 to the aligned address.
11565 o It's not documented but auto alignment is reinstated by
11566 a .align pseudo instruction.
11567 o Note also that after auto alignment is turned off the mips assembler
11568 issues an error on attempt to assemble an improperly aligned data item.
11573 temp = get_absolute_expression ();
11574 if (temp > max_alignment)
11575 as_bad (_("Alignment too large: %d. assumed."), temp = max_alignment);
11578 as_warn (_("Alignment negative: 0 assumed."));
11581 if (*input_line_pointer == ',')
11583 ++input_line_pointer;
11584 temp_fill = get_absolute_expression ();
11591 mips_align (temp, (int) temp_fill,
11592 insn_labels != NULL ? insn_labels->label : NULL);
11599 demand_empty_rest_of_line ();
11603 mips_flush_pending_output ()
11605 mips_emit_delays (FALSE);
11606 mips_clear_insn_labels ();
11615 /* When generating embedded PIC code, we only use the .text, .lit8,
11616 .sdata and .sbss sections. We change the .data and .rdata
11617 pseudo-ops to use .sdata. */
11618 if (mips_pic == EMBEDDED_PIC
11619 && (sec == 'd' || sec == 'r'))
11623 /* The ELF backend needs to know that we are changing sections, so
11624 that .previous works correctly. We could do something like check
11625 for an obj_section_change_hook macro, but that might be confusing
11626 as it would not be appropriate to use it in the section changing
11627 functions in read.c, since obj-elf.c intercepts those. FIXME:
11628 This should be cleaner, somehow. */
11629 obj_elf_section_change_hook ();
11632 mips_emit_delays (FALSE);
11642 subseg_set (bss_section, (subsegT) get_absolute_expression ());
11643 demand_empty_rest_of_line ();
11647 if (USE_GLOBAL_POINTER_OPT)
11649 seg = subseg_new (RDATA_SECTION_NAME,
11650 (subsegT) get_absolute_expression ());
11651 if (OUTPUT_FLAVOR == bfd_target_elf_flavour)
11653 bfd_set_section_flags (stdoutput, seg,
11659 if (strcmp (TARGET_OS, "elf") != 0)
11660 record_alignment (seg, 4);
11662 demand_empty_rest_of_line ();
11666 as_bad (_("No read only data section in this object file format"));
11667 demand_empty_rest_of_line ();
11673 if (USE_GLOBAL_POINTER_OPT)
11675 seg = subseg_new (".sdata", (subsegT) get_absolute_expression ());
11676 if (OUTPUT_FLAVOR == bfd_target_elf_flavour)
11678 bfd_set_section_flags (stdoutput, seg,
11679 SEC_ALLOC | SEC_LOAD | SEC_RELOC
11681 if (strcmp (TARGET_OS, "elf") != 0)
11682 record_alignment (seg, 4);
11684 demand_empty_rest_of_line ();
11689 as_bad (_("Global pointers not supported; recompile -G 0"));
11690 demand_empty_rest_of_line ();
11699 s_change_section (ignore)
11700 int ignore ATTRIBUTE_UNUSED;
11703 char *section_name;
11708 int section_entry_size;
11709 int section_alignment;
11711 if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
11714 section_name = input_line_pointer;
11715 c = get_symbol_end ();
11717 next_c = *(input_line_pointer + 1);
11719 /* Do we have .section Name<,"flags">? */
11720 if (c != ',' || (c == ',' && next_c == '"'))
11722 /* just after name is now '\0'. */
11723 *input_line_pointer = c;
11724 input_line_pointer = section_name;
11725 obj_elf_section (ignore);
11728 input_line_pointer++;
11730 /* Do we have .section Name<,type><,flag><,entry_size><,alignment> */
11732 section_type = get_absolute_expression ();
11735 if (*input_line_pointer++ == ',')
11736 section_flag = get_absolute_expression ();
11739 if (*input_line_pointer++ == ',')
11740 section_entry_size = get_absolute_expression ();
11742 section_entry_size = 0;
11743 if (*input_line_pointer++ == ',')
11744 section_alignment = get_absolute_expression ();
11746 section_alignment = 0;
11748 section_name = xstrdup (section_name);
11750 obj_elf_change_section (section_name, section_type, section_flag,
11751 section_entry_size, 0, 0, 0);
11753 if (now_seg->name != section_name)
11754 free (section_name);
11755 #endif /* OBJ_ELF */
11759 mips_enable_auto_align ()
11770 label = insn_labels != NULL ? insn_labels->label : NULL;
11771 mips_emit_delays (FALSE);
11772 if (log_size > 0 && auto_align)
11773 mips_align (log_size, 0, label);
11774 mips_clear_insn_labels ();
11775 cons (1 << log_size);
11779 s_float_cons (type)
11784 label = insn_labels != NULL ? insn_labels->label : NULL;
11786 mips_emit_delays (FALSE);
11791 mips_align (3, 0, label);
11793 mips_align (2, 0, label);
11796 mips_clear_insn_labels ();
11801 /* Handle .globl. We need to override it because on Irix 5 you are
11804 where foo is an undefined symbol, to mean that foo should be
11805 considered to be the address of a function. */
11809 int x ATTRIBUTE_UNUSED;
11816 name = input_line_pointer;
11817 c = get_symbol_end ();
11818 symbolP = symbol_find_or_make (name);
11819 *input_line_pointer = c;
11820 SKIP_WHITESPACE ();
11822 /* On Irix 5, every global symbol that is not explicitly labelled as
11823 being a function is apparently labelled as being an object. */
11826 if (! is_end_of_line[(unsigned char) *input_line_pointer])
11831 secname = input_line_pointer;
11832 c = get_symbol_end ();
11833 sec = bfd_get_section_by_name (stdoutput, secname);
11835 as_bad (_("%s: no such section"), secname);
11836 *input_line_pointer = c;
11838 if (sec != NULL && (sec->flags & SEC_CODE) != 0)
11839 flag = BSF_FUNCTION;
11842 symbol_get_bfdsym (symbolP)->flags |= flag;
11844 S_SET_EXTERNAL (symbolP);
11845 demand_empty_rest_of_line ();
11850 int x ATTRIBUTE_UNUSED;
11855 opt = input_line_pointer;
11856 c = get_symbol_end ();
11860 /* FIXME: What does this mean? */
11862 else if (strncmp (opt, "pic", 3) == 0)
11866 i = atoi (opt + 3);
11870 mips_pic = SVR4_PIC;
11872 as_bad (_(".option pic%d not supported"), i);
11874 if (USE_GLOBAL_POINTER_OPT && mips_pic == SVR4_PIC)
11876 if (g_switch_seen && g_switch_value != 0)
11877 as_warn (_("-G may not be used with SVR4 PIC code"));
11878 g_switch_value = 0;
11879 bfd_set_gp_size (stdoutput, 0);
11883 as_warn (_("Unrecognized option \"%s\""), opt);
11885 *input_line_pointer = c;
11886 demand_empty_rest_of_line ();
11889 /* This structure is used to hold a stack of .set values. */
11891 struct mips_option_stack
11893 struct mips_option_stack *next;
11894 struct mips_set_options options;
11897 static struct mips_option_stack *mips_opts_stack;
11899 /* Handle the .set pseudo-op. */
11903 int x ATTRIBUTE_UNUSED;
11905 char *name = input_line_pointer, ch;
11907 while (!is_end_of_line[(unsigned char) *input_line_pointer])
11908 ++input_line_pointer;
11909 ch = *input_line_pointer;
11910 *input_line_pointer = '\0';
11912 if (strcmp (name, "reorder") == 0)
11914 if (mips_opts.noreorder && prev_nop_frag != NULL)
11916 /* If we still have pending nops, we can discard them. The
11917 usual nop handling will insert any that are still
11919 prev_nop_frag->fr_fix -= (prev_nop_frag_holds
11920 * (mips_opts.mips16 ? 2 : 4));
11921 prev_nop_frag = NULL;
11923 mips_opts.noreorder = 0;
11925 else if (strcmp (name, "noreorder") == 0)
11927 mips_emit_delays (TRUE);
11928 mips_opts.noreorder = 1;
11929 mips_any_noreorder = 1;
11931 else if (strcmp (name, "at") == 0)
11933 mips_opts.noat = 0;
11935 else if (strcmp (name, "noat") == 0)
11937 mips_opts.noat = 1;
11939 else if (strcmp (name, "macro") == 0)
11941 mips_opts.warn_about_macros = 0;
11943 else if (strcmp (name, "nomacro") == 0)
11945 if (mips_opts.noreorder == 0)
11946 as_bad (_("`noreorder' must be set before `nomacro'"));
11947 mips_opts.warn_about_macros = 1;
11949 else if (strcmp (name, "move") == 0 || strcmp (name, "novolatile") == 0)
11951 mips_opts.nomove = 0;
11953 else if (strcmp (name, "nomove") == 0 || strcmp (name, "volatile") == 0)
11955 mips_opts.nomove = 1;
11957 else if (strcmp (name, "bopt") == 0)
11959 mips_opts.nobopt = 0;
11961 else if (strcmp (name, "nobopt") == 0)
11963 mips_opts.nobopt = 1;
11965 else if (strcmp (name, "mips16") == 0
11966 || strcmp (name, "MIPS-16") == 0)
11967 mips_opts.mips16 = 1;
11968 else if (strcmp (name, "nomips16") == 0
11969 || strcmp (name, "noMIPS-16") == 0)
11970 mips_opts.mips16 = 0;
11971 else if (strcmp (name, "mips3d") == 0)
11972 mips_opts.ase_mips3d = 1;
11973 else if (strcmp (name, "nomips3d") == 0)
11974 mips_opts.ase_mips3d = 0;
11975 else if (strcmp (name, "mdmx") == 0)
11976 mips_opts.ase_mdmx = 1;
11977 else if (strcmp (name, "nomdmx") == 0)
11978 mips_opts.ase_mdmx = 0;
11979 else if (strncmp (name, "mips", 4) == 0)
11983 /* Permit the user to change the ISA on the fly. Needless to
11984 say, misuse can cause serious problems. */
11985 if (strcmp (name, "mips0") == 0)
11988 mips_opts.isa = file_mips_isa;
11990 else if (strcmp (name, "mips1") == 0)
11991 mips_opts.isa = ISA_MIPS1;
11992 else if (strcmp (name, "mips2") == 0)
11993 mips_opts.isa = ISA_MIPS2;
11994 else if (strcmp (name, "mips3") == 0)
11995 mips_opts.isa = ISA_MIPS3;
11996 else if (strcmp (name, "mips4") == 0)
11997 mips_opts.isa = ISA_MIPS4;
11998 else if (strcmp (name, "mips5") == 0)
11999 mips_opts.isa = ISA_MIPS5;
12000 else if (strcmp (name, "mips32") == 0)
12001 mips_opts.isa = ISA_MIPS32;
12002 else if (strcmp (name, "mips32r2") == 0)
12003 mips_opts.isa = ISA_MIPS32R2;
12004 else if (strcmp (name, "mips64") == 0)
12005 mips_opts.isa = ISA_MIPS64;
12007 as_bad (_("unknown ISA level %s"), name + 4);
12009 switch (mips_opts.isa)
12017 mips_opts.gp32 = 1;
12018 mips_opts.fp32 = 1;
12024 mips_opts.gp32 = 0;
12025 mips_opts.fp32 = 0;
12028 as_bad (_("unknown ISA level %s"), name + 4);
12033 mips_opts.gp32 = file_mips_gp32;
12034 mips_opts.fp32 = file_mips_fp32;
12037 else if (strcmp (name, "autoextend") == 0)
12038 mips_opts.noautoextend = 0;
12039 else if (strcmp (name, "noautoextend") == 0)
12040 mips_opts.noautoextend = 1;
12041 else if (strcmp (name, "push") == 0)
12043 struct mips_option_stack *s;
12045 s = (struct mips_option_stack *) xmalloc (sizeof *s);
12046 s->next = mips_opts_stack;
12047 s->options = mips_opts;
12048 mips_opts_stack = s;
12050 else if (strcmp (name, "pop") == 0)
12052 struct mips_option_stack *s;
12054 s = mips_opts_stack;
12056 as_bad (_(".set pop with no .set push"));
12059 /* If we're changing the reorder mode we need to handle
12060 delay slots correctly. */
12061 if (s->options.noreorder && ! mips_opts.noreorder)
12062 mips_emit_delays (TRUE);
12063 else if (! s->options.noreorder && mips_opts.noreorder)
12065 if (prev_nop_frag != NULL)
12067 prev_nop_frag->fr_fix -= (prev_nop_frag_holds
12068 * (mips_opts.mips16 ? 2 : 4));
12069 prev_nop_frag = NULL;
12073 mips_opts = s->options;
12074 mips_opts_stack = s->next;
12080 as_warn (_("Tried to set unrecognized symbol: %s\n"), name);
12082 *input_line_pointer = ch;
12083 demand_empty_rest_of_line ();
12086 /* Handle the .abicalls pseudo-op. I believe this is equivalent to
12087 .option pic2. It means to generate SVR4 PIC calls. */
12090 s_abicalls (ignore)
12091 int ignore ATTRIBUTE_UNUSED;
12093 mips_pic = SVR4_PIC;
12094 if (USE_GLOBAL_POINTER_OPT)
12096 if (g_switch_seen && g_switch_value != 0)
12097 as_warn (_("-G may not be used with SVR4 PIC code"));
12098 g_switch_value = 0;
12100 bfd_set_gp_size (stdoutput, 0);
12101 demand_empty_rest_of_line ();
12104 /* Handle the .cpload pseudo-op. This is used when generating SVR4
12105 PIC code. It sets the $gp register for the function based on the
12106 function address, which is in the register named in the argument.
12107 This uses a relocation against _gp_disp, which is handled specially
12108 by the linker. The result is:
12109 lui $gp,%hi(_gp_disp)
12110 addiu $gp,$gp,%lo(_gp_disp)
12111 addu $gp,$gp,.cpload argument
12112 The .cpload argument is normally $25 == $t9. */
12116 int ignore ATTRIBUTE_UNUSED;
12121 /* If we are not generating SVR4 PIC code, or if this is NewABI code,
12122 .cpload is ignored. */
12123 if (mips_pic != SVR4_PIC || HAVE_NEWABI)
12129 /* .cpload should be in a .set noreorder section. */
12130 if (mips_opts.noreorder == 0)
12131 as_warn (_(".cpload not in noreorder section"));
12133 ex.X_op = O_symbol;
12134 ex.X_add_symbol = symbol_find_or_make ("_gp_disp");
12135 ex.X_op_symbol = NULL;
12136 ex.X_add_number = 0;
12138 /* In ELF, this symbol is implicitly an STT_OBJECT symbol. */
12139 symbol_get_bfdsym (ex.X_add_symbol)->flags |= BSF_OBJECT;
12141 macro_build_lui (NULL, &icnt, &ex, mips_gp_register);
12142 macro_build ((char *) NULL, &icnt, &ex, "addiu", "t,r,j",
12143 mips_gp_register, mips_gp_register, (int) BFD_RELOC_LO16);
12145 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "addu", "d,v,t",
12146 mips_gp_register, mips_gp_register, tc_get_register (0));
12148 demand_empty_rest_of_line ();
12151 /* Handle the .cpsetup pseudo-op defined for NewABI PIC code. The syntax is:
12152 .cpsetup $reg1, offset|$reg2, label
12154 If offset is given, this results in:
12155 sd $gp, offset($sp)
12156 lui $gp, %hi(%neg(%gp_rel(label)))
12157 addiu $gp, $gp, %lo(%neg(%gp_rel(label)))
12158 daddu $gp, $gp, $reg1
12160 If $reg2 is given, this results in:
12161 daddu $reg2, $gp, $0
12162 lui $gp, %hi(%neg(%gp_rel(label)))
12163 addiu $gp, $gp, %lo(%neg(%gp_rel(label)))
12164 daddu $gp, $gp, $reg1
12165 $reg1 is normally $25 == $t9. */
12168 int ignore ATTRIBUTE_UNUSED;
12170 expressionS ex_off;
12171 expressionS ex_sym;
12176 /* If we are not generating SVR4 PIC code, .cpsetup is ignored.
12177 We also need NewABI support. */
12178 if (mips_pic != SVR4_PIC || ! HAVE_NEWABI)
12184 reg1 = tc_get_register (0);
12185 SKIP_WHITESPACE ();
12186 if (*input_line_pointer != ',')
12188 as_bad (_("missing argument separator ',' for .cpsetup"));
12192 ++input_line_pointer;
12193 SKIP_WHITESPACE ();
12194 if (*input_line_pointer == '$')
12196 mips_cpreturn_register = tc_get_register (0);
12197 mips_cpreturn_offset = -1;
12201 mips_cpreturn_offset = get_absolute_expression ();
12202 mips_cpreturn_register = -1;
12204 SKIP_WHITESPACE ();
12205 if (*input_line_pointer != ',')
12207 as_bad (_("missing argument separator ',' for .cpsetup"));
12211 ++input_line_pointer;
12212 SKIP_WHITESPACE ();
12213 expression (&ex_sym);
12215 if (mips_cpreturn_register == -1)
12217 ex_off.X_op = O_constant;
12218 ex_off.X_add_symbol = NULL;
12219 ex_off.X_op_symbol = NULL;
12220 ex_off.X_add_number = mips_cpreturn_offset;
12222 macro_build ((char *) NULL, &icnt, &ex_off, "sd", "t,o(b)",
12223 mips_gp_register, (int) BFD_RELOC_LO16, SP);
12226 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "daddu",
12227 "d,v,t", mips_cpreturn_register, mips_gp_register, 0);
12229 /* Ensure there's room for the next two instructions, so that `f'
12230 doesn't end up with an address in the wrong frag. */
12233 macro_build ((char *) NULL, &icnt, &ex_sym, "lui", "t,u", mips_gp_register,
12234 (int) BFD_RELOC_GPREL16);
12235 fix_new (frag_now, f - frag_now->fr_literal,
12236 0, NULL, 0, 0, BFD_RELOC_MIPS_SUB);
12237 fix_new (frag_now, f - frag_now->fr_literal,
12238 0, NULL, 0, 0, BFD_RELOC_HI16_S);
12241 macro_build ((char *) NULL, &icnt, &ex_sym, "addiu", "t,r,j",
12242 mips_gp_register, mips_gp_register, (int) BFD_RELOC_GPREL16);
12243 fix_new (frag_now, f - frag_now->fr_literal,
12244 0, NULL, 0, 0, BFD_RELOC_MIPS_SUB);
12245 fix_new (frag_now, f - frag_now->fr_literal,
12246 0, NULL, 0, 0, BFD_RELOC_LO16);
12248 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
12249 HAVE_64BIT_ADDRESSES ? "daddu" : "addu", "d,v,t",
12250 mips_gp_register, mips_gp_register, reg1);
12252 demand_empty_rest_of_line ();
12257 int ignore ATTRIBUTE_UNUSED;
12259 /* If we are not generating SVR4 PIC code, or if this is not NewABI code,
12260 .cplocal is ignored. */
12261 if (mips_pic != SVR4_PIC || ! HAVE_NEWABI)
12267 mips_gp_register = tc_get_register (0);
12268 demand_empty_rest_of_line ();
12271 /* Handle the .cprestore pseudo-op. This stores $gp into a given
12272 offset from $sp. The offset is remembered, and after making a PIC
12273 call $gp is restored from that location. */
12276 s_cprestore (ignore)
12277 int ignore ATTRIBUTE_UNUSED;
12282 /* If we are not generating SVR4 PIC code, or if this is NewABI code,
12283 .cprestore is ignored. */
12284 if (mips_pic != SVR4_PIC || HAVE_NEWABI)
12290 mips_cprestore_offset = get_absolute_expression ();
12291 mips_cprestore_valid = 1;
12293 ex.X_op = O_constant;
12294 ex.X_add_symbol = NULL;
12295 ex.X_op_symbol = NULL;
12296 ex.X_add_number = mips_cprestore_offset;
12298 macro_build_ldst_constoffset ((char *) NULL, &icnt, &ex,
12299 HAVE_32BIT_ADDRESSES ? "sw" : "sd",
12300 mips_gp_register, SP);
12302 demand_empty_rest_of_line ();
12305 /* Handle the .cpreturn pseudo-op defined for NewABI PIC code. If an offset
12306 was given in the preceeding .gpsetup, it results in:
12307 ld $gp, offset($sp)
12309 If a register $reg2 was given there, it results in:
12310 daddiu $gp, $gp, $reg2
12313 s_cpreturn (ignore)
12314 int ignore ATTRIBUTE_UNUSED;
12319 /* If we are not generating SVR4 PIC code, .cpreturn is ignored.
12320 We also need NewABI support. */
12321 if (mips_pic != SVR4_PIC || ! HAVE_NEWABI)
12327 if (mips_cpreturn_register == -1)
12329 ex.X_op = O_constant;
12330 ex.X_add_symbol = NULL;
12331 ex.X_op_symbol = NULL;
12332 ex.X_add_number = mips_cpreturn_offset;
12334 macro_build ((char *) NULL, &icnt, &ex, "ld", "t,o(b)",
12335 mips_gp_register, (int) BFD_RELOC_LO16, SP);
12338 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "daddu",
12339 "d,v,t", mips_gp_register, mips_cpreturn_register, 0);
12341 demand_empty_rest_of_line ();
12344 /* Handle the .gpvalue pseudo-op. This is used when generating NewABI PIC
12345 code. It sets the offset to use in gp_rel relocations. */
12349 int ignore ATTRIBUTE_UNUSED;
12351 /* If we are not generating SVR4 PIC code, .gpvalue is ignored.
12352 We also need NewABI support. */
12353 if (mips_pic != SVR4_PIC || ! HAVE_NEWABI)
12359 mips_gprel_offset = get_absolute_expression ();
12361 demand_empty_rest_of_line ();
12364 /* Handle the .gpword pseudo-op. This is used when generating PIC
12365 code. It generates a 32 bit GP relative reloc. */
12369 int ignore ATTRIBUTE_UNUSED;
12375 /* When not generating PIC code, this is treated as .word. */
12376 if (mips_pic != SVR4_PIC)
12382 label = insn_labels != NULL ? insn_labels->label : NULL;
12383 mips_emit_delays (TRUE);
12385 mips_align (2, 0, label);
12386 mips_clear_insn_labels ();
12390 if (ex.X_op != O_symbol || ex.X_add_number != 0)
12392 as_bad (_("Unsupported use of .gpword"));
12393 ignore_rest_of_line ();
12397 md_number_to_chars (p, (valueT) 0, 4);
12398 fix_new_exp (frag_now, p - frag_now->fr_literal, 4, &ex, FALSE,
12399 BFD_RELOC_GPREL32);
12401 demand_empty_rest_of_line ();
12406 int ignore ATTRIBUTE_UNUSED;
12412 /* When not generating PIC code, this is treated as .dword. */
12413 if (mips_pic != SVR4_PIC)
12419 label = insn_labels != NULL ? insn_labels->label : NULL;
12420 mips_emit_delays (TRUE);
12422 mips_align (3, 0, label);
12423 mips_clear_insn_labels ();
12427 if (ex.X_op != O_symbol || ex.X_add_number != 0)
12429 as_bad (_("Unsupported use of .gpdword"));
12430 ignore_rest_of_line ();
12434 md_number_to_chars (p, (valueT) 0, 8);
12435 fix_new_exp (frag_now, p - frag_now->fr_literal, 8, &ex, FALSE,
12436 BFD_RELOC_GPREL32);
12438 /* GPREL32 composed with 64 gives a 64-bit GP offset. */
12439 ex.X_op = O_absent;
12440 ex.X_add_symbol = 0;
12441 ex.X_add_number = 0;
12442 fix_new_exp (frag_now, p - frag_now->fr_literal, 8, &ex, FALSE,
12445 demand_empty_rest_of_line ();
12448 /* Handle the .cpadd pseudo-op. This is used when dealing with switch
12449 tables in SVR4 PIC code. */
12453 int ignore ATTRIBUTE_UNUSED;
12458 /* This is ignored when not generating SVR4 PIC code. */
12459 if (mips_pic != SVR4_PIC)
12465 /* Add $gp to the register named as an argument. */
12466 reg = tc_get_register (0);
12467 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
12468 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
12469 "d,v,t", reg, reg, mips_gp_register);
12471 demand_empty_rest_of_line ();
12474 /* Handle the .insn pseudo-op. This marks instruction labels in
12475 mips16 mode. This permits the linker to handle them specially,
12476 such as generating jalx instructions when needed. We also make
12477 them odd for the duration of the assembly, in order to generate the
12478 right sort of code. We will make them even in the adjust_symtab
12479 routine, while leaving them marked. This is convenient for the
12480 debugger and the disassembler. The linker knows to make them odd
12485 int ignore ATTRIBUTE_UNUSED;
12487 mips16_mark_labels ();
12489 demand_empty_rest_of_line ();
12492 /* Handle a .stabn directive. We need these in order to mark a label
12493 as being a mips16 text label correctly. Sometimes the compiler
12494 will emit a label, followed by a .stabn, and then switch sections.
12495 If the label and .stabn are in mips16 mode, then the label is
12496 really a mips16 text label. */
12503 mips16_mark_labels ();
12508 /* Handle the .weakext pseudo-op as defined in Kane and Heinrich.
12512 s_mips_weakext (ignore)
12513 int ignore ATTRIBUTE_UNUSED;
12520 name = input_line_pointer;
12521 c = get_symbol_end ();
12522 symbolP = symbol_find_or_make (name);
12523 S_SET_WEAK (symbolP);
12524 *input_line_pointer = c;
12526 SKIP_WHITESPACE ();
12528 if (! is_end_of_line[(unsigned char) *input_line_pointer])
12530 if (S_IS_DEFINED (symbolP))
12532 as_bad ("ignoring attempt to redefine symbol %s",
12533 S_GET_NAME (symbolP));
12534 ignore_rest_of_line ();
12538 if (*input_line_pointer == ',')
12540 ++input_line_pointer;
12541 SKIP_WHITESPACE ();
12545 if (exp.X_op != O_symbol)
12547 as_bad ("bad .weakext directive");
12548 ignore_rest_of_line ();
12551 symbol_set_value_expression (symbolP, &exp);
12554 demand_empty_rest_of_line ();
12557 /* Parse a register string into a number. Called from the ECOFF code
12558 to parse .frame. The argument is non-zero if this is the frame
12559 register, so that we can record it in mips_frame_reg. */
12562 tc_get_register (frame)
12567 SKIP_WHITESPACE ();
12568 if (*input_line_pointer++ != '$')
12570 as_warn (_("expected `$'"));
12573 else if (ISDIGIT (*input_line_pointer))
12575 reg = get_absolute_expression ();
12576 if (reg < 0 || reg >= 32)
12578 as_warn (_("Bad register number"));
12584 if (strncmp (input_line_pointer, "ra", 2) == 0)
12587 input_line_pointer += 2;
12589 else if (strncmp (input_line_pointer, "fp", 2) == 0)
12592 input_line_pointer += 2;
12594 else if (strncmp (input_line_pointer, "sp", 2) == 0)
12597 input_line_pointer += 2;
12599 else if (strncmp (input_line_pointer, "gp", 2) == 0)
12602 input_line_pointer += 2;
12604 else if (strncmp (input_line_pointer, "at", 2) == 0)
12607 input_line_pointer += 2;
12609 else if (strncmp (input_line_pointer, "kt0", 3) == 0)
12612 input_line_pointer += 3;
12614 else if (strncmp (input_line_pointer, "kt1", 3) == 0)
12617 input_line_pointer += 3;
12619 else if (strncmp (input_line_pointer, "zero", 4) == 0)
12622 input_line_pointer += 4;
12626 as_warn (_("Unrecognized register name"));
12628 while (ISALNUM(*input_line_pointer))
12629 input_line_pointer++;
12634 mips_frame_reg = reg != 0 ? reg : SP;
12635 mips_frame_reg_valid = 1;
12636 mips_cprestore_valid = 0;
12642 md_section_align (seg, addr)
12646 int align = bfd_get_section_alignment (stdoutput, seg);
12649 /* We don't need to align ELF sections to the full alignment.
12650 However, Irix 5 may prefer that we align them at least to a 16
12651 byte boundary. We don't bother to align the sections if we are
12652 targeted for an embedded system. */
12653 if (strcmp (TARGET_OS, "elf") == 0)
12659 return ((addr + (1 << align) - 1) & (-1 << align));
12662 /* Utility routine, called from above as well. If called while the
12663 input file is still being read, it's only an approximation. (For
12664 example, a symbol may later become defined which appeared to be
12665 undefined earlier.) */
12668 nopic_need_relax (sym, before_relaxing)
12670 int before_relaxing;
12675 if (USE_GLOBAL_POINTER_OPT && g_switch_value > 0)
12677 const char *symname;
12680 /* Find out whether this symbol can be referenced off the $gp
12681 register. It can be if it is smaller than the -G size or if
12682 it is in the .sdata or .sbss section. Certain symbols can
12683 not be referenced off the $gp, although it appears as though
12685 symname = S_GET_NAME (sym);
12686 if (symname != (const char *) NULL
12687 && (strcmp (symname, "eprol") == 0
12688 || strcmp (symname, "etext") == 0
12689 || strcmp (symname, "_gp") == 0
12690 || strcmp (symname, "edata") == 0
12691 || strcmp (symname, "_fbss") == 0
12692 || strcmp (symname, "_fdata") == 0
12693 || strcmp (symname, "_ftext") == 0
12694 || strcmp (symname, "end") == 0
12695 || strcmp (symname, "_gp_disp") == 0))
12697 else if ((! S_IS_DEFINED (sym) || S_IS_COMMON (sym))
12699 #ifndef NO_ECOFF_DEBUGGING
12700 || (symbol_get_obj (sym)->ecoff_extern_size != 0
12701 && (symbol_get_obj (sym)->ecoff_extern_size
12702 <= g_switch_value))
12704 /* We must defer this decision until after the whole
12705 file has been read, since there might be a .extern
12706 after the first use of this symbol. */
12707 || (before_relaxing
12708 #ifndef NO_ECOFF_DEBUGGING
12709 && symbol_get_obj (sym)->ecoff_extern_size == 0
12711 && S_GET_VALUE (sym) == 0)
12712 || (S_GET_VALUE (sym) != 0
12713 && S_GET_VALUE (sym) <= g_switch_value)))
12717 const char *segname;
12719 segname = segment_name (S_GET_SEGMENT (sym));
12720 assert (strcmp (segname, ".lit8") != 0
12721 && strcmp (segname, ".lit4") != 0);
12722 change = (strcmp (segname, ".sdata") != 0
12723 && strcmp (segname, ".sbss") != 0
12724 && strncmp (segname, ".sdata.", 7) != 0
12725 && strncmp (segname, ".gnu.linkonce.s.", 16) != 0);
12730 /* We are not optimizing for the $gp register. */
12735 /* Return true if the given symbol should be considered local for SVR4 PIC. */
12738 pic_need_relax (sym, segtype)
12743 bfd_boolean linkonce;
12745 /* Handle the case of a symbol equated to another symbol. */
12746 while (symbol_equated_reloc_p (sym))
12750 /* It's possible to get a loop here in a badly written
12752 n = symbol_get_value_expression (sym)->X_add_symbol;
12758 symsec = S_GET_SEGMENT (sym);
12760 /* duplicate the test for LINK_ONCE sections as in adjust_reloc_syms */
12762 if (symsec != segtype && ! S_IS_LOCAL (sym))
12764 if ((bfd_get_section_flags (stdoutput, symsec) & SEC_LINK_ONCE)
12768 /* The GNU toolchain uses an extension for ELF: a section
12769 beginning with the magic string .gnu.linkonce is a linkonce
12771 if (strncmp (segment_name (symsec), ".gnu.linkonce",
12772 sizeof ".gnu.linkonce" - 1) == 0)
12776 /* This must duplicate the test in adjust_reloc_syms. */
12777 return (symsec != &bfd_und_section
12778 && symsec != &bfd_abs_section
12779 && ! bfd_is_com_section (symsec)
12782 /* A global or weak symbol is treated as external. */
12783 && (OUTPUT_FLAVOR != bfd_target_elf_flavour
12784 || (! S_IS_WEAK (sym)
12785 && (! S_IS_EXTERNAL (sym)
12786 || mips_pic == EMBEDDED_PIC)))
12792 /* Given a mips16 variant frag FRAGP, return non-zero if it needs an
12793 extended opcode. SEC is the section the frag is in. */
12796 mips16_extended_frag (fragp, sec, stretch)
12802 register const struct mips16_immed_operand *op;
12804 int mintiny, maxtiny;
12808 if (RELAX_MIPS16_USER_SMALL (fragp->fr_subtype))
12810 if (RELAX_MIPS16_USER_EXT (fragp->fr_subtype))
12813 type = RELAX_MIPS16_TYPE (fragp->fr_subtype);
12814 op = mips16_immed_operands;
12815 while (op->type != type)
12818 assert (op < mips16_immed_operands + MIPS16_NUM_IMMED);
12823 if (type == '<' || type == '>' || type == '[' || type == ']')
12826 maxtiny = 1 << op->nbits;
12831 maxtiny = (1 << op->nbits) - 1;
12836 mintiny = - (1 << (op->nbits - 1));
12837 maxtiny = (1 << (op->nbits - 1)) - 1;
12840 sym_frag = symbol_get_frag (fragp->fr_symbol);
12841 val = S_GET_VALUE (fragp->fr_symbol);
12842 symsec = S_GET_SEGMENT (fragp->fr_symbol);
12848 /* We won't have the section when we are called from
12849 mips_relax_frag. However, we will always have been called
12850 from md_estimate_size_before_relax first. If this is a
12851 branch to a different section, we mark it as such. If SEC is
12852 NULL, and the frag is not marked, then it must be a branch to
12853 the same section. */
12856 if (RELAX_MIPS16_LONG_BRANCH (fragp->fr_subtype))
12861 /* Must have been called from md_estimate_size_before_relax. */
12864 fragp->fr_subtype =
12865 RELAX_MIPS16_MARK_LONG_BRANCH (fragp->fr_subtype);
12867 /* FIXME: We should support this, and let the linker
12868 catch branches and loads that are out of range. */
12869 as_bad_where (fragp->fr_file, fragp->fr_line,
12870 _("unsupported PC relative reference to different section"));
12874 if (fragp != sym_frag && sym_frag->fr_address == 0)
12875 /* Assume non-extended on the first relaxation pass.
12876 The address we have calculated will be bogus if this is
12877 a forward branch to another frag, as the forward frag
12878 will have fr_address == 0. */
12882 /* In this case, we know for sure that the symbol fragment is in
12883 the same section. If the relax_marker of the symbol fragment
12884 differs from the relax_marker of this fragment, we have not
12885 yet adjusted the symbol fragment fr_address. We want to add
12886 in STRETCH in order to get a better estimate of the address.
12887 This particularly matters because of the shift bits. */
12889 && sym_frag->relax_marker != fragp->relax_marker)
12893 /* Adjust stretch for any alignment frag. Note that if have
12894 been expanding the earlier code, the symbol may be
12895 defined in what appears to be an earlier frag. FIXME:
12896 This doesn't handle the fr_subtype field, which specifies
12897 a maximum number of bytes to skip when doing an
12899 for (f = fragp; f != NULL && f != sym_frag; f = f->fr_next)
12901 if (f->fr_type == rs_align || f->fr_type == rs_align_code)
12904 stretch = - ((- stretch)
12905 & ~ ((1 << (int) f->fr_offset) - 1));
12907 stretch &= ~ ((1 << (int) f->fr_offset) - 1);
12916 addr = fragp->fr_address + fragp->fr_fix;
12918 /* The base address rules are complicated. The base address of
12919 a branch is the following instruction. The base address of a
12920 PC relative load or add is the instruction itself, but if it
12921 is in a delay slot (in which case it can not be extended) use
12922 the address of the instruction whose delay slot it is in. */
12923 if (type == 'p' || type == 'q')
12927 /* If we are currently assuming that this frag should be
12928 extended, then, the current address is two bytes
12930 if (RELAX_MIPS16_EXTENDED (fragp->fr_subtype))
12933 /* Ignore the low bit in the target, since it will be set
12934 for a text label. */
12935 if ((val & 1) != 0)
12938 else if (RELAX_MIPS16_JAL_DSLOT (fragp->fr_subtype))
12940 else if (RELAX_MIPS16_DSLOT (fragp->fr_subtype))
12943 val -= addr & ~ ((1 << op->shift) - 1);
12945 /* Branch offsets have an implicit 0 in the lowest bit. */
12946 if (type == 'p' || type == 'q')
12949 /* If any of the shifted bits are set, we must use an extended
12950 opcode. If the address depends on the size of this
12951 instruction, this can lead to a loop, so we arrange to always
12952 use an extended opcode. We only check this when we are in
12953 the main relaxation loop, when SEC is NULL. */
12954 if ((val & ((1 << op->shift) - 1)) != 0 && sec == NULL)
12956 fragp->fr_subtype =
12957 RELAX_MIPS16_MARK_LONG_BRANCH (fragp->fr_subtype);
12961 /* If we are about to mark a frag as extended because the value
12962 is precisely maxtiny + 1, then there is a chance of an
12963 infinite loop as in the following code:
12968 In this case when the la is extended, foo is 0x3fc bytes
12969 away, so the la can be shrunk, but then foo is 0x400 away, so
12970 the la must be extended. To avoid this loop, we mark the
12971 frag as extended if it was small, and is about to become
12972 extended with a value of maxtiny + 1. */
12973 if (val == ((maxtiny + 1) << op->shift)
12974 && ! RELAX_MIPS16_EXTENDED (fragp->fr_subtype)
12977 fragp->fr_subtype =
12978 RELAX_MIPS16_MARK_LONG_BRANCH (fragp->fr_subtype);
12982 else if (symsec != absolute_section && sec != NULL)
12983 as_bad_where (fragp->fr_file, fragp->fr_line, _("unsupported relocation"));
12985 if ((val & ((1 << op->shift) - 1)) != 0
12986 || val < (mintiny << op->shift)
12987 || val > (maxtiny << op->shift))
12993 /* Compute the length of a branch sequence, and adjust the
12994 RELAX_BRANCH_TOOFAR bit accordingly. If FRAGP is NULL, the
12995 worst-case length is computed, with UPDATE being used to indicate
12996 whether an unconditional (-1), branch-likely (+1) or regular (0)
12997 branch is to be computed. */
12999 relaxed_branch_length (fragp, sec, update)
13004 bfd_boolean toofar;
13008 && S_IS_DEFINED (fragp->fr_symbol)
13009 && sec == S_GET_SEGMENT (fragp->fr_symbol))
13014 val = S_GET_VALUE (fragp->fr_symbol) + fragp->fr_offset;
13016 addr = fragp->fr_address + fragp->fr_fix + 4;
13020 toofar = val < - (0x8000 << 2) || val >= (0x8000 << 2);
13023 /* If the symbol is not defined or it's in a different segment,
13024 assume the user knows what's going on and emit a short
13030 if (fragp && update && toofar != RELAX_BRANCH_TOOFAR (fragp->fr_subtype))
13032 = RELAX_BRANCH_ENCODE (RELAX_BRANCH_UNCOND (fragp->fr_subtype),
13033 RELAX_BRANCH_LIKELY (fragp->fr_subtype),
13034 RELAX_BRANCH_LINK (fragp->fr_subtype),
13040 if (fragp ? RELAX_BRANCH_LIKELY (fragp->fr_subtype) : (update > 0))
13043 if (mips_pic != NO_PIC)
13045 /* Additional space for PIC loading of target address. */
13047 if (mips_opts.isa == ISA_MIPS1)
13048 /* Additional space for $at-stabilizing nop. */
13052 /* If branch is conditional. */
13053 if (fragp ? !RELAX_BRANCH_UNCOND (fragp->fr_subtype) : (update >= 0))
13060 /* Estimate the size of a frag before relaxing. Unless this is the
13061 mips16, we are not really relaxing here, and the final size is
13062 encoded in the subtype information. For the mips16, we have to
13063 decide whether we are using an extended opcode or not. */
13066 md_estimate_size_before_relax (fragp, segtype)
13072 if (RELAX_BRANCH_P (fragp->fr_subtype))
13075 fragp->fr_var = relaxed_branch_length (fragp, segtype, FALSE);
13077 return fragp->fr_var;
13080 if (RELAX_MIPS16_P (fragp->fr_subtype))
13081 /* We don't want to modify the EXTENDED bit here; it might get us
13082 into infinite loops. We change it only in mips_relax_frag(). */
13083 return (RELAX_MIPS16_EXTENDED (fragp->fr_subtype) ? 4 : 2);
13085 if (mips_pic == NO_PIC)
13086 change = nopic_need_relax (fragp->fr_symbol, 0);
13087 else if (mips_pic == SVR4_PIC)
13088 change = pic_need_relax (fragp->fr_symbol, segtype);
13094 /* Record the offset to the first reloc in the fr_opcode field.
13095 This lets md_convert_frag and tc_gen_reloc know that the code
13096 must be expanded. */
13097 fragp->fr_opcode = (fragp->fr_literal
13099 - RELAX_OLD (fragp->fr_subtype)
13100 + RELAX_RELOC1 (fragp->fr_subtype));
13101 /* FIXME: This really needs as_warn_where. */
13102 if (RELAX_WARN (fragp->fr_subtype))
13103 as_warn (_("AT used after \".set noat\" or macro used after "
13104 "\".set nomacro\""));
13106 return RELAX_NEW (fragp->fr_subtype) - RELAX_OLD (fragp->fr_subtype);
13112 /* This is called to see whether a reloc against a defined symbol
13113 should be converted into a reloc against a section. Don't adjust
13114 MIPS16 jump relocations, so we don't have to worry about the format
13115 of the offset in the .o file. Don't adjust relocations against
13116 mips16 symbols, so that the linker can find them if it needs to set
13120 mips_fix_adjustable (fixp)
13123 if (fixp->fx_r_type == BFD_RELOC_MIPS16_JMP)
13126 if (fixp->fx_r_type == BFD_RELOC_VTABLE_INHERIT
13127 || fixp->fx_r_type == BFD_RELOC_VTABLE_ENTRY)
13130 if (fixp->fx_addsy == NULL)
13134 if (OUTPUT_FLAVOR == bfd_target_elf_flavour
13135 && S_GET_OTHER (fixp->fx_addsy) == STO_MIPS16
13136 && fixp->fx_subsy == NULL)
13143 /* Translate internal representation of relocation info to BFD target
13147 tc_gen_reloc (section, fixp)
13148 asection *section ATTRIBUTE_UNUSED;
13151 static arelent *retval[4];
13153 bfd_reloc_code_real_type code;
13155 reloc = retval[0] = (arelent *) xmalloc (sizeof (arelent));
13158 reloc->sym_ptr_ptr = (asymbol **) xmalloc (sizeof (asymbol *));
13159 *reloc->sym_ptr_ptr = symbol_get_bfdsym (fixp->fx_addsy);
13160 reloc->address = fixp->fx_frag->fr_address + fixp->fx_where;
13162 if (mips_pic == EMBEDDED_PIC
13163 && SWITCH_TABLE (fixp))
13165 /* For a switch table entry we use a special reloc. The addend
13166 is actually the difference between the reloc address and the
13168 reloc->addend = reloc->address - S_GET_VALUE (fixp->fx_subsy);
13169 if (OUTPUT_FLAVOR != bfd_target_ecoff_flavour)
13170 as_fatal (_("Double check fx_r_type in tc-mips.c:tc_gen_reloc"));
13171 fixp->fx_r_type = BFD_RELOC_GPREL32;
13173 else if (fixp->fx_r_type == BFD_RELOC_PCREL_LO16)
13175 if (OUTPUT_FLAVOR == bfd_target_elf_flavour)
13176 reloc->addend = fixp->fx_addnumber;
13179 /* We use a special addend for an internal RELLO reloc. */
13180 if (symbol_section_p (fixp->fx_addsy))
13181 reloc->addend = reloc->address - S_GET_VALUE (fixp->fx_subsy);
13183 reloc->addend = fixp->fx_addnumber + reloc->address;
13186 else if (fixp->fx_r_type == BFD_RELOC_PCREL_HI16_S)
13188 assert (fixp->fx_next != NULL
13189 && fixp->fx_next->fx_r_type == BFD_RELOC_PCREL_LO16);
13191 /* The reloc is relative to the RELLO; adjust the addend
13193 if (OUTPUT_FLAVOR == bfd_target_elf_flavour)
13194 reloc->addend = fixp->fx_next->fx_addnumber;
13197 /* We use a special addend for an internal RELHI reloc. */
13198 if (symbol_section_p (fixp->fx_addsy))
13199 reloc->addend = (fixp->fx_next->fx_frag->fr_address
13200 + fixp->fx_next->fx_where
13201 - S_GET_VALUE (fixp->fx_subsy));
13203 reloc->addend = (fixp->fx_addnumber
13204 + fixp->fx_next->fx_frag->fr_address
13205 + fixp->fx_next->fx_where);
13208 else if (fixp->fx_pcrel == 0 || OUTPUT_FLAVOR == bfd_target_elf_flavour)
13209 reloc->addend = fixp->fx_addnumber;
13212 if (OUTPUT_FLAVOR != bfd_target_aout_flavour)
13213 /* A gruesome hack which is a result of the gruesome gas reloc
13215 reloc->addend = reloc->address;
13217 reloc->addend = -reloc->address;
13220 /* If this is a variant frag, we may need to adjust the existing
13221 reloc and generate a new one. */
13222 if (fixp->fx_frag->fr_opcode != NULL
13223 && ((fixp->fx_r_type == BFD_RELOC_GPREL16
13225 || fixp->fx_r_type == BFD_RELOC_MIPS_GOT16
13226 || fixp->fx_r_type == BFD_RELOC_MIPS_CALL16
13227 || fixp->fx_r_type == BFD_RELOC_MIPS_GOT_HI16
13228 || fixp->fx_r_type == BFD_RELOC_MIPS_GOT_LO16
13229 || fixp->fx_r_type == BFD_RELOC_MIPS_CALL_HI16
13230 || fixp->fx_r_type == BFD_RELOC_MIPS_CALL_LO16)
13235 assert (! RELAX_MIPS16_P (fixp->fx_frag->fr_subtype));
13237 /* If this is not the last reloc in this frag, then we have two
13238 GPREL relocs, or a GOT_HI16/GOT_LO16 pair, or a
13239 CALL_HI16/CALL_LO16, both of which are being replaced. Let
13240 the second one handle all of them. */
13241 if (fixp->fx_next != NULL
13242 && fixp->fx_frag == fixp->fx_next->fx_frag)
13244 assert ((fixp->fx_r_type == BFD_RELOC_GPREL16
13245 && fixp->fx_next->fx_r_type == BFD_RELOC_GPREL16)
13246 || (fixp->fx_r_type == BFD_RELOC_MIPS_GOT_HI16
13247 && (fixp->fx_next->fx_r_type
13248 == BFD_RELOC_MIPS_GOT_LO16))
13249 || (fixp->fx_r_type == BFD_RELOC_MIPS_CALL_HI16
13250 && (fixp->fx_next->fx_r_type
13251 == BFD_RELOC_MIPS_CALL_LO16)));
13256 fixp->fx_where = fixp->fx_frag->fr_opcode - fixp->fx_frag->fr_literal;
13257 reloc->address = fixp->fx_frag->fr_address + fixp->fx_where;
13258 reloc2 = retval[1] = (arelent *) xmalloc (sizeof (arelent));
13260 reloc2->sym_ptr_ptr = (asymbol **) xmalloc (sizeof (asymbol *));
13261 *reloc2->sym_ptr_ptr = symbol_get_bfdsym (fixp->fx_addsy);
13262 reloc2->address = (reloc->address
13263 + (RELAX_RELOC2 (fixp->fx_frag->fr_subtype)
13264 - RELAX_RELOC1 (fixp->fx_frag->fr_subtype)));
13265 reloc2->addend = fixp->fx_addnumber;
13266 reloc2->howto = bfd_reloc_type_lookup (stdoutput, BFD_RELOC_LO16);
13267 assert (reloc2->howto != NULL);
13269 if (RELAX_RELOC3 (fixp->fx_frag->fr_subtype))
13273 reloc3 = retval[2] = (arelent *) xmalloc (sizeof (arelent));
13276 reloc3->address += 4;
13279 if (mips_pic == NO_PIC)
13281 assert (fixp->fx_r_type == BFD_RELOC_GPREL16);
13282 fixp->fx_r_type = BFD_RELOC_HI16_S;
13284 else if (mips_pic == SVR4_PIC)
13286 switch (fixp->fx_r_type)
13290 case BFD_RELOC_MIPS_GOT16:
13292 case BFD_RELOC_MIPS_GOT_LO16:
13293 case BFD_RELOC_MIPS_CALL_LO16:
13294 fixp->fx_r_type = BFD_RELOC_MIPS_GOT16;
13296 case BFD_RELOC_MIPS_CALL16:
13299 /* BFD_RELOC_MIPS_GOT16;*/
13300 fixp->fx_r_type = BFD_RELOC_MIPS_GOT_PAGE;
13301 reloc2->howto = bfd_reloc_type_lookup
13302 (stdoutput, BFD_RELOC_MIPS_GOT_OFST);
13305 fixp->fx_r_type = BFD_RELOC_MIPS_GOT16;
13312 /* newabi uses R_MIPS_GOT_DISP for local symbols */
13313 if (HAVE_NEWABI && fixp->fx_r_type == BFD_RELOC_MIPS_GOT_LO16)
13315 fixp->fx_r_type = BFD_RELOC_MIPS_GOT_DISP;
13320 /* Since the old MIPS ELF ABI uses Rel instead of Rela, encode the vtable
13321 entry to be used in the relocation's section offset. */
13322 if (! HAVE_NEWABI && fixp->fx_r_type == BFD_RELOC_VTABLE_ENTRY)
13324 reloc->address = reloc->addend;
13328 /* Since DIFF_EXPR_OK is defined in tc-mips.h, it is possible that
13329 fixup_segment converted a non-PC relative reloc into a PC
13330 relative reloc. In such a case, we need to convert the reloc
13332 code = fixp->fx_r_type;
13333 if (fixp->fx_pcrel)
13338 code = BFD_RELOC_8_PCREL;
13341 code = BFD_RELOC_16_PCREL;
13344 code = BFD_RELOC_32_PCREL;
13347 code = BFD_RELOC_64_PCREL;
13349 case BFD_RELOC_8_PCREL:
13350 case BFD_RELOC_16_PCREL:
13351 case BFD_RELOC_32_PCREL:
13352 case BFD_RELOC_64_PCREL:
13353 case BFD_RELOC_16_PCREL_S2:
13354 case BFD_RELOC_PCREL_HI16_S:
13355 case BFD_RELOC_PCREL_LO16:
13358 as_bad_where (fixp->fx_file, fixp->fx_line,
13359 _("Cannot make %s relocation PC relative"),
13360 bfd_get_reloc_code_name (code));
13365 /* md_apply_fix3 has a double-subtraction hack to get
13366 bfd_install_relocation to behave nicely. GPREL relocations are
13367 handled correctly without this hack, so undo it here. We can't
13368 stop md_apply_fix3 from subtracting twice in the first place since
13369 the fake addend is required for variant frags above. */
13370 if (fixp->fx_addsy != NULL && OUTPUT_FLAVOR == bfd_target_elf_flavour
13371 && (code == BFD_RELOC_GPREL16 || code == BFD_RELOC_MIPS16_GPREL)
13372 && reloc->addend != 0
13373 && mips_need_elf_addend_fixup (fixp))
13374 reloc->addend += S_GET_VALUE (fixp->fx_addsy);
13377 /* To support a PC relative reloc when generating embedded PIC code
13378 for ECOFF, we use a Cygnus extension. We check for that here to
13379 make sure that we don't let such a reloc escape normally. */
13380 if ((OUTPUT_FLAVOR == bfd_target_ecoff_flavour
13381 || OUTPUT_FLAVOR == bfd_target_elf_flavour)
13382 && code == BFD_RELOC_16_PCREL_S2
13383 && mips_pic != EMBEDDED_PIC)
13384 reloc->howto = NULL;
13386 reloc->howto = bfd_reloc_type_lookup (stdoutput, code);
13388 if (reloc->howto == NULL)
13390 as_bad_where (fixp->fx_file, fixp->fx_line,
13391 _("Can not represent %s relocation in this object file format"),
13392 bfd_get_reloc_code_name (code));
13399 /* Relax a machine dependent frag. This returns the amount by which
13400 the current size of the frag should change. */
13403 mips_relax_frag (sec, fragp, stretch)
13408 if (RELAX_BRANCH_P (fragp->fr_subtype))
13410 offsetT old_var = fragp->fr_var;
13412 fragp->fr_var = relaxed_branch_length (fragp, sec, TRUE);
13414 return fragp->fr_var - old_var;
13417 if (! RELAX_MIPS16_P (fragp->fr_subtype))
13420 if (mips16_extended_frag (fragp, NULL, stretch))
13422 if (RELAX_MIPS16_EXTENDED (fragp->fr_subtype))
13424 fragp->fr_subtype = RELAX_MIPS16_MARK_EXTENDED (fragp->fr_subtype);
13429 if (! RELAX_MIPS16_EXTENDED (fragp->fr_subtype))
13431 fragp->fr_subtype = RELAX_MIPS16_CLEAR_EXTENDED (fragp->fr_subtype);
13438 /* Convert a machine dependent frag. */
13441 md_convert_frag (abfd, asec, fragp)
13442 bfd *abfd ATTRIBUTE_UNUSED;
13449 if (RELAX_BRANCH_P (fragp->fr_subtype))
13452 unsigned long insn;
13456 buf = (bfd_byte *)fragp->fr_literal + fragp->fr_fix;
13458 if (target_big_endian)
13459 insn = bfd_getb32 (buf);
13461 insn = bfd_getl32 (buf);
13463 if (!RELAX_BRANCH_TOOFAR (fragp->fr_subtype))
13465 /* We generate a fixup instead of applying it right now
13466 because, if there are linker relaxations, we're going to
13467 need the relocations. */
13468 exp.X_op = O_symbol;
13469 exp.X_add_symbol = fragp->fr_symbol;
13470 exp.X_add_number = fragp->fr_offset;
13472 fixp = fix_new_exp (fragp, buf - (bfd_byte *)fragp->fr_literal,
13474 BFD_RELOC_16_PCREL_S2);
13475 fixp->fx_file = fragp->fr_file;
13476 fixp->fx_line = fragp->fr_line;
13478 md_number_to_chars ((char *)buf, insn, 4);
13485 as_warn_where (fragp->fr_file, fragp->fr_line,
13486 _("relaxed out-of-range branch into a jump"));
13488 if (RELAX_BRANCH_UNCOND (fragp->fr_subtype))
13491 if (!RELAX_BRANCH_LIKELY (fragp->fr_subtype))
13493 /* Reverse the branch. */
13494 switch ((insn >> 28) & 0xf)
13497 /* bc[0-3][tf]l? and bc1any[24][ft] instructions can
13498 have the condition reversed by tweaking a single
13499 bit, and their opcodes all have 0x4???????. */
13500 assert ((insn & 0xf1000000) == 0x41000000);
13501 insn ^= 0x00010000;
13505 /* bltz 0x04000000 bgez 0x04010000
13506 bltzal 0x04100000 bgezal 0x04110000 */
13507 assert ((insn & 0xfc0e0000) == 0x04000000);
13508 insn ^= 0x00010000;
13512 /* beq 0x10000000 bne 0x14000000
13513 blez 0x18000000 bgtz 0x1c000000 */
13514 insn ^= 0x04000000;
13522 if (RELAX_BRANCH_LINK (fragp->fr_subtype))
13524 /* Clear the and-link bit. */
13525 assert ((insn & 0xfc1c0000) == 0x04100000);
13527 /* bltzal 0x04100000 bgezal 0x04110000
13528 bltzall 0x04120000 bgezall 0x04130000 */
13529 insn &= ~0x00100000;
13532 /* Branch over the branch (if the branch was likely) or the
13533 full jump (not likely case). Compute the offset from the
13534 current instruction to branch to. */
13535 if (RELAX_BRANCH_LIKELY (fragp->fr_subtype))
13539 /* How many bytes in instructions we've already emitted? */
13540 i = buf - (bfd_byte *)fragp->fr_literal - fragp->fr_fix;
13541 /* How many bytes in instructions from here to the end? */
13542 i = fragp->fr_var - i;
13544 /* Convert to instruction count. */
13546 /* Branch counts from the next instruction. */
13549 /* Branch over the jump. */
13550 md_number_to_chars ((char *)buf, insn, 4);
13554 md_number_to_chars ((char*)buf, 0, 4);
13557 if (RELAX_BRANCH_LIKELY (fragp->fr_subtype))
13559 /* beql $0, $0, 2f */
13561 /* Compute the PC offset from the current instruction to
13562 the end of the variable frag. */
13563 /* How many bytes in instructions we've already emitted? */
13564 i = buf - (bfd_byte *)fragp->fr_literal - fragp->fr_fix;
13565 /* How many bytes in instructions from here to the end? */
13566 i = fragp->fr_var - i;
13567 /* Convert to instruction count. */
13569 /* Don't decrement i, because we want to branch over the
13573 md_number_to_chars ((char *)buf, insn, 4);
13576 md_number_to_chars ((char *)buf, 0, 4);
13581 if (mips_pic == NO_PIC)
13584 insn = (RELAX_BRANCH_LINK (fragp->fr_subtype)
13585 ? 0x0c000000 : 0x08000000);
13586 exp.X_op = O_symbol;
13587 exp.X_add_symbol = fragp->fr_symbol;
13588 exp.X_add_number = fragp->fr_offset;
13590 fixp = fix_new_exp (fragp, buf - (bfd_byte *)fragp->fr_literal,
13591 4, &exp, 0, BFD_RELOC_MIPS_JMP);
13592 fixp->fx_file = fragp->fr_file;
13593 fixp->fx_line = fragp->fr_line;
13595 md_number_to_chars ((char*)buf, insn, 4);
13600 /* lw/ld $at, <sym>($gp) R_MIPS_GOT16 */
13601 insn = HAVE_64BIT_ADDRESSES ? 0xdf810000 : 0x8f810000;
13602 exp.X_op = O_symbol;
13603 exp.X_add_symbol = fragp->fr_symbol;
13604 exp.X_add_number = fragp->fr_offset;
13606 if (fragp->fr_offset)
13608 exp.X_add_symbol = make_expr_symbol (&exp);
13609 exp.X_add_number = 0;
13612 fixp = fix_new_exp (fragp, buf - (bfd_byte *)fragp->fr_literal,
13613 4, &exp, 0, BFD_RELOC_MIPS_GOT16);
13614 fixp->fx_file = fragp->fr_file;
13615 fixp->fx_line = fragp->fr_line;
13617 md_number_to_chars ((char*)buf, insn, 4);
13620 if (mips_opts.isa == ISA_MIPS1)
13623 md_number_to_chars ((char*)buf, 0, 4);
13627 /* d/addiu $at, $at, <sym> R_MIPS_LO16 */
13628 insn = HAVE_64BIT_ADDRESSES ? 0x64210000 : 0x24210000;
13630 fixp = fix_new_exp (fragp, buf - (bfd_byte *)fragp->fr_literal,
13631 4, &exp, 0, BFD_RELOC_LO16);
13632 fixp->fx_file = fragp->fr_file;
13633 fixp->fx_line = fragp->fr_line;
13635 md_number_to_chars ((char*)buf, insn, 4);
13639 if (RELAX_BRANCH_LINK (fragp->fr_subtype))
13644 md_number_to_chars ((char*)buf, insn, 4);
13649 assert (buf == (bfd_byte *)fragp->fr_literal
13650 + fragp->fr_fix + fragp->fr_var);
13652 fragp->fr_fix += fragp->fr_var;
13657 if (RELAX_MIPS16_P (fragp->fr_subtype))
13660 register const struct mips16_immed_operand *op;
13661 bfd_boolean small, ext;
13664 unsigned long insn;
13665 bfd_boolean use_extend;
13666 unsigned short extend;
13668 type = RELAX_MIPS16_TYPE (fragp->fr_subtype);
13669 op = mips16_immed_operands;
13670 while (op->type != type)
13673 if (RELAX_MIPS16_EXTENDED (fragp->fr_subtype))
13684 resolve_symbol_value (fragp->fr_symbol);
13685 val = S_GET_VALUE (fragp->fr_symbol);
13690 addr = fragp->fr_address + fragp->fr_fix;
13692 /* The rules for the base address of a PC relative reloc are
13693 complicated; see mips16_extended_frag. */
13694 if (type == 'p' || type == 'q')
13699 /* Ignore the low bit in the target, since it will be
13700 set for a text label. */
13701 if ((val & 1) != 0)
13704 else if (RELAX_MIPS16_JAL_DSLOT (fragp->fr_subtype))
13706 else if (RELAX_MIPS16_DSLOT (fragp->fr_subtype))
13709 addr &= ~ (addressT) ((1 << op->shift) - 1);
13712 /* Make sure the section winds up with the alignment we have
13715 record_alignment (asec, op->shift);
13719 && (RELAX_MIPS16_JAL_DSLOT (fragp->fr_subtype)
13720 || RELAX_MIPS16_DSLOT (fragp->fr_subtype)))
13721 as_warn_where (fragp->fr_file, fragp->fr_line,
13722 _("extended instruction in delay slot"));
13724 buf = (bfd_byte *) (fragp->fr_literal + fragp->fr_fix);
13726 if (target_big_endian)
13727 insn = bfd_getb16 (buf);
13729 insn = bfd_getl16 (buf);
13731 mips16_immed (fragp->fr_file, fragp->fr_line, type, val,
13732 RELAX_MIPS16_USER_EXT (fragp->fr_subtype),
13733 small, ext, &insn, &use_extend, &extend);
13737 md_number_to_chars ((char *) buf, 0xf000 | extend, 2);
13738 fragp->fr_fix += 2;
13742 md_number_to_chars ((char *) buf, insn, 2);
13743 fragp->fr_fix += 2;
13748 if (fragp->fr_opcode == NULL)
13751 old = RELAX_OLD (fragp->fr_subtype);
13752 new = RELAX_NEW (fragp->fr_subtype);
13753 fixptr = fragp->fr_literal + fragp->fr_fix;
13756 memcpy (fixptr - old, fixptr, new);
13758 fragp->fr_fix += new - old;
13764 /* This function is called after the relocs have been generated.
13765 We've been storing mips16 text labels as odd. Here we convert them
13766 back to even for the convenience of the debugger. */
13769 mips_frob_file_after_relocs ()
13772 unsigned int count, i;
13774 if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
13777 syms = bfd_get_outsymbols (stdoutput);
13778 count = bfd_get_symcount (stdoutput);
13779 for (i = 0; i < count; i++, syms++)
13781 if (elf_symbol (*syms)->internal_elf_sym.st_other == STO_MIPS16
13782 && ((*syms)->value & 1) != 0)
13784 (*syms)->value &= ~1;
13785 /* If the symbol has an odd size, it was probably computed
13786 incorrectly, so adjust that as well. */
13787 if ((elf_symbol (*syms)->internal_elf_sym.st_size & 1) != 0)
13788 ++elf_symbol (*syms)->internal_elf_sym.st_size;
13795 /* This function is called whenever a label is defined. It is used
13796 when handling branch delays; if a branch has a label, we assume we
13797 can not move it. */
13800 mips_define_label (sym)
13803 struct insn_label_list *l;
13805 if (free_insn_labels == NULL)
13806 l = (struct insn_label_list *) xmalloc (sizeof *l);
13809 l = free_insn_labels;
13810 free_insn_labels = l->next;
13814 l->next = insn_labels;
13818 #if defined (OBJ_ELF) || defined (OBJ_MAYBE_ELF)
13820 /* Some special processing for a MIPS ELF file. */
13823 mips_elf_final_processing ()
13825 /* Write out the register information. */
13826 if (mips_abi != N64_ABI)
13830 s.ri_gprmask = mips_gprmask;
13831 s.ri_cprmask[0] = mips_cprmask[0];
13832 s.ri_cprmask[1] = mips_cprmask[1];
13833 s.ri_cprmask[2] = mips_cprmask[2];
13834 s.ri_cprmask[3] = mips_cprmask[3];
13835 /* The gp_value field is set by the MIPS ELF backend. */
13837 bfd_mips_elf32_swap_reginfo_out (stdoutput, &s,
13838 ((Elf32_External_RegInfo *)
13839 mips_regmask_frag));
13843 Elf64_Internal_RegInfo s;
13845 s.ri_gprmask = mips_gprmask;
13847 s.ri_cprmask[0] = mips_cprmask[0];
13848 s.ri_cprmask[1] = mips_cprmask[1];
13849 s.ri_cprmask[2] = mips_cprmask[2];
13850 s.ri_cprmask[3] = mips_cprmask[3];
13851 /* The gp_value field is set by the MIPS ELF backend. */
13853 bfd_mips_elf64_swap_reginfo_out (stdoutput, &s,
13854 ((Elf64_External_RegInfo *)
13855 mips_regmask_frag));
13858 /* Set the MIPS ELF flag bits. FIXME: There should probably be some
13859 sort of BFD interface for this. */
13860 if (mips_any_noreorder)
13861 elf_elfheader (stdoutput)->e_flags |= EF_MIPS_NOREORDER;
13862 if (mips_pic != NO_PIC)
13863 elf_elfheader (stdoutput)->e_flags |= EF_MIPS_PIC;
13865 /* Set MIPS ELF flags for ASEs. */
13866 if (file_ase_mips16)
13867 elf_elfheader (stdoutput)->e_flags |= EF_MIPS_ARCH_ASE_M16;
13868 #if 0 /* XXX FIXME */
13869 if (file_ase_mips3d)
13870 elf_elfheader (stdoutput)->e_flags |= ???;
13873 elf_elfheader (stdoutput)->e_flags |= EF_MIPS_ARCH_ASE_MDMX;
13875 /* Set the MIPS ELF ABI flags. */
13876 if (mips_abi == O32_ABI && USE_E_MIPS_ABI_O32)
13877 elf_elfheader (stdoutput)->e_flags |= E_MIPS_ABI_O32;
13878 else if (mips_abi == O64_ABI)
13879 elf_elfheader (stdoutput)->e_flags |= E_MIPS_ABI_O64;
13880 else if (mips_abi == EABI_ABI)
13882 if (!file_mips_gp32)
13883 elf_elfheader (stdoutput)->e_flags |= E_MIPS_ABI_EABI64;
13885 elf_elfheader (stdoutput)->e_flags |= E_MIPS_ABI_EABI32;
13887 else if (mips_abi == N32_ABI)
13888 elf_elfheader (stdoutput)->e_flags |= EF_MIPS_ABI2;
13890 /* Nothing to do for N64_ABI. */
13892 if (mips_32bitmode)
13893 elf_elfheader (stdoutput)->e_flags |= EF_MIPS_32BITMODE;
13896 #endif /* OBJ_ELF || OBJ_MAYBE_ELF */
13898 typedef struct proc {
13900 unsigned long reg_mask;
13901 unsigned long reg_offset;
13902 unsigned long fpreg_mask;
13903 unsigned long fpreg_offset;
13904 unsigned long frame_offset;
13905 unsigned long frame_reg;
13906 unsigned long pc_reg;
13909 static procS cur_proc;
13910 static procS *cur_proc_ptr;
13911 static int numprocs;
13913 /* Fill in an rs_align_code fragment. */
13916 mips_handle_align (fragp)
13919 if (fragp->fr_type != rs_align_code)
13922 if (mips_opts.mips16)
13924 static const unsigned char be_nop[] = { 0x65, 0x00 };
13925 static const unsigned char le_nop[] = { 0x00, 0x65 };
13930 bytes = fragp->fr_next->fr_address - fragp->fr_address - fragp->fr_fix;
13931 p = fragp->fr_literal + fragp->fr_fix;
13939 memcpy (p, (target_big_endian ? be_nop : le_nop), 2);
13943 /* For mips32, a nop is a zero, which we trivially get by doing nothing. */
13954 /* check for premature end, nesting errors, etc */
13956 as_warn (_("missing .end at end of assembly"));
13965 if (*input_line_pointer == '-')
13967 ++input_line_pointer;
13970 if (!ISDIGIT (*input_line_pointer))
13971 as_bad (_("expected simple number"));
13972 if (input_line_pointer[0] == '0')
13974 if (input_line_pointer[1] == 'x')
13976 input_line_pointer += 2;
13977 while (ISXDIGIT (*input_line_pointer))
13980 val |= hex_value (*input_line_pointer++);
13982 return negative ? -val : val;
13986 ++input_line_pointer;
13987 while (ISDIGIT (*input_line_pointer))
13990 val |= *input_line_pointer++ - '0';
13992 return negative ? -val : val;
13995 if (!ISDIGIT (*input_line_pointer))
13997 printf (_(" *input_line_pointer == '%c' 0x%02x\n"),
13998 *input_line_pointer, *input_line_pointer);
13999 as_warn (_("invalid number"));
14002 while (ISDIGIT (*input_line_pointer))
14005 val += *input_line_pointer++ - '0';
14007 return negative ? -val : val;
14010 /* The .file directive; just like the usual .file directive, but there
14011 is an initial number which is the ECOFF file index. In the non-ECOFF
14012 case .file implies DWARF-2. */
14016 int x ATTRIBUTE_UNUSED;
14018 static int first_file_directive = 0;
14020 if (ECOFF_DEBUGGING)
14029 filename = dwarf2_directive_file (0);
14031 /* Versions of GCC up to 3.1 start files with a ".file"
14032 directive even for stabs output. Make sure that this
14033 ".file" is handled. Note that you need a version of GCC
14034 after 3.1 in order to support DWARF-2 on MIPS. */
14035 if (filename != NULL && ! first_file_directive)
14037 (void) new_logical_line (filename, -1);
14038 s_app_file_string (filename);
14040 first_file_directive = 1;
14044 /* The .loc directive, implying DWARF-2. */
14048 int x ATTRIBUTE_UNUSED;
14050 if (!ECOFF_DEBUGGING)
14051 dwarf2_directive_loc (0);
14054 /* The .end directive. */
14058 int x ATTRIBUTE_UNUSED;
14063 /* Following functions need their own .frame and .cprestore directives. */
14064 mips_frame_reg_valid = 0;
14065 mips_cprestore_valid = 0;
14067 if (!is_end_of_line[(unsigned char) *input_line_pointer])
14070 demand_empty_rest_of_line ();
14075 #ifdef BFD_ASSEMBLER
14076 if ((bfd_get_section_flags (stdoutput, now_seg) & SEC_CODE) != 0)
14081 if (now_seg != data_section && now_seg != bss_section)
14088 as_warn (_(".end not in text section"));
14092 as_warn (_(".end directive without a preceding .ent directive."));
14093 demand_empty_rest_of_line ();
14099 assert (S_GET_NAME (p));
14100 if (strcmp (S_GET_NAME (p), S_GET_NAME (cur_proc_ptr->isym)))
14101 as_warn (_(".end symbol does not match .ent symbol."));
14103 if (debug_type == DEBUG_STABS)
14104 stabs_generate_asm_endfunc (S_GET_NAME (p),
14108 as_warn (_(".end directive missing or unknown symbol"));
14111 /* Generate a .pdr section. */
14112 if (OUTPUT_FLAVOR == bfd_target_elf_flavour && ! ECOFF_DEBUGGING)
14114 segT saved_seg = now_seg;
14115 subsegT saved_subseg = now_subseg;
14120 dot = frag_now_fix ();
14122 #ifdef md_flush_pending_output
14123 md_flush_pending_output ();
14127 subseg_set (pdr_seg, 0);
14129 /* Write the symbol. */
14130 exp.X_op = O_symbol;
14131 exp.X_add_symbol = p;
14132 exp.X_add_number = 0;
14133 emit_expr (&exp, 4);
14135 fragp = frag_more (7 * 4);
14137 md_number_to_chars (fragp, (valueT) cur_proc_ptr->reg_mask, 4);
14138 md_number_to_chars (fragp + 4, (valueT) cur_proc_ptr->reg_offset, 4);
14139 md_number_to_chars (fragp + 8, (valueT) cur_proc_ptr->fpreg_mask, 4);
14140 md_number_to_chars (fragp + 12, (valueT) cur_proc_ptr->fpreg_offset, 4);
14141 md_number_to_chars (fragp + 16, (valueT) cur_proc_ptr->frame_offset, 4);
14142 md_number_to_chars (fragp + 20, (valueT) cur_proc_ptr->frame_reg, 4);
14143 md_number_to_chars (fragp + 24, (valueT) cur_proc_ptr->pc_reg, 4);
14145 subseg_set (saved_seg, saved_subseg);
14147 #endif /* OBJ_ELF */
14149 cur_proc_ptr = NULL;
14152 /* The .aent and .ent directives. */
14161 symbolP = get_symbol ();
14162 if (*input_line_pointer == ',')
14163 ++input_line_pointer;
14164 SKIP_WHITESPACE ();
14165 if (ISDIGIT (*input_line_pointer)
14166 || *input_line_pointer == '-')
14169 #ifdef BFD_ASSEMBLER
14170 if ((bfd_get_section_flags (stdoutput, now_seg) & SEC_CODE) != 0)
14175 if (now_seg != data_section && now_seg != bss_section)
14182 as_warn (_(".ent or .aent not in text section."));
14184 if (!aent && cur_proc_ptr)
14185 as_warn (_("missing .end"));
14189 /* This function needs its own .frame and .cprestore directives. */
14190 mips_frame_reg_valid = 0;
14191 mips_cprestore_valid = 0;
14193 cur_proc_ptr = &cur_proc;
14194 memset (cur_proc_ptr, '\0', sizeof (procS));
14196 cur_proc_ptr->isym = symbolP;
14198 symbol_get_bfdsym (symbolP)->flags |= BSF_FUNCTION;
14202 if (debug_type == DEBUG_STABS)
14203 stabs_generate_asm_func (S_GET_NAME (symbolP),
14204 S_GET_NAME (symbolP));
14207 demand_empty_rest_of_line ();
14210 /* The .frame directive. If the mdebug section is present (IRIX 5 native)
14211 then ecoff.c (ecoff_directive_frame) is used. For embedded targets,
14212 s_mips_frame is used so that we can set the PDR information correctly.
14213 We can't use the ecoff routines because they make reference to the ecoff
14214 symbol table (in the mdebug section). */
14217 s_mips_frame (ignore)
14218 int ignore ATTRIBUTE_UNUSED;
14221 if (OUTPUT_FLAVOR == bfd_target_elf_flavour && ! ECOFF_DEBUGGING)
14225 if (cur_proc_ptr == (procS *) NULL)
14227 as_warn (_(".frame outside of .ent"));
14228 demand_empty_rest_of_line ();
14232 cur_proc_ptr->frame_reg = tc_get_register (1);
14234 SKIP_WHITESPACE ();
14235 if (*input_line_pointer++ != ','
14236 || get_absolute_expression_and_terminator (&val) != ',')
14238 as_warn (_("Bad .frame directive"));
14239 --input_line_pointer;
14240 demand_empty_rest_of_line ();
14244 cur_proc_ptr->frame_offset = val;
14245 cur_proc_ptr->pc_reg = tc_get_register (0);
14247 demand_empty_rest_of_line ();
14250 #endif /* OBJ_ELF */
14254 /* The .fmask and .mask directives. If the mdebug section is present
14255 (IRIX 5 native) then ecoff.c (ecoff_directive_mask) is used. For
14256 embedded targets, s_mips_mask is used so that we can set the PDR
14257 information correctly. We can't use the ecoff routines because they
14258 make reference to the ecoff symbol table (in the mdebug section). */
14261 s_mips_mask (reg_type)
14265 if (OUTPUT_FLAVOR == bfd_target_elf_flavour && ! ECOFF_DEBUGGING)
14269 if (cur_proc_ptr == (procS *) NULL)
14271 as_warn (_(".mask/.fmask outside of .ent"));
14272 demand_empty_rest_of_line ();
14276 if (get_absolute_expression_and_terminator (&mask) != ',')
14278 as_warn (_("Bad .mask/.fmask directive"));
14279 --input_line_pointer;
14280 demand_empty_rest_of_line ();
14284 off = get_absolute_expression ();
14286 if (reg_type == 'F')
14288 cur_proc_ptr->fpreg_mask = mask;
14289 cur_proc_ptr->fpreg_offset = off;
14293 cur_proc_ptr->reg_mask = mask;
14294 cur_proc_ptr->reg_offset = off;
14297 demand_empty_rest_of_line ();
14300 #endif /* OBJ_ELF */
14301 s_ignore (reg_type);
14304 /* The .loc directive. */
14315 assert (now_seg == text_section);
14317 lineno = get_number ();
14318 addroff = frag_now_fix ();
14320 symbolP = symbol_new ("", N_SLINE, addroff, frag_now);
14321 S_SET_TYPE (symbolP, N_SLINE);
14322 S_SET_OTHER (symbolP, 0);
14323 S_SET_DESC (symbolP, lineno);
14324 symbolP->sy_segment = now_seg;
14328 /* A table describing all the processors gas knows about. Names are
14329 matched in the order listed.
14331 To ease comparison, please keep this table in the same order as
14332 gcc's mips_cpu_info_table[]. */
14333 static const struct mips_cpu_info mips_cpu_info_table[] =
14335 /* Entries for generic ISAs */
14336 { "mips1", 1, ISA_MIPS1, CPU_R3000 },
14337 { "mips2", 1, ISA_MIPS2, CPU_R6000 },
14338 { "mips3", 1, ISA_MIPS3, CPU_R4000 },
14339 { "mips4", 1, ISA_MIPS4, CPU_R8000 },
14340 { "mips5", 1, ISA_MIPS5, CPU_MIPS5 },
14341 { "mips32", 1, ISA_MIPS32, CPU_MIPS32 },
14342 { "mips32r2", 1, ISA_MIPS32R2, CPU_MIPS32R2 },
14343 { "mips64", 1, ISA_MIPS64, CPU_MIPS64 },
14346 { "r3000", 0, ISA_MIPS1, CPU_R3000 },
14347 { "r2000", 0, ISA_MIPS1, CPU_R3000 },
14348 { "r3900", 0, ISA_MIPS1, CPU_R3900 },
14351 { "r6000", 0, ISA_MIPS2, CPU_R6000 },
14354 { "r4000", 0, ISA_MIPS3, CPU_R4000 },
14355 { "r4010", 0, ISA_MIPS2, CPU_R4010 },
14356 { "vr4100", 0, ISA_MIPS3, CPU_VR4100 },
14357 { "vr4111", 0, ISA_MIPS3, CPU_R4111 },
14358 { "vr4120", 0, ISA_MIPS3, CPU_VR4120 },
14359 { "vr4130", 0, ISA_MIPS3, CPU_VR4120 },
14360 { "vr4181", 0, ISA_MIPS3, CPU_R4111 },
14361 { "vr4300", 0, ISA_MIPS3, CPU_R4300 },
14362 { "r4400", 0, ISA_MIPS3, CPU_R4400 },
14363 { "r4600", 0, ISA_MIPS3, CPU_R4600 },
14364 { "orion", 0, ISA_MIPS3, CPU_R4600 },
14365 { "r4650", 0, ISA_MIPS3, CPU_R4650 },
14368 { "r8000", 0, ISA_MIPS4, CPU_R8000 },
14369 { "r10000", 0, ISA_MIPS4, CPU_R10000 },
14370 { "r12000", 0, ISA_MIPS4, CPU_R12000 },
14371 { "vr5000", 0, ISA_MIPS4, CPU_R5000 },
14372 { "vr5400", 0, ISA_MIPS4, CPU_VR5400 },
14373 { "vr5500", 0, ISA_MIPS4, CPU_VR5500 },
14374 { "rm5200", 0, ISA_MIPS4, CPU_R5000 },
14375 { "rm5230", 0, ISA_MIPS4, CPU_R5000 },
14376 { "rm5231", 0, ISA_MIPS4, CPU_R5000 },
14377 { "rm5261", 0, ISA_MIPS4, CPU_R5000 },
14378 { "rm5721", 0, ISA_MIPS4, CPU_R5000 },
14379 { "r7000", 0, ISA_MIPS4, CPU_R5000 },
14382 { "4kc", 0, ISA_MIPS32, CPU_MIPS32, },
14383 { "4km", 0, ISA_MIPS32, CPU_MIPS32 },
14384 { "4kp", 0, ISA_MIPS32, CPU_MIPS32 },
14387 { "5kc", 0, ISA_MIPS64, CPU_MIPS64 },
14388 { "20kc", 0, ISA_MIPS64, CPU_MIPS64 },
14390 /* Broadcom SB-1 CPU core */
14391 { "sb1", 0, ISA_MIPS64, CPU_SB1 },
14398 /* Return true if GIVEN is the same as CANONICAL, or if it is CANONICAL
14399 with a final "000" replaced by "k". Ignore case.
14401 Note: this function is shared between GCC and GAS. */
14404 mips_strict_matching_cpu_name_p (canonical, given)
14405 const char *canonical, *given;
14407 while (*given != 0 && TOLOWER (*given) == TOLOWER (*canonical))
14408 given++, canonical++;
14410 return ((*given == 0 && *canonical == 0)
14411 || (strcmp (canonical, "000") == 0 && strcasecmp (given, "k") == 0));
14415 /* Return true if GIVEN matches CANONICAL, where GIVEN is a user-supplied
14416 CPU name. We've traditionally allowed a lot of variation here.
14418 Note: this function is shared between GCC and GAS. */
14421 mips_matching_cpu_name_p (canonical, given)
14422 const char *canonical, *given;
14424 /* First see if the name matches exactly, or with a final "000"
14425 turned into "k". */
14426 if (mips_strict_matching_cpu_name_p (canonical, given))
14429 /* If not, try comparing based on numerical designation alone.
14430 See if GIVEN is an unadorned number, or 'r' followed by a number. */
14431 if (TOLOWER (*given) == 'r')
14433 if (!ISDIGIT (*given))
14436 /* Skip over some well-known prefixes in the canonical name,
14437 hoping to find a number there too. */
14438 if (TOLOWER (canonical[0]) == 'v' && TOLOWER (canonical[1]) == 'r')
14440 else if (TOLOWER (canonical[0]) == 'r' && TOLOWER (canonical[1]) == 'm')
14442 else if (TOLOWER (canonical[0]) == 'r')
14445 return mips_strict_matching_cpu_name_p (canonical, given);
14449 /* Parse an option that takes the name of a processor as its argument.
14450 OPTION is the name of the option and CPU_STRING is the argument.
14451 Return the corresponding processor enumeration if the CPU_STRING is
14452 recognized, otherwise report an error and return null.
14454 A similar function exists in GCC. */
14456 static const struct mips_cpu_info *
14457 mips_parse_cpu (option, cpu_string)
14458 const char *option, *cpu_string;
14460 const struct mips_cpu_info *p;
14462 /* 'from-abi' selects the most compatible architecture for the given
14463 ABI: MIPS I for 32-bit ABIs and MIPS III for 64-bit ABIs. For the
14464 EABIs, we have to decide whether we're using the 32-bit or 64-bit
14465 version. Look first at the -mgp options, if given, otherwise base
14466 the choice on MIPS_DEFAULT_64BIT.
14468 Treat NO_ABI like the EABIs. One reason to do this is that the
14469 plain 'mips' and 'mips64' configs have 'from-abi' as their default
14470 architecture. This code picks MIPS I for 'mips' and MIPS III for
14471 'mips64', just as we did in the days before 'from-abi'. */
14472 if (strcasecmp (cpu_string, "from-abi") == 0)
14474 if (ABI_NEEDS_32BIT_REGS (mips_abi))
14475 return mips_cpu_info_from_isa (ISA_MIPS1);
14477 if (ABI_NEEDS_64BIT_REGS (mips_abi))
14478 return mips_cpu_info_from_isa (ISA_MIPS3);
14480 if (file_mips_gp32 >= 0)
14481 return mips_cpu_info_from_isa (file_mips_gp32 ? ISA_MIPS1 : ISA_MIPS3);
14483 return mips_cpu_info_from_isa (MIPS_DEFAULT_64BIT
14488 /* 'default' has traditionally been a no-op. Probably not very useful. */
14489 if (strcasecmp (cpu_string, "default") == 0)
14492 for (p = mips_cpu_info_table; p->name != 0; p++)
14493 if (mips_matching_cpu_name_p (p->name, cpu_string))
14496 as_bad ("Bad value (%s) for %s", cpu_string, option);
14500 /* Return the canonical processor information for ISA (a member of the
14501 ISA_MIPS* enumeration). */
14503 static const struct mips_cpu_info *
14504 mips_cpu_info_from_isa (isa)
14509 for (i = 0; mips_cpu_info_table[i].name != NULL; i++)
14510 if (mips_cpu_info_table[i].is_isa
14511 && isa == mips_cpu_info_table[i].isa)
14512 return (&mips_cpu_info_table[i]);
14518 show (stream, string, col_p, first_p)
14520 const char *string;
14526 fprintf (stream, "%24s", "");
14531 fprintf (stream, ", ");
14535 if (*col_p + strlen (string) > 72)
14537 fprintf (stream, "\n%24s", "");
14541 fprintf (stream, "%s", string);
14542 *col_p += strlen (string);
14548 md_show_usage (stream)
14554 fprintf (stream, _("\
14556 -membedded-pic generate embedded position independent code\n\
14557 -EB generate big endian output\n\
14558 -EL generate little endian output\n\
14559 -g, -g2 do not remove unneeded NOPs or swap branches\n\
14560 -G NUM allow referencing objects up to NUM bytes\n\
14561 implicitly with the gp register [default 8]\n"));
14562 fprintf (stream, _("\
14563 -mips1 generate MIPS ISA I instructions\n\
14564 -mips2 generate MIPS ISA II instructions\n\
14565 -mips3 generate MIPS ISA III instructions\n\
14566 -mips4 generate MIPS ISA IV instructions\n\
14567 -mips5 generate MIPS ISA V instructions\n\
14568 -mips32 generate MIPS32 ISA instructions\n\
14569 -mips32r2 generate MIPS32 release 2 ISA instructions\n\
14570 -mips64 generate MIPS64 ISA instructions\n\
14571 -march=CPU/-mtune=CPU generate code/schedule for CPU, where CPU is one of:\n"));
14575 for (i = 0; mips_cpu_info_table[i].name != NULL; i++)
14576 show (stream, mips_cpu_info_table[i].name, &column, &first);
14577 show (stream, "from-abi", &column, &first);
14578 fputc ('\n', stream);
14580 fprintf (stream, _("\
14581 -mCPU equivalent to -march=CPU -mtune=CPU. Deprecated.\n\
14582 -no-mCPU don't generate code specific to CPU.\n\
14583 For -mCPU and -no-mCPU, CPU must be one of:\n"));
14587 show (stream, "3900", &column, &first);
14588 show (stream, "4010", &column, &first);
14589 show (stream, "4100", &column, &first);
14590 show (stream, "4650", &column, &first);
14591 fputc ('\n', stream);
14593 fprintf (stream, _("\
14594 -mips16 generate mips16 instructions\n\
14595 -no-mips16 do not generate mips16 instructions\n"));
14596 fprintf (stream, _("\
14597 -mgp32 use 32-bit GPRs, regardless of the chosen ISA\n\
14598 -mfp32 use 32-bit FPRs, regardless of the chosen ISA\n\
14599 -O0 remove unneeded NOPs, do not swap branches\n\
14600 -O remove unneeded NOPs and swap branches\n\
14601 -n warn about NOPs generated from macros\n\
14602 --[no-]construct-floats [dis]allow floating point values to be constructed\n\
14603 --trap, --no-break trap exception on div by 0 and mult overflow\n\
14604 --break, --no-trap break exception on div by 0 and mult overflow\n"));
14606 fprintf (stream, _("\
14607 -KPIC, -call_shared generate SVR4 position independent code\n\
14608 -non_shared do not generate position independent code\n\
14609 -xgot assume a 32 bit GOT\n\
14610 -mabi=ABI create ABI conformant object file for:\n"));
14614 show (stream, "32", &column, &first);
14615 show (stream, "o64", &column, &first);
14616 show (stream, "n32", &column, &first);
14617 show (stream, "64", &column, &first);
14618 show (stream, "eabi", &column, &first);
14620 fputc ('\n', stream);
14622 fprintf (stream, _("\
14623 -32 create o32 ABI object file (default)\n\
14624 -n32 create n32 ABI object file\n\
14625 -64 create 64 ABI object file\n"));
14630 mips_dwarf2_format ()
14632 if (mips_abi == N64_ABI)
14635 return dwarf2_format_64bit_irix;
14637 return dwarf2_format_64bit;
14641 return dwarf2_format_32bit;