1 /* tc-mips.c -- assemble code for a MIPS chip.
2 Copyright 1993, 1994, 1995, 1996, 1997, 1998, 1999, 2000, 2001, 2002
3 Free Software Foundation, Inc.
4 Contributed by the OSF and Ralph Campbell.
5 Written by Keith Knowles and Ralph Campbell, working independently.
6 Modified for ECOFF and R4000 support by Ian Lance Taylor of Cygnus
9 This file is part of GAS.
11 GAS is free software; you can redistribute it and/or modify
12 it under the terms of the GNU General Public License as published by
13 the Free Software Foundation; either version 2, or (at your option)
16 GAS is distributed in the hope that it will be useful,
17 but WITHOUT ANY WARRANTY; without even the implied warranty of
18 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
19 GNU General Public License for more details.
21 You should have received a copy of the GNU General Public License
22 along with GAS; see the file COPYING. If not, write to the Free
23 Software Foundation, 59 Temple Place - Suite 330, Boston, MA
29 #include "safe-ctype.h"
38 #include "opcode/mips.h"
40 #include "dwarf2dbg.h"
43 #define DBG(x) printf x
49 /* Clean up namespace so we can include obj-elf.h too. */
50 static int mips_output_flavor PARAMS ((void));
51 static int mips_output_flavor () { return OUTPUT_FLAVOR; }
52 #undef OBJ_PROCESS_STAB
59 #undef obj_frob_file_after_relocs
60 #undef obj_frob_symbol
62 #undef obj_sec_sym_ok_for_reloc
63 #undef OBJ_COPY_SYMBOL_ATTRIBUTES
66 /* Fix any of them that we actually care about. */
68 #define OUTPUT_FLAVOR mips_output_flavor()
75 #ifndef ECOFF_DEBUGGING
76 #define NO_ECOFF_DEBUGGING
77 #define ECOFF_DEBUGGING 0
80 int mips_flag_mdebug = -1;
84 #if defined (OBJ_ELF) || defined (OBJ_MAYBE_ELF)
85 static char *mips_regmask_frag;
91 #define PIC_CALL_REG 25
99 #define ILLEGAL_REG (32)
101 /* Allow override of standard little-endian ECOFF format. */
103 #ifndef ECOFF_LITTLE_FORMAT
104 #define ECOFF_LITTLE_FORMAT "ecoff-littlemips"
107 extern int target_big_endian;
109 /* The name of the readonly data section. */
110 #define RDATA_SECTION_NAME (OUTPUT_FLAVOR == bfd_target_aout_flavour \
112 : OUTPUT_FLAVOR == bfd_target_ecoff_flavour \
114 : OUTPUT_FLAVOR == bfd_target_coff_flavour \
116 : OUTPUT_FLAVOR == bfd_target_elf_flavour \
120 /* The ABI to use. */
131 /* MIPS ABI we are using for this output file. */
132 static enum mips_abi_level mips_abi = NO_ABI;
134 /* This is the set of options which may be modified by the .set
135 pseudo-op. We use a struct so that .set push and .set pop are more
138 struct mips_set_options
140 /* MIPS ISA (Instruction Set Architecture) level. This is set to -1
141 if it has not been initialized. Changed by `.set mipsN', and the
142 -mipsN command line option, and the default CPU. */
144 /* Enabled Application Specific Extensions (ASEs). These are set to -1
145 if they have not been initialized. Changed by `.set <asename>', by
146 command line options, and based on the default architecture. */
149 /* Whether we are assembling for the mips16 processor. 0 if we are
150 not, 1 if we are, and -1 if the value has not been initialized.
151 Changed by `.set mips16' and `.set nomips16', and the -mips16 and
152 -nomips16 command line options, and the default CPU. */
154 /* Non-zero if we should not reorder instructions. Changed by `.set
155 reorder' and `.set noreorder'. */
157 /* Non-zero if we should not permit the $at ($1) register to be used
158 in instructions. Changed by `.set at' and `.set noat'. */
160 /* Non-zero if we should warn when a macro instruction expands into
161 more than one machine instruction. Changed by `.set nomacro' and
163 int warn_about_macros;
164 /* Non-zero if we should not move instructions. Changed by `.set
165 move', `.set volatile', `.set nomove', and `.set novolatile'. */
167 /* Non-zero if we should not optimize branches by moving the target
168 of the branch into the delay slot. Actually, we don't perform
169 this optimization anyhow. Changed by `.set bopt' and `.set
172 /* Non-zero if we should not autoextend mips16 instructions.
173 Changed by `.set autoextend' and `.set noautoextend'. */
175 /* Restrict general purpose registers and floating point registers
176 to 32 bit. This is initially determined when -mgp32 or -mfp32
177 is passed but can changed if the assembler code uses .set mipsN. */
182 /* True if -mgp32 was passed. */
183 static int file_mips_gp32 = -1;
185 /* True if -mfp32 was passed. */
186 static int file_mips_fp32 = -1;
188 /* This is the struct we use to hold the current set of options. Note
189 that we must set the isa field to ISA_UNKNOWN and the ASE fields to
190 -1 to indicate that they have not been initialized. */
192 static struct mips_set_options mips_opts =
194 ISA_UNKNOWN, -1, -1, -1, 0, 0, 0, 0, 0, 0, 0, 0
197 /* These variables are filled in with the masks of registers used.
198 The object format code reads them and puts them in the appropriate
200 unsigned long mips_gprmask;
201 unsigned long mips_cprmask[4];
203 /* MIPS ISA we are using for this output file. */
204 static int file_mips_isa = ISA_UNKNOWN;
206 /* True if -mips16 was passed or implied by arguments passed on the
207 command line (e.g., by -march). */
208 static int file_ase_mips16;
210 /* True if -mips3d was passed or implied by arguments passed on the
211 command line (e.g., by -march). */
212 static int file_ase_mips3d;
214 /* True if -mdmx was passed or implied by arguments passed on the
215 command line (e.g., by -march). */
216 static int file_ase_mdmx;
218 /* The argument of the -march= flag. The architecture we are assembling. */
219 static int mips_arch = CPU_UNKNOWN;
220 static const char *mips_arch_string;
221 static const struct mips_cpu_info *mips_arch_info;
223 /* The argument of the -mtune= flag. The architecture for which we
225 static int mips_tune = CPU_UNKNOWN;
226 static const char *mips_tune_string;
227 static const struct mips_cpu_info *mips_tune_info;
229 /* True when generating 32-bit code for a 64-bit processor. */
230 static int mips_32bitmode = 0;
232 /* Some ISA's have delay slots for instructions which read or write
233 from a coprocessor (eg. mips1-mips3); some don't (eg mips4).
234 Return true if instructions marked INSN_LOAD_COPROC_DELAY,
235 INSN_COPROC_MOVE_DELAY, or INSN_WRITE_COND_CODE actually have a
236 delay slot in this ISA. The uses of this macro assume that any
237 ISA that has delay slots for one of these, has them for all. They
238 also assume that ISAs which don't have delays for these insns, don't
239 have delays for the INSN_LOAD_MEMORY_DELAY instructions either. */
240 #define ISA_HAS_COPROC_DELAYS(ISA) ( \
242 || (ISA) == ISA_MIPS2 \
243 || (ISA) == ISA_MIPS3 \
246 /* True if the given ABI requires 32-bit registers. */
247 #define ABI_NEEDS_32BIT_REGS(ABI) ((ABI) == O32_ABI)
249 /* Likewise 64-bit registers. */
250 #define ABI_NEEDS_64BIT_REGS(ABI) \
252 || (ABI) == N64_ABI \
255 /* Return true if ISA supports 64 bit gp register instructions. */
256 #define ISA_HAS_64BIT_REGS(ISA) ( \
258 || (ISA) == ISA_MIPS4 \
259 || (ISA) == ISA_MIPS5 \
260 || (ISA) == ISA_MIPS64 \
263 /* 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 /* Map normal MIPS register numbers to mips16 register numbers. */
560 #define X ILLEGAL_REG
561 static const int mips32_to_16_reg_map[] =
563 X, X, 2, 3, 4, 5, 6, 7,
564 X, X, X, X, X, X, X, X,
565 0, 1, X, X, X, X, X, X,
566 X, X, X, X, X, X, X, X
570 /* Map mips16 register numbers to normal MIPS register numbers. */
572 static const unsigned int mips16_to_32_reg_map[] =
574 16, 17, 2, 3, 4, 5, 6, 7
577 static int mips_fix_4122_bugs;
579 /* We don't relax branches by default, since this causes us to expand
580 `la .l2 - .l1' if there's a branch between .l1 and .l2, because we
581 fail to compute the offset before expanding the macro to the most
582 efficient expansion. */
584 static int mips_relax_branch;
586 /* Since the MIPS does not have multiple forms of PC relative
587 instructions, we do not have to do relaxing as is done on other
588 platforms. However, we do have to handle GP relative addressing
589 correctly, which turns out to be a similar problem.
591 Every macro that refers to a symbol can occur in (at least) two
592 forms, one with GP relative addressing and one without. For
593 example, loading a global variable into a register generally uses
594 a macro instruction like this:
596 If i can be addressed off the GP register (this is true if it is in
597 the .sbss or .sdata section, or if it is known to be smaller than
598 the -G argument) this will generate the following instruction:
600 This instruction will use a GPREL reloc. If i can not be addressed
601 off the GP register, the following instruction sequence will be used:
604 In this case the first instruction will have a HI16 reloc, and the
605 second reloc will have a LO16 reloc. Both relocs will be against
608 The issue here is that we may not know whether i is GP addressable
609 until after we see the instruction that uses it. Therefore, we
610 want to be able to choose the final instruction sequence only at
611 the end of the assembly. This is similar to the way other
612 platforms choose the size of a PC relative instruction only at the
615 When generating position independent code we do not use GP
616 addressing in quite the same way, but the issue still arises as
617 external symbols and local symbols must be handled differently.
619 We handle these issues by actually generating both possible
620 instruction sequences. The longer one is put in a frag_var with
621 type rs_machine_dependent. We encode what to do with the frag in
622 the subtype field. We encode (1) the number of existing bytes to
623 replace, (2) the number of new bytes to use, (3) the offset from
624 the start of the existing bytes to the first reloc we must generate
625 (that is, the offset is applied from the start of the existing
626 bytes after they are replaced by the new bytes, if any), (4) the
627 offset from the start of the existing bytes to the second reloc,
628 (5) whether a third reloc is needed (the third reloc is always four
629 bytes after the second reloc), and (6) whether to warn if this
630 variant is used (this is sometimes needed if .set nomacro or .set
631 noat is in effect). All these numbers are reasonably small.
633 Generating two instruction sequences must be handled carefully to
634 ensure that delay slots are handled correctly. Fortunately, there
635 are a limited number of cases. When the second instruction
636 sequence is generated, append_insn is directed to maintain the
637 existing delay slot information, so it continues to apply to any
638 code after the second instruction sequence. This means that the
639 second instruction sequence must not impose any requirements not
640 required by the first instruction sequence.
642 These variant frags are then handled in functions called by the
643 machine independent code. md_estimate_size_before_relax returns
644 the final size of the frag. md_convert_frag sets up the final form
645 of the frag. tc_gen_reloc adjust the first reloc and adds a second
647 #define RELAX_ENCODE(old, new, reloc1, reloc2, reloc3, warn) \
651 | (((reloc1) + 64) << 9) \
652 | (((reloc2) + 64) << 2) \
653 | ((reloc3) ? (1 << 1) : 0) \
655 #define RELAX_OLD(i) (((i) >> 23) & 0x7f)
656 #define RELAX_NEW(i) (((i) >> 16) & 0x7f)
657 #define RELAX_RELOC1(i) ((valueT) (((i) >> 9) & 0x7f) - 64)
658 #define RELAX_RELOC2(i) ((valueT) (((i) >> 2) & 0x7f) - 64)
659 #define RELAX_RELOC3(i) (((i) >> 1) & 1)
660 #define RELAX_WARN(i) ((i) & 1)
662 /* Branch without likely bit. If label is out of range, we turn:
664 beq reg1, reg2, label
674 with the following opcode replacements:
681 bltzal <-> bgezal (with jal label instead of j label)
683 Even though keeping the delay slot instruction in the delay slot of
684 the branch would be more efficient, it would be very tricky to do
685 correctly, because we'd have to introduce a variable frag *after*
686 the delay slot instruction, and expand that instead. Let's do it
687 the easy way for now, even if the branch-not-taken case now costs
688 one additional instruction. Out-of-range branches are not supposed
689 to be common, anyway.
691 Branch likely. If label is out of range, we turn:
693 beql reg1, reg2, label
694 delay slot (annulled if branch not taken)
703 delay slot (executed only if branch taken)
706 It would be possible to generate a shorter sequence by losing the
707 likely bit, generating something like:
712 delay slot (executed only if branch taken)
724 bltzall -> bgezal (with jal label instead of j label)
725 bgezall -> bltzal (ditto)
728 but it's not clear that it would actually improve performance. */
729 #define RELAX_BRANCH_ENCODE(uncond, likely, link, toofar) \
732 | ((toofar) ? 1 : 0) \
734 | ((likely) ? 4 : 0) \
735 | ((uncond) ? 8 : 0)))
736 #define RELAX_BRANCH_P(i) (((i) & 0xf0000000) == 0xc0000000)
737 #define RELAX_BRANCH_UNCOND(i) (((i) & 8) != 0)
738 #define RELAX_BRANCH_LIKELY(i) (((i) & 4) != 0)
739 #define RELAX_BRANCH_LINK(i) (((i) & 2) != 0)
740 #define RELAX_BRANCH_TOOFAR(i) (((i) & 1))
742 /* For mips16 code, we use an entirely different form of relaxation.
743 mips16 supports two versions of most instructions which take
744 immediate values: a small one which takes some small value, and a
745 larger one which takes a 16 bit value. Since branches also follow
746 this pattern, relaxing these values is required.
748 We can assemble both mips16 and normal MIPS code in a single
749 object. Therefore, we need to support this type of relaxation at
750 the same time that we support the relaxation described above. We
751 use the high bit of the subtype field to distinguish these cases.
753 The information we store for this type of relaxation is the
754 argument code found in the opcode file for this relocation, whether
755 the user explicitly requested a small or extended form, and whether
756 the relocation is in a jump or jal delay slot. That tells us the
757 size of the value, and how it should be stored. We also store
758 whether the fragment is considered to be extended or not. We also
759 store whether this is known to be a branch to a different section,
760 whether we have tried to relax this frag yet, and whether we have
761 ever extended a PC relative fragment because of a shift count. */
762 #define RELAX_MIPS16_ENCODE(type, small, ext, dslot, jal_dslot) \
765 | ((small) ? 0x100 : 0) \
766 | ((ext) ? 0x200 : 0) \
767 | ((dslot) ? 0x400 : 0) \
768 | ((jal_dslot) ? 0x800 : 0))
769 #define RELAX_MIPS16_P(i) (((i) & 0xc0000000) == 0x80000000)
770 #define RELAX_MIPS16_TYPE(i) ((i) & 0xff)
771 #define RELAX_MIPS16_USER_SMALL(i) (((i) & 0x100) != 0)
772 #define RELAX_MIPS16_USER_EXT(i) (((i) & 0x200) != 0)
773 #define RELAX_MIPS16_DSLOT(i) (((i) & 0x400) != 0)
774 #define RELAX_MIPS16_JAL_DSLOT(i) (((i) & 0x800) != 0)
775 #define RELAX_MIPS16_EXTENDED(i) (((i) & 0x1000) != 0)
776 #define RELAX_MIPS16_MARK_EXTENDED(i) ((i) | 0x1000)
777 #define RELAX_MIPS16_CLEAR_EXTENDED(i) ((i) &~ 0x1000)
778 #define RELAX_MIPS16_LONG_BRANCH(i) (((i) & 0x2000) != 0)
779 #define RELAX_MIPS16_MARK_LONG_BRANCH(i) ((i) | 0x2000)
780 #define RELAX_MIPS16_CLEAR_LONG_BRANCH(i) ((i) &~ 0x2000)
782 /* Is the given value a sign-extended 32-bit value? */
783 #define IS_SEXT_32BIT_NUM(x) \
784 (((x) &~ (offsetT) 0x7fffffff) == 0 \
785 || (((x) &~ (offsetT) 0x7fffffff) == ~ (offsetT) 0x7fffffff))
787 /* Is the given value a sign-extended 16-bit value? */
788 #define IS_SEXT_16BIT_NUM(x) \
789 (((x) &~ (offsetT) 0x7fff) == 0 \
790 || (((x) &~ (offsetT) 0x7fff) == ~ (offsetT) 0x7fff))
793 /* Prototypes for static functions. */
796 #define internalError() \
797 as_fatal (_("internal Error, line %d, %s"), __LINE__, __FILE__)
799 #define internalError() as_fatal (_("MIPS internal Error"));
802 enum mips_regclass { MIPS_GR_REG, MIPS_FP_REG, MIPS16_REG };
804 static int insn_uses_reg
805 PARAMS ((struct mips_cl_insn *ip, unsigned int reg,
806 enum mips_regclass class));
807 static int reg_needs_delay
808 PARAMS ((unsigned int));
809 static void mips16_mark_labels
811 static void append_insn
812 PARAMS ((char *place, struct mips_cl_insn * ip, expressionS * p,
813 bfd_reloc_code_real_type *r, bfd_boolean));
814 static void mips_no_prev_insn
816 static void mips_emit_delays
817 PARAMS ((bfd_boolean));
819 static void macro_build
820 PARAMS ((char *place, int *counter, expressionS * ep, const char *name,
821 const char *fmt, ...));
823 static void macro_build ();
825 static void mips16_macro_build
826 PARAMS ((char *, int *, expressionS *, const char *, const char *, va_list));
827 static void macro_build_jalr
828 PARAMS ((int, expressionS *));
829 static void macro_build_lui
830 PARAMS ((char *place, int *counter, expressionS * ep, int regnum));
831 static void macro_build_ldst_constoffset
832 PARAMS ((char *place, int *counter, expressionS * ep, const char *op,
833 int valreg, int breg));
835 PARAMS ((int *counter, int reg, int unsignedp));
836 static void check_absolute_expr
837 PARAMS ((struct mips_cl_insn * ip, expressionS *));
838 static void load_register
839 PARAMS ((int *, int, expressionS *, int));
840 static void load_address
841 PARAMS ((int *, int, expressionS *, int *));
842 static void move_register
843 PARAMS ((int *, int, int));
845 PARAMS ((struct mips_cl_insn * ip));
846 static void mips16_macro
847 PARAMS ((struct mips_cl_insn * ip));
848 #ifdef LOSING_COMPILER
850 PARAMS ((struct mips_cl_insn * ip));
853 PARAMS ((char *str, struct mips_cl_insn * ip));
854 static void mips16_ip
855 PARAMS ((char *str, struct mips_cl_insn * ip));
856 static void mips16_immed
857 PARAMS ((char *, unsigned int, int, offsetT, bfd_boolean, bfd_boolean,
858 bfd_boolean, unsigned long *, bfd_boolean *, unsigned short *));
859 static int my_getPercentOp
860 PARAMS ((char **, unsigned int *, int *));
861 static int my_getSmallParser
862 PARAMS ((char **, unsigned int *, int *));
863 static int my_getSmallExpression
864 PARAMS ((expressionS *, char *));
865 static void my_getExpression
866 PARAMS ((expressionS *, char *));
868 static int support_64bit_objects
871 static void mips_set_option_string
872 PARAMS ((const char **, const char *));
873 static symbolS *get_symbol
875 static void mips_align
876 PARAMS ((int to, int fill, symbolS *label));
879 static void s_change_sec
881 static void s_change_section
885 static void s_float_cons
887 static void s_mips_globl
891 static void s_mipsset
893 static void s_abicalls
897 static void s_cpsetup
899 static void s_cplocal
901 static void s_cprestore
903 static void s_cpreturn
905 static void s_gpvalue
909 static void s_gpdword
915 static void md_obj_begin
917 static void md_obj_end
919 static long get_number
921 static void s_mips_ent
923 static void s_mips_end
925 static void s_mips_frame
927 static void s_mips_mask
929 static void s_mips_stab
931 static void s_mips_weakext
933 static void s_mips_file
935 static void s_mips_loc
937 static int mips16_extended_frag
938 PARAMS ((fragS *, asection *, long));
939 static int relaxed_branch_length (fragS *, asection *, int);
940 static int validate_mips_insn
941 PARAMS ((const struct mips_opcode *));
943 PARAMS ((FILE *, const char *, int *, int *));
945 static int mips_need_elf_addend_fixup
949 /* Return values of my_getSmallExpression(). */
956 /* Direct relocation creation by %percent_op(). */
975 /* Table and functions used to map between CPU/ISA names, and
976 ISA levels, and CPU numbers. */
980 const char *name; /* CPU or ISA name. */
981 int is_isa; /* Is this an ISA? (If 0, a CPU.) */
982 int isa; /* ISA level. */
983 int cpu; /* CPU number (default CPU if ISA). */
986 static void mips_set_architecture
987 PARAMS ((const struct mips_cpu_info *));
988 static void mips_set_tune
989 PARAMS ((const struct mips_cpu_info *));
990 static bfd_boolean mips_strict_matching_cpu_name_p
991 PARAMS ((const char *, const char *));
992 static bfd_boolean mips_matching_cpu_name_p
993 PARAMS ((const char *, const char *));
994 static const struct mips_cpu_info *mips_parse_cpu
995 PARAMS ((const char *, const char *));
996 static const struct mips_cpu_info *mips_cpu_info_from_isa
1001 The following pseudo-ops from the Kane and Heinrich MIPS book
1002 should be defined here, but are currently unsupported: .alias,
1003 .galive, .gjaldef, .gjrlive, .livereg, .noalias.
1005 The following pseudo-ops from the Kane and Heinrich MIPS book are
1006 specific to the type of debugging information being generated, and
1007 should be defined by the object format: .aent, .begin, .bend,
1008 .bgnb, .end, .endb, .ent, .fmask, .frame, .loc, .mask, .verstamp,
1011 The following pseudo-ops from the Kane and Heinrich MIPS book are
1012 not MIPS CPU specific, but are also not specific to the object file
1013 format. This file is probably the best place to define them, but
1014 they are not currently supported: .asm0, .endr, .lab, .repeat,
1017 static const pseudo_typeS mips_pseudo_table[] =
1019 /* MIPS specific pseudo-ops. */
1020 {"option", s_option, 0},
1021 {"set", s_mipsset, 0},
1022 {"rdata", s_change_sec, 'r'},
1023 {"sdata", s_change_sec, 's'},
1024 {"livereg", s_ignore, 0},
1025 {"abicalls", s_abicalls, 0},
1026 {"cpload", s_cpload, 0},
1027 {"cpsetup", s_cpsetup, 0},
1028 {"cplocal", s_cplocal, 0},
1029 {"cprestore", s_cprestore, 0},
1030 {"cpreturn", s_cpreturn, 0},
1031 {"gpvalue", s_gpvalue, 0},
1032 {"gpword", s_gpword, 0},
1033 {"gpdword", s_gpdword, 0},
1034 {"cpadd", s_cpadd, 0},
1035 {"insn", s_insn, 0},
1037 /* Relatively generic pseudo-ops that happen to be used on MIPS
1039 {"asciiz", stringer, 1},
1040 {"bss", s_change_sec, 'b'},
1042 {"half", s_cons, 1},
1043 {"dword", s_cons, 3},
1044 {"weakext", s_mips_weakext, 0},
1046 /* These pseudo-ops are defined in read.c, but must be overridden
1047 here for one reason or another. */
1048 {"align", s_align, 0},
1049 {"byte", s_cons, 0},
1050 {"data", s_change_sec, 'd'},
1051 {"double", s_float_cons, 'd'},
1052 {"float", s_float_cons, 'f'},
1053 {"globl", s_mips_globl, 0},
1054 {"global", s_mips_globl, 0},
1055 {"hword", s_cons, 1},
1057 {"long", s_cons, 2},
1058 {"octa", s_cons, 4},
1059 {"quad", s_cons, 3},
1060 {"section", s_change_section, 0},
1061 {"short", s_cons, 1},
1062 {"single", s_float_cons, 'f'},
1063 {"stabn", s_mips_stab, 'n'},
1064 {"text", s_change_sec, 't'},
1065 {"word", s_cons, 2},
1067 { "extern", ecoff_directive_extern, 0},
1072 static const pseudo_typeS mips_nonecoff_pseudo_table[] =
1074 /* These pseudo-ops should be defined by the object file format.
1075 However, a.out doesn't support them, so we have versions here. */
1076 {"aent", s_mips_ent, 1},
1077 {"bgnb", s_ignore, 0},
1078 {"end", s_mips_end, 0},
1079 {"endb", s_ignore, 0},
1080 {"ent", s_mips_ent, 0},
1081 {"file", s_mips_file, 0},
1082 {"fmask", s_mips_mask, 'F'},
1083 {"frame", s_mips_frame, 0},
1084 {"loc", s_mips_loc, 0},
1085 {"mask", s_mips_mask, 'R'},
1086 {"verstamp", s_ignore, 0},
1090 extern void pop_insert PARAMS ((const pseudo_typeS *));
1095 pop_insert (mips_pseudo_table);
1096 if (! ECOFF_DEBUGGING)
1097 pop_insert (mips_nonecoff_pseudo_table);
1100 /* Symbols labelling the current insn. */
1102 struct insn_label_list
1104 struct insn_label_list *next;
1108 static struct insn_label_list *insn_labels;
1109 static struct insn_label_list *free_insn_labels;
1111 static void mips_clear_insn_labels PARAMS ((void));
1114 mips_clear_insn_labels ()
1116 register struct insn_label_list **pl;
1118 for (pl = &free_insn_labels; *pl != NULL; pl = &(*pl)->next)
1124 static char *expr_end;
1126 /* Expressions which appear in instructions. These are set by
1129 static expressionS imm_expr;
1130 static expressionS offset_expr;
1132 /* Relocs associated with imm_expr and offset_expr. */
1134 static bfd_reloc_code_real_type imm_reloc[3]
1135 = {BFD_RELOC_UNUSED, BFD_RELOC_UNUSED, BFD_RELOC_UNUSED};
1136 static bfd_reloc_code_real_type offset_reloc[3]
1137 = {BFD_RELOC_UNUSED, BFD_RELOC_UNUSED, BFD_RELOC_UNUSED};
1139 /* This is set by mips_ip if imm_reloc is an unmatched HI16_S reloc. */
1141 static bfd_boolean imm_unmatched_hi;
1143 /* These are set by mips16_ip if an explicit extension is used. */
1145 static bfd_boolean mips16_small, mips16_ext;
1148 /* The pdr segment for per procedure frame/regmask info. Not used for
1151 static segT pdr_seg;
1154 /* The default target format to use. */
1157 mips_target_format ()
1159 switch (OUTPUT_FLAVOR)
1161 case bfd_target_aout_flavour:
1162 return target_big_endian ? "a.out-mips-big" : "a.out-mips-little";
1163 case bfd_target_ecoff_flavour:
1164 return target_big_endian ? "ecoff-bigmips" : ECOFF_LITTLE_FORMAT;
1165 case bfd_target_coff_flavour:
1167 case bfd_target_elf_flavour:
1169 /* This is traditional mips. */
1170 return (target_big_endian
1171 ? (HAVE_64BIT_OBJECTS
1172 ? "elf64-tradbigmips"
1174 ? "elf32-ntradbigmips" : "elf32-tradbigmips"))
1175 : (HAVE_64BIT_OBJECTS
1176 ? "elf64-tradlittlemips"
1178 ? "elf32-ntradlittlemips" : "elf32-tradlittlemips")));
1180 return (target_big_endian
1181 ? (HAVE_64BIT_OBJECTS
1184 ? "elf32-nbigmips" : "elf32-bigmips"))
1185 : (HAVE_64BIT_OBJECTS
1186 ? "elf64-littlemips"
1188 ? "elf32-nlittlemips" : "elf32-littlemips")));
1196 /* This function is called once, at assembler startup time. It should
1197 set up all the tables, etc. that the MD part of the assembler will need. */
1202 register const char *retval = NULL;
1206 if (! bfd_set_arch_mach (stdoutput, bfd_arch_mips, mips_arch))
1207 as_warn (_("Could not set architecture and machine"));
1209 op_hash = hash_new ();
1211 for (i = 0; i < NUMOPCODES;)
1213 const char *name = mips_opcodes[i].name;
1215 retval = hash_insert (op_hash, name, (PTR) &mips_opcodes[i]);
1218 fprintf (stderr, _("internal error: can't hash `%s': %s\n"),
1219 mips_opcodes[i].name, retval);
1220 /* Probably a memory allocation problem? Give up now. */
1221 as_fatal (_("Broken assembler. No assembly attempted."));
1225 if (mips_opcodes[i].pinfo != INSN_MACRO)
1227 if (!validate_mips_insn (&mips_opcodes[i]))
1232 while ((i < NUMOPCODES) && !strcmp (mips_opcodes[i].name, name));
1235 mips16_op_hash = hash_new ();
1238 while (i < bfd_mips16_num_opcodes)
1240 const char *name = mips16_opcodes[i].name;
1242 retval = hash_insert (mips16_op_hash, name, (PTR) &mips16_opcodes[i]);
1244 as_fatal (_("internal: can't hash `%s': %s"),
1245 mips16_opcodes[i].name, retval);
1248 if (mips16_opcodes[i].pinfo != INSN_MACRO
1249 && ((mips16_opcodes[i].match & mips16_opcodes[i].mask)
1250 != mips16_opcodes[i].match))
1252 fprintf (stderr, _("internal error: bad mips16 opcode: %s %s\n"),
1253 mips16_opcodes[i].name, mips16_opcodes[i].args);
1258 while (i < bfd_mips16_num_opcodes
1259 && strcmp (mips16_opcodes[i].name, name) == 0);
1263 as_fatal (_("Broken assembler. No assembly attempted."));
1265 /* We add all the general register names to the symbol table. This
1266 helps us detect invalid uses of them. */
1267 for (i = 0; i < 32; i++)
1271 sprintf (buf, "$%d", i);
1272 symbol_table_insert (symbol_new (buf, reg_section, i,
1273 &zero_address_frag));
1275 symbol_table_insert (symbol_new ("$ra", reg_section, RA,
1276 &zero_address_frag));
1277 symbol_table_insert (symbol_new ("$fp", reg_section, FP,
1278 &zero_address_frag));
1279 symbol_table_insert (symbol_new ("$sp", reg_section, SP,
1280 &zero_address_frag));
1281 symbol_table_insert (symbol_new ("$gp", reg_section, GP,
1282 &zero_address_frag));
1283 symbol_table_insert (symbol_new ("$at", reg_section, AT,
1284 &zero_address_frag));
1285 symbol_table_insert (symbol_new ("$kt0", reg_section, KT0,
1286 &zero_address_frag));
1287 symbol_table_insert (symbol_new ("$kt1", reg_section, KT1,
1288 &zero_address_frag));
1289 symbol_table_insert (symbol_new ("$zero", reg_section, ZERO,
1290 &zero_address_frag));
1291 symbol_table_insert (symbol_new ("$pc", reg_section, -1,
1292 &zero_address_frag));
1294 /* If we don't add these register names to the symbol table, they
1295 may end up being added as regular symbols by operand(), and then
1296 make it to the object file as undefined in case they're not
1297 regarded as local symbols. They're local in o32, since `$' is a
1298 local symbol prefix, but not in n32 or n64. */
1299 for (i = 0; i < 8; i++)
1303 sprintf (buf, "$fcc%i", i);
1304 symbol_table_insert (symbol_new (buf, reg_section, -1,
1305 &zero_address_frag));
1308 mips_no_prev_insn (FALSE);
1311 mips_cprmask[0] = 0;
1312 mips_cprmask[1] = 0;
1313 mips_cprmask[2] = 0;
1314 mips_cprmask[3] = 0;
1316 /* set the default alignment for the text section (2**2) */
1317 record_alignment (text_section, 2);
1319 if (USE_GLOBAL_POINTER_OPT)
1320 bfd_set_gp_size (stdoutput, g_switch_value);
1322 if (OUTPUT_FLAVOR == bfd_target_elf_flavour)
1324 /* On a native system, sections must be aligned to 16 byte
1325 boundaries. When configured for an embedded ELF target, we
1327 if (strcmp (TARGET_OS, "elf") != 0)
1329 (void) bfd_set_section_alignment (stdoutput, text_section, 4);
1330 (void) bfd_set_section_alignment (stdoutput, data_section, 4);
1331 (void) bfd_set_section_alignment (stdoutput, bss_section, 4);
1334 /* Create a .reginfo section for register masks and a .mdebug
1335 section for debugging information. */
1343 subseg = now_subseg;
1345 /* The ABI says this section should be loaded so that the
1346 running program can access it. However, we don't load it
1347 if we are configured for an embedded target */
1348 flags = SEC_READONLY | SEC_DATA;
1349 if (strcmp (TARGET_OS, "elf") != 0)
1350 flags |= SEC_ALLOC | SEC_LOAD;
1352 if (mips_abi != N64_ABI)
1354 sec = subseg_new (".reginfo", (subsegT) 0);
1356 bfd_set_section_flags (stdoutput, sec, flags);
1357 bfd_set_section_alignment (stdoutput, sec, HAVE_NEWABI ? 3 : 2);
1360 mips_regmask_frag = frag_more (sizeof (Elf32_External_RegInfo));
1365 /* The 64-bit ABI uses a .MIPS.options section rather than
1366 .reginfo section. */
1367 sec = subseg_new (".MIPS.options", (subsegT) 0);
1368 bfd_set_section_flags (stdoutput, sec, flags);
1369 bfd_set_section_alignment (stdoutput, sec, 3);
1372 /* Set up the option header. */
1374 Elf_Internal_Options opthdr;
1377 opthdr.kind = ODK_REGINFO;
1378 opthdr.size = (sizeof (Elf_External_Options)
1379 + sizeof (Elf64_External_RegInfo));
1382 f = frag_more (sizeof (Elf_External_Options));
1383 bfd_mips_elf_swap_options_out (stdoutput, &opthdr,
1384 (Elf_External_Options *) f);
1386 mips_regmask_frag = frag_more (sizeof (Elf64_External_RegInfo));
1391 if (ECOFF_DEBUGGING)
1393 sec = subseg_new (".mdebug", (subsegT) 0);
1394 (void) bfd_set_section_flags (stdoutput, sec,
1395 SEC_HAS_CONTENTS | SEC_READONLY);
1396 (void) bfd_set_section_alignment (stdoutput, sec, 2);
1399 else if (OUTPUT_FLAVOR == bfd_target_elf_flavour)
1401 pdr_seg = subseg_new (".pdr", (subsegT) 0);
1402 (void) bfd_set_section_flags (stdoutput, pdr_seg,
1403 SEC_READONLY | SEC_RELOC
1405 (void) bfd_set_section_alignment (stdoutput, pdr_seg, 2);
1409 subseg_set (seg, subseg);
1413 if (! ECOFF_DEBUGGING)
1420 if (! ECOFF_DEBUGGING)
1428 struct mips_cl_insn insn;
1429 bfd_reloc_code_real_type unused_reloc[3]
1430 = {BFD_RELOC_UNUSED, BFD_RELOC_UNUSED, BFD_RELOC_UNUSED};
1432 imm_expr.X_op = O_absent;
1433 imm_unmatched_hi = FALSE;
1434 offset_expr.X_op = O_absent;
1435 imm_reloc[0] = BFD_RELOC_UNUSED;
1436 imm_reloc[1] = BFD_RELOC_UNUSED;
1437 imm_reloc[2] = BFD_RELOC_UNUSED;
1438 offset_reloc[0] = BFD_RELOC_UNUSED;
1439 offset_reloc[1] = BFD_RELOC_UNUSED;
1440 offset_reloc[2] = BFD_RELOC_UNUSED;
1442 if (mips_opts.mips16)
1443 mips16_ip (str, &insn);
1446 mips_ip (str, &insn);
1447 DBG ((_("returned from mips_ip(%s) insn_opcode = 0x%x\n"),
1448 str, insn.insn_opcode));
1453 as_bad ("%s `%s'", insn_error, str);
1457 if (insn.insn_mo->pinfo == INSN_MACRO)
1459 if (mips_opts.mips16)
1460 mips16_macro (&insn);
1466 if (imm_expr.X_op != O_absent)
1467 append_insn (NULL, &insn, &imm_expr, imm_reloc, imm_unmatched_hi);
1468 else if (offset_expr.X_op != O_absent)
1469 append_insn (NULL, &insn, &offset_expr, offset_reloc, FALSE);
1471 append_insn (NULL, &insn, NULL, unused_reloc, FALSE);
1475 /* See whether instruction IP reads register REG. CLASS is the type
1479 insn_uses_reg (ip, reg, class)
1480 struct mips_cl_insn *ip;
1482 enum mips_regclass class;
1484 if (class == MIPS16_REG)
1486 assert (mips_opts.mips16);
1487 reg = mips16_to_32_reg_map[reg];
1488 class = MIPS_GR_REG;
1491 /* Don't report on general register ZERO, since it never changes. */
1492 if (class == MIPS_GR_REG && reg == ZERO)
1495 if (class == MIPS_FP_REG)
1497 assert (! mips_opts.mips16);
1498 /* If we are called with either $f0 or $f1, we must check $f0.
1499 This is not optimal, because it will introduce an unnecessary
1500 NOP between "lwc1 $f0" and "swc1 $f1". To fix this we would
1501 need to distinguish reading both $f0 and $f1 or just one of
1502 them. Note that we don't have to check the other way,
1503 because there is no instruction that sets both $f0 and $f1
1504 and requires a delay. */
1505 if ((ip->insn_mo->pinfo & INSN_READ_FPR_S)
1506 && ((((ip->insn_opcode >> OP_SH_FS) & OP_MASK_FS) &~(unsigned)1)
1507 == (reg &~ (unsigned) 1)))
1509 if ((ip->insn_mo->pinfo & INSN_READ_FPR_T)
1510 && ((((ip->insn_opcode >> OP_SH_FT) & OP_MASK_FT) &~(unsigned)1)
1511 == (reg &~ (unsigned) 1)))
1514 else if (! mips_opts.mips16)
1516 if ((ip->insn_mo->pinfo & INSN_READ_GPR_S)
1517 && ((ip->insn_opcode >> OP_SH_RS) & OP_MASK_RS) == reg)
1519 if ((ip->insn_mo->pinfo & INSN_READ_GPR_T)
1520 && ((ip->insn_opcode >> OP_SH_RT) & OP_MASK_RT) == reg)
1525 if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_X)
1526 && (mips16_to_32_reg_map[((ip->insn_opcode >> MIPS16OP_SH_RX)
1527 & MIPS16OP_MASK_RX)]
1530 if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_Y)
1531 && (mips16_to_32_reg_map[((ip->insn_opcode >> MIPS16OP_SH_RY)
1532 & MIPS16OP_MASK_RY)]
1535 if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_Z)
1536 && (mips16_to_32_reg_map[((ip->insn_opcode >> MIPS16OP_SH_MOVE32Z)
1537 & MIPS16OP_MASK_MOVE32Z)]
1540 if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_T) && reg == TREG)
1542 if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_SP) && reg == SP)
1544 if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_31) && reg == RA)
1546 if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_GPR_X)
1547 && ((ip->insn_opcode >> MIPS16OP_SH_REGR32)
1548 & MIPS16OP_MASK_REGR32) == reg)
1555 /* This function returns true if modifying a register requires a
1559 reg_needs_delay (reg)
1562 unsigned long prev_pinfo;
1564 prev_pinfo = prev_insn.insn_mo->pinfo;
1565 if (! mips_opts.noreorder
1566 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
1567 && ((prev_pinfo & INSN_LOAD_COPROC_DELAY)
1568 || (! gpr_interlocks
1569 && (prev_pinfo & INSN_LOAD_MEMORY_DELAY))))
1571 /* A load from a coprocessor or from memory. All load
1572 delays delay the use of general register rt for one
1573 instruction on the r3000. The r6000 and r4000 use
1575 /* Itbl support may require additional care here. */
1576 know (prev_pinfo & INSN_WRITE_GPR_T);
1577 if (reg == ((prev_insn.insn_opcode >> OP_SH_RT) & OP_MASK_RT))
1584 /* Mark instruction labels in mips16 mode. This permits the linker to
1585 handle them specially, such as generating jalx instructions when
1586 needed. We also make them odd for the duration of the assembly, in
1587 order to generate the right sort of code. We will make them even
1588 in the adjust_symtab routine, while leaving them marked. This is
1589 convenient for the debugger and the disassembler. The linker knows
1590 to make them odd again. */
1593 mips16_mark_labels ()
1595 if (mips_opts.mips16)
1597 struct insn_label_list *l;
1600 for (l = insn_labels; l != NULL; l = l->next)
1603 if (OUTPUT_FLAVOR == bfd_target_elf_flavour)
1604 S_SET_OTHER (l->label, STO_MIPS16);
1606 val = S_GET_VALUE (l->label);
1608 S_SET_VALUE (l->label, val + 1);
1613 /* Output an instruction. PLACE is where to put the instruction; if
1614 it is NULL, this uses frag_more to get room. IP is the instruction
1615 information. ADDRESS_EXPR is an operand of the instruction to be
1616 used with RELOC_TYPE. */
1619 append_insn (place, ip, address_expr, reloc_type, unmatched_hi)
1621 struct mips_cl_insn *ip;
1622 expressionS *address_expr;
1623 bfd_reloc_code_real_type *reloc_type;
1624 bfd_boolean unmatched_hi;
1626 register unsigned long prev_pinfo, pinfo;
1631 /* Mark instruction labels in mips16 mode. */
1632 mips16_mark_labels ();
1634 prev_pinfo = prev_insn.insn_mo->pinfo;
1635 pinfo = ip->insn_mo->pinfo;
1637 if (place == NULL && (! mips_opts.noreorder || prev_nop_frag != NULL))
1641 /* If the previous insn required any delay slots, see if we need
1642 to insert a NOP or two. There are eight kinds of possible
1643 hazards, of which an instruction can have at most one type.
1644 (1) a load from memory delay
1645 (2) a load from a coprocessor delay
1646 (3) an unconditional branch delay
1647 (4) a conditional branch delay
1648 (5) a move to coprocessor register delay
1649 (6) a load coprocessor register from memory delay
1650 (7) a coprocessor condition code delay
1651 (8) a HI/LO special register delay
1653 There are a lot of optimizations we could do that we don't.
1654 In particular, we do not, in general, reorder instructions.
1655 If you use gcc with optimization, it will reorder
1656 instructions and generally do much more optimization then we
1657 do here; repeating all that work in the assembler would only
1658 benefit hand written assembly code, and does not seem worth
1661 /* This is how a NOP is emitted. */
1662 #define emit_nop() \
1664 ? md_number_to_chars (frag_more (2), 0x6500, 2) \
1665 : md_number_to_chars (frag_more (4), 0, 4))
1667 /* The previous insn might require a delay slot, depending upon
1668 the contents of the current insn. */
1669 if (! mips_opts.mips16
1670 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
1671 && (((prev_pinfo & INSN_LOAD_COPROC_DELAY)
1672 && ! cop_interlocks)
1673 || (! gpr_interlocks
1674 && (prev_pinfo & INSN_LOAD_MEMORY_DELAY))))
1676 /* A load from a coprocessor or from memory. All load
1677 delays delay the use of general register rt for one
1678 instruction on the r3000. The r6000 and r4000 use
1680 /* Itbl support may require additional care here. */
1681 know (prev_pinfo & INSN_WRITE_GPR_T);
1682 if (mips_optimize == 0
1683 || insn_uses_reg (ip,
1684 ((prev_insn.insn_opcode >> OP_SH_RT)
1689 else if (! mips_opts.mips16
1690 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
1691 && (((prev_pinfo & INSN_COPROC_MOVE_DELAY)
1692 && ! cop_interlocks)
1693 || (mips_opts.isa == ISA_MIPS1
1694 && (prev_pinfo & INSN_COPROC_MEMORY_DELAY))))
1696 /* A generic coprocessor delay. The previous instruction
1697 modified a coprocessor general or control register. If
1698 it modified a control register, we need to avoid any
1699 coprocessor instruction (this is probably not always
1700 required, but it sometimes is). If it modified a general
1701 register, we avoid using that register.
1703 On the r6000 and r4000 loading a coprocessor register
1704 from memory is interlocked, and does not require a delay.
1706 This case is not handled very well. There is no special
1707 knowledge of CP0 handling, and the coprocessors other
1708 than the floating point unit are not distinguished at
1710 /* Itbl support may require additional care here. FIXME!
1711 Need to modify this to include knowledge about
1712 user specified delays! */
1713 if (prev_pinfo & INSN_WRITE_FPR_T)
1715 if (mips_optimize == 0
1716 || insn_uses_reg (ip,
1717 ((prev_insn.insn_opcode >> OP_SH_FT)
1722 else if (prev_pinfo & INSN_WRITE_FPR_S)
1724 if (mips_optimize == 0
1725 || insn_uses_reg (ip,
1726 ((prev_insn.insn_opcode >> OP_SH_FS)
1733 /* We don't know exactly what the previous instruction
1734 does. If the current instruction uses a coprocessor
1735 register, we must insert a NOP. If previous
1736 instruction may set the condition codes, and the
1737 current instruction uses them, we must insert two
1739 /* Itbl support may require additional care here. */
1740 if (mips_optimize == 0
1741 || ((prev_pinfo & INSN_WRITE_COND_CODE)
1742 && (pinfo & INSN_READ_COND_CODE)))
1744 else if (pinfo & INSN_COP)
1748 else if (! mips_opts.mips16
1749 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
1750 && (prev_pinfo & INSN_WRITE_COND_CODE)
1751 && ! cop_interlocks)
1753 /* The previous instruction sets the coprocessor condition
1754 codes, but does not require a general coprocessor delay
1755 (this means it is a floating point comparison
1756 instruction). If this instruction uses the condition
1757 codes, we need to insert a single NOP. */
1758 /* Itbl support may require additional care here. */
1759 if (mips_optimize == 0
1760 || (pinfo & INSN_READ_COND_CODE))
1764 /* If we're fixing up mfhi/mflo for the r7000 and the
1765 previous insn was an mfhi/mflo and the current insn
1766 reads the register that the mfhi/mflo wrote to, then
1769 else if (mips_7000_hilo_fix
1770 && MF_HILO_INSN (prev_pinfo)
1771 && insn_uses_reg (ip, ((prev_insn.insn_opcode >> OP_SH_RD)
1778 /* If we're fixing up mfhi/mflo for the r7000 and the
1779 2nd previous insn was an mfhi/mflo and the current insn
1780 reads the register that the mfhi/mflo wrote to, then
1783 else if (mips_7000_hilo_fix
1784 && MF_HILO_INSN (prev_prev_insn.insn_opcode)
1785 && insn_uses_reg (ip, ((prev_prev_insn.insn_opcode >> OP_SH_RD)
1793 else if (prev_pinfo & INSN_READ_LO)
1795 /* The previous instruction reads the LO register; if the
1796 current instruction writes to the LO register, we must
1797 insert two NOPS. Some newer processors have interlocks.
1798 Also the tx39's multiply instructions can be exectuted
1799 immediatly after a read from HI/LO (without the delay),
1800 though the tx39's divide insns still do require the
1802 if (! (hilo_interlocks
1803 || (mips_tune == CPU_R3900 && (pinfo & INSN_MULT)))
1804 && (mips_optimize == 0
1805 || (pinfo & INSN_WRITE_LO)))
1807 /* Most mips16 branch insns don't have a delay slot.
1808 If a read from LO is immediately followed by a branch
1809 to a write to LO we have a read followed by a write
1810 less than 2 insns away. We assume the target of
1811 a branch might be a write to LO, and insert a nop
1812 between a read and an immediately following branch. */
1813 else if (mips_opts.mips16
1814 && (mips_optimize == 0
1815 || (pinfo & MIPS16_INSN_BRANCH)))
1818 else if (prev_insn.insn_mo->pinfo & INSN_READ_HI)
1820 /* The previous instruction reads the HI register; if the
1821 current instruction writes to the HI register, we must
1822 insert a NOP. Some newer processors have interlocks.
1823 Also the note tx39's multiply above. */
1824 if (! (hilo_interlocks
1825 || (mips_tune == CPU_R3900 && (pinfo & INSN_MULT)))
1826 && (mips_optimize == 0
1827 || (pinfo & INSN_WRITE_HI)))
1829 /* Most mips16 branch insns don't have a delay slot.
1830 If a read from HI is immediately followed by a branch
1831 to a write to HI we have a read followed by a write
1832 less than 2 insns away. We assume the target of
1833 a branch might be a write to HI, and insert a nop
1834 between a read and an immediately following branch. */
1835 else if (mips_opts.mips16
1836 && (mips_optimize == 0
1837 || (pinfo & MIPS16_INSN_BRANCH)))
1841 /* If the previous instruction was in a noreorder section, then
1842 we don't want to insert the nop after all. */
1843 /* Itbl support may require additional care here. */
1844 if (prev_insn_unreordered)
1847 /* There are two cases which require two intervening
1848 instructions: 1) setting the condition codes using a move to
1849 coprocessor instruction which requires a general coprocessor
1850 delay and then reading the condition codes 2) reading the HI
1851 or LO register and then writing to it (except on processors
1852 which have interlocks). If we are not already emitting a NOP
1853 instruction, we must check for these cases compared to the
1854 instruction previous to the previous instruction. */
1855 if ((! mips_opts.mips16
1856 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
1857 && (prev_prev_insn.insn_mo->pinfo & INSN_COPROC_MOVE_DELAY)
1858 && (prev_prev_insn.insn_mo->pinfo & INSN_WRITE_COND_CODE)
1859 && (pinfo & INSN_READ_COND_CODE)
1860 && ! cop_interlocks)
1861 || ((prev_prev_insn.insn_mo->pinfo & INSN_READ_LO)
1862 && (pinfo & INSN_WRITE_LO)
1863 && ! (hilo_interlocks
1864 || (mips_tune == CPU_R3900 && (pinfo & INSN_MULT))))
1865 || ((prev_prev_insn.insn_mo->pinfo & INSN_READ_HI)
1866 && (pinfo & INSN_WRITE_HI)
1867 && ! (hilo_interlocks
1868 || (mips_tune == CPU_R3900 && (pinfo & INSN_MULT)))))
1873 if (prev_prev_insn_unreordered)
1876 if (prev_prev_nop && nops == 0)
1879 if (mips_fix_4122_bugs && prev_insn.insn_mo->name)
1881 /* We're out of bits in pinfo, so we must resort to string
1882 ops here. Shortcuts are selected based on opcodes being
1883 limited to the VR4122 instruction set. */
1885 const char *pn = prev_insn.insn_mo->name;
1886 const char *tn = ip->insn_mo->name;
1887 if (strncmp(pn, "macc", 4) == 0
1888 || strncmp(pn, "dmacc", 5) == 0)
1890 /* Errata 21 - [D]DIV[U] after [D]MACC */
1891 if (strstr (tn, "div"))
1896 /* Errata 23 - Continuous DMULT[U]/DMACC instructions */
1897 if (pn[0] == 'd' /* dmacc */
1898 && (strncmp(tn, "dmult", 5) == 0
1899 || strncmp(tn, "dmacc", 5) == 0))
1904 /* Errata 24 - MT{LO,HI} after [D]MACC */
1905 if (strcmp (tn, "mtlo") == 0
1906 || strcmp (tn, "mthi") == 0)
1912 else if (strncmp(pn, "dmult", 5) == 0
1913 && (strncmp(tn, "dmult", 5) == 0
1914 || strncmp(tn, "dmacc", 5) == 0))
1916 /* Here is the rest of errata 23. */
1919 if (nops < min_nops)
1923 /* If we are being given a nop instruction, don't bother with
1924 one of the nops we would otherwise output. This will only
1925 happen when a nop instruction is used with mips_optimize set
1928 && ! mips_opts.noreorder
1929 && ip->insn_opcode == (unsigned) (mips_opts.mips16 ? 0x6500 : 0))
1932 /* Now emit the right number of NOP instructions. */
1933 if (nops > 0 && ! mips_opts.noreorder)
1936 unsigned long old_frag_offset;
1938 struct insn_label_list *l;
1940 old_frag = frag_now;
1941 old_frag_offset = frag_now_fix ();
1943 for (i = 0; i < nops; i++)
1948 listing_prev_line ();
1949 /* We may be at the start of a variant frag. In case we
1950 are, make sure there is enough space for the frag
1951 after the frags created by listing_prev_line. The
1952 argument to frag_grow here must be at least as large
1953 as the argument to all other calls to frag_grow in
1954 this file. We don't have to worry about being in the
1955 middle of a variant frag, because the variants insert
1956 all needed nop instructions themselves. */
1960 for (l = insn_labels; l != NULL; l = l->next)
1964 assert (S_GET_SEGMENT (l->label) == now_seg);
1965 symbol_set_frag (l->label, frag_now);
1966 val = (valueT) frag_now_fix ();
1967 /* mips16 text labels are stored as odd. */
1968 if (mips_opts.mips16)
1970 S_SET_VALUE (l->label, val);
1973 #ifndef NO_ECOFF_DEBUGGING
1974 if (ECOFF_DEBUGGING)
1975 ecoff_fix_loc (old_frag, old_frag_offset);
1978 else if (prev_nop_frag != NULL)
1980 /* We have a frag holding nops we may be able to remove. If
1981 we don't need any nops, we can decrease the size of
1982 prev_nop_frag by the size of one instruction. If we do
1983 need some nops, we count them in prev_nops_required. */
1984 if (prev_nop_frag_since == 0)
1988 prev_nop_frag->fr_fix -= mips_opts.mips16 ? 2 : 4;
1989 --prev_nop_frag_holds;
1992 prev_nop_frag_required += nops;
1996 if (prev_prev_nop == 0)
1998 prev_nop_frag->fr_fix -= mips_opts.mips16 ? 2 : 4;
1999 --prev_nop_frag_holds;
2002 ++prev_nop_frag_required;
2005 if (prev_nop_frag_holds <= prev_nop_frag_required)
2006 prev_nop_frag = NULL;
2008 ++prev_nop_frag_since;
2010 /* Sanity check: by the time we reach the second instruction
2011 after prev_nop_frag, we should have used up all the nops
2012 one way or another. */
2013 assert (prev_nop_frag_since <= 1 || prev_nop_frag == NULL);
2019 && *reloc_type == BFD_RELOC_16_PCREL_S2
2020 && (pinfo & INSN_UNCOND_BRANCH_DELAY || pinfo & INSN_COND_BRANCH_DELAY
2021 || pinfo & INSN_COND_BRANCH_LIKELY)
2022 && mips_relax_branch
2023 /* Don't try branch relaxation within .set nomacro, or within
2024 .set noat if we use $at for PIC computations. If it turns
2025 out that the branch was out-of-range, we'll get an error. */
2026 && !mips_opts.warn_about_macros
2027 && !(mips_opts.noat && mips_pic != NO_PIC)
2028 && !mips_opts.mips16)
2030 f = frag_var (rs_machine_dependent,
2031 relaxed_branch_length
2033 (pinfo & INSN_UNCOND_BRANCH_DELAY) ? -1
2034 : (pinfo & INSN_COND_BRANCH_LIKELY) ? 1 : 0), 4,
2036 (pinfo & INSN_UNCOND_BRANCH_DELAY,
2037 pinfo & INSN_COND_BRANCH_LIKELY,
2038 pinfo & INSN_WRITE_GPR_31,
2040 address_expr->X_add_symbol,
2041 address_expr->X_add_number,
2043 *reloc_type = BFD_RELOC_UNUSED;
2045 else if (*reloc_type > BFD_RELOC_UNUSED)
2047 /* We need to set up a variant frag. */
2048 assert (mips_opts.mips16 && address_expr != NULL);
2049 f = frag_var (rs_machine_dependent, 4, 0,
2050 RELAX_MIPS16_ENCODE (*reloc_type - BFD_RELOC_UNUSED,
2051 mips16_small, mips16_ext,
2053 & INSN_UNCOND_BRANCH_DELAY),
2054 (*prev_insn_reloc_type
2055 == BFD_RELOC_MIPS16_JMP)),
2056 make_expr_symbol (address_expr), 0, NULL);
2058 else if (place != NULL)
2060 else if (mips_opts.mips16
2062 && *reloc_type != BFD_RELOC_MIPS16_JMP)
2064 /* Make sure there is enough room to swap this instruction with
2065 a following jump instruction. */
2071 if (mips_opts.mips16
2072 && mips_opts.noreorder
2073 && (prev_pinfo & INSN_UNCOND_BRANCH_DELAY) != 0)
2074 as_warn (_("extended instruction in delay slot"));
2079 fixp[0] = fixp[1] = fixp[2] = NULL;
2080 if (address_expr != NULL && *reloc_type < BFD_RELOC_UNUSED)
2082 if (address_expr->X_op == O_constant)
2086 switch (*reloc_type)
2089 ip->insn_opcode |= address_expr->X_add_number;
2092 case BFD_RELOC_MIPS_HIGHEST:
2093 tmp = (address_expr->X_add_number + 0x800080008000) >> 16;
2095 ip->insn_opcode |= (tmp >> 16) & 0xffff;
2098 case BFD_RELOC_MIPS_HIGHER:
2099 tmp = (address_expr->X_add_number + 0x80008000) >> 16;
2100 ip->insn_opcode |= (tmp >> 16) & 0xffff;
2103 case BFD_RELOC_HI16_S:
2104 ip->insn_opcode |= ((address_expr->X_add_number + 0x8000)
2108 case BFD_RELOC_HI16:
2109 ip->insn_opcode |= (address_expr->X_add_number >> 16) & 0xffff;
2112 case BFD_RELOC_LO16:
2113 case BFD_RELOC_MIPS_GOT_DISP:
2114 ip->insn_opcode |= address_expr->X_add_number & 0xffff;
2117 case BFD_RELOC_MIPS_JMP:
2118 if ((address_expr->X_add_number & 3) != 0)
2119 as_bad (_("jump to misaligned address (0x%lx)"),
2120 (unsigned long) address_expr->X_add_number);
2121 if (address_expr->X_add_number & ~0xfffffff)
2122 as_bad (_("jump address range overflow (0x%lx)"),
2123 (unsigned long) address_expr->X_add_number);
2124 ip->insn_opcode |= (address_expr->X_add_number >> 2) & 0x3ffffff;
2127 case BFD_RELOC_MIPS16_JMP:
2128 if ((address_expr->X_add_number & 3) != 0)
2129 as_bad (_("jump to misaligned address (0x%lx)"),
2130 (unsigned long) address_expr->X_add_number);
2131 if (address_expr->X_add_number & ~0xfffffff)
2132 as_bad (_("jump address range overflow (0x%lx)"),
2133 (unsigned long) address_expr->X_add_number);
2135 (((address_expr->X_add_number & 0x7c0000) << 3)
2136 | ((address_expr->X_add_number & 0xf800000) >> 7)
2137 | ((address_expr->X_add_number & 0x3fffc) >> 2));
2140 case BFD_RELOC_16_PCREL_S2:
2150 /* Don't generate a reloc if we are writing into a variant frag. */
2153 fixp[0] = fix_new_exp (frag_now, f - frag_now->fr_literal, 4,
2155 *reloc_type == BFD_RELOC_16_PCREL_S2,
2158 /* These relocations can have an addend that won't fit in
2159 4 octets for 64bit assembly. */
2160 if (HAVE_64BIT_GPRS &&
2161 (*reloc_type == BFD_RELOC_16
2162 || *reloc_type == BFD_RELOC_32
2163 || *reloc_type == BFD_RELOC_MIPS_JMP
2164 || *reloc_type == BFD_RELOC_HI16_S
2165 || *reloc_type == BFD_RELOC_LO16
2166 || *reloc_type == BFD_RELOC_GPREL16
2167 || *reloc_type == BFD_RELOC_MIPS_LITERAL
2168 || *reloc_type == BFD_RELOC_GPREL32
2169 || *reloc_type == BFD_RELOC_64
2170 || *reloc_type == BFD_RELOC_CTOR
2171 || *reloc_type == BFD_RELOC_MIPS_SUB
2172 || *reloc_type == BFD_RELOC_MIPS_HIGHEST
2173 || *reloc_type == BFD_RELOC_MIPS_HIGHER
2174 || *reloc_type == BFD_RELOC_MIPS_SCN_DISP
2175 || *reloc_type == BFD_RELOC_MIPS_REL16
2176 || *reloc_type == BFD_RELOC_MIPS_RELGOT))
2177 fixp[0]->fx_no_overflow = 1;
2181 struct mips_hi_fixup *hi_fixup;
2183 assert (*reloc_type == BFD_RELOC_HI16_S);
2184 hi_fixup = ((struct mips_hi_fixup *)
2185 xmalloc (sizeof (struct mips_hi_fixup)));
2186 hi_fixup->fixp = fixp[0];
2187 hi_fixup->seg = now_seg;
2188 hi_fixup->next = mips_hi_fixup_list;
2189 mips_hi_fixup_list = hi_fixup;
2192 if (reloc_type[1] != BFD_RELOC_UNUSED)
2194 /* FIXME: This symbol can be one of
2195 RSS_UNDEF, RSS_GP, RSS_GP0, RSS_LOC. */
2196 address_expr->X_op = O_absent;
2197 address_expr->X_add_symbol = 0;
2198 address_expr->X_add_number = 0;
2200 fixp[1] = fix_new_exp (frag_now, f - frag_now->fr_literal,
2201 4, address_expr, FALSE,
2204 /* These relocations can have an addend that won't fit in
2205 4 octets for 64bit assembly. */
2206 if (HAVE_64BIT_GPRS &&
2207 (*reloc_type == BFD_RELOC_16
2208 || *reloc_type == BFD_RELOC_32
2209 || *reloc_type == BFD_RELOC_MIPS_JMP
2210 || *reloc_type == BFD_RELOC_HI16_S
2211 || *reloc_type == BFD_RELOC_LO16
2212 || *reloc_type == BFD_RELOC_GPREL16
2213 || *reloc_type == BFD_RELOC_MIPS_LITERAL
2214 || *reloc_type == BFD_RELOC_GPREL32
2215 || *reloc_type == BFD_RELOC_64
2216 || *reloc_type == BFD_RELOC_CTOR
2217 || *reloc_type == BFD_RELOC_MIPS_SUB
2218 || *reloc_type == BFD_RELOC_MIPS_HIGHEST
2219 || *reloc_type == BFD_RELOC_MIPS_HIGHER
2220 || *reloc_type == BFD_RELOC_MIPS_SCN_DISP
2221 || *reloc_type == BFD_RELOC_MIPS_REL16
2222 || *reloc_type == BFD_RELOC_MIPS_RELGOT))
2223 fixp[1]->fx_no_overflow = 1;
2225 if (reloc_type[2] != BFD_RELOC_UNUSED)
2227 address_expr->X_op = O_absent;
2228 address_expr->X_add_symbol = 0;
2229 address_expr->X_add_number = 0;
2231 fixp[2] = fix_new_exp (frag_now,
2232 f - frag_now->fr_literal, 4,
2233 address_expr, FALSE,
2236 /* These relocations can have an addend that won't fit in
2237 4 octets for 64bit assembly. */
2238 if (HAVE_64BIT_GPRS &&
2239 (*reloc_type == BFD_RELOC_16
2240 || *reloc_type == BFD_RELOC_32
2241 || *reloc_type == BFD_RELOC_MIPS_JMP
2242 || *reloc_type == BFD_RELOC_HI16_S
2243 || *reloc_type == BFD_RELOC_LO16
2244 || *reloc_type == BFD_RELOC_GPREL16
2245 || *reloc_type == BFD_RELOC_MIPS_LITERAL
2246 || *reloc_type == BFD_RELOC_GPREL32
2247 || *reloc_type == BFD_RELOC_64
2248 || *reloc_type == BFD_RELOC_CTOR
2249 || *reloc_type == BFD_RELOC_MIPS_SUB
2250 || *reloc_type == BFD_RELOC_MIPS_HIGHEST
2251 || *reloc_type == BFD_RELOC_MIPS_HIGHER
2252 || *reloc_type == BFD_RELOC_MIPS_SCN_DISP
2253 || *reloc_type == BFD_RELOC_MIPS_REL16
2254 || *reloc_type == BFD_RELOC_MIPS_RELGOT))
2255 fixp[2]->fx_no_overflow = 1;
2262 if (! mips_opts.mips16)
2264 md_number_to_chars (f, ip->insn_opcode, 4);
2266 dwarf2_emit_insn (4);
2269 else if (*reloc_type == BFD_RELOC_MIPS16_JMP)
2271 md_number_to_chars (f, ip->insn_opcode >> 16, 2);
2272 md_number_to_chars (f + 2, ip->insn_opcode & 0xffff, 2);
2274 dwarf2_emit_insn (4);
2281 md_number_to_chars (f, 0xf000 | ip->extend, 2);
2284 md_number_to_chars (f, ip->insn_opcode, 2);
2286 dwarf2_emit_insn (ip->use_extend ? 4 : 2);
2290 /* Update the register mask information. */
2291 if (! mips_opts.mips16)
2293 if (pinfo & INSN_WRITE_GPR_D)
2294 mips_gprmask |= 1 << ((ip->insn_opcode >> OP_SH_RD) & OP_MASK_RD);
2295 if ((pinfo & (INSN_WRITE_GPR_T | INSN_READ_GPR_T)) != 0)
2296 mips_gprmask |= 1 << ((ip->insn_opcode >> OP_SH_RT) & OP_MASK_RT);
2297 if (pinfo & INSN_READ_GPR_S)
2298 mips_gprmask |= 1 << ((ip->insn_opcode >> OP_SH_RS) & OP_MASK_RS);
2299 if (pinfo & INSN_WRITE_GPR_31)
2300 mips_gprmask |= 1 << RA;
2301 if (pinfo & INSN_WRITE_FPR_D)
2302 mips_cprmask[1] |= 1 << ((ip->insn_opcode >> OP_SH_FD) & OP_MASK_FD);
2303 if ((pinfo & (INSN_WRITE_FPR_S | INSN_READ_FPR_S)) != 0)
2304 mips_cprmask[1] |= 1 << ((ip->insn_opcode >> OP_SH_FS) & OP_MASK_FS);
2305 if ((pinfo & (INSN_WRITE_FPR_T | INSN_READ_FPR_T)) != 0)
2306 mips_cprmask[1] |= 1 << ((ip->insn_opcode >> OP_SH_FT) & OP_MASK_FT);
2307 if ((pinfo & INSN_READ_FPR_R) != 0)
2308 mips_cprmask[1] |= 1 << ((ip->insn_opcode >> OP_SH_FR) & OP_MASK_FR);
2309 if (pinfo & INSN_COP)
2311 /* We don't keep enough information to sort these cases out.
2312 The itbl support does keep this information however, although
2313 we currently don't support itbl fprmats as part of the cop
2314 instruction. May want to add this support in the future. */
2316 /* Never set the bit for $0, which is always zero. */
2317 mips_gprmask &= ~1 << 0;
2321 if (pinfo & (MIPS16_INSN_WRITE_X | MIPS16_INSN_READ_X))
2322 mips_gprmask |= 1 << ((ip->insn_opcode >> MIPS16OP_SH_RX)
2323 & MIPS16OP_MASK_RX);
2324 if (pinfo & (MIPS16_INSN_WRITE_Y | MIPS16_INSN_READ_Y))
2325 mips_gprmask |= 1 << ((ip->insn_opcode >> MIPS16OP_SH_RY)
2326 & MIPS16OP_MASK_RY);
2327 if (pinfo & MIPS16_INSN_WRITE_Z)
2328 mips_gprmask |= 1 << ((ip->insn_opcode >> MIPS16OP_SH_RZ)
2329 & MIPS16OP_MASK_RZ);
2330 if (pinfo & (MIPS16_INSN_WRITE_T | MIPS16_INSN_READ_T))
2331 mips_gprmask |= 1 << TREG;
2332 if (pinfo & (MIPS16_INSN_WRITE_SP | MIPS16_INSN_READ_SP))
2333 mips_gprmask |= 1 << SP;
2334 if (pinfo & (MIPS16_INSN_WRITE_31 | MIPS16_INSN_READ_31))
2335 mips_gprmask |= 1 << RA;
2336 if (pinfo & MIPS16_INSN_WRITE_GPR_Y)
2337 mips_gprmask |= 1 << MIPS16OP_EXTRACT_REG32R (ip->insn_opcode);
2338 if (pinfo & MIPS16_INSN_READ_Z)
2339 mips_gprmask |= 1 << ((ip->insn_opcode >> MIPS16OP_SH_MOVE32Z)
2340 & MIPS16OP_MASK_MOVE32Z);
2341 if (pinfo & MIPS16_INSN_READ_GPR_X)
2342 mips_gprmask |= 1 << ((ip->insn_opcode >> MIPS16OP_SH_REGR32)
2343 & MIPS16OP_MASK_REGR32);
2346 if (place == NULL && ! mips_opts.noreorder)
2348 /* Filling the branch delay slot is more complex. We try to
2349 switch the branch with the previous instruction, which we can
2350 do if the previous instruction does not set up a condition
2351 that the branch tests and if the branch is not itself the
2352 target of any branch. */
2353 if ((pinfo & INSN_UNCOND_BRANCH_DELAY)
2354 || (pinfo & INSN_COND_BRANCH_DELAY))
2356 if (mips_optimize < 2
2357 /* If we have seen .set volatile or .set nomove, don't
2359 || mips_opts.nomove != 0
2360 /* If we had to emit any NOP instructions, then we
2361 already know we can not swap. */
2363 /* If we don't even know the previous insn, we can not
2365 || ! prev_insn_valid
2366 /* If the previous insn is already in a branch delay
2367 slot, then we can not swap. */
2368 || prev_insn_is_delay_slot
2369 /* If the previous previous insn was in a .set
2370 noreorder, we can't swap. Actually, the MIPS
2371 assembler will swap in this situation. However, gcc
2372 configured -with-gnu-as will generate code like
2378 in which we can not swap the bne and INSN. If gcc is
2379 not configured -with-gnu-as, it does not output the
2380 .set pseudo-ops. We don't have to check
2381 prev_insn_unreordered, because prev_insn_valid will
2382 be 0 in that case. We don't want to use
2383 prev_prev_insn_valid, because we do want to be able
2384 to swap at the start of a function. */
2385 || prev_prev_insn_unreordered
2386 /* If the branch is itself the target of a branch, we
2387 can not swap. We cheat on this; all we check for is
2388 whether there is a label on this instruction. If
2389 there are any branches to anything other than a
2390 label, users must use .set noreorder. */
2391 || insn_labels != NULL
2392 /* If the previous instruction is in a variant frag, we
2393 can not do the swap. This does not apply to the
2394 mips16, which uses variant frags for different
2396 || (! mips_opts.mips16
2397 && prev_insn_frag->fr_type == rs_machine_dependent)
2398 /* If the branch reads the condition codes, we don't
2399 even try to swap, because in the sequence
2404 we can not swap, and I don't feel like handling that
2406 || (! mips_opts.mips16
2407 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
2408 && (pinfo & INSN_READ_COND_CODE))
2409 /* We can not swap with an instruction that requires a
2410 delay slot, becase the target of the branch might
2411 interfere with that instruction. */
2412 || (! mips_opts.mips16
2413 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
2415 /* Itbl support may require additional care here. */
2416 & (INSN_LOAD_COPROC_DELAY
2417 | INSN_COPROC_MOVE_DELAY
2418 | INSN_WRITE_COND_CODE)))
2419 || (! (hilo_interlocks
2420 || (mips_tune == CPU_R3900 && (pinfo & INSN_MULT)))
2424 || (! mips_opts.mips16
2426 && (prev_pinfo & INSN_LOAD_MEMORY_DELAY))
2427 || (! mips_opts.mips16
2428 && mips_opts.isa == ISA_MIPS1
2429 /* Itbl support may require additional care here. */
2430 && (prev_pinfo & INSN_COPROC_MEMORY_DELAY))
2431 /* We can not swap with a branch instruction. */
2433 & (INSN_UNCOND_BRANCH_DELAY
2434 | INSN_COND_BRANCH_DELAY
2435 | INSN_COND_BRANCH_LIKELY))
2436 /* We do not swap with a trap instruction, since it
2437 complicates trap handlers to have the trap
2438 instruction be in a delay slot. */
2439 || (prev_pinfo & INSN_TRAP)
2440 /* If the branch reads a register that the previous
2441 instruction sets, we can not swap. */
2442 || (! mips_opts.mips16
2443 && (prev_pinfo & INSN_WRITE_GPR_T)
2444 && insn_uses_reg (ip,
2445 ((prev_insn.insn_opcode >> OP_SH_RT)
2448 || (! mips_opts.mips16
2449 && (prev_pinfo & INSN_WRITE_GPR_D)
2450 && insn_uses_reg (ip,
2451 ((prev_insn.insn_opcode >> OP_SH_RD)
2454 || (mips_opts.mips16
2455 && (((prev_pinfo & MIPS16_INSN_WRITE_X)
2456 && insn_uses_reg (ip,
2457 ((prev_insn.insn_opcode
2459 & MIPS16OP_MASK_RX),
2461 || ((prev_pinfo & MIPS16_INSN_WRITE_Y)
2462 && insn_uses_reg (ip,
2463 ((prev_insn.insn_opcode
2465 & MIPS16OP_MASK_RY),
2467 || ((prev_pinfo & MIPS16_INSN_WRITE_Z)
2468 && insn_uses_reg (ip,
2469 ((prev_insn.insn_opcode
2471 & MIPS16OP_MASK_RZ),
2473 || ((prev_pinfo & MIPS16_INSN_WRITE_T)
2474 && insn_uses_reg (ip, TREG, MIPS_GR_REG))
2475 || ((prev_pinfo & MIPS16_INSN_WRITE_31)
2476 && insn_uses_reg (ip, RA, MIPS_GR_REG))
2477 || ((prev_pinfo & MIPS16_INSN_WRITE_GPR_Y)
2478 && insn_uses_reg (ip,
2479 MIPS16OP_EXTRACT_REG32R (prev_insn.
2482 /* If the branch writes a register that the previous
2483 instruction sets, we can not swap (we know that
2484 branches write only to RD or to $31). */
2485 || (! mips_opts.mips16
2486 && (prev_pinfo & INSN_WRITE_GPR_T)
2487 && (((pinfo & INSN_WRITE_GPR_D)
2488 && (((prev_insn.insn_opcode >> OP_SH_RT) & OP_MASK_RT)
2489 == ((ip->insn_opcode >> OP_SH_RD) & OP_MASK_RD)))
2490 || ((pinfo & INSN_WRITE_GPR_31)
2491 && (((prev_insn.insn_opcode >> OP_SH_RT)
2494 || (! mips_opts.mips16
2495 && (prev_pinfo & INSN_WRITE_GPR_D)
2496 && (((pinfo & INSN_WRITE_GPR_D)
2497 && (((prev_insn.insn_opcode >> OP_SH_RD) & OP_MASK_RD)
2498 == ((ip->insn_opcode >> OP_SH_RD) & OP_MASK_RD)))
2499 || ((pinfo & INSN_WRITE_GPR_31)
2500 && (((prev_insn.insn_opcode >> OP_SH_RD)
2503 || (mips_opts.mips16
2504 && (pinfo & MIPS16_INSN_WRITE_31)
2505 && ((prev_pinfo & MIPS16_INSN_WRITE_31)
2506 || ((prev_pinfo & MIPS16_INSN_WRITE_GPR_Y)
2507 && (MIPS16OP_EXTRACT_REG32R (prev_insn.insn_opcode)
2509 /* If the branch writes a register that the previous
2510 instruction reads, we can not swap (we know that
2511 branches only write to RD or to $31). */
2512 || (! mips_opts.mips16
2513 && (pinfo & INSN_WRITE_GPR_D)
2514 && insn_uses_reg (&prev_insn,
2515 ((ip->insn_opcode >> OP_SH_RD)
2518 || (! mips_opts.mips16
2519 && (pinfo & INSN_WRITE_GPR_31)
2520 && insn_uses_reg (&prev_insn, RA, MIPS_GR_REG))
2521 || (mips_opts.mips16
2522 && (pinfo & MIPS16_INSN_WRITE_31)
2523 && insn_uses_reg (&prev_insn, RA, MIPS_GR_REG))
2524 /* If we are generating embedded PIC code, the branch
2525 might be expanded into a sequence which uses $at, so
2526 we can't swap with an instruction which reads it. */
2527 || (mips_pic == EMBEDDED_PIC
2528 && insn_uses_reg (&prev_insn, AT, MIPS_GR_REG))
2529 /* If the previous previous instruction has a load
2530 delay, and sets a register that the branch reads, we
2532 || (! mips_opts.mips16
2533 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
2534 /* Itbl support may require additional care here. */
2535 && ((prev_prev_insn.insn_mo->pinfo & INSN_LOAD_COPROC_DELAY)
2536 || (! gpr_interlocks
2537 && (prev_prev_insn.insn_mo->pinfo
2538 & INSN_LOAD_MEMORY_DELAY)))
2539 && insn_uses_reg (ip,
2540 ((prev_prev_insn.insn_opcode >> OP_SH_RT)
2543 /* If one instruction sets a condition code and the
2544 other one uses a condition code, we can not swap. */
2545 || ((pinfo & INSN_READ_COND_CODE)
2546 && (prev_pinfo & INSN_WRITE_COND_CODE))
2547 || ((pinfo & INSN_WRITE_COND_CODE)
2548 && (prev_pinfo & INSN_READ_COND_CODE))
2549 /* If the previous instruction uses the PC, we can not
2551 || (mips_opts.mips16
2552 && (prev_pinfo & MIPS16_INSN_READ_PC))
2553 /* If the previous instruction was extended, we can not
2555 || (mips_opts.mips16 && prev_insn_extended)
2556 /* If the previous instruction had a fixup in mips16
2557 mode, we can not swap. This normally means that the
2558 previous instruction was a 4 byte branch anyhow. */
2559 || (mips_opts.mips16 && prev_insn_fixp[0])
2560 /* If the previous instruction is a sync, sync.l, or
2561 sync.p, we can not swap. */
2562 || (prev_pinfo & INSN_SYNC))
2564 /* We could do even better for unconditional branches to
2565 portions of this object file; we could pick up the
2566 instruction at the destination, put it in the delay
2567 slot, and bump the destination address. */
2569 /* Update the previous insn information. */
2570 prev_prev_insn = *ip;
2571 prev_insn.insn_mo = &dummy_opcode;
2575 /* It looks like we can actually do the swap. */
2576 if (! mips_opts.mips16)
2581 prev_f = prev_insn_frag->fr_literal + prev_insn_where;
2582 memcpy (temp, prev_f, 4);
2583 memcpy (prev_f, f, 4);
2584 memcpy (f, temp, 4);
2585 if (prev_insn_fixp[0])
2587 prev_insn_fixp[0]->fx_frag = frag_now;
2588 prev_insn_fixp[0]->fx_where = f - frag_now->fr_literal;
2590 if (prev_insn_fixp[1])
2592 prev_insn_fixp[1]->fx_frag = frag_now;
2593 prev_insn_fixp[1]->fx_where = f - frag_now->fr_literal;
2595 if (prev_insn_fixp[2])
2597 prev_insn_fixp[2]->fx_frag = frag_now;
2598 prev_insn_fixp[2]->fx_where = f - frag_now->fr_literal;
2602 fixp[0]->fx_frag = prev_insn_frag;
2603 fixp[0]->fx_where = prev_insn_where;
2607 fixp[1]->fx_frag = prev_insn_frag;
2608 fixp[1]->fx_where = prev_insn_where;
2612 fixp[2]->fx_frag = prev_insn_frag;
2613 fixp[2]->fx_where = prev_insn_where;
2621 assert (prev_insn_fixp[0] == NULL);
2622 assert (prev_insn_fixp[1] == NULL);
2623 assert (prev_insn_fixp[2] == NULL);
2624 prev_f = prev_insn_frag->fr_literal + prev_insn_where;
2625 memcpy (temp, prev_f, 2);
2626 memcpy (prev_f, f, 2);
2627 if (*reloc_type != BFD_RELOC_MIPS16_JMP)
2629 assert (*reloc_type == BFD_RELOC_UNUSED);
2630 memcpy (f, temp, 2);
2634 memcpy (f, f + 2, 2);
2635 memcpy (f + 2, temp, 2);
2639 fixp[0]->fx_frag = prev_insn_frag;
2640 fixp[0]->fx_where = prev_insn_where;
2644 fixp[1]->fx_frag = prev_insn_frag;
2645 fixp[1]->fx_where = prev_insn_where;
2649 fixp[2]->fx_frag = prev_insn_frag;
2650 fixp[2]->fx_where = prev_insn_where;
2654 /* Update the previous insn information; leave prev_insn
2656 prev_prev_insn = *ip;
2658 prev_insn_is_delay_slot = 1;
2660 /* If that was an unconditional branch, forget the previous
2661 insn information. */
2662 if (pinfo & INSN_UNCOND_BRANCH_DELAY)
2664 prev_prev_insn.insn_mo = &dummy_opcode;
2665 prev_insn.insn_mo = &dummy_opcode;
2668 prev_insn_fixp[0] = NULL;
2669 prev_insn_fixp[1] = NULL;
2670 prev_insn_fixp[2] = NULL;
2671 prev_insn_reloc_type[0] = BFD_RELOC_UNUSED;
2672 prev_insn_reloc_type[1] = BFD_RELOC_UNUSED;
2673 prev_insn_reloc_type[2] = BFD_RELOC_UNUSED;
2674 prev_insn_extended = 0;
2676 else if (pinfo & INSN_COND_BRANCH_LIKELY)
2678 /* We don't yet optimize a branch likely. What we should do
2679 is look at the target, copy the instruction found there
2680 into the delay slot, and increment the branch to jump to
2681 the next instruction. */
2683 /* Update the previous insn information. */
2684 prev_prev_insn = *ip;
2685 prev_insn.insn_mo = &dummy_opcode;
2686 prev_insn_fixp[0] = NULL;
2687 prev_insn_fixp[1] = NULL;
2688 prev_insn_fixp[2] = NULL;
2689 prev_insn_reloc_type[0] = BFD_RELOC_UNUSED;
2690 prev_insn_reloc_type[1] = BFD_RELOC_UNUSED;
2691 prev_insn_reloc_type[2] = BFD_RELOC_UNUSED;
2692 prev_insn_extended = 0;
2696 /* Update the previous insn information. */
2698 prev_prev_insn.insn_mo = &dummy_opcode;
2700 prev_prev_insn = prev_insn;
2703 /* Any time we see a branch, we always fill the delay slot
2704 immediately; since this insn is not a branch, we know it
2705 is not in a delay slot. */
2706 prev_insn_is_delay_slot = 0;
2708 prev_insn_fixp[0] = fixp[0];
2709 prev_insn_fixp[1] = fixp[1];
2710 prev_insn_fixp[2] = fixp[2];
2711 prev_insn_reloc_type[0] = reloc_type[0];
2712 prev_insn_reloc_type[1] = reloc_type[1];
2713 prev_insn_reloc_type[2] = reloc_type[2];
2714 if (mips_opts.mips16)
2715 prev_insn_extended = (ip->use_extend
2716 || *reloc_type > BFD_RELOC_UNUSED);
2719 prev_prev_insn_unreordered = prev_insn_unreordered;
2720 prev_insn_unreordered = 0;
2721 prev_insn_frag = frag_now;
2722 prev_insn_where = f - frag_now->fr_literal;
2723 prev_insn_valid = 1;
2725 else if (place == NULL)
2727 /* We need to record a bit of information even when we are not
2728 reordering, in order to determine the base address for mips16
2729 PC relative relocs. */
2730 prev_prev_insn = prev_insn;
2732 prev_insn_reloc_type[0] = reloc_type[0];
2733 prev_insn_reloc_type[1] = reloc_type[1];
2734 prev_insn_reloc_type[2] = reloc_type[2];
2735 prev_prev_insn_unreordered = prev_insn_unreordered;
2736 prev_insn_unreordered = 1;
2739 /* We just output an insn, so the next one doesn't have a label. */
2740 mips_clear_insn_labels ();
2742 /* We must ensure that a fixup associated with an unmatched %hi
2743 reloc does not become a variant frag. Otherwise, the
2744 rearrangement of %hi relocs in frob_file may confuse
2748 frag_wane (frag_now);
2753 /* This function forgets that there was any previous instruction or
2754 label. If PRESERVE is non-zero, it remembers enough information to
2755 know whether nops are needed before a noreorder section. */
2758 mips_no_prev_insn (preserve)
2763 prev_insn.insn_mo = &dummy_opcode;
2764 prev_prev_insn.insn_mo = &dummy_opcode;
2765 prev_nop_frag = NULL;
2766 prev_nop_frag_holds = 0;
2767 prev_nop_frag_required = 0;
2768 prev_nop_frag_since = 0;
2770 prev_insn_valid = 0;
2771 prev_insn_is_delay_slot = 0;
2772 prev_insn_unreordered = 0;
2773 prev_insn_extended = 0;
2774 prev_insn_reloc_type[0] = BFD_RELOC_UNUSED;
2775 prev_insn_reloc_type[1] = BFD_RELOC_UNUSED;
2776 prev_insn_reloc_type[2] = BFD_RELOC_UNUSED;
2777 prev_prev_insn_unreordered = 0;
2778 mips_clear_insn_labels ();
2781 /* This function must be called whenever we turn on noreorder or emit
2782 something other than instructions. It inserts any NOPS which might
2783 be needed by the previous instruction, and clears the information
2784 kept for the previous instructions. The INSNS parameter is true if
2785 instructions are to follow. */
2788 mips_emit_delays (insns)
2791 if (! mips_opts.noreorder)
2796 if ((! mips_opts.mips16
2797 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
2798 && (! cop_interlocks
2799 && (prev_insn.insn_mo->pinfo
2800 & (INSN_LOAD_COPROC_DELAY
2801 | INSN_COPROC_MOVE_DELAY
2802 | INSN_WRITE_COND_CODE))))
2803 || (! hilo_interlocks
2804 && (prev_insn.insn_mo->pinfo
2807 || (! mips_opts.mips16
2809 && (prev_insn.insn_mo->pinfo
2810 & INSN_LOAD_MEMORY_DELAY))
2811 || (! mips_opts.mips16
2812 && mips_opts.isa == ISA_MIPS1
2813 && (prev_insn.insn_mo->pinfo
2814 & INSN_COPROC_MEMORY_DELAY)))
2816 /* Itbl support may require additional care here. */
2818 if ((! mips_opts.mips16
2819 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
2820 && (! cop_interlocks
2821 && prev_insn.insn_mo->pinfo & INSN_WRITE_COND_CODE))
2822 || (! hilo_interlocks
2823 && ((prev_insn.insn_mo->pinfo & INSN_READ_HI)
2824 || (prev_insn.insn_mo->pinfo & INSN_READ_LO))))
2827 if (prev_insn_unreordered)
2830 else if ((! mips_opts.mips16
2831 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
2832 && (! cop_interlocks
2833 && prev_prev_insn.insn_mo->pinfo & INSN_WRITE_COND_CODE))
2834 || (! hilo_interlocks
2835 && ((prev_prev_insn.insn_mo->pinfo & INSN_READ_HI)
2836 || (prev_prev_insn.insn_mo->pinfo & INSN_READ_LO))))
2838 /* Itbl support may require additional care here. */
2839 if (! prev_prev_insn_unreordered)
2843 if (mips_fix_4122_bugs && prev_insn.insn_mo->name)
2846 const char *pn = prev_insn.insn_mo->name;
2847 if (strncmp(pn, "macc", 4) == 0
2848 || strncmp(pn, "dmacc", 5) == 0
2849 || strncmp(pn, "dmult", 5) == 0)
2853 if (nops < min_nops)
2859 struct insn_label_list *l;
2863 /* Record the frag which holds the nop instructions, so
2864 that we can remove them if we don't need them. */
2865 frag_grow (mips_opts.mips16 ? nops * 2 : nops * 4);
2866 prev_nop_frag = frag_now;
2867 prev_nop_frag_holds = nops;
2868 prev_nop_frag_required = 0;
2869 prev_nop_frag_since = 0;
2872 for (; nops > 0; --nops)
2877 /* Move on to a new frag, so that it is safe to simply
2878 decrease the size of prev_nop_frag. */
2879 frag_wane (frag_now);
2883 for (l = insn_labels; l != NULL; l = l->next)
2887 assert (S_GET_SEGMENT (l->label) == now_seg);
2888 symbol_set_frag (l->label, frag_now);
2889 val = (valueT) frag_now_fix ();
2890 /* mips16 text labels are stored as odd. */
2891 if (mips_opts.mips16)
2893 S_SET_VALUE (l->label, val);
2898 /* Mark instruction labels in mips16 mode. */
2900 mips16_mark_labels ();
2902 mips_no_prev_insn (insns);
2905 /* Build an instruction created by a macro expansion. This is passed
2906 a pointer to the count of instructions created so far, an
2907 expression, the name of the instruction to build, an operand format
2908 string, and corresponding arguments. */
2912 macro_build (char *place,
2920 macro_build (place, counter, ep, name, fmt, va_alist)
2929 struct mips_cl_insn insn;
2930 bfd_reloc_code_real_type r[3];
2934 va_start (args, fmt);
2940 * If the macro is about to expand into a second instruction,
2941 * print a warning if needed. We need to pass ip as a parameter
2942 * to generate a better warning message here...
2944 if (mips_opts.warn_about_macros && place == NULL && *counter == 1)
2945 as_warn (_("Macro instruction expanded into multiple instructions"));
2948 * If the macro is about to expand into a second instruction,
2949 * and it is in a delay slot, print a warning.
2953 && mips_opts.noreorder
2954 && (prev_prev_insn.insn_mo->pinfo
2955 & (INSN_UNCOND_BRANCH_DELAY | INSN_COND_BRANCH_DELAY
2956 | INSN_COND_BRANCH_LIKELY)) != 0)
2957 as_warn (_("Macro instruction expanded into multiple instructions in a branch delay slot"));
2960 ++*counter; /* bump instruction counter */
2962 if (mips_opts.mips16)
2964 mips16_macro_build (place, counter, ep, name, fmt, args);
2969 r[0] = BFD_RELOC_UNUSED;
2970 r[1] = BFD_RELOC_UNUSED;
2971 r[2] = BFD_RELOC_UNUSED;
2972 insn.insn_mo = (struct mips_opcode *) hash_find (op_hash, name);
2973 assert (insn.insn_mo);
2974 assert (strcmp (name, insn.insn_mo->name) == 0);
2976 /* Search until we get a match for NAME. */
2979 /* It is assumed here that macros will never generate
2980 MDMX or MIPS-3D instructions. */
2981 if (strcmp (fmt, insn.insn_mo->args) == 0
2982 && insn.insn_mo->pinfo != INSN_MACRO
2983 && OPCODE_IS_MEMBER (insn.insn_mo,
2985 | (file_ase_mips16 ? INSN_MIPS16 : 0)),
2987 && (mips_arch != CPU_R4650 || (insn.insn_mo->pinfo & FP_D) == 0))
2991 assert (insn.insn_mo->name);
2992 assert (strcmp (name, insn.insn_mo->name) == 0);
2995 insn.insn_opcode = insn.insn_mo->match;
3011 insn.insn_opcode |= va_arg (args, int) << OP_SH_RT;
3015 insn.insn_opcode |= va_arg (args, int) << OP_SH_CODE;
3020 insn.insn_opcode |= va_arg (args, int) << OP_SH_FT;
3026 insn.insn_opcode |= va_arg (args, int) << OP_SH_RD;
3031 int tmp = va_arg (args, int);
3033 insn.insn_opcode |= tmp << OP_SH_RT;
3034 insn.insn_opcode |= tmp << OP_SH_RD;
3040 insn.insn_opcode |= va_arg (args, int) << OP_SH_FS;
3047 insn.insn_opcode |= va_arg (args, int) << OP_SH_SHAMT;
3051 insn.insn_opcode |= va_arg (args, int) << OP_SH_FD;
3055 insn.insn_opcode |= va_arg (args, int) << OP_SH_CODE20;
3059 insn.insn_opcode |= va_arg (args, int) << OP_SH_CODE19;
3063 insn.insn_opcode |= va_arg (args, int) << OP_SH_CODE2;
3070 insn.insn_opcode |= va_arg (args, int) << OP_SH_RS;
3076 *r = (bfd_reloc_code_real_type) va_arg (args, int);
3077 assert (*r == BFD_RELOC_GPREL16
3078 || *r == BFD_RELOC_MIPS_LITERAL
3079 || *r == BFD_RELOC_MIPS_HIGHER
3080 || *r == BFD_RELOC_HI16_S
3081 || *r == BFD_RELOC_LO16
3082 || *r == BFD_RELOC_MIPS_GOT16
3083 || *r == BFD_RELOC_MIPS_CALL16
3084 || *r == BFD_RELOC_MIPS_GOT_DISP
3085 || *r == BFD_RELOC_MIPS_GOT_PAGE
3086 || *r == BFD_RELOC_MIPS_GOT_OFST
3087 || *r == BFD_RELOC_MIPS_GOT_LO16
3088 || *r == BFD_RELOC_MIPS_CALL_LO16
3089 || (ep->X_op == O_subtract
3090 && *r == BFD_RELOC_PCREL_LO16));
3094 *r = (bfd_reloc_code_real_type) va_arg (args, int);
3096 && (ep->X_op == O_constant
3097 || (ep->X_op == O_symbol
3098 && (*r == BFD_RELOC_MIPS_HIGHEST
3099 || *r == BFD_RELOC_HI16_S
3100 || *r == BFD_RELOC_HI16
3101 || *r == BFD_RELOC_GPREL16
3102 || *r == BFD_RELOC_MIPS_GOT_HI16
3103 || *r == BFD_RELOC_MIPS_CALL_HI16))
3104 || (ep->X_op == O_subtract
3105 && *r == BFD_RELOC_PCREL_HI16_S)));
3109 assert (ep != NULL);
3111 * This allows macro() to pass an immediate expression for
3112 * creating short branches without creating a symbol.
3113 * Note that the expression still might come from the assembly
3114 * input, in which case the value is not checked for range nor
3115 * is a relocation entry generated (yuck).
3117 if (ep->X_op == O_constant)
3119 insn.insn_opcode |= (ep->X_add_number >> 2) & 0xffff;
3123 *r = BFD_RELOC_16_PCREL_S2;
3127 assert (ep != NULL);
3128 *r = BFD_RELOC_MIPS_JMP;
3132 insn.insn_opcode |= va_arg (args, unsigned long);
3141 assert (*r == BFD_RELOC_UNUSED ? ep == NULL : ep != NULL);
3143 append_insn (place, &insn, ep, r, FALSE);
3147 mips16_macro_build (place, counter, ep, name, fmt, args)
3149 int *counter ATTRIBUTE_UNUSED;
3155 struct mips_cl_insn insn;
3156 bfd_reloc_code_real_type r[3]
3157 = {BFD_RELOC_UNUSED, BFD_RELOC_UNUSED, BFD_RELOC_UNUSED};
3159 insn.insn_mo = (struct mips_opcode *) hash_find (mips16_op_hash, name);
3160 assert (insn.insn_mo);
3161 assert (strcmp (name, insn.insn_mo->name) == 0);
3163 while (strcmp (fmt, insn.insn_mo->args) != 0
3164 || insn.insn_mo->pinfo == INSN_MACRO)
3167 assert (insn.insn_mo->name);
3168 assert (strcmp (name, insn.insn_mo->name) == 0);
3171 insn.insn_opcode = insn.insn_mo->match;
3172 insn.use_extend = FALSE;
3191 insn.insn_opcode |= va_arg (args, int) << MIPS16OP_SH_RY;
3196 insn.insn_opcode |= va_arg (args, int) << MIPS16OP_SH_RX;
3200 insn.insn_opcode |= va_arg (args, int) << MIPS16OP_SH_RZ;
3204 insn.insn_opcode |= va_arg (args, int) << MIPS16OP_SH_MOVE32Z;
3214 insn.insn_opcode |= va_arg (args, int) << MIPS16OP_SH_REGR32;
3221 regno = va_arg (args, int);
3222 regno = ((regno & 7) << 2) | ((regno & 0x18) >> 3);
3223 insn.insn_opcode |= regno << MIPS16OP_SH_REG32R;
3244 assert (ep != NULL);
3246 if (ep->X_op != O_constant)
3247 *r = (int) BFD_RELOC_UNUSED + c;
3250 mips16_immed (NULL, 0, c, ep->X_add_number, FALSE, FALSE,
3251 FALSE, &insn.insn_opcode, &insn.use_extend,
3254 *r = BFD_RELOC_UNUSED;
3260 insn.insn_opcode |= va_arg (args, int) << MIPS16OP_SH_IMM6;
3267 assert (*r == BFD_RELOC_UNUSED ? ep == NULL : ep != NULL);
3269 append_insn (place, &insn, ep, r, FALSE);
3273 * Generate a "jalr" instruction with a relocation hint to the called
3274 * function. This occurs in NewABI PIC code.
3277 macro_build_jalr (icnt, ep)
3288 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "jalr", "d,s",
3291 fix_new_exp (frag_now, f - frag_now->fr_literal,
3292 0, ep, FALSE, BFD_RELOC_MIPS_JALR);
3296 * Generate a "lui" instruction.
3299 macro_build_lui (place, counter, ep, regnum)
3305 expressionS high_expr;
3306 struct mips_cl_insn insn;
3307 bfd_reloc_code_real_type r[3]
3308 = {BFD_RELOC_UNUSED, BFD_RELOC_UNUSED, BFD_RELOC_UNUSED};
3309 const char *name = "lui";
3310 const char *fmt = "t,u";
3312 assert (! mips_opts.mips16);
3318 high_expr.X_op = O_constant;
3319 high_expr.X_add_number = ep->X_add_number;
3322 if (high_expr.X_op == O_constant)
3324 /* we can compute the instruction now without a relocation entry */
3325 high_expr.X_add_number = ((high_expr.X_add_number + 0x8000)
3327 *r = BFD_RELOC_UNUSED;
3331 assert (ep->X_op == O_symbol);
3332 /* _gp_disp is a special case, used from s_cpload. */
3333 assert (mips_pic == NO_PIC
3335 && strcmp (S_GET_NAME (ep->X_add_symbol), "_gp_disp") == 0));
3336 *r = BFD_RELOC_HI16_S;
3340 * If the macro is about to expand into a second instruction,
3341 * print a warning if needed. We need to pass ip as a parameter
3342 * to generate a better warning message here...
3344 if (mips_opts.warn_about_macros && place == NULL && *counter == 1)
3345 as_warn (_("Macro instruction expanded into multiple instructions"));
3348 ++*counter; /* bump instruction counter */
3350 insn.insn_mo = (struct mips_opcode *) hash_find (op_hash, name);
3351 assert (insn.insn_mo);
3352 assert (strcmp (name, insn.insn_mo->name) == 0);
3353 assert (strcmp (fmt, insn.insn_mo->args) == 0);
3355 insn.insn_opcode = insn.insn_mo->match | (regnum << OP_SH_RT);
3356 if (*r == BFD_RELOC_UNUSED)
3358 insn.insn_opcode |= high_expr.X_add_number;
3359 append_insn (place, &insn, NULL, r, FALSE);
3362 append_insn (place, &insn, &high_expr, r, FALSE);
3365 /* Generate a sequence of instructions to do a load or store from a constant
3366 offset off of a base register (breg) into/from a target register (treg),
3367 using AT if necessary. */
3369 macro_build_ldst_constoffset (place, counter, ep, op, treg, breg)
3376 assert (ep->X_op == O_constant);
3378 /* Right now, this routine can only handle signed 32-bit contants. */
3379 if (! IS_SEXT_32BIT_NUM(ep->X_add_number))
3380 as_warn (_("operand overflow"));
3382 if (IS_SEXT_16BIT_NUM(ep->X_add_number))
3384 /* Signed 16-bit offset will fit in the op. Easy! */
3385 macro_build (place, counter, ep, op, "t,o(b)", treg,
3386 (int) BFD_RELOC_LO16, breg);
3390 /* 32-bit offset, need multiple instructions and AT, like:
3391 lui $tempreg,const_hi (BFD_RELOC_HI16_S)
3392 addu $tempreg,$tempreg,$breg
3393 <op> $treg,const_lo($tempreg) (BFD_RELOC_LO16)
3394 to handle the complete offset. */
3395 macro_build_lui (place, counter, ep, AT);
3398 macro_build (place, counter, (expressionS *) NULL,
3399 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
3400 "d,v,t", AT, AT, breg);
3403 macro_build (place, counter, ep, op, "t,o(b)", treg,
3404 (int) BFD_RELOC_LO16, AT);
3407 as_warn (_("Macro used $at after \".set noat\""));
3412 * Generates code to set the $at register to true (one)
3413 * if reg is less than the immediate expression.
3416 set_at (counter, reg, unsignedp)
3421 if (imm_expr.X_op == O_constant
3422 && imm_expr.X_add_number >= -0x8000
3423 && imm_expr.X_add_number < 0x8000)
3424 macro_build ((char *) NULL, counter, &imm_expr,
3425 unsignedp ? "sltiu" : "slti",
3426 "t,r,j", AT, reg, (int) BFD_RELOC_LO16);
3429 load_register (counter, AT, &imm_expr, HAVE_64BIT_GPRS);
3430 macro_build ((char *) NULL, counter, (expressionS *) NULL,
3431 unsignedp ? "sltu" : "slt",
3432 "d,v,t", AT, reg, AT);
3436 /* Warn if an expression is not a constant. */
3439 check_absolute_expr (ip, ex)
3440 struct mips_cl_insn *ip;
3443 if (ex->X_op == O_big)
3444 as_bad (_("unsupported large constant"));
3445 else if (ex->X_op != O_constant)
3446 as_bad (_("Instruction %s requires absolute expression"), ip->insn_mo->name);
3449 /* Count the leading zeroes by performing a binary chop. This is a
3450 bulky bit of source, but performance is a LOT better for the
3451 majority of values than a simple loop to count the bits:
3452 for (lcnt = 0; (lcnt < 32); lcnt++)
3453 if ((v) & (1 << (31 - lcnt)))
3455 However it is not code size friendly, and the gain will drop a bit
3456 on certain cached systems.
3458 #define COUNT_TOP_ZEROES(v) \
3459 (((v) & ~0xffff) == 0 \
3460 ? ((v) & ~0xff) == 0 \
3461 ? ((v) & ~0xf) == 0 \
3462 ? ((v) & ~0x3) == 0 \
3463 ? ((v) & ~0x1) == 0 \
3468 : ((v) & ~0x7) == 0 \
3471 : ((v) & ~0x3f) == 0 \
3472 ? ((v) & ~0x1f) == 0 \
3475 : ((v) & ~0x7f) == 0 \
3478 : ((v) & ~0xfff) == 0 \
3479 ? ((v) & ~0x3ff) == 0 \
3480 ? ((v) & ~0x1ff) == 0 \
3483 : ((v) & ~0x7ff) == 0 \
3486 : ((v) & ~0x3fff) == 0 \
3487 ? ((v) & ~0x1fff) == 0 \
3490 : ((v) & ~0x7fff) == 0 \
3493 : ((v) & ~0xffffff) == 0 \
3494 ? ((v) & ~0xfffff) == 0 \
3495 ? ((v) & ~0x3ffff) == 0 \
3496 ? ((v) & ~0x1ffff) == 0 \
3499 : ((v) & ~0x7ffff) == 0 \
3502 : ((v) & ~0x3fffff) == 0 \
3503 ? ((v) & ~0x1fffff) == 0 \
3506 : ((v) & ~0x7fffff) == 0 \
3509 : ((v) & ~0xfffffff) == 0 \
3510 ? ((v) & ~0x3ffffff) == 0 \
3511 ? ((v) & ~0x1ffffff) == 0 \
3514 : ((v) & ~0x7ffffff) == 0 \
3517 : ((v) & ~0x3fffffff) == 0 \
3518 ? ((v) & ~0x1fffffff) == 0 \
3521 : ((v) & ~0x7fffffff) == 0 \
3526 * This routine generates the least number of instructions neccessary to load
3527 * an absolute expression value into a register.
3530 load_register (counter, reg, ep, dbl)
3537 expressionS hi32, lo32;
3539 if (ep->X_op != O_big)
3541 assert (ep->X_op == O_constant);
3542 if (ep->X_add_number < 0x8000
3543 && (ep->X_add_number >= 0
3544 || (ep->X_add_number >= -0x8000
3547 || sizeof (ep->X_add_number) > 4))))
3549 /* We can handle 16 bit signed values with an addiu to
3550 $zero. No need to ever use daddiu here, since $zero and
3551 the result are always correct in 32 bit mode. */
3552 macro_build ((char *) NULL, counter, ep, "addiu", "t,r,j", reg, 0,
3553 (int) BFD_RELOC_LO16);
3556 else if (ep->X_add_number >= 0 && ep->X_add_number < 0x10000)
3558 /* We can handle 16 bit unsigned values with an ori to
3560 macro_build ((char *) NULL, counter, ep, "ori", "t,r,i", reg, 0,
3561 (int) BFD_RELOC_LO16);
3564 else if ((IS_SEXT_32BIT_NUM (ep->X_add_number)
3567 || sizeof (ep->X_add_number) > 4
3568 || (ep->X_add_number & 0x80000000) == 0))
3569 || ((HAVE_32BIT_GPRS || ! dbl)
3570 && (ep->X_add_number &~ (offsetT) 0xffffffff) == 0)
3573 && ((ep->X_add_number &~ (offsetT) 0xffffffff)
3574 == ~ (offsetT) 0xffffffff)))
3576 /* 32 bit values require an lui. */
3577 macro_build ((char *) NULL, counter, ep, "lui", "t,u", reg,
3578 (int) BFD_RELOC_HI16);
3579 if ((ep->X_add_number & 0xffff) != 0)
3580 macro_build ((char *) NULL, counter, ep, "ori", "t,r,i", reg, reg,
3581 (int) BFD_RELOC_LO16);
3586 /* The value is larger than 32 bits. */
3588 if (HAVE_32BIT_GPRS)
3590 as_bad (_("Number (0x%lx) larger than 32 bits"),
3591 (unsigned long) ep->X_add_number);
3592 macro_build ((char *) NULL, counter, ep, "addiu", "t,r,j", reg, 0,
3593 (int) BFD_RELOC_LO16);
3597 if (ep->X_op != O_big)
3600 hi32.X_add_number = (valueT) hi32.X_add_number >> 16;
3601 hi32.X_add_number = (valueT) hi32.X_add_number >> 16;
3602 hi32.X_add_number &= 0xffffffff;
3604 lo32.X_add_number &= 0xffffffff;
3608 assert (ep->X_add_number > 2);
3609 if (ep->X_add_number == 3)
3610 generic_bignum[3] = 0;
3611 else if (ep->X_add_number > 4)
3612 as_bad (_("Number larger than 64 bits"));
3613 lo32.X_op = O_constant;
3614 lo32.X_add_number = generic_bignum[0] + (generic_bignum[1] << 16);
3615 hi32.X_op = O_constant;
3616 hi32.X_add_number = generic_bignum[2] + (generic_bignum[3] << 16);
3619 if (hi32.X_add_number == 0)
3624 unsigned long hi, lo;
3626 if (hi32.X_add_number == (offsetT) 0xffffffff)
3628 if ((lo32.X_add_number & 0xffff8000) == 0xffff8000)
3630 macro_build ((char *) NULL, counter, &lo32, "addiu", "t,r,j",
3631 reg, 0, (int) BFD_RELOC_LO16);
3634 if (lo32.X_add_number & 0x80000000)
3636 macro_build ((char *) NULL, counter, &lo32, "lui", "t,u", reg,
3637 (int) BFD_RELOC_HI16);
3638 if (lo32.X_add_number & 0xffff)
3639 macro_build ((char *) NULL, counter, &lo32, "ori", "t,r,i",
3640 reg, reg, (int) BFD_RELOC_LO16);
3645 /* Check for 16bit shifted constant. We know that hi32 is
3646 non-zero, so start the mask on the first bit of the hi32
3651 unsigned long himask, lomask;
3655 himask = 0xffff >> (32 - shift);
3656 lomask = (0xffff << shift) & 0xffffffff;
3660 himask = 0xffff << (shift - 32);
3663 if ((hi32.X_add_number & ~(offsetT) himask) == 0
3664 && (lo32.X_add_number & ~(offsetT) lomask) == 0)
3668 tmp.X_op = O_constant;
3670 tmp.X_add_number = ((hi32.X_add_number << (32 - shift))
3671 | (lo32.X_add_number >> shift));
3673 tmp.X_add_number = hi32.X_add_number >> (shift - 32);
3674 macro_build ((char *) NULL, counter, &tmp,
3675 "ori", "t,r,i", reg, 0,
3676 (int) BFD_RELOC_LO16);
3677 macro_build ((char *) NULL, counter, (expressionS *) NULL,
3678 (shift >= 32) ? "dsll32" : "dsll",
3680 (shift >= 32) ? shift - 32 : shift);
3685 while (shift <= (64 - 16));
3687 /* Find the bit number of the lowest one bit, and store the
3688 shifted value in hi/lo. */
3689 hi = (unsigned long) (hi32.X_add_number & 0xffffffff);
3690 lo = (unsigned long) (lo32.X_add_number & 0xffffffff);
3694 while ((lo & 1) == 0)
3699 lo |= (hi & (((unsigned long) 1 << bit) - 1)) << (32 - bit);
3705 while ((hi & 1) == 0)
3714 /* Optimize if the shifted value is a (power of 2) - 1. */
3715 if ((hi == 0 && ((lo + 1) & lo) == 0)
3716 || (lo == 0xffffffff && ((hi + 1) & hi) == 0))
3718 shift = COUNT_TOP_ZEROES ((unsigned int) hi32.X_add_number);
3723 /* This instruction will set the register to be all
3725 tmp.X_op = O_constant;
3726 tmp.X_add_number = (offsetT) -1;
3727 macro_build ((char *) NULL, counter, &tmp, "addiu", "t,r,j",
3728 reg, 0, (int) BFD_RELOC_LO16);
3732 macro_build ((char *) NULL, counter, (expressionS *) NULL,
3733 (bit >= 32) ? "dsll32" : "dsll",
3735 (bit >= 32) ? bit - 32 : bit);
3737 macro_build ((char *) NULL, counter, (expressionS *) NULL,
3738 (shift >= 32) ? "dsrl32" : "dsrl",
3740 (shift >= 32) ? shift - 32 : shift);
3745 /* Sign extend hi32 before calling load_register, because we can
3746 generally get better code when we load a sign extended value. */
3747 if ((hi32.X_add_number & 0x80000000) != 0)
3748 hi32.X_add_number |= ~(offsetT) 0xffffffff;
3749 load_register (counter, reg, &hi32, 0);
3752 if ((lo32.X_add_number & 0xffff0000) == 0)
3756 macro_build ((char *) NULL, counter, (expressionS *) NULL,
3757 "dsll32", "d,w,<", reg, freg, 0);
3765 if ((freg == 0) && (lo32.X_add_number == (offsetT) 0xffffffff))
3767 macro_build ((char *) NULL, counter, &lo32, "lui", "t,u", reg,
3768 (int) BFD_RELOC_HI16);
3769 macro_build ((char *) NULL, counter, (expressionS *) NULL,
3770 "dsrl32", "d,w,<", reg, reg, 0);
3776 macro_build ((char *) NULL, counter, (expressionS *) NULL, "dsll",
3777 "d,w,<", reg, freg, 16);
3781 mid16.X_add_number >>= 16;
3782 macro_build ((char *) NULL, counter, &mid16, "ori", "t,r,i", reg,
3783 freg, (int) BFD_RELOC_LO16);
3784 macro_build ((char *) NULL, counter, (expressionS *) NULL, "dsll",
3785 "d,w,<", reg, reg, 16);
3788 if ((lo32.X_add_number & 0xffff) != 0)
3789 macro_build ((char *) NULL, counter, &lo32, "ori", "t,r,i", reg, freg,
3790 (int) BFD_RELOC_LO16);
3793 /* Load an address into a register. */
3796 load_address (counter, reg, ep, used_at)
3804 if (ep->X_op != O_constant
3805 && ep->X_op != O_symbol)
3807 as_bad (_("expression too complex"));
3808 ep->X_op = O_constant;
3811 if (ep->X_op == O_constant)
3813 load_register (counter, reg, ep, HAVE_64BIT_ADDRESSES);
3817 if (mips_pic == NO_PIC)
3819 /* If this is a reference to a GP relative symbol, we want
3820 addiu $reg,$gp,<sym> (BFD_RELOC_GPREL16)
3822 lui $reg,<sym> (BFD_RELOC_HI16_S)
3823 addiu $reg,$reg,<sym> (BFD_RELOC_LO16)
3824 If we have an addend, we always use the latter form.
3826 With 64bit address space and a usable $at we want
3827 lui $reg,<sym> (BFD_RELOC_MIPS_HIGHEST)
3828 lui $at,<sym> (BFD_RELOC_HI16_S)
3829 daddiu $reg,<sym> (BFD_RELOC_MIPS_HIGHER)
3830 daddiu $at,<sym> (BFD_RELOC_LO16)
3834 If $at is already in use, we use a path which is suboptimal
3835 on superscalar processors.
3836 lui $reg,<sym> (BFD_RELOC_MIPS_HIGHEST)
3837 daddiu $reg,<sym> (BFD_RELOC_MIPS_HIGHER)
3839 daddiu $reg,<sym> (BFD_RELOC_HI16_S)
3841 daddiu $reg,<sym> (BFD_RELOC_LO16)
3843 if (HAVE_64BIT_ADDRESSES)
3845 /* We don't do GP optimization for now because RELAX_ENCODE can't
3846 hold the data for such large chunks. */
3848 if (*used_at == 0 && ! mips_opts.noat)
3850 macro_build (p, counter, ep, "lui", "t,u",
3851 reg, (int) BFD_RELOC_MIPS_HIGHEST);
3852 macro_build (p, counter, ep, "lui", "t,u",
3853 AT, (int) BFD_RELOC_HI16_S);
3854 macro_build (p, counter, ep, "daddiu", "t,r,j",
3855 reg, reg, (int) BFD_RELOC_MIPS_HIGHER);
3856 macro_build (p, counter, ep, "daddiu", "t,r,j",
3857 AT, AT, (int) BFD_RELOC_LO16);
3858 macro_build (p, counter, (expressionS *) NULL, "dsll32",
3859 "d,w,<", reg, reg, 0);
3860 macro_build (p, counter, (expressionS *) NULL, "daddu",
3861 "d,v,t", reg, reg, AT);
3866 macro_build (p, counter, ep, "lui", "t,u",
3867 reg, (int) BFD_RELOC_MIPS_HIGHEST);
3868 macro_build (p, counter, ep, "daddiu", "t,r,j",
3869 reg, reg, (int) BFD_RELOC_MIPS_HIGHER);
3870 macro_build (p, counter, (expressionS *) NULL, "dsll",
3871 "d,w,<", reg, reg, 16);
3872 macro_build (p, counter, ep, "daddiu", "t,r,j",
3873 reg, reg, (int) BFD_RELOC_HI16_S);
3874 macro_build (p, counter, (expressionS *) NULL, "dsll",
3875 "d,w,<", reg, reg, 16);
3876 macro_build (p, counter, ep, "daddiu", "t,r,j",
3877 reg, reg, (int) BFD_RELOC_LO16);
3882 if ((valueT) ep->X_add_number <= MAX_GPREL_OFFSET
3883 && ! nopic_need_relax (ep->X_add_symbol, 1))
3886 macro_build ((char *) NULL, counter, ep,
3887 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu", "t,r,j",
3888 reg, mips_gp_register, (int) BFD_RELOC_GPREL16);
3889 p = frag_var (rs_machine_dependent, 8, 0,
3890 RELAX_ENCODE (4, 8, 0, 4, 0,
3891 mips_opts.warn_about_macros),
3892 ep->X_add_symbol, 0, NULL);
3894 macro_build_lui (p, counter, ep, reg);
3897 macro_build (p, counter, ep,
3898 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
3899 "t,r,j", reg, reg, (int) BFD_RELOC_LO16);
3902 else if (mips_pic == SVR4_PIC && ! mips_big_got)
3906 /* If this is a reference to an external symbol, we want
3907 lw $reg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
3909 lw $reg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
3911 addiu $reg,$reg,<sym> (BFD_RELOC_LO16)
3912 If we have NewABI, we want
3913 lw $reg,<sym>($gp) (BFD_RELOC_MIPS_GOT_DISP)
3914 If there is a constant, it must be added in after. */
3915 ex.X_add_number = ep->X_add_number;
3916 ep->X_add_number = 0;
3920 macro_build ((char *) NULL, counter, ep,
3921 HAVE_32BIT_ADDRESSES ? "lw" : "ld", "t,o(b)", reg,
3922 (int) BFD_RELOC_MIPS_GOT_DISP, mips_gp_register);
3926 macro_build ((char *) NULL, counter, ep,
3927 HAVE_32BIT_ADDRESSES ? "lw" : "ld", "t,o(b)",
3928 reg, (int) BFD_RELOC_MIPS_GOT16, mips_gp_register);
3929 macro_build ((char *) NULL, counter, (expressionS *) NULL, "nop", "");
3930 p = frag_var (rs_machine_dependent, 4, 0,
3931 RELAX_ENCODE (0, 4, -8, 0, 0, mips_opts.warn_about_macros),
3932 ep->X_add_symbol, (offsetT) 0, (char *) NULL);
3933 macro_build (p, counter, ep,
3934 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
3935 "t,r,j", reg, reg, (int) BFD_RELOC_LO16);
3938 if (ex.X_add_number != 0)
3940 if (ex.X_add_number < -0x8000 || ex.X_add_number >= 0x8000)
3941 as_bad (_("PIC code offset overflow (max 16 signed bits)"));
3942 ex.X_op = O_constant;
3943 macro_build ((char *) NULL, counter, &ex,
3944 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
3945 "t,r,j", reg, reg, (int) BFD_RELOC_LO16);
3948 else if (mips_pic == SVR4_PIC)
3953 /* This is the large GOT case. If this is a reference to an
3954 external symbol, we want
3955 lui $reg,<sym> (BFD_RELOC_MIPS_GOT_HI16)
3957 lw $reg,<sym>($reg) (BFD_RELOC_MIPS_GOT_LO16)
3958 Otherwise, for a reference to a local symbol, we want
3959 lw $reg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
3961 addiu $reg,$reg,<sym> (BFD_RELOC_LO16)
3962 If we have NewABI, we want
3963 lw $reg,<sym>($gp) (BFD_RELOC_MIPS_GOT_PAGE)
3964 addiu $reg,$reg,<sym> (BFD_RELOC_MIPS_GOT_OFST)
3965 If there is a constant, it must be added in after. */
3966 ex.X_add_number = ep->X_add_number;
3967 ep->X_add_number = 0;
3970 macro_build ((char *) NULL, counter, ep,
3971 HAVE_32BIT_ADDRESSES ? "lw" : "ld", "t,o(b)", reg,
3972 (int) BFD_RELOC_MIPS_GOT_PAGE, mips_gp_register);
3973 macro_build (p, counter, ep,
3974 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu", "t,r,j",
3975 reg, reg, (int) BFD_RELOC_MIPS_GOT_OFST);
3979 if (reg_needs_delay (mips_gp_register))
3984 macro_build ((char *) NULL, counter, ep, "lui", "t,u", reg,
3985 (int) BFD_RELOC_MIPS_GOT_HI16);
3986 macro_build ((char *) NULL, counter, (expressionS *) NULL,
3987 HAVE_32BIT_ADDRESSES ? "addu" : "daddu", "d,v,t", reg,
3988 reg, mips_gp_register);
3989 macro_build ((char *) NULL, counter, ep,
3990 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
3991 "t,o(b)", reg, (int) BFD_RELOC_MIPS_GOT_LO16, reg);
3992 p = frag_var (rs_machine_dependent, 12 + off, 0,
3993 RELAX_ENCODE (12, 12 + off, off, 8 + off, 0,
3994 mips_opts.warn_about_macros),
3995 ep->X_add_symbol, 0, NULL);
3998 /* We need a nop before loading from $gp. This special
3999 check is required because the lui which starts the main
4000 instruction stream does not refer to $gp, and so will not
4001 insert the nop which may be required. */
4002 macro_build (p, counter, (expressionS *) NULL, "nop", "");
4005 macro_build (p, counter, ep,
4006 HAVE_32BIT_ADDRESSES ? "lw" : "ld", "t,o(b)", reg,
4007 (int) BFD_RELOC_MIPS_GOT16, mips_gp_register);
4009 macro_build (p, counter, (expressionS *) NULL, "nop", "");
4011 macro_build (p, counter, ep,
4012 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
4013 "t,r,j", reg, reg, (int) BFD_RELOC_LO16);
4016 if (ex.X_add_number != 0)
4018 if (ex.X_add_number < -0x8000 || ex.X_add_number >= 0x8000)
4019 as_bad (_("PIC code offset overflow (max 16 signed bits)"));
4020 ex.X_op = O_constant;
4021 macro_build ((char *) NULL, counter, &ex,
4022 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
4023 "t,r,j", reg, reg, (int) BFD_RELOC_LO16);
4026 else if (mips_pic == EMBEDDED_PIC)
4029 addiu $reg,$gp,<sym> (BFD_RELOC_GPREL16)
4031 macro_build ((char *) NULL, counter, ep,
4032 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
4033 "t,r,j", reg, mips_gp_register, (int) BFD_RELOC_GPREL16);
4039 /* Move the contents of register SOURCE into register DEST. */
4042 move_register (counter, dest, source)
4047 macro_build ((char *) NULL, counter, (expressionS *) NULL,
4048 HAVE_32BIT_GPRS ? "addu" : "daddu",
4049 "d,v,t", dest, source, 0);
4054 * This routine implements the seemingly endless macro or synthesized
4055 * instructions and addressing modes in the mips assembly language. Many
4056 * of these macros are simple and are similar to each other. These could
4057 * probably be handled by some kind of table or grammer aproach instead of
4058 * this verbose method. Others are not simple macros but are more like
4059 * optimizing code generation.
4060 * One interesting optimization is when several store macros appear
4061 * consecutivly that would load AT with the upper half of the same address.
4062 * The ensuing load upper instructions are ommited. This implies some kind
4063 * of global optimization. We currently only optimize within a single macro.
4064 * For many of the load and store macros if the address is specified as a
4065 * constant expression in the first 64k of memory (ie ld $2,0x4000c) we
4066 * first load register 'at' with zero and use it as the base register. The
4067 * mips assembler simply uses register $zero. Just one tiny optimization
4072 struct mips_cl_insn *ip;
4074 register int treg, sreg, dreg, breg;
4090 bfd_reloc_code_real_type r;
4091 int hold_mips_optimize;
4093 assert (! mips_opts.mips16);
4095 treg = (ip->insn_opcode >> 16) & 0x1f;
4096 dreg = (ip->insn_opcode >> 11) & 0x1f;
4097 sreg = breg = (ip->insn_opcode >> 21) & 0x1f;
4098 mask = ip->insn_mo->mask;
4100 expr1.X_op = O_constant;
4101 expr1.X_op_symbol = NULL;
4102 expr1.X_add_symbol = NULL;
4103 expr1.X_add_number = 1;
4115 mips_emit_delays (TRUE);
4116 ++mips_opts.noreorder;
4117 mips_any_noreorder = 1;
4119 expr1.X_add_number = 8;
4120 macro_build ((char *) NULL, &icnt, &expr1, "bgez", "s,p", sreg);
4122 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "",
4125 move_register (&icnt, dreg, sreg);
4126 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
4127 dbl ? "dsub" : "sub", "d,v,t", dreg, 0, sreg);
4129 --mips_opts.noreorder;
4150 if (imm_expr.X_op == O_constant
4151 && imm_expr.X_add_number >= -0x8000
4152 && imm_expr.X_add_number < 0x8000)
4154 macro_build ((char *) NULL, &icnt, &imm_expr, s, "t,r,j", treg, sreg,
4155 (int) BFD_RELOC_LO16);
4158 load_register (&icnt, AT, &imm_expr, dbl);
4159 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s2, "d,v,t",
4179 if (imm_expr.X_op == O_constant
4180 && imm_expr.X_add_number >= 0
4181 && imm_expr.X_add_number < 0x10000)
4183 if (mask != M_NOR_I)
4184 macro_build ((char *) NULL, &icnt, &imm_expr, s, "t,r,i", treg,
4185 sreg, (int) BFD_RELOC_LO16);
4188 macro_build ((char *) NULL, &icnt, &imm_expr, "ori", "t,r,i",
4189 treg, sreg, (int) BFD_RELOC_LO16);
4190 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nor",
4191 "d,v,t", treg, treg, 0);
4196 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_GPRS);
4197 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s2, "d,v,t",
4215 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
4217 macro_build ((char *) NULL, &icnt, &offset_expr, s, "s,t,p", sreg,
4221 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_GPRS);
4222 macro_build ((char *) NULL, &icnt, &offset_expr, s, "s,t,p", sreg, AT);
4230 macro_build ((char *) NULL, &icnt, &offset_expr,
4231 likely ? "bgezl" : "bgez", "s,p", sreg);
4236 macro_build ((char *) NULL, &icnt, &offset_expr,
4237 likely ? "blezl" : "blez", "s,p", treg);
4240 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "slt", "d,v,t",
4242 macro_build ((char *) NULL, &icnt, &offset_expr,
4243 likely ? "beql" : "beq", "s,t,p", AT, 0);
4249 /* check for > max integer */
4250 maxnum = 0x7fffffff;
4251 if (HAVE_64BIT_GPRS && sizeof (maxnum) > 4)
4258 if (imm_expr.X_op == O_constant
4259 && imm_expr.X_add_number >= maxnum
4260 && (HAVE_32BIT_GPRS || sizeof (maxnum) > 4))
4263 /* result is always false */
4267 as_warn (_("Branch %s is always false (nop)"),
4269 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop",
4275 as_warn (_("Branch likely %s is always false"),
4277 macro_build ((char *) NULL, &icnt, &offset_expr, "bnel",
4282 if (imm_expr.X_op != O_constant)
4283 as_bad (_("Unsupported large constant"));
4284 ++imm_expr.X_add_number;
4288 if (mask == M_BGEL_I)
4290 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
4292 macro_build ((char *) NULL, &icnt, &offset_expr,
4293 likely ? "bgezl" : "bgez", "s,p", sreg);
4296 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 1)
4298 macro_build ((char *) NULL, &icnt, &offset_expr,
4299 likely ? "bgtzl" : "bgtz", "s,p", sreg);
4302 maxnum = 0x7fffffff;
4303 if (HAVE_64BIT_GPRS && sizeof (maxnum) > 4)
4310 maxnum = - maxnum - 1;
4311 if (imm_expr.X_op == O_constant
4312 && imm_expr.X_add_number <= maxnum
4313 && (HAVE_32BIT_GPRS || sizeof (maxnum) > 4))
4316 /* result is always true */
4317 as_warn (_("Branch %s is always true"), ip->insn_mo->name);
4318 macro_build ((char *) NULL, &icnt, &offset_expr, "b", "p");
4321 set_at (&icnt, sreg, 0);
4322 macro_build ((char *) NULL, &icnt, &offset_expr,
4323 likely ? "beql" : "beq", "s,t,p", AT, 0);
4333 macro_build ((char *) NULL, &icnt, &offset_expr,
4334 likely ? "beql" : "beq", "s,t,p", 0, treg);
4337 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sltu",
4338 "d,v,t", AT, sreg, treg);
4339 macro_build ((char *) NULL, &icnt, &offset_expr,
4340 likely ? "beql" : "beq", "s,t,p", AT, 0);
4348 && imm_expr.X_op == O_constant
4349 && imm_expr.X_add_number == (offsetT) 0xffffffff))
4351 if (imm_expr.X_op != O_constant)
4352 as_bad (_("Unsupported large constant"));
4353 ++imm_expr.X_add_number;
4357 if (mask == M_BGEUL_I)
4359 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
4361 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 1)
4363 macro_build ((char *) NULL, &icnt, &offset_expr,
4364 likely ? "bnel" : "bne", "s,t,p", sreg, 0);
4367 set_at (&icnt, sreg, 1);
4368 macro_build ((char *) NULL, &icnt, &offset_expr,
4369 likely ? "beql" : "beq", "s,t,p", AT, 0);
4377 macro_build ((char *) NULL, &icnt, &offset_expr,
4378 likely ? "bgtzl" : "bgtz", "s,p", sreg);
4383 macro_build ((char *) NULL, &icnt, &offset_expr,
4384 likely ? "bltzl" : "bltz", "s,p", treg);
4387 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "slt", "d,v,t",
4389 macro_build ((char *) NULL, &icnt, &offset_expr,
4390 likely ? "bnel" : "bne", "s,t,p", AT, 0);
4398 macro_build ((char *) NULL, &icnt, &offset_expr,
4399 likely ? "bnel" : "bne", "s,t,p", sreg, 0);
4404 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sltu",
4405 "d,v,t", AT, treg, sreg);
4406 macro_build ((char *) NULL, &icnt, &offset_expr,
4407 likely ? "bnel" : "bne", "s,t,p", AT, 0);
4415 macro_build ((char *) NULL, &icnt, &offset_expr,
4416 likely ? "blezl" : "blez", "s,p", sreg);
4421 macro_build ((char *) NULL, &icnt, &offset_expr,
4422 likely ? "bgezl" : "bgez", "s,p", treg);
4425 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "slt", "d,v,t",
4427 macro_build ((char *) NULL, &icnt, &offset_expr,
4428 likely ? "beql" : "beq", "s,t,p", AT, 0);
4434 maxnum = 0x7fffffff;
4435 if (HAVE_64BIT_GPRS && sizeof (maxnum) > 4)
4442 if (imm_expr.X_op == O_constant
4443 && imm_expr.X_add_number >= maxnum
4444 && (HAVE_32BIT_GPRS || sizeof (maxnum) > 4))
4446 if (imm_expr.X_op != O_constant)
4447 as_bad (_("Unsupported large constant"));
4448 ++imm_expr.X_add_number;
4452 if (mask == M_BLTL_I)
4454 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
4456 macro_build ((char *) NULL, &icnt, &offset_expr,
4457 likely ? "bltzl" : "bltz", "s,p", sreg);
4460 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 1)
4462 macro_build ((char *) NULL, &icnt, &offset_expr,
4463 likely ? "blezl" : "blez", "s,p", sreg);
4466 set_at (&icnt, sreg, 0);
4467 macro_build ((char *) NULL, &icnt, &offset_expr,
4468 likely ? "bnel" : "bne", "s,t,p", AT, 0);
4476 macro_build ((char *) NULL, &icnt, &offset_expr,
4477 likely ? "beql" : "beq", "s,t,p", sreg, 0);
4482 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sltu",
4483 "d,v,t", AT, treg, sreg);
4484 macro_build ((char *) NULL, &icnt, &offset_expr,
4485 likely ? "beql" : "beq", "s,t,p", AT, 0);
4493 && imm_expr.X_op == O_constant
4494 && imm_expr.X_add_number == (offsetT) 0xffffffff))
4496 if (imm_expr.X_op != O_constant)
4497 as_bad (_("Unsupported large constant"));
4498 ++imm_expr.X_add_number;
4502 if (mask == M_BLTUL_I)
4504 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
4506 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 1)
4508 macro_build ((char *) NULL, &icnt, &offset_expr,
4509 likely ? "beql" : "beq",
4513 set_at (&icnt, sreg, 1);
4514 macro_build ((char *) NULL, &icnt, &offset_expr,
4515 likely ? "bnel" : "bne", "s,t,p", AT, 0);
4523 macro_build ((char *) NULL, &icnt, &offset_expr,
4524 likely ? "bltzl" : "bltz", "s,p", sreg);
4529 macro_build ((char *) NULL, &icnt, &offset_expr,
4530 likely ? "bgtzl" : "bgtz", "s,p", treg);
4533 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "slt", "d,v,t",
4535 macro_build ((char *) NULL, &icnt, &offset_expr,
4536 likely ? "bnel" : "bne", "s,t,p", AT, 0);
4546 macro_build ((char *) NULL, &icnt, &offset_expr,
4547 likely ? "bnel" : "bne", "s,t,p", 0, treg);
4550 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sltu",
4553 macro_build ((char *) NULL, &icnt, &offset_expr,
4554 likely ? "bnel" : "bne", "s,t,p", AT, 0);
4569 as_warn (_("Divide by zero."));
4571 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "teq",
4574 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "break",
4579 mips_emit_delays (TRUE);
4580 ++mips_opts.noreorder;
4581 mips_any_noreorder = 1;
4584 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "teq",
4585 "s,t,q", treg, 0, 7);
4586 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
4587 dbl ? "ddiv" : "div", "z,s,t", sreg, treg);
4591 expr1.X_add_number = 8;
4592 macro_build ((char *) NULL, &icnt, &expr1, "bne", "s,t,p", treg, 0);
4593 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
4594 dbl ? "ddiv" : "div", "z,s,t", sreg, treg);
4595 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "break",
4598 expr1.X_add_number = -1;
4599 macro_build ((char *) NULL, &icnt, &expr1,
4600 dbl ? "daddiu" : "addiu",
4601 "t,r,j", AT, 0, (int) BFD_RELOC_LO16);
4602 expr1.X_add_number = mips_trap ? (dbl ? 12 : 8) : (dbl ? 20 : 16);
4603 macro_build ((char *) NULL, &icnt, &expr1, "bne", "s,t,p", treg, AT);
4606 expr1.X_add_number = 1;
4607 macro_build ((char *) NULL, &icnt, &expr1, "daddiu", "t,r,j", AT, 0,
4608 (int) BFD_RELOC_LO16);
4609 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "dsll32",
4610 "d,w,<", AT, AT, 31);
4614 expr1.X_add_number = 0x80000000;
4615 macro_build ((char *) NULL, &icnt, &expr1, "lui", "t,u", AT,
4616 (int) BFD_RELOC_HI16);
4620 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "teq",
4621 "s,t,q", sreg, AT, 6);
4622 /* We want to close the noreorder block as soon as possible, so
4623 that later insns are available for delay slot filling. */
4624 --mips_opts.noreorder;
4628 expr1.X_add_number = 8;
4629 macro_build ((char *) NULL, &icnt, &expr1, "bne", "s,t,p", sreg, AT);
4630 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "",
4633 /* We want to close the noreorder block as soon as possible, so
4634 that later insns are available for delay slot filling. */
4635 --mips_opts.noreorder;
4637 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "break",
4640 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "d", dreg);
4679 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
4681 as_warn (_("Divide by zero."));
4683 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "teq",
4686 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "break",
4690 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 1)
4692 if (strcmp (s2, "mflo") == 0)
4693 move_register (&icnt, dreg, sreg);
4695 move_register (&icnt, dreg, 0);
4698 if (imm_expr.X_op == O_constant
4699 && imm_expr.X_add_number == -1
4700 && s[strlen (s) - 1] != 'u')
4702 if (strcmp (s2, "mflo") == 0)
4704 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
4705 dbl ? "dneg" : "neg", "d,w", dreg, sreg);
4708 move_register (&icnt, dreg, 0);
4712 load_register (&icnt, AT, &imm_expr, dbl);
4713 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "z,s,t",
4715 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s2, "d", dreg);
4734 mips_emit_delays (TRUE);
4735 ++mips_opts.noreorder;
4736 mips_any_noreorder = 1;
4739 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "teq",
4740 "s,t,q", treg, 0, 7);
4741 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "z,s,t",
4743 /* We want to close the noreorder block as soon as possible, so
4744 that later insns are available for delay slot filling. */
4745 --mips_opts.noreorder;
4749 expr1.X_add_number = 8;
4750 macro_build ((char *) NULL, &icnt, &expr1, "bne", "s,t,p", treg, 0);
4751 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "z,s,t",
4754 /* We want to close the noreorder block as soon as possible, so
4755 that later insns are available for delay slot filling. */
4756 --mips_opts.noreorder;
4757 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "break",
4760 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s2, "d", dreg);
4766 /* Load the address of a symbol into a register. If breg is not
4767 zero, we then add a base register to it. */
4769 if (dbl && HAVE_32BIT_GPRS)
4770 as_warn (_("dla used to load 32-bit register"));
4772 if (! dbl && HAVE_64BIT_OBJECTS)
4773 as_warn (_("la used to load 64-bit address"));
4775 if (offset_expr.X_op == O_constant
4776 && offset_expr.X_add_number >= -0x8000
4777 && offset_expr.X_add_number < 0x8000)
4779 macro_build ((char *) NULL, &icnt, &offset_expr,
4780 (dbl || HAVE_64BIT_ADDRESSES) ? "daddiu" : "addiu",
4781 "t,r,j", treg, sreg, (int) BFD_RELOC_LO16);
4796 /* When generating embedded PIC code, we permit expressions of
4799 la $treg,foo-bar($breg)
4800 where bar is an address in the current section. These are used
4801 when getting the addresses of functions. We don't permit
4802 X_add_number to be non-zero, because if the symbol is
4803 external the relaxing code needs to know that any addend is
4804 purely the offset to X_op_symbol. */
4805 if (mips_pic == EMBEDDED_PIC
4806 && offset_expr.X_op == O_subtract
4807 && (symbol_constant_p (offset_expr.X_op_symbol)
4808 ? S_GET_SEGMENT (offset_expr.X_op_symbol) == now_seg
4809 : (symbol_equated_p (offset_expr.X_op_symbol)
4811 (symbol_get_value_expression (offset_expr.X_op_symbol)
4814 && (offset_expr.X_add_number == 0
4815 || OUTPUT_FLAVOR == bfd_target_elf_flavour))
4821 macro_build ((char *) NULL, &icnt, &offset_expr, "lui", "t,u",
4822 tempreg, (int) BFD_RELOC_PCREL_HI16_S);
4826 macro_build ((char *) NULL, &icnt, &offset_expr, "lui", "t,u",
4827 tempreg, (int) BFD_RELOC_PCREL_HI16_S);
4828 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
4829 (dbl || HAVE_64BIT_ADDRESSES) ? "daddu" : "addu",
4830 "d,v,t", tempreg, tempreg, breg);
4832 macro_build ((char *) NULL, &icnt, &offset_expr,
4833 (dbl || HAVE_64BIT_ADDRESSES) ? "daddiu" : "addiu",
4834 "t,r,j", treg, tempreg, (int) BFD_RELOC_PCREL_LO16);
4840 if (offset_expr.X_op != O_symbol
4841 && offset_expr.X_op != O_constant)
4843 as_bad (_("expression too complex"));
4844 offset_expr.X_op = O_constant;
4847 if (offset_expr.X_op == O_constant)
4848 load_register (&icnt, tempreg, &offset_expr,
4849 ((mips_pic == EMBEDDED_PIC || mips_pic == NO_PIC)
4850 ? (dbl || HAVE_64BIT_ADDRESSES)
4851 : HAVE_64BIT_ADDRESSES));
4852 else if (mips_pic == NO_PIC)
4854 /* If this is a reference to a GP relative symbol, we want
4855 addiu $tempreg,$gp,<sym> (BFD_RELOC_GPREL16)
4857 lui $tempreg,<sym> (BFD_RELOC_HI16_S)
4858 addiu $tempreg,$tempreg,<sym> (BFD_RELOC_LO16)
4859 If we have a constant, we need two instructions anyhow,
4860 so we may as well always use the latter form.
4862 With 64bit address space and a usable $at we want
4863 lui $tempreg,<sym> (BFD_RELOC_MIPS_HIGHEST)
4864 lui $at,<sym> (BFD_RELOC_HI16_S)
4865 daddiu $tempreg,<sym> (BFD_RELOC_MIPS_HIGHER)
4866 daddiu $at,<sym> (BFD_RELOC_LO16)
4868 daddu $tempreg,$tempreg,$at
4870 If $at is already in use, we use a path which is suboptimal
4871 on superscalar processors.
4872 lui $tempreg,<sym> (BFD_RELOC_MIPS_HIGHEST)
4873 daddiu $tempreg,<sym> (BFD_RELOC_MIPS_HIGHER)
4875 daddiu $tempreg,<sym> (BFD_RELOC_HI16_S)
4877 daddiu $tempreg,<sym> (BFD_RELOC_LO16)
4880 if (HAVE_64BIT_ADDRESSES)
4882 /* We don't do GP optimization for now because RELAX_ENCODE can't
4883 hold the data for such large chunks. */
4885 if (used_at == 0 && ! mips_opts.noat)
4887 macro_build (p, &icnt, &offset_expr, "lui", "t,u",
4888 tempreg, (int) BFD_RELOC_MIPS_HIGHEST);
4889 macro_build (p, &icnt, &offset_expr, "lui", "t,u",
4890 AT, (int) BFD_RELOC_HI16_S);
4891 macro_build (p, &icnt, &offset_expr, "daddiu", "t,r,j",
4892 tempreg, tempreg, (int) BFD_RELOC_MIPS_HIGHER);
4893 macro_build (p, &icnt, &offset_expr, "daddiu", "t,r,j",
4894 AT, AT, (int) BFD_RELOC_LO16);
4895 macro_build (p, &icnt, (expressionS *) NULL, "dsll32",
4896 "d,w,<", tempreg, tempreg, 0);
4897 macro_build (p, &icnt, (expressionS *) NULL, "daddu",
4898 "d,v,t", tempreg, tempreg, AT);
4903 macro_build (p, &icnt, &offset_expr, "lui", "t,u",
4904 tempreg, (int) BFD_RELOC_MIPS_HIGHEST);
4905 macro_build (p, &icnt, &offset_expr, "daddiu", "t,r,j",
4906 tempreg, tempreg, (int) BFD_RELOC_MIPS_HIGHER);
4907 macro_build (p, &icnt, (expressionS *) NULL, "dsll", "d,w,<",
4908 tempreg, tempreg, 16);
4909 macro_build (p, &icnt, &offset_expr, "daddiu", "t,r,j",
4910 tempreg, tempreg, (int) BFD_RELOC_HI16_S);
4911 macro_build (p, &icnt, (expressionS *) NULL, "dsll", "d,w,<",
4912 tempreg, tempreg, 16);
4913 macro_build (p, &icnt, &offset_expr, "daddiu", "t,r,j",
4914 tempreg, tempreg, (int) BFD_RELOC_LO16);
4919 if ((valueT) offset_expr.X_add_number <= MAX_GPREL_OFFSET
4920 && ! nopic_need_relax (offset_expr.X_add_symbol, 1))
4923 macro_build ((char *) NULL, &icnt, &offset_expr, "addiu",
4924 "t,r,j", tempreg, mips_gp_register,
4925 (int) BFD_RELOC_GPREL16);
4926 p = frag_var (rs_machine_dependent, 8, 0,
4927 RELAX_ENCODE (4, 8, 0, 4, 0,
4928 mips_opts.warn_about_macros),
4929 offset_expr.X_add_symbol, 0, NULL);
4931 macro_build_lui (p, &icnt, &offset_expr, tempreg);
4934 macro_build (p, &icnt, &offset_expr, "addiu",
4935 "t,r,j", tempreg, tempreg, (int) BFD_RELOC_LO16);
4938 else if (mips_pic == SVR4_PIC && ! mips_big_got)
4940 int lw_reloc_type = (int) BFD_RELOC_MIPS_GOT16;
4942 /* If this is a reference to an external symbol, and there
4943 is no constant, we want
4944 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
4945 or if tempreg is PIC_CALL_REG
4946 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_CALL16)
4947 For a local symbol, we want
4948 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
4950 addiu $tempreg,$tempreg,<sym> (BFD_RELOC_LO16)
4952 If we have a small constant, and this is a reference to
4953 an external symbol, we want
4954 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
4956 addiu $tempreg,$tempreg,<constant>
4957 For a local symbol, we want the same instruction
4958 sequence, but we output a BFD_RELOC_LO16 reloc on the
4961 If we have a large constant, and this is a reference to
4962 an external symbol, we want
4963 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
4964 lui $at,<hiconstant>
4965 addiu $at,$at,<loconstant>
4966 addu $tempreg,$tempreg,$at
4967 For a local symbol, we want the same instruction
4968 sequence, but we output a BFD_RELOC_LO16 reloc on the
4971 For NewABI, we want for local or external data addresses
4972 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT_DISP)
4973 For a local function symbol, we want
4974 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT_PAGE)
4976 addiu $tempreg,$tempreg,<sym> (BFD_RELOC_MIPS_GOT_OFST)
4979 expr1.X_add_number = offset_expr.X_add_number;
4980 offset_expr.X_add_number = 0;
4982 if (expr1.X_add_number == 0 && tempreg == PIC_CALL_REG)
4983 lw_reloc_type = (int) BFD_RELOC_MIPS_CALL16;
4984 else if (HAVE_NEWABI)
4985 lw_reloc_type = (int) BFD_RELOC_MIPS_GOT_DISP;
4986 macro_build ((char *) NULL, &icnt, &offset_expr,
4987 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
4988 "t,o(b)", tempreg, lw_reloc_type, mips_gp_register);
4989 if (expr1.X_add_number == 0)
4998 /* We're going to put in an addu instruction using
4999 tempreg, so we may as well insert the nop right
5001 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5005 p = frag_var (rs_machine_dependent, 8 - off, 0,
5006 RELAX_ENCODE (0, 8 - off, -4 - off, 4 - off, 0,
5008 ? mips_opts.warn_about_macros
5010 offset_expr.X_add_symbol, 0, NULL);
5013 macro_build (p, &icnt, (expressionS *) NULL, "nop", "");
5016 macro_build (p, &icnt, &expr1,
5017 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
5018 "t,r,j", tempreg, tempreg, (int) BFD_RELOC_LO16);
5019 /* FIXME: If breg == 0, and the next instruction uses
5020 $tempreg, then if this variant case is used an extra
5021 nop will be generated. */
5023 else if (expr1.X_add_number >= -0x8000
5024 && expr1.X_add_number < 0x8000)
5026 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5028 macro_build ((char *) NULL, &icnt, &expr1,
5029 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
5030 "t,r,j", tempreg, tempreg, (int) BFD_RELOC_LO16);
5031 frag_var (rs_machine_dependent, 0, 0,
5032 RELAX_ENCODE (0, 0, -12, -4, 0, 0),
5033 offset_expr.X_add_symbol, 0, NULL);
5039 /* If we are going to add in a base register, and the
5040 target register and the base register are the same,
5041 then we are using AT as a temporary register. Since
5042 we want to load the constant into AT, we add our
5043 current AT (from the global offset table) and the
5044 register into the register now, and pretend we were
5045 not using a base register. */
5050 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5052 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5053 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
5054 "d,v,t", treg, AT, breg);
5060 /* Set mips_optimize around the lui instruction to avoid
5061 inserting an unnecessary nop after the lw. */
5062 hold_mips_optimize = mips_optimize;
5064 macro_build_lui (NULL, &icnt, &expr1, AT);
5065 mips_optimize = hold_mips_optimize;
5067 macro_build ((char *) NULL, &icnt, &expr1,
5068 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
5069 "t,r,j", AT, AT, (int) BFD_RELOC_LO16);
5070 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5071 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
5072 "d,v,t", tempreg, tempreg, AT);
5073 frag_var (rs_machine_dependent, 0, 0,
5074 RELAX_ENCODE (0, 0, -16 + off1, -8, 0, 0),
5075 offset_expr.X_add_symbol, 0, NULL);
5079 else if (mips_pic == SVR4_PIC)
5083 int lui_reloc_type = (int) BFD_RELOC_MIPS_GOT_HI16;
5084 int lw_reloc_type = (int) BFD_RELOC_MIPS_GOT_LO16;
5085 int local_reloc_type = (int) BFD_RELOC_MIPS_GOT16;
5087 /* This is the large GOT case. If this is a reference to an
5088 external symbol, and there is no constant, we want
5089 lui $tempreg,<sym> (BFD_RELOC_MIPS_GOT_HI16)
5090 addu $tempreg,$tempreg,$gp
5091 lw $tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_LO16)
5092 or if tempreg is PIC_CALL_REG
5093 lui $tempreg,<sym> (BFD_RELOC_MIPS_CALL_HI16)
5094 addu $tempreg,$tempreg,$gp
5095 lw $tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_CALL_LO16)
5096 For a local symbol, we want
5097 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
5099 addiu $tempreg,$tempreg,<sym> (BFD_RELOC_LO16)
5101 If we have a small constant, and this is a reference to
5102 an external symbol, we want
5103 lui $tempreg,<sym> (BFD_RELOC_MIPS_GOT_HI16)
5104 addu $tempreg,$tempreg,$gp
5105 lw $tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_LO16)
5107 addiu $tempreg,$tempreg,<constant>
5108 For a local symbol, we want
5109 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
5111 addiu $tempreg,$tempreg,<constant> (BFD_RELOC_LO16)
5113 If we have a large constant, and this is a reference to
5114 an external symbol, we want
5115 lui $tempreg,<sym> (BFD_RELOC_MIPS_GOT_HI16)
5116 addu $tempreg,$tempreg,$gp
5117 lw $tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_LO16)
5118 lui $at,<hiconstant>
5119 addiu $at,$at,<loconstant>
5120 addu $tempreg,$tempreg,$at
5121 For a local symbol, we want
5122 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
5123 lui $at,<hiconstant>
5124 addiu $at,$at,<loconstant> (BFD_RELOC_LO16)
5125 addu $tempreg,$tempreg,$at
5127 For NewABI, we want for local data addresses
5128 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT_DISP)
5131 expr1.X_add_number = offset_expr.X_add_number;
5132 offset_expr.X_add_number = 0;
5134 if (reg_needs_delay (mips_gp_register))
5138 if (expr1.X_add_number == 0 && tempreg == PIC_CALL_REG)
5140 lui_reloc_type = (int) BFD_RELOC_MIPS_CALL_HI16;
5141 lw_reloc_type = (int) BFD_RELOC_MIPS_CALL_LO16;
5143 macro_build ((char *) NULL, &icnt, &offset_expr, "lui", "t,u",
5144 tempreg, lui_reloc_type);
5145 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5146 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
5147 "d,v,t", tempreg, tempreg, mips_gp_register);
5148 macro_build ((char *) NULL, &icnt, &offset_expr,
5149 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
5150 "t,o(b)", tempreg, lw_reloc_type, tempreg);
5151 if (expr1.X_add_number == 0)
5159 /* We're going to put in an addu instruction using
5160 tempreg, so we may as well insert the nop right
5162 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5167 p = frag_var (rs_machine_dependent, 12 + gpdel, 0,
5168 RELAX_ENCODE (12 + off, 12 + gpdel, gpdel,
5171 ? mips_opts.warn_about_macros
5173 offset_expr.X_add_symbol, 0, NULL);
5175 else if (expr1.X_add_number >= -0x8000
5176 && expr1.X_add_number < 0x8000)
5178 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5180 macro_build ((char *) NULL, &icnt, &expr1,
5181 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
5182 "t,r,j", tempreg, tempreg, (int) BFD_RELOC_LO16);
5184 p = frag_var (rs_machine_dependent, 12 + gpdel, 0,
5185 RELAX_ENCODE (20, 12 + gpdel, gpdel, 8 + gpdel, 0,
5187 ? mips_opts.warn_about_macros
5189 offset_expr.X_add_symbol, 0, NULL);
5195 /* If we are going to add in a base register, and the
5196 target register and the base register are the same,
5197 then we are using AT as a temporary register. Since
5198 we want to load the constant into AT, we add our
5199 current AT (from the global offset table) and the
5200 register into the register now, and pretend we were
5201 not using a base register. */
5209 assert (tempreg == AT);
5210 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5212 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5213 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
5214 "d,v,t", treg, AT, breg);
5219 /* Set mips_optimize around the lui instruction to avoid
5220 inserting an unnecessary nop after the lw. */
5221 hold_mips_optimize = mips_optimize;
5223 macro_build_lui (NULL, &icnt, &expr1, AT);
5224 mips_optimize = hold_mips_optimize;
5226 macro_build ((char *) NULL, &icnt, &expr1,
5227 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
5228 "t,r,j", AT, AT, (int) BFD_RELOC_LO16);
5229 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5230 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
5231 "d,v,t", dreg, dreg, AT);
5233 p = frag_var (rs_machine_dependent, 16 + gpdel + adj, 0,
5234 RELAX_ENCODE (24 + adj, 16 + gpdel + adj, gpdel,
5237 ? mips_opts.warn_about_macros
5239 offset_expr.X_add_symbol, 0, NULL);
5246 /* This is needed because this instruction uses $gp, but
5247 the first instruction on the main stream does not. */
5248 macro_build (p, &icnt, (expressionS *) NULL, "nop", "");
5253 local_reloc_type = (int) BFD_RELOC_MIPS_GOT_DISP;
5254 macro_build (p, &icnt, &offset_expr,
5255 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
5260 if (expr1.X_add_number == 0 && HAVE_NEWABI)
5262 /* BFD_RELOC_MIPS_GOT_DISP is sufficient for newabi */
5265 if (expr1.X_add_number >= -0x8000
5266 && expr1.X_add_number < 0x8000)
5268 macro_build (p, &icnt, (expressionS *) NULL, "nop", "");
5270 macro_build (p, &icnt, &expr1,
5271 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
5272 "t,r,j", tempreg, tempreg, (int) BFD_RELOC_LO16);
5273 /* FIXME: If add_number is 0, and there was no base
5274 register, the external symbol case ended with a load,
5275 so if the symbol turns out to not be external, and
5276 the next instruction uses tempreg, an unnecessary nop
5277 will be inserted. */
5283 /* We must add in the base register now, as in the
5284 external symbol case. */
5285 assert (tempreg == AT);
5286 macro_build (p, &icnt, (expressionS *) NULL, "nop", "");
5288 macro_build (p, &icnt, (expressionS *) NULL,
5289 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
5290 "d,v,t", treg, AT, breg);
5293 /* We set breg to 0 because we have arranged to add
5294 it in in both cases. */
5298 macro_build_lui (p, &icnt, &expr1, AT);
5300 macro_build (p, &icnt, &expr1,
5301 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
5302 "t,r,j", AT, AT, (int) BFD_RELOC_LO16);
5304 macro_build (p, &icnt, (expressionS *) NULL,
5305 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
5306 "d,v,t", tempreg, tempreg, AT);
5310 else if (mips_pic == EMBEDDED_PIC)
5313 addiu $tempreg,$gp,<sym> (BFD_RELOC_GPREL16)
5315 macro_build ((char *) NULL, &icnt, &offset_expr,
5316 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu", "t,r,j",
5317 tempreg, mips_gp_register, (int) BFD_RELOC_GPREL16);
5326 if (mips_pic == EMBEDDED_PIC || mips_pic == NO_PIC)
5327 s = (dbl || HAVE_64BIT_ADDRESSES) ? "daddu" : "addu";
5329 s = HAVE_64BIT_ADDRESSES ? "daddu" : "addu";
5331 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s,
5332 "d,v,t", treg, tempreg, breg);
5341 /* The j instruction may not be used in PIC code, since it
5342 requires an absolute address. We convert it to a b
5344 if (mips_pic == NO_PIC)
5345 macro_build ((char *) NULL, &icnt, &offset_expr, "j", "a");
5347 macro_build ((char *) NULL, &icnt, &offset_expr, "b", "p");
5350 /* The jal instructions must be handled as macros because when
5351 generating PIC code they expand to multi-instruction
5352 sequences. Normally they are simple instructions. */
5357 if (mips_pic == NO_PIC
5358 || mips_pic == EMBEDDED_PIC)
5359 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "jalr",
5361 else if (mips_pic == SVR4_PIC)
5363 if (sreg != PIC_CALL_REG)
5364 as_warn (_("MIPS PIC call to register other than $25"));
5366 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "jalr",
5370 if (mips_cprestore_offset < 0)
5371 as_warn (_("No .cprestore pseudo-op used in PIC code"));
5374 if (! mips_frame_reg_valid)
5376 as_warn (_("No .frame pseudo-op used in PIC code"));
5377 /* Quiet this warning. */
5378 mips_frame_reg_valid = 1;
5380 if (! mips_cprestore_valid)
5382 as_warn (_("No .cprestore pseudo-op used in PIC code"));
5383 /* Quiet this warning. */
5384 mips_cprestore_valid = 1;
5386 expr1.X_add_number = mips_cprestore_offset;
5387 macro_build_ldst_constoffset ((char *) NULL, &icnt, &expr1,
5388 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
5389 mips_gp_register, mips_frame_reg);
5399 if (mips_pic == NO_PIC)
5400 macro_build ((char *) NULL, &icnt, &offset_expr, "jal", "a");
5401 else if (mips_pic == SVR4_PIC)
5405 /* If this is a reference to an external symbol, and we are
5406 using a small GOT, we want
5407 lw $25,<sym>($gp) (BFD_RELOC_MIPS_CALL16)
5411 lw $gp,cprestore($sp)
5412 The cprestore value is set using the .cprestore
5413 pseudo-op. If we are using a big GOT, we want
5414 lui $25,<sym> (BFD_RELOC_MIPS_CALL_HI16)
5416 lw $25,<sym>($25) (BFD_RELOC_MIPS_CALL_LO16)
5420 lw $gp,cprestore($sp)
5421 If the symbol is not external, we want
5422 lw $25,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
5424 addiu $25,$25,<sym> (BFD_RELOC_LO16)
5427 lw $gp,cprestore($sp)
5429 lw $25,<sym>($gp) (BFD_RELOC_MIPS_GOT_DISP)
5430 jalr $ra,$25 (BFD_RELOC_MIPS_JALR)
5434 macro_build ((char *) NULL, &icnt, &offset_expr,
5435 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
5436 "t,o(b)", PIC_CALL_REG,
5437 (int) BFD_RELOC_MIPS_GOT_DISP, mips_gp_register);
5438 macro_build_jalr (icnt, &offset_expr);
5445 macro_build ((char *) NULL, &icnt, &offset_expr,
5446 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
5447 "t,o(b)", PIC_CALL_REG,
5448 (int) BFD_RELOC_MIPS_CALL16, mips_gp_register);
5449 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5451 p = frag_var (rs_machine_dependent, 4, 0,
5452 RELAX_ENCODE (0, 4, -8, 0, 0, 0),
5453 offset_expr.X_add_symbol, 0, NULL);
5459 if (reg_needs_delay (mips_gp_register))
5463 macro_build ((char *) NULL, &icnt, &offset_expr, "lui",
5464 "t,u", PIC_CALL_REG,
5465 (int) BFD_RELOC_MIPS_CALL_HI16);
5466 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5467 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
5468 "d,v,t", PIC_CALL_REG, PIC_CALL_REG,
5470 macro_build ((char *) NULL, &icnt, &offset_expr,
5471 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
5472 "t,o(b)", PIC_CALL_REG,
5473 (int) BFD_RELOC_MIPS_CALL_LO16, PIC_CALL_REG);
5474 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5476 p = frag_var (rs_machine_dependent, 12 + gpdel, 0,
5477 RELAX_ENCODE (16, 12 + gpdel, gpdel,
5479 offset_expr.X_add_symbol, 0, NULL);
5482 macro_build (p, &icnt, (expressionS *) NULL, "nop", "");
5485 macro_build (p, &icnt, &offset_expr,
5486 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
5487 "t,o(b)", PIC_CALL_REG,
5488 (int) BFD_RELOC_MIPS_GOT16, mips_gp_register);
5490 macro_build (p, &icnt, (expressionS *) NULL, "nop", "");
5493 macro_build (p, &icnt, &offset_expr,
5494 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
5495 "t,r,j", PIC_CALL_REG, PIC_CALL_REG,
5496 (int) BFD_RELOC_LO16);
5497 macro_build_jalr (icnt, &offset_expr);
5499 if (mips_cprestore_offset < 0)
5500 as_warn (_("No .cprestore pseudo-op used in PIC code"));
5503 if (! mips_frame_reg_valid)
5505 as_warn (_("No .frame pseudo-op used in PIC code"));
5506 /* Quiet this warning. */
5507 mips_frame_reg_valid = 1;
5509 if (! mips_cprestore_valid)
5511 as_warn (_("No .cprestore pseudo-op used in PIC code"));
5512 /* Quiet this warning. */
5513 mips_cprestore_valid = 1;
5515 if (mips_opts.noreorder)
5516 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5518 expr1.X_add_number = mips_cprestore_offset;
5519 macro_build_ldst_constoffset ((char *) NULL, &icnt, &expr1,
5520 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
5521 mips_gp_register, mips_frame_reg);
5525 else if (mips_pic == EMBEDDED_PIC)
5527 macro_build ((char *) NULL, &icnt, &offset_expr, "bal", "p");
5528 /* The linker may expand the call to a longer sequence which
5529 uses $at, so we must break rather than return. */
5554 /* Itbl support may require additional care here. */
5559 /* Itbl support may require additional care here. */
5564 /* Itbl support may require additional care here. */
5569 /* Itbl support may require additional care here. */
5581 if (mips_arch == CPU_R4650)
5583 as_bad (_("opcode not supported on this processor"));
5587 /* Itbl support may require additional care here. */
5592 /* Itbl support may require additional care here. */
5597 /* Itbl support may require additional care here. */
5617 if (breg == treg || coproc || lr)
5639 /* Itbl support may require additional care here. */
5644 /* Itbl support may require additional care here. */
5649 /* Itbl support may require additional care here. */
5654 /* Itbl support may require additional care here. */
5670 if (mips_arch == CPU_R4650)
5672 as_bad (_("opcode not supported on this processor"));
5677 /* Itbl support may require additional care here. */
5681 /* Itbl support may require additional care here. */
5686 /* Itbl support may require additional care here. */
5698 /* Itbl support may require additional care here. */
5699 if (mask == M_LWC1_AB
5700 || mask == M_SWC1_AB
5701 || mask == M_LDC1_AB
5702 || mask == M_SDC1_AB
5711 /* For embedded PIC, we allow loads where the offset is calculated
5712 by subtracting a symbol in the current segment from an unknown
5713 symbol, relative to a base register, e.g.:
5714 <op> $treg, <sym>-<localsym>($breg)
5715 This is used by the compiler for switch statements. */
5716 if (mips_pic == EMBEDDED_PIC
5717 && offset_expr.X_op == O_subtract
5718 && (symbol_constant_p (offset_expr.X_op_symbol)
5719 ? S_GET_SEGMENT (offset_expr.X_op_symbol) == now_seg
5720 : (symbol_equated_p (offset_expr.X_op_symbol)
5722 (symbol_get_value_expression (offset_expr.X_op_symbol)
5726 && (offset_expr.X_add_number == 0
5727 || OUTPUT_FLAVOR == bfd_target_elf_flavour))
5729 /* For this case, we output the instructions:
5730 lui $tempreg,<sym> (BFD_RELOC_PCREL_HI16_S)
5731 addiu $tempreg,$tempreg,$breg
5732 <op> $treg,<sym>($tempreg) (BFD_RELOC_PCREL_LO16)
5733 If the relocation would fit entirely in 16 bits, it would be
5735 <op> $treg,<sym>($breg) (BFD_RELOC_PCREL_LO16)
5736 instead, but that seems quite difficult. */
5737 macro_build ((char *) NULL, &icnt, &offset_expr, "lui", "t,u",
5738 tempreg, (int) BFD_RELOC_PCREL_HI16_S);
5739 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5740 ((bfd_arch_bits_per_address (stdoutput) == 32
5741 || ! ISA_HAS_64BIT_REGS (mips_opts.isa))
5742 ? "addu" : "daddu"),
5743 "d,v,t", tempreg, tempreg, breg);
5744 macro_build ((char *) NULL, &icnt, &offset_expr, s, fmt, treg,
5745 (int) BFD_RELOC_PCREL_LO16, tempreg);
5751 if (offset_expr.X_op != O_constant
5752 && offset_expr.X_op != O_symbol)
5754 as_bad (_("expression too complex"));
5755 offset_expr.X_op = O_constant;
5758 /* A constant expression in PIC code can be handled just as it
5759 is in non PIC code. */
5760 if (mips_pic == NO_PIC
5761 || offset_expr.X_op == O_constant)
5765 /* If this is a reference to a GP relative symbol, and there
5766 is no base register, we want
5767 <op> $treg,<sym>($gp) (BFD_RELOC_GPREL16)
5768 Otherwise, if there is no base register, we want
5769 lui $tempreg,<sym> (BFD_RELOC_HI16_S)
5770 <op> $treg,<sym>($tempreg) (BFD_RELOC_LO16)
5771 If we have a constant, we need two instructions anyhow,
5772 so we always use the latter form.
5774 If we have a base register, and this is a reference to a
5775 GP relative symbol, we want
5776 addu $tempreg,$breg,$gp
5777 <op> $treg,<sym>($tempreg) (BFD_RELOC_GPREL16)
5779 lui $tempreg,<sym> (BFD_RELOC_HI16_S)
5780 addu $tempreg,$tempreg,$breg
5781 <op> $treg,<sym>($tempreg) (BFD_RELOC_LO16)
5782 With a constant we always use the latter case.
5784 With 64bit address space and no base register and $at usable,
5786 lui $tempreg,<sym> (BFD_RELOC_MIPS_HIGHEST)
5787 lui $at,<sym> (BFD_RELOC_HI16_S)
5788 daddiu $tempreg,<sym> (BFD_RELOC_MIPS_HIGHER)
5791 <op> $treg,<sym>($tempreg) (BFD_RELOC_LO16)
5792 If we have a base register, we want
5793 lui $tempreg,<sym> (BFD_RELOC_MIPS_HIGHEST)
5794 lui $at,<sym> (BFD_RELOC_HI16_S)
5795 daddiu $tempreg,<sym> (BFD_RELOC_MIPS_HIGHER)
5799 <op> $treg,<sym>($tempreg) (BFD_RELOC_LO16)
5801 Without $at we can't generate the optimal path for superscalar
5802 processors here since this would require two temporary registers.
5803 lui $tempreg,<sym> (BFD_RELOC_MIPS_HIGHEST)
5804 daddiu $tempreg,<sym> (BFD_RELOC_MIPS_HIGHER)
5806 daddiu $tempreg,<sym> (BFD_RELOC_HI16_S)
5808 <op> $treg,<sym>($tempreg) (BFD_RELOC_LO16)
5809 If we have a base register, we want
5810 lui $tempreg,<sym> (BFD_RELOC_MIPS_HIGHEST)
5811 daddiu $tempreg,<sym> (BFD_RELOC_MIPS_HIGHER)
5813 daddiu $tempreg,<sym> (BFD_RELOC_HI16_S)
5815 daddu $tempreg,$tempreg,$breg
5816 <op> $treg,<sym>($tempreg) (BFD_RELOC_LO16)
5818 If we have 64-bit addresses, as an optimization, for
5819 addresses which are 32-bit constants (e.g. kseg0/kseg1
5820 addresses) we fall back to the 32-bit address generation
5821 mechanism since it is more efficient. Note that due to
5822 the signed offset used by memory operations, the 32-bit
5823 range is shifted down by 32768 here. This code should
5824 probably attempt to generate 64-bit constants more
5825 efficiently in general.
5827 if (HAVE_64BIT_ADDRESSES
5828 && !(offset_expr.X_op == O_constant
5829 && IS_SEXT_32BIT_NUM (offset_expr.X_add_number + 0x8000)))
5833 /* We don't do GP optimization for now because RELAX_ENCODE can't
5834 hold the data for such large chunks. */
5836 if (used_at == 0 && ! mips_opts.noat)
5838 macro_build (p, &icnt, &offset_expr, "lui", "t,u",
5839 tempreg, (int) BFD_RELOC_MIPS_HIGHEST);
5840 macro_build (p, &icnt, &offset_expr, "lui", "t,u",
5841 AT, (int) BFD_RELOC_HI16_S);
5842 macro_build (p, &icnt, &offset_expr, "daddiu", "t,r,j",
5843 tempreg, tempreg, (int) BFD_RELOC_MIPS_HIGHER);
5845 macro_build (p, &icnt, (expressionS *) NULL, "daddu",
5846 "d,v,t", AT, AT, breg);
5847 macro_build (p, &icnt, (expressionS *) NULL, "dsll32",
5848 "d,w,<", tempreg, tempreg, 0);
5849 macro_build (p, &icnt, (expressionS *) NULL, "daddu",
5850 "d,v,t", tempreg, tempreg, AT);
5851 macro_build (p, &icnt, &offset_expr, s,
5852 fmt, treg, (int) BFD_RELOC_LO16, tempreg);
5857 macro_build (p, &icnt, &offset_expr, "lui", "t,u",
5858 tempreg, (int) BFD_RELOC_MIPS_HIGHEST);
5859 macro_build (p, &icnt, &offset_expr, "daddiu", "t,r,j",
5860 tempreg, tempreg, (int) BFD_RELOC_MIPS_HIGHER);
5861 macro_build (p, &icnt, (expressionS *) NULL, "dsll",
5862 "d,w,<", tempreg, tempreg, 16);
5863 macro_build (p, &icnt, &offset_expr, "daddiu", "t,r,j",
5864 tempreg, tempreg, (int) BFD_RELOC_HI16_S);
5865 macro_build (p, &icnt, (expressionS *) NULL, "dsll",
5866 "d,w,<", tempreg, tempreg, 16);
5868 macro_build (p, &icnt, (expressionS *) NULL, "daddu",
5869 "d,v,t", tempreg, tempreg, breg);
5870 macro_build (p, &icnt, &offset_expr, s,
5871 fmt, treg, (int) BFD_RELOC_LO16, tempreg);
5879 if ((valueT) offset_expr.X_add_number > MAX_GPREL_OFFSET
5880 || nopic_need_relax (offset_expr.X_add_symbol, 1))
5885 macro_build ((char *) NULL, &icnt, &offset_expr, s, fmt,
5886 treg, (int) BFD_RELOC_GPREL16,
5888 p = frag_var (rs_machine_dependent, 8, 0,
5889 RELAX_ENCODE (4, 8, 0, 4, 0,
5890 (mips_opts.warn_about_macros
5892 && mips_opts.noat))),
5893 offset_expr.X_add_symbol, 0, NULL);
5896 macro_build_lui (p, &icnt, &offset_expr, tempreg);
5899 macro_build (p, &icnt, &offset_expr, s, fmt, treg,
5900 (int) BFD_RELOC_LO16, tempreg);
5904 if ((valueT) offset_expr.X_add_number > MAX_GPREL_OFFSET
5905 || nopic_need_relax (offset_expr.X_add_symbol, 1))
5910 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5911 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
5912 "d,v,t", tempreg, breg, mips_gp_register);
5913 macro_build ((char *) NULL, &icnt, &offset_expr, s, fmt,
5914 treg, (int) BFD_RELOC_GPREL16, tempreg);
5915 p = frag_var (rs_machine_dependent, 12, 0,
5916 RELAX_ENCODE (8, 12, 0, 8, 0, 0),
5917 offset_expr.X_add_symbol, 0, NULL);
5919 macro_build_lui (p, &icnt, &offset_expr, tempreg);
5922 macro_build (p, &icnt, (expressionS *) NULL,
5923 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
5924 "d,v,t", tempreg, tempreg, breg);
5927 macro_build (p, &icnt, &offset_expr, s, fmt, treg,
5928 (int) BFD_RELOC_LO16, tempreg);
5931 else if (mips_pic == SVR4_PIC && ! mips_big_got)
5934 int lw_reloc_type = (int) BFD_RELOC_MIPS_GOT16;
5936 /* If this is a reference to an external symbol, we want
5937 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
5939 <op> $treg,0($tempreg)
5941 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
5943 addiu $tempreg,$tempreg,<sym> (BFD_RELOC_LO16)
5944 <op> $treg,0($tempreg)
5945 If we have NewABI, we want
5946 lw $reg,<sym>($gp) (BFD_RELOC_MIPS_GOT_DISP)
5947 If there is a base register, we add it to $tempreg before
5948 the <op>. If there is a constant, we stick it in the
5949 <op> instruction. We don't handle constants larger than
5950 16 bits, because we have no way to load the upper 16 bits
5951 (actually, we could handle them for the subset of cases
5952 in which we are not using $at). */
5953 assert (offset_expr.X_op == O_symbol);
5954 expr1.X_add_number = offset_expr.X_add_number;
5955 offset_expr.X_add_number = 0;
5957 lw_reloc_type = (int) BFD_RELOC_MIPS_GOT_DISP;
5958 if (expr1.X_add_number < -0x8000
5959 || expr1.X_add_number >= 0x8000)
5960 as_bad (_("PIC code offset overflow (max 16 signed bits)"));
5962 macro_build ((char *) NULL, &icnt, &offset_expr,
5963 HAVE_32BIT_ADDRESSES ? "lw" : "ld", "t,o(b)", tempreg,
5964 (int) lw_reloc_type, mips_gp_register);
5965 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "");
5966 p = frag_var (rs_machine_dependent, 4, 0,
5967 RELAX_ENCODE (0, 4, -8, 0, 0, 0),
5968 offset_expr.X_add_symbol, 0, NULL);
5969 macro_build (p, &icnt, &offset_expr,
5970 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
5971 "t,r,j", tempreg, tempreg, (int) BFD_RELOC_LO16);
5973 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5974 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
5975 "d,v,t", tempreg, tempreg, breg);
5976 macro_build ((char *) NULL, &icnt, &expr1, s, fmt, treg,
5977 (int) BFD_RELOC_LO16, tempreg);
5979 else if (mips_pic == SVR4_PIC)
5984 /* If this is a reference to an external symbol, we want
5985 lui $tempreg,<sym> (BFD_RELOC_MIPS_GOT_HI16)
5986 addu $tempreg,$tempreg,$gp
5987 lw $tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_LO16)
5988 <op> $treg,0($tempreg)
5990 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
5992 addiu $tempreg,$tempreg,<sym> (BFD_RELOC_LO16)
5993 <op> $treg,0($tempreg)
5994 If there is a base register, we add it to $tempreg before
5995 the <op>. If there is a constant, we stick it in the
5996 <op> instruction. We don't handle constants larger than
5997 16 bits, because we have no way to load the upper 16 bits
5998 (actually, we could handle them for the subset of cases
5999 in which we are not using $at).
6002 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT_PAGE)
6003 addiu $tempreg,$tempreg,<sym> (BFD_RELOC_MIPS_GOT_OFST)
6004 <op> $treg,0($tempreg)
6006 assert (offset_expr.X_op == O_symbol);
6007 expr1.X_add_number = offset_expr.X_add_number;
6008 offset_expr.X_add_number = 0;
6009 if (expr1.X_add_number < -0x8000
6010 || expr1.X_add_number >= 0x8000)
6011 as_bad (_("PIC code offset overflow (max 16 signed bits)"));
6014 macro_build ((char *) NULL, &icnt, &offset_expr,
6015 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
6016 "t,o(b)", tempreg, BFD_RELOC_MIPS_GOT_PAGE,
6018 macro_build ((char *) NULL, &icnt, &offset_expr,
6019 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
6020 "t,r,j", tempreg, tempreg,
6021 BFD_RELOC_MIPS_GOT_OFST);
6023 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6024 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
6025 "d,v,t", tempreg, tempreg, breg);
6026 macro_build ((char *) NULL, &icnt, &expr1, s, fmt, treg,
6027 (int) BFD_RELOC_LO16, tempreg);
6034 if (reg_needs_delay (mips_gp_register))
6039 macro_build ((char *) NULL, &icnt, &offset_expr, "lui", "t,u",
6040 tempreg, (int) BFD_RELOC_MIPS_GOT_HI16);
6041 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6042 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
6043 "d,v,t", tempreg, tempreg, mips_gp_register);
6044 macro_build ((char *) NULL, &icnt, &offset_expr,
6045 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
6046 "t,o(b)", tempreg, (int) BFD_RELOC_MIPS_GOT_LO16,
6048 p = frag_var (rs_machine_dependent, 12 + gpdel, 0,
6049 RELAX_ENCODE (12, 12 + gpdel, gpdel, 8 + gpdel, 0, 0),
6050 offset_expr.X_add_symbol, 0, NULL);
6053 macro_build (p, &icnt, (expressionS *) NULL, "nop", "");
6056 macro_build (p, &icnt, &offset_expr,
6057 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
6058 "t,o(b)", tempreg, (int) BFD_RELOC_MIPS_GOT16,
6061 macro_build (p, &icnt, (expressionS *) NULL, "nop", "");
6063 macro_build (p, &icnt, &offset_expr,
6064 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu",
6065 "t,r,j", tempreg, tempreg, (int) BFD_RELOC_LO16);
6067 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6068 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
6069 "d,v,t", tempreg, tempreg, breg);
6070 macro_build ((char *) NULL, &icnt, &expr1, s, fmt, treg,
6071 (int) BFD_RELOC_LO16, tempreg);
6073 else if (mips_pic == EMBEDDED_PIC)
6075 /* If there is no base register, we want
6076 <op> $treg,<sym>($gp) (BFD_RELOC_GPREL16)
6077 If there is a base register, we want
6078 addu $tempreg,$breg,$gp
6079 <op> $treg,<sym>($tempreg) (BFD_RELOC_GPREL16)
6081 assert (offset_expr.X_op == O_symbol);
6084 macro_build ((char *) NULL, &icnt, &offset_expr, s, fmt,
6085 treg, (int) BFD_RELOC_GPREL16, mips_gp_register);
6090 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6091 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
6092 "d,v,t", tempreg, breg, mips_gp_register);
6093 macro_build ((char *) NULL, &icnt, &offset_expr, s, fmt,
6094 treg, (int) BFD_RELOC_GPREL16, tempreg);
6107 load_register (&icnt, treg, &imm_expr, 0);
6111 load_register (&icnt, treg, &imm_expr, 1);
6115 if (imm_expr.X_op == O_constant)
6117 load_register (&icnt, AT, &imm_expr, 0);
6118 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6119 "mtc1", "t,G", AT, treg);
6124 assert (offset_expr.X_op == O_symbol
6125 && strcmp (segment_name (S_GET_SEGMENT
6126 (offset_expr.X_add_symbol)),
6128 && offset_expr.X_add_number == 0);
6129 macro_build ((char *) NULL, &icnt, &offset_expr, "lwc1", "T,o(b)",
6130 treg, (int) BFD_RELOC_MIPS_LITERAL, mips_gp_register);
6135 /* Check if we have a constant in IMM_EXPR. If the GPRs are 64 bits
6136 wide, IMM_EXPR is the entire value. Otherwise IMM_EXPR is the high
6137 order 32 bits of the value and the low order 32 bits are either
6138 zero or in OFFSET_EXPR. */
6139 if (imm_expr.X_op == O_constant || imm_expr.X_op == O_big)
6141 if (HAVE_64BIT_GPRS)
6142 load_register (&icnt, treg, &imm_expr, 1);
6147 if (target_big_endian)
6159 load_register (&icnt, hreg, &imm_expr, 0);
6162 if (offset_expr.X_op == O_absent)
6163 move_register (&icnt, lreg, 0);
6166 assert (offset_expr.X_op == O_constant);
6167 load_register (&icnt, lreg, &offset_expr, 0);
6174 /* We know that sym is in the .rdata section. First we get the
6175 upper 16 bits of the address. */
6176 if (mips_pic == NO_PIC)
6178 macro_build_lui (NULL, &icnt, &offset_expr, AT);
6180 else if (mips_pic == SVR4_PIC)
6182 macro_build ((char *) NULL, &icnt, &offset_expr,
6183 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
6184 "t,o(b)", AT, (int) BFD_RELOC_MIPS_GOT16,
6187 else if (mips_pic == EMBEDDED_PIC)
6189 /* For embedded PIC we pick up the entire address off $gp in
6190 a single instruction. */
6191 macro_build ((char *) NULL, &icnt, &offset_expr,
6192 HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu", "t,r,j", AT,
6193 mips_gp_register, (int) BFD_RELOC_GPREL16);
6194 offset_expr.X_op = O_constant;
6195 offset_expr.X_add_number = 0;
6200 /* Now we load the register(s). */
6201 if (HAVE_64BIT_GPRS)
6202 macro_build ((char *) NULL, &icnt, &offset_expr, "ld", "t,o(b)",
6203 treg, (int) BFD_RELOC_LO16, AT);
6206 macro_build ((char *) NULL, &icnt, &offset_expr, "lw", "t,o(b)",
6207 treg, (int) BFD_RELOC_LO16, AT);
6210 /* FIXME: How in the world do we deal with the possible
6212 offset_expr.X_add_number += 4;
6213 macro_build ((char *) NULL, &icnt, &offset_expr, "lw", "t,o(b)",
6214 treg + 1, (int) BFD_RELOC_LO16, AT);
6218 /* To avoid confusion in tc_gen_reloc, we must ensure that this
6219 does not become a variant frag. */
6220 frag_wane (frag_now);
6226 /* Check if we have a constant in IMM_EXPR. If the FPRs are 64 bits
6227 wide, IMM_EXPR is the entire value and the GPRs are known to be 64
6228 bits wide as well. Otherwise IMM_EXPR is the high order 32 bits of
6229 the value and the low order 32 bits are either zero or in
6231 if (imm_expr.X_op == O_constant || imm_expr.X_op == O_big)
6233 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_FPRS);
6234 if (HAVE_64BIT_FPRS)
6236 assert (HAVE_64BIT_GPRS);
6237 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6238 "dmtc1", "t,S", AT, treg);
6242 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6243 "mtc1", "t,G", AT, treg + 1);
6244 if (offset_expr.X_op == O_absent)
6245 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6246 "mtc1", "t,G", 0, treg);
6249 assert (offset_expr.X_op == O_constant);
6250 load_register (&icnt, AT, &offset_expr, 0);
6251 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6252 "mtc1", "t,G", AT, treg);
6258 assert (offset_expr.X_op == O_symbol
6259 && offset_expr.X_add_number == 0);
6260 s = segment_name (S_GET_SEGMENT (offset_expr.X_add_symbol));
6261 if (strcmp (s, ".lit8") == 0)
6263 if (mips_opts.isa != ISA_MIPS1)
6265 macro_build ((char *) NULL, &icnt, &offset_expr, "ldc1",
6266 "T,o(b)", treg, (int) BFD_RELOC_MIPS_LITERAL,
6270 breg = mips_gp_register;
6271 r = BFD_RELOC_MIPS_LITERAL;
6276 assert (strcmp (s, RDATA_SECTION_NAME) == 0);
6277 if (mips_pic == SVR4_PIC)
6278 macro_build ((char *) NULL, &icnt, &offset_expr,
6279 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
6280 "t,o(b)", AT, (int) BFD_RELOC_MIPS_GOT16,
6284 /* FIXME: This won't work for a 64 bit address. */
6285 macro_build_lui (NULL, &icnt, &offset_expr, AT);
6288 if (mips_opts.isa != ISA_MIPS1)
6290 macro_build ((char *) NULL, &icnt, &offset_expr, "ldc1",
6291 "T,o(b)", treg, (int) BFD_RELOC_LO16, AT);
6293 /* To avoid confusion in tc_gen_reloc, we must ensure
6294 that this does not become a variant frag. */
6295 frag_wane (frag_now);
6306 if (mips_arch == CPU_R4650)
6308 as_bad (_("opcode not supported on this processor"));
6311 /* Even on a big endian machine $fn comes before $fn+1. We have
6312 to adjust when loading from memory. */
6315 assert (mips_opts.isa == ISA_MIPS1);
6316 macro_build ((char *) NULL, &icnt, &offset_expr, "lwc1", "T,o(b)",
6317 target_big_endian ? treg + 1 : treg,
6319 /* FIXME: A possible overflow which I don't know how to deal
6321 offset_expr.X_add_number += 4;
6322 macro_build ((char *) NULL, &icnt, &offset_expr, "lwc1", "T,o(b)",
6323 target_big_endian ? treg : treg + 1,
6326 /* To avoid confusion in tc_gen_reloc, we must ensure that this
6327 does not become a variant frag. */
6328 frag_wane (frag_now);
6337 * The MIPS assembler seems to check for X_add_number not
6338 * being double aligned and generating:
6341 * addiu at,at,%lo(foo+1)
6344 * But, the resulting address is the same after relocation so why
6345 * generate the extra instruction?
6347 if (mips_arch == CPU_R4650)
6349 as_bad (_("opcode not supported on this processor"));
6352 /* Itbl support may require additional care here. */
6354 if (mips_opts.isa != ISA_MIPS1)
6365 if (mips_arch == CPU_R4650)
6367 as_bad (_("opcode not supported on this processor"));
6371 if (mips_opts.isa != ISA_MIPS1)
6379 /* Itbl support may require additional care here. */
6384 if (HAVE_64BIT_GPRS)
6395 if (HAVE_64BIT_GPRS)
6405 /* We do _not_ bother to allow embedded PIC (symbol-local_symbol)
6406 loads for the case of doing a pair of loads to simulate an 'ld'.
6407 This is not currently done by the compiler, and assembly coders
6408 writing embedded-pic code can cope. */
6410 if (offset_expr.X_op != O_symbol
6411 && offset_expr.X_op != O_constant)
6413 as_bad (_("expression too complex"));
6414 offset_expr.X_op = O_constant;
6417 /* Even on a big endian machine $fn comes before $fn+1. We have
6418 to adjust when loading from memory. We set coproc if we must
6419 load $fn+1 first. */
6420 /* Itbl support may require additional care here. */
6421 if (! target_big_endian)
6424 if (mips_pic == NO_PIC
6425 || offset_expr.X_op == O_constant)
6429 /* If this is a reference to a GP relative symbol, we want
6430 <op> $treg,<sym>($gp) (BFD_RELOC_GPREL16)
6431 <op> $treg+1,<sym>+4($gp) (BFD_RELOC_GPREL16)
6432 If we have a base register, we use this
6434 <op> $treg,<sym>($at) (BFD_RELOC_GPREL16)
6435 <op> $treg+1,<sym>+4($at) (BFD_RELOC_GPREL16)
6436 If this is not a GP relative symbol, we want
6437 lui $at,<sym> (BFD_RELOC_HI16_S)
6438 <op> $treg,<sym>($at) (BFD_RELOC_LO16)
6439 <op> $treg+1,<sym>+4($at) (BFD_RELOC_LO16)
6440 If there is a base register, we add it to $at after the
6441 lui instruction. If there is a constant, we always use
6443 if ((valueT) offset_expr.X_add_number > MAX_GPREL_OFFSET
6444 || nopic_need_relax (offset_expr.X_add_symbol, 1))
6456 tempreg = mips_gp_register;
6463 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6464 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
6465 "d,v,t", AT, breg, mips_gp_register);
6471 /* Itbl support may require additional care here. */
6472 macro_build ((char *) NULL, &icnt, &offset_expr, s, fmt,
6473 coproc ? treg + 1 : treg,
6474 (int) BFD_RELOC_GPREL16, tempreg);
6475 offset_expr.X_add_number += 4;
6477 /* Set mips_optimize to 2 to avoid inserting an
6479 hold_mips_optimize = mips_optimize;
6481 /* Itbl support may require additional care here. */
6482 macro_build ((char *) NULL, &icnt, &offset_expr, s, fmt,
6483 coproc ? treg : treg + 1,
6484 (int) BFD_RELOC_GPREL16, tempreg);
6485 mips_optimize = hold_mips_optimize;
6487 p = frag_var (rs_machine_dependent, 12 + off, 0,
6488 RELAX_ENCODE (8 + off, 12 + off, 0, 4 + off, 1,
6489 used_at && mips_opts.noat),
6490 offset_expr.X_add_symbol, 0, NULL);
6492 /* We just generated two relocs. When tc_gen_reloc
6493 handles this case, it will skip the first reloc and
6494 handle the second. The second reloc already has an
6495 extra addend of 4, which we added above. We must
6496 subtract it out, and then subtract another 4 to make
6497 the first reloc come out right. The second reloc
6498 will come out right because we are going to add 4 to
6499 offset_expr when we build its instruction below.
6501 If we have a symbol, then we don't want to include
6502 the offset, because it will wind up being included
6503 when we generate the reloc. */
6505 if (offset_expr.X_op == O_constant)
6506 offset_expr.X_add_number -= 8;
6509 offset_expr.X_add_number = -4;
6510 offset_expr.X_op = O_constant;
6513 macro_build_lui (p, &icnt, &offset_expr, AT);
6518 macro_build (p, &icnt, (expressionS *) NULL,
6519 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
6520 "d,v,t", AT, breg, AT);
6524 /* Itbl support may require additional care here. */
6525 macro_build (p, &icnt, &offset_expr, s, fmt,
6526 coproc ? treg + 1 : treg,
6527 (int) BFD_RELOC_LO16, AT);
6530 /* FIXME: How do we handle overflow here? */
6531 offset_expr.X_add_number += 4;
6532 /* Itbl support may require additional care here. */
6533 macro_build (p, &icnt, &offset_expr, s, fmt,
6534 coproc ? treg : treg + 1,
6535 (int) BFD_RELOC_LO16, AT);
6537 else if (mips_pic == SVR4_PIC && ! mips_big_got)
6541 /* If this is a reference to an external symbol, we want
6542 lw $at,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
6547 lw $at,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
6549 <op> $treg,<sym>($at) (BFD_RELOC_LO16)
6550 <op> $treg+1,<sym>+4($at) (BFD_RELOC_LO16)
6551 If there is a base register we add it to $at before the
6552 lwc1 instructions. If there is a constant we include it
6553 in the lwc1 instructions. */
6555 expr1.X_add_number = offset_expr.X_add_number;
6556 offset_expr.X_add_number = 0;
6557 if (expr1.X_add_number < -0x8000
6558 || expr1.X_add_number >= 0x8000 - 4)
6559 as_bad (_("PIC code offset overflow (max 16 signed bits)"));
6564 frag_grow (24 + off);
6565 macro_build ((char *) NULL, &icnt, &offset_expr,
6566 HAVE_32BIT_ADDRESSES ? "lw" : "ld", "t,o(b)", AT,
6567 (int) BFD_RELOC_MIPS_GOT16, mips_gp_register);
6568 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "");
6570 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6571 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
6572 "d,v,t", AT, breg, AT);
6573 /* Itbl support may require additional care here. */
6574 macro_build ((char *) NULL, &icnt, &expr1, s, fmt,
6575 coproc ? treg + 1 : treg,
6576 (int) BFD_RELOC_LO16, AT);
6577 expr1.X_add_number += 4;
6579 /* Set mips_optimize to 2 to avoid inserting an undesired
6581 hold_mips_optimize = mips_optimize;
6583 /* Itbl support may require additional care here. */
6584 macro_build ((char *) NULL, &icnt, &expr1, s, fmt,
6585 coproc ? treg : treg + 1,
6586 (int) BFD_RELOC_LO16, AT);
6587 mips_optimize = hold_mips_optimize;
6589 (void) frag_var (rs_machine_dependent, 0, 0,
6590 RELAX_ENCODE (0, 0, -16 - off, -8, 1, 0),
6591 offset_expr.X_add_symbol, 0, NULL);
6593 else if (mips_pic == SVR4_PIC)
6598 /* If this is a reference to an external symbol, we want
6599 lui $at,<sym> (BFD_RELOC_MIPS_GOT_HI16)
6601 lw $at,<sym>($at) (BFD_RELOC_MIPS_GOT_LO16)
6606 lw $at,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
6608 <op> $treg,<sym>($at) (BFD_RELOC_LO16)
6609 <op> $treg+1,<sym>+4($at) (BFD_RELOC_LO16)
6610 If there is a base register we add it to $at before the
6611 lwc1 instructions. If there is a constant we include it
6612 in the lwc1 instructions. */
6614 expr1.X_add_number = offset_expr.X_add_number;
6615 offset_expr.X_add_number = 0;
6616 if (expr1.X_add_number < -0x8000
6617 || expr1.X_add_number >= 0x8000 - 4)
6618 as_bad (_("PIC code offset overflow (max 16 signed bits)"));
6619 if (reg_needs_delay (mips_gp_register))
6628 macro_build ((char *) NULL, &icnt, &offset_expr, "lui", "t,u",
6629 AT, (int) BFD_RELOC_MIPS_GOT_HI16);
6630 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6631 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
6632 "d,v,t", AT, AT, mips_gp_register);
6633 macro_build ((char *) NULL, &icnt, &offset_expr,
6634 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
6635 "t,o(b)", AT, (int) BFD_RELOC_MIPS_GOT_LO16, AT);
6636 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "");
6638 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6639 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
6640 "d,v,t", AT, breg, AT);
6641 /* Itbl support may require additional care here. */
6642 macro_build ((char *) NULL, &icnt, &expr1, s, fmt,
6643 coproc ? treg + 1 : treg,
6644 (int) BFD_RELOC_LO16, AT);
6645 expr1.X_add_number += 4;
6647 /* Set mips_optimize to 2 to avoid inserting an undesired
6649 hold_mips_optimize = mips_optimize;
6651 /* Itbl support may require additional care here. */
6652 macro_build ((char *) NULL, &icnt, &expr1, s, fmt,
6653 coproc ? treg : treg + 1,
6654 (int) BFD_RELOC_LO16, AT);
6655 mips_optimize = hold_mips_optimize;
6656 expr1.X_add_number -= 4;
6658 p = frag_var (rs_machine_dependent, 16 + gpdel + off, 0,
6659 RELAX_ENCODE (24 + off, 16 + gpdel + off, gpdel,
6660 8 + gpdel + off, 1, 0),
6661 offset_expr.X_add_symbol, 0, NULL);
6664 macro_build (p, &icnt, (expressionS *) NULL, "nop", "");
6667 macro_build (p, &icnt, &offset_expr,
6668 HAVE_32BIT_ADDRESSES ? "lw" : "ld",
6669 "t,o(b)", AT, (int) BFD_RELOC_MIPS_GOT16,
6672 macro_build (p, &icnt, (expressionS *) NULL, "nop", "");
6676 macro_build (p, &icnt, (expressionS *) NULL,
6677 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
6678 "d,v,t", AT, breg, AT);
6681 /* Itbl support may require additional care here. */
6682 macro_build (p, &icnt, &expr1, s, fmt,
6683 coproc ? treg + 1 : treg,
6684 (int) BFD_RELOC_LO16, AT);
6686 expr1.X_add_number += 4;
6688 /* Set mips_optimize to 2 to avoid inserting an undesired
6690 hold_mips_optimize = mips_optimize;
6692 /* Itbl support may require additional care here. */
6693 macro_build (p, &icnt, &expr1, s, fmt,
6694 coproc ? treg : treg + 1,
6695 (int) BFD_RELOC_LO16, AT);
6696 mips_optimize = hold_mips_optimize;
6698 else if (mips_pic == EMBEDDED_PIC)
6700 /* If there is no base register, we use
6701 <op> $treg,<sym>($gp) (BFD_RELOC_GPREL16)
6702 <op> $treg+1,<sym>+4($gp) (BFD_RELOC_GPREL16)
6703 If we have a base register, we use
6705 <op> $treg,<sym>($at) (BFD_RELOC_GPREL16)
6706 <op> $treg+1,<sym>+4($at) (BFD_RELOC_GPREL16)
6710 tempreg = mips_gp_register;
6715 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6716 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
6717 "d,v,t", AT, breg, mips_gp_register);
6722 /* Itbl support may require additional care here. */
6723 macro_build ((char *) NULL, &icnt, &offset_expr, s, fmt,
6724 coproc ? treg + 1 : treg,
6725 (int) BFD_RELOC_GPREL16, tempreg);
6726 offset_expr.X_add_number += 4;
6727 /* Itbl support may require additional care here. */
6728 macro_build ((char *) NULL, &icnt, &offset_expr, s, fmt,
6729 coproc ? treg : treg + 1,
6730 (int) BFD_RELOC_GPREL16, tempreg);
6746 assert (HAVE_32BIT_ADDRESSES);
6747 macro_build ((char *) NULL, &icnt, &offset_expr, s, "t,o(b)", treg,
6748 (int) BFD_RELOC_LO16, breg);
6749 offset_expr.X_add_number += 4;
6750 macro_build ((char *) NULL, &icnt, &offset_expr, s, "t,o(b)", treg + 1,
6751 (int) BFD_RELOC_LO16, breg);
6754 /* New code added to support COPZ instructions.
6755 This code builds table entries out of the macros in mip_opcodes.
6756 R4000 uses interlocks to handle coproc delays.
6757 Other chips (like the R3000) require nops to be inserted for delays.
6759 FIXME: Currently, we require that the user handle delays.
6760 In order to fill delay slots for non-interlocked chips,
6761 we must have a way to specify delays based on the coprocessor.
6762 Eg. 4 cycles if load coproc reg from memory, 1 if in cache, etc.
6763 What are the side-effects of the cop instruction?
6764 What cache support might we have and what are its effects?
6765 Both coprocessor & memory require delays. how long???
6766 What registers are read/set/modified?
6768 If an itbl is provided to interpret cop instructions,
6769 this knowledge can be encoded in the itbl spec. */
6783 /* For now we just do C (same as Cz). The parameter will be
6784 stored in insn_opcode by mips_ip. */
6785 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "C",
6790 move_register (&icnt, dreg, sreg);
6793 #ifdef LOSING_COMPILER
6795 /* Try and see if this is a new itbl instruction.
6796 This code builds table entries out of the macros in mip_opcodes.
6797 FIXME: For now we just assemble the expression and pass it's
6798 value along as a 32-bit immediate.
6799 We may want to have the assembler assemble this value,
6800 so that we gain the assembler's knowledge of delay slots,
6802 Would it be more efficient to use mask (id) here? */
6803 if (itbl_have_entries
6804 && (immed_expr = itbl_assemble (ip->insn_mo->name, "")))
6806 s = ip->insn_mo->name;
6808 coproc = ITBL_DECODE_PNUM (immed_expr);;
6809 macro_build ((char *) NULL, &icnt, &immed_expr, s, "C");
6816 as_warn (_("Macro used $at after \".set noat\""));
6821 struct mips_cl_insn *ip;
6823 register int treg, sreg, dreg, breg;
6839 bfd_reloc_code_real_type r;
6842 treg = (ip->insn_opcode >> 16) & 0x1f;
6843 dreg = (ip->insn_opcode >> 11) & 0x1f;
6844 sreg = breg = (ip->insn_opcode >> 21) & 0x1f;
6845 mask = ip->insn_mo->mask;
6847 expr1.X_op = O_constant;
6848 expr1.X_op_symbol = NULL;
6849 expr1.X_add_symbol = NULL;
6850 expr1.X_add_number = 1;
6854 #endif /* LOSING_COMPILER */
6859 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6860 dbl ? "dmultu" : "multu", "s,t", sreg, treg);
6861 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "mflo", "d",
6868 /* The MIPS assembler some times generates shifts and adds. I'm
6869 not trying to be that fancy. GCC should do this for us
6871 load_register (&icnt, AT, &imm_expr, dbl);
6872 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6873 dbl ? "dmult" : "mult", "s,t", sreg, AT);
6874 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "mflo", "d",
6888 mips_emit_delays (TRUE);
6889 ++mips_opts.noreorder;
6890 mips_any_noreorder = 1;
6892 load_register (&icnt, AT, &imm_expr, dbl);
6893 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6894 dbl ? "dmult" : "mult", "s,t", sreg, imm ? AT : treg);
6895 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "mflo", "d",
6897 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6898 dbl ? "dsra32" : "sra", "d,w,<", dreg, dreg, RA);
6899 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "mfhi", "d",
6902 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "tne",
6903 "s,t,q", dreg, AT, 6);
6906 expr1.X_add_number = 8;
6907 macro_build ((char *) NULL, &icnt, &expr1, "beq", "s,t,p", dreg,
6909 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "",
6911 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "break",
6914 --mips_opts.noreorder;
6915 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "mflo", "d", dreg);
6928 mips_emit_delays (TRUE);
6929 ++mips_opts.noreorder;
6930 mips_any_noreorder = 1;
6932 load_register (&icnt, AT, &imm_expr, dbl);
6933 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6934 dbl ? "dmultu" : "multu",
6935 "s,t", sreg, imm ? AT : treg);
6936 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "mfhi", "d",
6938 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "mflo", "d",
6941 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "tne",
6945 expr1.X_add_number = 8;
6946 macro_build ((char *) NULL, &icnt, &expr1, "beq", "s,t,p", AT, 0);
6947 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "",
6949 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "break",
6952 --mips_opts.noreorder;
6956 if (ISA_HAS_DROR (mips_opts.isa) || CPU_HAS_DROR (mips_arch))
6968 macro_build ((char *) NULL, &icnt, NULL, "dnegu",
6969 "d,w", tempreg, treg);
6970 macro_build ((char *) NULL, &icnt, NULL, "drorv",
6971 "d,t,s", dreg, sreg, tempreg);
6976 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "dsubu",
6977 "d,v,t", AT, 0, treg);
6978 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "dsrlv",
6979 "d,t,s", AT, sreg, AT);
6980 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "dsllv",
6981 "d,t,s", dreg, sreg, treg);
6982 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or",
6983 "d,v,t", dreg, dreg, AT);
6987 if (ISA_HAS_ROR (mips_opts.isa) || CPU_HAS_ROR (mips_arch))
6999 macro_build ((char *) NULL, &icnt, NULL, "negu",
7000 "d,w", tempreg, treg);
7001 macro_build ((char *) NULL, &icnt, NULL, "rorv",
7002 "d,t,s", dreg, sreg, tempreg);
7007 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "subu",
7008 "d,v,t", AT, 0, treg);
7009 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "srlv",
7010 "d,t,s", AT, sreg, AT);
7011 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sllv",
7012 "d,t,s", dreg, sreg, treg);
7013 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or",
7014 "d,v,t", dreg, dreg, AT);
7022 if (imm_expr.X_op != O_constant)
7023 as_bad (_("Improper rotate count"));
7024 rot = imm_expr.X_add_number & 0x3f;
7025 if (ISA_HAS_DROR (mips_opts.isa) || CPU_HAS_DROR (mips_arch))
7027 rot = (64 - rot) & 0x3f;
7029 macro_build ((char *) NULL, &icnt, NULL, "dror32",
7030 "d,w,<", dreg, sreg, rot - 32);
7032 macro_build ((char *) NULL, &icnt, NULL, "dror",
7033 "d,w,<", dreg, sreg, rot);
7038 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "dsrl",
7039 "d,w,<", dreg, sreg, 0);
7042 l = (rot < 0x20) ? "dsll" : "dsll32";
7043 r = ((0x40 - rot) < 0x20) ? "dsrl" : "dsrl32";
7045 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, l,
7046 "d,w,<", AT, sreg, rot);
7047 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, r,
7048 "d,w,<", dreg, sreg, (0x20 - rot) & 0x1f);
7049 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or",
7050 "d,v,t", dreg, dreg, AT);
7058 if (imm_expr.X_op != O_constant)
7059 as_bad (_("Improper rotate count"));
7060 rot = imm_expr.X_add_number & 0x1f;
7061 if (ISA_HAS_ROR (mips_opts.isa) || CPU_HAS_ROR (mips_arch))
7063 macro_build ((char *) NULL, &icnt, NULL, "ror",
7064 "d,w,<", dreg, sreg, (32 - rot) & 0x1f);
7069 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "srl",
7070 "d,w,<", dreg, sreg, 0);
7073 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sll",
7074 "d,w,<", AT, sreg, rot);
7075 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "srl",
7076 "d,w,<", dreg, sreg, (0x20 - rot) & 0x1f);
7077 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or",
7078 "d,v,t", dreg, dreg, AT);
7083 if (ISA_HAS_DROR (mips_opts.isa) || CPU_HAS_DROR (mips_arch))
7085 macro_build ((char *) NULL, &icnt, NULL, "drorv",
7086 "d,t,s", dreg, sreg, treg);
7089 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "dsubu",
7090 "d,v,t", AT, 0, treg);
7091 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "dsllv",
7092 "d,t,s", AT, sreg, AT);
7093 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "dsrlv",
7094 "d,t,s", dreg, sreg, treg);
7095 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or",
7096 "d,v,t", dreg, dreg, AT);
7100 if (ISA_HAS_ROR (mips_opts.isa) || CPU_HAS_ROR (mips_arch))
7102 macro_build ((char *) NULL, &icnt, NULL, "rorv",
7103 "d,t,s", dreg, sreg, treg);
7106 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "subu",
7107 "d,v,t", AT, 0, treg);
7108 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sllv",
7109 "d,t,s", AT, sreg, AT);
7110 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "srlv",
7111 "d,t,s", dreg, sreg, treg);
7112 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or",
7113 "d,v,t", dreg, dreg, AT);
7121 if (imm_expr.X_op != O_constant)
7122 as_bad (_("Improper rotate count"));
7123 rot = imm_expr.X_add_number & 0x3f;
7124 if (ISA_HAS_DROR (mips_opts.isa) || CPU_HAS_DROR (mips_arch))
7127 macro_build ((char *) NULL, &icnt, NULL, "dror32",
7128 "d,w,<", dreg, sreg, rot - 32);
7130 macro_build ((char *) NULL, &icnt, NULL, "dror",
7131 "d,w,<", dreg, sreg, rot);
7136 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "dsrl",
7137 "d,w,<", dreg, sreg, 0);
7140 r = (rot < 0x20) ? "dsrl" : "dsrl32";
7141 l = ((0x40 - rot) < 0x20) ? "dsll" : "dsll32";
7143 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, r,
7144 "d,w,<", AT, sreg, rot);
7145 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, l,
7146 "d,w,<", dreg, sreg, (0x20 - rot) & 0x1f);
7147 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or",
7148 "d,v,t", dreg, dreg, AT);
7156 if (imm_expr.X_op != O_constant)
7157 as_bad (_("Improper rotate count"));
7158 rot = imm_expr.X_add_number & 0x1f;
7159 if (ISA_HAS_ROR (mips_opts.isa) || CPU_HAS_ROR (mips_arch))
7161 macro_build ((char *) NULL, &icnt, NULL, "ror",
7162 "d,w,<", dreg, sreg, rot);
7167 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "srl",
7168 "d,w,<", dreg, sreg, 0);
7171 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "srl",
7172 "d,w,<", AT, sreg, rot);
7173 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sll",
7174 "d,w,<", dreg, sreg, (0x20 - rot) & 0x1f);
7175 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or",
7176 "d,v,t", dreg, dreg, AT);
7181 if (mips_arch == CPU_R4650)
7183 as_bad (_("opcode not supported on this processor"));
7186 assert (mips_opts.isa == ISA_MIPS1);
7187 /* Even on a big endian machine $fn comes before $fn+1. We have
7188 to adjust when storing to memory. */
7189 macro_build ((char *) NULL, &icnt, &offset_expr, "swc1", "T,o(b)",
7190 target_big_endian ? treg + 1 : treg,
7191 (int) BFD_RELOC_LO16, breg);
7192 offset_expr.X_add_number += 4;
7193 macro_build ((char *) NULL, &icnt, &offset_expr, "swc1", "T,o(b)",
7194 target_big_endian ? treg : treg + 1,
7195 (int) BFD_RELOC_LO16, breg);
7200 macro_build ((char *) NULL, &icnt, &expr1, "sltiu", "t,r,j", dreg,
7201 treg, (int) BFD_RELOC_LO16);
7203 macro_build ((char *) NULL, &icnt, &expr1, "sltiu", "t,r,j", dreg,
7204 sreg, (int) BFD_RELOC_LO16);
7207 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "xor",
7208 "d,v,t", dreg, sreg, treg);
7209 macro_build ((char *) NULL, &icnt, &expr1, "sltiu", "t,r,j", dreg,
7210 dreg, (int) BFD_RELOC_LO16);
7215 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
7217 macro_build ((char *) NULL, &icnt, &expr1, "sltiu", "t,r,j", dreg,
7218 sreg, (int) BFD_RELOC_LO16);
7223 as_warn (_("Instruction %s: result is always false"),
7225 move_register (&icnt, dreg, 0);
7228 if (imm_expr.X_op == O_constant
7229 && imm_expr.X_add_number >= 0
7230 && imm_expr.X_add_number < 0x10000)
7232 macro_build ((char *) NULL, &icnt, &imm_expr, "xori", "t,r,i", dreg,
7233 sreg, (int) BFD_RELOC_LO16);
7236 else if (imm_expr.X_op == O_constant
7237 && imm_expr.X_add_number > -0x8000
7238 && imm_expr.X_add_number < 0)
7240 imm_expr.X_add_number = -imm_expr.X_add_number;
7241 macro_build ((char *) NULL, &icnt, &imm_expr,
7242 HAVE_32BIT_GPRS ? "addiu" : "daddiu",
7243 "t,r,j", dreg, sreg,
7244 (int) BFD_RELOC_LO16);
7249 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_GPRS);
7250 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "xor",
7251 "d,v,t", dreg, sreg, AT);
7254 macro_build ((char *) NULL, &icnt, &expr1, "sltiu", "t,r,j", dreg, dreg,
7255 (int) BFD_RELOC_LO16);
7260 case M_SGE: /* sreg >= treg <==> not (sreg < treg) */
7266 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "d,v,t",
7268 macro_build ((char *) NULL, &icnt, &expr1, "xori", "t,r,i", dreg, dreg,
7269 (int) BFD_RELOC_LO16);
7272 case M_SGE_I: /* sreg >= I <==> not (sreg < I) */
7274 if (imm_expr.X_op == O_constant
7275 && imm_expr.X_add_number >= -0x8000
7276 && imm_expr.X_add_number < 0x8000)
7278 macro_build ((char *) NULL, &icnt, &imm_expr,
7279 mask == M_SGE_I ? "slti" : "sltiu",
7280 "t,r,j", dreg, sreg, (int) BFD_RELOC_LO16);
7285 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_GPRS);
7286 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7287 mask == M_SGE_I ? "slt" : "sltu", "d,v,t", dreg, sreg,
7291 macro_build ((char *) NULL, &icnt, &expr1, "xori", "t,r,i", dreg, dreg,
7292 (int) BFD_RELOC_LO16);
7297 case M_SGT: /* sreg > treg <==> treg < sreg */
7303 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "d,v,t",
7307 case M_SGT_I: /* sreg > I <==> I < sreg */
7313 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_GPRS);
7314 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "d,v,t",
7318 case M_SLE: /* sreg <= treg <==> treg >= sreg <==> not (treg < sreg) */
7324 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "d,v,t",
7326 macro_build ((char *) NULL, &icnt, &expr1, "xori", "t,r,i", dreg, dreg,
7327 (int) BFD_RELOC_LO16);
7330 case M_SLE_I: /* sreg <= I <==> I >= sreg <==> not (I < sreg) */
7336 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_GPRS);
7337 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "d,v,t",
7339 macro_build ((char *) NULL, &icnt, &expr1, "xori", "t,r,i", dreg, dreg,
7340 (int) BFD_RELOC_LO16);
7344 if (imm_expr.X_op == O_constant
7345 && imm_expr.X_add_number >= -0x8000
7346 && imm_expr.X_add_number < 0x8000)
7348 macro_build ((char *) NULL, &icnt, &imm_expr, "slti", "t,r,j",
7349 dreg, sreg, (int) BFD_RELOC_LO16);
7352 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_GPRS);
7353 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "slt", "d,v,t",
7358 if (imm_expr.X_op == O_constant
7359 && imm_expr.X_add_number >= -0x8000
7360 && imm_expr.X_add_number < 0x8000)
7362 macro_build ((char *) NULL, &icnt, &imm_expr, "sltiu", "t,r,j",
7363 dreg, sreg, (int) BFD_RELOC_LO16);
7366 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_GPRS);
7367 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sltu",
7368 "d,v,t", dreg, sreg, AT);
7373 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sltu",
7374 "d,v,t", dreg, 0, treg);
7376 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sltu",
7377 "d,v,t", dreg, 0, sreg);
7380 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "xor",
7381 "d,v,t", dreg, sreg, treg);
7382 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sltu",
7383 "d,v,t", dreg, 0, dreg);
7388 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
7390 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sltu",
7391 "d,v,t", dreg, 0, sreg);
7396 as_warn (_("Instruction %s: result is always true"),
7398 macro_build ((char *) NULL, &icnt, &expr1,
7399 HAVE_32BIT_GPRS ? "addiu" : "daddiu",
7400 "t,r,j", dreg, 0, (int) BFD_RELOC_LO16);
7403 if (imm_expr.X_op == O_constant
7404 && imm_expr.X_add_number >= 0
7405 && imm_expr.X_add_number < 0x10000)
7407 macro_build ((char *) NULL, &icnt, &imm_expr, "xori", "t,r,i",
7408 dreg, sreg, (int) BFD_RELOC_LO16);
7411 else if (imm_expr.X_op == O_constant
7412 && imm_expr.X_add_number > -0x8000
7413 && imm_expr.X_add_number < 0)
7415 imm_expr.X_add_number = -imm_expr.X_add_number;
7416 macro_build ((char *) NULL, &icnt, &imm_expr,
7417 HAVE_32BIT_GPRS ? "addiu" : "daddiu",
7418 "t,r,j", dreg, sreg, (int) BFD_RELOC_LO16);
7423 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_GPRS);
7424 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "xor",
7425 "d,v,t", dreg, sreg, AT);
7428 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sltu",
7429 "d,v,t", dreg, 0, dreg);
7437 if (imm_expr.X_op == O_constant
7438 && imm_expr.X_add_number > -0x8000
7439 && imm_expr.X_add_number <= 0x8000)
7441 imm_expr.X_add_number = -imm_expr.X_add_number;
7442 macro_build ((char *) NULL, &icnt, &imm_expr,
7443 dbl ? "daddi" : "addi",
7444 "t,r,j", dreg, sreg, (int) BFD_RELOC_LO16);
7447 load_register (&icnt, AT, &imm_expr, dbl);
7448 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7449 dbl ? "dsub" : "sub", "d,v,t", dreg, sreg, AT);
7455 if (imm_expr.X_op == O_constant
7456 && imm_expr.X_add_number > -0x8000
7457 && imm_expr.X_add_number <= 0x8000)
7459 imm_expr.X_add_number = -imm_expr.X_add_number;
7460 macro_build ((char *) NULL, &icnt, &imm_expr,
7461 dbl ? "daddiu" : "addiu",
7462 "t,r,j", dreg, sreg, (int) BFD_RELOC_LO16);
7465 load_register (&icnt, AT, &imm_expr, dbl);
7466 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7467 dbl ? "dsubu" : "subu", "d,v,t", dreg, sreg, AT);
7488 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_GPRS);
7489 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "s,t", sreg,
7495 assert (mips_opts.isa == ISA_MIPS1);
7496 sreg = (ip->insn_opcode >> 11) & 0x1f; /* floating reg */
7497 dreg = (ip->insn_opcode >> 06) & 0x1f; /* floating reg */
7500 * Is the double cfc1 instruction a bug in the mips assembler;
7501 * or is there a reason for it?
7503 mips_emit_delays (TRUE);
7504 ++mips_opts.noreorder;
7505 mips_any_noreorder = 1;
7506 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "cfc1", "t,G",
7508 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "cfc1", "t,G",
7510 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "");
7511 expr1.X_add_number = 3;
7512 macro_build ((char *) NULL, &icnt, &expr1, "ori", "t,r,i", AT, treg,
7513 (int) BFD_RELOC_LO16);
7514 expr1.X_add_number = 2;
7515 macro_build ((char *) NULL, &icnt, &expr1, "xori", "t,r,i", AT, AT,
7516 (int) BFD_RELOC_LO16);
7517 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "ctc1", "t,G",
7519 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "");
7520 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7521 mask == M_TRUNCWD ? "cvt.w.d" : "cvt.w.s", "D,S", dreg, sreg);
7522 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "ctc1", "t,G",
7524 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "");
7525 --mips_opts.noreorder;
7534 if (offset_expr.X_add_number >= 0x7fff)
7535 as_bad (_("operand overflow"));
7536 /* avoid load delay */
7537 if (! target_big_endian)
7538 ++offset_expr.X_add_number;
7539 macro_build ((char *) NULL, &icnt, &offset_expr, s, "t,o(b)", treg,
7540 (int) BFD_RELOC_LO16, breg);
7541 if (! target_big_endian)
7542 --offset_expr.X_add_number;
7544 ++offset_expr.X_add_number;
7545 macro_build ((char *) NULL, &icnt, &offset_expr, "lbu", "t,o(b)", AT,
7546 (int) BFD_RELOC_LO16, breg);
7547 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sll", "d,w,<",
7549 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or", "d,v,t",
7563 if (offset_expr.X_add_number >= 0x8000 - off)
7564 as_bad (_("operand overflow"));
7565 if (! target_big_endian)
7566 offset_expr.X_add_number += off;
7567 macro_build ((char *) NULL, &icnt, &offset_expr, s, "t,o(b)", treg,
7568 (int) BFD_RELOC_LO16, breg);
7569 if (! target_big_endian)
7570 offset_expr.X_add_number -= off;
7572 offset_expr.X_add_number += off;
7573 macro_build ((char *) NULL, &icnt, &offset_expr, s2, "t,o(b)", treg,
7574 (int) BFD_RELOC_LO16, breg);
7588 load_address (&icnt, AT, &offset_expr, &used_at);
7590 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7591 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
7592 "d,v,t", AT, AT, breg);
7593 if (! target_big_endian)
7594 expr1.X_add_number = off;
7596 expr1.X_add_number = 0;
7597 macro_build ((char *) NULL, &icnt, &expr1, s, "t,o(b)", treg,
7598 (int) BFD_RELOC_LO16, AT);
7599 if (! target_big_endian)
7600 expr1.X_add_number = 0;
7602 expr1.X_add_number = off;
7603 macro_build ((char *) NULL, &icnt, &expr1, s2, "t,o(b)", treg,
7604 (int) BFD_RELOC_LO16, AT);
7610 load_address (&icnt, AT, &offset_expr, &used_at);
7612 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7613 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
7614 "d,v,t", AT, AT, breg);
7615 if (target_big_endian)
7616 expr1.X_add_number = 0;
7617 macro_build ((char *) NULL, &icnt, &expr1,
7618 mask == M_ULH_A ? "lb" : "lbu", "t,o(b)", treg,
7619 (int) BFD_RELOC_LO16, AT);
7620 if (target_big_endian)
7621 expr1.X_add_number = 1;
7623 expr1.X_add_number = 0;
7624 macro_build ((char *) NULL, &icnt, &expr1, "lbu", "t,o(b)", AT,
7625 (int) BFD_RELOC_LO16, AT);
7626 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sll", "d,w,<",
7628 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or", "d,v,t",
7633 if (offset_expr.X_add_number >= 0x7fff)
7634 as_bad (_("operand overflow"));
7635 if (target_big_endian)
7636 ++offset_expr.X_add_number;
7637 macro_build ((char *) NULL, &icnt, &offset_expr, "sb", "t,o(b)", treg,
7638 (int) BFD_RELOC_LO16, breg);
7639 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "srl", "d,w,<",
7641 if (target_big_endian)
7642 --offset_expr.X_add_number;
7644 ++offset_expr.X_add_number;
7645 macro_build ((char *) NULL, &icnt, &offset_expr, "sb", "t,o(b)", AT,
7646 (int) BFD_RELOC_LO16, breg);
7659 if (offset_expr.X_add_number >= 0x8000 - off)
7660 as_bad (_("operand overflow"));
7661 if (! target_big_endian)
7662 offset_expr.X_add_number += off;
7663 macro_build ((char *) NULL, &icnt, &offset_expr, s, "t,o(b)", treg,
7664 (int) BFD_RELOC_LO16, breg);
7665 if (! target_big_endian)
7666 offset_expr.X_add_number -= off;
7668 offset_expr.X_add_number += off;
7669 macro_build ((char *) NULL, &icnt, &offset_expr, s2, "t,o(b)", treg,
7670 (int) BFD_RELOC_LO16, breg);
7684 load_address (&icnt, AT, &offset_expr, &used_at);
7686 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7687 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
7688 "d,v,t", AT, AT, breg);
7689 if (! target_big_endian)
7690 expr1.X_add_number = off;
7692 expr1.X_add_number = 0;
7693 macro_build ((char *) NULL, &icnt, &expr1, s, "t,o(b)", treg,
7694 (int) BFD_RELOC_LO16, AT);
7695 if (! target_big_endian)
7696 expr1.X_add_number = 0;
7698 expr1.X_add_number = off;
7699 macro_build ((char *) NULL, &icnt, &expr1, s2, "t,o(b)", treg,
7700 (int) BFD_RELOC_LO16, AT);
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 = 0;
7712 macro_build ((char *) NULL, &icnt, &expr1, "sb", "t,o(b)", treg,
7713 (int) BFD_RELOC_LO16, AT);
7714 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "srl", "d,w,<",
7716 if (! target_big_endian)
7717 expr1.X_add_number = 1;
7719 expr1.X_add_number = 0;
7720 macro_build ((char *) NULL, &icnt, &expr1, "sb", "t,o(b)", treg,
7721 (int) BFD_RELOC_LO16, AT);
7722 if (! target_big_endian)
7723 expr1.X_add_number = 0;
7725 expr1.X_add_number = 1;
7726 macro_build ((char *) NULL, &icnt, &expr1, "lbu", "t,o(b)", AT,
7727 (int) BFD_RELOC_LO16, AT);
7728 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sll", "d,w,<",
7730 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or", "d,v,t",
7735 /* FIXME: Check if this is one of the itbl macros, since they
7736 are added dynamically. */
7737 as_bad (_("Macro %s not implemented yet"), ip->insn_mo->name);
7741 as_warn (_("Macro used $at after \".set noat\""));
7744 /* Implement macros in mips16 mode. */
7748 struct mips_cl_insn *ip;
7751 int xreg, yreg, zreg, tmp;
7755 const char *s, *s2, *s3;
7757 mask = ip->insn_mo->mask;
7759 xreg = (ip->insn_opcode >> MIPS16OP_SH_RX) & MIPS16OP_MASK_RX;
7760 yreg = (ip->insn_opcode >> MIPS16OP_SH_RY) & MIPS16OP_MASK_RY;
7761 zreg = (ip->insn_opcode >> MIPS16OP_SH_RZ) & MIPS16OP_MASK_RZ;
7765 expr1.X_op = O_constant;
7766 expr1.X_op_symbol = NULL;
7767 expr1.X_add_symbol = NULL;
7768 expr1.X_add_number = 1;
7787 mips_emit_delays (TRUE);
7788 ++mips_opts.noreorder;
7789 mips_any_noreorder = 1;
7790 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7791 dbl ? "ddiv" : "div",
7792 "0,x,y", xreg, yreg);
7793 expr1.X_add_number = 2;
7794 macro_build ((char *) NULL, &icnt, &expr1, "bnez", "x,p", yreg);
7795 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "break", "6",
7798 /* FIXME: The normal code checks for of -1 / -0x80000000 here,
7799 since that causes an overflow. We should do that as well,
7800 but I don't see how to do the comparisons without a temporary
7802 --mips_opts.noreorder;
7803 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "x", zreg);
7822 mips_emit_delays (TRUE);
7823 ++mips_opts.noreorder;
7824 mips_any_noreorder = 1;
7825 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "0,x,y",
7827 expr1.X_add_number = 2;
7828 macro_build ((char *) NULL, &icnt, &expr1, "bnez", "x,p", yreg);
7829 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "break",
7831 --mips_opts.noreorder;
7832 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s2, "x", zreg);
7838 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7839 dbl ? "dmultu" : "multu", "x,y", xreg, yreg);
7840 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "mflo", "x",
7849 if (imm_expr.X_op != O_constant)
7850 as_bad (_("Unsupported large constant"));
7851 imm_expr.X_add_number = -imm_expr.X_add_number;
7852 macro_build ((char *) NULL, &icnt, &imm_expr,
7853 dbl ? "daddiu" : "addiu", "y,x,4", yreg, xreg);
7857 if (imm_expr.X_op != O_constant)
7858 as_bad (_("Unsupported large constant"));
7859 imm_expr.X_add_number = -imm_expr.X_add_number;
7860 macro_build ((char *) NULL, &icnt, &imm_expr, "addiu",
7865 if (imm_expr.X_op != O_constant)
7866 as_bad (_("Unsupported large constant"));
7867 imm_expr.X_add_number = -imm_expr.X_add_number;
7868 macro_build ((char *) NULL, &icnt, &imm_expr, "daddiu",
7891 goto do_reverse_branch;
7895 goto do_reverse_branch;
7907 goto do_reverse_branch;
7918 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "x,y",
7920 macro_build ((char *) NULL, &icnt, &offset_expr, s2, "p");
7947 goto do_addone_branch_i;
7952 goto do_addone_branch_i;
7967 goto do_addone_branch_i;
7974 if (imm_expr.X_op != O_constant)
7975 as_bad (_("Unsupported large constant"));
7976 ++imm_expr.X_add_number;
7979 macro_build ((char *) NULL, &icnt, &imm_expr, s, s3, xreg);
7980 macro_build ((char *) NULL, &icnt, &offset_expr, s2, "p");
7984 expr1.X_add_number = 0;
7985 macro_build ((char *) NULL, &icnt, &expr1, "slti", "x,8", yreg);
7987 move_register (&icnt, xreg, yreg);
7988 expr1.X_add_number = 2;
7989 macro_build ((char *) NULL, &icnt, &expr1, "bteqz", "p");
7990 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7991 "neg", "x,w", xreg, xreg);
7995 /* For consistency checking, verify that all bits are specified either
7996 by the match/mask part of the instruction definition, or by the
7999 validate_mips_insn (opc)
8000 const struct mips_opcode *opc;
8002 const char *p = opc->args;
8004 unsigned long used_bits = opc->mask;
8006 if ((used_bits & opc->match) != opc->match)
8008 as_bad (_("internal: bad mips opcode (mask error): %s %s"),
8009 opc->name, opc->args);
8012 #define USE_BITS(mask,shift) (used_bits |= ((mask) << (shift)))
8022 case 'A': USE_BITS (OP_MASK_SHAMT, OP_SH_SHAMT); break;
8023 case 'B': USE_BITS (OP_MASK_INSMSB, OP_SH_INSMSB); break;
8024 case 'C': USE_BITS (OP_MASK_EXTMSBD, OP_SH_EXTMSBD); break;
8026 as_bad (_("internal: bad mips opcode (unknown extension operand type `+%c'): %s %s"),
8027 c, opc->name, opc->args);
8031 case '<': USE_BITS (OP_MASK_SHAMT, OP_SH_SHAMT); break;
8032 case '>': USE_BITS (OP_MASK_SHAMT, OP_SH_SHAMT); break;
8034 case 'B': USE_BITS (OP_MASK_CODE20, OP_SH_CODE20); break;
8035 case 'C': USE_BITS (OP_MASK_COPZ, OP_SH_COPZ); break;
8036 case 'D': USE_BITS (OP_MASK_FD, OP_SH_FD); break;
8037 case 'E': USE_BITS (OP_MASK_RT, OP_SH_RT); break;
8039 case 'G': USE_BITS (OP_MASK_RD, OP_SH_RD); break;
8040 case 'H': USE_BITS (OP_MASK_SEL, OP_SH_SEL); break;
8042 case 'J': USE_BITS (OP_MASK_CODE19, OP_SH_CODE19); break;
8043 case 'K': USE_BITS (OP_MASK_RD, OP_SH_RD); break;
8045 case 'M': USE_BITS (OP_MASK_CCC, OP_SH_CCC); break;
8046 case 'N': USE_BITS (OP_MASK_BCC, OP_SH_BCC); break;
8047 case 'O': USE_BITS (OP_MASK_ALN, OP_SH_ALN); break;
8048 case 'Q': USE_BITS (OP_MASK_VSEL, OP_SH_VSEL);
8049 USE_BITS (OP_MASK_FT, OP_SH_FT); break;
8050 case 'R': USE_BITS (OP_MASK_FR, OP_SH_FR); break;
8051 case 'S': USE_BITS (OP_MASK_FS, OP_SH_FS); break;
8052 case 'T': USE_BITS (OP_MASK_FT, OP_SH_FT); break;
8053 case 'V': USE_BITS (OP_MASK_FS, OP_SH_FS); break;
8054 case 'W': USE_BITS (OP_MASK_FT, OP_SH_FT); break;
8055 case 'X': USE_BITS (OP_MASK_FD, OP_SH_FD); break;
8056 case 'Y': USE_BITS (OP_MASK_FS, OP_SH_FS); break;
8057 case 'Z': USE_BITS (OP_MASK_FT, OP_SH_FT); break;
8058 case 'a': USE_BITS (OP_MASK_TARGET, OP_SH_TARGET); break;
8059 case 'b': USE_BITS (OP_MASK_RS, OP_SH_RS); break;
8060 case 'c': USE_BITS (OP_MASK_CODE, OP_SH_CODE); break;
8061 case 'd': USE_BITS (OP_MASK_RD, OP_SH_RD); break;
8063 case 'h': USE_BITS (OP_MASK_PREFX, OP_SH_PREFX); break;
8064 case 'i': USE_BITS (OP_MASK_IMMEDIATE, OP_SH_IMMEDIATE); break;
8065 case 'j': USE_BITS (OP_MASK_DELTA, OP_SH_DELTA); break;
8066 case 'k': USE_BITS (OP_MASK_CACHE, OP_SH_CACHE); break;
8068 case 'o': USE_BITS (OP_MASK_DELTA, OP_SH_DELTA); break;
8069 case 'p': USE_BITS (OP_MASK_DELTA, OP_SH_DELTA); break;
8070 case 'q': USE_BITS (OP_MASK_CODE2, OP_SH_CODE2); break;
8071 case 'r': USE_BITS (OP_MASK_RS, OP_SH_RS); break;
8072 case 's': USE_BITS (OP_MASK_RS, OP_SH_RS); break;
8073 case 't': USE_BITS (OP_MASK_RT, OP_SH_RT); break;
8074 case 'u': USE_BITS (OP_MASK_IMMEDIATE, OP_SH_IMMEDIATE); break;
8075 case 'v': USE_BITS (OP_MASK_RS, OP_SH_RS); break;
8076 case 'w': USE_BITS (OP_MASK_RT, OP_SH_RT); break;
8079 case 'P': USE_BITS (OP_MASK_PERFREG, OP_SH_PERFREG); break;
8080 case 'U': USE_BITS (OP_MASK_RD, OP_SH_RD);
8081 USE_BITS (OP_MASK_RT, OP_SH_RT); break;
8082 case 'e': USE_BITS (OP_MASK_VECBYTE, OP_SH_VECBYTE); break;
8083 case '%': USE_BITS (OP_MASK_VECALIGN, OP_SH_VECALIGN); break;
8087 as_bad (_("internal: bad mips opcode (unknown operand type `%c'): %s %s"),
8088 c, opc->name, opc->args);
8092 if (used_bits != 0xffffffff)
8094 as_bad (_("internal: bad mips opcode (bits 0x%lx undefined): %s %s"),
8095 ~used_bits & 0xffffffff, opc->name, opc->args);
8101 /* This routine assembles an instruction into its binary format. As a
8102 side effect, it sets one of the global variables imm_reloc or
8103 offset_reloc to the type of relocation to do if one of the operands
8104 is an address expression. */
8109 struct mips_cl_insn *ip;
8114 struct mips_opcode *insn;
8117 unsigned int lastregno = 0;
8118 unsigned int lastpos = 0;
8124 /* If the instruction contains a '.', we first try to match an instruction
8125 including the '.'. Then we try again without the '.'. */
8127 for (s = str; *s != '\0' && !ISSPACE (*s); ++s)
8130 /* If we stopped on whitespace, then replace the whitespace with null for
8131 the call to hash_find. Save the character we replaced just in case we
8132 have to re-parse the instruction. */
8139 insn = (struct mips_opcode *) hash_find (op_hash, str);
8141 /* If we didn't find the instruction in the opcode table, try again, but
8142 this time with just the instruction up to, but not including the
8146 /* Restore the character we overwrite above (if any). */
8150 /* Scan up to the first '.' or whitespace. */
8152 *s != '\0' && *s != '.' && !ISSPACE (*s);
8156 /* If we did not find a '.', then we can quit now. */
8159 insn_error = "unrecognized opcode";
8163 /* Lookup the instruction in the hash table. */
8165 if ((insn = (struct mips_opcode *) hash_find (op_hash, str)) == NULL)
8167 insn_error = "unrecognized opcode";
8177 assert (strcmp (insn->name, str) == 0);
8179 if (OPCODE_IS_MEMBER (insn,
8181 | (file_ase_mips16 ? INSN_MIPS16 : 0)
8182 | (mips_opts.ase_mdmx ? INSN_MDMX : 0)
8183 | (mips_opts.ase_mips3d ? INSN_MIPS3D : 0)),
8189 if (insn->pinfo != INSN_MACRO)
8191 if (mips_arch == CPU_R4650 && (insn->pinfo & FP_D) != 0)
8197 if (insn + 1 < &mips_opcodes[NUMOPCODES]
8198 && strcmp (insn->name, insn[1].name) == 0)
8207 static char buf[100];
8208 if (mips_arch_info->is_isa)
8210 _("opcode not supported at this ISA level (%s)"),
8211 mips_cpu_info_from_isa (mips_opts.isa)->name);
8214 _("opcode not supported on this processor: %s (%s)"),
8215 mips_arch_info->name,
8216 mips_cpu_info_from_isa (mips_opts.isa)->name);
8226 ip->insn_opcode = insn->match;
8228 for (args = insn->args;; ++args)
8232 s += strspn (s, " \t");
8236 case '\0': /* end of args */
8249 ip->insn_opcode |= lastregno << OP_SH_RS;
8253 ip->insn_opcode |= lastregno << OP_SH_RT;
8257 ip->insn_opcode |= lastregno << OP_SH_FT;
8261 ip->insn_opcode |= lastregno << OP_SH_FS;
8267 /* Handle optional base register.
8268 Either the base register is omitted or
8269 we must have a left paren. */
8270 /* This is dependent on the next operand specifier
8271 is a base register specification. */
8272 assert (args[1] == 'b' || args[1] == '5'
8273 || args[1] == '-' || args[1] == '4');
8277 case ')': /* these must match exactly */
8284 case '+': /* Opcode extension character. */
8287 case 'A': /* ins/ext "pos". */
8288 my_getExpression (&imm_expr, s);
8289 check_absolute_expr (ip, &imm_expr);
8290 if ((unsigned long) imm_expr.X_add_number > 31)
8292 as_bad (_("Improper position (%lu)"),
8293 (unsigned long) imm_expr.X_add_number);
8294 imm_expr.X_add_number = 0;
8296 lastpos = imm_expr.X_add_number;
8297 ip->insn_opcode |= lastpos << OP_SH_SHAMT;
8298 imm_expr.X_op = O_absent;
8302 case 'B': /* "ins" size spec (becomes MSB). */
8303 my_getExpression (&imm_expr, s);
8304 check_absolute_expr (ip, &imm_expr);
8305 if (imm_expr.X_add_number == 0
8306 || (unsigned long) imm_expr.X_add_number > 32
8307 || ((unsigned long) imm_expr.X_add_number
8310 as_bad (_("Improper insert size (%lu, position %lu)"),
8311 (unsigned long) imm_expr.X_add_number,
8312 (unsigned long) lastpos);
8313 imm_expr.X_add_number &= OP_MASK_INSMSB;
8315 ip->insn_opcode |= (lastpos + imm_expr.X_add_number
8316 - 1) << OP_SH_INSMSB;
8317 imm_expr.X_op = O_absent;
8321 case 'C': /* "ext" size spec (becomes MSBD). */
8322 my_getExpression (&imm_expr, s);
8323 check_absolute_expr (ip, &imm_expr);
8324 if (imm_expr.X_add_number == 0
8325 || (unsigned long) imm_expr.X_add_number > 32
8326 || ((unsigned long) imm_expr.X_add_number
8329 as_bad (_("Improper extract size (%lu, position %lu)"),
8330 (unsigned long) imm_expr.X_add_number,
8331 (unsigned long) lastpos);
8332 imm_expr.X_add_number &= OP_MASK_EXTMSBD;
8334 ip->insn_opcode |= (imm_expr.X_add_number
8335 - 1) << OP_SH_EXTMSBD;
8336 imm_expr.X_op = O_absent;
8341 as_bad (_("internal: bad mips opcode (unknown extension operand type `+%c'): %s %s"),
8342 *args, insn->name, insn->args);
8343 /* Further processing is fruitless. */
8348 case '<': /* must be at least one digit */
8350 * According to the manual, if the shift amount is greater
8351 * than 31 or less than 0, then the shift amount should be
8352 * mod 32. In reality the mips assembler issues an error.
8353 * We issue a warning and mask out all but the low 5 bits.
8355 my_getExpression (&imm_expr, s);
8356 check_absolute_expr (ip, &imm_expr);
8357 if ((unsigned long) imm_expr.X_add_number > 31)
8359 as_warn (_("Improper shift amount (%lu)"),
8360 (unsigned long) imm_expr.X_add_number);
8361 imm_expr.X_add_number &= OP_MASK_SHAMT;
8363 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_SHAMT;
8364 imm_expr.X_op = O_absent;
8368 case '>': /* shift amount minus 32 */
8369 my_getExpression (&imm_expr, s);
8370 check_absolute_expr (ip, &imm_expr);
8371 if ((unsigned long) imm_expr.X_add_number < 32
8372 || (unsigned long) imm_expr.X_add_number > 63)
8374 ip->insn_opcode |= (imm_expr.X_add_number - 32) << OP_SH_SHAMT;
8375 imm_expr.X_op = O_absent;
8379 case 'k': /* cache code */
8380 case 'h': /* prefx code */
8381 my_getExpression (&imm_expr, s);
8382 check_absolute_expr (ip, &imm_expr);
8383 if ((unsigned long) imm_expr.X_add_number > 31)
8385 as_warn (_("Invalid value for `%s' (%lu)"),
8387 (unsigned long) imm_expr.X_add_number);
8388 imm_expr.X_add_number &= 0x1f;
8391 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_CACHE;
8393 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_PREFX;
8394 imm_expr.X_op = O_absent;
8398 case 'c': /* break code */
8399 my_getExpression (&imm_expr, s);
8400 check_absolute_expr (ip, &imm_expr);
8401 if ((unsigned long) imm_expr.X_add_number > 1023)
8403 as_warn (_("Illegal break code (%lu)"),
8404 (unsigned long) imm_expr.X_add_number);
8405 imm_expr.X_add_number &= OP_MASK_CODE;
8407 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_CODE;
8408 imm_expr.X_op = O_absent;
8412 case 'q': /* lower break code */
8413 my_getExpression (&imm_expr, s);
8414 check_absolute_expr (ip, &imm_expr);
8415 if ((unsigned long) imm_expr.X_add_number > 1023)
8417 as_warn (_("Illegal lower break code (%lu)"),
8418 (unsigned long) imm_expr.X_add_number);
8419 imm_expr.X_add_number &= OP_MASK_CODE2;
8421 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_CODE2;
8422 imm_expr.X_op = O_absent;
8426 case 'B': /* 20-bit syscall/break code. */
8427 my_getExpression (&imm_expr, s);
8428 check_absolute_expr (ip, &imm_expr);
8429 if ((unsigned long) imm_expr.X_add_number > OP_MASK_CODE20)
8430 as_warn (_("Illegal 20-bit code (%lu)"),
8431 (unsigned long) imm_expr.X_add_number);
8432 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_CODE20;
8433 imm_expr.X_op = O_absent;
8437 case 'C': /* Coprocessor code */
8438 my_getExpression (&imm_expr, s);
8439 check_absolute_expr (ip, &imm_expr);
8440 if ((unsigned long) imm_expr.X_add_number >= (1 << 25))
8442 as_warn (_("Coproccesor code > 25 bits (%lu)"),
8443 (unsigned long) imm_expr.X_add_number);
8444 imm_expr.X_add_number &= ((1 << 25) - 1);
8446 ip->insn_opcode |= imm_expr.X_add_number;
8447 imm_expr.X_op = O_absent;
8451 case 'J': /* 19-bit wait code. */
8452 my_getExpression (&imm_expr, s);
8453 check_absolute_expr (ip, &imm_expr);
8454 if ((unsigned long) imm_expr.X_add_number > OP_MASK_CODE19)
8455 as_warn (_("Illegal 19-bit code (%lu)"),
8456 (unsigned long) imm_expr.X_add_number);
8457 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_CODE19;
8458 imm_expr.X_op = O_absent;
8462 case 'P': /* Performance register */
8463 my_getExpression (&imm_expr, s);
8464 check_absolute_expr (ip, &imm_expr);
8465 if (imm_expr.X_add_number != 0 && imm_expr.X_add_number != 1)
8467 as_warn (_("Invalid performance register (%lu)"),
8468 (unsigned long) imm_expr.X_add_number);
8469 imm_expr.X_add_number &= OP_MASK_PERFREG;
8471 ip->insn_opcode |= (imm_expr.X_add_number << OP_SH_PERFREG);
8472 imm_expr.X_op = O_absent;
8476 case 'b': /* base register */
8477 case 'd': /* destination register */
8478 case 's': /* source register */
8479 case 't': /* target register */
8480 case 'r': /* both target and source */
8481 case 'v': /* both dest and source */
8482 case 'w': /* both dest and target */
8483 case 'E': /* coprocessor target register */
8484 case 'G': /* coprocessor destination register */
8485 case 'K': /* 'rdhwr' destination register */
8486 case 'x': /* ignore register name */
8487 case 'z': /* must be zero register */
8488 case 'U': /* destination register (clo/clz). */
8503 while (ISDIGIT (*s));
8505 as_bad (_("Invalid register number (%d)"), regno);
8507 else if (*args == 'E' || *args == 'G' || *args == 'K')
8511 if (s[1] == 'r' && s[2] == 'a')
8516 else if (s[1] == 'f' && s[2] == 'p')
8521 else if (s[1] == 's' && s[2] == 'p')
8526 else if (s[1] == 'g' && s[2] == 'p')
8531 else if (s[1] == 'a' && s[2] == 't')
8536 else if (s[1] == 'k' && s[2] == 't' && s[3] == '0')
8541 else if (s[1] == 'k' && s[2] == 't' && s[3] == '1')
8546 else if (s[1] == 'z' && s[2] == 'e' && s[3] == 'r' && s[4] == 'o')
8551 else if (itbl_have_entries)
8556 p = s + 1; /* advance past '$' */
8557 n = itbl_get_field (&p); /* n is name */
8559 /* See if this is a register defined in an
8561 if (itbl_get_reg_val (n, &r))
8563 /* Get_field advances to the start of
8564 the next field, so we need to back
8565 rack to the end of the last field. */
8569 s = strchr (s, '\0');
8583 as_warn (_("Used $at without \".set noat\""));
8589 if (c == 'r' || c == 'v' || c == 'w')
8596 /* 'z' only matches $0. */
8597 if (c == 'z' && regno != 0)
8600 /* Now that we have assembled one operand, we use the args string
8601 * to figure out where it goes in the instruction. */
8608 ip->insn_opcode |= regno << OP_SH_RS;
8613 ip->insn_opcode |= regno << OP_SH_RD;
8616 ip->insn_opcode |= regno << OP_SH_RD;
8617 ip->insn_opcode |= regno << OP_SH_RT;
8622 ip->insn_opcode |= regno << OP_SH_RT;
8625 /* This case exists because on the r3000 trunc
8626 expands into a macro which requires a gp
8627 register. On the r6000 or r4000 it is
8628 assembled into a single instruction which
8629 ignores the register. Thus the insn version
8630 is MIPS_ISA2 and uses 'x', and the macro
8631 version is MIPS_ISA1 and uses 't'. */
8634 /* This case is for the div instruction, which
8635 acts differently if the destination argument
8636 is $0. This only matches $0, and is checked
8637 outside the switch. */
8640 /* Itbl operand; not yet implemented. FIXME ?? */
8642 /* What about all other operands like 'i', which
8643 can be specified in the opcode table? */
8653 ip->insn_opcode |= lastregno << OP_SH_RS;
8656 ip->insn_opcode |= lastregno << OP_SH_RT;
8661 case 'O': /* MDMX alignment immediate constant. */
8662 my_getExpression (&imm_expr, s);
8663 check_absolute_expr (ip, &imm_expr);
8664 if ((unsigned long) imm_expr.X_add_number > OP_MASK_ALN)
8666 as_warn ("Improper align amount (%ld), using low bits",
8667 (long) imm_expr.X_add_number);
8668 imm_expr.X_add_number &= OP_MASK_ALN;
8670 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_ALN;
8671 imm_expr.X_op = O_absent;
8675 case 'Q': /* MDMX vector, element sel, or const. */
8678 /* MDMX Immediate. */
8679 my_getExpression (&imm_expr, s);
8680 check_absolute_expr (ip, &imm_expr);
8681 if ((unsigned long) imm_expr.X_add_number > OP_MASK_FT)
8683 as_warn (_("Invalid MDMX Immediate (%ld)"),
8684 (long) imm_expr.X_add_number);
8685 imm_expr.X_add_number &= OP_MASK_FT;
8687 imm_expr.X_add_number &= OP_MASK_FT;
8688 if (ip->insn_opcode & (OP_MASK_VSEL << OP_SH_VSEL))
8689 ip->insn_opcode |= MDMX_FMTSEL_IMM_QH << OP_SH_VSEL;
8691 ip->insn_opcode |= MDMX_FMTSEL_IMM_OB << OP_SH_VSEL;
8692 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_FT;
8693 imm_expr.X_op = O_absent;
8697 /* Not MDMX Immediate. Fall through. */
8698 case 'X': /* MDMX destination register. */
8699 case 'Y': /* MDMX source register. */
8700 case 'Z': /* MDMX target register. */
8702 case 'D': /* floating point destination register */
8703 case 'S': /* floating point source register */
8704 case 'T': /* floating point target register */
8705 case 'R': /* floating point source register */
8709 /* Accept $fN for FP and MDMX register numbers, and in
8710 addition accept $vN for MDMX register numbers. */
8711 if ((s[0] == '$' && s[1] == 'f' && ISDIGIT (s[2]))
8712 || (is_mdmx != 0 && s[0] == '$' && s[1] == 'v'
8723 while (ISDIGIT (*s));
8726 as_bad (_("Invalid float register number (%d)"), regno);
8728 if ((regno & 1) != 0
8730 && ! (strcmp (str, "mtc1") == 0
8731 || strcmp (str, "mfc1") == 0
8732 || strcmp (str, "lwc1") == 0
8733 || strcmp (str, "swc1") == 0
8734 || strcmp (str, "l.s") == 0
8735 || strcmp (str, "s.s") == 0))
8736 as_warn (_("Float register should be even, was %d"),
8744 if (c == 'V' || c == 'W')
8755 ip->insn_opcode |= regno << OP_SH_FD;
8760 ip->insn_opcode |= regno << OP_SH_FS;
8763 /* This is like 'Z', but also needs to fix the MDMX
8764 vector/scalar select bits. Note that the
8765 scalar immediate case is handled above. */
8768 int is_qh = (ip->insn_opcode & (1 << OP_SH_VSEL));
8769 int max_el = (is_qh ? 3 : 7);
8771 my_getExpression(&imm_expr, s);
8772 check_absolute_expr (ip, &imm_expr);
8774 if (imm_expr.X_add_number > max_el)
8775 as_bad(_("Bad element selector %ld"),
8776 (long) imm_expr.X_add_number);
8777 imm_expr.X_add_number &= max_el;
8778 ip->insn_opcode |= (imm_expr.X_add_number
8782 as_warn(_("Expecting ']' found '%s'"), s);
8788 if (ip->insn_opcode & (OP_MASK_VSEL << OP_SH_VSEL))
8789 ip->insn_opcode |= (MDMX_FMTSEL_VEC_QH
8792 ip->insn_opcode |= (MDMX_FMTSEL_VEC_OB <<
8799 ip->insn_opcode |= regno << OP_SH_FT;
8802 ip->insn_opcode |= regno << OP_SH_FR;
8812 ip->insn_opcode |= lastregno << OP_SH_FS;
8815 ip->insn_opcode |= lastregno << OP_SH_FT;
8821 my_getExpression (&imm_expr, s);
8822 if (imm_expr.X_op != O_big
8823 && imm_expr.X_op != O_constant)
8824 insn_error = _("absolute expression required");
8829 my_getExpression (&offset_expr, s);
8830 *imm_reloc = BFD_RELOC_32;
8843 unsigned char temp[8];
8845 unsigned int length;
8850 /* These only appear as the last operand in an
8851 instruction, and every instruction that accepts
8852 them in any variant accepts them in all variants.
8853 This means we don't have to worry about backing out
8854 any changes if the instruction does not match.
8856 The difference between them is the size of the
8857 floating point constant and where it goes. For 'F'
8858 and 'L' the constant is 64 bits; for 'f' and 'l' it
8859 is 32 bits. Where the constant is placed is based
8860 on how the MIPS assembler does things:
8863 f -- immediate value
8866 The .lit4 and .lit8 sections are only used if
8867 permitted by the -G argument.
8869 When generating embedded PIC code, we use the
8870 .lit8 section but not the .lit4 section (we can do
8871 .lit4 inline easily; we need to put .lit8
8872 somewhere in the data segment, and using .lit8
8873 permits the linker to eventually combine identical
8876 The code below needs to know whether the target register
8877 is 32 or 64 bits wide. It relies on the fact 'f' and
8878 'F' are used with GPR-based instructions and 'l' and
8879 'L' are used with FPR-based instructions. */
8881 f64 = *args == 'F' || *args == 'L';
8882 using_gprs = *args == 'F' || *args == 'f';
8884 save_in = input_line_pointer;
8885 input_line_pointer = s;
8886 err = md_atof (f64 ? 'd' : 'f', (char *) temp, &len);
8888 s = input_line_pointer;
8889 input_line_pointer = save_in;
8890 if (err != NULL && *err != '\0')
8892 as_bad (_("Bad floating point constant: %s"), err);
8893 memset (temp, '\0', sizeof temp);
8894 length = f64 ? 8 : 4;
8897 assert (length == (unsigned) (f64 ? 8 : 4));
8901 && (! USE_GLOBAL_POINTER_OPT
8902 || mips_pic == EMBEDDED_PIC
8903 || g_switch_value < 4
8904 || (temp[0] == 0 && temp[1] == 0)
8905 || (temp[2] == 0 && temp[3] == 0))))
8907 imm_expr.X_op = O_constant;
8908 if (! target_big_endian)
8909 imm_expr.X_add_number = bfd_getl32 (temp);
8911 imm_expr.X_add_number = bfd_getb32 (temp);
8914 && ! mips_disable_float_construction
8915 /* Constants can only be constructed in GPRs and
8916 copied to FPRs if the GPRs are at least as wide
8917 as the FPRs. Force the constant into memory if
8918 we are using 64-bit FPRs but the GPRs are only
8921 || ! (HAVE_64BIT_FPRS && HAVE_32BIT_GPRS))
8922 && ((temp[0] == 0 && temp[1] == 0)
8923 || (temp[2] == 0 && temp[3] == 0))
8924 && ((temp[4] == 0 && temp[5] == 0)
8925 || (temp[6] == 0 && temp[7] == 0)))
8927 /* The value is simple enough to load with a couple of
8928 instructions. If using 32-bit registers, set
8929 imm_expr to the high order 32 bits and offset_expr to
8930 the low order 32 bits. Otherwise, set imm_expr to
8931 the entire 64 bit constant. */
8932 if (using_gprs ? HAVE_32BIT_GPRS : HAVE_32BIT_FPRS)
8934 imm_expr.X_op = O_constant;
8935 offset_expr.X_op = O_constant;
8936 if (! target_big_endian)
8938 imm_expr.X_add_number = bfd_getl32 (temp + 4);
8939 offset_expr.X_add_number = bfd_getl32 (temp);
8943 imm_expr.X_add_number = bfd_getb32 (temp);
8944 offset_expr.X_add_number = bfd_getb32 (temp + 4);
8946 if (offset_expr.X_add_number == 0)
8947 offset_expr.X_op = O_absent;
8949 else if (sizeof (imm_expr.X_add_number) > 4)
8951 imm_expr.X_op = O_constant;
8952 if (! target_big_endian)
8953 imm_expr.X_add_number = bfd_getl64 (temp);
8955 imm_expr.X_add_number = bfd_getb64 (temp);
8959 imm_expr.X_op = O_big;
8960 imm_expr.X_add_number = 4;
8961 if (! target_big_endian)
8963 generic_bignum[0] = bfd_getl16 (temp);
8964 generic_bignum[1] = bfd_getl16 (temp + 2);
8965 generic_bignum[2] = bfd_getl16 (temp + 4);
8966 generic_bignum[3] = bfd_getl16 (temp + 6);
8970 generic_bignum[0] = bfd_getb16 (temp + 6);
8971 generic_bignum[1] = bfd_getb16 (temp + 4);
8972 generic_bignum[2] = bfd_getb16 (temp + 2);
8973 generic_bignum[3] = bfd_getb16 (temp);
8979 const char *newname;
8982 /* Switch to the right section. */
8984 subseg = now_subseg;
8987 default: /* unused default case avoids warnings. */
8989 newname = RDATA_SECTION_NAME;
8990 if ((USE_GLOBAL_POINTER_OPT && g_switch_value >= 8)
8991 || mips_pic == EMBEDDED_PIC)
8995 if (mips_pic == EMBEDDED_PIC)
8998 newname = RDATA_SECTION_NAME;
9001 assert (!USE_GLOBAL_POINTER_OPT
9002 || g_switch_value >= 4);
9006 new_seg = subseg_new (newname, (subsegT) 0);
9007 if (OUTPUT_FLAVOR == bfd_target_elf_flavour)
9008 bfd_set_section_flags (stdoutput, new_seg,
9013 frag_align (*args == 'l' ? 2 : 3, 0, 0);
9014 if (OUTPUT_FLAVOR == bfd_target_elf_flavour
9015 && strcmp (TARGET_OS, "elf") != 0)
9016 record_alignment (new_seg, 4);
9018 record_alignment (new_seg, *args == 'l' ? 2 : 3);
9020 as_bad (_("Can't use floating point insn in this section"));
9022 /* Set the argument to the current address in the
9024 offset_expr.X_op = O_symbol;
9025 offset_expr.X_add_symbol =
9026 symbol_new ("L0\001", now_seg,
9027 (valueT) frag_now_fix (), frag_now);
9028 offset_expr.X_add_number = 0;
9030 /* Put the floating point number into the section. */
9031 p = frag_more ((int) length);
9032 memcpy (p, temp, length);
9034 /* Switch back to the original section. */
9035 subseg_set (seg, subseg);
9040 case 'i': /* 16 bit unsigned immediate */
9041 case 'j': /* 16 bit signed immediate */
9042 *imm_reloc = BFD_RELOC_LO16;
9043 c = my_getSmallExpression (&imm_expr, s);
9050 *imm_reloc = BFD_RELOC_HI16_S;
9051 imm_unmatched_hi = TRUE;
9054 else if (c == S_EX_HIGHEST)
9055 *imm_reloc = BFD_RELOC_MIPS_HIGHEST;
9056 else if (c == S_EX_HIGHER)
9057 *imm_reloc = BFD_RELOC_MIPS_HIGHER;
9058 else if (c == S_EX_GP_REL)
9060 /* This occurs in NewABI only. */
9061 c = my_getSmallExpression (&imm_expr, s);
9063 as_bad (_("bad composition of relocations"));
9066 c = my_getSmallExpression (&imm_expr, s);
9068 as_bad (_("bad composition of relocations"));
9071 imm_reloc[0] = BFD_RELOC_GPREL16;
9072 imm_reloc[1] = BFD_RELOC_MIPS_SUB;
9073 imm_reloc[2] = BFD_RELOC_LO16;
9079 *imm_reloc = BFD_RELOC_HI16;
9081 else if (imm_expr.X_op == O_constant)
9082 imm_expr.X_add_number &= 0xffff;
9086 if ((c == S_EX_NONE && imm_expr.X_op != O_constant)
9087 || ((imm_expr.X_add_number < 0
9088 || imm_expr.X_add_number >= 0x10000)
9089 && imm_expr.X_op == O_constant))
9091 if (insn + 1 < &mips_opcodes[NUMOPCODES] &&
9092 !strcmp (insn->name, insn[1].name))
9094 if (imm_expr.X_op == O_constant
9095 || imm_expr.X_op == O_big)
9096 as_bad (_("16 bit expression not in range 0..65535"));
9104 /* The upper bound should be 0x8000, but
9105 unfortunately the MIPS assembler accepts numbers
9106 from 0x8000 to 0xffff and sign extends them, and
9107 we want to be compatible. We only permit this
9108 extended range for an instruction which does not
9109 provide any further alternates, since those
9110 alternates may handle other cases. People should
9111 use the numbers they mean, rather than relying on
9112 a mysterious sign extension. */
9113 more = (insn + 1 < &mips_opcodes[NUMOPCODES] &&
9114 strcmp (insn->name, insn[1].name) == 0);
9119 if ((c == S_EX_NONE && imm_expr.X_op != O_constant)
9120 || ((imm_expr.X_add_number < -0x8000
9121 || imm_expr.X_add_number >= max)
9122 && imm_expr.X_op == O_constant)
9124 && imm_expr.X_add_number < 0
9126 && imm_expr.X_unsigned
9127 && sizeof (imm_expr.X_add_number) <= 4))
9131 if (imm_expr.X_op == O_constant
9132 || imm_expr.X_op == O_big)
9133 as_bad (_("16 bit expression not in range -32768..32767"));
9139 case 'o': /* 16 bit offset */
9140 c = my_getSmallExpression (&offset_expr, s);
9142 /* If this value won't fit into a 16 bit offset, then go
9143 find a macro that will generate the 32 bit offset
9146 && (offset_expr.X_op != O_constant
9147 || offset_expr.X_add_number >= 0x8000
9148 || offset_expr.X_add_number < -0x8000))
9153 if (offset_expr.X_op != O_constant)
9155 offset_expr.X_add_number =
9156 (offset_expr.X_add_number >> 16) & 0xffff;
9158 *offset_reloc = BFD_RELOC_LO16;
9162 case 'p': /* pc relative offset */
9163 *offset_reloc = BFD_RELOC_16_PCREL_S2;
9164 my_getExpression (&offset_expr, s);
9168 case 'u': /* upper 16 bits */
9169 c = my_getSmallExpression (&imm_expr, s);
9170 *imm_reloc = BFD_RELOC_LO16;
9177 *imm_reloc = BFD_RELOC_HI16_S;
9178 imm_unmatched_hi = TRUE;
9181 else if (c == S_EX_HIGHEST)
9182 *imm_reloc = BFD_RELOC_MIPS_HIGHEST;
9183 else if (c == S_EX_GP_REL)
9185 /* This occurs in NewABI only. */
9186 c = my_getSmallExpression (&imm_expr, s);
9188 as_bad (_("bad composition of relocations"));
9191 c = my_getSmallExpression (&imm_expr, s);
9193 as_bad (_("bad composition of relocations"));
9196 imm_reloc[0] = BFD_RELOC_GPREL16;
9197 imm_reloc[1] = BFD_RELOC_MIPS_SUB;
9198 imm_reloc[2] = BFD_RELOC_HI16_S;
9204 *imm_reloc = BFD_RELOC_HI16;
9206 else if (imm_expr.X_op == O_constant)
9207 imm_expr.X_add_number &= 0xffff;
9209 else if (imm_expr.X_op == O_constant
9210 && (imm_expr.X_add_number < 0
9211 || imm_expr.X_add_number >= 0x10000))
9212 as_bad (_("lui expression not in range 0..65535"));
9216 case 'a': /* 26 bit address */
9217 my_getExpression (&offset_expr, s);
9219 *offset_reloc = BFD_RELOC_MIPS_JMP;
9222 case 'N': /* 3 bit branch condition code */
9223 case 'M': /* 3 bit compare condition code */
9224 if (strncmp (s, "$fcc", 4) != 0)
9234 while (ISDIGIT (*s));
9236 as_bad (_("invalid condition code register $fcc%d"), regno);
9238 ip->insn_opcode |= regno << OP_SH_BCC;
9240 ip->insn_opcode |= regno << OP_SH_CCC;
9244 if (s[0] == '0' && (s[1] == 'x' || s[1] == 'X'))
9255 while (ISDIGIT (*s));
9258 c = 8; /* Invalid sel value. */
9261 as_bad (_("invalid coprocessor sub-selection value (0-7)"));
9262 ip->insn_opcode |= c;
9266 /* Must be at least one digit. */
9267 my_getExpression (&imm_expr, s);
9268 check_absolute_expr (ip, &imm_expr);
9270 if ((unsigned long) imm_expr.X_add_number
9271 > (unsigned long) OP_MASK_VECBYTE)
9273 as_bad (_("bad byte vector index (%ld)"),
9274 (long) imm_expr.X_add_number);
9275 imm_expr.X_add_number = 0;
9278 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_VECBYTE;
9279 imm_expr.X_op = O_absent;
9284 my_getExpression (&imm_expr, s);
9285 check_absolute_expr (ip, &imm_expr);
9287 if ((unsigned long) imm_expr.X_add_number
9288 > (unsigned long) OP_MASK_VECALIGN)
9290 as_bad (_("bad byte vector index (%ld)"),
9291 (long) imm_expr.X_add_number);
9292 imm_expr.X_add_number = 0;
9295 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_VECALIGN;
9296 imm_expr.X_op = O_absent;
9301 as_bad (_("bad char = '%c'\n"), *args);
9306 /* Args don't match. */
9307 if (insn + 1 < &mips_opcodes[NUMOPCODES] &&
9308 !strcmp (insn->name, insn[1].name))
9312 insn_error = _("illegal operands");
9317 insn_error = _("illegal operands");
9322 /* This routine assembles an instruction into its binary format when
9323 assembling for the mips16. As a side effect, it sets one of the
9324 global variables imm_reloc or offset_reloc to the type of
9325 relocation to do if one of the operands is an address expression.
9326 It also sets mips16_small and mips16_ext if the user explicitly
9327 requested a small or extended instruction. */
9332 struct mips_cl_insn *ip;
9336 struct mips_opcode *insn;
9339 unsigned int lastregno = 0;
9344 mips16_small = FALSE;
9347 for (s = str; ISLOWER (*s); ++s)
9359 if (s[1] == 't' && s[2] == ' ')
9362 mips16_small = TRUE;
9366 else if (s[1] == 'e' && s[2] == ' ')
9375 insn_error = _("unknown opcode");
9379 if (mips_opts.noautoextend && ! mips16_ext)
9380 mips16_small = TRUE;
9382 if ((insn = (struct mips_opcode *) hash_find (mips16_op_hash, str)) == NULL)
9384 insn_error = _("unrecognized opcode");
9391 assert (strcmp (insn->name, str) == 0);
9394 ip->insn_opcode = insn->match;
9395 ip->use_extend = FALSE;
9396 imm_expr.X_op = O_absent;
9397 imm_reloc[0] = BFD_RELOC_UNUSED;
9398 imm_reloc[1] = BFD_RELOC_UNUSED;
9399 imm_reloc[2] = BFD_RELOC_UNUSED;
9400 offset_expr.X_op = O_absent;
9401 offset_reloc[0] = BFD_RELOC_UNUSED;
9402 offset_reloc[1] = BFD_RELOC_UNUSED;
9403 offset_reloc[2] = BFD_RELOC_UNUSED;
9404 for (args = insn->args; 1; ++args)
9411 /* In this switch statement we call break if we did not find
9412 a match, continue if we did find a match, or return if we
9421 /* Stuff the immediate value in now, if we can. */
9422 if (imm_expr.X_op == O_constant
9423 && *imm_reloc > BFD_RELOC_UNUSED
9424 && insn->pinfo != INSN_MACRO)
9426 mips16_immed (NULL, 0, *imm_reloc - BFD_RELOC_UNUSED,
9427 imm_expr.X_add_number, TRUE, mips16_small,
9428 mips16_ext, &ip->insn_opcode,
9429 &ip->use_extend, &ip->extend);
9430 imm_expr.X_op = O_absent;
9431 *imm_reloc = BFD_RELOC_UNUSED;
9445 ip->insn_opcode |= lastregno << MIPS16OP_SH_RX;
9448 ip->insn_opcode |= lastregno << MIPS16OP_SH_RY;
9464 ip->insn_opcode |= lastregno << MIPS16OP_SH_RX;
9466 ip->insn_opcode |= lastregno << MIPS16OP_SH_RY;
9493 while (ISDIGIT (*s));
9496 as_bad (_("invalid register number (%d)"), regno);
9502 if (s[1] == 'r' && s[2] == 'a')
9507 else if (s[1] == 'f' && s[2] == 'p')
9512 else if (s[1] == 's' && s[2] == 'p')
9517 else if (s[1] == 'g' && s[2] == 'p')
9522 else if (s[1] == 'a' && s[2] == 't')
9527 else if (s[1] == 'k' && s[2] == 't' && s[3] == '0')
9532 else if (s[1] == 'k' && s[2] == 't' && s[3] == '1')
9537 else if (s[1] == 'z' && s[2] == 'e' && s[3] == 'r' && s[4] == 'o')
9550 if (c == 'v' || c == 'w')
9552 regno = mips16_to_32_reg_map[lastregno];
9566 regno = mips32_to_16_reg_map[regno];
9571 regno = ILLEGAL_REG;
9576 regno = ILLEGAL_REG;
9581 regno = ILLEGAL_REG;
9586 if (regno == AT && ! mips_opts.noat)
9587 as_warn (_("used $at without \".set noat\""));
9594 if (regno == ILLEGAL_REG)
9601 ip->insn_opcode |= regno << MIPS16OP_SH_RX;
9605 ip->insn_opcode |= regno << MIPS16OP_SH_RY;
9608 ip->insn_opcode |= regno << MIPS16OP_SH_RZ;
9611 ip->insn_opcode |= regno << MIPS16OP_SH_MOVE32Z;
9617 ip->insn_opcode |= regno << MIPS16OP_SH_REGR32;
9620 regno = ((regno & 7) << 2) | ((regno & 0x18) >> 3);
9621 ip->insn_opcode |= regno << MIPS16OP_SH_REG32R;
9631 if (strncmp (s, "$pc", 3) == 0)
9655 && strncmp (s + 1, "gprel(", sizeof "gprel(" - 1) == 0)
9657 /* This is %gprel(SYMBOL). We need to read SYMBOL,
9658 and generate the appropriate reloc. If the text
9659 inside %gprel is not a symbol name with an
9660 optional offset, then we generate a normal reloc
9661 and will probably fail later. */
9662 my_getExpression (&imm_expr, s + sizeof "%gprel" - 1);
9663 if (imm_expr.X_op == O_symbol)
9666 *imm_reloc = BFD_RELOC_MIPS16_GPREL;
9668 ip->use_extend = TRUE;
9675 /* Just pick up a normal expression. */
9676 my_getExpression (&imm_expr, s);
9679 if (imm_expr.X_op == O_register)
9681 /* What we thought was an expression turned out to
9684 if (s[0] == '(' && args[1] == '(')
9686 /* It looks like the expression was omitted
9687 before a register indirection, which means
9688 that the expression is implicitly zero. We
9689 still set up imm_expr, so that we handle
9690 explicit extensions correctly. */
9691 imm_expr.X_op = O_constant;
9692 imm_expr.X_add_number = 0;
9693 *imm_reloc = (int) BFD_RELOC_UNUSED + c;
9700 /* We need to relax this instruction. */
9701 *imm_reloc = (int) BFD_RELOC_UNUSED + c;
9710 /* We use offset_reloc rather than imm_reloc for the PC
9711 relative operands. This lets macros with both
9712 immediate and address operands work correctly. */
9713 my_getExpression (&offset_expr, s);
9715 if (offset_expr.X_op == O_register)
9718 /* We need to relax this instruction. */
9719 *offset_reloc = (int) BFD_RELOC_UNUSED + c;
9723 case '6': /* break code */
9724 my_getExpression (&imm_expr, s);
9725 check_absolute_expr (ip, &imm_expr);
9726 if ((unsigned long) imm_expr.X_add_number > 63)
9728 as_warn (_("Invalid value for `%s' (%lu)"),
9730 (unsigned long) imm_expr.X_add_number);
9731 imm_expr.X_add_number &= 0x3f;
9733 ip->insn_opcode |= imm_expr.X_add_number << MIPS16OP_SH_IMM6;
9734 imm_expr.X_op = O_absent;
9738 case 'a': /* 26 bit address */
9739 my_getExpression (&offset_expr, s);
9741 *offset_reloc = BFD_RELOC_MIPS16_JMP;
9742 ip->insn_opcode <<= 16;
9745 case 'l': /* register list for entry macro */
9746 case 'L': /* register list for exit macro */
9756 int freg, reg1, reg2;
9758 while (*s == ' ' || *s == ',')
9762 as_bad (_("can't parse register list"));
9774 while (ISDIGIT (*s))
9796 as_bad (_("invalid register list"));
9801 while (ISDIGIT (*s))
9808 if (freg && reg1 == 0 && reg2 == 0 && c == 'L')
9813 else if (freg && reg1 == 0 && reg2 == 1 && c == 'L')
9818 else if (reg1 == 4 && reg2 >= 4 && reg2 <= 7 && c != 'L')
9819 mask |= (reg2 - 3) << 3;
9820 else if (reg1 == 16 && reg2 >= 16 && reg2 <= 17)
9821 mask |= (reg2 - 15) << 1;
9822 else if (reg1 == RA && reg2 == RA)
9826 as_bad (_("invalid register list"));
9830 /* The mask is filled in in the opcode table for the
9831 benefit of the disassembler. We remove it before
9832 applying the actual mask. */
9833 ip->insn_opcode &= ~ ((7 << 3) << MIPS16OP_SH_IMM6);
9834 ip->insn_opcode |= mask << MIPS16OP_SH_IMM6;
9838 case 'e': /* extend code */
9839 my_getExpression (&imm_expr, s);
9840 check_absolute_expr (ip, &imm_expr);
9841 if ((unsigned long) imm_expr.X_add_number > 0x7ff)
9843 as_warn (_("Invalid value for `%s' (%lu)"),
9845 (unsigned long) imm_expr.X_add_number);
9846 imm_expr.X_add_number &= 0x7ff;
9848 ip->insn_opcode |= imm_expr.X_add_number;
9849 imm_expr.X_op = O_absent;
9859 /* Args don't match. */
9860 if (insn + 1 < &mips16_opcodes[bfd_mips16_num_opcodes] &&
9861 strcmp (insn->name, insn[1].name) == 0)
9868 insn_error = _("illegal operands");
9874 /* This structure holds information we know about a mips16 immediate
9877 struct mips16_immed_operand
9879 /* The type code used in the argument string in the opcode table. */
9881 /* The number of bits in the short form of the opcode. */
9883 /* The number of bits in the extended form of the opcode. */
9885 /* The amount by which the short form is shifted when it is used;
9886 for example, the sw instruction has a shift count of 2. */
9888 /* The amount by which the short form is shifted when it is stored
9889 into the instruction code. */
9891 /* Non-zero if the short form is unsigned. */
9893 /* Non-zero if the extended form is unsigned. */
9895 /* Non-zero if the value is PC relative. */
9899 /* The mips16 immediate operand types. */
9901 static const struct mips16_immed_operand mips16_immed_operands[] =
9903 { '<', 3, 5, 0, MIPS16OP_SH_RZ, 1, 1, 0 },
9904 { '>', 3, 5, 0, MIPS16OP_SH_RX, 1, 1, 0 },
9905 { '[', 3, 6, 0, MIPS16OP_SH_RZ, 1, 1, 0 },
9906 { ']', 3, 6, 0, MIPS16OP_SH_RX, 1, 1, 0 },
9907 { '4', 4, 15, 0, MIPS16OP_SH_IMM4, 0, 0, 0 },
9908 { '5', 5, 16, 0, MIPS16OP_SH_IMM5, 1, 0, 0 },
9909 { 'H', 5, 16, 1, MIPS16OP_SH_IMM5, 1, 0, 0 },
9910 { 'W', 5, 16, 2, MIPS16OP_SH_IMM5, 1, 0, 0 },
9911 { 'D', 5, 16, 3, MIPS16OP_SH_IMM5, 1, 0, 0 },
9912 { 'j', 5, 16, 0, MIPS16OP_SH_IMM5, 0, 0, 0 },
9913 { '8', 8, 16, 0, MIPS16OP_SH_IMM8, 1, 0, 0 },
9914 { 'V', 8, 16, 2, MIPS16OP_SH_IMM8, 1, 0, 0 },
9915 { 'C', 8, 16, 3, MIPS16OP_SH_IMM8, 1, 0, 0 },
9916 { 'U', 8, 16, 0, MIPS16OP_SH_IMM8, 1, 1, 0 },
9917 { 'k', 8, 16, 0, MIPS16OP_SH_IMM8, 0, 0, 0 },
9918 { 'K', 8, 16, 3, MIPS16OP_SH_IMM8, 0, 0, 0 },
9919 { 'p', 8, 16, 0, MIPS16OP_SH_IMM8, 0, 0, 1 },
9920 { 'q', 11, 16, 0, MIPS16OP_SH_IMM8, 0, 0, 1 },
9921 { 'A', 8, 16, 2, MIPS16OP_SH_IMM8, 1, 0, 1 },
9922 { 'B', 5, 16, 3, MIPS16OP_SH_IMM5, 1, 0, 1 },
9923 { 'E', 5, 16, 2, MIPS16OP_SH_IMM5, 1, 0, 1 }
9926 #define MIPS16_NUM_IMMED \
9927 (sizeof mips16_immed_operands / sizeof mips16_immed_operands[0])
9929 /* Handle a mips16 instruction with an immediate value. This or's the
9930 small immediate value into *INSN. It sets *USE_EXTEND to indicate
9931 whether an extended value is needed; if one is needed, it sets
9932 *EXTEND to the value. The argument type is TYPE. The value is VAL.
9933 If SMALL is true, an unextended opcode was explicitly requested.
9934 If EXT is true, an extended opcode was explicitly requested. If
9935 WARN is true, warn if EXT does not match reality. */
9938 mips16_immed (file, line, type, val, warn, small, ext, insn, use_extend,
9947 unsigned long *insn;
9948 bfd_boolean *use_extend;
9949 unsigned short *extend;
9951 register const struct mips16_immed_operand *op;
9952 int mintiny, maxtiny;
9953 bfd_boolean needext;
9955 op = mips16_immed_operands;
9956 while (op->type != type)
9959 assert (op < mips16_immed_operands + MIPS16_NUM_IMMED);
9964 if (type == '<' || type == '>' || type == '[' || type == ']')
9967 maxtiny = 1 << op->nbits;
9972 maxtiny = (1 << op->nbits) - 1;
9977 mintiny = - (1 << (op->nbits - 1));
9978 maxtiny = (1 << (op->nbits - 1)) - 1;
9981 /* Branch offsets have an implicit 0 in the lowest bit. */
9982 if (type == 'p' || type == 'q')
9985 if ((val & ((1 << op->shift) - 1)) != 0
9986 || val < (mintiny << op->shift)
9987 || val > (maxtiny << op->shift))
9992 if (warn && ext && ! needext)
9993 as_warn_where (file, line,
9994 _("extended operand requested but not required"));
9995 if (small && needext)
9996 as_bad_where (file, line, _("invalid unextended operand value"));
9998 if (small || (! ext && ! needext))
10002 *use_extend = FALSE;
10003 insnval = ((val >> op->shift) & ((1 << op->nbits) - 1));
10004 insnval <<= op->op_shift;
10009 long minext, maxext;
10015 maxext = (1 << op->extbits) - 1;
10019 minext = - (1 << (op->extbits - 1));
10020 maxext = (1 << (op->extbits - 1)) - 1;
10022 if (val < minext || val > maxext)
10023 as_bad_where (file, line,
10024 _("operand value out of range for instruction"));
10026 *use_extend = TRUE;
10027 if (op->extbits == 16)
10029 extval = ((val >> 11) & 0x1f) | (val & 0x7e0);
10032 else if (op->extbits == 15)
10034 extval = ((val >> 11) & 0xf) | (val & 0x7f0);
10039 extval = ((val & 0x1f) << 6) | (val & 0x20);
10043 *extend = (unsigned short) extval;
10048 static struct percent_op_match
10051 const enum small_ex_type type;
10056 {"%call_hi", S_EX_CALL_HI},
10057 {"%call_lo", S_EX_CALL_LO},
10058 {"%call16", S_EX_CALL16},
10059 {"%got_disp", S_EX_GOT_DISP},
10060 {"%got_page", S_EX_GOT_PAGE},
10061 {"%got_ofst", S_EX_GOT_OFST},
10062 {"%got_hi", S_EX_GOT_HI},
10063 {"%got_lo", S_EX_GOT_LO},
10064 {"%got", S_EX_GOT},
10065 {"%gp_rel", S_EX_GP_REL},
10066 {"%half", S_EX_HALF},
10067 {"%highest", S_EX_HIGHEST},
10068 {"%higher", S_EX_HIGHER},
10069 {"%neg", S_EX_NEG},
10074 /* Parse small expression input. STR gets adjusted to eat up whitespace.
10075 It detects valid "%percent_op(...)" and "($reg)" strings. Percent_op's
10076 can be nested, this is handled by blanking the innermost, parsing the
10077 rest by subsequent calls. */
10080 my_getSmallParser (str, len, nestlevel)
10086 *str += strspn (*str, " \t");
10087 /* Check for expression in parentheses. */
10090 char *b = *str + 1 + strspn (*str + 1, " \t");
10093 /* Check for base register. */
10096 if (strchr (b, ')')
10097 && (e = b + strcspn (b, ") \t"))
10098 && e - b > 1 && e - b < 4)
10101 && ((b[1] == 'f' && b[2] == 'p')
10102 || (b[1] == 's' && b[2] == 'p')
10103 || (b[1] == 'g' && b[2] == 'p')
10104 || (b[1] == 'a' && b[2] == 't')
10106 && ISDIGIT (b[2]))))
10107 || (ISDIGIT (b[1])))
10109 *len = strcspn (*str, ")") + 1;
10110 return S_EX_REGISTER;
10114 /* Check for percent_op (in parentheses). */
10115 else if (b[0] == '%')
10118 return my_getPercentOp (str, len, nestlevel);
10121 /* Some other expression in the parentheses, which can contain
10122 parentheses itself. Attempt to find the matching one. */
10128 for (s = *str + 1; *s && pcnt; s++, (*len)++)
10132 else if (*s == ')')
10137 /* Check for percent_op (outside of parentheses). */
10138 else if (*str[0] == '%')
10139 return my_getPercentOp (str, len, nestlevel);
10141 /* Any other expression. */
10146 my_getPercentOp (str, len, nestlevel)
10151 char *tmp = *str + 1;
10152 unsigned int i = 0;
10154 while (ISALPHA (*tmp) || *tmp == '_')
10156 *tmp = TOLOWER (*tmp);
10159 while (i < (sizeof (percent_op) / sizeof (struct percent_op_match)))
10161 if (strncmp (*str, percent_op[i].str, strlen (percent_op[i].str)))
10165 int type = percent_op[i].type;
10167 /* Only %hi and %lo are allowed for OldABI. */
10168 if (! HAVE_NEWABI && type != S_EX_HI && type != S_EX_LO)
10171 *len = strlen (percent_op[i].str);
10180 my_getSmallExpression (ep, str)
10184 static char *oldstr = NULL;
10187 int nestlevel = -1;
10190 /* Don't update oldstr if the last call had nested percent_op's. We need
10191 it to parse the outer ones later. */
10198 c = my_getSmallParser (&str, &len, &nestlevel);
10199 if (c != S_EX_NONE && c != S_EX_REGISTER)
10202 while (c != S_EX_NONE && c != S_EX_REGISTER);
10204 if (nestlevel >= 0)
10206 /* A percent_op was encountered. Don't try to get an expression if
10207 it is already blanked out. */
10208 if (*(str + strspn (str + 1, " )")) != ')')
10212 /* Let my_getExpression() stop at the closing parenthesis. */
10213 save = *(str + len);
10214 *(str + len) = '\0';
10215 my_getExpression (ep, str);
10216 *(str + len) = save;
10220 /* Blank out including the % sign and the proper matching
10223 char *s = strrchr (oldstr, '%');
10226 for (end = strchr (s, '(') + 1; *end && pcnt; end++)
10230 else if (*end == ')')
10234 memset (s, ' ', end - s);
10238 expr_end = str + len;
10242 else if (c == S_EX_NONE)
10244 my_getExpression (ep, str);
10246 else if (c == S_EX_REGISTER)
10248 ep->X_op = O_constant;
10250 ep->X_add_symbol = NULL;
10251 ep->X_op_symbol = NULL;
10252 ep->X_add_number = 0;
10256 as_fatal (_("internal error"));
10259 if (nestlevel <= 0)
10260 /* All percent_op's have been handled. */
10267 my_getExpression (ep, str)
10274 save_in = input_line_pointer;
10275 input_line_pointer = str;
10277 expr_end = input_line_pointer;
10278 input_line_pointer = save_in;
10280 /* If we are in mips16 mode, and this is an expression based on `.',
10281 then we bump the value of the symbol by 1 since that is how other
10282 text symbols are handled. We don't bother to handle complex
10283 expressions, just `.' plus or minus a constant. */
10284 if (mips_opts.mips16
10285 && ep->X_op == O_symbol
10286 && strcmp (S_GET_NAME (ep->X_add_symbol), FAKE_LABEL_NAME) == 0
10287 && S_GET_SEGMENT (ep->X_add_symbol) == now_seg
10288 && symbol_get_frag (ep->X_add_symbol) == frag_now
10289 && symbol_constant_p (ep->X_add_symbol)
10290 && (val = S_GET_VALUE (ep->X_add_symbol)) == frag_now_fix ())
10291 S_SET_VALUE (ep->X_add_symbol, val + 1);
10294 /* Turn a string in input_line_pointer into a floating point constant
10295 of type TYPE, and store the appropriate bytes in *LITP. The number
10296 of LITTLENUMS emitted is stored in *SIZEP. An error message is
10297 returned, or NULL on OK. */
10300 md_atof (type, litP, sizeP)
10306 LITTLENUM_TYPE words[4];
10322 return _("bad call to md_atof");
10325 t = atof_ieee (input_line_pointer, type, words);
10327 input_line_pointer = t;
10331 if (! target_big_endian)
10333 for (i = prec - 1; i >= 0; i--)
10335 md_number_to_chars (litP, (valueT) words[i], 2);
10341 for (i = 0; i < prec; i++)
10343 md_number_to_chars (litP, (valueT) words[i], 2);
10352 md_number_to_chars (buf, val, n)
10357 if (target_big_endian)
10358 number_to_chars_bigendian (buf, val, n);
10360 number_to_chars_littleendian (buf, val, n);
10364 static int support_64bit_objects(void)
10366 const char **list, **l;
10369 list = bfd_target_list ();
10370 for (l = list; *l != NULL; l++)
10372 /* This is traditional mips */
10373 if (strcmp (*l, "elf64-tradbigmips") == 0
10374 || strcmp (*l, "elf64-tradlittlemips") == 0)
10376 if (strcmp (*l, "elf64-bigmips") == 0
10377 || strcmp (*l, "elf64-littlemips") == 0)
10380 yes = (*l != NULL);
10384 #endif /* OBJ_ELF */
10386 const char *md_shortopts = "nO::g::G:";
10388 struct option md_longopts[] =
10390 #define OPTION_MIPS1 (OPTION_MD_BASE + 1)
10391 {"mips0", no_argument, NULL, OPTION_MIPS1},
10392 {"mips1", no_argument, NULL, OPTION_MIPS1},
10393 #define OPTION_MIPS2 (OPTION_MD_BASE + 2)
10394 {"mips2", no_argument, NULL, OPTION_MIPS2},
10395 #define OPTION_MIPS3 (OPTION_MD_BASE + 3)
10396 {"mips3", no_argument, NULL, OPTION_MIPS3},
10397 #define OPTION_MIPS4 (OPTION_MD_BASE + 4)
10398 {"mips4", no_argument, NULL, OPTION_MIPS4},
10399 #define OPTION_MIPS5 (OPTION_MD_BASE + 5)
10400 {"mips5", no_argument, NULL, OPTION_MIPS5},
10401 #define OPTION_MIPS32 (OPTION_MD_BASE + 6)
10402 {"mips32", no_argument, NULL, OPTION_MIPS32},
10403 #define OPTION_MIPS64 (OPTION_MD_BASE + 7)
10404 {"mips64", no_argument, NULL, OPTION_MIPS64},
10405 #define OPTION_MEMBEDDED_PIC (OPTION_MD_BASE + 8)
10406 {"membedded-pic", no_argument, NULL, OPTION_MEMBEDDED_PIC},
10407 #define OPTION_TRAP (OPTION_MD_BASE + 9)
10408 {"trap", no_argument, NULL, OPTION_TRAP},
10409 {"no-break", no_argument, NULL, OPTION_TRAP},
10410 #define OPTION_BREAK (OPTION_MD_BASE + 10)
10411 {"break", no_argument, NULL, OPTION_BREAK},
10412 {"no-trap", no_argument, NULL, OPTION_BREAK},
10413 #define OPTION_EB (OPTION_MD_BASE + 11)
10414 {"EB", no_argument, NULL, OPTION_EB},
10415 #define OPTION_EL (OPTION_MD_BASE + 12)
10416 {"EL", no_argument, NULL, OPTION_EL},
10417 #define OPTION_MIPS16 (OPTION_MD_BASE + 13)
10418 {"mips16", no_argument, NULL, OPTION_MIPS16},
10419 #define OPTION_NO_MIPS16 (OPTION_MD_BASE + 14)
10420 {"no-mips16", no_argument, NULL, OPTION_NO_MIPS16},
10421 #define OPTION_M7000_HILO_FIX (OPTION_MD_BASE + 15)
10422 {"mfix7000", no_argument, NULL, OPTION_M7000_HILO_FIX},
10423 #define OPTION_MNO_7000_HILO_FIX (OPTION_MD_BASE + 16)
10424 {"no-fix-7000", no_argument, NULL, OPTION_MNO_7000_HILO_FIX},
10425 {"mno-fix7000", no_argument, NULL, OPTION_MNO_7000_HILO_FIX},
10426 #define OPTION_FP32 (OPTION_MD_BASE + 17)
10427 {"mfp32", no_argument, NULL, OPTION_FP32},
10428 #define OPTION_GP32 (OPTION_MD_BASE + 18)
10429 {"mgp32", no_argument, NULL, OPTION_GP32},
10430 #define OPTION_CONSTRUCT_FLOATS (OPTION_MD_BASE + 19)
10431 {"construct-floats", no_argument, NULL, OPTION_CONSTRUCT_FLOATS},
10432 #define OPTION_NO_CONSTRUCT_FLOATS (OPTION_MD_BASE + 20)
10433 {"no-construct-floats", no_argument, NULL, OPTION_NO_CONSTRUCT_FLOATS},
10434 #define OPTION_MARCH (OPTION_MD_BASE + 21)
10435 {"march", required_argument, NULL, OPTION_MARCH},
10436 #define OPTION_MTUNE (OPTION_MD_BASE + 22)
10437 {"mtune", required_argument, NULL, OPTION_MTUNE},
10438 #define OPTION_FP64 (OPTION_MD_BASE + 23)
10439 {"mfp64", no_argument, NULL, OPTION_FP64},
10440 #define OPTION_M4650 (OPTION_MD_BASE + 24)
10441 {"m4650", no_argument, NULL, OPTION_M4650},
10442 #define OPTION_NO_M4650 (OPTION_MD_BASE + 25)
10443 {"no-m4650", no_argument, NULL, OPTION_NO_M4650},
10444 #define OPTION_M4010 (OPTION_MD_BASE + 26)
10445 {"m4010", no_argument, NULL, OPTION_M4010},
10446 #define OPTION_NO_M4010 (OPTION_MD_BASE + 27)
10447 {"no-m4010", no_argument, NULL, OPTION_NO_M4010},
10448 #define OPTION_M4100 (OPTION_MD_BASE + 28)
10449 {"m4100", no_argument, NULL, OPTION_M4100},
10450 #define OPTION_NO_M4100 (OPTION_MD_BASE + 29)
10451 {"no-m4100", no_argument, NULL, OPTION_NO_M4100},
10452 #define OPTION_M3900 (OPTION_MD_BASE + 30)
10453 {"m3900", no_argument, NULL, OPTION_M3900},
10454 #define OPTION_NO_M3900 (OPTION_MD_BASE + 31)
10455 {"no-m3900", no_argument, NULL, OPTION_NO_M3900},
10456 #define OPTION_GP64 (OPTION_MD_BASE + 32)
10457 {"mgp64", no_argument, NULL, OPTION_GP64},
10458 #define OPTION_MIPS3D (OPTION_MD_BASE + 33)
10459 {"mips3d", no_argument, NULL, OPTION_MIPS3D},
10460 #define OPTION_NO_MIPS3D (OPTION_MD_BASE + 34)
10461 {"no-mips3d", no_argument, NULL, OPTION_NO_MIPS3D},
10462 #define OPTION_MDMX (OPTION_MD_BASE + 35)
10463 {"mdmx", no_argument, NULL, OPTION_MDMX},
10464 #define OPTION_NO_MDMX (OPTION_MD_BASE + 36)
10465 {"no-mdmx", no_argument, NULL, OPTION_NO_MDMX},
10466 #define OPTION_FIX_VR4122 (OPTION_MD_BASE + 37)
10467 #define OPTION_NO_FIX_VR4122 (OPTION_MD_BASE + 38)
10468 {"mfix-vr4122-bugs", no_argument, NULL, OPTION_FIX_VR4122},
10469 {"no-mfix-vr4122-bugs", no_argument, NULL, OPTION_NO_FIX_VR4122},
10470 #define OPTION_RELAX_BRANCH (OPTION_MD_BASE + 39)
10471 #define OPTION_NO_RELAX_BRANCH (OPTION_MD_BASE + 40)
10472 {"relax-branch", no_argument, NULL, OPTION_RELAX_BRANCH},
10473 {"no-relax-branch", no_argument, NULL, OPTION_NO_RELAX_BRANCH},
10474 #define OPTION_MIPS32R2 (OPTION_MD_BASE + 41)
10475 {"mips32r2", no_argument, NULL, OPTION_MIPS32R2},
10477 #define OPTION_ELF_BASE (OPTION_MD_BASE + 42)
10478 #define OPTION_CALL_SHARED (OPTION_ELF_BASE + 0)
10479 {"KPIC", no_argument, NULL, OPTION_CALL_SHARED},
10480 {"call_shared", no_argument, NULL, OPTION_CALL_SHARED},
10481 #define OPTION_NON_SHARED (OPTION_ELF_BASE + 1)
10482 {"non_shared", no_argument, NULL, OPTION_NON_SHARED},
10483 #define OPTION_XGOT (OPTION_ELF_BASE + 2)
10484 {"xgot", no_argument, NULL, OPTION_XGOT},
10485 #define OPTION_MABI (OPTION_ELF_BASE + 3)
10486 {"mabi", required_argument, NULL, OPTION_MABI},
10487 #define OPTION_32 (OPTION_ELF_BASE + 4)
10488 {"32", no_argument, NULL, OPTION_32},
10489 #define OPTION_N32 (OPTION_ELF_BASE + 5)
10490 {"n32", no_argument, NULL, OPTION_N32},
10491 #define OPTION_64 (OPTION_ELF_BASE + 6)
10492 {"64", no_argument, NULL, OPTION_64},
10493 #define OPTION_MDEBUG (OPTION_ELF_BASE + 7)
10494 {"mdebug", no_argument, NULL, OPTION_MDEBUG},
10495 #define OPTION_NO_MDEBUG (OPTION_ELF_BASE + 8)
10496 {"no-mdebug", no_argument, NULL, OPTION_NO_MDEBUG},
10497 #endif /* OBJ_ELF */
10498 {NULL, no_argument, NULL, 0}
10500 size_t md_longopts_size = sizeof (md_longopts);
10502 /* Set STRING_PTR (either &mips_arch_string or &mips_tune_string) to
10503 NEW_VALUE. Warn if another value was already specified. Note:
10504 we have to defer parsing the -march and -mtune arguments in order
10505 to handle 'from-abi' correctly, since the ABI might be specified
10506 in a later argument. */
10509 mips_set_option_string (string_ptr, new_value)
10510 const char **string_ptr, *new_value;
10512 if (*string_ptr != 0 && strcasecmp (*string_ptr, new_value) != 0)
10513 as_warn (_("A different %s was already specified, is now %s"),
10514 string_ptr == &mips_arch_string ? "-march" : "-mtune",
10517 *string_ptr = new_value;
10521 md_parse_option (c, arg)
10527 case OPTION_CONSTRUCT_FLOATS:
10528 mips_disable_float_construction = 0;
10531 case OPTION_NO_CONSTRUCT_FLOATS:
10532 mips_disable_float_construction = 1;
10544 target_big_endian = 1;
10548 target_big_endian = 0;
10556 if (arg && arg[1] == '0')
10566 mips_debug = atoi (arg);
10567 /* When the MIPS assembler sees -g or -g2, it does not do
10568 optimizations which limit full symbolic debugging. We take
10569 that to be equivalent to -O0. */
10570 if (mips_debug == 2)
10575 file_mips_isa = ISA_MIPS1;
10579 file_mips_isa = ISA_MIPS2;
10583 file_mips_isa = ISA_MIPS3;
10587 file_mips_isa = ISA_MIPS4;
10591 file_mips_isa = ISA_MIPS5;
10594 case OPTION_MIPS32:
10595 file_mips_isa = ISA_MIPS32;
10598 case OPTION_MIPS32R2:
10599 file_mips_isa = ISA_MIPS32R2;
10602 case OPTION_MIPS64:
10603 file_mips_isa = ISA_MIPS64;
10607 mips_set_option_string (&mips_tune_string, arg);
10611 mips_set_option_string (&mips_arch_string, arg);
10615 mips_set_option_string (&mips_arch_string, "4650");
10616 mips_set_option_string (&mips_tune_string, "4650");
10619 case OPTION_NO_M4650:
10623 mips_set_option_string (&mips_arch_string, "4010");
10624 mips_set_option_string (&mips_tune_string, "4010");
10627 case OPTION_NO_M4010:
10631 mips_set_option_string (&mips_arch_string, "4100");
10632 mips_set_option_string (&mips_tune_string, "4100");
10635 case OPTION_NO_M4100:
10639 mips_set_option_string (&mips_arch_string, "3900");
10640 mips_set_option_string (&mips_tune_string, "3900");
10643 case OPTION_NO_M3900:
10647 mips_opts.ase_mdmx = 1;
10650 case OPTION_NO_MDMX:
10651 mips_opts.ase_mdmx = 0;
10654 case OPTION_MIPS16:
10655 mips_opts.mips16 = 1;
10656 mips_no_prev_insn (FALSE);
10659 case OPTION_NO_MIPS16:
10660 mips_opts.mips16 = 0;
10661 mips_no_prev_insn (FALSE);
10664 case OPTION_MIPS3D:
10665 mips_opts.ase_mips3d = 1;
10668 case OPTION_NO_MIPS3D:
10669 mips_opts.ase_mips3d = 0;
10672 case OPTION_MEMBEDDED_PIC:
10673 mips_pic = EMBEDDED_PIC;
10674 if (USE_GLOBAL_POINTER_OPT && g_switch_seen)
10676 as_bad (_("-G may not be used with embedded PIC code"));
10679 g_switch_value = 0x7fffffff;
10682 case OPTION_FIX_VR4122:
10683 mips_fix_4122_bugs = 1;
10686 case OPTION_NO_FIX_VR4122:
10687 mips_fix_4122_bugs = 0;
10690 case OPTION_RELAX_BRANCH:
10691 mips_relax_branch = 1;
10694 case OPTION_NO_RELAX_BRANCH:
10695 mips_relax_branch = 0;
10699 /* When generating ELF code, we permit -KPIC and -call_shared to
10700 select SVR4_PIC, and -non_shared to select no PIC. This is
10701 intended to be compatible with Irix 5. */
10702 case OPTION_CALL_SHARED:
10703 if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
10705 as_bad (_("-call_shared is supported only for ELF format"));
10708 mips_pic = SVR4_PIC;
10709 if (g_switch_seen && g_switch_value != 0)
10711 as_bad (_("-G may not be used with SVR4 PIC code"));
10714 g_switch_value = 0;
10717 case OPTION_NON_SHARED:
10718 if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
10720 as_bad (_("-non_shared is supported only for ELF format"));
10726 /* The -xgot option tells the assembler to use 32 offsets when
10727 accessing the got in SVR4_PIC mode. It is for Irix
10732 #endif /* OBJ_ELF */
10735 if (! USE_GLOBAL_POINTER_OPT)
10737 as_bad (_("-G is not supported for this configuration"));
10740 else if (mips_pic == SVR4_PIC || mips_pic == EMBEDDED_PIC)
10742 as_bad (_("-G may not be used with SVR4 or embedded PIC code"));
10746 g_switch_value = atoi (arg);
10751 /* The -32, -n32 and -64 options are shortcuts for -mabi=32, -mabi=n32
10754 if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
10756 as_bad (_("-32 is supported for ELF format only"));
10759 mips_abi = O32_ABI;
10763 if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
10765 as_bad (_("-n32 is supported for ELF format only"));
10768 mips_abi = N32_ABI;
10772 if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
10774 as_bad (_("-64 is supported for ELF format only"));
10777 mips_abi = N64_ABI;
10778 if (! support_64bit_objects())
10779 as_fatal (_("No compiled in support for 64 bit object file format"));
10781 #endif /* OBJ_ELF */
10784 file_mips_gp32 = 1;
10788 file_mips_gp32 = 0;
10792 file_mips_fp32 = 1;
10796 file_mips_fp32 = 0;
10801 if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
10803 as_bad (_("-mabi is supported for ELF format only"));
10806 if (strcmp (arg, "32") == 0)
10807 mips_abi = O32_ABI;
10808 else if (strcmp (arg, "o64") == 0)
10809 mips_abi = O64_ABI;
10810 else if (strcmp (arg, "n32") == 0)
10811 mips_abi = N32_ABI;
10812 else if (strcmp (arg, "64") == 0)
10814 mips_abi = N64_ABI;
10815 if (! support_64bit_objects())
10816 as_fatal (_("No compiled in support for 64 bit object file "
10819 else if (strcmp (arg, "eabi") == 0)
10820 mips_abi = EABI_ABI;
10823 as_fatal (_("invalid abi -mabi=%s"), arg);
10827 #endif /* OBJ_ELF */
10829 case OPTION_M7000_HILO_FIX:
10830 mips_7000_hilo_fix = TRUE;
10833 case OPTION_MNO_7000_HILO_FIX:
10834 mips_7000_hilo_fix = FALSE;
10838 case OPTION_MDEBUG:
10839 mips_flag_mdebug = TRUE;
10842 case OPTION_NO_MDEBUG:
10843 mips_flag_mdebug = FALSE;
10845 #endif /* OBJ_ELF */
10854 /* Set up globals to generate code for the ISA or processor
10855 described by INFO. */
10858 mips_set_architecture (info)
10859 const struct mips_cpu_info *info;
10863 mips_arch_info = info;
10864 mips_arch = info->cpu;
10865 mips_opts.isa = info->isa;
10870 /* Likewise for tuning. */
10873 mips_set_tune (info)
10874 const struct mips_cpu_info *info;
10878 mips_tune_info = info;
10879 mips_tune = info->cpu;
10885 mips_after_parse_args ()
10887 /* GP relative stuff not working for PE */
10888 if (strncmp (TARGET_OS, "pe", 2) == 0
10889 && g_switch_value != 0)
10892 as_bad (_("-G not supported in this configuration."));
10893 g_switch_value = 0;
10896 /* The following code determines the architecture and register size.
10897 Similar code was added to GCC 3.3 (see override_options() in
10898 config/mips/mips.c). The GAS and GCC code should be kept in sync
10899 as much as possible. */
10901 if (mips_arch_string != 0)
10902 mips_set_architecture (mips_parse_cpu ("-march", mips_arch_string));
10904 if (mips_tune_string != 0)
10905 mips_set_tune (mips_parse_cpu ("-mtune", mips_tune_string));
10907 if (file_mips_isa != ISA_UNKNOWN)
10909 /* Handle -mipsN. At this point, file_mips_isa contains the
10910 ISA level specified by -mipsN, while mips_opts.isa contains
10911 the -march selection (if any). */
10912 if (mips_arch_info != 0)
10914 /* -march takes precedence over -mipsN, since it is more descriptive.
10915 There's no harm in specifying both as long as the ISA levels
10917 if (file_mips_isa != mips_opts.isa)
10918 as_bad (_("-%s conflicts with the other architecture options, which imply -%s"),
10919 mips_cpu_info_from_isa (file_mips_isa)->name,
10920 mips_cpu_info_from_isa (mips_opts.isa)->name);
10923 mips_set_architecture (mips_cpu_info_from_isa (file_mips_isa));
10926 if (mips_arch_info == 0)
10927 mips_set_architecture (mips_parse_cpu ("default CPU",
10928 MIPS_CPU_STRING_DEFAULT));
10930 if (ABI_NEEDS_64BIT_REGS (mips_abi) && !ISA_HAS_64BIT_REGS (mips_opts.isa))
10931 as_bad ("-march=%s is not compatible with the selected ABI",
10932 mips_arch_info->name);
10934 /* Optimize for mips_arch, unless -mtune selects a different processor. */
10935 if (mips_tune_info == 0)
10936 mips_set_tune (mips_arch_info);
10938 if (file_mips_gp32 >= 0)
10940 /* The user specified the size of the integer registers. Make sure
10941 it agrees with the ABI and ISA. */
10942 if (file_mips_gp32 == 0 && !ISA_HAS_64BIT_REGS (mips_opts.isa))
10943 as_bad (_("-mgp64 used with a 32-bit processor"));
10944 else if (file_mips_gp32 == 1 && ABI_NEEDS_64BIT_REGS (mips_abi))
10945 as_bad (_("-mgp32 used with a 64-bit ABI"));
10946 else if (file_mips_gp32 == 0 && ABI_NEEDS_32BIT_REGS (mips_abi))
10947 as_bad (_("-mgp64 used with a 32-bit ABI"));
10951 /* Infer the integer register size from the ABI and processor.
10952 Restrict ourselves to 32-bit registers if that's all the
10953 processor has, or if the ABI cannot handle 64-bit registers. */
10954 file_mips_gp32 = (ABI_NEEDS_32BIT_REGS (mips_abi)
10955 || !ISA_HAS_64BIT_REGS (mips_opts.isa));
10958 /* ??? GAS treats single-float processors as though they had 64-bit
10959 float registers (although it complains when double-precision
10960 instructions are used). As things stand, saying they have 32-bit
10961 registers would lead to spurious "register must be even" messages.
10962 So here we assume float registers are always the same size as
10963 integer ones, unless the user says otherwise. */
10964 if (file_mips_fp32 < 0)
10965 file_mips_fp32 = file_mips_gp32;
10967 /* End of GCC-shared inference code. */
10969 /* ??? When do we want this flag to be set? Who uses it? */
10970 if (file_mips_gp32 == 1
10971 && mips_abi == NO_ABI
10972 && ISA_HAS_64BIT_REGS (mips_opts.isa))
10973 mips_32bitmode = 1;
10975 if (mips_opts.isa == ISA_MIPS1 && mips_trap)
10976 as_bad (_("trap exception not supported at ISA 1"));
10978 /* If the selected architecture includes support for ASEs, enable
10979 generation of code for them. */
10980 if (mips_opts.mips16 == -1)
10981 mips_opts.mips16 = (CPU_HAS_MIPS16 (mips_arch)) ? 1 : 0;
10982 if (mips_opts.ase_mips3d == -1)
10983 mips_opts.ase_mips3d = (CPU_HAS_MIPS3D (mips_arch)) ? 1 : 0;
10984 if (mips_opts.ase_mdmx == -1)
10985 mips_opts.ase_mdmx = (CPU_HAS_MDMX (mips_arch)) ? 1 : 0;
10987 file_mips_isa = mips_opts.isa;
10988 file_ase_mips16 = mips_opts.mips16;
10989 file_ase_mips3d = mips_opts.ase_mips3d;
10990 file_ase_mdmx = mips_opts.ase_mdmx;
10991 mips_opts.gp32 = file_mips_gp32;
10992 mips_opts.fp32 = file_mips_fp32;
10994 if (mips_flag_mdebug < 0)
10996 #ifdef OBJ_MAYBE_ECOFF
10997 if (OUTPUT_FLAVOR == bfd_target_ecoff_flavour)
10998 mips_flag_mdebug = 1;
11000 #endif /* OBJ_MAYBE_ECOFF */
11001 mips_flag_mdebug = 0;
11006 mips_init_after_args ()
11008 /* initialize opcodes */
11009 bfd_mips_num_opcodes = bfd_mips_num_builtin_opcodes;
11010 mips_opcodes = (struct mips_opcode *) mips_builtin_opcodes;
11014 md_pcrel_from (fixP)
11017 if (OUTPUT_FLAVOR != bfd_target_aout_flavour
11018 && fixP->fx_addsy != (symbolS *) NULL
11019 && ! S_IS_DEFINED (fixP->fx_addsy))
11022 /* Return the address of the delay slot. */
11023 return fixP->fx_size + fixP->fx_where + fixP->fx_frag->fr_address;
11026 /* This is called before the symbol table is processed. In order to
11027 work with gcc when using mips-tfile, we must keep all local labels.
11028 However, in other cases, we want to discard them. If we were
11029 called with -g, but we didn't see any debugging information, it may
11030 mean that gcc is smuggling debugging information through to
11031 mips-tfile, in which case we must generate all local labels. */
11034 mips_frob_file_before_adjust ()
11036 #ifndef NO_ECOFF_DEBUGGING
11037 if (ECOFF_DEBUGGING
11039 && ! ecoff_debugging_seen)
11040 flag_keep_locals = 1;
11044 /* Sort any unmatched HI16_S relocs so that they immediately precede
11045 the corresponding LO reloc. This is called before md_apply_fix3 and
11046 tc_gen_reloc. Unmatched HI16_S relocs can only be generated by
11047 explicit use of the %hi modifier. */
11052 struct mips_hi_fixup *l;
11054 for (l = mips_hi_fixup_list; l != NULL; l = l->next)
11056 segment_info_type *seginfo;
11059 assert (l->fixp->fx_r_type == BFD_RELOC_HI16_S);
11061 /* Check quickly whether the next fixup happens to be a matching
11063 if (l->fixp->fx_next != NULL
11064 && l->fixp->fx_next->fx_r_type == BFD_RELOC_LO16
11065 && l->fixp->fx_addsy == l->fixp->fx_next->fx_addsy
11066 && l->fixp->fx_offset == l->fixp->fx_next->fx_offset)
11069 /* Look through the fixups for this segment for a matching %lo.
11070 When we find one, move the %hi just in front of it. We do
11071 this in two passes. In the first pass, we try to find a
11072 unique %lo. In the second pass, we permit multiple %hi
11073 relocs for a single %lo (this is a GNU extension). */
11074 seginfo = seg_info (l->seg);
11075 for (pass = 0; pass < 2; pass++)
11080 for (f = seginfo->fix_root; f != NULL; f = f->fx_next)
11082 /* Check whether this is a %lo fixup which matches l->fixp. */
11083 if (f->fx_r_type == BFD_RELOC_LO16
11084 && f->fx_addsy == l->fixp->fx_addsy
11085 && f->fx_offset == l->fixp->fx_offset
11088 || prev->fx_r_type != BFD_RELOC_HI16_S
11089 || prev->fx_addsy != f->fx_addsy
11090 || prev->fx_offset != f->fx_offset))
11094 /* Move l->fixp before f. */
11095 for (pf = &seginfo->fix_root;
11097 pf = &(*pf)->fx_next)
11098 assert (*pf != NULL);
11100 *pf = l->fixp->fx_next;
11102 l->fixp->fx_next = f;
11104 seginfo->fix_root = l->fixp;
11106 prev->fx_next = l->fixp;
11117 #if 0 /* GCC code motion plus incomplete dead code elimination
11118 can leave a %hi without a %lo. */
11120 as_warn_where (l->fixp->fx_file, l->fixp->fx_line,
11121 _("Unmatched %%hi reloc"));
11127 /* When generating embedded PIC code we need to use a special
11128 relocation to represent the difference of two symbols in the .text
11129 section (switch tables use a difference of this sort). See
11130 include/coff/mips.h for details. This macro checks whether this
11131 fixup requires the special reloc. */
11132 #define SWITCH_TABLE(fixp) \
11133 ((fixp)->fx_r_type == BFD_RELOC_32 \
11134 && OUTPUT_FLAVOR != bfd_target_elf_flavour \
11135 && (fixp)->fx_addsy != NULL \
11136 && (fixp)->fx_subsy != NULL \
11137 && S_GET_SEGMENT ((fixp)->fx_addsy) == text_section \
11138 && S_GET_SEGMENT ((fixp)->fx_subsy) == text_section)
11140 /* When generating embedded PIC code we must keep all PC relative
11141 relocations, in case the linker has to relax a call. We also need
11142 to keep relocations for switch table entries.
11144 We may have combined relocations without symbols in the N32/N64 ABI.
11145 We have to prevent gas from dropping them. */
11148 mips_force_relocation (fixp)
11151 if (fixp->fx_r_type == BFD_RELOC_VTABLE_INHERIT
11152 || fixp->fx_r_type == BFD_RELOC_VTABLE_ENTRY
11153 || S_FORCE_RELOC (fixp->fx_addsy))
11157 && S_GET_SEGMENT (fixp->fx_addsy) == bfd_abs_section_ptr
11158 && (fixp->fx_r_type == BFD_RELOC_MIPS_SUB
11159 || fixp->fx_r_type == BFD_RELOC_HI16_S
11160 || fixp->fx_r_type == BFD_RELOC_LO16))
11163 return (mips_pic == EMBEDDED_PIC
11165 || SWITCH_TABLE (fixp)
11166 || fixp->fx_r_type == BFD_RELOC_PCREL_HI16_S
11167 || fixp->fx_r_type == BFD_RELOC_PCREL_LO16));
11172 mips_need_elf_addend_fixup (fixP)
11175 if (S_GET_OTHER (fixP->fx_addsy) == STO_MIPS16)
11177 if (mips_pic == EMBEDDED_PIC
11178 && S_IS_WEAK (fixP->fx_addsy))
11180 if (mips_pic != EMBEDDED_PIC
11181 && (S_IS_WEAK (fixP->fx_addsy)
11182 || S_IS_EXTERNAL (fixP->fx_addsy))
11183 && !S_IS_COMMON (fixP->fx_addsy))
11185 if (symbol_used_in_reloc_p (fixP->fx_addsy)
11186 && (((bfd_get_section_flags (stdoutput,
11187 S_GET_SEGMENT (fixP->fx_addsy))
11188 & (SEC_LINK_ONCE | SEC_MERGE)) != 0)
11189 || !strncmp (segment_name (S_GET_SEGMENT (fixP->fx_addsy)),
11191 sizeof (".gnu.linkonce") - 1)))
11197 /* Apply a fixup to the object file. */
11200 md_apply_fix3 (fixP, valP, seg)
11203 segT seg ATTRIBUTE_UNUSED;
11208 static int previous_fx_r_type = 0;
11210 /* FIXME: Maybe just return for all reloc types not listed below?
11211 Eric Christopher says: "This is stupid, please rewrite md_apply_fix3. */
11212 if (fixP->fx_r_type == BFD_RELOC_8)
11215 assert (fixP->fx_size == 4
11216 || fixP->fx_r_type == BFD_RELOC_16
11217 || fixP->fx_r_type == BFD_RELOC_32
11218 || fixP->fx_r_type == BFD_RELOC_MIPS_JMP
11219 || fixP->fx_r_type == BFD_RELOC_HI16_S
11220 || fixP->fx_r_type == BFD_RELOC_LO16
11221 || fixP->fx_r_type == BFD_RELOC_GPREL16
11222 || fixP->fx_r_type == BFD_RELOC_MIPS_LITERAL
11223 || fixP->fx_r_type == BFD_RELOC_GPREL32
11224 || fixP->fx_r_type == BFD_RELOC_64
11225 || fixP->fx_r_type == BFD_RELOC_CTOR
11226 || fixP->fx_r_type == BFD_RELOC_MIPS_SUB
11227 || fixP->fx_r_type == BFD_RELOC_MIPS_HIGHEST
11228 || fixP->fx_r_type == BFD_RELOC_MIPS_HIGHER
11229 || fixP->fx_r_type == BFD_RELOC_MIPS_SCN_DISP
11230 || fixP->fx_r_type == BFD_RELOC_MIPS_REL16
11231 || fixP->fx_r_type == BFD_RELOC_MIPS_RELGOT
11232 || fixP->fx_r_type == BFD_RELOC_VTABLE_INHERIT
11233 || fixP->fx_r_type == BFD_RELOC_VTABLE_ENTRY
11234 || fixP->fx_r_type == BFD_RELOC_MIPS_JALR);
11238 /* If we aren't adjusting this fixup to be against the section
11239 symbol, we need to adjust the value. */
11241 if (fixP->fx_addsy != NULL && OUTPUT_FLAVOR == bfd_target_elf_flavour)
11243 if (mips_need_elf_addend_fixup (fixP))
11245 reloc_howto_type *howto;
11246 valueT symval = S_GET_VALUE (fixP->fx_addsy);
11250 howto = bfd_reloc_type_lookup (stdoutput, fixP->fx_r_type);
11251 if (value != 0 && howto && howto->partial_inplace
11252 && (! fixP->fx_pcrel || howto->pcrel_offset))
11254 /* In this case, the bfd_install_relocation routine will
11255 incorrectly add the symbol value back in. We just want
11256 the addend to appear in the object file.
11258 howto->pcrel_offset is added for R_MIPS_PC16, which is
11259 generated for code like
11270 /* Make sure the addend is still non-zero. If it became zero
11271 after the last operation, set it to a spurious value and
11272 subtract the same value from the object file's contents. */
11277 /* The in-place addends for LO16 relocations are signed;
11278 leave the matching HI16 in-place addends as zero. */
11279 if (fixP->fx_r_type != BFD_RELOC_HI16_S)
11281 bfd_vma contents, mask, field;
11283 contents = bfd_get_bits (fixP->fx_frag->fr_literal
11286 target_big_endian);
11288 /* MASK has bits set where the relocation should go.
11289 FIELD is -value, shifted into the appropriate place
11290 for this relocation. */
11291 mask = 1 << (howto->bitsize - 1);
11292 mask = (((mask - 1) << 1) | 1) << howto->bitpos;
11293 field = (-value >> howto->rightshift) << howto->bitpos;
11295 bfd_put_bits ((field & mask) | (contents & ~mask),
11296 fixP->fx_frag->fr_literal + fixP->fx_where,
11298 target_big_endian);
11304 /* This code was generated using trial and error and so is
11305 fragile and not trustworthy. If you change it, you should
11306 rerun the elf-rel, elf-rel2, and empic testcases and ensure
11307 they still pass. */
11308 if (fixP->fx_pcrel || fixP->fx_subsy != NULL)
11310 value += fixP->fx_frag->fr_address + fixP->fx_where;
11312 /* BFD's REL handling, for MIPS, is _very_ weird.
11313 This gives the right results, but it can't possibly
11314 be the way things are supposed to work. */
11315 if (fixP->fx_r_type != BFD_RELOC_16_PCREL_S2
11316 || S_GET_SEGMENT (fixP->fx_addsy) != undefined_section)
11317 value += fixP->fx_frag->fr_address + fixP->fx_where;
11322 fixP->fx_addnumber = value; /* Remember value for tc_gen_reloc. */
11324 /* We are not done if this is a composite relocation to set up gp. */
11325 if (fixP->fx_addsy == NULL && ! fixP->fx_pcrel
11326 && !(fixP->fx_r_type == BFD_RELOC_MIPS_SUB
11327 || (fixP->fx_r_type == BFD_RELOC_64
11328 && (previous_fx_r_type == BFD_RELOC_GPREL32
11329 || previous_fx_r_type == BFD_RELOC_GPREL16))
11330 || (previous_fx_r_type == BFD_RELOC_MIPS_SUB
11331 && (fixP->fx_r_type == BFD_RELOC_HI16_S
11332 || fixP->fx_r_type == BFD_RELOC_LO16))))
11334 previous_fx_r_type = fixP->fx_r_type;
11336 switch (fixP->fx_r_type)
11338 case BFD_RELOC_MIPS_JMP:
11339 case BFD_RELOC_MIPS_SHIFT5:
11340 case BFD_RELOC_MIPS_SHIFT6:
11341 case BFD_RELOC_MIPS_GOT_DISP:
11342 case BFD_RELOC_MIPS_GOT_PAGE:
11343 case BFD_RELOC_MIPS_GOT_OFST:
11344 case BFD_RELOC_MIPS_SUB:
11345 case BFD_RELOC_MIPS_INSERT_A:
11346 case BFD_RELOC_MIPS_INSERT_B:
11347 case BFD_RELOC_MIPS_DELETE:
11348 case BFD_RELOC_MIPS_HIGHEST:
11349 case BFD_RELOC_MIPS_HIGHER:
11350 case BFD_RELOC_MIPS_SCN_DISP:
11351 case BFD_RELOC_MIPS_REL16:
11352 case BFD_RELOC_MIPS_RELGOT:
11353 case BFD_RELOC_MIPS_JALR:
11354 case BFD_RELOC_HI16:
11355 case BFD_RELOC_HI16_S:
11356 case BFD_RELOC_GPREL16:
11357 case BFD_RELOC_MIPS_LITERAL:
11358 case BFD_RELOC_MIPS_CALL16:
11359 case BFD_RELOC_MIPS_GOT16:
11360 case BFD_RELOC_GPREL32:
11361 case BFD_RELOC_MIPS_GOT_HI16:
11362 case BFD_RELOC_MIPS_GOT_LO16:
11363 case BFD_RELOC_MIPS_CALL_HI16:
11364 case BFD_RELOC_MIPS_CALL_LO16:
11365 case BFD_RELOC_MIPS16_GPREL:
11366 if (fixP->fx_pcrel)
11367 as_bad_where (fixP->fx_file, fixP->fx_line,
11368 _("Invalid PC relative reloc"));
11369 /* Nothing needed to do. The value comes from the reloc entry */
11372 case BFD_RELOC_MIPS16_JMP:
11373 /* We currently always generate a reloc against a symbol, which
11374 means that we don't want an addend even if the symbol is
11376 fixP->fx_addnumber = 0;
11379 case BFD_RELOC_PCREL_HI16_S:
11380 /* The addend for this is tricky if it is internal, so we just
11381 do everything here rather than in bfd_install_relocation. */
11382 if (OUTPUT_FLAVOR == bfd_target_elf_flavour
11387 && (symbol_get_bfdsym (fixP->fx_addsy)->flags & BSF_SECTION_SYM) == 0)
11389 /* For an external symbol adjust by the address to make it
11390 pcrel_offset. We use the address of the RELLO reloc
11391 which follows this one. */
11392 value += (fixP->fx_next->fx_frag->fr_address
11393 + fixP->fx_next->fx_where);
11395 value = ((value + 0x8000) >> 16) & 0xffff;
11396 buf = (bfd_byte *) fixP->fx_frag->fr_literal + fixP->fx_where;
11397 if (target_big_endian)
11399 md_number_to_chars ((char *) buf, value, 2);
11402 case BFD_RELOC_PCREL_LO16:
11403 /* The addend for this is tricky if it is internal, so we just
11404 do everything here rather than in bfd_install_relocation. */
11405 if (OUTPUT_FLAVOR == bfd_target_elf_flavour
11410 && (symbol_get_bfdsym (fixP->fx_addsy)->flags & BSF_SECTION_SYM) == 0)
11411 value += fixP->fx_frag->fr_address + fixP->fx_where;
11412 buf = (bfd_byte *) fixP->fx_frag->fr_literal + fixP->fx_where;
11413 if (target_big_endian)
11415 md_number_to_chars ((char *) buf, value, 2);
11419 /* This is handled like BFD_RELOC_32, but we output a sign
11420 extended value if we are only 32 bits. */
11422 || (mips_pic == EMBEDDED_PIC && SWITCH_TABLE (fixP)))
11424 if (8 <= sizeof (valueT))
11425 md_number_to_chars (fixP->fx_frag->fr_literal + fixP->fx_where,
11432 w1 = w2 = fixP->fx_where;
11433 if (target_big_endian)
11437 md_number_to_chars (fixP->fx_frag->fr_literal + w1, value, 4);
11438 if ((value & 0x80000000) != 0)
11442 md_number_to_chars (fixP->fx_frag->fr_literal + w2, hiv, 4);
11447 case BFD_RELOC_RVA:
11449 /* If we are deleting this reloc entry, we must fill in the
11450 value now. This can happen if we have a .word which is not
11451 resolved when it appears but is later defined. We also need
11452 to fill in the value if this is an embedded PIC switch table
11455 || (mips_pic == EMBEDDED_PIC && SWITCH_TABLE (fixP)))
11456 md_number_to_chars (fixP->fx_frag->fr_literal + fixP->fx_where,
11461 /* If we are deleting this reloc entry, we must fill in the
11463 assert (fixP->fx_size == 2);
11465 md_number_to_chars (fixP->fx_frag->fr_literal + fixP->fx_where,
11469 case BFD_RELOC_LO16:
11470 /* When handling an embedded PIC switch statement, we can wind
11471 up deleting a LO16 reloc. See the 'o' case in mips_ip. */
11474 if (value + 0x8000 > 0xffff)
11475 as_bad_where (fixP->fx_file, fixP->fx_line,
11476 _("relocation overflow"));
11477 buf = (bfd_byte *) fixP->fx_frag->fr_literal + fixP->fx_where;
11478 if (target_big_endian)
11480 md_number_to_chars ((char *) buf, value, 2);
11484 case BFD_RELOC_16_PCREL_S2:
11485 if ((value & 0x3) != 0)
11486 as_bad_where (fixP->fx_file, fixP->fx_line,
11487 _("Branch to odd address (%lx)"), (long) value);
11490 * We need to save the bits in the instruction since fixup_segment()
11491 * might be deleting the relocation entry (i.e., a branch within
11492 * the current segment).
11494 if (!fixP->fx_done && (value != 0 || HAVE_NEWABI))
11496 /* If 'value' is zero, the remaining reloc code won't actually
11497 do the store, so it must be done here. This is probably
11498 a bug somewhere. */
11500 && (fixP->fx_r_type != BFD_RELOC_16_PCREL_S2
11501 || fixP->fx_addsy == NULL /* ??? */
11502 || ! S_IS_DEFINED (fixP->fx_addsy)))
11503 value -= fixP->fx_frag->fr_address + fixP->fx_where;
11505 value = (offsetT) value >> 2;
11507 /* update old instruction data */
11508 buf = (bfd_byte *) (fixP->fx_where + fixP->fx_frag->fr_literal);
11509 if (target_big_endian)
11510 insn = (buf[0] << 24) | (buf[1] << 16) | (buf[2] << 8) | buf[3];
11512 insn = (buf[3] << 24) | (buf[2] << 16) | (buf[1] << 8) | buf[0];
11514 if (value + 0x8000 <= 0xffff)
11515 insn |= value & 0xffff;
11518 /* The branch offset is too large. If this is an
11519 unconditional branch, and we are not generating PIC code,
11520 we can convert it to an absolute jump instruction. */
11521 if (mips_pic == NO_PIC
11523 && fixP->fx_frag->fr_address >= text_section->vma
11524 && (fixP->fx_frag->fr_address
11525 < text_section->vma + text_section->_raw_size)
11526 && ((insn & 0xffff0000) == 0x10000000 /* beq $0,$0 */
11527 || (insn & 0xffff0000) == 0x04010000 /* bgez $0 */
11528 || (insn & 0xffff0000) == 0x04110000)) /* bgezal $0 */
11530 if ((insn & 0xffff0000) == 0x04110000) /* bgezal $0 */
11531 insn = 0x0c000000; /* jal */
11533 insn = 0x08000000; /* j */
11534 fixP->fx_r_type = BFD_RELOC_MIPS_JMP;
11536 fixP->fx_addsy = section_symbol (text_section);
11537 fixP->fx_addnumber = (value << 2) + md_pcrel_from (fixP);
11541 /* If we got here, we have branch-relaxation disabled,
11542 and there's nothing we can do to fix this instruction
11543 without turning it into a longer sequence. */
11544 as_bad_where (fixP->fx_file, fixP->fx_line,
11545 _("Branch out of range"));
11549 md_number_to_chars ((char *) buf, (valueT) insn, 4);
11552 case BFD_RELOC_VTABLE_INHERIT:
11555 && !S_IS_DEFINED (fixP->fx_addsy)
11556 && !S_IS_WEAK (fixP->fx_addsy))
11557 S_SET_WEAK (fixP->fx_addsy);
11560 case BFD_RELOC_VTABLE_ENTRY:
11574 const struct mips_opcode *p;
11575 int treg, sreg, dreg, shamt;
11580 for (i = 0; i < NUMOPCODES; ++i)
11582 p = &mips_opcodes[i];
11583 if (((oc & p->mask) == p->match) && (p->pinfo != INSN_MACRO))
11585 printf ("%08lx %s\t", oc, p->name);
11586 treg = (oc >> 16) & 0x1f;
11587 sreg = (oc >> 21) & 0x1f;
11588 dreg = (oc >> 11) & 0x1f;
11589 shamt = (oc >> 6) & 0x1f;
11591 for (args = p->args;; ++args)
11602 printf ("%c", *args);
11606 assert (treg == sreg);
11607 printf ("$%d,$%d", treg, sreg);
11612 printf ("$%d", dreg);
11617 printf ("$%d", treg);
11621 printf ("0x%x", treg);
11626 printf ("$%d", sreg);
11630 printf ("0x%08lx", oc & 0x1ffffff);
11637 printf ("%d", imm);
11642 printf ("$%d", shamt);
11653 printf (_("%08lx UNDEFINED\n"), oc);
11664 name = input_line_pointer;
11665 c = get_symbol_end ();
11666 p = (symbolS *) symbol_find_or_make (name);
11667 *input_line_pointer = c;
11671 /* Align the current frag to a given power of two. The MIPS assembler
11672 also automatically adjusts any preceding label. */
11675 mips_align (to, fill, label)
11680 mips_emit_delays (FALSE);
11681 frag_align (to, fill, 0);
11682 record_alignment (now_seg, to);
11685 assert (S_GET_SEGMENT (label) == now_seg);
11686 symbol_set_frag (label, frag_now);
11687 S_SET_VALUE (label, (valueT) frag_now_fix ());
11691 /* Align to a given power of two. .align 0 turns off the automatic
11692 alignment used by the data creating pseudo-ops. */
11696 int x ATTRIBUTE_UNUSED;
11699 register long temp_fill;
11700 long max_alignment = 15;
11704 o Note that the assembler pulls down any immediately preceeding label
11705 to the aligned address.
11706 o It's not documented but auto alignment is reinstated by
11707 a .align pseudo instruction.
11708 o Note also that after auto alignment is turned off the mips assembler
11709 issues an error on attempt to assemble an improperly aligned data item.
11714 temp = get_absolute_expression ();
11715 if (temp > max_alignment)
11716 as_bad (_("Alignment too large: %d. assumed."), temp = max_alignment);
11719 as_warn (_("Alignment negative: 0 assumed."));
11722 if (*input_line_pointer == ',')
11724 ++input_line_pointer;
11725 temp_fill = get_absolute_expression ();
11732 mips_align (temp, (int) temp_fill,
11733 insn_labels != NULL ? insn_labels->label : NULL);
11740 demand_empty_rest_of_line ();
11744 mips_flush_pending_output ()
11746 mips_emit_delays (FALSE);
11747 mips_clear_insn_labels ();
11756 /* When generating embedded PIC code, we only use the .text, .lit8,
11757 .sdata and .sbss sections. We change the .data and .rdata
11758 pseudo-ops to use .sdata. */
11759 if (mips_pic == EMBEDDED_PIC
11760 && (sec == 'd' || sec == 'r'))
11764 /* The ELF backend needs to know that we are changing sections, so
11765 that .previous works correctly. We could do something like check
11766 for an obj_section_change_hook macro, but that might be confusing
11767 as it would not be appropriate to use it in the section changing
11768 functions in read.c, since obj-elf.c intercepts those. FIXME:
11769 This should be cleaner, somehow. */
11770 obj_elf_section_change_hook ();
11773 mips_emit_delays (FALSE);
11783 subseg_set (bss_section, (subsegT) get_absolute_expression ());
11784 demand_empty_rest_of_line ();
11788 if (USE_GLOBAL_POINTER_OPT)
11790 seg = subseg_new (RDATA_SECTION_NAME,
11791 (subsegT) get_absolute_expression ());
11792 if (OUTPUT_FLAVOR == bfd_target_elf_flavour)
11794 bfd_set_section_flags (stdoutput, seg,
11800 if (strcmp (TARGET_OS, "elf") != 0)
11801 record_alignment (seg, 4);
11803 demand_empty_rest_of_line ();
11807 as_bad (_("No read only data section in this object file format"));
11808 demand_empty_rest_of_line ();
11814 if (USE_GLOBAL_POINTER_OPT)
11816 seg = subseg_new (".sdata", (subsegT) get_absolute_expression ());
11817 if (OUTPUT_FLAVOR == bfd_target_elf_flavour)
11819 bfd_set_section_flags (stdoutput, seg,
11820 SEC_ALLOC | SEC_LOAD | SEC_RELOC
11822 if (strcmp (TARGET_OS, "elf") != 0)
11823 record_alignment (seg, 4);
11825 demand_empty_rest_of_line ();
11830 as_bad (_("Global pointers not supported; recompile -G 0"));
11831 demand_empty_rest_of_line ();
11840 s_change_section (ignore)
11841 int ignore ATTRIBUTE_UNUSED;
11844 char *section_name;
11849 int section_entry_size;
11850 int section_alignment;
11852 if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
11855 section_name = input_line_pointer;
11856 c = get_symbol_end ();
11858 next_c = *(input_line_pointer + 1);
11860 /* Do we have .section Name<,"flags">? */
11861 if (c != ',' || (c == ',' && next_c == '"'))
11863 /* just after name is now '\0'. */
11864 *input_line_pointer = c;
11865 input_line_pointer = section_name;
11866 obj_elf_section (ignore);
11869 input_line_pointer++;
11871 /* Do we have .section Name<,type><,flag><,entry_size><,alignment> */
11873 section_type = get_absolute_expression ();
11876 if (*input_line_pointer++ == ',')
11877 section_flag = get_absolute_expression ();
11880 if (*input_line_pointer++ == ',')
11881 section_entry_size = get_absolute_expression ();
11883 section_entry_size = 0;
11884 if (*input_line_pointer++ == ',')
11885 section_alignment = get_absolute_expression ();
11887 section_alignment = 0;
11889 section_name = xstrdup (section_name);
11891 obj_elf_change_section (section_name, section_type, section_flag,
11892 section_entry_size, 0, 0, 0);
11894 if (now_seg->name != section_name)
11895 free (section_name);
11896 #endif /* OBJ_ELF */
11900 mips_enable_auto_align ()
11911 label = insn_labels != NULL ? insn_labels->label : NULL;
11912 mips_emit_delays (FALSE);
11913 if (log_size > 0 && auto_align)
11914 mips_align (log_size, 0, label);
11915 mips_clear_insn_labels ();
11916 cons (1 << log_size);
11920 s_float_cons (type)
11925 label = insn_labels != NULL ? insn_labels->label : NULL;
11927 mips_emit_delays (FALSE);
11932 mips_align (3, 0, label);
11934 mips_align (2, 0, label);
11937 mips_clear_insn_labels ();
11942 /* Handle .globl. We need to override it because on Irix 5 you are
11945 where foo is an undefined symbol, to mean that foo should be
11946 considered to be the address of a function. */
11950 int x ATTRIBUTE_UNUSED;
11957 name = input_line_pointer;
11958 c = get_symbol_end ();
11959 symbolP = symbol_find_or_make (name);
11960 *input_line_pointer = c;
11961 SKIP_WHITESPACE ();
11963 /* On Irix 5, every global symbol that is not explicitly labelled as
11964 being a function is apparently labelled as being an object. */
11967 if (! is_end_of_line[(unsigned char) *input_line_pointer])
11972 secname = input_line_pointer;
11973 c = get_symbol_end ();
11974 sec = bfd_get_section_by_name (stdoutput, secname);
11976 as_bad (_("%s: no such section"), secname);
11977 *input_line_pointer = c;
11979 if (sec != NULL && (sec->flags & SEC_CODE) != 0)
11980 flag = BSF_FUNCTION;
11983 symbol_get_bfdsym (symbolP)->flags |= flag;
11985 S_SET_EXTERNAL (symbolP);
11986 demand_empty_rest_of_line ();
11991 int x ATTRIBUTE_UNUSED;
11996 opt = input_line_pointer;
11997 c = get_symbol_end ();
12001 /* FIXME: What does this mean? */
12003 else if (strncmp (opt, "pic", 3) == 0)
12007 i = atoi (opt + 3);
12011 mips_pic = SVR4_PIC;
12013 as_bad (_(".option pic%d not supported"), i);
12015 if (USE_GLOBAL_POINTER_OPT && mips_pic == SVR4_PIC)
12017 if (g_switch_seen && g_switch_value != 0)
12018 as_warn (_("-G may not be used with SVR4 PIC code"));
12019 g_switch_value = 0;
12020 bfd_set_gp_size (stdoutput, 0);
12024 as_warn (_("Unrecognized option \"%s\""), opt);
12026 *input_line_pointer = c;
12027 demand_empty_rest_of_line ();
12030 /* This structure is used to hold a stack of .set values. */
12032 struct mips_option_stack
12034 struct mips_option_stack *next;
12035 struct mips_set_options options;
12038 static struct mips_option_stack *mips_opts_stack;
12040 /* Handle the .set pseudo-op. */
12044 int x ATTRIBUTE_UNUSED;
12046 char *name = input_line_pointer, ch;
12048 while (!is_end_of_line[(unsigned char) *input_line_pointer])
12049 ++input_line_pointer;
12050 ch = *input_line_pointer;
12051 *input_line_pointer = '\0';
12053 if (strcmp (name, "reorder") == 0)
12055 if (mips_opts.noreorder && prev_nop_frag != NULL)
12057 /* If we still have pending nops, we can discard them. The
12058 usual nop handling will insert any that are still
12060 prev_nop_frag->fr_fix -= (prev_nop_frag_holds
12061 * (mips_opts.mips16 ? 2 : 4));
12062 prev_nop_frag = NULL;
12064 mips_opts.noreorder = 0;
12066 else if (strcmp (name, "noreorder") == 0)
12068 mips_emit_delays (TRUE);
12069 mips_opts.noreorder = 1;
12070 mips_any_noreorder = 1;
12072 else if (strcmp (name, "at") == 0)
12074 mips_opts.noat = 0;
12076 else if (strcmp (name, "noat") == 0)
12078 mips_opts.noat = 1;
12080 else if (strcmp (name, "macro") == 0)
12082 mips_opts.warn_about_macros = 0;
12084 else if (strcmp (name, "nomacro") == 0)
12086 if (mips_opts.noreorder == 0)
12087 as_bad (_("`noreorder' must be set before `nomacro'"));
12088 mips_opts.warn_about_macros = 1;
12090 else if (strcmp (name, "move") == 0 || strcmp (name, "novolatile") == 0)
12092 mips_opts.nomove = 0;
12094 else if (strcmp (name, "nomove") == 0 || strcmp (name, "volatile") == 0)
12096 mips_opts.nomove = 1;
12098 else if (strcmp (name, "bopt") == 0)
12100 mips_opts.nobopt = 0;
12102 else if (strcmp (name, "nobopt") == 0)
12104 mips_opts.nobopt = 1;
12106 else if (strcmp (name, "mips16") == 0
12107 || strcmp (name, "MIPS-16") == 0)
12108 mips_opts.mips16 = 1;
12109 else if (strcmp (name, "nomips16") == 0
12110 || strcmp (name, "noMIPS-16") == 0)
12111 mips_opts.mips16 = 0;
12112 else if (strcmp (name, "mips3d") == 0)
12113 mips_opts.ase_mips3d = 1;
12114 else if (strcmp (name, "nomips3d") == 0)
12115 mips_opts.ase_mips3d = 0;
12116 else if (strcmp (name, "mdmx") == 0)
12117 mips_opts.ase_mdmx = 1;
12118 else if (strcmp (name, "nomdmx") == 0)
12119 mips_opts.ase_mdmx = 0;
12120 else if (strncmp (name, "mips", 4) == 0)
12124 /* Permit the user to change the ISA on the fly. Needless to
12125 say, misuse can cause serious problems. */
12126 if (strcmp (name, "mips0") == 0)
12129 mips_opts.isa = file_mips_isa;
12131 else if (strcmp (name, "mips1") == 0)
12132 mips_opts.isa = ISA_MIPS1;
12133 else if (strcmp (name, "mips2") == 0)
12134 mips_opts.isa = ISA_MIPS2;
12135 else if (strcmp (name, "mips3") == 0)
12136 mips_opts.isa = ISA_MIPS3;
12137 else if (strcmp (name, "mips4") == 0)
12138 mips_opts.isa = ISA_MIPS4;
12139 else if (strcmp (name, "mips5") == 0)
12140 mips_opts.isa = ISA_MIPS5;
12141 else if (strcmp (name, "mips32") == 0)
12142 mips_opts.isa = ISA_MIPS32;
12143 else if (strcmp (name, "mips32r2") == 0)
12144 mips_opts.isa = ISA_MIPS32R2;
12145 else if (strcmp (name, "mips64") == 0)
12146 mips_opts.isa = ISA_MIPS64;
12148 as_bad (_("unknown ISA level %s"), name + 4);
12150 switch (mips_opts.isa)
12158 mips_opts.gp32 = 1;
12159 mips_opts.fp32 = 1;
12165 mips_opts.gp32 = 0;
12166 mips_opts.fp32 = 0;
12169 as_bad (_("unknown ISA level %s"), name + 4);
12174 mips_opts.gp32 = file_mips_gp32;
12175 mips_opts.fp32 = file_mips_fp32;
12178 else if (strcmp (name, "autoextend") == 0)
12179 mips_opts.noautoextend = 0;
12180 else if (strcmp (name, "noautoextend") == 0)
12181 mips_opts.noautoextend = 1;
12182 else if (strcmp (name, "push") == 0)
12184 struct mips_option_stack *s;
12186 s = (struct mips_option_stack *) xmalloc (sizeof *s);
12187 s->next = mips_opts_stack;
12188 s->options = mips_opts;
12189 mips_opts_stack = s;
12191 else if (strcmp (name, "pop") == 0)
12193 struct mips_option_stack *s;
12195 s = mips_opts_stack;
12197 as_bad (_(".set pop with no .set push"));
12200 /* If we're changing the reorder mode we need to handle
12201 delay slots correctly. */
12202 if (s->options.noreorder && ! mips_opts.noreorder)
12203 mips_emit_delays (TRUE);
12204 else if (! s->options.noreorder && mips_opts.noreorder)
12206 if (prev_nop_frag != NULL)
12208 prev_nop_frag->fr_fix -= (prev_nop_frag_holds
12209 * (mips_opts.mips16 ? 2 : 4));
12210 prev_nop_frag = NULL;
12214 mips_opts = s->options;
12215 mips_opts_stack = s->next;
12221 as_warn (_("Tried to set unrecognized symbol: %s\n"), name);
12223 *input_line_pointer = ch;
12224 demand_empty_rest_of_line ();
12227 /* Handle the .abicalls pseudo-op. I believe this is equivalent to
12228 .option pic2. It means to generate SVR4 PIC calls. */
12231 s_abicalls (ignore)
12232 int ignore ATTRIBUTE_UNUSED;
12234 mips_pic = SVR4_PIC;
12235 if (USE_GLOBAL_POINTER_OPT)
12237 if (g_switch_seen && g_switch_value != 0)
12238 as_warn (_("-G may not be used with SVR4 PIC code"));
12239 g_switch_value = 0;
12241 bfd_set_gp_size (stdoutput, 0);
12242 demand_empty_rest_of_line ();
12245 /* Handle the .cpload pseudo-op. This is used when generating SVR4
12246 PIC code. It sets the $gp register for the function based on the
12247 function address, which is in the register named in the argument.
12248 This uses a relocation against _gp_disp, which is handled specially
12249 by the linker. The result is:
12250 lui $gp,%hi(_gp_disp)
12251 addiu $gp,$gp,%lo(_gp_disp)
12252 addu $gp,$gp,.cpload argument
12253 The .cpload argument is normally $25 == $t9. */
12257 int ignore ATTRIBUTE_UNUSED;
12262 /* If we are not generating SVR4 PIC code, or if this is NewABI code,
12263 .cpload is ignored. */
12264 if (mips_pic != SVR4_PIC || HAVE_NEWABI)
12270 /* .cpload should be in a .set noreorder section. */
12271 if (mips_opts.noreorder == 0)
12272 as_warn (_(".cpload not in noreorder section"));
12274 ex.X_op = O_symbol;
12275 ex.X_add_symbol = symbol_find_or_make ("_gp_disp");
12276 ex.X_op_symbol = NULL;
12277 ex.X_add_number = 0;
12279 /* In ELF, this symbol is implicitly an STT_OBJECT symbol. */
12280 symbol_get_bfdsym (ex.X_add_symbol)->flags |= BSF_OBJECT;
12282 macro_build_lui (NULL, &icnt, &ex, mips_gp_register);
12283 macro_build ((char *) NULL, &icnt, &ex, "addiu", "t,r,j",
12284 mips_gp_register, mips_gp_register, (int) BFD_RELOC_LO16);
12286 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "addu", "d,v,t",
12287 mips_gp_register, mips_gp_register, tc_get_register (0));
12289 demand_empty_rest_of_line ();
12292 /* Handle the .cpsetup pseudo-op defined for NewABI PIC code. The syntax is:
12293 .cpsetup $reg1, offset|$reg2, label
12295 If offset is given, this results in:
12296 sd $gp, offset($sp)
12297 lui $gp, %hi(%neg(%gp_rel(label)))
12298 addiu $gp, $gp, %lo(%neg(%gp_rel(label)))
12299 daddu $gp, $gp, $reg1
12301 If $reg2 is given, this results in:
12302 daddu $reg2, $gp, $0
12303 lui $gp, %hi(%neg(%gp_rel(label)))
12304 addiu $gp, $gp, %lo(%neg(%gp_rel(label)))
12305 daddu $gp, $gp, $reg1
12306 $reg1 is normally $25 == $t9. */
12309 int ignore ATTRIBUTE_UNUSED;
12311 expressionS ex_off;
12312 expressionS ex_sym;
12317 /* If we are not generating SVR4 PIC code, .cpsetup is ignored.
12318 We also need NewABI support. */
12319 if (mips_pic != SVR4_PIC || ! HAVE_NEWABI)
12325 reg1 = tc_get_register (0);
12326 SKIP_WHITESPACE ();
12327 if (*input_line_pointer != ',')
12329 as_bad (_("missing argument separator ',' for .cpsetup"));
12333 ++input_line_pointer;
12334 SKIP_WHITESPACE ();
12335 if (*input_line_pointer == '$')
12337 mips_cpreturn_register = tc_get_register (0);
12338 mips_cpreturn_offset = -1;
12342 mips_cpreturn_offset = get_absolute_expression ();
12343 mips_cpreturn_register = -1;
12345 SKIP_WHITESPACE ();
12346 if (*input_line_pointer != ',')
12348 as_bad (_("missing argument separator ',' for .cpsetup"));
12352 ++input_line_pointer;
12353 SKIP_WHITESPACE ();
12354 expression (&ex_sym);
12356 if (mips_cpreturn_register == -1)
12358 ex_off.X_op = O_constant;
12359 ex_off.X_add_symbol = NULL;
12360 ex_off.X_op_symbol = NULL;
12361 ex_off.X_add_number = mips_cpreturn_offset;
12363 macro_build ((char *) NULL, &icnt, &ex_off, "sd", "t,o(b)",
12364 mips_gp_register, (int) BFD_RELOC_LO16, SP);
12367 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "daddu",
12368 "d,v,t", mips_cpreturn_register, mips_gp_register, 0);
12370 /* Ensure there's room for the next two instructions, so that `f'
12371 doesn't end up with an address in the wrong frag. */
12374 macro_build ((char *) NULL, &icnt, &ex_sym, "lui", "t,u", mips_gp_register,
12375 (int) BFD_RELOC_GPREL16);
12376 fix_new (frag_now, f - frag_now->fr_literal,
12377 0, NULL, 0, 0, BFD_RELOC_MIPS_SUB);
12378 fix_new (frag_now, f - frag_now->fr_literal,
12379 0, NULL, 0, 0, BFD_RELOC_HI16_S);
12382 macro_build ((char *) NULL, &icnt, &ex_sym, "addiu", "t,r,j",
12383 mips_gp_register, mips_gp_register, (int) BFD_RELOC_GPREL16);
12384 fix_new (frag_now, f - frag_now->fr_literal,
12385 0, NULL, 0, 0, BFD_RELOC_MIPS_SUB);
12386 fix_new (frag_now, f - frag_now->fr_literal,
12387 0, NULL, 0, 0, BFD_RELOC_LO16);
12389 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
12390 HAVE_64BIT_ADDRESSES ? "daddu" : "addu", "d,v,t",
12391 mips_gp_register, mips_gp_register, reg1);
12393 demand_empty_rest_of_line ();
12398 int ignore ATTRIBUTE_UNUSED;
12400 /* If we are not generating SVR4 PIC code, or if this is not NewABI code,
12401 .cplocal is ignored. */
12402 if (mips_pic != SVR4_PIC || ! HAVE_NEWABI)
12408 mips_gp_register = tc_get_register (0);
12409 demand_empty_rest_of_line ();
12412 /* Handle the .cprestore pseudo-op. This stores $gp into a given
12413 offset from $sp. The offset is remembered, and after making a PIC
12414 call $gp is restored from that location. */
12417 s_cprestore (ignore)
12418 int ignore ATTRIBUTE_UNUSED;
12423 /* If we are not generating SVR4 PIC code, or if this is NewABI code,
12424 .cprestore is ignored. */
12425 if (mips_pic != SVR4_PIC || HAVE_NEWABI)
12431 mips_cprestore_offset = get_absolute_expression ();
12432 mips_cprestore_valid = 1;
12434 ex.X_op = O_constant;
12435 ex.X_add_symbol = NULL;
12436 ex.X_op_symbol = NULL;
12437 ex.X_add_number = mips_cprestore_offset;
12439 macro_build_ldst_constoffset ((char *) NULL, &icnt, &ex,
12440 HAVE_32BIT_ADDRESSES ? "sw" : "sd",
12441 mips_gp_register, SP);
12443 demand_empty_rest_of_line ();
12446 /* Handle the .cpreturn pseudo-op defined for NewABI PIC code. If an offset
12447 was given in the preceeding .gpsetup, it results in:
12448 ld $gp, offset($sp)
12450 If a register $reg2 was given there, it results in:
12451 daddiu $gp, $gp, $reg2
12454 s_cpreturn (ignore)
12455 int ignore ATTRIBUTE_UNUSED;
12460 /* If we are not generating SVR4 PIC code, .cpreturn is ignored.
12461 We also need NewABI support. */
12462 if (mips_pic != SVR4_PIC || ! HAVE_NEWABI)
12468 if (mips_cpreturn_register == -1)
12470 ex.X_op = O_constant;
12471 ex.X_add_symbol = NULL;
12472 ex.X_op_symbol = NULL;
12473 ex.X_add_number = mips_cpreturn_offset;
12475 macro_build ((char *) NULL, &icnt, &ex, "ld", "t,o(b)",
12476 mips_gp_register, (int) BFD_RELOC_LO16, SP);
12479 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "daddu",
12480 "d,v,t", mips_gp_register, mips_cpreturn_register, 0);
12482 demand_empty_rest_of_line ();
12485 /* Handle the .gpvalue pseudo-op. This is used when generating NewABI PIC
12486 code. It sets the offset to use in gp_rel relocations. */
12490 int ignore ATTRIBUTE_UNUSED;
12492 /* If we are not generating SVR4 PIC code, .gpvalue is ignored.
12493 We also need NewABI support. */
12494 if (mips_pic != SVR4_PIC || ! HAVE_NEWABI)
12500 mips_gprel_offset = get_absolute_expression ();
12502 demand_empty_rest_of_line ();
12505 /* Handle the .gpword pseudo-op. This is used when generating PIC
12506 code. It generates a 32 bit GP relative reloc. */
12510 int ignore ATTRIBUTE_UNUSED;
12516 /* When not generating PIC code, this is treated as .word. */
12517 if (mips_pic != SVR4_PIC)
12523 label = insn_labels != NULL ? insn_labels->label : NULL;
12524 mips_emit_delays (TRUE);
12526 mips_align (2, 0, label);
12527 mips_clear_insn_labels ();
12531 if (ex.X_op != O_symbol || ex.X_add_number != 0)
12533 as_bad (_("Unsupported use of .gpword"));
12534 ignore_rest_of_line ();
12538 md_number_to_chars (p, (valueT) 0, 4);
12539 fix_new_exp (frag_now, p - frag_now->fr_literal, 4, &ex, FALSE,
12540 BFD_RELOC_GPREL32);
12542 demand_empty_rest_of_line ();
12547 int ignore ATTRIBUTE_UNUSED;
12553 /* When not generating PIC code, this is treated as .dword. */
12554 if (mips_pic != SVR4_PIC)
12560 label = insn_labels != NULL ? insn_labels->label : NULL;
12561 mips_emit_delays (TRUE);
12563 mips_align (3, 0, label);
12564 mips_clear_insn_labels ();
12568 if (ex.X_op != O_symbol || ex.X_add_number != 0)
12570 as_bad (_("Unsupported use of .gpdword"));
12571 ignore_rest_of_line ();
12575 md_number_to_chars (p, (valueT) 0, 8);
12576 fix_new_exp (frag_now, p - frag_now->fr_literal, 8, &ex, FALSE,
12577 BFD_RELOC_GPREL32);
12579 /* GPREL32 composed with 64 gives a 64-bit GP offset. */
12580 ex.X_op = O_absent;
12581 ex.X_add_symbol = 0;
12582 ex.X_add_number = 0;
12583 fix_new_exp (frag_now, p - frag_now->fr_literal, 8, &ex, FALSE,
12586 demand_empty_rest_of_line ();
12589 /* Handle the .cpadd pseudo-op. This is used when dealing with switch
12590 tables in SVR4 PIC code. */
12594 int ignore ATTRIBUTE_UNUSED;
12599 /* This is ignored when not generating SVR4 PIC code. */
12600 if (mips_pic != SVR4_PIC)
12606 /* Add $gp to the register named as an argument. */
12607 reg = tc_get_register (0);
12608 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
12609 HAVE_32BIT_ADDRESSES ? "addu" : "daddu",
12610 "d,v,t", reg, reg, mips_gp_register);
12612 demand_empty_rest_of_line ();
12615 /* Handle the .insn pseudo-op. This marks instruction labels in
12616 mips16 mode. This permits the linker to handle them specially,
12617 such as generating jalx instructions when needed. We also make
12618 them odd for the duration of the assembly, in order to generate the
12619 right sort of code. We will make them even in the adjust_symtab
12620 routine, while leaving them marked. This is convenient for the
12621 debugger and the disassembler. The linker knows to make them odd
12626 int ignore ATTRIBUTE_UNUSED;
12628 mips16_mark_labels ();
12630 demand_empty_rest_of_line ();
12633 /* Handle a .stabn directive. We need these in order to mark a label
12634 as being a mips16 text label correctly. Sometimes the compiler
12635 will emit a label, followed by a .stabn, and then switch sections.
12636 If the label and .stabn are in mips16 mode, then the label is
12637 really a mips16 text label. */
12644 mips16_mark_labels ();
12649 /* Handle the .weakext pseudo-op as defined in Kane and Heinrich.
12653 s_mips_weakext (ignore)
12654 int ignore ATTRIBUTE_UNUSED;
12661 name = input_line_pointer;
12662 c = get_symbol_end ();
12663 symbolP = symbol_find_or_make (name);
12664 S_SET_WEAK (symbolP);
12665 *input_line_pointer = c;
12667 SKIP_WHITESPACE ();
12669 if (! is_end_of_line[(unsigned char) *input_line_pointer])
12671 if (S_IS_DEFINED (symbolP))
12673 as_bad ("ignoring attempt to redefine symbol %s",
12674 S_GET_NAME (symbolP));
12675 ignore_rest_of_line ();
12679 if (*input_line_pointer == ',')
12681 ++input_line_pointer;
12682 SKIP_WHITESPACE ();
12686 if (exp.X_op != O_symbol)
12688 as_bad ("bad .weakext directive");
12689 ignore_rest_of_line ();
12692 symbol_set_value_expression (symbolP, &exp);
12695 demand_empty_rest_of_line ();
12698 /* Parse a register string into a number. Called from the ECOFF code
12699 to parse .frame. The argument is non-zero if this is the frame
12700 register, so that we can record it in mips_frame_reg. */
12703 tc_get_register (frame)
12708 SKIP_WHITESPACE ();
12709 if (*input_line_pointer++ != '$')
12711 as_warn (_("expected `$'"));
12714 else if (ISDIGIT (*input_line_pointer))
12716 reg = get_absolute_expression ();
12717 if (reg < 0 || reg >= 32)
12719 as_warn (_("Bad register number"));
12725 if (strncmp (input_line_pointer, "ra", 2) == 0)
12728 input_line_pointer += 2;
12730 else if (strncmp (input_line_pointer, "fp", 2) == 0)
12733 input_line_pointer += 2;
12735 else if (strncmp (input_line_pointer, "sp", 2) == 0)
12738 input_line_pointer += 2;
12740 else if (strncmp (input_line_pointer, "gp", 2) == 0)
12743 input_line_pointer += 2;
12745 else if (strncmp (input_line_pointer, "at", 2) == 0)
12748 input_line_pointer += 2;
12750 else if (strncmp (input_line_pointer, "kt0", 3) == 0)
12753 input_line_pointer += 3;
12755 else if (strncmp (input_line_pointer, "kt1", 3) == 0)
12758 input_line_pointer += 3;
12760 else if (strncmp (input_line_pointer, "zero", 4) == 0)
12763 input_line_pointer += 4;
12767 as_warn (_("Unrecognized register name"));
12769 while (ISALNUM(*input_line_pointer))
12770 input_line_pointer++;
12775 mips_frame_reg = reg != 0 ? reg : SP;
12776 mips_frame_reg_valid = 1;
12777 mips_cprestore_valid = 0;
12783 md_section_align (seg, addr)
12787 int align = bfd_get_section_alignment (stdoutput, seg);
12790 /* We don't need to align ELF sections to the full alignment.
12791 However, Irix 5 may prefer that we align them at least to a 16
12792 byte boundary. We don't bother to align the sections if we are
12793 targeted for an embedded system. */
12794 if (strcmp (TARGET_OS, "elf") == 0)
12800 return ((addr + (1 << align) - 1) & (-1 << align));
12803 /* Utility routine, called from above as well. If called while the
12804 input file is still being read, it's only an approximation. (For
12805 example, a symbol may later become defined which appeared to be
12806 undefined earlier.) */
12809 nopic_need_relax (sym, before_relaxing)
12811 int before_relaxing;
12816 if (USE_GLOBAL_POINTER_OPT && g_switch_value > 0)
12818 const char *symname;
12821 /* Find out whether this symbol can be referenced off the $gp
12822 register. It can be if it is smaller than the -G size or if
12823 it is in the .sdata or .sbss section. Certain symbols can
12824 not be referenced off the $gp, although it appears as though
12826 symname = S_GET_NAME (sym);
12827 if (symname != (const char *) NULL
12828 && (strcmp (symname, "eprol") == 0
12829 || strcmp (symname, "etext") == 0
12830 || strcmp (symname, "_gp") == 0
12831 || strcmp (symname, "edata") == 0
12832 || strcmp (symname, "_fbss") == 0
12833 || strcmp (symname, "_fdata") == 0
12834 || strcmp (symname, "_ftext") == 0
12835 || strcmp (symname, "end") == 0
12836 || strcmp (symname, "_gp_disp") == 0))
12838 else if ((! S_IS_DEFINED (sym) || S_IS_COMMON (sym))
12840 #ifndef NO_ECOFF_DEBUGGING
12841 || (symbol_get_obj (sym)->ecoff_extern_size != 0
12842 && (symbol_get_obj (sym)->ecoff_extern_size
12843 <= g_switch_value))
12845 /* We must defer this decision until after the whole
12846 file has been read, since there might be a .extern
12847 after the first use of this symbol. */
12848 || (before_relaxing
12849 #ifndef NO_ECOFF_DEBUGGING
12850 && symbol_get_obj (sym)->ecoff_extern_size == 0
12852 && S_GET_VALUE (sym) == 0)
12853 || (S_GET_VALUE (sym) != 0
12854 && S_GET_VALUE (sym) <= g_switch_value)))
12858 const char *segname;
12860 segname = segment_name (S_GET_SEGMENT (sym));
12861 assert (strcmp (segname, ".lit8") != 0
12862 && strcmp (segname, ".lit4") != 0);
12863 change = (strcmp (segname, ".sdata") != 0
12864 && strcmp (segname, ".sbss") != 0
12865 && strncmp (segname, ".sdata.", 7) != 0
12866 && strncmp (segname, ".gnu.linkonce.s.", 16) != 0);
12871 /* We are not optimizing for the $gp register. */
12875 /* Given a mips16 variant frag FRAGP, return non-zero if it needs an
12876 extended opcode. SEC is the section the frag is in. */
12879 mips16_extended_frag (fragp, sec, stretch)
12885 register const struct mips16_immed_operand *op;
12887 int mintiny, maxtiny;
12891 if (RELAX_MIPS16_USER_SMALL (fragp->fr_subtype))
12893 if (RELAX_MIPS16_USER_EXT (fragp->fr_subtype))
12896 type = RELAX_MIPS16_TYPE (fragp->fr_subtype);
12897 op = mips16_immed_operands;
12898 while (op->type != type)
12901 assert (op < mips16_immed_operands + MIPS16_NUM_IMMED);
12906 if (type == '<' || type == '>' || type == '[' || type == ']')
12909 maxtiny = 1 << op->nbits;
12914 maxtiny = (1 << op->nbits) - 1;
12919 mintiny = - (1 << (op->nbits - 1));
12920 maxtiny = (1 << (op->nbits - 1)) - 1;
12923 sym_frag = symbol_get_frag (fragp->fr_symbol);
12924 val = S_GET_VALUE (fragp->fr_symbol);
12925 symsec = S_GET_SEGMENT (fragp->fr_symbol);
12931 /* We won't have the section when we are called from
12932 mips_relax_frag. However, we will always have been called
12933 from md_estimate_size_before_relax first. If this is a
12934 branch to a different section, we mark it as such. If SEC is
12935 NULL, and the frag is not marked, then it must be a branch to
12936 the same section. */
12939 if (RELAX_MIPS16_LONG_BRANCH (fragp->fr_subtype))
12944 /* Must have been called from md_estimate_size_before_relax. */
12947 fragp->fr_subtype =
12948 RELAX_MIPS16_MARK_LONG_BRANCH (fragp->fr_subtype);
12950 /* FIXME: We should support this, and let the linker
12951 catch branches and loads that are out of range. */
12952 as_bad_where (fragp->fr_file, fragp->fr_line,
12953 _("unsupported PC relative reference to different section"));
12957 if (fragp != sym_frag && sym_frag->fr_address == 0)
12958 /* Assume non-extended on the first relaxation pass.
12959 The address we have calculated will be bogus if this is
12960 a forward branch to another frag, as the forward frag
12961 will have fr_address == 0. */
12965 /* In this case, we know for sure that the symbol fragment is in
12966 the same section. If the relax_marker of the symbol fragment
12967 differs from the relax_marker of this fragment, we have not
12968 yet adjusted the symbol fragment fr_address. We want to add
12969 in STRETCH in order to get a better estimate of the address.
12970 This particularly matters because of the shift bits. */
12972 && sym_frag->relax_marker != fragp->relax_marker)
12976 /* Adjust stretch for any alignment frag. Note that if have
12977 been expanding the earlier code, the symbol may be
12978 defined in what appears to be an earlier frag. FIXME:
12979 This doesn't handle the fr_subtype field, which specifies
12980 a maximum number of bytes to skip when doing an
12982 for (f = fragp; f != NULL && f != sym_frag; f = f->fr_next)
12984 if (f->fr_type == rs_align || f->fr_type == rs_align_code)
12987 stretch = - ((- stretch)
12988 & ~ ((1 << (int) f->fr_offset) - 1));
12990 stretch &= ~ ((1 << (int) f->fr_offset) - 1);
12999 addr = fragp->fr_address + fragp->fr_fix;
13001 /* The base address rules are complicated. The base address of
13002 a branch is the following instruction. The base address of a
13003 PC relative load or add is the instruction itself, but if it
13004 is in a delay slot (in which case it can not be extended) use
13005 the address of the instruction whose delay slot it is in. */
13006 if (type == 'p' || type == 'q')
13010 /* If we are currently assuming that this frag should be
13011 extended, then, the current address is two bytes
13013 if (RELAX_MIPS16_EXTENDED (fragp->fr_subtype))
13016 /* Ignore the low bit in the target, since it will be set
13017 for a text label. */
13018 if ((val & 1) != 0)
13021 else if (RELAX_MIPS16_JAL_DSLOT (fragp->fr_subtype))
13023 else if (RELAX_MIPS16_DSLOT (fragp->fr_subtype))
13026 val -= addr & ~ ((1 << op->shift) - 1);
13028 /* Branch offsets have an implicit 0 in the lowest bit. */
13029 if (type == 'p' || type == 'q')
13032 /* If any of the shifted bits are set, we must use an extended
13033 opcode. If the address depends on the size of this
13034 instruction, this can lead to a loop, so we arrange to always
13035 use an extended opcode. We only check this when we are in
13036 the main relaxation loop, when SEC is NULL. */
13037 if ((val & ((1 << op->shift) - 1)) != 0 && sec == NULL)
13039 fragp->fr_subtype =
13040 RELAX_MIPS16_MARK_LONG_BRANCH (fragp->fr_subtype);
13044 /* If we are about to mark a frag as extended because the value
13045 is precisely maxtiny + 1, then there is a chance of an
13046 infinite loop as in the following code:
13051 In this case when the la is extended, foo is 0x3fc bytes
13052 away, so the la can be shrunk, but then foo is 0x400 away, so
13053 the la must be extended. To avoid this loop, we mark the
13054 frag as extended if it was small, and is about to become
13055 extended with a value of maxtiny + 1. */
13056 if (val == ((maxtiny + 1) << op->shift)
13057 && ! RELAX_MIPS16_EXTENDED (fragp->fr_subtype)
13060 fragp->fr_subtype =
13061 RELAX_MIPS16_MARK_LONG_BRANCH (fragp->fr_subtype);
13065 else if (symsec != absolute_section && sec != NULL)
13066 as_bad_where (fragp->fr_file, fragp->fr_line, _("unsupported relocation"));
13068 if ((val & ((1 << op->shift) - 1)) != 0
13069 || val < (mintiny << op->shift)
13070 || val > (maxtiny << op->shift))
13076 /* Compute the length of a branch sequence, and adjust the
13077 RELAX_BRANCH_TOOFAR bit accordingly. If FRAGP is NULL, the
13078 worst-case length is computed, with UPDATE being used to indicate
13079 whether an unconditional (-1), branch-likely (+1) or regular (0)
13080 branch is to be computed. */
13082 relaxed_branch_length (fragp, sec, update)
13087 bfd_boolean toofar;
13091 && S_IS_DEFINED (fragp->fr_symbol)
13092 && sec == S_GET_SEGMENT (fragp->fr_symbol))
13097 val = S_GET_VALUE (fragp->fr_symbol) + fragp->fr_offset;
13099 addr = fragp->fr_address + fragp->fr_fix + 4;
13103 toofar = val < - (0x8000 << 2) || val >= (0x8000 << 2);
13106 /* If the symbol is not defined or it's in a different segment,
13107 assume the user knows what's going on and emit a short
13113 if (fragp && update && toofar != RELAX_BRANCH_TOOFAR (fragp->fr_subtype))
13115 = RELAX_BRANCH_ENCODE (RELAX_BRANCH_UNCOND (fragp->fr_subtype),
13116 RELAX_BRANCH_LIKELY (fragp->fr_subtype),
13117 RELAX_BRANCH_LINK (fragp->fr_subtype),
13123 if (fragp ? RELAX_BRANCH_LIKELY (fragp->fr_subtype) : (update > 0))
13126 if (mips_pic != NO_PIC)
13128 /* Additional space for PIC loading of target address. */
13130 if (mips_opts.isa == ISA_MIPS1)
13131 /* Additional space for $at-stabilizing nop. */
13135 /* If branch is conditional. */
13136 if (fragp ? !RELAX_BRANCH_UNCOND (fragp->fr_subtype) : (update >= 0))
13143 /* Estimate the size of a frag before relaxing. Unless this is the
13144 mips16, we are not really relaxing here, and the final size is
13145 encoded in the subtype information. For the mips16, we have to
13146 decide whether we are using an extended opcode or not. */
13149 md_estimate_size_before_relax (fragp, segtype)
13154 bfd_boolean linkonce = FALSE;
13156 if (RELAX_BRANCH_P (fragp->fr_subtype))
13159 fragp->fr_var = relaxed_branch_length (fragp, segtype, FALSE);
13161 return fragp->fr_var;
13164 if (RELAX_MIPS16_P (fragp->fr_subtype))
13165 /* We don't want to modify the EXTENDED bit here; it might get us
13166 into infinite loops. We change it only in mips_relax_frag(). */
13167 return (RELAX_MIPS16_EXTENDED (fragp->fr_subtype) ? 4 : 2);
13169 if (mips_pic == NO_PIC)
13171 change = nopic_need_relax (fragp->fr_symbol, 0);
13173 else if (mips_pic == SVR4_PIC)
13178 sym = fragp->fr_symbol;
13180 /* Handle the case of a symbol equated to another symbol. */
13181 while (symbol_equated_reloc_p (sym))
13185 /* It's possible to get a loop here in a badly written
13187 n = symbol_get_value_expression (sym)->X_add_symbol;
13193 symsec = S_GET_SEGMENT (sym);
13195 /* duplicate the test for LINK_ONCE sections as in adjust_reloc_syms */
13196 if (symsec != segtype && ! S_IS_LOCAL (sym))
13198 if ((bfd_get_section_flags (stdoutput, symsec) & SEC_LINK_ONCE)
13202 /* The GNU toolchain uses an extension for ELF: a section
13203 beginning with the magic string .gnu.linkonce is a linkonce
13205 if (strncmp (segment_name (symsec), ".gnu.linkonce",
13206 sizeof ".gnu.linkonce" - 1) == 0)
13210 /* This must duplicate the test in adjust_reloc_syms. */
13211 change = (symsec != &bfd_und_section
13212 && symsec != &bfd_abs_section
13213 && ! bfd_is_com_section (symsec)
13216 /* A global or weak symbol is treated as external. */
13217 && (OUTPUT_FLAVOR != bfd_target_elf_flavour
13218 || (! S_IS_WEAK (sym)
13219 && (! S_IS_EXTERNAL (sym)
13220 || mips_pic == EMBEDDED_PIC)))
13229 /* Record the offset to the first reloc in the fr_opcode field.
13230 This lets md_convert_frag and tc_gen_reloc know that the code
13231 must be expanded. */
13232 fragp->fr_opcode = (fragp->fr_literal
13234 - RELAX_OLD (fragp->fr_subtype)
13235 + RELAX_RELOC1 (fragp->fr_subtype));
13236 /* FIXME: This really needs as_warn_where. */
13237 if (RELAX_WARN (fragp->fr_subtype))
13238 as_warn (_("AT used after \".set noat\" or macro used after "
13239 "\".set nomacro\""));
13241 return RELAX_NEW (fragp->fr_subtype) - RELAX_OLD (fragp->fr_subtype);
13247 /* This is called to see whether a reloc against a defined symbol
13248 should be converted into a reloc against a section. Don't adjust
13249 MIPS16 jump relocations, so we don't have to worry about the format
13250 of the offset in the .o file. Don't adjust relocations against
13251 mips16 symbols, so that the linker can find them if it needs to set
13255 mips_fix_adjustable (fixp)
13258 if (fixp->fx_r_type == BFD_RELOC_MIPS16_JMP)
13261 if (fixp->fx_r_type == BFD_RELOC_VTABLE_INHERIT
13262 || fixp->fx_r_type == BFD_RELOC_VTABLE_ENTRY)
13265 if (fixp->fx_addsy == NULL)
13269 if (OUTPUT_FLAVOR == bfd_target_elf_flavour
13270 && S_GET_OTHER (fixp->fx_addsy) == STO_MIPS16
13271 && fixp->fx_subsy == NULL)
13278 /* Translate internal representation of relocation info to BFD target
13282 tc_gen_reloc (section, fixp)
13283 asection *section ATTRIBUTE_UNUSED;
13286 static arelent *retval[4];
13288 bfd_reloc_code_real_type code;
13290 reloc = retval[0] = (arelent *) xmalloc (sizeof (arelent));
13293 reloc->sym_ptr_ptr = (asymbol **) xmalloc (sizeof (asymbol *));
13294 *reloc->sym_ptr_ptr = symbol_get_bfdsym (fixp->fx_addsy);
13295 reloc->address = fixp->fx_frag->fr_address + fixp->fx_where;
13297 if (mips_pic == EMBEDDED_PIC
13298 && SWITCH_TABLE (fixp))
13300 /* For a switch table entry we use a special reloc. The addend
13301 is actually the difference between the reloc address and the
13303 reloc->addend = reloc->address - S_GET_VALUE (fixp->fx_subsy);
13304 if (OUTPUT_FLAVOR != bfd_target_ecoff_flavour)
13305 as_fatal (_("Double check fx_r_type in tc-mips.c:tc_gen_reloc"));
13306 fixp->fx_r_type = BFD_RELOC_GPREL32;
13308 else if (fixp->fx_r_type == BFD_RELOC_PCREL_LO16)
13310 if (OUTPUT_FLAVOR == bfd_target_elf_flavour)
13311 reloc->addend = fixp->fx_addnumber;
13314 /* We use a special addend for an internal RELLO reloc. */
13315 if (symbol_section_p (fixp->fx_addsy))
13316 reloc->addend = reloc->address - S_GET_VALUE (fixp->fx_subsy);
13318 reloc->addend = fixp->fx_addnumber + reloc->address;
13321 else if (fixp->fx_r_type == BFD_RELOC_PCREL_HI16_S)
13323 assert (fixp->fx_next != NULL
13324 && fixp->fx_next->fx_r_type == BFD_RELOC_PCREL_LO16);
13326 /* The reloc is relative to the RELLO; adjust the addend
13328 if (OUTPUT_FLAVOR == bfd_target_elf_flavour)
13329 reloc->addend = fixp->fx_next->fx_addnumber;
13332 /* We use a special addend for an internal RELHI reloc. */
13333 if (symbol_section_p (fixp->fx_addsy))
13334 reloc->addend = (fixp->fx_next->fx_frag->fr_address
13335 + fixp->fx_next->fx_where
13336 - S_GET_VALUE (fixp->fx_subsy));
13338 reloc->addend = (fixp->fx_addnumber
13339 + fixp->fx_next->fx_frag->fr_address
13340 + fixp->fx_next->fx_where);
13343 else if (fixp->fx_pcrel == 0 || OUTPUT_FLAVOR == bfd_target_elf_flavour)
13344 reloc->addend = fixp->fx_addnumber;
13347 if (OUTPUT_FLAVOR != bfd_target_aout_flavour)
13348 /* A gruesome hack which is a result of the gruesome gas reloc
13350 reloc->addend = reloc->address;
13352 reloc->addend = -reloc->address;
13355 /* If this is a variant frag, we may need to adjust the existing
13356 reloc and generate a new one. */
13357 if (fixp->fx_frag->fr_opcode != NULL
13358 && ((fixp->fx_r_type == BFD_RELOC_GPREL16
13360 || fixp->fx_r_type == BFD_RELOC_MIPS_GOT16
13361 || fixp->fx_r_type == BFD_RELOC_MIPS_CALL16
13362 || fixp->fx_r_type == BFD_RELOC_MIPS_GOT_HI16
13363 || fixp->fx_r_type == BFD_RELOC_MIPS_GOT_LO16
13364 || fixp->fx_r_type == BFD_RELOC_MIPS_CALL_HI16
13365 || fixp->fx_r_type == BFD_RELOC_MIPS_CALL_LO16)
13370 assert (! RELAX_MIPS16_P (fixp->fx_frag->fr_subtype));
13372 /* If this is not the last reloc in this frag, then we have two
13373 GPREL relocs, or a GOT_HI16/GOT_LO16 pair, or a
13374 CALL_HI16/CALL_LO16, both of which are being replaced. Let
13375 the second one handle all of them. */
13376 if (fixp->fx_next != NULL
13377 && fixp->fx_frag == fixp->fx_next->fx_frag)
13379 assert ((fixp->fx_r_type == BFD_RELOC_GPREL16
13380 && fixp->fx_next->fx_r_type == BFD_RELOC_GPREL16)
13381 || (fixp->fx_r_type == BFD_RELOC_MIPS_GOT_HI16
13382 && (fixp->fx_next->fx_r_type
13383 == BFD_RELOC_MIPS_GOT_LO16))
13384 || (fixp->fx_r_type == BFD_RELOC_MIPS_CALL_HI16
13385 && (fixp->fx_next->fx_r_type
13386 == BFD_RELOC_MIPS_CALL_LO16)));
13391 fixp->fx_where = fixp->fx_frag->fr_opcode - fixp->fx_frag->fr_literal;
13392 reloc->address = fixp->fx_frag->fr_address + fixp->fx_where;
13393 reloc2 = retval[1] = (arelent *) xmalloc (sizeof (arelent));
13395 reloc2->sym_ptr_ptr = (asymbol **) xmalloc (sizeof (asymbol *));
13396 *reloc2->sym_ptr_ptr = symbol_get_bfdsym (fixp->fx_addsy);
13397 reloc2->address = (reloc->address
13398 + (RELAX_RELOC2 (fixp->fx_frag->fr_subtype)
13399 - RELAX_RELOC1 (fixp->fx_frag->fr_subtype)));
13400 reloc2->addend = fixp->fx_addnumber;
13401 reloc2->howto = bfd_reloc_type_lookup (stdoutput, BFD_RELOC_LO16);
13402 assert (reloc2->howto != NULL);
13404 if (RELAX_RELOC3 (fixp->fx_frag->fr_subtype))
13408 reloc3 = retval[2] = (arelent *) xmalloc (sizeof (arelent));
13411 reloc3->address += 4;
13414 if (mips_pic == NO_PIC)
13416 assert (fixp->fx_r_type == BFD_RELOC_GPREL16);
13417 fixp->fx_r_type = BFD_RELOC_HI16_S;
13419 else if (mips_pic == SVR4_PIC)
13421 switch (fixp->fx_r_type)
13425 case BFD_RELOC_MIPS_GOT16:
13427 case BFD_RELOC_MIPS_GOT_LO16:
13428 case BFD_RELOC_MIPS_CALL_LO16:
13429 fixp->fx_r_type = BFD_RELOC_MIPS_GOT16;
13431 case BFD_RELOC_MIPS_CALL16:
13434 /* BFD_RELOC_MIPS_GOT16;*/
13435 fixp->fx_r_type = BFD_RELOC_MIPS_GOT_PAGE;
13436 reloc2->howto = bfd_reloc_type_lookup
13437 (stdoutput, BFD_RELOC_MIPS_GOT_OFST);
13440 fixp->fx_r_type = BFD_RELOC_MIPS_GOT16;
13447 /* newabi uses R_MIPS_GOT_DISP for local symbols */
13448 if (HAVE_NEWABI && fixp->fx_r_type == BFD_RELOC_MIPS_GOT_LO16)
13450 fixp->fx_r_type = BFD_RELOC_MIPS_GOT_DISP;
13455 /* Since the old MIPS ELF ABI uses Rel instead of Rela, encode the vtable
13456 entry to be used in the relocation's section offset. */
13457 if (! HAVE_NEWABI && fixp->fx_r_type == BFD_RELOC_VTABLE_ENTRY)
13459 reloc->address = reloc->addend;
13463 /* Since DIFF_EXPR_OK is defined in tc-mips.h, it is possible that
13464 fixup_segment converted a non-PC relative reloc into a PC
13465 relative reloc. In such a case, we need to convert the reloc
13467 code = fixp->fx_r_type;
13468 if (fixp->fx_pcrel)
13473 code = BFD_RELOC_8_PCREL;
13476 code = BFD_RELOC_16_PCREL;
13479 code = BFD_RELOC_32_PCREL;
13482 code = BFD_RELOC_64_PCREL;
13484 case BFD_RELOC_8_PCREL:
13485 case BFD_RELOC_16_PCREL:
13486 case BFD_RELOC_32_PCREL:
13487 case BFD_RELOC_64_PCREL:
13488 case BFD_RELOC_16_PCREL_S2:
13489 case BFD_RELOC_PCREL_HI16_S:
13490 case BFD_RELOC_PCREL_LO16:
13493 as_bad_where (fixp->fx_file, fixp->fx_line,
13494 _("Cannot make %s relocation PC relative"),
13495 bfd_get_reloc_code_name (code));
13500 /* md_apply_fix3 has a double-subtraction hack to get
13501 bfd_install_relocation to behave nicely. GPREL relocations are
13502 handled correctly without this hack, so undo it here. We can't
13503 stop md_apply_fix3 from subtracting twice in the first place since
13504 the fake addend is required for variant frags above. */
13505 if (fixp->fx_addsy != NULL && OUTPUT_FLAVOR == bfd_target_elf_flavour
13506 && (code == BFD_RELOC_GPREL16 || code == BFD_RELOC_MIPS16_GPREL)
13507 && reloc->addend != 0
13508 && mips_need_elf_addend_fixup (fixp))
13509 reloc->addend += S_GET_VALUE (fixp->fx_addsy);
13512 /* To support a PC relative reloc when generating embedded PIC code
13513 for ECOFF, we use a Cygnus extension. We check for that here to
13514 make sure that we don't let such a reloc escape normally. */
13515 if ((OUTPUT_FLAVOR == bfd_target_ecoff_flavour
13516 || OUTPUT_FLAVOR == bfd_target_elf_flavour)
13517 && code == BFD_RELOC_16_PCREL_S2
13518 && mips_pic != EMBEDDED_PIC)
13519 reloc->howto = NULL;
13521 reloc->howto = bfd_reloc_type_lookup (stdoutput, code);
13523 if (reloc->howto == NULL)
13525 as_bad_where (fixp->fx_file, fixp->fx_line,
13526 _("Can not represent %s relocation in this object file format"),
13527 bfd_get_reloc_code_name (code));
13534 /* Relax a machine dependent frag. This returns the amount by which
13535 the current size of the frag should change. */
13538 mips_relax_frag (sec, fragp, stretch)
13543 if (RELAX_BRANCH_P (fragp->fr_subtype))
13545 offsetT old_var = fragp->fr_var;
13547 fragp->fr_var = relaxed_branch_length (fragp, sec, TRUE);
13549 return fragp->fr_var - old_var;
13552 if (! RELAX_MIPS16_P (fragp->fr_subtype))
13555 if (mips16_extended_frag (fragp, NULL, stretch))
13557 if (RELAX_MIPS16_EXTENDED (fragp->fr_subtype))
13559 fragp->fr_subtype = RELAX_MIPS16_MARK_EXTENDED (fragp->fr_subtype);
13564 if (! RELAX_MIPS16_EXTENDED (fragp->fr_subtype))
13566 fragp->fr_subtype = RELAX_MIPS16_CLEAR_EXTENDED (fragp->fr_subtype);
13573 /* Convert a machine dependent frag. */
13576 md_convert_frag (abfd, asec, fragp)
13577 bfd *abfd ATTRIBUTE_UNUSED;
13584 if (RELAX_BRANCH_P (fragp->fr_subtype))
13587 unsigned long insn;
13591 buf = (bfd_byte *)fragp->fr_literal + fragp->fr_fix;
13593 if (target_big_endian)
13594 insn = bfd_getb32 (buf);
13596 insn = bfd_getl32 (buf);
13598 if (!RELAX_BRANCH_TOOFAR (fragp->fr_subtype))
13600 /* We generate a fixup instead of applying it right now
13601 because, if there are linker relaxations, we're going to
13602 need the relocations. */
13603 exp.X_op = O_symbol;
13604 exp.X_add_symbol = fragp->fr_symbol;
13605 exp.X_add_number = fragp->fr_offset;
13607 fixp = fix_new_exp (fragp, buf - (bfd_byte *)fragp->fr_literal,
13609 BFD_RELOC_16_PCREL_S2);
13610 fixp->fx_file = fragp->fr_file;
13611 fixp->fx_line = fragp->fr_line;
13613 md_number_to_chars ((char *)buf, insn, 4);
13620 as_warn_where (fragp->fr_file, fragp->fr_line,
13621 _("relaxed out-of-range branch into a jump"));
13623 if (RELAX_BRANCH_UNCOND (fragp->fr_subtype))
13626 if (!RELAX_BRANCH_LIKELY (fragp->fr_subtype))
13628 /* Reverse the branch. */
13629 switch ((insn >> 28) & 0xf)
13632 /* bc[0-3][tf]l? and bc1any[24][ft] instructions can
13633 have the condition reversed by tweaking a single
13634 bit, and their opcodes all have 0x4???????. */
13635 assert ((insn & 0xf1000000) == 0x41000000);
13636 insn ^= 0x00010000;
13640 /* bltz 0x04000000 bgez 0x04010000
13641 bltzal 0x04100000 bgezal 0x04110000 */
13642 assert ((insn & 0xfc0e0000) == 0x04000000);
13643 insn ^= 0x00010000;
13647 /* beq 0x10000000 bne 0x14000000
13648 blez 0x18000000 bgtz 0x1c000000 */
13649 insn ^= 0x04000000;
13657 if (RELAX_BRANCH_LINK (fragp->fr_subtype))
13659 /* Clear the and-link bit. */
13660 assert ((insn & 0xfc1c0000) == 0x04100000);
13662 /* bltzal 0x04100000 bgezal 0x04110000
13663 bltzall 0x04120000 bgezall 0x04130000 */
13664 insn &= ~0x00100000;
13667 /* Branch over the branch (if the branch was likely) or the
13668 full jump (not likely case). Compute the offset from the
13669 current instruction to branch to. */
13670 if (RELAX_BRANCH_LIKELY (fragp->fr_subtype))
13674 /* How many bytes in instructions we've already emitted? */
13675 i = buf - (bfd_byte *)fragp->fr_literal - fragp->fr_fix;
13676 /* How many bytes in instructions from here to the end? */
13677 i = fragp->fr_var - i;
13679 /* Convert to instruction count. */
13681 /* Branch counts from the next instruction. */
13684 /* Branch over the jump. */
13685 md_number_to_chars ((char *)buf, insn, 4);
13689 md_number_to_chars ((char*)buf, 0, 4);
13692 if (RELAX_BRANCH_LIKELY (fragp->fr_subtype))
13694 /* beql $0, $0, 2f */
13696 /* Compute the PC offset from the current instruction to
13697 the end of the variable frag. */
13698 /* How many bytes in instructions we've already emitted? */
13699 i = buf - (bfd_byte *)fragp->fr_literal - fragp->fr_fix;
13700 /* How many bytes in instructions from here to the end? */
13701 i = fragp->fr_var - i;
13702 /* Convert to instruction count. */
13704 /* Don't decrement i, because we want to branch over the
13708 md_number_to_chars ((char *)buf, insn, 4);
13711 md_number_to_chars ((char *)buf, 0, 4);
13716 if (mips_pic == NO_PIC)
13719 insn = (RELAX_BRANCH_LINK (fragp->fr_subtype)
13720 ? 0x0c000000 : 0x08000000);
13721 exp.X_op = O_symbol;
13722 exp.X_add_symbol = fragp->fr_symbol;
13723 exp.X_add_number = fragp->fr_offset;
13725 fixp = fix_new_exp (fragp, buf - (bfd_byte *)fragp->fr_literal,
13726 4, &exp, 0, BFD_RELOC_MIPS_JMP);
13727 fixp->fx_file = fragp->fr_file;
13728 fixp->fx_line = fragp->fr_line;
13730 md_number_to_chars ((char*)buf, insn, 4);
13735 /* lw/ld $at, <sym>($gp) R_MIPS_GOT16 */
13736 insn = HAVE_64BIT_ADDRESSES ? 0xdf810000 : 0x8f810000;
13737 exp.X_op = O_symbol;
13738 exp.X_add_symbol = fragp->fr_symbol;
13739 exp.X_add_number = fragp->fr_offset;
13741 if (fragp->fr_offset)
13743 exp.X_add_symbol = make_expr_symbol (&exp);
13744 exp.X_add_number = 0;
13747 fixp = fix_new_exp (fragp, buf - (bfd_byte *)fragp->fr_literal,
13748 4, &exp, 0, BFD_RELOC_MIPS_GOT16);
13749 fixp->fx_file = fragp->fr_file;
13750 fixp->fx_line = fragp->fr_line;
13752 md_number_to_chars ((char*)buf, insn, 4);
13755 if (mips_opts.isa == ISA_MIPS1)
13758 md_number_to_chars ((char*)buf, 0, 4);
13762 /* d/addiu $at, $at, <sym> R_MIPS_LO16 */
13763 insn = HAVE_64BIT_ADDRESSES ? 0x64210000 : 0x24210000;
13765 fixp = fix_new_exp (fragp, buf - (bfd_byte *)fragp->fr_literal,
13766 4, &exp, 0, BFD_RELOC_LO16);
13767 fixp->fx_file = fragp->fr_file;
13768 fixp->fx_line = fragp->fr_line;
13770 md_number_to_chars ((char*)buf, insn, 4);
13774 if (RELAX_BRANCH_LINK (fragp->fr_subtype))
13779 md_number_to_chars ((char*)buf, insn, 4);
13784 assert (buf == (bfd_byte *)fragp->fr_literal
13785 + fragp->fr_fix + fragp->fr_var);
13787 fragp->fr_fix += fragp->fr_var;
13792 if (RELAX_MIPS16_P (fragp->fr_subtype))
13795 register const struct mips16_immed_operand *op;
13796 bfd_boolean small, ext;
13799 unsigned long insn;
13800 bfd_boolean use_extend;
13801 unsigned short extend;
13803 type = RELAX_MIPS16_TYPE (fragp->fr_subtype);
13804 op = mips16_immed_operands;
13805 while (op->type != type)
13808 if (RELAX_MIPS16_EXTENDED (fragp->fr_subtype))
13819 resolve_symbol_value (fragp->fr_symbol);
13820 val = S_GET_VALUE (fragp->fr_symbol);
13825 addr = fragp->fr_address + fragp->fr_fix;
13827 /* The rules for the base address of a PC relative reloc are
13828 complicated; see mips16_extended_frag. */
13829 if (type == 'p' || type == 'q')
13834 /* Ignore the low bit in the target, since it will be
13835 set for a text label. */
13836 if ((val & 1) != 0)
13839 else if (RELAX_MIPS16_JAL_DSLOT (fragp->fr_subtype))
13841 else if (RELAX_MIPS16_DSLOT (fragp->fr_subtype))
13844 addr &= ~ (addressT) ((1 << op->shift) - 1);
13847 /* Make sure the section winds up with the alignment we have
13850 record_alignment (asec, op->shift);
13854 && (RELAX_MIPS16_JAL_DSLOT (fragp->fr_subtype)
13855 || RELAX_MIPS16_DSLOT (fragp->fr_subtype)))
13856 as_warn_where (fragp->fr_file, fragp->fr_line,
13857 _("extended instruction in delay slot"));
13859 buf = (bfd_byte *) (fragp->fr_literal + fragp->fr_fix);
13861 if (target_big_endian)
13862 insn = bfd_getb16 (buf);
13864 insn = bfd_getl16 (buf);
13866 mips16_immed (fragp->fr_file, fragp->fr_line, type, val,
13867 RELAX_MIPS16_USER_EXT (fragp->fr_subtype),
13868 small, ext, &insn, &use_extend, &extend);
13872 md_number_to_chars ((char *) buf, 0xf000 | extend, 2);
13873 fragp->fr_fix += 2;
13877 md_number_to_chars ((char *) buf, insn, 2);
13878 fragp->fr_fix += 2;
13883 if (fragp->fr_opcode == NULL)
13886 old = RELAX_OLD (fragp->fr_subtype);
13887 new = RELAX_NEW (fragp->fr_subtype);
13888 fixptr = fragp->fr_literal + fragp->fr_fix;
13891 memcpy (fixptr - old, fixptr, new);
13893 fragp->fr_fix += new - old;
13899 /* This function is called after the relocs have been generated.
13900 We've been storing mips16 text labels as odd. Here we convert them
13901 back to even for the convenience of the debugger. */
13904 mips_frob_file_after_relocs ()
13907 unsigned int count, i;
13909 if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
13912 syms = bfd_get_outsymbols (stdoutput);
13913 count = bfd_get_symcount (stdoutput);
13914 for (i = 0; i < count; i++, syms++)
13916 if (elf_symbol (*syms)->internal_elf_sym.st_other == STO_MIPS16
13917 && ((*syms)->value & 1) != 0)
13919 (*syms)->value &= ~1;
13920 /* If the symbol has an odd size, it was probably computed
13921 incorrectly, so adjust that as well. */
13922 if ((elf_symbol (*syms)->internal_elf_sym.st_size & 1) != 0)
13923 ++elf_symbol (*syms)->internal_elf_sym.st_size;
13930 /* This function is called whenever a label is defined. It is used
13931 when handling branch delays; if a branch has a label, we assume we
13932 can not move it. */
13935 mips_define_label (sym)
13938 struct insn_label_list *l;
13940 if (free_insn_labels == NULL)
13941 l = (struct insn_label_list *) xmalloc (sizeof *l);
13944 l = free_insn_labels;
13945 free_insn_labels = l->next;
13949 l->next = insn_labels;
13953 #if defined (OBJ_ELF) || defined (OBJ_MAYBE_ELF)
13955 /* Some special processing for a MIPS ELF file. */
13958 mips_elf_final_processing ()
13960 /* Write out the register information. */
13961 if (mips_abi != N64_ABI)
13965 s.ri_gprmask = mips_gprmask;
13966 s.ri_cprmask[0] = mips_cprmask[0];
13967 s.ri_cprmask[1] = mips_cprmask[1];
13968 s.ri_cprmask[2] = mips_cprmask[2];
13969 s.ri_cprmask[3] = mips_cprmask[3];
13970 /* The gp_value field is set by the MIPS ELF backend. */
13972 bfd_mips_elf32_swap_reginfo_out (stdoutput, &s,
13973 ((Elf32_External_RegInfo *)
13974 mips_regmask_frag));
13978 Elf64_Internal_RegInfo s;
13980 s.ri_gprmask = mips_gprmask;
13982 s.ri_cprmask[0] = mips_cprmask[0];
13983 s.ri_cprmask[1] = mips_cprmask[1];
13984 s.ri_cprmask[2] = mips_cprmask[2];
13985 s.ri_cprmask[3] = mips_cprmask[3];
13986 /* The gp_value field is set by the MIPS ELF backend. */
13988 bfd_mips_elf64_swap_reginfo_out (stdoutput, &s,
13989 ((Elf64_External_RegInfo *)
13990 mips_regmask_frag));
13993 /* Set the MIPS ELF flag bits. FIXME: There should probably be some
13994 sort of BFD interface for this. */
13995 if (mips_any_noreorder)
13996 elf_elfheader (stdoutput)->e_flags |= EF_MIPS_NOREORDER;
13997 if (mips_pic != NO_PIC)
13998 elf_elfheader (stdoutput)->e_flags |= EF_MIPS_PIC;
14000 /* Set MIPS ELF flags for ASEs. */
14001 if (file_ase_mips16)
14002 elf_elfheader (stdoutput)->e_flags |= EF_MIPS_ARCH_ASE_M16;
14003 #if 0 /* XXX FIXME */
14004 if (file_ase_mips3d)
14005 elf_elfheader (stdoutput)->e_flags |= ???;
14008 elf_elfheader (stdoutput)->e_flags |= EF_MIPS_ARCH_ASE_MDMX;
14010 /* Set the MIPS ELF ABI flags. */
14011 if (mips_abi == O32_ABI && USE_E_MIPS_ABI_O32)
14012 elf_elfheader (stdoutput)->e_flags |= E_MIPS_ABI_O32;
14013 else if (mips_abi == O64_ABI)
14014 elf_elfheader (stdoutput)->e_flags |= E_MIPS_ABI_O64;
14015 else if (mips_abi == EABI_ABI)
14017 if (!file_mips_gp32)
14018 elf_elfheader (stdoutput)->e_flags |= E_MIPS_ABI_EABI64;
14020 elf_elfheader (stdoutput)->e_flags |= E_MIPS_ABI_EABI32;
14022 else if (mips_abi == N32_ABI)
14023 elf_elfheader (stdoutput)->e_flags |= EF_MIPS_ABI2;
14025 /* Nothing to do for N64_ABI. */
14027 if (mips_32bitmode)
14028 elf_elfheader (stdoutput)->e_flags |= EF_MIPS_32BITMODE;
14031 #endif /* OBJ_ELF || OBJ_MAYBE_ELF */
14033 typedef struct proc {
14035 unsigned long reg_mask;
14036 unsigned long reg_offset;
14037 unsigned long fpreg_mask;
14038 unsigned long fpreg_offset;
14039 unsigned long frame_offset;
14040 unsigned long frame_reg;
14041 unsigned long pc_reg;
14044 static procS cur_proc;
14045 static procS *cur_proc_ptr;
14046 static int numprocs;
14048 /* Fill in an rs_align_code fragment. */
14051 mips_handle_align (fragp)
14054 if (fragp->fr_type != rs_align_code)
14057 if (mips_opts.mips16)
14059 static const unsigned char be_nop[] = { 0x65, 0x00 };
14060 static const unsigned char le_nop[] = { 0x00, 0x65 };
14065 bytes = fragp->fr_next->fr_address - fragp->fr_address - fragp->fr_fix;
14066 p = fragp->fr_literal + fragp->fr_fix;
14074 memcpy (p, (target_big_endian ? be_nop : le_nop), 2);
14078 /* For mips32, a nop is a zero, which we trivially get by doing nothing. */
14089 /* check for premature end, nesting errors, etc */
14091 as_warn (_("missing .end at end of assembly"));
14100 if (*input_line_pointer == '-')
14102 ++input_line_pointer;
14105 if (!ISDIGIT (*input_line_pointer))
14106 as_bad (_("expected simple number"));
14107 if (input_line_pointer[0] == '0')
14109 if (input_line_pointer[1] == 'x')
14111 input_line_pointer += 2;
14112 while (ISXDIGIT (*input_line_pointer))
14115 val |= hex_value (*input_line_pointer++);
14117 return negative ? -val : val;
14121 ++input_line_pointer;
14122 while (ISDIGIT (*input_line_pointer))
14125 val |= *input_line_pointer++ - '0';
14127 return negative ? -val : val;
14130 if (!ISDIGIT (*input_line_pointer))
14132 printf (_(" *input_line_pointer == '%c' 0x%02x\n"),
14133 *input_line_pointer, *input_line_pointer);
14134 as_warn (_("invalid number"));
14137 while (ISDIGIT (*input_line_pointer))
14140 val += *input_line_pointer++ - '0';
14142 return negative ? -val : val;
14145 /* The .file directive; just like the usual .file directive, but there
14146 is an initial number which is the ECOFF file index. In the non-ECOFF
14147 case .file implies DWARF-2. */
14151 int x ATTRIBUTE_UNUSED;
14153 static int first_file_directive = 0;
14155 if (ECOFF_DEBUGGING)
14164 filename = dwarf2_directive_file (0);
14166 /* Versions of GCC up to 3.1 start files with a ".file"
14167 directive even for stabs output. Make sure that this
14168 ".file" is handled. Note that you need a version of GCC
14169 after 3.1 in order to support DWARF-2 on MIPS. */
14170 if (filename != NULL && ! first_file_directive)
14172 (void) new_logical_line (filename, -1);
14173 s_app_file_string (filename);
14175 first_file_directive = 1;
14179 /* The .loc directive, implying DWARF-2. */
14183 int x ATTRIBUTE_UNUSED;
14185 if (!ECOFF_DEBUGGING)
14186 dwarf2_directive_loc (0);
14189 /* The .end directive. */
14193 int x ATTRIBUTE_UNUSED;
14198 /* Following functions need their own .frame and .cprestore directives. */
14199 mips_frame_reg_valid = 0;
14200 mips_cprestore_valid = 0;
14202 if (!is_end_of_line[(unsigned char) *input_line_pointer])
14205 demand_empty_rest_of_line ();
14210 #ifdef BFD_ASSEMBLER
14211 if ((bfd_get_section_flags (stdoutput, now_seg) & SEC_CODE) != 0)
14216 if (now_seg != data_section && now_seg != bss_section)
14223 as_warn (_(".end not in text section"));
14227 as_warn (_(".end directive without a preceding .ent directive."));
14228 demand_empty_rest_of_line ();
14234 assert (S_GET_NAME (p));
14235 if (strcmp (S_GET_NAME (p), S_GET_NAME (cur_proc_ptr->isym)))
14236 as_warn (_(".end symbol does not match .ent symbol."));
14238 if (debug_type == DEBUG_STABS)
14239 stabs_generate_asm_endfunc (S_GET_NAME (p),
14243 as_warn (_(".end directive missing or unknown symbol"));
14246 /* Generate a .pdr section. */
14247 if (OUTPUT_FLAVOR == bfd_target_elf_flavour && ! ECOFF_DEBUGGING)
14249 segT saved_seg = now_seg;
14250 subsegT saved_subseg = now_subseg;
14255 dot = frag_now_fix ();
14257 #ifdef md_flush_pending_output
14258 md_flush_pending_output ();
14262 subseg_set (pdr_seg, 0);
14264 /* Write the symbol. */
14265 exp.X_op = O_symbol;
14266 exp.X_add_symbol = p;
14267 exp.X_add_number = 0;
14268 emit_expr (&exp, 4);
14270 fragp = frag_more (7 * 4);
14272 md_number_to_chars (fragp, (valueT) cur_proc_ptr->reg_mask, 4);
14273 md_number_to_chars (fragp + 4, (valueT) cur_proc_ptr->reg_offset, 4);
14274 md_number_to_chars (fragp + 8, (valueT) cur_proc_ptr->fpreg_mask, 4);
14275 md_number_to_chars (fragp + 12, (valueT) cur_proc_ptr->fpreg_offset, 4);
14276 md_number_to_chars (fragp + 16, (valueT) cur_proc_ptr->frame_offset, 4);
14277 md_number_to_chars (fragp + 20, (valueT) cur_proc_ptr->frame_reg, 4);
14278 md_number_to_chars (fragp + 24, (valueT) cur_proc_ptr->pc_reg, 4);
14280 subseg_set (saved_seg, saved_subseg);
14282 #endif /* OBJ_ELF */
14284 cur_proc_ptr = NULL;
14287 /* The .aent and .ent directives. */
14296 symbolP = get_symbol ();
14297 if (*input_line_pointer == ',')
14298 ++input_line_pointer;
14299 SKIP_WHITESPACE ();
14300 if (ISDIGIT (*input_line_pointer)
14301 || *input_line_pointer == '-')
14304 #ifdef BFD_ASSEMBLER
14305 if ((bfd_get_section_flags (stdoutput, now_seg) & SEC_CODE) != 0)
14310 if (now_seg != data_section && now_seg != bss_section)
14317 as_warn (_(".ent or .aent not in text section."));
14319 if (!aent && cur_proc_ptr)
14320 as_warn (_("missing .end"));
14324 /* This function needs its own .frame and .cprestore directives. */
14325 mips_frame_reg_valid = 0;
14326 mips_cprestore_valid = 0;
14328 cur_proc_ptr = &cur_proc;
14329 memset (cur_proc_ptr, '\0', sizeof (procS));
14331 cur_proc_ptr->isym = symbolP;
14333 symbol_get_bfdsym (symbolP)->flags |= BSF_FUNCTION;
14337 if (debug_type == DEBUG_STABS)
14338 stabs_generate_asm_func (S_GET_NAME (symbolP),
14339 S_GET_NAME (symbolP));
14342 demand_empty_rest_of_line ();
14345 /* The .frame directive. If the mdebug section is present (IRIX 5 native)
14346 then ecoff.c (ecoff_directive_frame) is used. For embedded targets,
14347 s_mips_frame is used so that we can set the PDR information correctly.
14348 We can't use the ecoff routines because they make reference to the ecoff
14349 symbol table (in the mdebug section). */
14352 s_mips_frame (ignore)
14353 int ignore ATTRIBUTE_UNUSED;
14356 if (OUTPUT_FLAVOR == bfd_target_elf_flavour && ! ECOFF_DEBUGGING)
14360 if (cur_proc_ptr == (procS *) NULL)
14362 as_warn (_(".frame outside of .ent"));
14363 demand_empty_rest_of_line ();
14367 cur_proc_ptr->frame_reg = tc_get_register (1);
14369 SKIP_WHITESPACE ();
14370 if (*input_line_pointer++ != ','
14371 || get_absolute_expression_and_terminator (&val) != ',')
14373 as_warn (_("Bad .frame directive"));
14374 --input_line_pointer;
14375 demand_empty_rest_of_line ();
14379 cur_proc_ptr->frame_offset = val;
14380 cur_proc_ptr->pc_reg = tc_get_register (0);
14382 demand_empty_rest_of_line ();
14385 #endif /* OBJ_ELF */
14389 /* The .fmask and .mask directives. If the mdebug section is present
14390 (IRIX 5 native) then ecoff.c (ecoff_directive_mask) is used. For
14391 embedded targets, s_mips_mask is used so that we can set the PDR
14392 information correctly. We can't use the ecoff routines because they
14393 make reference to the ecoff symbol table (in the mdebug section). */
14396 s_mips_mask (reg_type)
14400 if (OUTPUT_FLAVOR == bfd_target_elf_flavour && ! ECOFF_DEBUGGING)
14404 if (cur_proc_ptr == (procS *) NULL)
14406 as_warn (_(".mask/.fmask outside of .ent"));
14407 demand_empty_rest_of_line ();
14411 if (get_absolute_expression_and_terminator (&mask) != ',')
14413 as_warn (_("Bad .mask/.fmask directive"));
14414 --input_line_pointer;
14415 demand_empty_rest_of_line ();
14419 off = get_absolute_expression ();
14421 if (reg_type == 'F')
14423 cur_proc_ptr->fpreg_mask = mask;
14424 cur_proc_ptr->fpreg_offset = off;
14428 cur_proc_ptr->reg_mask = mask;
14429 cur_proc_ptr->reg_offset = off;
14432 demand_empty_rest_of_line ();
14435 #endif /* OBJ_ELF */
14436 s_ignore (reg_type);
14439 /* The .loc directive. */
14450 assert (now_seg == text_section);
14452 lineno = get_number ();
14453 addroff = frag_now_fix ();
14455 symbolP = symbol_new ("", N_SLINE, addroff, frag_now);
14456 S_SET_TYPE (symbolP, N_SLINE);
14457 S_SET_OTHER (symbolP, 0);
14458 S_SET_DESC (symbolP, lineno);
14459 symbolP->sy_segment = now_seg;
14463 /* A table describing all the processors gas knows about. Names are
14464 matched in the order listed.
14466 To ease comparison, please keep this table in the same order as
14467 gcc's mips_cpu_info_table[]. */
14468 static const struct mips_cpu_info mips_cpu_info_table[] =
14470 /* Entries for generic ISAs */
14471 { "mips1", 1, ISA_MIPS1, CPU_R3000 },
14472 { "mips2", 1, ISA_MIPS2, CPU_R6000 },
14473 { "mips3", 1, ISA_MIPS3, CPU_R4000 },
14474 { "mips4", 1, ISA_MIPS4, CPU_R8000 },
14475 { "mips5", 1, ISA_MIPS5, CPU_MIPS5 },
14476 { "mips32", 1, ISA_MIPS32, CPU_MIPS32 },
14477 { "mips32r2", 1, ISA_MIPS32R2, CPU_MIPS32R2 },
14478 { "mips64", 1, ISA_MIPS64, CPU_MIPS64 },
14481 { "r3000", 0, ISA_MIPS1, CPU_R3000 },
14482 { "r2000", 0, ISA_MIPS1, CPU_R3000 },
14483 { "r3900", 0, ISA_MIPS1, CPU_R3900 },
14486 { "r6000", 0, ISA_MIPS2, CPU_R6000 },
14489 { "r4000", 0, ISA_MIPS3, CPU_R4000 },
14490 { "r4010", 0, ISA_MIPS2, CPU_R4010 },
14491 { "vr4100", 0, ISA_MIPS3, CPU_VR4100 },
14492 { "vr4111", 0, ISA_MIPS3, CPU_R4111 },
14493 { "vr4120", 0, ISA_MIPS3, CPU_VR4120 },
14494 { "vr4130", 0, ISA_MIPS3, CPU_VR4120 },
14495 { "vr4181", 0, ISA_MIPS3, CPU_R4111 },
14496 { "vr4300", 0, ISA_MIPS3, CPU_R4300 },
14497 { "r4400", 0, ISA_MIPS3, CPU_R4400 },
14498 { "r4600", 0, ISA_MIPS3, CPU_R4600 },
14499 { "orion", 0, ISA_MIPS3, CPU_R4600 },
14500 { "r4650", 0, ISA_MIPS3, CPU_R4650 },
14503 { "r8000", 0, ISA_MIPS4, CPU_R8000 },
14504 { "r10000", 0, ISA_MIPS4, CPU_R10000 },
14505 { "r12000", 0, ISA_MIPS4, CPU_R12000 },
14506 { "vr5000", 0, ISA_MIPS4, CPU_R5000 },
14507 { "vr5400", 0, ISA_MIPS4, CPU_VR5400 },
14508 { "vr5500", 0, ISA_MIPS4, CPU_VR5500 },
14509 { "rm5200", 0, ISA_MIPS4, CPU_R5000 },
14510 { "rm5230", 0, ISA_MIPS4, CPU_R5000 },
14511 { "rm5231", 0, ISA_MIPS4, CPU_R5000 },
14512 { "rm5261", 0, ISA_MIPS4, CPU_R5000 },
14513 { "rm5721", 0, ISA_MIPS4, CPU_R5000 },
14514 { "r7000", 0, ISA_MIPS4, CPU_R5000 },
14517 { "4kc", 0, ISA_MIPS32, CPU_MIPS32, },
14518 { "4km", 0, ISA_MIPS32, CPU_MIPS32 },
14519 { "4kp", 0, ISA_MIPS32, CPU_MIPS32 },
14522 { "5kc", 0, ISA_MIPS64, CPU_MIPS64 },
14523 { "20kc", 0, ISA_MIPS64, CPU_MIPS64 },
14525 /* Broadcom SB-1 CPU core */
14526 { "sb1", 0, ISA_MIPS64, CPU_SB1 },
14533 /* Return true if GIVEN is the same as CANONICAL, or if it is CANONICAL
14534 with a final "000" replaced by "k". Ignore case.
14536 Note: this function is shared between GCC and GAS. */
14539 mips_strict_matching_cpu_name_p (canonical, given)
14540 const char *canonical, *given;
14542 while (*given != 0 && TOLOWER (*given) == TOLOWER (*canonical))
14543 given++, canonical++;
14545 return ((*given == 0 && *canonical == 0)
14546 || (strcmp (canonical, "000") == 0 && strcasecmp (given, "k") == 0));
14550 /* Return true if GIVEN matches CANONICAL, where GIVEN is a user-supplied
14551 CPU name. We've traditionally allowed a lot of variation here.
14553 Note: this function is shared between GCC and GAS. */
14556 mips_matching_cpu_name_p (canonical, given)
14557 const char *canonical, *given;
14559 /* First see if the name matches exactly, or with a final "000"
14560 turned into "k". */
14561 if (mips_strict_matching_cpu_name_p (canonical, given))
14564 /* If not, try comparing based on numerical designation alone.
14565 See if GIVEN is an unadorned number, or 'r' followed by a number. */
14566 if (TOLOWER (*given) == 'r')
14568 if (!ISDIGIT (*given))
14571 /* Skip over some well-known prefixes in the canonical name,
14572 hoping to find a number there too. */
14573 if (TOLOWER (canonical[0]) == 'v' && TOLOWER (canonical[1]) == 'r')
14575 else if (TOLOWER (canonical[0]) == 'r' && TOLOWER (canonical[1]) == 'm')
14577 else if (TOLOWER (canonical[0]) == 'r')
14580 return mips_strict_matching_cpu_name_p (canonical, given);
14584 /* Parse an option that takes the name of a processor as its argument.
14585 OPTION is the name of the option and CPU_STRING is the argument.
14586 Return the corresponding processor enumeration if the CPU_STRING is
14587 recognized, otherwise report an error and return null.
14589 A similar function exists in GCC. */
14591 static const struct mips_cpu_info *
14592 mips_parse_cpu (option, cpu_string)
14593 const char *option, *cpu_string;
14595 const struct mips_cpu_info *p;
14597 /* 'from-abi' selects the most compatible architecture for the given
14598 ABI: MIPS I for 32-bit ABIs and MIPS III for 64-bit ABIs. For the
14599 EABIs, we have to decide whether we're using the 32-bit or 64-bit
14600 version. Look first at the -mgp options, if given, otherwise base
14601 the choice on MIPS_DEFAULT_64BIT.
14603 Treat NO_ABI like the EABIs. One reason to do this is that the
14604 plain 'mips' and 'mips64' configs have 'from-abi' as their default
14605 architecture. This code picks MIPS I for 'mips' and MIPS III for
14606 'mips64', just as we did in the days before 'from-abi'. */
14607 if (strcasecmp (cpu_string, "from-abi") == 0)
14609 if (ABI_NEEDS_32BIT_REGS (mips_abi))
14610 return mips_cpu_info_from_isa (ISA_MIPS1);
14612 if (ABI_NEEDS_64BIT_REGS (mips_abi))
14613 return mips_cpu_info_from_isa (ISA_MIPS3);
14615 if (file_mips_gp32 >= 0)
14616 return mips_cpu_info_from_isa (file_mips_gp32 ? ISA_MIPS1 : ISA_MIPS3);
14618 return mips_cpu_info_from_isa (MIPS_DEFAULT_64BIT
14623 /* 'default' has traditionally been a no-op. Probably not very useful. */
14624 if (strcasecmp (cpu_string, "default") == 0)
14627 for (p = mips_cpu_info_table; p->name != 0; p++)
14628 if (mips_matching_cpu_name_p (p->name, cpu_string))
14631 as_bad ("Bad value (%s) for %s", cpu_string, option);
14635 /* Return the canonical processor information for ISA (a member of the
14636 ISA_MIPS* enumeration). */
14638 static const struct mips_cpu_info *
14639 mips_cpu_info_from_isa (isa)
14644 for (i = 0; mips_cpu_info_table[i].name != NULL; i++)
14645 if (mips_cpu_info_table[i].is_isa
14646 && isa == mips_cpu_info_table[i].isa)
14647 return (&mips_cpu_info_table[i]);
14653 show (stream, string, col_p, first_p)
14655 const char *string;
14661 fprintf (stream, "%24s", "");
14666 fprintf (stream, ", ");
14670 if (*col_p + strlen (string) > 72)
14672 fprintf (stream, "\n%24s", "");
14676 fprintf (stream, "%s", string);
14677 *col_p += strlen (string);
14683 md_show_usage (stream)
14689 fprintf (stream, _("\
14691 -membedded-pic generate embedded position independent code\n\
14692 -EB generate big endian output\n\
14693 -EL generate little endian output\n\
14694 -g, -g2 do not remove unneeded NOPs or swap branches\n\
14695 -G NUM allow referencing objects up to NUM bytes\n\
14696 implicitly with the gp register [default 8]\n"));
14697 fprintf (stream, _("\
14698 -mips1 generate MIPS ISA I instructions\n\
14699 -mips2 generate MIPS ISA II instructions\n\
14700 -mips3 generate MIPS ISA III instructions\n\
14701 -mips4 generate MIPS ISA IV instructions\n\
14702 -mips5 generate MIPS ISA V instructions\n\
14703 -mips32 generate MIPS32 ISA instructions\n\
14704 -mips32r2 generate MIPS32 release 2 ISA instructions\n\
14705 -mips64 generate MIPS64 ISA instructions\n\
14706 -march=CPU/-mtune=CPU generate code/schedule for CPU, where CPU is one of:\n"));
14710 for (i = 0; mips_cpu_info_table[i].name != NULL; i++)
14711 show (stream, mips_cpu_info_table[i].name, &column, &first);
14712 show (stream, "from-abi", &column, &first);
14713 fputc ('\n', stream);
14715 fprintf (stream, _("\
14716 -mCPU equivalent to -march=CPU -mtune=CPU. Deprecated.\n\
14717 -no-mCPU don't generate code specific to CPU.\n\
14718 For -mCPU and -no-mCPU, CPU must be one of:\n"));
14722 show (stream, "3900", &column, &first);
14723 show (stream, "4010", &column, &first);
14724 show (stream, "4100", &column, &first);
14725 show (stream, "4650", &column, &first);
14726 fputc ('\n', stream);
14728 fprintf (stream, _("\
14729 -mips16 generate mips16 instructions\n\
14730 -no-mips16 do not generate mips16 instructions\n"));
14731 fprintf (stream, _("\
14732 -mgp32 use 32-bit GPRs, regardless of the chosen ISA\n\
14733 -mfp32 use 32-bit FPRs, regardless of the chosen ISA\n\
14734 -O0 remove unneeded NOPs, do not swap branches\n\
14735 -O remove unneeded NOPs and swap branches\n\
14736 -n warn about NOPs generated from macros\n\
14737 --[no-]construct-floats [dis]allow floating point values to be constructed\n\
14738 --trap, --no-break trap exception on div by 0 and mult overflow\n\
14739 --break, --no-trap break exception on div by 0 and mult overflow\n"));
14741 fprintf (stream, _("\
14742 -KPIC, -call_shared generate SVR4 position independent code\n\
14743 -non_shared do not generate position independent code\n\
14744 -xgot assume a 32 bit GOT\n\
14745 -mabi=ABI create ABI conformant object file for:\n"));
14749 show (stream, "32", &column, &first);
14750 show (stream, "o64", &column, &first);
14751 show (stream, "n32", &column, &first);
14752 show (stream, "64", &column, &first);
14753 show (stream, "eabi", &column, &first);
14755 fputc ('\n', stream);
14757 fprintf (stream, _("\
14758 -32 create o32 ABI object file (default)\n\
14759 -n32 create n32 ABI object file\n\
14760 -64 create 64 ABI object file\n"));
14765 mips_dwarf2_format ()
14767 if (mips_abi == N64_ABI)
14768 return dwarf2_format_64bit_irix;
14770 return dwarf2_format_32bit;