1 /* tc-mips.c -- assemble code for a MIPS chip.
2 Copyright 1993, 1994, 1995, 1996, 1997, 1998, 1999, 2000, 2001, 2002, 2003
3 Free Software Foundation, Inc.
4 Contributed by the OSF and Ralph Campbell.
5 Written by Keith Knowles and Ralph Campbell, working independently.
6 Modified for ECOFF and R4000 support by Ian Lance Taylor of Cygnus
9 This file is part of GAS.
11 GAS is free software; you can redistribute it and/or modify
12 it under the terms of the GNU General Public License as published by
13 the Free Software Foundation; either version 2, or (at your option)
16 GAS is distributed in the hope that it will be useful,
17 but WITHOUT ANY WARRANTY; without even the implied warranty of
18 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
19 GNU General Public License for more details.
21 You should have received a copy of the GNU General Public License
22 along with GAS; see the file COPYING. If not, write to the Free
23 Software Foundation, 59 Temple Place - Suite 330, Boston, MA
29 #include "safe-ctype.h"
38 #include "opcode/mips.h"
40 #include "dwarf2dbg.h"
43 #define DBG(x) printf x
49 /* Clean up namespace so we can include obj-elf.h too. */
50 static int mips_output_flavor PARAMS ((void));
51 static int mips_output_flavor () { return OUTPUT_FLAVOR; }
52 #undef OBJ_PROCESS_STAB
59 #undef obj_frob_file_after_relocs
60 #undef obj_frob_symbol
62 #undef obj_sec_sym_ok_for_reloc
63 #undef OBJ_COPY_SYMBOL_ATTRIBUTES
66 /* Fix any of them that we actually care about. */
68 #define OUTPUT_FLAVOR mips_output_flavor()
75 #ifndef ECOFF_DEBUGGING
76 #define NO_ECOFF_DEBUGGING
77 #define ECOFF_DEBUGGING 0
80 int mips_flag_mdebug = -1;
84 #if defined (OBJ_ELF) || defined (OBJ_MAYBE_ELF)
85 static char *mips_regmask_frag;
91 #define PIC_CALL_REG 25
99 #define ILLEGAL_REG (32)
101 /* Allow override of standard little-endian ECOFF format. */
103 #ifndef ECOFF_LITTLE_FORMAT
104 #define ECOFF_LITTLE_FORMAT "ecoff-littlemips"
107 extern int target_big_endian;
109 /* The name of the readonly data section. */
110 #define RDATA_SECTION_NAME (OUTPUT_FLAVOR == bfd_target_aout_flavour \
112 : OUTPUT_FLAVOR == bfd_target_ecoff_flavour \
114 : OUTPUT_FLAVOR == bfd_target_coff_flavour \
116 : OUTPUT_FLAVOR == bfd_target_elf_flavour \
120 /* The ABI to use. */
131 /* MIPS ABI we are using for this output file. */
132 static enum mips_abi_level mips_abi = NO_ABI;
134 /* Whether or not we have code that can call pic code. */
135 int mips_abicalls = FALSE;
137 /* This is the set of options which may be modified by the .set
138 pseudo-op. We use a struct so that .set push and .set pop are more
141 struct mips_set_options
143 /* MIPS ISA (Instruction Set Architecture) level. This is set to -1
144 if it has not been initialized. Changed by `.set mipsN', and the
145 -mipsN command line option, and the default CPU. */
147 /* Enabled Application Specific Extensions (ASEs). These are set to -1
148 if they have not been initialized. Changed by `.set <asename>', by
149 command line options, and based on the default architecture. */
152 /* Whether we are assembling for the mips16 processor. 0 if we are
153 not, 1 if we are, and -1 if the value has not been initialized.
154 Changed by `.set mips16' and `.set nomips16', and the -mips16 and
155 -nomips16 command line options, and the default CPU. */
157 /* Non-zero if we should not reorder instructions. Changed by `.set
158 reorder' and `.set noreorder'. */
160 /* Non-zero if we should not permit the $at ($1) register to be used
161 in instructions. Changed by `.set at' and `.set noat'. */
163 /* Non-zero if we should warn when a macro instruction expands into
164 more than one machine instruction. Changed by `.set nomacro' and
166 int warn_about_macros;
167 /* Non-zero if we should not move instructions. Changed by `.set
168 move', `.set volatile', `.set nomove', and `.set novolatile'. */
170 /* Non-zero if we should not optimize branches by moving the target
171 of the branch into the delay slot. Actually, we don't perform
172 this optimization anyhow. Changed by `.set bopt' and `.set
175 /* Non-zero if we should not autoextend mips16 instructions.
176 Changed by `.set autoextend' and `.set noautoextend'. */
178 /* Restrict general purpose registers and floating point registers
179 to 32 bit. This is initially determined when -mgp32 or -mfp32
180 is passed but can changed if the assembler code uses .set mipsN. */
185 /* True if -mgp32 was passed. */
186 static int file_mips_gp32 = -1;
188 /* True if -mfp32 was passed. */
189 static int file_mips_fp32 = -1;
191 /* This is the struct we use to hold the current set of options. Note
192 that we must set the isa field to ISA_UNKNOWN and the ASE fields to
193 -1 to indicate that they have not been initialized. */
195 static struct mips_set_options mips_opts =
197 ISA_UNKNOWN, -1, -1, -1, 0, 0, 0, 0, 0, 0, 0, 0
200 /* These variables are filled in with the masks of registers used.
201 The object format code reads them and puts them in the appropriate
203 unsigned long mips_gprmask;
204 unsigned long mips_cprmask[4];
206 /* MIPS ISA we are using for this output file. */
207 static int file_mips_isa = ISA_UNKNOWN;
209 /* True if -mips16 was passed or implied by arguments passed on the
210 command line (e.g., by -march). */
211 static int file_ase_mips16;
213 /* True if -mips3d was passed or implied by arguments passed on the
214 command line (e.g., by -march). */
215 static int file_ase_mips3d;
217 /* True if -mdmx was passed or implied by arguments passed on the
218 command line (e.g., by -march). */
219 static int file_ase_mdmx;
221 /* The argument of the -march= flag. The architecture we are assembling. */
222 static int mips_arch = CPU_UNKNOWN;
223 static const char *mips_arch_string;
224 static const struct mips_cpu_info *mips_arch_info;
226 /* The argument of the -mtune= flag. The architecture for which we
228 static int mips_tune = CPU_UNKNOWN;
229 static const char *mips_tune_string;
230 static const struct mips_cpu_info *mips_tune_info;
232 /* True when generating 32-bit code for a 64-bit processor. */
233 static int mips_32bitmode = 0;
235 /* Some ISA's have delay slots for instructions which read or write
236 from a coprocessor (eg. mips1-mips3); some don't (eg mips4).
237 Return true if instructions marked INSN_LOAD_COPROC_DELAY,
238 INSN_COPROC_MOVE_DELAY, or INSN_WRITE_COND_CODE actually have a
239 delay slot in this ISA. The uses of this macro assume that any
240 ISA that has delay slots for one of these, has them for all. They
241 also assume that ISAs which don't have delays for these insns, don't
242 have delays for the INSN_LOAD_MEMORY_DELAY instructions either. */
243 #define ISA_HAS_COPROC_DELAYS(ISA) ( \
245 || (ISA) == ISA_MIPS2 \
246 || (ISA) == ISA_MIPS3 \
249 /* True if the given ABI requires 32-bit registers. */
250 #define ABI_NEEDS_32BIT_REGS(ABI) ((ABI) == O32_ABI)
252 /* Likewise 64-bit registers. */
253 #define ABI_NEEDS_64BIT_REGS(ABI) \
255 || (ABI) == N64_ABI \
258 /* Return true if ISA supports 64 bit gp register instructions. */
259 #define ISA_HAS_64BIT_REGS(ISA) ( \
261 || (ISA) == ISA_MIPS4 \
262 || (ISA) == ISA_MIPS5 \
263 || (ISA) == ISA_MIPS64 \
266 /* Return true if ISA supports 64-bit right rotate (dror et al.)
268 #define ISA_HAS_DROR(ISA) ( \
272 /* Return true if ISA supports 32-bit right rotate (ror et al.)
274 #define ISA_HAS_ROR(ISA) ( \
275 (ISA) == ISA_MIPS32R2 \
278 #define HAVE_32BIT_GPRS \
279 (mips_opts.gp32 || ! ISA_HAS_64BIT_REGS (mips_opts.isa))
281 #define HAVE_32BIT_FPRS \
282 (mips_opts.fp32 || ! ISA_HAS_64BIT_REGS (mips_opts.isa))
284 #define HAVE_64BIT_GPRS (! HAVE_32BIT_GPRS)
285 #define HAVE_64BIT_FPRS (! HAVE_32BIT_FPRS)
287 #define HAVE_NEWABI (mips_abi == N32_ABI || mips_abi == N64_ABI)
289 #define HAVE_64BIT_OBJECTS (mips_abi == N64_ABI)
291 /* We can only have 64bit addresses if the object file format
293 #define HAVE_32BIT_ADDRESSES \
295 || ((bfd_arch_bits_per_address (stdoutput) == 32 \
296 || ! HAVE_64BIT_OBJECTS) \
297 && mips_pic != EMBEDDED_PIC))
299 #define HAVE_64BIT_ADDRESSES (! HAVE_32BIT_ADDRESSES)
300 #define HAVE_64BIT_ADDRESS_CONSTANTS (HAVE_64BIT_ADDRESSES \
303 /* Addresses are loaded in different ways, depending on the address size
304 in use. The n32 ABI Documentation also mandates the use of additions
305 with overflow checking, but existing implementations don't follow it. */
306 #define ADDRESS_ADD_INSN \
307 (HAVE_32BIT_ADDRESSES ? "addu" : "daddu")
309 #define ADDRESS_ADDI_INSN \
310 (HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu")
312 #define ADDRESS_LOAD_INSN \
313 (HAVE_32BIT_ADDRESSES ? "lw" : "ld")
315 #define ADDRESS_STORE_INSN \
316 (HAVE_32BIT_ADDRESSES ? "sw" : "sd")
318 /* Return true if the given CPU supports the MIPS16 ASE. */
319 #define CPU_HAS_MIPS16(cpu) \
320 (strncmp (TARGET_CPU, "mips16", sizeof ("mips16") - 1) == 0 \
321 || strncmp (TARGET_CANONICAL, "mips-lsi-elf", sizeof ("mips-lsi-elf") - 1) == 0)
323 /* Return true if the given CPU supports the MIPS3D ASE. */
324 #define CPU_HAS_MIPS3D(cpu) ((cpu) == CPU_SB1 \
327 /* Return true if the given CPU supports the MDMX ASE. */
328 #define CPU_HAS_MDMX(cpu) (FALSE \
331 /* True if CPU has a dror instruction. */
332 #define CPU_HAS_DROR(CPU) ((CPU) == CPU_VR5400 || (CPU) == CPU_VR5500)
334 /* True if CPU has a ror instruction. */
335 #define CPU_HAS_ROR(CPU) CPU_HAS_DROR (CPU)
337 /* Whether the processor uses hardware interlocks to protect
338 reads from the HI and LO registers, and thus does not
339 require nops to be inserted. */
341 #define hilo_interlocks (mips_arch == CPU_R4010 \
342 || mips_arch == CPU_VR5500 \
343 || mips_arch == CPU_SB1 \
346 /* Whether the processor uses hardware interlocks to protect reads
347 from the GPRs, and thus does not require nops to be inserted. */
348 #define gpr_interlocks \
349 (mips_opts.isa != ISA_MIPS1 \
350 || mips_arch == CPU_VR5400 \
351 || mips_arch == CPU_VR5500 \
352 || mips_arch == CPU_R3900)
354 /* As with other "interlocks" this is used by hardware that has FP
355 (co-processor) interlocks. */
356 /* Itbl support may require additional care here. */
357 #define cop_interlocks (mips_arch == CPU_R4300 \
358 || mips_arch == CPU_VR5400 \
359 || mips_arch == CPU_VR5500 \
360 || mips_arch == CPU_SB1 \
363 /* Is this a mfhi or mflo instruction? */
364 #define MF_HILO_INSN(PINFO) \
365 ((PINFO & INSN_READ_HI) || (PINFO & INSN_READ_LO))
367 /* MIPS PIC level. */
369 enum mips_pic_level mips_pic;
371 /* Warn about all NOPS that the assembler generates. */
372 static int warn_nops = 0;
374 /* 1 if we should generate 32 bit offsets from the $gp register in
375 SVR4_PIC mode. Currently has no meaning in other modes. */
376 static int mips_big_got = 0;
378 /* 1 if trap instructions should used for overflow rather than break
380 static int mips_trap = 0;
382 /* 1 if double width floating point constants should not be constructed
383 by assembling two single width halves into two single width floating
384 point registers which just happen to alias the double width destination
385 register. On some architectures this aliasing can be disabled by a bit
386 in the status register, and the setting of this bit cannot be determined
387 automatically at assemble time. */
388 static int mips_disable_float_construction;
390 /* Non-zero if any .set noreorder directives were used. */
392 static int mips_any_noreorder;
394 /* Non-zero if nops should be inserted when the register referenced in
395 an mfhi/mflo instruction is read in the next two instructions. */
396 static int mips_7000_hilo_fix;
398 /* The size of the small data section. */
399 static unsigned int g_switch_value = 8;
400 /* Whether the -G option was used. */
401 static int g_switch_seen = 0;
406 /* If we can determine in advance that GP optimization won't be
407 possible, we can skip the relaxation stuff that tries to produce
408 GP-relative references. This makes delay slot optimization work
411 This function can only provide a guess, but it seems to work for
412 gcc output. It needs to guess right for gcc, otherwise gcc
413 will put what it thinks is a GP-relative instruction in a branch
416 I don't know if a fix is needed for the SVR4_PIC mode. I've only
417 fixed it for the non-PIC mode. KR 95/04/07 */
418 static int nopic_need_relax PARAMS ((symbolS *, int));
420 /* handle of the OPCODE hash table */
421 static struct hash_control *op_hash = NULL;
423 /* The opcode hash table we use for the mips16. */
424 static struct hash_control *mips16_op_hash = NULL;
426 /* This array holds the chars that always start a comment. If the
427 pre-processor is disabled, these aren't very useful */
428 const char comment_chars[] = "#";
430 /* This array holds the chars that only start a comment at the beginning of
431 a line. If the line seems to have the form '# 123 filename'
432 .line and .file directives will appear in the pre-processed output */
433 /* Note that input_file.c hand checks for '#' at the beginning of the
434 first line of the input file. This is because the compiler outputs
435 #NO_APP at the beginning of its output. */
436 /* Also note that C style comments are always supported. */
437 const char line_comment_chars[] = "#";
439 /* This array holds machine specific line separator characters. */
440 const char line_separator_chars[] = ";";
442 /* Chars that can be used to separate mant from exp in floating point nums */
443 const char EXP_CHARS[] = "eE";
445 /* Chars that mean this number is a floating point constant */
448 const char FLT_CHARS[] = "rRsSfFdDxXpP";
450 /* Also be aware that MAXIMUM_NUMBER_OF_CHARS_FOR_FLOAT may have to be
451 changed in read.c . Ideally it shouldn't have to know about it at all,
452 but nothing is ideal around here.
455 static char *insn_error;
457 static int auto_align = 1;
459 /* When outputting SVR4 PIC code, the assembler needs to know the
460 offset in the stack frame from which to restore the $gp register.
461 This is set by the .cprestore pseudo-op, and saved in this
463 static offsetT mips_cprestore_offset = -1;
465 /* Similiar for NewABI PIC code, where $gp is callee-saved. NewABI has some
466 more optimizations, it can use a register value instead of a memory-saved
467 offset and even an other register than $gp as global pointer. */
468 static offsetT mips_cpreturn_offset = -1;
469 static int mips_cpreturn_register = -1;
470 static int mips_gp_register = GP;
471 static int mips_gprel_offset = 0;
473 /* Whether mips_cprestore_offset has been set in the current function
474 (or whether it has already been warned about, if not). */
475 static int mips_cprestore_valid = 0;
477 /* This is the register which holds the stack frame, as set by the
478 .frame pseudo-op. This is needed to implement .cprestore. */
479 static int mips_frame_reg = SP;
481 /* Whether mips_frame_reg has been set in the current function
482 (or whether it has already been warned about, if not). */
483 static int mips_frame_reg_valid = 0;
485 /* To output NOP instructions correctly, we need to keep information
486 about the previous two instructions. */
488 /* Whether we are optimizing. The default value of 2 means to remove
489 unneeded NOPs and swap branch instructions when possible. A value
490 of 1 means to not swap branches. A value of 0 means to always
492 static int mips_optimize = 2;
494 /* Debugging level. -g sets this to 2. -gN sets this to N. -g0 is
495 equivalent to seeing no -g option at all. */
496 static int mips_debug = 0;
498 /* The previous instruction. */
499 static struct mips_cl_insn prev_insn;
501 /* The instruction before prev_insn. */
502 static struct mips_cl_insn prev_prev_insn;
504 /* If we don't want information for prev_insn or prev_prev_insn, we
505 point the insn_mo field at this dummy integer. */
506 static const struct mips_opcode dummy_opcode = { NULL, NULL, 0, 0, 0, 0 };
508 /* Non-zero if prev_insn is valid. */
509 static int prev_insn_valid;
511 /* The frag for the previous instruction. */
512 static struct frag *prev_insn_frag;
514 /* The offset into prev_insn_frag for the previous instruction. */
515 static long prev_insn_where;
517 /* The reloc type for the previous instruction, if any. */
518 static bfd_reloc_code_real_type prev_insn_reloc_type[3];
520 /* The reloc for the previous instruction, if any. */
521 static fixS *prev_insn_fixp[3];
523 /* Non-zero if the previous instruction was in a delay slot. */
524 static int prev_insn_is_delay_slot;
526 /* Non-zero if the previous instruction was in a .set noreorder. */
527 static int prev_insn_unreordered;
529 /* Non-zero if the previous instruction uses an extend opcode (if
531 static int prev_insn_extended;
533 /* Non-zero if the previous previous instruction was in a .set
535 static int prev_prev_insn_unreordered;
537 /* If this is set, it points to a frag holding nop instructions which
538 were inserted before the start of a noreorder section. If those
539 nops turn out to be unnecessary, the size of the frag can be
541 static fragS *prev_nop_frag;
543 /* The number of nop instructions we created in prev_nop_frag. */
544 static int prev_nop_frag_holds;
546 /* The number of nop instructions that we know we need in
548 static int prev_nop_frag_required;
550 /* The number of instructions we've seen since prev_nop_frag. */
551 static int prev_nop_frag_since;
553 /* For ECOFF and ELF, relocations against symbols are done in two
554 parts, with a HI relocation and a LO relocation. Each relocation
555 has only 16 bits of space to store an addend. This means that in
556 order for the linker to handle carries correctly, it must be able
557 to locate both the HI and the LO relocation. This means that the
558 relocations must appear in order in the relocation table.
560 In order to implement this, we keep track of each unmatched HI
561 relocation. We then sort them so that they immediately precede the
562 corresponding LO relocation. */
567 struct mips_hi_fixup *next;
570 /* The section this fixup is in. */
574 /* The list of unmatched HI relocs. */
576 static struct mips_hi_fixup *mips_hi_fixup_list;
578 /* The frag containing the last explicit relocation operator.
579 Null if explicit relocations have not been used. */
581 static fragS *prev_reloc_op_frag;
583 /* Map normal MIPS register numbers to mips16 register numbers. */
585 #define X ILLEGAL_REG
586 static const int mips32_to_16_reg_map[] =
588 X, X, 2, 3, 4, 5, 6, 7,
589 X, X, X, X, X, X, X, X,
590 0, 1, X, X, X, X, X, X,
591 X, X, X, X, X, X, X, X
595 /* Map mips16 register numbers to normal MIPS register numbers. */
597 static const unsigned int mips16_to_32_reg_map[] =
599 16, 17, 2, 3, 4, 5, 6, 7
602 static int mips_fix_4122_bugs;
604 /* We don't relax branches by default, since this causes us to expand
605 `la .l2 - .l1' if there's a branch between .l1 and .l2, because we
606 fail to compute the offset before expanding the macro to the most
607 efficient expansion. */
609 static int mips_relax_branch;
611 /* Since the MIPS does not have multiple forms of PC relative
612 instructions, we do not have to do relaxing as is done on other
613 platforms. However, we do have to handle GP relative addressing
614 correctly, which turns out to be a similar problem.
616 Every macro that refers to a symbol can occur in (at least) two
617 forms, one with GP relative addressing and one without. For
618 example, loading a global variable into a register generally uses
619 a macro instruction like this:
621 If i can be addressed off the GP register (this is true if it is in
622 the .sbss or .sdata section, or if it is known to be smaller than
623 the -G argument) this will generate the following instruction:
625 This instruction will use a GPREL reloc. If i can not be addressed
626 off the GP register, the following instruction sequence will be used:
629 In this case the first instruction will have a HI16 reloc, and the
630 second reloc will have a LO16 reloc. Both relocs will be against
633 The issue here is that we may not know whether i is GP addressable
634 until after we see the instruction that uses it. Therefore, we
635 want to be able to choose the final instruction sequence only at
636 the end of the assembly. This is similar to the way other
637 platforms choose the size of a PC relative instruction only at the
640 When generating position independent code we do not use GP
641 addressing in quite the same way, but the issue still arises as
642 external symbols and local symbols must be handled differently.
644 We handle these issues by actually generating both possible
645 instruction sequences. The longer one is put in a frag_var with
646 type rs_machine_dependent. We encode what to do with the frag in
647 the subtype field. We encode (1) the number of existing bytes to
648 replace, (2) the number of new bytes to use, (3) the offset from
649 the start of the existing bytes to the first reloc we must generate
650 (that is, the offset is applied from the start of the existing
651 bytes after they are replaced by the new bytes, if any), (4) the
652 offset from the start of the existing bytes to the second reloc,
653 (5) whether a third reloc is needed (the third reloc is always four
654 bytes after the second reloc), and (6) whether to warn if this
655 variant is used (this is sometimes needed if .set nomacro or .set
656 noat is in effect). All these numbers are reasonably small.
658 Generating two instruction sequences must be handled carefully to
659 ensure that delay slots are handled correctly. Fortunately, there
660 are a limited number of cases. When the second instruction
661 sequence is generated, append_insn is directed to maintain the
662 existing delay slot information, so it continues to apply to any
663 code after the second instruction sequence. This means that the
664 second instruction sequence must not impose any requirements not
665 required by the first instruction sequence.
667 These variant frags are then handled in functions called by the
668 machine independent code. md_estimate_size_before_relax returns
669 the final size of the frag. md_convert_frag sets up the final form
670 of the frag. tc_gen_reloc adjust the first reloc and adds a second
672 #define RELAX_ENCODE(old, new, reloc1, reloc2, reloc3, warn) \
676 | (((reloc1) + 64) << 9) \
677 | (((reloc2) + 64) << 2) \
678 | ((reloc3) ? (1 << 1) : 0) \
680 #define RELAX_OLD(i) (((i) >> 23) & 0x7f)
681 #define RELAX_NEW(i) (((i) >> 16) & 0x7f)
682 #define RELAX_RELOC1(i) ((valueT) (((i) >> 9) & 0x7f) - 64)
683 #define RELAX_RELOC2(i) ((valueT) (((i) >> 2) & 0x7f) - 64)
684 #define RELAX_RELOC3(i) (((i) >> 1) & 1)
685 #define RELAX_WARN(i) ((i) & 1)
687 /* Branch without likely bit. If label is out of range, we turn:
689 beq reg1, reg2, label
699 with the following opcode replacements:
706 bltzal <-> bgezal (with jal label instead of j label)
708 Even though keeping the delay slot instruction in the delay slot of
709 the branch would be more efficient, it would be very tricky to do
710 correctly, because we'd have to introduce a variable frag *after*
711 the delay slot instruction, and expand that instead. Let's do it
712 the easy way for now, even if the branch-not-taken case now costs
713 one additional instruction. Out-of-range branches are not supposed
714 to be common, anyway.
716 Branch likely. If label is out of range, we turn:
718 beql reg1, reg2, label
719 delay slot (annulled if branch not taken)
728 delay slot (executed only if branch taken)
731 It would be possible to generate a shorter sequence by losing the
732 likely bit, generating something like:
737 delay slot (executed only if branch taken)
749 bltzall -> bgezal (with jal label instead of j label)
750 bgezall -> bltzal (ditto)
753 but it's not clear that it would actually improve performance. */
754 #define RELAX_BRANCH_ENCODE(uncond, likely, link, toofar) \
757 | ((toofar) ? 1 : 0) \
759 | ((likely) ? 4 : 0) \
760 | ((uncond) ? 8 : 0)))
761 #define RELAX_BRANCH_P(i) (((i) & 0xf0000000) == 0xc0000000)
762 #define RELAX_BRANCH_UNCOND(i) (((i) & 8) != 0)
763 #define RELAX_BRANCH_LIKELY(i) (((i) & 4) != 0)
764 #define RELAX_BRANCH_LINK(i) (((i) & 2) != 0)
765 #define RELAX_BRANCH_TOOFAR(i) (((i) & 1) != 0)
767 /* For mips16 code, we use an entirely different form of relaxation.
768 mips16 supports two versions of most instructions which take
769 immediate values: a small one which takes some small value, and a
770 larger one which takes a 16 bit value. Since branches also follow
771 this pattern, relaxing these values is required.
773 We can assemble both mips16 and normal MIPS code in a single
774 object. Therefore, we need to support this type of relaxation at
775 the same time that we support the relaxation described above. We
776 use the high bit of the subtype field to distinguish these cases.
778 The information we store for this type of relaxation is the
779 argument code found in the opcode file for this relocation, whether
780 the user explicitly requested a small or extended form, and whether
781 the relocation is in a jump or jal delay slot. That tells us the
782 size of the value, and how it should be stored. We also store
783 whether the fragment is considered to be extended or not. We also
784 store whether this is known to be a branch to a different section,
785 whether we have tried to relax this frag yet, and whether we have
786 ever extended a PC relative fragment because of a shift count. */
787 #define RELAX_MIPS16_ENCODE(type, small, ext, dslot, jal_dslot) \
790 | ((small) ? 0x100 : 0) \
791 | ((ext) ? 0x200 : 0) \
792 | ((dslot) ? 0x400 : 0) \
793 | ((jal_dslot) ? 0x800 : 0))
794 #define RELAX_MIPS16_P(i) (((i) & 0xc0000000) == 0x80000000)
795 #define RELAX_MIPS16_TYPE(i) ((i) & 0xff)
796 #define RELAX_MIPS16_USER_SMALL(i) (((i) & 0x100) != 0)
797 #define RELAX_MIPS16_USER_EXT(i) (((i) & 0x200) != 0)
798 #define RELAX_MIPS16_DSLOT(i) (((i) & 0x400) != 0)
799 #define RELAX_MIPS16_JAL_DSLOT(i) (((i) & 0x800) != 0)
800 #define RELAX_MIPS16_EXTENDED(i) (((i) & 0x1000) != 0)
801 #define RELAX_MIPS16_MARK_EXTENDED(i) ((i) | 0x1000)
802 #define RELAX_MIPS16_CLEAR_EXTENDED(i) ((i) &~ 0x1000)
803 #define RELAX_MIPS16_LONG_BRANCH(i) (((i) & 0x2000) != 0)
804 #define RELAX_MIPS16_MARK_LONG_BRANCH(i) ((i) | 0x2000)
805 #define RELAX_MIPS16_CLEAR_LONG_BRANCH(i) ((i) &~ 0x2000)
807 /* Is the given value a sign-extended 32-bit value? */
808 #define IS_SEXT_32BIT_NUM(x) \
809 (((x) &~ (offsetT) 0x7fffffff) == 0 \
810 || (((x) &~ (offsetT) 0x7fffffff) == ~ (offsetT) 0x7fffffff))
812 /* Is the given value a sign-extended 16-bit value? */
813 #define IS_SEXT_16BIT_NUM(x) \
814 (((x) &~ (offsetT) 0x7fff) == 0 \
815 || (((x) &~ (offsetT) 0x7fff) == ~ (offsetT) 0x7fff))
818 /* Prototypes for static functions. */
821 #define internalError() \
822 as_fatal (_("internal Error, line %d, %s"), __LINE__, __FILE__)
824 #define internalError() as_fatal (_("MIPS internal Error"));
827 enum mips_regclass { MIPS_GR_REG, MIPS_FP_REG, MIPS16_REG };
829 static inline bfd_boolean reloc_needs_lo_p
830 PARAMS ((bfd_reloc_code_real_type));
831 static inline bfd_boolean fixup_has_matching_lo_p
833 static int insn_uses_reg
834 PARAMS ((struct mips_cl_insn *ip, unsigned int reg,
835 enum mips_regclass class));
836 static int reg_needs_delay
837 PARAMS ((unsigned int));
838 static void mips16_mark_labels
840 static void append_insn
841 PARAMS ((char *place, struct mips_cl_insn * ip, expressionS * p,
842 bfd_reloc_code_real_type *r));
843 static void mips_no_prev_insn
845 static void mips_emit_delays
846 PARAMS ((bfd_boolean));
848 static void macro_build
849 PARAMS ((char *place, int *counter, expressionS * ep, const char *name,
850 const char *fmt, ...));
852 static void macro_build ();
854 static void mips16_macro_build
855 PARAMS ((char *, int *, expressionS *, const char *, const char *, va_list));
856 static void macro_build_jalr
857 PARAMS ((int, expressionS *));
858 static void macro_build_lui
859 PARAMS ((char *place, int *counter, expressionS * ep, int regnum));
860 static void macro_build_ldst_constoffset
861 PARAMS ((char *place, int *counter, expressionS * ep, const char *op,
862 int valreg, int breg));
864 PARAMS ((int *counter, int reg, int unsignedp));
865 static void check_absolute_expr
866 PARAMS ((struct mips_cl_insn * ip, expressionS *));
867 static void load_register
868 PARAMS ((int *, int, expressionS *, int));
869 static void load_address
870 PARAMS ((int *, int, expressionS *, int *));
871 static void move_register
872 PARAMS ((int *, int, int));
874 PARAMS ((struct mips_cl_insn * ip));
875 static void mips16_macro
876 PARAMS ((struct mips_cl_insn * ip));
877 #ifdef LOSING_COMPILER
879 PARAMS ((struct mips_cl_insn * ip));
882 PARAMS ((char *str, struct mips_cl_insn * ip));
883 static void mips16_ip
884 PARAMS ((char *str, struct mips_cl_insn * ip));
885 static void mips16_immed
886 PARAMS ((char *, unsigned int, int, offsetT, bfd_boolean, bfd_boolean,
887 bfd_boolean, unsigned long *, bfd_boolean *, unsigned short *));
888 static bfd_boolean parse_relocation
889 PARAMS ((char **, bfd_reloc_code_real_type *));
890 static size_t my_getSmallExpression
891 PARAMS ((expressionS *, bfd_reloc_code_real_type *, char *));
892 static void my_getExpression
893 PARAMS ((expressionS *, char *));
895 static int support_64bit_objects
898 static void mips_set_option_string
899 PARAMS ((const char **, const char *));
900 static symbolS *get_symbol
902 static void mips_align
903 PARAMS ((int to, int fill, symbolS *label));
906 static void s_change_sec
908 static void s_change_section
912 static void s_float_cons
914 static void s_mips_globl
918 static void s_mipsset
920 static void s_abicalls
924 static void s_cpsetup
926 static void s_cplocal
928 static void s_cprestore
930 static void s_cpreturn
932 static void s_gpvalue
936 static void s_gpdword
942 static void md_obj_begin
944 static void md_obj_end
946 static long get_number
948 static void s_mips_ent
950 static void s_mips_end
952 static void s_mips_frame
954 static void s_mips_mask
956 static void s_mips_stab
958 static void s_mips_weakext
960 static void s_mips_file
962 static void s_mips_loc
964 static bfd_boolean pic_need_relax
965 PARAMS ((symbolS *, asection *));
966 static int mips16_extended_frag
967 PARAMS ((fragS *, asection *, long));
968 static int relaxed_branch_length (fragS *, asection *, int);
969 static int validate_mips_insn
970 PARAMS ((const struct mips_opcode *));
972 PARAMS ((FILE *, const char *, int *, int *));
974 static int mips_need_elf_addend_fixup
978 /* Table and functions used to map between CPU/ISA names, and
979 ISA levels, and CPU numbers. */
983 const char *name; /* CPU or ISA name. */
984 int is_isa; /* Is this an ISA? (If 0, a CPU.) */
985 int isa; /* ISA level. */
986 int cpu; /* CPU number (default CPU if ISA). */
989 static void mips_set_architecture
990 PARAMS ((const struct mips_cpu_info *));
991 static void mips_set_tune
992 PARAMS ((const struct mips_cpu_info *));
993 static bfd_boolean mips_strict_matching_cpu_name_p
994 PARAMS ((const char *, const char *));
995 static bfd_boolean mips_matching_cpu_name_p
996 PARAMS ((const char *, const char *));
997 static const struct mips_cpu_info *mips_parse_cpu
998 PARAMS ((const char *, const char *));
999 static const struct mips_cpu_info *mips_cpu_info_from_isa
1004 The following pseudo-ops from the Kane and Heinrich MIPS book
1005 should be defined here, but are currently unsupported: .alias,
1006 .galive, .gjaldef, .gjrlive, .livereg, .noalias.
1008 The following pseudo-ops from the Kane and Heinrich MIPS book are
1009 specific to the type of debugging information being generated, and
1010 should be defined by the object format: .aent, .begin, .bend,
1011 .bgnb, .end, .endb, .ent, .fmask, .frame, .loc, .mask, .verstamp,
1014 The following pseudo-ops from the Kane and Heinrich MIPS book are
1015 not MIPS CPU specific, but are also not specific to the object file
1016 format. This file is probably the best place to define them, but
1017 they are not currently supported: .asm0, .endr, .lab, .repeat,
1020 static const pseudo_typeS mips_pseudo_table[] =
1022 /* MIPS specific pseudo-ops. */
1023 {"option", s_option, 0},
1024 {"set", s_mipsset, 0},
1025 {"rdata", s_change_sec, 'r'},
1026 {"sdata", s_change_sec, 's'},
1027 {"livereg", s_ignore, 0},
1028 {"abicalls", s_abicalls, 0},
1029 {"cpload", s_cpload, 0},
1030 {"cpsetup", s_cpsetup, 0},
1031 {"cplocal", s_cplocal, 0},
1032 {"cprestore", s_cprestore, 0},
1033 {"cpreturn", s_cpreturn, 0},
1034 {"gpvalue", s_gpvalue, 0},
1035 {"gpword", s_gpword, 0},
1036 {"gpdword", s_gpdword, 0},
1037 {"cpadd", s_cpadd, 0},
1038 {"insn", s_insn, 0},
1040 /* Relatively generic pseudo-ops that happen to be used on MIPS
1042 {"asciiz", stringer, 1},
1043 {"bss", s_change_sec, 'b'},
1045 {"half", s_cons, 1},
1046 {"dword", s_cons, 3},
1047 {"weakext", s_mips_weakext, 0},
1049 /* These pseudo-ops are defined in read.c, but must be overridden
1050 here for one reason or another. */
1051 {"align", s_align, 0},
1052 {"byte", s_cons, 0},
1053 {"data", s_change_sec, 'd'},
1054 {"double", s_float_cons, 'd'},
1055 {"float", s_float_cons, 'f'},
1056 {"globl", s_mips_globl, 0},
1057 {"global", s_mips_globl, 0},
1058 {"hword", s_cons, 1},
1060 {"long", s_cons, 2},
1061 {"octa", s_cons, 4},
1062 {"quad", s_cons, 3},
1063 {"section", s_change_section, 0},
1064 {"short", s_cons, 1},
1065 {"single", s_float_cons, 'f'},
1066 {"stabn", s_mips_stab, 'n'},
1067 {"text", s_change_sec, 't'},
1068 {"word", s_cons, 2},
1070 { "extern", ecoff_directive_extern, 0},
1075 static const pseudo_typeS mips_nonecoff_pseudo_table[] =
1077 /* These pseudo-ops should be defined by the object file format.
1078 However, a.out doesn't support them, so we have versions here. */
1079 {"aent", s_mips_ent, 1},
1080 {"bgnb", s_ignore, 0},
1081 {"end", s_mips_end, 0},
1082 {"endb", s_ignore, 0},
1083 {"ent", s_mips_ent, 0},
1084 {"file", s_mips_file, 0},
1085 {"fmask", s_mips_mask, 'F'},
1086 {"frame", s_mips_frame, 0},
1087 {"loc", s_mips_loc, 0},
1088 {"mask", s_mips_mask, 'R'},
1089 {"verstamp", s_ignore, 0},
1093 extern void pop_insert PARAMS ((const pseudo_typeS *));
1098 pop_insert (mips_pseudo_table);
1099 if (! ECOFF_DEBUGGING)
1100 pop_insert (mips_nonecoff_pseudo_table);
1103 /* Symbols labelling the current insn. */
1105 struct insn_label_list
1107 struct insn_label_list *next;
1111 static struct insn_label_list *insn_labels;
1112 static struct insn_label_list *free_insn_labels;
1114 static void mips_clear_insn_labels PARAMS ((void));
1117 mips_clear_insn_labels ()
1119 register struct insn_label_list **pl;
1121 for (pl = &free_insn_labels; *pl != NULL; pl = &(*pl)->next)
1127 static char *expr_end;
1129 /* Expressions which appear in instructions. These are set by
1132 static expressionS imm_expr;
1133 static expressionS offset_expr;
1135 /* Relocs associated with imm_expr and offset_expr. */
1137 static bfd_reloc_code_real_type imm_reloc[3]
1138 = {BFD_RELOC_UNUSED, BFD_RELOC_UNUSED, BFD_RELOC_UNUSED};
1139 static bfd_reloc_code_real_type offset_reloc[3]
1140 = {BFD_RELOC_UNUSED, BFD_RELOC_UNUSED, BFD_RELOC_UNUSED};
1142 /* These are set by mips16_ip if an explicit extension is used. */
1144 static bfd_boolean mips16_small, mips16_ext;
1147 /* The pdr segment for per procedure frame/regmask info. Not used for
1150 static segT pdr_seg;
1153 /* The default target format to use. */
1156 mips_target_format ()
1158 switch (OUTPUT_FLAVOR)
1160 case bfd_target_aout_flavour:
1161 return target_big_endian ? "a.out-mips-big" : "a.out-mips-little";
1162 case bfd_target_ecoff_flavour:
1163 return target_big_endian ? "ecoff-bigmips" : ECOFF_LITTLE_FORMAT;
1164 case bfd_target_coff_flavour:
1166 case bfd_target_elf_flavour:
1168 /* This is traditional mips. */
1169 return (target_big_endian
1170 ? (HAVE_64BIT_OBJECTS
1171 ? "elf64-tradbigmips"
1173 ? "elf32-ntradbigmips" : "elf32-tradbigmips"))
1174 : (HAVE_64BIT_OBJECTS
1175 ? "elf64-tradlittlemips"
1177 ? "elf32-ntradlittlemips" : "elf32-tradlittlemips")));
1179 return (target_big_endian
1180 ? (HAVE_64BIT_OBJECTS
1183 ? "elf32-nbigmips" : "elf32-bigmips"))
1184 : (HAVE_64BIT_OBJECTS
1185 ? "elf64-littlemips"
1187 ? "elf32-nlittlemips" : "elf32-littlemips")));
1195 /* This function is called once, at assembler startup time. It should
1196 set up all the tables, etc. that the MD part of the assembler will need. */
1201 register const char *retval = NULL;
1205 if (! bfd_set_arch_mach (stdoutput, bfd_arch_mips, mips_arch))
1206 as_warn (_("Could not set architecture and machine"));
1208 op_hash = hash_new ();
1210 for (i = 0; i < NUMOPCODES;)
1212 const char *name = mips_opcodes[i].name;
1214 retval = hash_insert (op_hash, name, (PTR) &mips_opcodes[i]);
1217 fprintf (stderr, _("internal error: can't hash `%s': %s\n"),
1218 mips_opcodes[i].name, retval);
1219 /* Probably a memory allocation problem? Give up now. */
1220 as_fatal (_("Broken assembler. No assembly attempted."));
1224 if (mips_opcodes[i].pinfo != INSN_MACRO)
1226 if (!validate_mips_insn (&mips_opcodes[i]))
1231 while ((i < NUMOPCODES) && !strcmp (mips_opcodes[i].name, name));
1234 mips16_op_hash = hash_new ();
1237 while (i < bfd_mips16_num_opcodes)
1239 const char *name = mips16_opcodes[i].name;
1241 retval = hash_insert (mips16_op_hash, name, (PTR) &mips16_opcodes[i]);
1243 as_fatal (_("internal: can't hash `%s': %s"),
1244 mips16_opcodes[i].name, retval);
1247 if (mips16_opcodes[i].pinfo != INSN_MACRO
1248 && ((mips16_opcodes[i].match & mips16_opcodes[i].mask)
1249 != mips16_opcodes[i].match))
1251 fprintf (stderr, _("internal error: bad mips16 opcode: %s %s\n"),
1252 mips16_opcodes[i].name, mips16_opcodes[i].args);
1257 while (i < bfd_mips16_num_opcodes
1258 && strcmp (mips16_opcodes[i].name, name) == 0);
1262 as_fatal (_("Broken assembler. No assembly attempted."));
1264 /* We add all the general register names to the symbol table. This
1265 helps us detect invalid uses of them. */
1266 for (i = 0; i < 32; i++)
1270 sprintf (buf, "$%d", i);
1271 symbol_table_insert (symbol_new (buf, reg_section, i,
1272 &zero_address_frag));
1274 symbol_table_insert (symbol_new ("$ra", reg_section, RA,
1275 &zero_address_frag));
1276 symbol_table_insert (symbol_new ("$fp", reg_section, FP,
1277 &zero_address_frag));
1278 symbol_table_insert (symbol_new ("$sp", reg_section, SP,
1279 &zero_address_frag));
1280 symbol_table_insert (symbol_new ("$gp", reg_section, GP,
1281 &zero_address_frag));
1282 symbol_table_insert (symbol_new ("$at", reg_section, AT,
1283 &zero_address_frag));
1284 symbol_table_insert (symbol_new ("$kt0", reg_section, KT0,
1285 &zero_address_frag));
1286 symbol_table_insert (symbol_new ("$kt1", reg_section, KT1,
1287 &zero_address_frag));
1288 symbol_table_insert (symbol_new ("$zero", reg_section, ZERO,
1289 &zero_address_frag));
1290 symbol_table_insert (symbol_new ("$pc", reg_section, -1,
1291 &zero_address_frag));
1293 /* If we don't add these register names to the symbol table, they
1294 may end up being added as regular symbols by operand(), and then
1295 make it to the object file as undefined in case they're not
1296 regarded as local symbols. They're local in o32, since `$' is a
1297 local symbol prefix, but not in n32 or n64. */
1298 for (i = 0; i < 8; i++)
1302 sprintf (buf, "$fcc%i", i);
1303 symbol_table_insert (symbol_new (buf, reg_section, -1,
1304 &zero_address_frag));
1307 mips_no_prev_insn (FALSE);
1310 mips_cprmask[0] = 0;
1311 mips_cprmask[1] = 0;
1312 mips_cprmask[2] = 0;
1313 mips_cprmask[3] = 0;
1315 /* set the default alignment for the text section (2**2) */
1316 record_alignment (text_section, 2);
1318 if (USE_GLOBAL_POINTER_OPT)
1319 bfd_set_gp_size (stdoutput, g_switch_value);
1321 if (OUTPUT_FLAVOR == bfd_target_elf_flavour)
1323 /* On a native system, sections must be aligned to 16 byte
1324 boundaries. When configured for an embedded ELF target, we
1326 if (strcmp (TARGET_OS, "elf") != 0)
1328 (void) bfd_set_section_alignment (stdoutput, text_section, 4);
1329 (void) bfd_set_section_alignment (stdoutput, data_section, 4);
1330 (void) bfd_set_section_alignment (stdoutput, bss_section, 4);
1333 /* Create a .reginfo section for register masks and a .mdebug
1334 section for debugging information. */
1342 subseg = now_subseg;
1344 /* The ABI says this section should be loaded so that the
1345 running program can access it. However, we don't load it
1346 if we are configured for an embedded target */
1347 flags = SEC_READONLY | SEC_DATA;
1348 if (strcmp (TARGET_OS, "elf") != 0)
1349 flags |= SEC_ALLOC | SEC_LOAD;
1351 if (mips_abi != N64_ABI)
1353 sec = subseg_new (".reginfo", (subsegT) 0);
1355 bfd_set_section_flags (stdoutput, sec, flags);
1356 bfd_set_section_alignment (stdoutput, sec, HAVE_NEWABI ? 3 : 2);
1359 mips_regmask_frag = frag_more (sizeof (Elf32_External_RegInfo));
1364 /* The 64-bit ABI uses a .MIPS.options section rather than
1365 .reginfo section. */
1366 sec = subseg_new (".MIPS.options", (subsegT) 0);
1367 bfd_set_section_flags (stdoutput, sec, flags);
1368 bfd_set_section_alignment (stdoutput, sec, 3);
1371 /* Set up the option header. */
1373 Elf_Internal_Options opthdr;
1376 opthdr.kind = ODK_REGINFO;
1377 opthdr.size = (sizeof (Elf_External_Options)
1378 + sizeof (Elf64_External_RegInfo));
1381 f = frag_more (sizeof (Elf_External_Options));
1382 bfd_mips_elf_swap_options_out (stdoutput, &opthdr,
1383 (Elf_External_Options *) f);
1385 mips_regmask_frag = frag_more (sizeof (Elf64_External_RegInfo));
1390 if (ECOFF_DEBUGGING)
1392 sec = subseg_new (".mdebug", (subsegT) 0);
1393 (void) bfd_set_section_flags (stdoutput, sec,
1394 SEC_HAS_CONTENTS | SEC_READONLY);
1395 (void) bfd_set_section_alignment (stdoutput, sec, 2);
1398 else if (OUTPUT_FLAVOR == bfd_target_elf_flavour)
1400 pdr_seg = subseg_new (".pdr", (subsegT) 0);
1401 (void) bfd_set_section_flags (stdoutput, pdr_seg,
1402 SEC_READONLY | SEC_RELOC
1404 (void) bfd_set_section_alignment (stdoutput, pdr_seg, 2);
1408 subseg_set (seg, subseg);
1412 if (! ECOFF_DEBUGGING)
1419 if (! ECOFF_DEBUGGING)
1427 struct mips_cl_insn insn;
1428 bfd_reloc_code_real_type unused_reloc[3]
1429 = {BFD_RELOC_UNUSED, BFD_RELOC_UNUSED, BFD_RELOC_UNUSED};
1431 imm_expr.X_op = O_absent;
1432 offset_expr.X_op = O_absent;
1433 imm_reloc[0] = BFD_RELOC_UNUSED;
1434 imm_reloc[1] = BFD_RELOC_UNUSED;
1435 imm_reloc[2] = BFD_RELOC_UNUSED;
1436 offset_reloc[0] = BFD_RELOC_UNUSED;
1437 offset_reloc[1] = BFD_RELOC_UNUSED;
1438 offset_reloc[2] = BFD_RELOC_UNUSED;
1440 if (mips_opts.mips16)
1441 mips16_ip (str, &insn);
1444 mips_ip (str, &insn);
1445 DBG ((_("returned from mips_ip(%s) insn_opcode = 0x%x\n"),
1446 str, insn.insn_opcode));
1451 as_bad ("%s `%s'", insn_error, str);
1455 if (insn.insn_mo->pinfo == INSN_MACRO)
1457 if (mips_opts.mips16)
1458 mips16_macro (&insn);
1464 if (imm_expr.X_op != O_absent)
1465 append_insn (NULL, &insn, &imm_expr, imm_reloc);
1466 else if (offset_expr.X_op != O_absent)
1467 append_insn (NULL, &insn, &offset_expr, offset_reloc);
1469 append_insn (NULL, &insn, NULL, unused_reloc);
1473 /* Return true if the given relocation might need a matching %lo().
1474 Note that R_MIPS_GOT16 relocations only need a matching %lo() when
1475 applied to local symbols. */
1477 static inline bfd_boolean
1478 reloc_needs_lo_p (reloc)
1479 bfd_reloc_code_real_type reloc;
1481 return (reloc == BFD_RELOC_HI16_S
1482 || reloc == BFD_RELOC_MIPS_GOT16);
1485 /* Return true if the given fixup is followed by a matching R_MIPS_LO16
1488 static inline bfd_boolean
1489 fixup_has_matching_lo_p (fixp)
1492 return (fixp->fx_next != NULL
1493 && fixp->fx_next->fx_r_type == BFD_RELOC_LO16
1494 && fixp->fx_addsy == fixp->fx_next->fx_addsy
1495 && fixp->fx_offset == fixp->fx_next->fx_offset);
1498 /* See whether instruction IP reads register REG. CLASS is the type
1502 insn_uses_reg (ip, reg, class)
1503 struct mips_cl_insn *ip;
1505 enum mips_regclass class;
1507 if (class == MIPS16_REG)
1509 assert (mips_opts.mips16);
1510 reg = mips16_to_32_reg_map[reg];
1511 class = MIPS_GR_REG;
1514 /* Don't report on general register ZERO, since it never changes. */
1515 if (class == MIPS_GR_REG && reg == ZERO)
1518 if (class == MIPS_FP_REG)
1520 assert (! mips_opts.mips16);
1521 /* If we are called with either $f0 or $f1, we must check $f0.
1522 This is not optimal, because it will introduce an unnecessary
1523 NOP between "lwc1 $f0" and "swc1 $f1". To fix this we would
1524 need to distinguish reading both $f0 and $f1 or just one of
1525 them. Note that we don't have to check the other way,
1526 because there is no instruction that sets both $f0 and $f1
1527 and requires a delay. */
1528 if ((ip->insn_mo->pinfo & INSN_READ_FPR_S)
1529 && ((((ip->insn_opcode >> OP_SH_FS) & OP_MASK_FS) &~(unsigned)1)
1530 == (reg &~ (unsigned) 1)))
1532 if ((ip->insn_mo->pinfo & INSN_READ_FPR_T)
1533 && ((((ip->insn_opcode >> OP_SH_FT) & OP_MASK_FT) &~(unsigned)1)
1534 == (reg &~ (unsigned) 1)))
1537 else if (! mips_opts.mips16)
1539 if ((ip->insn_mo->pinfo & INSN_READ_GPR_S)
1540 && ((ip->insn_opcode >> OP_SH_RS) & OP_MASK_RS) == reg)
1542 if ((ip->insn_mo->pinfo & INSN_READ_GPR_T)
1543 && ((ip->insn_opcode >> OP_SH_RT) & OP_MASK_RT) == reg)
1548 if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_X)
1549 && (mips16_to_32_reg_map[((ip->insn_opcode >> MIPS16OP_SH_RX)
1550 & MIPS16OP_MASK_RX)]
1553 if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_Y)
1554 && (mips16_to_32_reg_map[((ip->insn_opcode >> MIPS16OP_SH_RY)
1555 & MIPS16OP_MASK_RY)]
1558 if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_Z)
1559 && (mips16_to_32_reg_map[((ip->insn_opcode >> MIPS16OP_SH_MOVE32Z)
1560 & MIPS16OP_MASK_MOVE32Z)]
1563 if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_T) && reg == TREG)
1565 if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_SP) && reg == SP)
1567 if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_31) && reg == RA)
1569 if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_GPR_X)
1570 && ((ip->insn_opcode >> MIPS16OP_SH_REGR32)
1571 & MIPS16OP_MASK_REGR32) == reg)
1578 /* This function returns true if modifying a register requires a
1582 reg_needs_delay (reg)
1585 unsigned long prev_pinfo;
1587 prev_pinfo = prev_insn.insn_mo->pinfo;
1588 if (! mips_opts.noreorder
1589 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
1590 && ((prev_pinfo & INSN_LOAD_COPROC_DELAY)
1591 || (! gpr_interlocks
1592 && (prev_pinfo & INSN_LOAD_MEMORY_DELAY))))
1594 /* A load from a coprocessor or from memory. All load
1595 delays delay the use of general register rt for one
1596 instruction on the r3000. The r6000 and r4000 use
1598 /* Itbl support may require additional care here. */
1599 know (prev_pinfo & INSN_WRITE_GPR_T);
1600 if (reg == ((prev_insn.insn_opcode >> OP_SH_RT) & OP_MASK_RT))
1607 /* Mark instruction labels in mips16 mode. This permits the linker to
1608 handle them specially, such as generating jalx instructions when
1609 needed. We also make them odd for the duration of the assembly, in
1610 order to generate the right sort of code. We will make them even
1611 in the adjust_symtab routine, while leaving them marked. This is
1612 convenient for the debugger and the disassembler. The linker knows
1613 to make them odd again. */
1616 mips16_mark_labels ()
1618 if (mips_opts.mips16)
1620 struct insn_label_list *l;
1623 for (l = insn_labels; l != NULL; l = l->next)
1626 if (OUTPUT_FLAVOR == bfd_target_elf_flavour)
1627 S_SET_OTHER (l->label, STO_MIPS16);
1629 val = S_GET_VALUE (l->label);
1631 S_SET_VALUE (l->label, val + 1);
1636 /* Output an instruction. PLACE is where to put the instruction; if
1637 it is NULL, this uses frag_more to get room. IP is the instruction
1638 information. ADDRESS_EXPR is an operand of the instruction to be
1639 used with RELOC_TYPE. */
1642 append_insn (place, ip, address_expr, reloc_type)
1644 struct mips_cl_insn *ip;
1645 expressionS *address_expr;
1646 bfd_reloc_code_real_type *reloc_type;
1648 register unsigned long prev_pinfo, pinfo;
1652 bfd_boolean force_new_frag = FALSE;
1654 /* Mark instruction labels in mips16 mode. */
1655 mips16_mark_labels ();
1657 prev_pinfo = prev_insn.insn_mo->pinfo;
1658 pinfo = ip->insn_mo->pinfo;
1660 if (place == NULL && (! mips_opts.noreorder || prev_nop_frag != NULL))
1664 /* If the previous insn required any delay slots, see if we need
1665 to insert a NOP or two. There are eight kinds of possible
1666 hazards, of which an instruction can have at most one type.
1667 (1) a load from memory delay
1668 (2) a load from a coprocessor delay
1669 (3) an unconditional branch delay
1670 (4) a conditional branch delay
1671 (5) a move to coprocessor register delay
1672 (6) a load coprocessor register from memory delay
1673 (7) a coprocessor condition code delay
1674 (8) a HI/LO special register delay
1676 There are a lot of optimizations we could do that we don't.
1677 In particular, we do not, in general, reorder instructions.
1678 If you use gcc with optimization, it will reorder
1679 instructions and generally do much more optimization then we
1680 do here; repeating all that work in the assembler would only
1681 benefit hand written assembly code, and does not seem worth
1684 /* This is how a NOP is emitted. */
1685 #define emit_nop() \
1687 ? md_number_to_chars (frag_more (2), 0x6500, 2) \
1688 : md_number_to_chars (frag_more (4), 0, 4))
1690 /* The previous insn might require a delay slot, depending upon
1691 the contents of the current insn. */
1692 if (! mips_opts.mips16
1693 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
1694 && (((prev_pinfo & INSN_LOAD_COPROC_DELAY)
1695 && ! cop_interlocks)
1696 || (! gpr_interlocks
1697 && (prev_pinfo & INSN_LOAD_MEMORY_DELAY))))
1699 /* A load from a coprocessor or from memory. All load
1700 delays delay the use of general register rt for one
1701 instruction on the r3000. The r6000 and r4000 use
1703 /* Itbl support may require additional care here. */
1704 know (prev_pinfo & INSN_WRITE_GPR_T);
1705 if (mips_optimize == 0
1706 || insn_uses_reg (ip,
1707 ((prev_insn.insn_opcode >> OP_SH_RT)
1712 else if (! mips_opts.mips16
1713 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
1714 && (((prev_pinfo & INSN_COPROC_MOVE_DELAY)
1715 && ! cop_interlocks)
1716 || (mips_opts.isa == ISA_MIPS1
1717 && (prev_pinfo & INSN_COPROC_MEMORY_DELAY))))
1719 /* A generic coprocessor delay. The previous instruction
1720 modified a coprocessor general or control register. If
1721 it modified a control register, we need to avoid any
1722 coprocessor instruction (this is probably not always
1723 required, but it sometimes is). If it modified a general
1724 register, we avoid using that register.
1726 On the r6000 and r4000 loading a coprocessor register
1727 from memory is interlocked, and does not require a delay.
1729 This case is not handled very well. There is no special
1730 knowledge of CP0 handling, and the coprocessors other
1731 than the floating point unit are not distinguished at
1733 /* Itbl support may require additional care here. FIXME!
1734 Need to modify this to include knowledge about
1735 user specified delays! */
1736 if (prev_pinfo & INSN_WRITE_FPR_T)
1738 if (mips_optimize == 0
1739 || insn_uses_reg (ip,
1740 ((prev_insn.insn_opcode >> OP_SH_FT)
1745 else if (prev_pinfo & INSN_WRITE_FPR_S)
1747 if (mips_optimize == 0
1748 || insn_uses_reg (ip,
1749 ((prev_insn.insn_opcode >> OP_SH_FS)
1756 /* We don't know exactly what the previous instruction
1757 does. If the current instruction uses a coprocessor
1758 register, we must insert a NOP. If previous
1759 instruction may set the condition codes, and the
1760 current instruction uses them, we must insert two
1762 /* Itbl support may require additional care here. */
1763 if (mips_optimize == 0
1764 || ((prev_pinfo & INSN_WRITE_COND_CODE)
1765 && (pinfo & INSN_READ_COND_CODE)))
1767 else if (pinfo & INSN_COP)
1771 else if (! mips_opts.mips16
1772 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
1773 && (prev_pinfo & INSN_WRITE_COND_CODE)
1774 && ! cop_interlocks)
1776 /* The previous instruction sets the coprocessor condition
1777 codes, but does not require a general coprocessor delay
1778 (this means it is a floating point comparison
1779 instruction). If this instruction uses the condition
1780 codes, we need to insert a single NOP. */
1781 /* Itbl support may require additional care here. */
1782 if (mips_optimize == 0
1783 || (pinfo & INSN_READ_COND_CODE))
1787 /* If we're fixing up mfhi/mflo for the r7000 and the
1788 previous insn was an mfhi/mflo and the current insn
1789 reads the register that the mfhi/mflo wrote to, then
1792 else if (mips_7000_hilo_fix
1793 && MF_HILO_INSN (prev_pinfo)
1794 && insn_uses_reg (ip, ((prev_insn.insn_opcode >> OP_SH_RD)
1801 /* If we're fixing up mfhi/mflo for the r7000 and the
1802 2nd previous insn was an mfhi/mflo and the current insn
1803 reads the register that the mfhi/mflo wrote to, then
1806 else if (mips_7000_hilo_fix
1807 && MF_HILO_INSN (prev_prev_insn.insn_opcode)
1808 && insn_uses_reg (ip, ((prev_prev_insn.insn_opcode >> OP_SH_RD)
1816 else if (prev_pinfo & INSN_READ_LO)
1818 /* The previous instruction reads the LO register; if the
1819 current instruction writes to the LO register, we must
1820 insert two NOPS. Some newer processors have interlocks.
1821 Also the tx39's multiply instructions can be exectuted
1822 immediatly after a read from HI/LO (without the delay),
1823 though the tx39's divide insns still do require the
1825 if (! (hilo_interlocks
1826 || (mips_tune == CPU_R3900 && (pinfo & INSN_MULT)))
1827 && (mips_optimize == 0
1828 || (pinfo & INSN_WRITE_LO)))
1830 /* Most mips16 branch insns don't have a delay slot.
1831 If a read from LO is immediately followed by a branch
1832 to a write to LO we have a read followed by a write
1833 less than 2 insns away. We assume the target of
1834 a branch might be a write to LO, and insert a nop
1835 between a read and an immediately following branch. */
1836 else if (mips_opts.mips16
1837 && (mips_optimize == 0
1838 || (pinfo & MIPS16_INSN_BRANCH)))
1841 else if (prev_insn.insn_mo->pinfo & INSN_READ_HI)
1843 /* The previous instruction reads the HI register; if the
1844 current instruction writes to the HI register, we must
1845 insert a NOP. Some newer processors have interlocks.
1846 Also the note tx39's multiply above. */
1847 if (! (hilo_interlocks
1848 || (mips_tune == CPU_R3900 && (pinfo & INSN_MULT)))
1849 && (mips_optimize == 0
1850 || (pinfo & INSN_WRITE_HI)))
1852 /* Most mips16 branch insns don't have a delay slot.
1853 If a read from HI is immediately followed by a branch
1854 to a write to HI we have a read followed by a write
1855 less than 2 insns away. We assume the target of
1856 a branch might be a write to HI, and insert a nop
1857 between a read and an immediately following branch. */
1858 else if (mips_opts.mips16
1859 && (mips_optimize == 0
1860 || (pinfo & MIPS16_INSN_BRANCH)))
1864 /* If the previous instruction was in a noreorder section, then
1865 we don't want to insert the nop after all. */
1866 /* Itbl support may require additional care here. */
1867 if (prev_insn_unreordered)
1870 /* There are two cases which require two intervening
1871 instructions: 1) setting the condition codes using a move to
1872 coprocessor instruction which requires a general coprocessor
1873 delay and then reading the condition codes 2) reading the HI
1874 or LO register and then writing to it (except on processors
1875 which have interlocks). If we are not already emitting a NOP
1876 instruction, we must check for these cases compared to the
1877 instruction previous to the previous instruction. */
1878 if ((! mips_opts.mips16
1879 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
1880 && (prev_prev_insn.insn_mo->pinfo & INSN_COPROC_MOVE_DELAY)
1881 && (prev_prev_insn.insn_mo->pinfo & INSN_WRITE_COND_CODE)
1882 && (pinfo & INSN_READ_COND_CODE)
1883 && ! cop_interlocks)
1884 || ((prev_prev_insn.insn_mo->pinfo & INSN_READ_LO)
1885 && (pinfo & INSN_WRITE_LO)
1886 && ! (hilo_interlocks
1887 || (mips_tune == CPU_R3900 && (pinfo & INSN_MULT))))
1888 || ((prev_prev_insn.insn_mo->pinfo & INSN_READ_HI)
1889 && (pinfo & INSN_WRITE_HI)
1890 && ! (hilo_interlocks
1891 || (mips_tune == CPU_R3900 && (pinfo & INSN_MULT)))))
1896 if (prev_prev_insn_unreordered)
1899 if (prev_prev_nop && nops == 0)
1902 if (mips_fix_4122_bugs && prev_insn.insn_mo->name)
1904 /* We're out of bits in pinfo, so we must resort to string
1905 ops here. Shortcuts are selected based on opcodes being
1906 limited to the VR4122 instruction set. */
1908 const char *pn = prev_insn.insn_mo->name;
1909 const char *tn = ip->insn_mo->name;
1910 if (strncmp(pn, "macc", 4) == 0
1911 || strncmp(pn, "dmacc", 5) == 0)
1913 /* Errata 21 - [D]DIV[U] after [D]MACC */
1914 if (strstr (tn, "div"))
1919 /* Errata 23 - Continuous DMULT[U]/DMACC instructions */
1920 if (pn[0] == 'd' /* dmacc */
1921 && (strncmp(tn, "dmult", 5) == 0
1922 || strncmp(tn, "dmacc", 5) == 0))
1927 /* Errata 24 - MT{LO,HI} after [D]MACC */
1928 if (strcmp (tn, "mtlo") == 0
1929 || strcmp (tn, "mthi") == 0)
1935 else if (strncmp(pn, "dmult", 5) == 0
1936 && (strncmp(tn, "dmult", 5) == 0
1937 || strncmp(tn, "dmacc", 5) == 0))
1939 /* Here is the rest of errata 23. */
1942 if (nops < min_nops)
1946 /* If we are being given a nop instruction, don't bother with
1947 one of the nops we would otherwise output. This will only
1948 happen when a nop instruction is used with mips_optimize set
1951 && ! mips_opts.noreorder
1952 && ip->insn_opcode == (unsigned) (mips_opts.mips16 ? 0x6500 : 0))
1955 /* Now emit the right number of NOP instructions. */
1956 if (nops > 0 && ! mips_opts.noreorder)
1959 unsigned long old_frag_offset;
1961 struct insn_label_list *l;
1963 old_frag = frag_now;
1964 old_frag_offset = frag_now_fix ();
1966 for (i = 0; i < nops; i++)
1971 listing_prev_line ();
1972 /* We may be at the start of a variant frag. In case we
1973 are, make sure there is enough space for the frag
1974 after the frags created by listing_prev_line. The
1975 argument to frag_grow here must be at least as large
1976 as the argument to all other calls to frag_grow in
1977 this file. We don't have to worry about being in the
1978 middle of a variant frag, because the variants insert
1979 all needed nop instructions themselves. */
1983 for (l = insn_labels; l != NULL; l = l->next)
1987 assert (S_GET_SEGMENT (l->label) == now_seg);
1988 symbol_set_frag (l->label, frag_now);
1989 val = (valueT) frag_now_fix ();
1990 /* mips16 text labels are stored as odd. */
1991 if (mips_opts.mips16)
1993 S_SET_VALUE (l->label, val);
1996 #ifndef NO_ECOFF_DEBUGGING
1997 if (ECOFF_DEBUGGING)
1998 ecoff_fix_loc (old_frag, old_frag_offset);
2001 else if (prev_nop_frag != NULL)
2003 /* We have a frag holding nops we may be able to remove. If
2004 we don't need any nops, we can decrease the size of
2005 prev_nop_frag by the size of one instruction. If we do
2006 need some nops, we count them in prev_nops_required. */
2007 if (prev_nop_frag_since == 0)
2011 prev_nop_frag->fr_fix -= mips_opts.mips16 ? 2 : 4;
2012 --prev_nop_frag_holds;
2015 prev_nop_frag_required += nops;
2019 if (prev_prev_nop == 0)
2021 prev_nop_frag->fr_fix -= mips_opts.mips16 ? 2 : 4;
2022 --prev_nop_frag_holds;
2025 ++prev_nop_frag_required;
2028 if (prev_nop_frag_holds <= prev_nop_frag_required)
2029 prev_nop_frag = NULL;
2031 ++prev_nop_frag_since;
2033 /* Sanity check: by the time we reach the second instruction
2034 after prev_nop_frag, we should have used up all the nops
2035 one way or another. */
2036 assert (prev_nop_frag_since <= 1 || prev_nop_frag == NULL);
2042 && *reloc_type == BFD_RELOC_16_PCREL_S2
2043 && (pinfo & INSN_UNCOND_BRANCH_DELAY || pinfo & INSN_COND_BRANCH_DELAY
2044 || pinfo & INSN_COND_BRANCH_LIKELY)
2045 && mips_relax_branch
2046 /* Don't try branch relaxation within .set nomacro, or within
2047 .set noat if we use $at for PIC computations. If it turns
2048 out that the branch was out-of-range, we'll get an error. */
2049 && !mips_opts.warn_about_macros
2050 && !(mips_opts.noat && mips_pic != NO_PIC)
2051 && !mips_opts.mips16)
2053 f = frag_var (rs_machine_dependent,
2054 relaxed_branch_length
2056 (pinfo & INSN_UNCOND_BRANCH_DELAY) ? -1
2057 : (pinfo & INSN_COND_BRANCH_LIKELY) ? 1 : 0), 4,
2059 (pinfo & INSN_UNCOND_BRANCH_DELAY,
2060 pinfo & INSN_COND_BRANCH_LIKELY,
2061 pinfo & INSN_WRITE_GPR_31,
2063 address_expr->X_add_symbol,
2064 address_expr->X_add_number,
2066 *reloc_type = BFD_RELOC_UNUSED;
2068 else if (*reloc_type > BFD_RELOC_UNUSED)
2070 /* We need to set up a variant frag. */
2071 assert (mips_opts.mips16 && address_expr != NULL);
2072 f = frag_var (rs_machine_dependent, 4, 0,
2073 RELAX_MIPS16_ENCODE (*reloc_type - BFD_RELOC_UNUSED,
2074 mips16_small, mips16_ext,
2076 & INSN_UNCOND_BRANCH_DELAY),
2077 (*prev_insn_reloc_type
2078 == BFD_RELOC_MIPS16_JMP)),
2079 make_expr_symbol (address_expr), 0, NULL);
2081 else if (place != NULL)
2083 else if (mips_opts.mips16
2085 && *reloc_type != BFD_RELOC_MIPS16_JMP)
2087 /* Make sure there is enough room to swap this instruction with
2088 a following jump instruction. */
2094 if (mips_opts.mips16
2095 && mips_opts.noreorder
2096 && (prev_pinfo & INSN_UNCOND_BRANCH_DELAY) != 0)
2097 as_warn (_("extended instruction in delay slot"));
2102 fixp[0] = fixp[1] = fixp[2] = NULL;
2103 if (address_expr != NULL && *reloc_type < BFD_RELOC_UNUSED)
2105 if (address_expr->X_op == O_constant)
2109 switch (*reloc_type)
2112 ip->insn_opcode |= address_expr->X_add_number;
2115 case BFD_RELOC_MIPS_HIGHEST:
2116 tmp = (address_expr->X_add_number + 0x800080008000) >> 16;
2118 ip->insn_opcode |= (tmp >> 16) & 0xffff;
2121 case BFD_RELOC_MIPS_HIGHER:
2122 tmp = (address_expr->X_add_number + 0x80008000) >> 16;
2123 ip->insn_opcode |= (tmp >> 16) & 0xffff;
2126 case BFD_RELOC_HI16_S:
2127 ip->insn_opcode |= ((address_expr->X_add_number + 0x8000)
2131 case BFD_RELOC_HI16:
2132 ip->insn_opcode |= (address_expr->X_add_number >> 16) & 0xffff;
2135 case BFD_RELOC_LO16:
2136 case BFD_RELOC_MIPS_GOT_DISP:
2137 ip->insn_opcode |= address_expr->X_add_number & 0xffff;
2140 case BFD_RELOC_MIPS_JMP:
2141 if ((address_expr->X_add_number & 3) != 0)
2142 as_bad (_("jump to misaligned address (0x%lx)"),
2143 (unsigned long) address_expr->X_add_number);
2144 if (address_expr->X_add_number & ~0xfffffff)
2145 as_bad (_("jump address range overflow (0x%lx)"),
2146 (unsigned long) address_expr->X_add_number);
2147 ip->insn_opcode |= (address_expr->X_add_number >> 2) & 0x3ffffff;
2150 case BFD_RELOC_MIPS16_JMP:
2151 if ((address_expr->X_add_number & 3) != 0)
2152 as_bad (_("jump to misaligned address (0x%lx)"),
2153 (unsigned long) address_expr->X_add_number);
2154 if (address_expr->X_add_number & ~0xfffffff)
2155 as_bad (_("jump address range overflow (0x%lx)"),
2156 (unsigned long) address_expr->X_add_number);
2158 (((address_expr->X_add_number & 0x7c0000) << 3)
2159 | ((address_expr->X_add_number & 0xf800000) >> 7)
2160 | ((address_expr->X_add_number & 0x3fffc) >> 2));
2163 case BFD_RELOC_16_PCREL_S2:
2173 /* Don't generate a reloc if we are writing into a variant frag. */
2176 reloc_howto_type *howto;
2179 /* In a compound relocation, it is the final (outermost)
2180 operator that determines the relocated field. */
2181 for (i = 1; i < 3; i++)
2182 if (reloc_type[i] == BFD_RELOC_UNUSED)
2185 howto = bfd_reloc_type_lookup (stdoutput, reloc_type[i - 1]);
2186 fixp[0] = fix_new_exp (frag_now, f - frag_now->fr_literal,
2187 bfd_get_reloc_size(howto),
2189 reloc_type[0] == BFD_RELOC_16_PCREL_S2,
2192 /* These relocations can have an addend that won't fit in
2193 4 octets for 64bit assembly. */
2195 && ! howto->partial_inplace
2196 && (reloc_type[0] == BFD_RELOC_16
2197 || reloc_type[0] == BFD_RELOC_32
2198 || reloc_type[0] == BFD_RELOC_MIPS_JMP
2199 || reloc_type[0] == BFD_RELOC_HI16_S
2200 || reloc_type[0] == BFD_RELOC_LO16
2201 || reloc_type[0] == BFD_RELOC_GPREL16
2202 || reloc_type[0] == BFD_RELOC_MIPS_LITERAL
2203 || reloc_type[0] == BFD_RELOC_GPREL32
2204 || reloc_type[0] == BFD_RELOC_64
2205 || reloc_type[0] == BFD_RELOC_CTOR
2206 || reloc_type[0] == BFD_RELOC_MIPS_SUB
2207 || reloc_type[0] == BFD_RELOC_MIPS_HIGHEST
2208 || reloc_type[0] == BFD_RELOC_MIPS_HIGHER
2209 || reloc_type[0] == BFD_RELOC_MIPS_SCN_DISP
2210 || reloc_type[0] == BFD_RELOC_MIPS_REL16
2211 || reloc_type[0] == BFD_RELOC_MIPS_RELGOT))
2212 fixp[0]->fx_no_overflow = 1;
2214 if (reloc_needs_lo_p (*reloc_type))
2216 struct mips_hi_fixup *hi_fixup;
2218 /* Reuse the last entry if it already has a matching %lo. */
2219 hi_fixup = mips_hi_fixup_list;
2221 || !fixup_has_matching_lo_p (hi_fixup->fixp))
2223 hi_fixup = ((struct mips_hi_fixup *)
2224 xmalloc (sizeof (struct mips_hi_fixup)));
2225 hi_fixup->next = mips_hi_fixup_list;
2226 mips_hi_fixup_list = hi_fixup;
2228 hi_fixup->fixp = fixp[0];
2229 hi_fixup->seg = now_seg;
2232 /* Add fixups for the second and third relocations, if given.
2233 Note that the ABI allows the second relocation to be
2234 against RSS_UNDEF, RSS_GP, RSS_GP0 or RSS_LOC. At the
2235 moment we only use RSS_UNDEF, but we could add support
2236 for the others if it ever becomes necessary. */
2237 for (i = 1; i < 3; i++)
2238 if (reloc_type[i] != BFD_RELOC_UNUSED)
2240 address_expr->X_op = O_absent;
2241 address_expr->X_add_symbol = 0;
2242 address_expr->X_add_number = 0;
2244 fixp[i] = fix_new_exp (frag_now, fixp[0]->fx_where,
2245 fixp[0]->fx_size, address_expr,
2246 FALSE, reloc_type[i]);
2252 if (! mips_opts.mips16)
2254 md_number_to_chars (f, ip->insn_opcode, 4);
2256 dwarf2_emit_insn (4);
2259 else if (*reloc_type == BFD_RELOC_MIPS16_JMP)
2261 md_number_to_chars (f, ip->insn_opcode >> 16, 2);
2262 md_number_to_chars (f + 2, ip->insn_opcode & 0xffff, 2);
2264 dwarf2_emit_insn (4);
2271 md_number_to_chars (f, 0xf000 | ip->extend, 2);
2274 md_number_to_chars (f, ip->insn_opcode, 2);
2276 dwarf2_emit_insn (ip->use_extend ? 4 : 2);
2280 /* Update the register mask information. */
2281 if (! mips_opts.mips16)
2283 if (pinfo & INSN_WRITE_GPR_D)
2284 mips_gprmask |= 1 << ((ip->insn_opcode >> OP_SH_RD) & OP_MASK_RD);
2285 if ((pinfo & (INSN_WRITE_GPR_T | INSN_READ_GPR_T)) != 0)
2286 mips_gprmask |= 1 << ((ip->insn_opcode >> OP_SH_RT) & OP_MASK_RT);
2287 if (pinfo & INSN_READ_GPR_S)
2288 mips_gprmask |= 1 << ((ip->insn_opcode >> OP_SH_RS) & OP_MASK_RS);
2289 if (pinfo & INSN_WRITE_GPR_31)
2290 mips_gprmask |= 1 << RA;
2291 if (pinfo & INSN_WRITE_FPR_D)
2292 mips_cprmask[1] |= 1 << ((ip->insn_opcode >> OP_SH_FD) & OP_MASK_FD);
2293 if ((pinfo & (INSN_WRITE_FPR_S | INSN_READ_FPR_S)) != 0)
2294 mips_cprmask[1] |= 1 << ((ip->insn_opcode >> OP_SH_FS) & OP_MASK_FS);
2295 if ((pinfo & (INSN_WRITE_FPR_T | INSN_READ_FPR_T)) != 0)
2296 mips_cprmask[1] |= 1 << ((ip->insn_opcode >> OP_SH_FT) & OP_MASK_FT);
2297 if ((pinfo & INSN_READ_FPR_R) != 0)
2298 mips_cprmask[1] |= 1 << ((ip->insn_opcode >> OP_SH_FR) & OP_MASK_FR);
2299 if (pinfo & INSN_COP)
2301 /* We don't keep enough information to sort these cases out.
2302 The itbl support does keep this information however, although
2303 we currently don't support itbl fprmats as part of the cop
2304 instruction. May want to add this support in the future. */
2306 /* Never set the bit for $0, which is always zero. */
2307 mips_gprmask &= ~1 << 0;
2311 if (pinfo & (MIPS16_INSN_WRITE_X | MIPS16_INSN_READ_X))
2312 mips_gprmask |= 1 << ((ip->insn_opcode >> MIPS16OP_SH_RX)
2313 & MIPS16OP_MASK_RX);
2314 if (pinfo & (MIPS16_INSN_WRITE_Y | MIPS16_INSN_READ_Y))
2315 mips_gprmask |= 1 << ((ip->insn_opcode >> MIPS16OP_SH_RY)
2316 & MIPS16OP_MASK_RY);
2317 if (pinfo & MIPS16_INSN_WRITE_Z)
2318 mips_gprmask |= 1 << ((ip->insn_opcode >> MIPS16OP_SH_RZ)
2319 & MIPS16OP_MASK_RZ);
2320 if (pinfo & (MIPS16_INSN_WRITE_T | MIPS16_INSN_READ_T))
2321 mips_gprmask |= 1 << TREG;
2322 if (pinfo & (MIPS16_INSN_WRITE_SP | MIPS16_INSN_READ_SP))
2323 mips_gprmask |= 1 << SP;
2324 if (pinfo & (MIPS16_INSN_WRITE_31 | MIPS16_INSN_READ_31))
2325 mips_gprmask |= 1 << RA;
2326 if (pinfo & MIPS16_INSN_WRITE_GPR_Y)
2327 mips_gprmask |= 1 << MIPS16OP_EXTRACT_REG32R (ip->insn_opcode);
2328 if (pinfo & MIPS16_INSN_READ_Z)
2329 mips_gprmask |= 1 << ((ip->insn_opcode >> MIPS16OP_SH_MOVE32Z)
2330 & MIPS16OP_MASK_MOVE32Z);
2331 if (pinfo & MIPS16_INSN_READ_GPR_X)
2332 mips_gprmask |= 1 << ((ip->insn_opcode >> MIPS16OP_SH_REGR32)
2333 & MIPS16OP_MASK_REGR32);
2336 if (place == NULL && ! mips_opts.noreorder)
2338 /* Filling the branch delay slot is more complex. We try to
2339 switch the branch with the previous instruction, which we can
2340 do if the previous instruction does not set up a condition
2341 that the branch tests and if the branch is not itself the
2342 target of any branch. */
2343 if ((pinfo & INSN_UNCOND_BRANCH_DELAY)
2344 || (pinfo & INSN_COND_BRANCH_DELAY))
2346 if (mips_optimize < 2
2347 /* If we have seen .set volatile or .set nomove, don't
2349 || mips_opts.nomove != 0
2350 /* If we had to emit any NOP instructions, then we
2351 already know we can not swap. */
2353 /* If we don't even know the previous insn, we can not
2355 || ! prev_insn_valid
2356 /* If the previous insn is already in a branch delay
2357 slot, then we can not swap. */
2358 || prev_insn_is_delay_slot
2359 /* If the previous previous insn was in a .set
2360 noreorder, we can't swap. Actually, the MIPS
2361 assembler will swap in this situation. However, gcc
2362 configured -with-gnu-as will generate code like
2368 in which we can not swap the bne and INSN. If gcc is
2369 not configured -with-gnu-as, it does not output the
2370 .set pseudo-ops. We don't have to check
2371 prev_insn_unreordered, because prev_insn_valid will
2372 be 0 in that case. We don't want to use
2373 prev_prev_insn_valid, because we do want to be able
2374 to swap at the start of a function. */
2375 || prev_prev_insn_unreordered
2376 /* If the branch is itself the target of a branch, we
2377 can not swap. We cheat on this; all we check for is
2378 whether there is a label on this instruction. If
2379 there are any branches to anything other than a
2380 label, users must use .set noreorder. */
2381 || insn_labels != NULL
2382 /* If the previous instruction is in a variant frag, we
2383 can not do the swap. This does not apply to the
2384 mips16, which uses variant frags for different
2386 || (! mips_opts.mips16
2387 && prev_insn_frag->fr_type == rs_machine_dependent)
2388 /* If the branch reads the condition codes, we don't
2389 even try to swap, because in the sequence
2394 we can not swap, and I don't feel like handling that
2396 || (! mips_opts.mips16
2397 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
2398 && (pinfo & INSN_READ_COND_CODE))
2399 /* We can not swap with an instruction that requires a
2400 delay slot, becase the target of the branch might
2401 interfere with that instruction. */
2402 || (! mips_opts.mips16
2403 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
2405 /* Itbl support may require additional care here. */
2406 & (INSN_LOAD_COPROC_DELAY
2407 | INSN_COPROC_MOVE_DELAY
2408 | INSN_WRITE_COND_CODE)))
2409 || (! (hilo_interlocks
2410 || (mips_tune == CPU_R3900 && (pinfo & INSN_MULT)))
2414 || (! mips_opts.mips16
2416 && (prev_pinfo & INSN_LOAD_MEMORY_DELAY))
2417 || (! mips_opts.mips16
2418 && mips_opts.isa == ISA_MIPS1
2419 /* Itbl support may require additional care here. */
2420 && (prev_pinfo & INSN_COPROC_MEMORY_DELAY))
2421 /* We can not swap with a branch instruction. */
2423 & (INSN_UNCOND_BRANCH_DELAY
2424 | INSN_COND_BRANCH_DELAY
2425 | INSN_COND_BRANCH_LIKELY))
2426 /* We do not swap with a trap instruction, since it
2427 complicates trap handlers to have the trap
2428 instruction be in a delay slot. */
2429 || (prev_pinfo & INSN_TRAP)
2430 /* If the branch reads a register that the previous
2431 instruction sets, we can not swap. */
2432 || (! mips_opts.mips16
2433 && (prev_pinfo & INSN_WRITE_GPR_T)
2434 && insn_uses_reg (ip,
2435 ((prev_insn.insn_opcode >> OP_SH_RT)
2438 || (! mips_opts.mips16
2439 && (prev_pinfo & INSN_WRITE_GPR_D)
2440 && insn_uses_reg (ip,
2441 ((prev_insn.insn_opcode >> OP_SH_RD)
2444 || (mips_opts.mips16
2445 && (((prev_pinfo & MIPS16_INSN_WRITE_X)
2446 && insn_uses_reg (ip,
2447 ((prev_insn.insn_opcode
2449 & MIPS16OP_MASK_RX),
2451 || ((prev_pinfo & MIPS16_INSN_WRITE_Y)
2452 && insn_uses_reg (ip,
2453 ((prev_insn.insn_opcode
2455 & MIPS16OP_MASK_RY),
2457 || ((prev_pinfo & MIPS16_INSN_WRITE_Z)
2458 && insn_uses_reg (ip,
2459 ((prev_insn.insn_opcode
2461 & MIPS16OP_MASK_RZ),
2463 || ((prev_pinfo & MIPS16_INSN_WRITE_T)
2464 && insn_uses_reg (ip, TREG, MIPS_GR_REG))
2465 || ((prev_pinfo & MIPS16_INSN_WRITE_31)
2466 && insn_uses_reg (ip, RA, MIPS_GR_REG))
2467 || ((prev_pinfo & MIPS16_INSN_WRITE_GPR_Y)
2468 && insn_uses_reg (ip,
2469 MIPS16OP_EXTRACT_REG32R (prev_insn.
2472 /* If the branch writes a register that the previous
2473 instruction sets, we can not swap (we know that
2474 branches write only to RD or to $31). */
2475 || (! mips_opts.mips16
2476 && (prev_pinfo & INSN_WRITE_GPR_T)
2477 && (((pinfo & INSN_WRITE_GPR_D)
2478 && (((prev_insn.insn_opcode >> OP_SH_RT) & OP_MASK_RT)
2479 == ((ip->insn_opcode >> OP_SH_RD) & OP_MASK_RD)))
2480 || ((pinfo & INSN_WRITE_GPR_31)
2481 && (((prev_insn.insn_opcode >> OP_SH_RT)
2484 || (! mips_opts.mips16
2485 && (prev_pinfo & INSN_WRITE_GPR_D)
2486 && (((pinfo & INSN_WRITE_GPR_D)
2487 && (((prev_insn.insn_opcode >> OP_SH_RD) & OP_MASK_RD)
2488 == ((ip->insn_opcode >> OP_SH_RD) & OP_MASK_RD)))
2489 || ((pinfo & INSN_WRITE_GPR_31)
2490 && (((prev_insn.insn_opcode >> OP_SH_RD)
2493 || (mips_opts.mips16
2494 && (pinfo & MIPS16_INSN_WRITE_31)
2495 && ((prev_pinfo & MIPS16_INSN_WRITE_31)
2496 || ((prev_pinfo & MIPS16_INSN_WRITE_GPR_Y)
2497 && (MIPS16OP_EXTRACT_REG32R (prev_insn.insn_opcode)
2499 /* If the branch writes a register that the previous
2500 instruction reads, we can not swap (we know that
2501 branches only write to RD or to $31). */
2502 || (! mips_opts.mips16
2503 && (pinfo & INSN_WRITE_GPR_D)
2504 && insn_uses_reg (&prev_insn,
2505 ((ip->insn_opcode >> OP_SH_RD)
2508 || (! mips_opts.mips16
2509 && (pinfo & INSN_WRITE_GPR_31)
2510 && insn_uses_reg (&prev_insn, RA, MIPS_GR_REG))
2511 || (mips_opts.mips16
2512 && (pinfo & MIPS16_INSN_WRITE_31)
2513 && insn_uses_reg (&prev_insn, RA, MIPS_GR_REG))
2514 /* If we are generating embedded PIC code, the branch
2515 might be expanded into a sequence which uses $at, so
2516 we can't swap with an instruction which reads it. */
2517 || (mips_pic == EMBEDDED_PIC
2518 && insn_uses_reg (&prev_insn, AT, MIPS_GR_REG))
2519 /* If the previous previous instruction has a load
2520 delay, and sets a register that the branch reads, we
2522 || (! mips_opts.mips16
2523 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
2524 /* Itbl support may require additional care here. */
2525 && ((prev_prev_insn.insn_mo->pinfo & INSN_LOAD_COPROC_DELAY)
2526 || (! gpr_interlocks
2527 && (prev_prev_insn.insn_mo->pinfo
2528 & INSN_LOAD_MEMORY_DELAY)))
2529 && insn_uses_reg (ip,
2530 ((prev_prev_insn.insn_opcode >> OP_SH_RT)
2533 /* If one instruction sets a condition code and the
2534 other one uses a condition code, we can not swap. */
2535 || ((pinfo & INSN_READ_COND_CODE)
2536 && (prev_pinfo & INSN_WRITE_COND_CODE))
2537 || ((pinfo & INSN_WRITE_COND_CODE)
2538 && (prev_pinfo & INSN_READ_COND_CODE))
2539 /* If the previous instruction uses the PC, we can not
2541 || (mips_opts.mips16
2542 && (prev_pinfo & MIPS16_INSN_READ_PC))
2543 /* If the previous instruction was extended, we can not
2545 || (mips_opts.mips16 && prev_insn_extended)
2546 /* If the previous instruction had a fixup in mips16
2547 mode, we can not swap. This normally means that the
2548 previous instruction was a 4 byte branch anyhow. */
2549 || (mips_opts.mips16 && prev_insn_fixp[0])
2550 /* If the previous instruction is a sync, sync.l, or
2551 sync.p, we can not swap. */
2552 || (prev_pinfo & INSN_SYNC))
2554 /* We could do even better for unconditional branches to
2555 portions of this object file; we could pick up the
2556 instruction at the destination, put it in the delay
2557 slot, and bump the destination address. */
2559 /* Update the previous insn information. */
2560 prev_prev_insn = *ip;
2561 prev_insn.insn_mo = &dummy_opcode;
2565 /* It looks like we can actually do the swap. */
2566 if (! mips_opts.mips16)
2571 prev_f = prev_insn_frag->fr_literal + prev_insn_where;
2572 memcpy (temp, prev_f, 4);
2573 memcpy (prev_f, f, 4);
2574 memcpy (f, temp, 4);
2575 if (prev_insn_fixp[0])
2577 prev_insn_fixp[0]->fx_frag = frag_now;
2578 prev_insn_fixp[0]->fx_where = f - frag_now->fr_literal;
2580 if (prev_insn_fixp[1])
2582 prev_insn_fixp[1]->fx_frag = frag_now;
2583 prev_insn_fixp[1]->fx_where = f - frag_now->fr_literal;
2585 if (prev_insn_fixp[2])
2587 prev_insn_fixp[2]->fx_frag = frag_now;
2588 prev_insn_fixp[2]->fx_where = f - frag_now->fr_literal;
2590 if (prev_insn_fixp[0] && HAVE_NEWABI
2591 && prev_insn_frag != frag_now
2592 && (prev_insn_fixp[0]->fx_r_type
2593 == BFD_RELOC_MIPS_GOT_DISP
2594 || (prev_insn_fixp[0]->fx_r_type
2595 == BFD_RELOC_MIPS_CALL16)))
2597 /* To avoid confusion in tc_gen_reloc, we must
2598 ensure that this does not become a variant
2600 force_new_frag = TRUE;
2604 fixp[0]->fx_frag = prev_insn_frag;
2605 fixp[0]->fx_where = prev_insn_where;
2609 fixp[1]->fx_frag = prev_insn_frag;
2610 fixp[1]->fx_where = prev_insn_where;
2614 fixp[2]->fx_frag = prev_insn_frag;
2615 fixp[2]->fx_where = prev_insn_where;
2623 assert (prev_insn_fixp[0] == NULL);
2624 assert (prev_insn_fixp[1] == NULL);
2625 assert (prev_insn_fixp[2] == NULL);
2626 prev_f = prev_insn_frag->fr_literal + prev_insn_where;
2627 memcpy (temp, prev_f, 2);
2628 memcpy (prev_f, f, 2);
2629 if (*reloc_type != BFD_RELOC_MIPS16_JMP)
2631 assert (*reloc_type == BFD_RELOC_UNUSED);
2632 memcpy (f, temp, 2);
2636 memcpy (f, f + 2, 2);
2637 memcpy (f + 2, temp, 2);
2641 fixp[0]->fx_frag = prev_insn_frag;
2642 fixp[0]->fx_where = prev_insn_where;
2646 fixp[1]->fx_frag = prev_insn_frag;
2647 fixp[1]->fx_where = prev_insn_where;
2651 fixp[2]->fx_frag = prev_insn_frag;
2652 fixp[2]->fx_where = prev_insn_where;
2656 /* Update the previous insn information; leave prev_insn
2658 prev_prev_insn = *ip;
2660 prev_insn_is_delay_slot = 1;
2662 /* If that was an unconditional branch, forget the previous
2663 insn information. */
2664 if (pinfo & INSN_UNCOND_BRANCH_DELAY)
2666 prev_prev_insn.insn_mo = &dummy_opcode;
2667 prev_insn.insn_mo = &dummy_opcode;
2670 prev_insn_fixp[0] = NULL;
2671 prev_insn_fixp[1] = NULL;
2672 prev_insn_fixp[2] = NULL;
2673 prev_insn_reloc_type[0] = BFD_RELOC_UNUSED;
2674 prev_insn_reloc_type[1] = BFD_RELOC_UNUSED;
2675 prev_insn_reloc_type[2] = BFD_RELOC_UNUSED;
2676 prev_insn_extended = 0;
2678 else if (pinfo & INSN_COND_BRANCH_LIKELY)
2680 /* We don't yet optimize a branch likely. What we should do
2681 is look at the target, copy the instruction found there
2682 into the delay slot, and increment the branch to jump to
2683 the next instruction. */
2685 /* Update the previous insn information. */
2686 prev_prev_insn = *ip;
2687 prev_insn.insn_mo = &dummy_opcode;
2688 prev_insn_fixp[0] = NULL;
2689 prev_insn_fixp[1] = NULL;
2690 prev_insn_fixp[2] = NULL;
2691 prev_insn_reloc_type[0] = BFD_RELOC_UNUSED;
2692 prev_insn_reloc_type[1] = BFD_RELOC_UNUSED;
2693 prev_insn_reloc_type[2] = BFD_RELOC_UNUSED;
2694 prev_insn_extended = 0;
2698 /* Update the previous insn information. */
2700 prev_prev_insn.insn_mo = &dummy_opcode;
2702 prev_prev_insn = prev_insn;
2705 /* Any time we see a branch, we always fill the delay slot
2706 immediately; since this insn is not a branch, we know it
2707 is not in a delay slot. */
2708 prev_insn_is_delay_slot = 0;
2710 prev_insn_fixp[0] = fixp[0];
2711 prev_insn_fixp[1] = fixp[1];
2712 prev_insn_fixp[2] = fixp[2];
2713 prev_insn_reloc_type[0] = reloc_type[0];
2714 prev_insn_reloc_type[1] = reloc_type[1];
2715 prev_insn_reloc_type[2] = reloc_type[2];
2716 if (mips_opts.mips16)
2717 prev_insn_extended = (ip->use_extend
2718 || *reloc_type > BFD_RELOC_UNUSED);
2721 prev_prev_insn_unreordered = prev_insn_unreordered;
2722 prev_insn_unreordered = 0;
2723 prev_insn_frag = frag_now;
2724 prev_insn_where = f - frag_now->fr_literal;
2725 prev_insn_valid = 1;
2727 else if (place == NULL)
2729 /* We need to record a bit of information even when we are not
2730 reordering, in order to determine the base address for mips16
2731 PC relative relocs. */
2732 prev_prev_insn = prev_insn;
2734 prev_insn_reloc_type[0] = reloc_type[0];
2735 prev_insn_reloc_type[1] = reloc_type[1];
2736 prev_insn_reloc_type[2] = reloc_type[2];
2737 prev_prev_insn_unreordered = prev_insn_unreordered;
2738 prev_insn_unreordered = 1;
2741 /* We just output an insn, so the next one doesn't have a label. */
2742 mips_clear_insn_labels ();
2744 /* We must ensure that the frag to which an instruction that was
2745 moved from a non-variant frag doesn't become a variant frag,
2746 otherwise tc_gen_reloc may get confused. */
2749 frag_wane (frag_now);
2754 /* This function forgets that there was any previous instruction or
2755 label. If PRESERVE is non-zero, it remembers enough information to
2756 know whether nops are needed before a noreorder section. */
2759 mips_no_prev_insn (preserve)
2764 prev_insn.insn_mo = &dummy_opcode;
2765 prev_prev_insn.insn_mo = &dummy_opcode;
2766 prev_nop_frag = NULL;
2767 prev_nop_frag_holds = 0;
2768 prev_nop_frag_required = 0;
2769 prev_nop_frag_since = 0;
2771 prev_insn_valid = 0;
2772 prev_insn_is_delay_slot = 0;
2773 prev_insn_unreordered = 0;
2774 prev_insn_extended = 0;
2775 prev_insn_reloc_type[0] = BFD_RELOC_UNUSED;
2776 prev_insn_reloc_type[1] = BFD_RELOC_UNUSED;
2777 prev_insn_reloc_type[2] = BFD_RELOC_UNUSED;
2778 prev_prev_insn_unreordered = 0;
2779 mips_clear_insn_labels ();
2782 /* This function must be called whenever we turn on noreorder or emit
2783 something other than instructions. It inserts any NOPS which might
2784 be needed by the previous instruction, and clears the information
2785 kept for the previous instructions. The INSNS parameter is true if
2786 instructions are to follow. */
2789 mips_emit_delays (insns)
2792 if (! mips_opts.noreorder)
2797 if ((! mips_opts.mips16
2798 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
2799 && (! cop_interlocks
2800 && (prev_insn.insn_mo->pinfo
2801 & (INSN_LOAD_COPROC_DELAY
2802 | INSN_COPROC_MOVE_DELAY
2803 | INSN_WRITE_COND_CODE))))
2804 || (! hilo_interlocks
2805 && (prev_insn.insn_mo->pinfo
2808 || (! mips_opts.mips16
2810 && (prev_insn.insn_mo->pinfo
2811 & INSN_LOAD_MEMORY_DELAY))
2812 || (! mips_opts.mips16
2813 && mips_opts.isa == ISA_MIPS1
2814 && (prev_insn.insn_mo->pinfo
2815 & INSN_COPROC_MEMORY_DELAY)))
2817 /* Itbl support may require additional care here. */
2819 if ((! mips_opts.mips16
2820 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
2821 && (! cop_interlocks
2822 && prev_insn.insn_mo->pinfo & INSN_WRITE_COND_CODE))
2823 || (! hilo_interlocks
2824 && ((prev_insn.insn_mo->pinfo & INSN_READ_HI)
2825 || (prev_insn.insn_mo->pinfo & INSN_READ_LO))))
2828 if (prev_insn_unreordered)
2831 else if ((! mips_opts.mips16
2832 && ISA_HAS_COPROC_DELAYS (mips_opts.isa)
2833 && (! cop_interlocks
2834 && prev_prev_insn.insn_mo->pinfo & INSN_WRITE_COND_CODE))
2835 || (! hilo_interlocks
2836 && ((prev_prev_insn.insn_mo->pinfo & INSN_READ_HI)
2837 || (prev_prev_insn.insn_mo->pinfo & INSN_READ_LO))))
2839 /* Itbl support may require additional care here. */
2840 if (! prev_prev_insn_unreordered)
2844 if (mips_fix_4122_bugs && prev_insn.insn_mo->name)
2847 const char *pn = prev_insn.insn_mo->name;
2848 if (strncmp(pn, "macc", 4) == 0
2849 || strncmp(pn, "dmacc", 5) == 0
2850 || strncmp(pn, "dmult", 5) == 0)
2854 if (nops < min_nops)
2860 struct insn_label_list *l;
2864 /* Record the frag which holds the nop instructions, so
2865 that we can remove them if we don't need them. */
2866 frag_grow (mips_opts.mips16 ? nops * 2 : nops * 4);
2867 prev_nop_frag = frag_now;
2868 prev_nop_frag_holds = nops;
2869 prev_nop_frag_required = 0;
2870 prev_nop_frag_since = 0;
2873 for (; nops > 0; --nops)
2878 /* Move on to a new frag, so that it is safe to simply
2879 decrease the size of prev_nop_frag. */
2880 frag_wane (frag_now);
2884 for (l = insn_labels; l != NULL; l = l->next)
2888 assert (S_GET_SEGMENT (l->label) == now_seg);
2889 symbol_set_frag (l->label, frag_now);
2890 val = (valueT) frag_now_fix ();
2891 /* mips16 text labels are stored as odd. */
2892 if (mips_opts.mips16)
2894 S_SET_VALUE (l->label, val);
2899 /* Mark instruction labels in mips16 mode. */
2901 mips16_mark_labels ();
2903 mips_no_prev_insn (insns);
2906 /* Build an instruction created by a macro expansion. This is passed
2907 a pointer to the count of instructions created so far, an
2908 expression, the name of the instruction to build, an operand format
2909 string, and corresponding arguments. */
2913 macro_build (char *place,
2921 macro_build (place, counter, ep, name, fmt, va_alist)
2930 struct mips_cl_insn insn;
2931 bfd_reloc_code_real_type r[3];
2935 va_start (args, fmt);
2941 * If the macro is about to expand into a second instruction,
2942 * print a warning if needed. We need to pass ip as a parameter
2943 * to generate a better warning message here...
2945 if (mips_opts.warn_about_macros && place == NULL && *counter == 1)
2946 as_warn (_("Macro instruction expanded into multiple instructions"));
2949 * If the macro is about to expand into a second instruction,
2950 * and it is in a delay slot, print a warning.
2954 && mips_opts.noreorder
2955 && (prev_prev_insn.insn_mo->pinfo
2956 & (INSN_UNCOND_BRANCH_DELAY | INSN_COND_BRANCH_DELAY
2957 | INSN_COND_BRANCH_LIKELY)) != 0)
2958 as_warn (_("Macro instruction expanded into multiple instructions in a branch delay slot"));
2961 ++*counter; /* bump instruction counter */
2963 if (mips_opts.mips16)
2965 mips16_macro_build (place, counter, ep, name, fmt, args);
2970 r[0] = BFD_RELOC_UNUSED;
2971 r[1] = BFD_RELOC_UNUSED;
2972 r[2] = BFD_RELOC_UNUSED;
2973 insn.insn_mo = (struct mips_opcode *) hash_find (op_hash, name);
2974 assert (insn.insn_mo);
2975 assert (strcmp (name, insn.insn_mo->name) == 0);
2977 /* Search until we get a match for NAME. */
2980 /* It is assumed here that macros will never generate
2981 MDMX or MIPS-3D instructions. */
2982 if (strcmp (fmt, insn.insn_mo->args) == 0
2983 && insn.insn_mo->pinfo != INSN_MACRO
2984 && OPCODE_IS_MEMBER (insn.insn_mo,
2986 | (file_ase_mips16 ? INSN_MIPS16 : 0)),
2988 && (mips_arch != CPU_R4650 || (insn.insn_mo->pinfo & FP_D) == 0))
2992 assert (insn.insn_mo->name);
2993 assert (strcmp (name, insn.insn_mo->name) == 0);
2996 insn.insn_opcode = insn.insn_mo->match;
3012 insn.insn_opcode |= va_arg (args, int) << OP_SH_RT;
3016 insn.insn_opcode |= va_arg (args, int) << OP_SH_CODE;
3021 insn.insn_opcode |= va_arg (args, int) << OP_SH_FT;
3027 insn.insn_opcode |= va_arg (args, int) << OP_SH_RD;
3032 int tmp = va_arg (args, int);
3034 insn.insn_opcode |= tmp << OP_SH_RT;
3035 insn.insn_opcode |= tmp << OP_SH_RD;
3041 insn.insn_opcode |= va_arg (args, int) << OP_SH_FS;
3048 insn.insn_opcode |= va_arg (args, int) << OP_SH_SHAMT;
3052 insn.insn_opcode |= va_arg (args, int) << OP_SH_FD;
3056 insn.insn_opcode |= va_arg (args, int) << OP_SH_CODE20;
3060 insn.insn_opcode |= va_arg (args, int) << OP_SH_CODE19;
3064 insn.insn_opcode |= va_arg (args, int) << OP_SH_CODE2;
3071 insn.insn_opcode |= va_arg (args, int) << OP_SH_RS;
3077 *r = (bfd_reloc_code_real_type) va_arg (args, int);
3078 assert (*r == BFD_RELOC_GPREL16
3079 || *r == BFD_RELOC_MIPS_LITERAL
3080 || *r == BFD_RELOC_MIPS_HIGHER
3081 || *r == BFD_RELOC_HI16_S
3082 || *r == BFD_RELOC_LO16
3083 || *r == BFD_RELOC_MIPS_GOT16
3084 || *r == BFD_RELOC_MIPS_CALL16
3085 || *r == BFD_RELOC_MIPS_GOT_DISP
3086 || *r == BFD_RELOC_MIPS_GOT_PAGE
3087 || *r == BFD_RELOC_MIPS_GOT_OFST
3088 || *r == BFD_RELOC_MIPS_GOT_LO16
3089 || *r == BFD_RELOC_MIPS_CALL_LO16
3090 || (ep->X_op == O_subtract
3091 && *r == BFD_RELOC_PCREL_LO16));
3095 *r = (bfd_reloc_code_real_type) va_arg (args, int);
3097 && (ep->X_op == O_constant
3098 || (ep->X_op == O_symbol
3099 && (*r == BFD_RELOC_MIPS_HIGHEST
3100 || *r == BFD_RELOC_HI16_S
3101 || *r == BFD_RELOC_HI16
3102 || *r == BFD_RELOC_GPREL16
3103 || *r == BFD_RELOC_MIPS_GOT_HI16
3104 || *r == BFD_RELOC_MIPS_CALL_HI16))
3105 || (ep->X_op == O_subtract
3106 && *r == BFD_RELOC_PCREL_HI16_S)));
3110 assert (ep != NULL);
3112 * This allows macro() to pass an immediate expression for
3113 * creating short branches without creating a symbol.
3114 * Note that the expression still might come from the assembly
3115 * input, in which case the value is not checked for range nor
3116 * is a relocation entry generated (yuck).
3118 if (ep->X_op == O_constant)
3120 insn.insn_opcode |= (ep->X_add_number >> 2) & 0xffff;
3124 *r = BFD_RELOC_16_PCREL_S2;
3128 assert (ep != NULL);
3129 *r = BFD_RELOC_MIPS_JMP;
3133 insn.insn_opcode |= va_arg (args, unsigned long);
3142 assert (*r == BFD_RELOC_UNUSED ? ep == NULL : ep != NULL);
3144 append_insn (place, &insn, ep, r);
3148 mips16_macro_build (place, counter, ep, name, fmt, args)
3150 int *counter ATTRIBUTE_UNUSED;
3156 struct mips_cl_insn insn;
3157 bfd_reloc_code_real_type r[3]
3158 = {BFD_RELOC_UNUSED, BFD_RELOC_UNUSED, BFD_RELOC_UNUSED};
3160 insn.insn_mo = (struct mips_opcode *) hash_find (mips16_op_hash, name);
3161 assert (insn.insn_mo);
3162 assert (strcmp (name, insn.insn_mo->name) == 0);
3164 while (strcmp (fmt, insn.insn_mo->args) != 0
3165 || insn.insn_mo->pinfo == INSN_MACRO)
3168 assert (insn.insn_mo->name);
3169 assert (strcmp (name, insn.insn_mo->name) == 0);
3172 insn.insn_opcode = insn.insn_mo->match;
3173 insn.use_extend = FALSE;
3192 insn.insn_opcode |= va_arg (args, int) << MIPS16OP_SH_RY;
3197 insn.insn_opcode |= va_arg (args, int) << MIPS16OP_SH_RX;
3201 insn.insn_opcode |= va_arg (args, int) << MIPS16OP_SH_RZ;
3205 insn.insn_opcode |= va_arg (args, int) << MIPS16OP_SH_MOVE32Z;
3215 insn.insn_opcode |= va_arg (args, int) << MIPS16OP_SH_REGR32;
3222 regno = va_arg (args, int);
3223 regno = ((regno & 7) << 2) | ((regno & 0x18) >> 3);
3224 insn.insn_opcode |= regno << MIPS16OP_SH_REG32R;
3245 assert (ep != NULL);
3247 if (ep->X_op != O_constant)
3248 *r = (int) BFD_RELOC_UNUSED + c;
3251 mips16_immed (NULL, 0, c, ep->X_add_number, FALSE, FALSE,
3252 FALSE, &insn.insn_opcode, &insn.use_extend,
3255 *r = BFD_RELOC_UNUSED;
3261 insn.insn_opcode |= va_arg (args, int) << MIPS16OP_SH_IMM6;
3268 assert (*r == BFD_RELOC_UNUSED ? ep == NULL : ep != NULL);
3270 append_insn (place, &insn, ep, r);
3274 * Generate a "jalr" instruction with a relocation hint to the called
3275 * function. This occurs in NewABI PIC code.
3278 macro_build_jalr (icnt, ep)
3289 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "jalr", "d,s",
3292 fix_new_exp (frag_now, f - frag_now->fr_literal,
3293 4, ep, FALSE, BFD_RELOC_MIPS_JALR);
3297 * Generate a "lui" instruction.
3300 macro_build_lui (place, counter, ep, regnum)
3306 expressionS high_expr;
3307 struct mips_cl_insn insn;
3308 bfd_reloc_code_real_type r[3]
3309 = {BFD_RELOC_UNUSED, BFD_RELOC_UNUSED, BFD_RELOC_UNUSED};
3310 const char *name = "lui";
3311 const char *fmt = "t,u";
3313 assert (! mips_opts.mips16);
3319 high_expr.X_op = O_constant;
3320 high_expr.X_add_number = ep->X_add_number;
3323 if (high_expr.X_op == O_constant)
3325 /* we can compute the instruction now without a relocation entry */
3326 high_expr.X_add_number = ((high_expr.X_add_number + 0x8000)
3328 *r = BFD_RELOC_UNUSED;
3332 assert (ep->X_op == O_symbol);
3333 /* _gp_disp is a special case, used from s_cpload. */
3334 assert (mips_pic == NO_PIC
3336 && strcmp (S_GET_NAME (ep->X_add_symbol), "_gp_disp") == 0));
3337 *r = BFD_RELOC_HI16_S;
3341 * If the macro is about to expand into a second instruction,
3342 * print a warning if needed. We need to pass ip as a parameter
3343 * to generate a better warning message here...
3345 if (mips_opts.warn_about_macros && place == NULL && *counter == 1)
3346 as_warn (_("Macro instruction expanded into multiple instructions"));
3349 ++*counter; /* bump instruction counter */
3351 insn.insn_mo = (struct mips_opcode *) hash_find (op_hash, name);
3352 assert (insn.insn_mo);
3353 assert (strcmp (name, insn.insn_mo->name) == 0);
3354 assert (strcmp (fmt, insn.insn_mo->args) == 0);
3356 insn.insn_opcode = insn.insn_mo->match | (regnum << OP_SH_RT);
3357 if (*r == BFD_RELOC_UNUSED)
3359 insn.insn_opcode |= high_expr.X_add_number;
3360 append_insn (place, &insn, NULL, r);
3363 append_insn (place, &insn, &high_expr, r);
3366 /* Generate a sequence of instructions to do a load or store from a constant
3367 offset off of a base register (breg) into/from a target register (treg),
3368 using AT if necessary. */
3370 macro_build_ldst_constoffset (place, counter, ep, op, treg, breg)
3377 assert (ep->X_op == O_constant);
3379 /* Right now, this routine can only handle signed 32-bit contants. */
3380 if (! IS_SEXT_32BIT_NUM(ep->X_add_number))
3381 as_warn (_("operand overflow"));
3383 if (IS_SEXT_16BIT_NUM(ep->X_add_number))
3385 /* Signed 16-bit offset will fit in the op. Easy! */
3386 macro_build (place, counter, ep, op, "t,o(b)", treg,
3387 (int) BFD_RELOC_LO16, breg);
3391 /* 32-bit offset, need multiple instructions and AT, like:
3392 lui $tempreg,const_hi (BFD_RELOC_HI16_S)
3393 addu $tempreg,$tempreg,$breg
3394 <op> $treg,const_lo($tempreg) (BFD_RELOC_LO16)
3395 to handle the complete offset. */
3396 macro_build_lui (place, counter, ep, AT);
3399 macro_build (place, counter, (expressionS *) NULL, ADDRESS_ADD_INSN,
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, ADDRESS_ADDI_INSN,
3887 "t,r,j", reg, mips_gp_register,
3888 (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, ADDRESS_ADDI_INSN,
3898 "t,r,j", reg, reg, (int) BFD_RELOC_LO16);
3901 else if (mips_pic == SVR4_PIC && ! mips_big_got)
3905 /* If this is a reference to an external symbol, we want
3906 lw $reg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
3908 lw $reg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
3910 addiu $reg,$reg,<sym> (BFD_RELOC_LO16)
3911 If there is a constant, it must be added in after.
3913 If we have NewABI, we want
3914 lw $reg,<sym+cst>($gp) (BFD_RELOC_MIPS_GOT_DISP)
3915 unless we're referencing a global symbol with a non-zero
3916 offset, in which case cst must be added separately. */
3921 if (ep->X_add_number)
3923 frag_now->tc_frag_data.tc_fr_offset =
3924 ex.X_add_number = ep->X_add_number;
3925 ep->X_add_number = 0;
3926 macro_build ((char *) NULL, counter, ep, ADDRESS_LOAD_INSN,
3927 "t,o(b)", reg, (int) BFD_RELOC_MIPS_GOT_DISP,
3929 if (ex.X_add_number < -0x8000 || ex.X_add_number >= 0x8000)
3930 as_bad (_("PIC code offset overflow (max 16 signed bits)"));
3931 ex.X_op = O_constant;
3932 macro_build ((char *) NULL, counter, &ex, ADDRESS_ADDI_INSN,
3933 "t,r,j", reg, reg, (int) BFD_RELOC_LO16);
3934 p = frag_var (rs_machine_dependent, 8, 0,
3935 RELAX_ENCODE (8, 4, 0, 0, 0,
3936 mips_opts.warn_about_macros),
3937 ep->X_add_symbol, 0, (char *) NULL);
3938 ep->X_add_number = ex.X_add_number;
3941 macro_build (p, counter, ep, ADDRESS_LOAD_INSN, "t,o(b)", reg,
3942 (int) BFD_RELOC_MIPS_GOT_DISP, mips_gp_register);
3946 /* To avoid confusion in tc_gen_reloc, we must ensure
3947 that this does not become a variant frag. */
3948 frag_wane (frag_now);
3954 ex.X_add_number = ep->X_add_number;
3955 ep->X_add_number = 0;
3957 macro_build ((char *) NULL, counter, ep, ADDRESS_LOAD_INSN,
3958 "t,o(b)", reg, (int) BFD_RELOC_MIPS_GOT16,
3960 macro_build ((char *) NULL, counter, (expressionS *) NULL, "nop", "");
3961 p = frag_var (rs_machine_dependent, 4, 0,
3962 RELAX_ENCODE (0, 4, -8, 0, 0, mips_opts.warn_about_macros),
3963 ep->X_add_symbol, (offsetT) 0, (char *) NULL);
3964 macro_build (p, counter, ep, ADDRESS_ADDI_INSN,
3965 "t,r,j", reg, reg, (int) BFD_RELOC_LO16);
3967 if (ex.X_add_number != 0)
3969 if (ex.X_add_number < -0x8000 || ex.X_add_number >= 0x8000)
3970 as_bad (_("PIC code offset overflow (max 16 signed bits)"));
3971 ex.X_op = O_constant;
3972 macro_build ((char *) NULL, counter, &ex, ADDRESS_ADDI_INSN,
3973 "t,r,j", reg, reg, (int) BFD_RELOC_LO16);
3977 else if (mips_pic == SVR4_PIC)
3982 /* This is the large GOT case. If this is a reference to an
3983 external symbol, we want
3984 lui $reg,<sym> (BFD_RELOC_MIPS_GOT_HI16)
3986 lw $reg,<sym>($reg) (BFD_RELOC_MIPS_GOT_LO16)
3988 Otherwise, for a reference to a local symbol in old ABI, we want
3989 lw $reg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
3991 addiu $reg,$reg,<sym> (BFD_RELOC_LO16)
3992 If there is a constant, it must be added in after.
3994 In the NewABI, for local symbols, with or without offsets, we want:
3995 lw $reg,<sym>($gp) (BFD_RELOC_MIPS_GOT_PAGE)
3996 addiu $reg,$reg,<sym> (BFD_RELOC_MIPS_GOT_OFST)
4002 frag_now->tc_frag_data.tc_fr_offset =
4003 ex.X_add_number = ep->X_add_number;
4004 ep->X_add_number = 0;
4005 macro_build ((char *) NULL, counter, ep, "lui", "t,u", reg,
4006 (int) BFD_RELOC_MIPS_GOT_HI16);
4007 macro_build ((char *) NULL, counter, (expressionS *) NULL,
4008 ADDRESS_ADD_INSN, "d,v,t", reg, reg, mips_gp_register);
4009 macro_build ((char *) NULL, counter, ep, ADDRESS_LOAD_INSN,
4010 "t,o(b)", reg, (int) BFD_RELOC_MIPS_GOT_LO16, reg);
4011 if (ex.X_add_number < -0x8000 || ex.X_add_number >= 0x8000)
4012 as_bad (_("PIC code offset overflow (max 16 signed bits)"));
4013 else if (ex.X_add_number)
4015 ex.X_op = O_constant;
4016 macro_build ((char *) NULL, counter, &ex, ADDRESS_ADDI_INSN,
4017 "t,r,j", reg, reg, (int) BFD_RELOC_LO16);
4020 ep->X_add_number = ex.X_add_number;
4021 p = frag_var (rs_machine_dependent, 8, 0,
4022 RELAX_ENCODE (ex.X_add_number ? 16 : 12, 8, 0, 4, 0,
4023 mips_opts.warn_about_macros),
4024 ep->X_add_symbol, 0, (char *) NULL);
4025 macro_build (p, counter, ep, ADDRESS_LOAD_INSN, "t,o(b)", reg,
4026 (int) BFD_RELOC_MIPS_GOT_PAGE, mips_gp_register);
4027 macro_build (p + 4, counter, ep, ADDRESS_ADDI_INSN, "t,r,j",
4028 reg, reg, (int) BFD_RELOC_MIPS_GOT_OFST);
4032 ex.X_add_number = ep->X_add_number;
4033 ep->X_add_number = 0;
4034 if (reg_needs_delay (mips_gp_register))
4039 macro_build ((char *) NULL, counter, ep, "lui", "t,u", reg,
4040 (int) BFD_RELOC_MIPS_GOT_HI16);
4041 macro_build ((char *) NULL, counter, (expressionS *) NULL,
4042 ADDRESS_ADD_INSN, "d,v,t", reg, reg, mips_gp_register);
4043 macro_build ((char *) NULL, counter, ep, ADDRESS_LOAD_INSN,
4044 "t,o(b)", reg, (int) BFD_RELOC_MIPS_GOT_LO16, reg);
4045 p = frag_var (rs_machine_dependent, 12 + off, 0,
4046 RELAX_ENCODE (12, 12 + off, off, 8 + off, 0,
4047 mips_opts.warn_about_macros),
4048 ep->X_add_symbol, 0, NULL);
4051 /* We need a nop before loading from $gp. This special
4052 check is required because the lui which starts the main
4053 instruction stream does not refer to $gp, and so will not
4054 insert the nop which may be required. */
4055 macro_build (p, counter, (expressionS *) NULL, "nop", "");
4058 macro_build (p, counter, ep, ADDRESS_LOAD_INSN, "t,o(b)", reg,
4059 (int) BFD_RELOC_MIPS_GOT16, mips_gp_register);
4061 macro_build (p, counter, (expressionS *) NULL, "nop", "");
4063 macro_build (p, counter, ep, ADDRESS_ADDI_INSN,
4064 "t,r,j", reg, reg, (int) BFD_RELOC_LO16);
4066 if (ex.X_add_number != 0)
4068 if (ex.X_add_number < -0x8000 || ex.X_add_number >= 0x8000)
4069 as_bad (_("PIC code offset overflow (max 16 signed bits)"));
4070 ex.X_op = O_constant;
4071 macro_build ((char *) NULL, counter, &ex, ADDRESS_ADDI_INSN,
4072 "t,r,j", reg, reg, (int) BFD_RELOC_LO16);
4076 else if (mips_pic == EMBEDDED_PIC)
4079 addiu $reg,$gp,<sym> (BFD_RELOC_GPREL16)
4081 macro_build ((char *) NULL, counter, ep, ADDRESS_ADDI_INSN,
4082 "t,r,j", reg, mips_gp_register, (int) BFD_RELOC_GPREL16);
4088 /* Move the contents of register SOURCE into register DEST. */
4091 move_register (counter, dest, source)
4096 macro_build ((char *) NULL, counter, (expressionS *) NULL,
4097 HAVE_32BIT_GPRS ? "addu" : "daddu",
4098 "d,v,t", dest, source, 0);
4103 * This routine implements the seemingly endless macro or synthesized
4104 * instructions and addressing modes in the mips assembly language. Many
4105 * of these macros are simple and are similar to each other. These could
4106 * probably be handled by some kind of table or grammer aproach instead of
4107 * this verbose method. Others are not simple macros but are more like
4108 * optimizing code generation.
4109 * One interesting optimization is when several store macros appear
4110 * consecutivly that would load AT with the upper half of the same address.
4111 * The ensuing load upper instructions are ommited. This implies some kind
4112 * of global optimization. We currently only optimize within a single macro.
4113 * For many of the load and store macros if the address is specified as a
4114 * constant expression in the first 64k of memory (ie ld $2,0x4000c) we
4115 * first load register 'at' with zero and use it as the base register. The
4116 * mips assembler simply uses register $zero. Just one tiny optimization
4121 struct mips_cl_insn *ip;
4123 register int treg, sreg, dreg, breg;
4139 bfd_reloc_code_real_type r;
4140 int hold_mips_optimize;
4142 assert (! mips_opts.mips16);
4144 treg = (ip->insn_opcode >> 16) & 0x1f;
4145 dreg = (ip->insn_opcode >> 11) & 0x1f;
4146 sreg = breg = (ip->insn_opcode >> 21) & 0x1f;
4147 mask = ip->insn_mo->mask;
4149 expr1.X_op = O_constant;
4150 expr1.X_op_symbol = NULL;
4151 expr1.X_add_symbol = NULL;
4152 expr1.X_add_number = 1;
4154 /* Umatched fixups should not be put in the same frag as a relaxable
4155 macro. For example, suppose we have:
4159 addiu $4,$4,%lo(l1) # 3
4161 If instructions 1 and 2 were put in the same frag, md_frob_file would
4162 move the fixup for #1 after the fixups for the "unrelaxed" version of
4163 #2. This would confuse tc_gen_reloc, which expects the relocations
4164 for #2 to be the last for that frag.
4166 Also, if tc_gen_reloc sees certain relocations in a variant frag,
4167 it assumes that they belong to a relaxable macro. We mustn't put
4168 other uses of such relocations into a variant frag.
4170 To avoid both problems, finish the current frag it contains a
4171 %reloc() operator. The macro then goes into a new frag. */
4172 if (prev_reloc_op_frag == frag_now)
4174 frag_wane (frag_now);
4188 mips_emit_delays (TRUE);
4189 ++mips_opts.noreorder;
4190 mips_any_noreorder = 1;
4192 expr1.X_add_number = 8;
4193 macro_build ((char *) NULL, &icnt, &expr1, "bgez", "s,p", sreg);
4195 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "",
4198 move_register (&icnt, dreg, sreg);
4199 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
4200 dbl ? "dsub" : "sub", "d,v,t", dreg, 0, sreg);
4202 --mips_opts.noreorder;
4223 if (imm_expr.X_op == O_constant
4224 && imm_expr.X_add_number >= -0x8000
4225 && imm_expr.X_add_number < 0x8000)
4227 macro_build ((char *) NULL, &icnt, &imm_expr, s, "t,r,j", treg, sreg,
4228 (int) BFD_RELOC_LO16);
4231 load_register (&icnt, AT, &imm_expr, dbl);
4232 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s2, "d,v,t",
4252 if (imm_expr.X_op == O_constant
4253 && imm_expr.X_add_number >= 0
4254 && imm_expr.X_add_number < 0x10000)
4256 if (mask != M_NOR_I)
4257 macro_build ((char *) NULL, &icnt, &imm_expr, s, "t,r,i", treg,
4258 sreg, (int) BFD_RELOC_LO16);
4261 macro_build ((char *) NULL, &icnt, &imm_expr, "ori", "t,r,i",
4262 treg, sreg, (int) BFD_RELOC_LO16);
4263 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nor",
4264 "d,v,t", treg, treg, 0);
4269 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_GPRS);
4270 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s2, "d,v,t",
4288 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
4290 macro_build ((char *) NULL, &icnt, &offset_expr, s, "s,t,p", sreg,
4294 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_GPRS);
4295 macro_build ((char *) NULL, &icnt, &offset_expr, s, "s,t,p", sreg, AT);
4303 macro_build ((char *) NULL, &icnt, &offset_expr,
4304 likely ? "bgezl" : "bgez", "s,p", sreg);
4309 macro_build ((char *) NULL, &icnt, &offset_expr,
4310 likely ? "blezl" : "blez", "s,p", treg);
4313 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "slt", "d,v,t",
4315 macro_build ((char *) NULL, &icnt, &offset_expr,
4316 likely ? "beql" : "beq", "s,t,p", AT, 0);
4322 /* check for > max integer */
4323 maxnum = 0x7fffffff;
4324 if (HAVE_64BIT_GPRS && sizeof (maxnum) > 4)
4331 if (imm_expr.X_op == O_constant
4332 && imm_expr.X_add_number >= maxnum
4333 && (HAVE_32BIT_GPRS || sizeof (maxnum) > 4))
4336 /* result is always false */
4340 as_warn (_("Branch %s is always false (nop)"),
4342 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop",
4348 as_warn (_("Branch likely %s is always false"),
4350 macro_build ((char *) NULL, &icnt, &offset_expr, "bnel",
4355 if (imm_expr.X_op != O_constant)
4356 as_bad (_("Unsupported large constant"));
4357 ++imm_expr.X_add_number;
4361 if (mask == M_BGEL_I)
4363 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
4365 macro_build ((char *) NULL, &icnt, &offset_expr,
4366 likely ? "bgezl" : "bgez", "s,p", sreg);
4369 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 1)
4371 macro_build ((char *) NULL, &icnt, &offset_expr,
4372 likely ? "bgtzl" : "bgtz", "s,p", sreg);
4375 maxnum = 0x7fffffff;
4376 if (HAVE_64BIT_GPRS && sizeof (maxnum) > 4)
4383 maxnum = - maxnum - 1;
4384 if (imm_expr.X_op == O_constant
4385 && imm_expr.X_add_number <= maxnum
4386 && (HAVE_32BIT_GPRS || sizeof (maxnum) > 4))
4389 /* result is always true */
4390 as_warn (_("Branch %s is always true"), ip->insn_mo->name);
4391 macro_build ((char *) NULL, &icnt, &offset_expr, "b", "p");
4394 set_at (&icnt, sreg, 0);
4395 macro_build ((char *) NULL, &icnt, &offset_expr,
4396 likely ? "beql" : "beq", "s,t,p", AT, 0);
4406 macro_build ((char *) NULL, &icnt, &offset_expr,
4407 likely ? "beql" : "beq", "s,t,p", 0, treg);
4410 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sltu",
4411 "d,v,t", AT, sreg, treg);
4412 macro_build ((char *) NULL, &icnt, &offset_expr,
4413 likely ? "beql" : "beq", "s,t,p", AT, 0);
4421 && imm_expr.X_op == O_constant
4422 && imm_expr.X_add_number == (offsetT) 0xffffffff))
4424 if (imm_expr.X_op != O_constant)
4425 as_bad (_("Unsupported large constant"));
4426 ++imm_expr.X_add_number;
4430 if (mask == M_BGEUL_I)
4432 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
4434 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 1)
4436 macro_build ((char *) NULL, &icnt, &offset_expr,
4437 likely ? "bnel" : "bne", "s,t,p", sreg, 0);
4440 set_at (&icnt, sreg, 1);
4441 macro_build ((char *) NULL, &icnt, &offset_expr,
4442 likely ? "beql" : "beq", "s,t,p", AT, 0);
4450 macro_build ((char *) NULL, &icnt, &offset_expr,
4451 likely ? "bgtzl" : "bgtz", "s,p", sreg);
4456 macro_build ((char *) NULL, &icnt, &offset_expr,
4457 likely ? "bltzl" : "bltz", "s,p", treg);
4460 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "slt", "d,v,t",
4462 macro_build ((char *) NULL, &icnt, &offset_expr,
4463 likely ? "bnel" : "bne", "s,t,p", AT, 0);
4471 macro_build ((char *) NULL, &icnt, &offset_expr,
4472 likely ? "bnel" : "bne", "s,t,p", sreg, 0);
4477 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sltu",
4478 "d,v,t", AT, treg, sreg);
4479 macro_build ((char *) NULL, &icnt, &offset_expr,
4480 likely ? "bnel" : "bne", "s,t,p", AT, 0);
4488 macro_build ((char *) NULL, &icnt, &offset_expr,
4489 likely ? "blezl" : "blez", "s,p", sreg);
4494 macro_build ((char *) NULL, &icnt, &offset_expr,
4495 likely ? "bgezl" : "bgez", "s,p", treg);
4498 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "slt", "d,v,t",
4500 macro_build ((char *) NULL, &icnt, &offset_expr,
4501 likely ? "beql" : "beq", "s,t,p", AT, 0);
4507 maxnum = 0x7fffffff;
4508 if (HAVE_64BIT_GPRS && sizeof (maxnum) > 4)
4515 if (imm_expr.X_op == O_constant
4516 && imm_expr.X_add_number >= maxnum
4517 && (HAVE_32BIT_GPRS || sizeof (maxnum) > 4))
4519 if (imm_expr.X_op != O_constant)
4520 as_bad (_("Unsupported large constant"));
4521 ++imm_expr.X_add_number;
4525 if (mask == M_BLTL_I)
4527 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
4529 macro_build ((char *) NULL, &icnt, &offset_expr,
4530 likely ? "bltzl" : "bltz", "s,p", sreg);
4533 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 1)
4535 macro_build ((char *) NULL, &icnt, &offset_expr,
4536 likely ? "blezl" : "blez", "s,p", sreg);
4539 set_at (&icnt, sreg, 0);
4540 macro_build ((char *) NULL, &icnt, &offset_expr,
4541 likely ? "bnel" : "bne", "s,t,p", AT, 0);
4549 macro_build ((char *) NULL, &icnt, &offset_expr,
4550 likely ? "beql" : "beq", "s,t,p", sreg, 0);
4555 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sltu",
4556 "d,v,t", AT, treg, sreg);
4557 macro_build ((char *) NULL, &icnt, &offset_expr,
4558 likely ? "beql" : "beq", "s,t,p", AT, 0);
4566 && imm_expr.X_op == O_constant
4567 && imm_expr.X_add_number == (offsetT) 0xffffffff))
4569 if (imm_expr.X_op != O_constant)
4570 as_bad (_("Unsupported large constant"));
4571 ++imm_expr.X_add_number;
4575 if (mask == M_BLTUL_I)
4577 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
4579 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 1)
4581 macro_build ((char *) NULL, &icnt, &offset_expr,
4582 likely ? "beql" : "beq",
4586 set_at (&icnt, sreg, 1);
4587 macro_build ((char *) NULL, &icnt, &offset_expr,
4588 likely ? "bnel" : "bne", "s,t,p", AT, 0);
4596 macro_build ((char *) NULL, &icnt, &offset_expr,
4597 likely ? "bltzl" : "bltz", "s,p", sreg);
4602 macro_build ((char *) NULL, &icnt, &offset_expr,
4603 likely ? "bgtzl" : "bgtz", "s,p", treg);
4606 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "slt", "d,v,t",
4608 macro_build ((char *) NULL, &icnt, &offset_expr,
4609 likely ? "bnel" : "bne", "s,t,p", AT, 0);
4619 macro_build ((char *) NULL, &icnt, &offset_expr,
4620 likely ? "bnel" : "bne", "s,t,p", 0, treg);
4623 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sltu",
4626 macro_build ((char *) NULL, &icnt, &offset_expr,
4627 likely ? "bnel" : "bne", "s,t,p", AT, 0);
4642 as_warn (_("Divide by zero."));
4644 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "teq",
4647 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "break",
4652 mips_emit_delays (TRUE);
4653 ++mips_opts.noreorder;
4654 mips_any_noreorder = 1;
4657 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "teq",
4658 "s,t,q", treg, 0, 7);
4659 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
4660 dbl ? "ddiv" : "div", "z,s,t", sreg, treg);
4664 expr1.X_add_number = 8;
4665 macro_build ((char *) NULL, &icnt, &expr1, "bne", "s,t,p", treg, 0);
4666 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
4667 dbl ? "ddiv" : "div", "z,s,t", sreg, treg);
4668 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "break",
4671 expr1.X_add_number = -1;
4672 macro_build ((char *) NULL, &icnt, &expr1,
4673 dbl ? "daddiu" : "addiu",
4674 "t,r,j", AT, 0, (int) BFD_RELOC_LO16);
4675 expr1.X_add_number = mips_trap ? (dbl ? 12 : 8) : (dbl ? 20 : 16);
4676 macro_build ((char *) NULL, &icnt, &expr1, "bne", "s,t,p", treg, AT);
4679 expr1.X_add_number = 1;
4680 macro_build ((char *) NULL, &icnt, &expr1, "daddiu", "t,r,j", AT, 0,
4681 (int) BFD_RELOC_LO16);
4682 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "dsll32",
4683 "d,w,<", AT, AT, 31);
4687 expr1.X_add_number = 0x80000000;
4688 macro_build ((char *) NULL, &icnt, &expr1, "lui", "t,u", AT,
4689 (int) BFD_RELOC_HI16);
4693 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "teq",
4694 "s,t,q", sreg, AT, 6);
4695 /* We want to close the noreorder block as soon as possible, so
4696 that later insns are available for delay slot filling. */
4697 --mips_opts.noreorder;
4701 expr1.X_add_number = 8;
4702 macro_build ((char *) NULL, &icnt, &expr1, "bne", "s,t,p", sreg, AT);
4703 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "",
4706 /* We want to close the noreorder block as soon as possible, so
4707 that later insns are available for delay slot filling. */
4708 --mips_opts.noreorder;
4710 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "break",
4713 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "d", dreg);
4752 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
4754 as_warn (_("Divide by zero."));
4756 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "teq",
4759 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "break",
4763 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 1)
4765 if (strcmp (s2, "mflo") == 0)
4766 move_register (&icnt, dreg, sreg);
4768 move_register (&icnt, dreg, 0);
4771 if (imm_expr.X_op == O_constant
4772 && imm_expr.X_add_number == -1
4773 && s[strlen (s) - 1] != 'u')
4775 if (strcmp (s2, "mflo") == 0)
4777 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
4778 dbl ? "dneg" : "neg", "d,w", dreg, sreg);
4781 move_register (&icnt, dreg, 0);
4785 load_register (&icnt, AT, &imm_expr, dbl);
4786 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "z,s,t",
4788 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s2, "d", dreg);
4807 mips_emit_delays (TRUE);
4808 ++mips_opts.noreorder;
4809 mips_any_noreorder = 1;
4812 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "teq",
4813 "s,t,q", treg, 0, 7);
4814 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "z,s,t",
4816 /* We want to close the noreorder block as soon as possible, so
4817 that later insns are available for delay slot filling. */
4818 --mips_opts.noreorder;
4822 expr1.X_add_number = 8;
4823 macro_build ((char *) NULL, &icnt, &expr1, "bne", "s,t,p", treg, 0);
4824 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "z,s,t",
4827 /* We want to close the noreorder block as soon as possible, so
4828 that later insns are available for delay slot filling. */
4829 --mips_opts.noreorder;
4830 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "break",
4833 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s2, "d", dreg);
4839 /* Load the address of a symbol into a register. If breg is not
4840 zero, we then add a base register to it. */
4842 if (dbl && HAVE_32BIT_GPRS)
4843 as_warn (_("dla used to load 32-bit register"));
4845 if (! dbl && HAVE_64BIT_OBJECTS)
4846 as_warn (_("la used to load 64-bit address"));
4848 if (offset_expr.X_op == O_constant
4849 && offset_expr.X_add_number >= -0x8000
4850 && offset_expr.X_add_number < 0x8000)
4852 macro_build ((char *) NULL, &icnt, &offset_expr,
4853 (dbl || HAVE_64BIT_ADDRESSES) ? "daddiu" : "addiu",
4854 "t,r,j", treg, sreg, (int) BFD_RELOC_LO16);
4869 /* When generating embedded PIC code, we permit expressions of
4872 la $treg,foo-bar($breg)
4873 where bar is an address in the current section. These are used
4874 when getting the addresses of functions. We don't permit
4875 X_add_number to be non-zero, because if the symbol is
4876 external the relaxing code needs to know that any addend is
4877 purely the offset to X_op_symbol. */
4878 if (mips_pic == EMBEDDED_PIC
4879 && offset_expr.X_op == O_subtract
4880 && (symbol_constant_p (offset_expr.X_op_symbol)
4881 ? S_GET_SEGMENT (offset_expr.X_op_symbol) == now_seg
4882 : (symbol_equated_p (offset_expr.X_op_symbol)
4884 (symbol_get_value_expression (offset_expr.X_op_symbol)
4887 && (offset_expr.X_add_number == 0
4888 || OUTPUT_FLAVOR == bfd_target_elf_flavour))
4894 macro_build ((char *) NULL, &icnt, &offset_expr, "lui", "t,u",
4895 tempreg, (int) BFD_RELOC_PCREL_HI16_S);
4899 macro_build ((char *) NULL, &icnt, &offset_expr, "lui", "t,u",
4900 tempreg, (int) BFD_RELOC_PCREL_HI16_S);
4901 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
4902 (dbl || HAVE_64BIT_ADDRESSES) ? "daddu" : "addu",
4903 "d,v,t", tempreg, tempreg, breg);
4905 macro_build ((char *) NULL, &icnt, &offset_expr,
4906 (dbl || HAVE_64BIT_ADDRESSES) ? "daddiu" : "addiu",
4907 "t,r,j", treg, tempreg, (int) BFD_RELOC_PCREL_LO16);
4913 if (offset_expr.X_op != O_symbol
4914 && offset_expr.X_op != O_constant)
4916 as_bad (_("expression too complex"));
4917 offset_expr.X_op = O_constant;
4920 if (offset_expr.X_op == O_constant)
4921 load_register (&icnt, tempreg, &offset_expr,
4922 ((mips_pic == EMBEDDED_PIC || mips_pic == NO_PIC)
4923 ? (dbl || HAVE_64BIT_ADDRESSES)
4924 : HAVE_64BIT_ADDRESSES));
4925 else if (mips_pic == NO_PIC)
4927 /* If this is a reference to a GP relative symbol, we want
4928 addiu $tempreg,$gp,<sym> (BFD_RELOC_GPREL16)
4930 lui $tempreg,<sym> (BFD_RELOC_HI16_S)
4931 addiu $tempreg,$tempreg,<sym> (BFD_RELOC_LO16)
4932 If we have a constant, we need two instructions anyhow,
4933 so we may as well always use the latter form.
4935 With 64bit address space and a usable $at we want
4936 lui $tempreg,<sym> (BFD_RELOC_MIPS_HIGHEST)
4937 lui $at,<sym> (BFD_RELOC_HI16_S)
4938 daddiu $tempreg,<sym> (BFD_RELOC_MIPS_HIGHER)
4939 daddiu $at,<sym> (BFD_RELOC_LO16)
4941 daddu $tempreg,$tempreg,$at
4943 If $at is already in use, we use a path which is suboptimal
4944 on superscalar processors.
4945 lui $tempreg,<sym> (BFD_RELOC_MIPS_HIGHEST)
4946 daddiu $tempreg,<sym> (BFD_RELOC_MIPS_HIGHER)
4948 daddiu $tempreg,<sym> (BFD_RELOC_HI16_S)
4950 daddiu $tempreg,<sym> (BFD_RELOC_LO16)
4953 if (HAVE_64BIT_ADDRESSES)
4955 /* We don't do GP optimization for now because RELAX_ENCODE can't
4956 hold the data for such large chunks. */
4958 if (used_at == 0 && ! mips_opts.noat)
4960 macro_build (p, &icnt, &offset_expr, "lui", "t,u",
4961 tempreg, (int) BFD_RELOC_MIPS_HIGHEST);
4962 macro_build (p, &icnt, &offset_expr, "lui", "t,u",
4963 AT, (int) BFD_RELOC_HI16_S);
4964 macro_build (p, &icnt, &offset_expr, "daddiu", "t,r,j",
4965 tempreg, tempreg, (int) BFD_RELOC_MIPS_HIGHER);
4966 macro_build (p, &icnt, &offset_expr, "daddiu", "t,r,j",
4967 AT, AT, (int) BFD_RELOC_LO16);
4968 macro_build (p, &icnt, (expressionS *) NULL, "dsll32",
4969 "d,w,<", tempreg, tempreg, 0);
4970 macro_build (p, &icnt, (expressionS *) NULL, "daddu",
4971 "d,v,t", tempreg, tempreg, AT);
4976 macro_build (p, &icnt, &offset_expr, "lui", "t,u",
4977 tempreg, (int) BFD_RELOC_MIPS_HIGHEST);
4978 macro_build (p, &icnt, &offset_expr, "daddiu", "t,r,j",
4979 tempreg, tempreg, (int) BFD_RELOC_MIPS_HIGHER);
4980 macro_build (p, &icnt, (expressionS *) NULL, "dsll", "d,w,<",
4981 tempreg, tempreg, 16);
4982 macro_build (p, &icnt, &offset_expr, "daddiu", "t,r,j",
4983 tempreg, tempreg, (int) BFD_RELOC_HI16_S);
4984 macro_build (p, &icnt, (expressionS *) NULL, "dsll", "d,w,<",
4985 tempreg, tempreg, 16);
4986 macro_build (p, &icnt, &offset_expr, "daddiu", "t,r,j",
4987 tempreg, tempreg, (int) BFD_RELOC_LO16);
4992 if ((valueT) offset_expr.X_add_number <= MAX_GPREL_OFFSET
4993 && ! nopic_need_relax (offset_expr.X_add_symbol, 1))
4996 macro_build ((char *) NULL, &icnt, &offset_expr,
4997 ADDRESS_ADDI_INSN, "t,r,j", tempreg,
4998 mips_gp_register, (int) BFD_RELOC_GPREL16);
4999 p = frag_var (rs_machine_dependent, 8, 0,
5000 RELAX_ENCODE (4, 8, 0, 4, 0,
5001 mips_opts.warn_about_macros),
5002 offset_expr.X_add_symbol, 0, NULL);
5004 macro_build_lui (p, &icnt, &offset_expr, tempreg);
5007 macro_build (p, &icnt, &offset_expr, ADDRESS_ADDI_INSN,
5008 "t,r,j", tempreg, tempreg, (int) BFD_RELOC_LO16);
5011 else if (mips_pic == SVR4_PIC && ! mips_big_got && ! HAVE_NEWABI)
5013 int lw_reloc_type = (int) BFD_RELOC_MIPS_GOT16;
5015 /* If this is a reference to an external symbol, and there
5016 is no constant, we want
5017 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
5018 or if tempreg is PIC_CALL_REG
5019 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_CALL16)
5020 For a local symbol, we want
5021 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
5023 addiu $tempreg,$tempreg,<sym> (BFD_RELOC_LO16)
5025 If we have a small constant, and this is a reference to
5026 an external symbol, we want
5027 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
5029 addiu $tempreg,$tempreg,<constant>
5030 For a local symbol, we want the same instruction
5031 sequence, but we output a BFD_RELOC_LO16 reloc on the
5034 If we have a large constant, and this is a reference to
5035 an external symbol, we want
5036 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
5037 lui $at,<hiconstant>
5038 addiu $at,$at,<loconstant>
5039 addu $tempreg,$tempreg,$at
5040 For a local symbol, we want the same instruction
5041 sequence, but we output a BFD_RELOC_LO16 reloc on the
5045 expr1.X_add_number = offset_expr.X_add_number;
5046 offset_expr.X_add_number = 0;
5048 if (expr1.X_add_number == 0 && tempreg == PIC_CALL_REG)
5049 lw_reloc_type = (int) BFD_RELOC_MIPS_CALL16;
5050 macro_build ((char *) NULL, &icnt, &offset_expr, ADDRESS_LOAD_INSN,
5051 "t,o(b)", tempreg, lw_reloc_type, mips_gp_register);
5052 if (expr1.X_add_number == 0)
5061 /* We're going to put in an addu instruction using
5062 tempreg, so we may as well insert the nop right
5064 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5068 p = frag_var (rs_machine_dependent, 8 - off, 0,
5069 RELAX_ENCODE (0, 8 - off, -4 - off, 4 - off, 0,
5071 ? mips_opts.warn_about_macros
5073 offset_expr.X_add_symbol, 0, NULL);
5076 macro_build (p, &icnt, (expressionS *) NULL, "nop", "");
5079 macro_build (p, &icnt, &expr1, ADDRESS_ADDI_INSN,
5080 "t,r,j", tempreg, tempreg, (int) BFD_RELOC_LO16);
5081 /* FIXME: If breg == 0, and the next instruction uses
5082 $tempreg, then if this variant case is used an extra
5083 nop will be generated. */
5085 else if (expr1.X_add_number >= -0x8000
5086 && expr1.X_add_number < 0x8000)
5088 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5090 macro_build ((char *) NULL, &icnt, &expr1, ADDRESS_ADDI_INSN,
5091 "t,r,j", tempreg, tempreg, (int) BFD_RELOC_LO16);
5092 frag_var (rs_machine_dependent, 0, 0,
5093 RELAX_ENCODE (0, 0, -12, -4, 0, 0),
5094 offset_expr.X_add_symbol, 0, NULL);
5100 /* If we are going to add in a base register, and the
5101 target register and the base register are the same,
5102 then we are using AT as a temporary register. Since
5103 we want to load the constant into AT, we add our
5104 current AT (from the global offset table) and the
5105 register into the register now, and pretend we were
5106 not using a base register. */
5111 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5113 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5114 ADDRESS_ADD_INSN, "d,v,t", treg, AT, breg);
5120 /* Set mips_optimize around the lui instruction to avoid
5121 inserting an unnecessary nop after the lw. */
5122 hold_mips_optimize = mips_optimize;
5124 macro_build_lui (NULL, &icnt, &expr1, AT);
5125 mips_optimize = hold_mips_optimize;
5127 macro_build ((char *) NULL, &icnt, &expr1, ADDRESS_ADDI_INSN,
5128 "t,r,j", AT, AT, (int) BFD_RELOC_LO16);
5129 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5130 ADDRESS_ADD_INSN, "d,v,t", tempreg, tempreg, AT);
5131 frag_var (rs_machine_dependent, 0, 0,
5132 RELAX_ENCODE (0, 0, -16 + off1, -8, 0, 0),
5133 offset_expr.X_add_symbol, 0, NULL);
5137 else if (mips_pic == SVR4_PIC && ! mips_big_got && HAVE_NEWABI)
5140 int lw_reloc_type = (int) BFD_RELOC_MIPS_GOT_DISP;
5143 /* If this is a reference to an external, and there is no
5144 constant, or local symbol (*), with or without a
5146 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT_DISP)
5147 or if tempreg is PIC_CALL_REG
5148 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_CALL16)
5150 If we have a small constant, and this is a reference to
5151 an external symbol, we want
5152 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT_DISP)
5153 addiu $tempreg,$tempreg,<constant>
5155 If we have a large constant, and this is a reference to
5156 an external symbol, we want
5157 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT_DISP)
5158 lui $at,<hiconstant>
5159 addiu $at,$at,<loconstant>
5160 addu $tempreg,$tempreg,$at
5162 (*) Other assemblers seem to prefer GOT_PAGE/GOT_OFST for
5163 local symbols, even though it introduces an additional
5167 if (offset_expr.X_add_number == 0 && tempreg == PIC_CALL_REG)
5168 lw_reloc_type = (int) BFD_RELOC_MIPS_CALL16;
5169 if (offset_expr.X_add_number)
5171 frag_now->tc_frag_data.tc_fr_offset =
5172 expr1.X_add_number = offset_expr.X_add_number;
5173 offset_expr.X_add_number = 0;
5175 macro_build ((char *) NULL, &icnt, &offset_expr,
5176 ADDRESS_LOAD_INSN, "t,o(b)", tempreg,
5177 lw_reloc_type, mips_gp_register);
5179 if (expr1.X_add_number >= -0x8000
5180 && expr1.X_add_number < 0x8000)
5182 macro_build ((char *) NULL, &icnt, &expr1,
5183 ADDRESS_ADDI_INSN, "t,r,j", tempreg, tempreg,
5184 (int) BFD_RELOC_LO16);
5185 p = frag_var (rs_machine_dependent, 4, 0,
5186 RELAX_ENCODE (8, 4, 0, 0, 0, 0),
5187 offset_expr.X_add_symbol, 0, NULL);
5189 else if (IS_SEXT_32BIT_NUM (expr1.X_add_number))
5193 /* If we are going to add in a base register, and the
5194 target register and the base register are the same,
5195 then we are using AT as a temporary register. Since
5196 we want to load the constant into AT, we add our
5197 current AT (from the global offset table) and the
5198 register into the register now, and pretend we were
5199 not using a base register. */
5204 assert (tempreg == AT);
5205 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5206 ADDRESS_ADD_INSN, "d,v,t", treg, AT, breg);
5211 macro_build_lui ((char *) NULL, &icnt, &expr1, AT);
5212 macro_build ((char *) NULL, &icnt, &expr1,
5213 ADDRESS_ADDI_INSN, "t,r,j", AT, AT,
5214 (int) BFD_RELOC_LO16);
5215 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5216 ADDRESS_ADD_INSN, "d,v,t", dreg, dreg, AT);
5218 p = frag_var (rs_machine_dependent, 4 + adj, 0,
5219 RELAX_ENCODE (16 + adj, 4 + adj,
5221 offset_expr.X_add_symbol, 0, NULL);
5226 as_bad (_("PIC code offset overflow (max 32 signed bits)"));
5228 offset_expr.X_add_number = expr1.X_add_number;
5230 macro_build (p, &icnt, &offset_expr, ADDRESS_LOAD_INSN,
5231 "t,o(b)", tempreg, (int) BFD_RELOC_MIPS_GOT_DISP,
5235 macro_build (p + 4, &icnt, (expressionS *) NULL,
5236 ADDRESS_ADD_INSN, "d,v,t",
5237 treg, tempreg, breg);
5244 macro_build ((char *) NULL, &icnt, &offset_expr,
5245 ADDRESS_LOAD_INSN, "t,o(b)", tempreg,
5246 lw_reloc_type, mips_gp_register);
5247 if (lw_reloc_type != BFD_RELOC_MIPS_GOT_DISP)
5248 p = frag_var (rs_machine_dependent, 0, 0,
5249 RELAX_ENCODE (0, 0, -4, 0, 0, 0),
5250 offset_expr.X_add_symbol, 0, NULL);
5255 /* To avoid confusion in tc_gen_reloc, we must ensure
5256 that this does not become a variant frag. */
5257 frag_wane (frag_now);
5261 else if (mips_pic == SVR4_PIC && ! HAVE_NEWABI)
5265 int lui_reloc_type = (int) BFD_RELOC_MIPS_GOT_HI16;
5266 int lw_reloc_type = (int) BFD_RELOC_MIPS_GOT_LO16;
5267 int local_reloc_type = (int) BFD_RELOC_MIPS_GOT16;
5269 /* This is the large GOT case. If this is a reference to an
5270 external symbol, and there is no constant, we want
5271 lui $tempreg,<sym> (BFD_RELOC_MIPS_GOT_HI16)
5272 addu $tempreg,$tempreg,$gp
5273 lw $tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_LO16)
5274 or if tempreg is PIC_CALL_REG
5275 lui $tempreg,<sym> (BFD_RELOC_MIPS_CALL_HI16)
5276 addu $tempreg,$tempreg,$gp
5277 lw $tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_CALL_LO16)
5278 For a local symbol, we want
5279 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
5281 addiu $tempreg,$tempreg,<sym> (BFD_RELOC_LO16)
5283 If we have a small constant, and this is a reference to
5284 an external symbol, we want
5285 lui $tempreg,<sym> (BFD_RELOC_MIPS_GOT_HI16)
5286 addu $tempreg,$tempreg,$gp
5287 lw $tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_LO16)
5289 addiu $tempreg,$tempreg,<constant>
5290 For a local symbol, we want
5291 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
5293 addiu $tempreg,$tempreg,<constant> (BFD_RELOC_LO16)
5295 If we have a large constant, and this is a reference to
5296 an external symbol, we want
5297 lui $tempreg,<sym> (BFD_RELOC_MIPS_GOT_HI16)
5298 addu $tempreg,$tempreg,$gp
5299 lw $tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_LO16)
5300 lui $at,<hiconstant>
5301 addiu $at,$at,<loconstant>
5302 addu $tempreg,$tempreg,$at
5303 For a local symbol, we want
5304 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
5305 lui $at,<hiconstant>
5306 addiu $at,$at,<loconstant> (BFD_RELOC_LO16)
5307 addu $tempreg,$tempreg,$at
5310 expr1.X_add_number = offset_expr.X_add_number;
5311 offset_expr.X_add_number = 0;
5313 if (reg_needs_delay (mips_gp_register))
5317 if (expr1.X_add_number == 0 && tempreg == PIC_CALL_REG)
5319 lui_reloc_type = (int) BFD_RELOC_MIPS_CALL_HI16;
5320 lw_reloc_type = (int) BFD_RELOC_MIPS_CALL_LO16;
5322 macro_build ((char *) NULL, &icnt, &offset_expr, "lui", "t,u",
5323 tempreg, lui_reloc_type);
5324 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5325 ADDRESS_ADD_INSN, "d,v,t", tempreg, tempreg,
5327 macro_build ((char *) NULL, &icnt, &offset_expr, ADDRESS_LOAD_INSN,
5328 "t,o(b)", tempreg, lw_reloc_type, tempreg);
5329 if (expr1.X_add_number == 0)
5337 /* We're going to put in an addu instruction using
5338 tempreg, so we may as well insert the nop right
5340 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5345 p = frag_var (rs_machine_dependent, 12 + gpdel, 0,
5346 RELAX_ENCODE (12 + off, 12 + gpdel, gpdel,
5349 ? mips_opts.warn_about_macros
5351 offset_expr.X_add_symbol, 0, NULL);
5353 else if (expr1.X_add_number >= -0x8000
5354 && expr1.X_add_number < 0x8000)
5356 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5358 macro_build ((char *) NULL, &icnt, &expr1, ADDRESS_ADDI_INSN,
5359 "t,r,j", tempreg, tempreg, (int) BFD_RELOC_LO16);
5361 p = frag_var (rs_machine_dependent, 12 + gpdel, 0,
5362 RELAX_ENCODE (20, 12 + gpdel, gpdel, 8 + gpdel, 0,
5364 ? mips_opts.warn_about_macros
5366 offset_expr.X_add_symbol, 0, NULL);
5372 /* If we are going to add in a base register, and the
5373 target register and the base register are the same,
5374 then we are using AT as a temporary register. Since
5375 we want to load the constant into AT, we add our
5376 current AT (from the global offset table) and the
5377 register into the register now, and pretend we were
5378 not using a base register. */
5386 assert (tempreg == AT);
5387 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5389 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5390 ADDRESS_ADD_INSN, "d,v,t", treg, AT, breg);
5395 /* Set mips_optimize around the lui instruction to avoid
5396 inserting an unnecessary nop after the lw. */
5397 hold_mips_optimize = mips_optimize;
5399 macro_build_lui (NULL, &icnt, &expr1, AT);
5400 mips_optimize = hold_mips_optimize;
5402 macro_build ((char *) NULL, &icnt, &expr1, ADDRESS_ADDI_INSN,
5403 "t,r,j", AT, AT, (int) BFD_RELOC_LO16);
5404 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5405 ADDRESS_ADD_INSN, "d,v,t", dreg, dreg, AT);
5407 p = frag_var (rs_machine_dependent, 16 + gpdel + adj, 0,
5408 RELAX_ENCODE (24 + adj, 16 + gpdel + adj, gpdel,
5411 ? mips_opts.warn_about_macros
5413 offset_expr.X_add_symbol, 0, NULL);
5420 /* This is needed because this instruction uses $gp, but
5421 the first instruction on the main stream does not. */
5422 macro_build (p, &icnt, (expressionS *) NULL, "nop", "");
5426 macro_build (p, &icnt, &offset_expr, ADDRESS_LOAD_INSN, "t,o(b)",
5427 tempreg, local_reloc_type, mips_gp_register);
5429 if (expr1.X_add_number >= -0x8000
5430 && expr1.X_add_number < 0x8000)
5432 macro_build (p, &icnt, (expressionS *) NULL, "nop", "");
5434 macro_build (p, &icnt, &expr1, ADDRESS_ADDI_INSN,
5435 "t,r,j", tempreg, tempreg, (int) BFD_RELOC_LO16);
5436 /* FIXME: If add_number is 0, and there was no base
5437 register, the external symbol case ended with a load,
5438 so if the symbol turns out to not be external, and
5439 the next instruction uses tempreg, an unnecessary nop
5440 will be inserted. */
5446 /* We must add in the base register now, as in the
5447 external symbol case. */
5448 assert (tempreg == AT);
5449 macro_build (p, &icnt, (expressionS *) NULL, "nop", "");
5451 macro_build (p, &icnt, (expressionS *) NULL,
5452 ADDRESS_ADD_INSN, "d,v,t", treg, AT, breg);
5455 /* We set breg to 0 because we have arranged to add
5456 it in in both cases. */
5460 macro_build_lui (p, &icnt, &expr1, AT);
5462 macro_build (p, &icnt, &expr1, ADDRESS_ADDI_INSN,
5463 "t,r,j", AT, AT, (int) BFD_RELOC_LO16);
5465 macro_build (p, &icnt, (expressionS *) NULL, ADDRESS_ADD_INSN,
5466 "d,v,t", tempreg, tempreg, AT);
5470 else if (mips_pic == SVR4_PIC && HAVE_NEWABI)
5473 int lui_reloc_type = (int) BFD_RELOC_MIPS_GOT_HI16;
5474 int lw_reloc_type = (int) BFD_RELOC_MIPS_GOT_LO16;
5477 /* This is the large GOT case. If this is a reference to an
5478 external symbol, and there is no constant, we want
5479 lui $tempreg,<sym> (BFD_RELOC_MIPS_GOT_HI16)
5480 add $tempreg,$tempreg,$gp
5481 lw $tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_LO16)
5482 or if tempreg is PIC_CALL_REG
5483 lui $tempreg,<sym> (BFD_RELOC_MIPS_CALL_HI16)
5484 add $tempreg,$tempreg,$gp
5485 lw $tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_CALL_LO16)
5487 If we have a small constant, and this is a reference to
5488 an external symbol, we want
5489 lui $tempreg,<sym> (BFD_RELOC_MIPS_GOT_HI16)
5490 add $tempreg,$tempreg,$gp
5491 lw $tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_LO16)
5492 addi $tempreg,$tempreg,<constant>
5494 If we have a large constant, and this is a reference to
5495 an external symbol, we want
5496 lui $tempreg,<sym> (BFD_RELOC_MIPS_GOT_HI16)
5497 addu $tempreg,$tempreg,$gp
5498 lw $tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_LO16)
5499 lui $at,<hiconstant>
5500 addi $at,$at,<loconstant>
5501 add $tempreg,$tempreg,$at
5503 If we have NewABI, and we know it's a local symbol, we want
5504 lw $reg,<sym>($gp) (BFD_RELOC_MIPS_GOT_PAGE)
5505 addiu $reg,$reg,<sym> (BFD_RELOC_MIPS_GOT_OFST)
5506 otherwise we have to resort to GOT_HI16/GOT_LO16. */
5510 frag_now->tc_frag_data.tc_fr_offset =
5511 expr1.X_add_number = offset_expr.X_add_number;
5512 offset_expr.X_add_number = 0;
5514 if (expr1.X_add_number == 0 && tempreg == PIC_CALL_REG)
5516 lui_reloc_type = (int) BFD_RELOC_MIPS_CALL_HI16;
5517 lw_reloc_type = (int) BFD_RELOC_MIPS_CALL_LO16;
5519 macro_build ((char *) NULL, &icnt, &offset_expr, "lui", "t,u",
5520 tempreg, lui_reloc_type);
5521 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5522 ADDRESS_ADD_INSN, "d,v,t", tempreg, tempreg,
5524 macro_build ((char *) NULL, &icnt, &offset_expr, ADDRESS_LOAD_INSN,
5525 "t,o(b)", tempreg, lw_reloc_type, tempreg);
5527 if (expr1.X_add_number == 0)
5529 p = frag_var (rs_machine_dependent, 8, 0,
5530 RELAX_ENCODE (12, 8, 0, 4, 0,
5531 mips_opts.warn_about_macros),
5532 offset_expr.X_add_symbol, 0, NULL);
5534 else if (expr1.X_add_number >= -0x8000
5535 && expr1.X_add_number < 0x8000)
5537 macro_build ((char *) NULL, &icnt, &expr1, ADDRESS_ADDI_INSN,
5538 "t,r,j", tempreg, tempreg,
5539 (int) BFD_RELOC_LO16);
5540 p = frag_var (rs_machine_dependent, 8, 0,
5541 RELAX_ENCODE (16, 8, 0, 4, 0,
5542 mips_opts.warn_about_macros),
5543 offset_expr.X_add_symbol, 0, NULL);
5545 else if (IS_SEXT_32BIT_NUM (expr1.X_add_number))
5549 /* If we are going to add in a base register, and the
5550 target register and the base register are the same,
5551 then we are using AT as a temporary register. Since
5552 we want to load the constant into AT, we add our
5553 current AT (from the global offset table) and the
5554 register into the register now, and pretend we were
5555 not using a base register. */
5560 assert (tempreg == AT);
5561 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5562 ADDRESS_ADD_INSN, "d,v,t", treg, AT, breg);
5567 /* Set mips_optimize around the lui instruction to avoid
5568 inserting an unnecessary nop after the lw. */
5569 macro_build_lui ((char *) NULL, &icnt, &expr1, AT);
5570 macro_build ((char *) NULL, &icnt, &expr1, ADDRESS_ADDI_INSN,
5571 "t,r,j", AT, AT, (int) BFD_RELOC_LO16);
5572 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5573 ADDRESS_ADD_INSN, "d,v,t", dreg, dreg, AT);
5575 p = frag_var (rs_machine_dependent, 8 + adj, 0,
5576 RELAX_ENCODE (24 + adj, 8 + adj,
5579 ? mips_opts.warn_about_macros
5581 offset_expr.X_add_symbol, 0, NULL);
5586 as_bad (_("PIC code offset overflow (max 32 signed bits)"));
5588 offset_expr.X_add_number = expr1.X_add_number;
5589 macro_build (p, &icnt, &offset_expr, ADDRESS_LOAD_INSN, "t,o(b)",
5590 tempreg, (int) BFD_RELOC_MIPS_GOT_PAGE,
5592 macro_build (p + 4, &icnt, &offset_expr, ADDRESS_ADDI_INSN, "t,r,j",
5593 tempreg, tempreg, (int) BFD_RELOC_MIPS_GOT_OFST);
5596 macro_build (p + 8, &icnt, (expressionS *) NULL,
5597 ADDRESS_ADD_INSN, "d,v,t", treg, tempreg, breg);
5602 else if (mips_pic == EMBEDDED_PIC)
5605 addiu $tempreg,$gp,<sym> (BFD_RELOC_GPREL16)
5607 macro_build ((char *) NULL, &icnt, &offset_expr, ADDRESS_ADDI_INSN,
5608 "t,r,j", tempreg, mips_gp_register,
5609 (int) BFD_RELOC_GPREL16);
5618 if (mips_pic == EMBEDDED_PIC || mips_pic == NO_PIC)
5619 s = (dbl || HAVE_64BIT_ADDRESSES) ? "daddu" : "addu";
5621 s = ADDRESS_ADD_INSN;
5623 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s,
5624 "d,v,t", treg, tempreg, breg);
5633 /* The j instruction may not be used in PIC code, since it
5634 requires an absolute address. We convert it to a b
5636 if (mips_pic == NO_PIC)
5637 macro_build ((char *) NULL, &icnt, &offset_expr, "j", "a");
5639 macro_build ((char *) NULL, &icnt, &offset_expr, "b", "p");
5642 /* The jal instructions must be handled as macros because when
5643 generating PIC code they expand to multi-instruction
5644 sequences. Normally they are simple instructions. */
5649 if (mips_pic == NO_PIC
5650 || mips_pic == EMBEDDED_PIC)
5651 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "jalr",
5653 else if (mips_pic == SVR4_PIC)
5655 if (sreg != PIC_CALL_REG)
5656 as_warn (_("MIPS PIC call to register other than $25"));
5658 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "jalr",
5662 if (mips_cprestore_offset < 0)
5663 as_warn (_("No .cprestore pseudo-op used in PIC code"));
5666 if (! mips_frame_reg_valid)
5668 as_warn (_("No .frame pseudo-op used in PIC code"));
5669 /* Quiet this warning. */
5670 mips_frame_reg_valid = 1;
5672 if (! mips_cprestore_valid)
5674 as_warn (_("No .cprestore pseudo-op used in PIC code"));
5675 /* Quiet this warning. */
5676 mips_cprestore_valid = 1;
5678 expr1.X_add_number = mips_cprestore_offset;
5679 macro_build_ldst_constoffset ((char *) NULL, &icnt, &expr1,
5692 if (mips_pic == NO_PIC)
5693 macro_build ((char *) NULL, &icnt, &offset_expr, "jal", "a");
5694 else if (mips_pic == SVR4_PIC)
5698 /* If this is a reference to an external symbol, and we are
5699 using a small GOT, we want
5700 lw $25,<sym>($gp) (BFD_RELOC_MIPS_CALL16)
5704 lw $gp,cprestore($sp)
5705 The cprestore value is set using the .cprestore
5706 pseudo-op. If we are using a big GOT, we want
5707 lui $25,<sym> (BFD_RELOC_MIPS_CALL_HI16)
5709 lw $25,<sym>($25) (BFD_RELOC_MIPS_CALL_LO16)
5713 lw $gp,cprestore($sp)
5714 If the symbol is not external, we want
5715 lw $25,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
5717 addiu $25,$25,<sym> (BFD_RELOC_LO16)
5720 lw $gp,cprestore($sp)
5722 For NewABI, we use the same CALL16 or CALL_HI16/CALL_LO16
5723 sequences above, minus nops, unless the symbol is local,
5724 which enables us to use GOT_PAGE/GOT_OFST (big got) or
5731 macro_build ((char *) NULL, &icnt, &offset_expr,
5732 ADDRESS_LOAD_INSN, "t,o(b)", PIC_CALL_REG,
5733 (int) BFD_RELOC_MIPS_CALL16,
5735 frag_var (rs_machine_dependent, 0, 0,
5736 RELAX_ENCODE (0, 0, -4, 0, 0, 0),
5737 offset_expr.X_add_symbol, 0, NULL);
5742 macro_build ((char *) NULL, &icnt, &offset_expr, "lui",
5743 "t,u", PIC_CALL_REG,
5744 (int) BFD_RELOC_MIPS_CALL_HI16);
5745 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5746 ADDRESS_ADD_INSN, "d,v,t", PIC_CALL_REG,
5747 PIC_CALL_REG, mips_gp_register);
5748 macro_build ((char *) NULL, &icnt, &offset_expr,
5749 ADDRESS_LOAD_INSN, "t,o(b)", PIC_CALL_REG,
5750 (int) BFD_RELOC_MIPS_CALL_LO16, PIC_CALL_REG);
5751 p = frag_var (rs_machine_dependent, 8, 0,
5752 RELAX_ENCODE (12, 8, 0, 4, 0, 0),
5753 offset_expr.X_add_symbol, 0, NULL);
5754 macro_build (p, &icnt, &offset_expr, ADDRESS_LOAD_INSN,
5755 "t,o(b)", PIC_CALL_REG,
5756 (int) BFD_RELOC_MIPS_GOT_PAGE,
5758 macro_build (p + 4, &icnt, &offset_expr, ADDRESS_ADDI_INSN,
5759 "t,r,j", PIC_CALL_REG, PIC_CALL_REG,
5760 (int) BFD_RELOC_MIPS_GOT_OFST);
5763 macro_build_jalr (icnt, &offset_expr);
5770 macro_build ((char *) NULL, &icnt, &offset_expr,
5771 ADDRESS_LOAD_INSN, "t,o(b)", PIC_CALL_REG,
5772 (int) BFD_RELOC_MIPS_CALL16, mips_gp_register);
5773 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5775 p = frag_var (rs_machine_dependent, 4, 0,
5776 RELAX_ENCODE (0, 4, -8, 0, 0, 0),
5777 offset_expr.X_add_symbol, 0, NULL);
5783 if (reg_needs_delay (mips_gp_register))
5787 macro_build ((char *) NULL, &icnt, &offset_expr, "lui",
5788 "t,u", PIC_CALL_REG,
5789 (int) BFD_RELOC_MIPS_CALL_HI16);
5790 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5791 ADDRESS_ADD_INSN, "d,v,t", PIC_CALL_REG,
5792 PIC_CALL_REG, mips_gp_register);
5793 macro_build ((char *) NULL, &icnt, &offset_expr,
5794 ADDRESS_LOAD_INSN, "t,o(b)", PIC_CALL_REG,
5795 (int) BFD_RELOC_MIPS_CALL_LO16, PIC_CALL_REG);
5796 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5798 p = frag_var (rs_machine_dependent, 12 + gpdel, 0,
5799 RELAX_ENCODE (16, 12 + gpdel, gpdel,
5801 offset_expr.X_add_symbol, 0, NULL);
5804 macro_build (p, &icnt, (expressionS *) NULL, "nop", "");
5807 macro_build (p, &icnt, &offset_expr, ADDRESS_LOAD_INSN,
5808 "t,o(b)", PIC_CALL_REG,
5809 (int) BFD_RELOC_MIPS_GOT16, mips_gp_register);
5811 macro_build (p, &icnt, (expressionS *) NULL, "nop", "");
5814 macro_build (p, &icnt, &offset_expr, ADDRESS_ADDI_INSN,
5815 "t,r,j", PIC_CALL_REG, PIC_CALL_REG,
5816 (int) BFD_RELOC_LO16);
5817 macro_build_jalr (icnt, &offset_expr);
5819 if (mips_cprestore_offset < 0)
5820 as_warn (_("No .cprestore pseudo-op used in PIC code"));
5823 if (! mips_frame_reg_valid)
5825 as_warn (_("No .frame pseudo-op used in PIC code"));
5826 /* Quiet this warning. */
5827 mips_frame_reg_valid = 1;
5829 if (! mips_cprestore_valid)
5831 as_warn (_("No .cprestore pseudo-op used in PIC code"));
5832 /* Quiet this warning. */
5833 mips_cprestore_valid = 1;
5835 if (mips_opts.noreorder)
5836 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
5838 expr1.X_add_number = mips_cprestore_offset;
5839 macro_build_ldst_constoffset ((char *) NULL, &icnt, &expr1,
5846 else if (mips_pic == EMBEDDED_PIC)
5848 macro_build ((char *) NULL, &icnt, &offset_expr, "bal", "p");
5849 /* The linker may expand the call to a longer sequence which
5850 uses $at, so we must break rather than return. */
5875 /* Itbl support may require additional care here. */
5880 /* Itbl support may require additional care here. */
5885 /* Itbl support may require additional care here. */
5890 /* Itbl support may require additional care here. */
5902 if (mips_arch == CPU_R4650)
5904 as_bad (_("opcode not supported on this processor"));
5908 /* Itbl support may require additional care here. */
5913 /* Itbl support may require additional care here. */
5918 /* Itbl support may require additional care here. */
5938 if (breg == treg || coproc || lr)
5960 /* Itbl support may require additional care here. */
5965 /* Itbl support may require additional care here. */
5970 /* Itbl support may require additional care here. */
5975 /* Itbl support may require additional care here. */
5991 if (mips_arch == CPU_R4650)
5993 as_bad (_("opcode not supported on this processor"));
5998 /* Itbl support may require additional care here. */
6002 /* Itbl support may require additional care here. */
6007 /* Itbl support may require additional care here. */
6019 /* Itbl support may require additional care here. */
6020 if (mask == M_LWC1_AB
6021 || mask == M_SWC1_AB
6022 || mask == M_LDC1_AB
6023 || mask == M_SDC1_AB
6032 /* For embedded PIC, we allow loads where the offset is calculated
6033 by subtracting a symbol in the current segment from an unknown
6034 symbol, relative to a base register, e.g.:
6035 <op> $treg, <sym>-<localsym>($breg)
6036 This is used by the compiler for switch statements. */
6037 if (mips_pic == EMBEDDED_PIC
6038 && offset_expr.X_op == O_subtract
6039 && (symbol_constant_p (offset_expr.X_op_symbol)
6040 ? S_GET_SEGMENT (offset_expr.X_op_symbol) == now_seg
6041 : (symbol_equated_p (offset_expr.X_op_symbol)
6043 (symbol_get_value_expression (offset_expr.X_op_symbol)
6047 && (offset_expr.X_add_number == 0
6048 || OUTPUT_FLAVOR == bfd_target_elf_flavour))
6050 /* For this case, we output the instructions:
6051 lui $tempreg,<sym> (BFD_RELOC_PCREL_HI16_S)
6052 addiu $tempreg,$tempreg,$breg
6053 <op> $treg,<sym>($tempreg) (BFD_RELOC_PCREL_LO16)
6054 If the relocation would fit entirely in 16 bits, it would be
6056 <op> $treg,<sym>($breg) (BFD_RELOC_PCREL_LO16)
6057 instead, but that seems quite difficult. */
6058 macro_build ((char *) NULL, &icnt, &offset_expr, "lui", "t,u",
6059 tempreg, (int) BFD_RELOC_PCREL_HI16_S);
6060 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6061 ((bfd_arch_bits_per_address (stdoutput) == 32
6062 || ! ISA_HAS_64BIT_REGS (mips_opts.isa))
6063 ? "addu" : "daddu"),
6064 "d,v,t", tempreg, tempreg, breg);
6065 macro_build ((char *) NULL, &icnt, &offset_expr, s, fmt, treg,
6066 (int) BFD_RELOC_PCREL_LO16, tempreg);
6072 if (offset_expr.X_op != O_constant
6073 && offset_expr.X_op != O_symbol)
6075 as_bad (_("expression too complex"));
6076 offset_expr.X_op = O_constant;
6079 /* A constant expression in PIC code can be handled just as it
6080 is in non PIC code. */
6081 if (mips_pic == NO_PIC
6082 || offset_expr.X_op == O_constant)
6086 /* If this is a reference to a GP relative symbol, and there
6087 is no base register, we want
6088 <op> $treg,<sym>($gp) (BFD_RELOC_GPREL16)
6089 Otherwise, if there is no base register, we want
6090 lui $tempreg,<sym> (BFD_RELOC_HI16_S)
6091 <op> $treg,<sym>($tempreg) (BFD_RELOC_LO16)
6092 If we have a constant, we need two instructions anyhow,
6093 so we always use the latter form.
6095 If we have a base register, and this is a reference to a
6096 GP relative symbol, we want
6097 addu $tempreg,$breg,$gp
6098 <op> $treg,<sym>($tempreg) (BFD_RELOC_GPREL16)
6100 lui $tempreg,<sym> (BFD_RELOC_HI16_S)
6101 addu $tempreg,$tempreg,$breg
6102 <op> $treg,<sym>($tempreg) (BFD_RELOC_LO16)
6103 With a constant we always use the latter case.
6105 With 64bit address space and no base register and $at usable,
6107 lui $tempreg,<sym> (BFD_RELOC_MIPS_HIGHEST)
6108 lui $at,<sym> (BFD_RELOC_HI16_S)
6109 daddiu $tempreg,<sym> (BFD_RELOC_MIPS_HIGHER)
6112 <op> $treg,<sym>($tempreg) (BFD_RELOC_LO16)
6113 If we have a base register, we want
6114 lui $tempreg,<sym> (BFD_RELOC_MIPS_HIGHEST)
6115 lui $at,<sym> (BFD_RELOC_HI16_S)
6116 daddiu $tempreg,<sym> (BFD_RELOC_MIPS_HIGHER)
6120 <op> $treg,<sym>($tempreg) (BFD_RELOC_LO16)
6122 Without $at we can't generate the optimal path for superscalar
6123 processors here since this would require two temporary registers.
6124 lui $tempreg,<sym> (BFD_RELOC_MIPS_HIGHEST)
6125 daddiu $tempreg,<sym> (BFD_RELOC_MIPS_HIGHER)
6127 daddiu $tempreg,<sym> (BFD_RELOC_HI16_S)
6129 <op> $treg,<sym>($tempreg) (BFD_RELOC_LO16)
6130 If we have a base register, we want
6131 lui $tempreg,<sym> (BFD_RELOC_MIPS_HIGHEST)
6132 daddiu $tempreg,<sym> (BFD_RELOC_MIPS_HIGHER)
6134 daddiu $tempreg,<sym> (BFD_RELOC_HI16_S)
6136 daddu $tempreg,$tempreg,$breg
6137 <op> $treg,<sym>($tempreg) (BFD_RELOC_LO16)
6139 If we have 64-bit addresses, as an optimization, for
6140 addresses which are 32-bit constants (e.g. kseg0/kseg1
6141 addresses) we fall back to the 32-bit address generation
6142 mechanism since it is more efficient. Note that due to
6143 the signed offset used by memory operations, the 32-bit
6144 range is shifted down by 32768 here. This code should
6145 probably attempt to generate 64-bit constants more
6146 efficiently in general.
6148 As an extension for architectures with 64-bit registers,
6149 we don't truncate 64-bit addresses given as literal
6150 constants down to 32 bits, to support existing practice
6151 in the mips64 Linux (the kernel), that compiles source
6152 files with -mabi=64, assembling them as o32 or n32 (with
6153 -Wa,-32 or -Wa,-n32). This is not beautiful, but since
6154 the whole kernel is loaded into a memory region that is
6155 addressible with sign-extended 32-bit addresses, it is
6156 wasteful to compute the upper 32 bits of every
6157 non-literal address, that takes more space and time.
6158 Some day this should probably be implemented as an
6159 assembler option, such that the kernel doesn't have to
6160 use such ugly hacks, even though it will still have to
6161 end up converting the binary to ELF32 for a number of
6162 platforms whose boot loaders don't support ELF64
6164 if ((offset_expr.X_op != O_constant && HAVE_64BIT_ADDRESSES)
6165 || (offset_expr.X_op == O_constant
6166 && !IS_SEXT_32BIT_NUM (offset_expr.X_add_number + 0x8000)
6167 && HAVE_64BIT_ADDRESS_CONSTANTS))
6171 /* We don't do GP optimization for now because RELAX_ENCODE can't
6172 hold the data for such large chunks. */
6174 if (used_at == 0 && ! mips_opts.noat)
6176 macro_build (p, &icnt, &offset_expr, "lui", "t,u",
6177 tempreg, (int) BFD_RELOC_MIPS_HIGHEST);
6178 macro_build (p, &icnt, &offset_expr, "lui", "t,u",
6179 AT, (int) BFD_RELOC_HI16_S);
6180 macro_build (p, &icnt, &offset_expr, "daddiu", "t,r,j",
6181 tempreg, tempreg, (int) BFD_RELOC_MIPS_HIGHER);
6183 macro_build (p, &icnt, (expressionS *) NULL, "daddu",
6184 "d,v,t", AT, AT, breg);
6185 macro_build (p, &icnt, (expressionS *) NULL, "dsll32",
6186 "d,w,<", tempreg, tempreg, 0);
6187 macro_build (p, &icnt, (expressionS *) NULL, "daddu",
6188 "d,v,t", tempreg, tempreg, AT);
6189 macro_build (p, &icnt, &offset_expr, s,
6190 fmt, treg, (int) BFD_RELOC_LO16, tempreg);
6195 macro_build (p, &icnt, &offset_expr, "lui", "t,u",
6196 tempreg, (int) BFD_RELOC_MIPS_HIGHEST);
6197 macro_build (p, &icnt, &offset_expr, "daddiu", "t,r,j",
6198 tempreg, tempreg, (int) BFD_RELOC_MIPS_HIGHER);
6199 macro_build (p, &icnt, (expressionS *) NULL, "dsll",
6200 "d,w,<", tempreg, tempreg, 16);
6201 macro_build (p, &icnt, &offset_expr, "daddiu", "t,r,j",
6202 tempreg, tempreg, (int) BFD_RELOC_HI16_S);
6203 macro_build (p, &icnt, (expressionS *) NULL, "dsll",
6204 "d,w,<", tempreg, tempreg, 16);
6206 macro_build (p, &icnt, (expressionS *) NULL, "daddu",
6207 "d,v,t", tempreg, tempreg, breg);
6208 macro_build (p, &icnt, &offset_expr, s,
6209 fmt, treg, (int) BFD_RELOC_LO16, tempreg);
6214 else if (offset_expr.X_op == O_constant
6215 && !HAVE_64BIT_ADDRESS_CONSTANTS
6216 && !IS_SEXT_32BIT_NUM (offset_expr.X_add_number))
6217 as_bad (_("load/store address overflow (max 32 bits)"));
6221 if ((valueT) offset_expr.X_add_number > MAX_GPREL_OFFSET
6222 || nopic_need_relax (offset_expr.X_add_symbol, 1))
6227 macro_build ((char *) NULL, &icnt, &offset_expr, s, fmt,
6228 treg, (int) BFD_RELOC_GPREL16,
6230 p = frag_var (rs_machine_dependent, 8, 0,
6231 RELAX_ENCODE (4, 8, 0, 4, 0,
6232 (mips_opts.warn_about_macros
6234 && mips_opts.noat))),
6235 offset_expr.X_add_symbol, 0, NULL);
6238 macro_build_lui (p, &icnt, &offset_expr, tempreg);
6241 macro_build (p, &icnt, &offset_expr, s, fmt, treg,
6242 (int) BFD_RELOC_LO16, tempreg);
6246 if ((valueT) offset_expr.X_add_number > MAX_GPREL_OFFSET
6247 || nopic_need_relax (offset_expr.X_add_symbol, 1))
6252 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6253 ADDRESS_ADD_INSN, "d,v,t", tempreg, breg,
6255 macro_build ((char *) NULL, &icnt, &offset_expr, s, fmt,
6256 treg, (int) BFD_RELOC_GPREL16, tempreg);
6257 p = frag_var (rs_machine_dependent, 12, 0,
6258 RELAX_ENCODE (8, 12, 0, 8, 0, 0),
6259 offset_expr.X_add_symbol, 0, NULL);
6261 macro_build_lui (p, &icnt, &offset_expr, tempreg);
6264 macro_build (p, &icnt, (expressionS *) NULL, ADDRESS_ADD_INSN,
6265 "d,v,t", tempreg, tempreg, breg);
6268 macro_build (p, &icnt, &offset_expr, s, fmt, treg,
6269 (int) BFD_RELOC_LO16, tempreg);
6272 else if (mips_pic == SVR4_PIC && ! mips_big_got)
6275 int lw_reloc_type = (int) BFD_RELOC_MIPS_GOT16;
6277 /* If this is a reference to an external symbol, we want
6278 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
6280 <op> $treg,0($tempreg)
6282 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
6284 addiu $tempreg,$tempreg,<sym> (BFD_RELOC_LO16)
6285 <op> $treg,0($tempreg)
6288 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT_PAGE)
6289 <op> $treg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_OFST)
6291 If there is a base register, we add it to $tempreg before
6292 the <op>. If there is a constant, we stick it in the
6293 <op> instruction. We don't handle constants larger than
6294 16 bits, because we have no way to load the upper 16 bits
6295 (actually, we could handle them for the subset of cases
6296 in which we are not using $at). */
6297 assert (offset_expr.X_op == O_symbol);
6300 macro_build ((char *) NULL, &icnt, &offset_expr,
6301 ADDRESS_LOAD_INSN, "t,o(b)", tempreg,
6302 BFD_RELOC_MIPS_GOT_PAGE, mips_gp_register);
6304 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6305 ADDRESS_ADD_INSN, "d,v,t", tempreg, tempreg,
6307 macro_build ((char *) NULL, &icnt, &offset_expr, s, fmt, treg,
6308 (int) BFD_RELOC_MIPS_GOT_OFST, tempreg);
6315 expr1.X_add_number = offset_expr.X_add_number;
6316 offset_expr.X_add_number = 0;
6317 if (expr1.X_add_number < -0x8000
6318 || expr1.X_add_number >= 0x8000)
6319 as_bad (_("PIC code offset overflow (max 16 signed bits)"));
6321 macro_build ((char *) NULL, &icnt, &offset_expr, ADDRESS_LOAD_INSN,
6322 "t,o(b)", tempreg, (int) lw_reloc_type,
6324 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "");
6325 p = frag_var (rs_machine_dependent, 4, 0,
6326 RELAX_ENCODE (0, 4, -8, 0, 0, 0),
6327 offset_expr.X_add_symbol, 0, NULL);
6328 macro_build (p, &icnt, &offset_expr, ADDRESS_ADDI_INSN,
6329 "t,r,j", tempreg, tempreg, (int) BFD_RELOC_LO16);
6331 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6332 ADDRESS_ADD_INSN, "d,v,t", tempreg, tempreg, breg);
6333 macro_build ((char *) NULL, &icnt, &expr1, s, fmt, treg,
6334 (int) BFD_RELOC_LO16, tempreg);
6336 else if (mips_pic == SVR4_PIC && ! HAVE_NEWABI)
6341 /* If this is a reference to an external symbol, we want
6342 lui $tempreg,<sym> (BFD_RELOC_MIPS_GOT_HI16)
6343 addu $tempreg,$tempreg,$gp
6344 lw $tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_LO16)
6345 <op> $treg,0($tempreg)
6347 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
6349 addiu $tempreg,$tempreg,<sym> (BFD_RELOC_LO16)
6350 <op> $treg,0($tempreg)
6351 If there is a base register, we add it to $tempreg before
6352 the <op>. If there is a constant, we stick it in the
6353 <op> instruction. We don't handle constants larger than
6354 16 bits, because we have no way to load the upper 16 bits
6355 (actually, we could handle them for the subset of cases
6356 in which we are not using $at). */
6357 assert (offset_expr.X_op == O_symbol);
6358 expr1.X_add_number = offset_expr.X_add_number;
6359 offset_expr.X_add_number = 0;
6360 if (expr1.X_add_number < -0x8000
6361 || expr1.X_add_number >= 0x8000)
6362 as_bad (_("PIC code offset overflow (max 16 signed bits)"));
6363 if (reg_needs_delay (mips_gp_register))
6368 macro_build ((char *) NULL, &icnt, &offset_expr, "lui", "t,u",
6369 tempreg, (int) BFD_RELOC_MIPS_GOT_HI16);
6370 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6371 ADDRESS_ADD_INSN, "d,v,t", tempreg, tempreg,
6373 macro_build ((char *) NULL, &icnt, &offset_expr, ADDRESS_LOAD_INSN,
6374 "t,o(b)", tempreg, (int) BFD_RELOC_MIPS_GOT_LO16,
6376 p = frag_var (rs_machine_dependent, 12 + gpdel, 0,
6377 RELAX_ENCODE (12, 12 + gpdel, gpdel, 8 + gpdel, 0, 0),
6378 offset_expr.X_add_symbol, 0, NULL);
6381 macro_build (p, &icnt, (expressionS *) NULL, "nop", "");
6384 macro_build (p, &icnt, &offset_expr, ADDRESS_LOAD_INSN,
6385 "t,o(b)", tempreg, (int) BFD_RELOC_MIPS_GOT16,
6388 macro_build (p, &icnt, (expressionS *) NULL, "nop", "");
6390 macro_build (p, &icnt, &offset_expr, ADDRESS_ADDI_INSN,
6391 "t,r,j", tempreg, tempreg, (int) BFD_RELOC_LO16);
6393 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6394 ADDRESS_ADD_INSN, "d,v,t", tempreg, tempreg, breg);
6395 macro_build ((char *) NULL, &icnt, &expr1, s, fmt, treg,
6396 (int) BFD_RELOC_LO16, tempreg);
6398 else if (mips_pic == SVR4_PIC && HAVE_NEWABI)
6401 int bregsz = breg != 0 ? 4 : 0;
6403 /* If this is a reference to an external symbol, we want
6404 lui $tempreg,<sym> (BFD_RELOC_MIPS_GOT_HI16)
6405 add $tempreg,$tempreg,$gp
6406 lw $tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_LO16)
6407 <op> $treg,<ofst>($tempreg)
6408 Otherwise, for local symbols, we want:
6409 lw $tempreg,<sym>($gp) (BFD_RELOC_MIPS_GOT_PAGE)
6410 <op> $treg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_OFST) */
6411 assert (offset_expr.X_op == O_symbol);
6412 frag_now->tc_frag_data.tc_fr_offset =
6413 expr1.X_add_number = offset_expr.X_add_number;
6414 offset_expr.X_add_number = 0;
6415 if (expr1.X_add_number < -0x8000
6416 || expr1.X_add_number >= 0x8000)
6417 as_bad (_("PIC code offset overflow (max 16 signed bits)"));
6419 macro_build ((char *) NULL, &icnt, &offset_expr, "lui", "t,u",
6420 tempreg, (int) BFD_RELOC_MIPS_GOT_HI16);
6421 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6422 ADDRESS_ADD_INSN, "d,v,t", tempreg, tempreg,
6424 macro_build ((char *) NULL, &icnt, &offset_expr, ADDRESS_LOAD_INSN,
6425 "t,o(b)", tempreg, (int) BFD_RELOC_MIPS_GOT_LO16,
6428 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6429 ADDRESS_ADD_INSN, "d,v,t", tempreg, tempreg, breg);
6430 macro_build ((char *) NULL, &icnt, &expr1, s, fmt, treg,
6431 (int) BFD_RELOC_LO16, tempreg);
6433 offset_expr.X_add_number = expr1.X_add_number;
6434 p = frag_var (rs_machine_dependent, 12 + bregsz, 0,
6435 RELAX_ENCODE (16 + bregsz, 8 + bregsz,
6436 0, 4 + bregsz, 0, 0),
6437 offset_expr.X_add_symbol, 0, NULL);
6438 macro_build (p, &icnt, &offset_expr, ADDRESS_LOAD_INSN, "t,o(b)",
6439 tempreg, (int) BFD_RELOC_MIPS_GOT_PAGE,
6442 macro_build (p + 4, &icnt, (expressionS *) NULL,
6443 ADDRESS_ADD_INSN, "d,v,t", tempreg, tempreg, breg);
6444 macro_build (p + 4 + bregsz, &icnt, &offset_expr, s, fmt, treg,
6445 (int) BFD_RELOC_MIPS_GOT_OFST, tempreg);
6447 else if (mips_pic == EMBEDDED_PIC)
6449 /* If there is no base register, we want
6450 <op> $treg,<sym>($gp) (BFD_RELOC_GPREL16)
6451 If there is a base register, we want
6452 addu $tempreg,$breg,$gp
6453 <op> $treg,<sym>($tempreg) (BFD_RELOC_GPREL16)
6455 assert (offset_expr.X_op == O_symbol);
6458 macro_build ((char *) NULL, &icnt, &offset_expr, s, fmt,
6459 treg, (int) BFD_RELOC_GPREL16, mips_gp_register);
6464 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6465 ADDRESS_ADD_INSN, "d,v,t", tempreg, breg,
6467 macro_build ((char *) NULL, &icnt, &offset_expr, s, fmt,
6468 treg, (int) BFD_RELOC_GPREL16, tempreg);
6481 load_register (&icnt, treg, &imm_expr, 0);
6485 load_register (&icnt, treg, &imm_expr, 1);
6489 if (imm_expr.X_op == O_constant)
6491 load_register (&icnt, AT, &imm_expr, 0);
6492 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6493 "mtc1", "t,G", AT, treg);
6498 assert (offset_expr.X_op == O_symbol
6499 && strcmp (segment_name (S_GET_SEGMENT
6500 (offset_expr.X_add_symbol)),
6502 && offset_expr.X_add_number == 0);
6503 macro_build ((char *) NULL, &icnt, &offset_expr, "lwc1", "T,o(b)",
6504 treg, (int) BFD_RELOC_MIPS_LITERAL, mips_gp_register);
6509 /* Check if we have a constant in IMM_EXPR. If the GPRs are 64 bits
6510 wide, IMM_EXPR is the entire value. Otherwise IMM_EXPR is the high
6511 order 32 bits of the value and the low order 32 bits are either
6512 zero or in OFFSET_EXPR. */
6513 if (imm_expr.X_op == O_constant || imm_expr.X_op == O_big)
6515 if (HAVE_64BIT_GPRS)
6516 load_register (&icnt, treg, &imm_expr, 1);
6521 if (target_big_endian)
6533 load_register (&icnt, hreg, &imm_expr, 0);
6536 if (offset_expr.X_op == O_absent)
6537 move_register (&icnt, lreg, 0);
6540 assert (offset_expr.X_op == O_constant);
6541 load_register (&icnt, lreg, &offset_expr, 0);
6548 /* We know that sym is in the .rdata section. First we get the
6549 upper 16 bits of the address. */
6550 if (mips_pic == NO_PIC)
6552 macro_build_lui (NULL, &icnt, &offset_expr, AT);
6554 else if (mips_pic == SVR4_PIC)
6556 macro_build ((char *) NULL, &icnt, &offset_expr, ADDRESS_LOAD_INSN,
6557 "t,o(b)", AT, (int) BFD_RELOC_MIPS_GOT16,
6560 else if (mips_pic == EMBEDDED_PIC)
6562 /* For embedded PIC we pick up the entire address off $gp in
6563 a single instruction. */
6564 macro_build ((char *) NULL, &icnt, &offset_expr, ADDRESS_ADDI_INSN,
6565 "t,r,j", AT, mips_gp_register,
6566 (int) BFD_RELOC_GPREL16);
6567 offset_expr.X_op = O_constant;
6568 offset_expr.X_add_number = 0;
6573 /* Now we load the register(s). */
6574 if (HAVE_64BIT_GPRS)
6575 macro_build ((char *) NULL, &icnt, &offset_expr, "ld", "t,o(b)",
6576 treg, (int) BFD_RELOC_LO16, AT);
6579 macro_build ((char *) NULL, &icnt, &offset_expr, "lw", "t,o(b)",
6580 treg, (int) BFD_RELOC_LO16, AT);
6583 /* FIXME: How in the world do we deal with the possible
6585 offset_expr.X_add_number += 4;
6586 macro_build ((char *) NULL, &icnt, &offset_expr, "lw", "t,o(b)",
6587 treg + 1, (int) BFD_RELOC_LO16, AT);
6591 /* To avoid confusion in tc_gen_reloc, we must ensure that this
6592 does not become a variant frag. */
6593 frag_wane (frag_now);
6599 /* Check if we have a constant in IMM_EXPR. If the FPRs are 64 bits
6600 wide, IMM_EXPR is the entire value and the GPRs are known to be 64
6601 bits wide as well. Otherwise IMM_EXPR is the high order 32 bits of
6602 the value and the low order 32 bits are either zero or in
6604 if (imm_expr.X_op == O_constant || imm_expr.X_op == O_big)
6606 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_FPRS);
6607 if (HAVE_64BIT_FPRS)
6609 assert (HAVE_64BIT_GPRS);
6610 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6611 "dmtc1", "t,S", AT, treg);
6615 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6616 "mtc1", "t,G", AT, treg + 1);
6617 if (offset_expr.X_op == O_absent)
6618 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6619 "mtc1", "t,G", 0, treg);
6622 assert (offset_expr.X_op == O_constant);
6623 load_register (&icnt, AT, &offset_expr, 0);
6624 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6625 "mtc1", "t,G", AT, treg);
6631 assert (offset_expr.X_op == O_symbol
6632 && offset_expr.X_add_number == 0);
6633 s = segment_name (S_GET_SEGMENT (offset_expr.X_add_symbol));
6634 if (strcmp (s, ".lit8") == 0)
6636 if (mips_opts.isa != ISA_MIPS1)
6638 macro_build ((char *) NULL, &icnt, &offset_expr, "ldc1",
6639 "T,o(b)", treg, (int) BFD_RELOC_MIPS_LITERAL,
6643 breg = mips_gp_register;
6644 r = BFD_RELOC_MIPS_LITERAL;
6649 assert (strcmp (s, RDATA_SECTION_NAME) == 0);
6650 if (mips_pic == SVR4_PIC)
6651 macro_build ((char *) NULL, &icnt, &offset_expr,
6652 ADDRESS_LOAD_INSN, "t,o(b)", AT,
6653 (int) BFD_RELOC_MIPS_GOT16, mips_gp_register);
6656 /* FIXME: This won't work for a 64 bit address. */
6657 macro_build_lui (NULL, &icnt, &offset_expr, AT);
6660 if (mips_opts.isa != ISA_MIPS1)
6662 macro_build ((char *) NULL, &icnt, &offset_expr, "ldc1",
6663 "T,o(b)", treg, (int) BFD_RELOC_LO16, AT);
6665 /* To avoid confusion in tc_gen_reloc, we must ensure
6666 that this does not become a variant frag. */
6667 frag_wane (frag_now);
6678 if (mips_arch == CPU_R4650)
6680 as_bad (_("opcode not supported on this processor"));
6683 /* Even on a big endian machine $fn comes before $fn+1. We have
6684 to adjust when loading from memory. */
6687 assert (mips_opts.isa == ISA_MIPS1);
6688 macro_build ((char *) NULL, &icnt, &offset_expr, "lwc1", "T,o(b)",
6689 target_big_endian ? treg + 1 : treg,
6691 /* FIXME: A possible overflow which I don't know how to deal
6693 offset_expr.X_add_number += 4;
6694 macro_build ((char *) NULL, &icnt, &offset_expr, "lwc1", "T,o(b)",
6695 target_big_endian ? treg : treg + 1,
6698 /* To avoid confusion in tc_gen_reloc, we must ensure that this
6699 does not become a variant frag. */
6700 frag_wane (frag_now);
6709 * The MIPS assembler seems to check for X_add_number not
6710 * being double aligned and generating:
6713 * addiu at,at,%lo(foo+1)
6716 * But, the resulting address is the same after relocation so why
6717 * generate the extra instruction?
6719 if (mips_arch == CPU_R4650)
6721 as_bad (_("opcode not supported on this processor"));
6724 /* Itbl support may require additional care here. */
6726 if (mips_opts.isa != ISA_MIPS1)
6737 if (mips_arch == CPU_R4650)
6739 as_bad (_("opcode not supported on this processor"));
6743 if (mips_opts.isa != ISA_MIPS1)
6751 /* Itbl support may require additional care here. */
6756 if (HAVE_64BIT_GPRS)
6767 if (HAVE_64BIT_GPRS)
6777 /* We do _not_ bother to allow embedded PIC (symbol-local_symbol)
6778 loads for the case of doing a pair of loads to simulate an 'ld'.
6779 This is not currently done by the compiler, and assembly coders
6780 writing embedded-pic code can cope. */
6782 if (offset_expr.X_op != O_symbol
6783 && offset_expr.X_op != O_constant)
6785 as_bad (_("expression too complex"));
6786 offset_expr.X_op = O_constant;
6789 /* Even on a big endian machine $fn comes before $fn+1. We have
6790 to adjust when loading from memory. We set coproc if we must
6791 load $fn+1 first. */
6792 /* Itbl support may require additional care here. */
6793 if (! target_big_endian)
6796 if (mips_pic == NO_PIC
6797 || offset_expr.X_op == O_constant)
6801 /* If this is a reference to a GP relative symbol, we want
6802 <op> $treg,<sym>($gp) (BFD_RELOC_GPREL16)
6803 <op> $treg+1,<sym>+4($gp) (BFD_RELOC_GPREL16)
6804 If we have a base register, we use this
6806 <op> $treg,<sym>($at) (BFD_RELOC_GPREL16)
6807 <op> $treg+1,<sym>+4($at) (BFD_RELOC_GPREL16)
6808 If this is not a GP relative symbol, we want
6809 lui $at,<sym> (BFD_RELOC_HI16_S)
6810 <op> $treg,<sym>($at) (BFD_RELOC_LO16)
6811 <op> $treg+1,<sym>+4($at) (BFD_RELOC_LO16)
6812 If there is a base register, we add it to $at after the
6813 lui instruction. If there is a constant, we always use
6815 if ((valueT) offset_expr.X_add_number > MAX_GPREL_OFFSET
6816 || nopic_need_relax (offset_expr.X_add_symbol, 1))
6828 tempreg = mips_gp_register;
6835 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6836 ADDRESS_ADD_INSN, "d,v,t", AT, breg,
6843 /* Itbl support may require additional care here. */
6844 macro_build ((char *) NULL, &icnt, &offset_expr, s, fmt,
6845 coproc ? treg + 1 : treg,
6846 (int) BFD_RELOC_GPREL16, tempreg);
6847 offset_expr.X_add_number += 4;
6849 /* Set mips_optimize to 2 to avoid inserting an
6851 hold_mips_optimize = mips_optimize;
6853 /* Itbl support may require additional care here. */
6854 macro_build ((char *) NULL, &icnt, &offset_expr, s, fmt,
6855 coproc ? treg : treg + 1,
6856 (int) BFD_RELOC_GPREL16, tempreg);
6857 mips_optimize = hold_mips_optimize;
6859 p = frag_var (rs_machine_dependent, 12 + off, 0,
6860 RELAX_ENCODE (8 + off, 12 + off, 0, 4 + off, 1,
6861 used_at && mips_opts.noat),
6862 offset_expr.X_add_symbol, 0, NULL);
6864 /* We just generated two relocs. When tc_gen_reloc
6865 handles this case, it will skip the first reloc and
6866 handle the second. The second reloc already has an
6867 extra addend of 4, which we added above. We must
6868 subtract it out, and then subtract another 4 to make
6869 the first reloc come out right. The second reloc
6870 will come out right because we are going to add 4 to
6871 offset_expr when we build its instruction below.
6873 If we have a symbol, then we don't want to include
6874 the offset, because it will wind up being included
6875 when we generate the reloc. */
6877 if (offset_expr.X_op == O_constant)
6878 offset_expr.X_add_number -= 8;
6881 offset_expr.X_add_number = -4;
6882 offset_expr.X_op = O_constant;
6885 macro_build_lui (p, &icnt, &offset_expr, AT);
6890 macro_build (p, &icnt, (expressionS *) NULL, ADDRESS_ADD_INSN,
6891 "d,v,t", AT, breg, AT);
6895 /* Itbl support may require additional care here. */
6896 macro_build (p, &icnt, &offset_expr, s, fmt,
6897 coproc ? treg + 1 : treg,
6898 (int) BFD_RELOC_LO16, AT);
6901 /* FIXME: How do we handle overflow here? */
6902 offset_expr.X_add_number += 4;
6903 /* Itbl support may require additional care here. */
6904 macro_build (p, &icnt, &offset_expr, s, fmt,
6905 coproc ? treg : treg + 1,
6906 (int) BFD_RELOC_LO16, AT);
6908 else if (mips_pic == SVR4_PIC && ! mips_big_got)
6912 /* If this is a reference to an external symbol, we want
6913 lw $at,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
6918 lw $at,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
6920 <op> $treg,<sym>($at) (BFD_RELOC_LO16)
6921 <op> $treg+1,<sym>+4($at) (BFD_RELOC_LO16)
6922 If there is a base register we add it to $at before the
6923 lwc1 instructions. If there is a constant we include it
6924 in the lwc1 instructions. */
6926 expr1.X_add_number = offset_expr.X_add_number;
6927 offset_expr.X_add_number = 0;
6928 if (expr1.X_add_number < -0x8000
6929 || expr1.X_add_number >= 0x8000 - 4)
6930 as_bad (_("PIC code offset overflow (max 16 signed bits)"));
6935 frag_grow (24 + off);
6936 macro_build ((char *) NULL, &icnt, &offset_expr, ADDRESS_LOAD_INSN,
6937 "t,o(b)", AT, (int) BFD_RELOC_MIPS_GOT16,
6939 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "");
6941 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
6942 ADDRESS_ADD_INSN, "d,v,t", AT, breg, AT);
6943 /* Itbl support may require additional care here. */
6944 macro_build ((char *) NULL, &icnt, &expr1, s, fmt,
6945 coproc ? treg + 1 : treg,
6946 (int) BFD_RELOC_LO16, AT);
6947 expr1.X_add_number += 4;
6949 /* Set mips_optimize to 2 to avoid inserting an undesired
6951 hold_mips_optimize = mips_optimize;
6953 /* Itbl support may require additional care here. */
6954 macro_build ((char *) NULL, &icnt, &expr1, s, fmt,
6955 coproc ? treg : treg + 1,
6956 (int) BFD_RELOC_LO16, AT);
6957 mips_optimize = hold_mips_optimize;
6959 (void) frag_var (rs_machine_dependent, 0, 0,
6960 RELAX_ENCODE (0, 0, -16 - off, -8, 1, 0),
6961 offset_expr.X_add_symbol, 0, NULL);
6963 else if (mips_pic == SVR4_PIC)
6968 /* If this is a reference to an external symbol, we want
6969 lui $at,<sym> (BFD_RELOC_MIPS_GOT_HI16)
6971 lw $at,<sym>($at) (BFD_RELOC_MIPS_GOT_LO16)
6976 lw $at,<sym>($gp) (BFD_RELOC_MIPS_GOT16)
6978 <op> $treg,<sym>($at) (BFD_RELOC_LO16)
6979 <op> $treg+1,<sym>+4($at) (BFD_RELOC_LO16)
6980 If there is a base register we add it to $at before the
6981 lwc1 instructions. If there is a constant we include it
6982 in the lwc1 instructions. */
6984 expr1.X_add_number = offset_expr.X_add_number;
6985 offset_expr.X_add_number = 0;
6986 if (expr1.X_add_number < -0x8000
6987 || expr1.X_add_number >= 0x8000 - 4)
6988 as_bad (_("PIC code offset overflow (max 16 signed bits)"));
6989 if (reg_needs_delay (mips_gp_register))
6998 macro_build ((char *) NULL, &icnt, &offset_expr, "lui", "t,u",
6999 AT, (int) BFD_RELOC_MIPS_GOT_HI16);
7000 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7001 ADDRESS_ADD_INSN, "d,v,t", AT, AT, mips_gp_register);
7002 macro_build ((char *) NULL, &icnt, &offset_expr, ADDRESS_LOAD_INSN,
7003 "t,o(b)", AT, (int) BFD_RELOC_MIPS_GOT_LO16, AT);
7004 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "");
7006 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7007 ADDRESS_ADD_INSN, "d,v,t", AT, breg, AT);
7008 /* Itbl support may require additional care here. */
7009 macro_build ((char *) NULL, &icnt, &expr1, s, fmt,
7010 coproc ? treg + 1 : treg,
7011 (int) BFD_RELOC_LO16, AT);
7012 expr1.X_add_number += 4;
7014 /* Set mips_optimize to 2 to avoid inserting an undesired
7016 hold_mips_optimize = mips_optimize;
7018 /* Itbl support may require additional care here. */
7019 macro_build ((char *) NULL, &icnt, &expr1, s, fmt,
7020 coproc ? treg : treg + 1,
7021 (int) BFD_RELOC_LO16, AT);
7022 mips_optimize = hold_mips_optimize;
7023 expr1.X_add_number -= 4;
7025 p = frag_var (rs_machine_dependent, 16 + gpdel + off, 0,
7026 RELAX_ENCODE (24 + off, 16 + gpdel + off, gpdel,
7027 8 + gpdel + off, 1, 0),
7028 offset_expr.X_add_symbol, 0, NULL);
7031 macro_build (p, &icnt, (expressionS *) NULL, "nop", "");
7034 macro_build (p, &icnt, &offset_expr, ADDRESS_LOAD_INSN,
7035 "t,o(b)", AT, (int) BFD_RELOC_MIPS_GOT16,
7038 macro_build (p, &icnt, (expressionS *) NULL, "nop", "");
7042 macro_build (p, &icnt, (expressionS *) NULL, ADDRESS_ADD_INSN,
7043 "d,v,t", AT, breg, AT);
7046 /* Itbl support may require additional care here. */
7047 macro_build (p, &icnt, &expr1, s, fmt,
7048 coproc ? treg + 1 : treg,
7049 (int) BFD_RELOC_LO16, AT);
7051 expr1.X_add_number += 4;
7053 /* Set mips_optimize to 2 to avoid inserting an undesired
7055 hold_mips_optimize = mips_optimize;
7057 /* Itbl support may require additional care here. */
7058 macro_build (p, &icnt, &expr1, s, fmt,
7059 coproc ? treg : treg + 1,
7060 (int) BFD_RELOC_LO16, AT);
7061 mips_optimize = hold_mips_optimize;
7063 else if (mips_pic == EMBEDDED_PIC)
7065 /* If there is no base register, we use
7066 <op> $treg,<sym>($gp) (BFD_RELOC_GPREL16)
7067 <op> $treg+1,<sym>+4($gp) (BFD_RELOC_GPREL16)
7068 If we have a base register, we use
7070 <op> $treg,<sym>($at) (BFD_RELOC_GPREL16)
7071 <op> $treg+1,<sym>+4($at) (BFD_RELOC_GPREL16)
7075 tempreg = mips_gp_register;
7080 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7081 ADDRESS_ADD_INSN, "d,v,t", AT, breg,
7087 /* Itbl support may require additional care here. */
7088 macro_build ((char *) NULL, &icnt, &offset_expr, s, fmt,
7089 coproc ? treg + 1 : treg,
7090 (int) BFD_RELOC_GPREL16, tempreg);
7091 offset_expr.X_add_number += 4;
7092 /* Itbl support may require additional care here. */
7093 macro_build ((char *) NULL, &icnt, &offset_expr, s, fmt,
7094 coproc ? treg : treg + 1,
7095 (int) BFD_RELOC_GPREL16, tempreg);
7111 assert (HAVE_32BIT_ADDRESSES);
7112 macro_build ((char *) NULL, &icnt, &offset_expr, s, "t,o(b)", treg,
7113 (int) BFD_RELOC_LO16, breg);
7114 offset_expr.X_add_number += 4;
7115 macro_build ((char *) NULL, &icnt, &offset_expr, s, "t,o(b)", treg + 1,
7116 (int) BFD_RELOC_LO16, breg);
7119 /* New code added to support COPZ instructions.
7120 This code builds table entries out of the macros in mip_opcodes.
7121 R4000 uses interlocks to handle coproc delays.
7122 Other chips (like the R3000) require nops to be inserted for delays.
7124 FIXME: Currently, we require that the user handle delays.
7125 In order to fill delay slots for non-interlocked chips,
7126 we must have a way to specify delays based on the coprocessor.
7127 Eg. 4 cycles if load coproc reg from memory, 1 if in cache, etc.
7128 What are the side-effects of the cop instruction?
7129 What cache support might we have and what are its effects?
7130 Both coprocessor & memory require delays. how long???
7131 What registers are read/set/modified?
7133 If an itbl is provided to interpret cop instructions,
7134 this knowledge can be encoded in the itbl spec. */
7148 /* For now we just do C (same as Cz). The parameter will be
7149 stored in insn_opcode by mips_ip. */
7150 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "C",
7155 move_register (&icnt, dreg, sreg);
7158 #ifdef LOSING_COMPILER
7160 /* Try and see if this is a new itbl instruction.
7161 This code builds table entries out of the macros in mip_opcodes.
7162 FIXME: For now we just assemble the expression and pass it's
7163 value along as a 32-bit immediate.
7164 We may want to have the assembler assemble this value,
7165 so that we gain the assembler's knowledge of delay slots,
7167 Would it be more efficient to use mask (id) here? */
7168 if (itbl_have_entries
7169 && (immed_expr = itbl_assemble (ip->insn_mo->name, "")))
7171 s = ip->insn_mo->name;
7173 coproc = ITBL_DECODE_PNUM (immed_expr);;
7174 macro_build ((char *) NULL, &icnt, &immed_expr, s, "C");
7181 as_warn (_("Macro used $at after \".set noat\""));
7186 struct mips_cl_insn *ip;
7188 register int treg, sreg, dreg, breg;
7204 bfd_reloc_code_real_type r;
7207 treg = (ip->insn_opcode >> 16) & 0x1f;
7208 dreg = (ip->insn_opcode >> 11) & 0x1f;
7209 sreg = breg = (ip->insn_opcode >> 21) & 0x1f;
7210 mask = ip->insn_mo->mask;
7212 expr1.X_op = O_constant;
7213 expr1.X_op_symbol = NULL;
7214 expr1.X_add_symbol = NULL;
7215 expr1.X_add_number = 1;
7219 #endif /* LOSING_COMPILER */
7224 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7225 dbl ? "dmultu" : "multu", "s,t", sreg, treg);
7226 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "mflo", "d",
7233 /* The MIPS assembler some times generates shifts and adds. I'm
7234 not trying to be that fancy. GCC should do this for us
7236 load_register (&icnt, AT, &imm_expr, dbl);
7237 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7238 dbl ? "dmult" : "mult", "s,t", sreg, AT);
7239 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "mflo", "d",
7253 mips_emit_delays (TRUE);
7254 ++mips_opts.noreorder;
7255 mips_any_noreorder = 1;
7257 load_register (&icnt, AT, &imm_expr, dbl);
7258 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7259 dbl ? "dmult" : "mult", "s,t", sreg, imm ? AT : treg);
7260 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "mflo", "d",
7262 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7263 dbl ? "dsra32" : "sra", "d,w,<", dreg, dreg, RA);
7264 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "mfhi", "d",
7267 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "tne",
7268 "s,t,q", dreg, AT, 6);
7271 expr1.X_add_number = 8;
7272 macro_build ((char *) NULL, &icnt, &expr1, "beq", "s,t,p", dreg,
7274 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "",
7276 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "break",
7279 --mips_opts.noreorder;
7280 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "mflo", "d", dreg);
7293 mips_emit_delays (TRUE);
7294 ++mips_opts.noreorder;
7295 mips_any_noreorder = 1;
7297 load_register (&icnt, AT, &imm_expr, dbl);
7298 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7299 dbl ? "dmultu" : "multu",
7300 "s,t", sreg, imm ? AT : treg);
7301 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "mfhi", "d",
7303 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "mflo", "d",
7306 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "tne",
7310 expr1.X_add_number = 8;
7311 macro_build ((char *) NULL, &icnt, &expr1, "beq", "s,t,p", AT, 0);
7312 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "",
7314 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "break",
7317 --mips_opts.noreorder;
7321 if (ISA_HAS_DROR (mips_opts.isa) || CPU_HAS_DROR (mips_arch))
7333 macro_build ((char *) NULL, &icnt, NULL, "dnegu",
7334 "d,w", tempreg, treg);
7335 macro_build ((char *) NULL, &icnt, NULL, "drorv",
7336 "d,t,s", dreg, sreg, tempreg);
7341 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "dsubu",
7342 "d,v,t", AT, 0, treg);
7343 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "dsrlv",
7344 "d,t,s", AT, sreg, AT);
7345 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "dsllv",
7346 "d,t,s", dreg, sreg, treg);
7347 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or",
7348 "d,v,t", dreg, dreg, AT);
7352 if (ISA_HAS_ROR (mips_opts.isa) || CPU_HAS_ROR (mips_arch))
7364 macro_build ((char *) NULL, &icnt, NULL, "negu",
7365 "d,w", tempreg, treg);
7366 macro_build ((char *) NULL, &icnt, NULL, "rorv",
7367 "d,t,s", dreg, sreg, tempreg);
7372 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "subu",
7373 "d,v,t", AT, 0, treg);
7374 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "srlv",
7375 "d,t,s", AT, sreg, AT);
7376 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sllv",
7377 "d,t,s", dreg, sreg, treg);
7378 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or",
7379 "d,v,t", dreg, dreg, AT);
7387 if (imm_expr.X_op != O_constant)
7388 as_bad (_("Improper rotate count"));
7389 rot = imm_expr.X_add_number & 0x3f;
7390 if (ISA_HAS_DROR (mips_opts.isa) || CPU_HAS_DROR (mips_arch))
7392 rot = (64 - rot) & 0x3f;
7394 macro_build ((char *) NULL, &icnt, NULL, "dror32",
7395 "d,w,<", dreg, sreg, rot - 32);
7397 macro_build ((char *) NULL, &icnt, NULL, "dror",
7398 "d,w,<", dreg, sreg, rot);
7403 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "dsrl",
7404 "d,w,<", dreg, sreg, 0);
7407 l = (rot < 0x20) ? "dsll" : "dsll32";
7408 r = ((0x40 - rot) < 0x20) ? "dsrl" : "dsrl32";
7410 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, l,
7411 "d,w,<", AT, sreg, rot);
7412 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, r,
7413 "d,w,<", dreg, sreg, (0x20 - rot) & 0x1f);
7414 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or",
7415 "d,v,t", dreg, dreg, AT);
7423 if (imm_expr.X_op != O_constant)
7424 as_bad (_("Improper rotate count"));
7425 rot = imm_expr.X_add_number & 0x1f;
7426 if (ISA_HAS_ROR (mips_opts.isa) || CPU_HAS_ROR (mips_arch))
7428 macro_build ((char *) NULL, &icnt, NULL, "ror",
7429 "d,w,<", dreg, sreg, (32 - rot) & 0x1f);
7434 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "srl",
7435 "d,w,<", dreg, sreg, 0);
7438 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sll",
7439 "d,w,<", AT, sreg, rot);
7440 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "srl",
7441 "d,w,<", dreg, sreg, (0x20 - rot) & 0x1f);
7442 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or",
7443 "d,v,t", dreg, dreg, AT);
7448 if (ISA_HAS_DROR (mips_opts.isa) || CPU_HAS_DROR (mips_arch))
7450 macro_build ((char *) NULL, &icnt, NULL, "drorv",
7451 "d,t,s", dreg, sreg, treg);
7454 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "dsubu",
7455 "d,v,t", AT, 0, treg);
7456 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "dsllv",
7457 "d,t,s", AT, sreg, AT);
7458 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "dsrlv",
7459 "d,t,s", dreg, sreg, treg);
7460 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or",
7461 "d,v,t", dreg, dreg, AT);
7465 if (ISA_HAS_ROR (mips_opts.isa) || CPU_HAS_ROR (mips_arch))
7467 macro_build ((char *) NULL, &icnt, NULL, "rorv",
7468 "d,t,s", dreg, sreg, treg);
7471 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "subu",
7472 "d,v,t", AT, 0, treg);
7473 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sllv",
7474 "d,t,s", AT, sreg, AT);
7475 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "srlv",
7476 "d,t,s", dreg, sreg, treg);
7477 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or",
7478 "d,v,t", dreg, dreg, AT);
7486 if (imm_expr.X_op != O_constant)
7487 as_bad (_("Improper rotate count"));
7488 rot = imm_expr.X_add_number & 0x3f;
7489 if (ISA_HAS_DROR (mips_opts.isa) || CPU_HAS_DROR (mips_arch))
7492 macro_build ((char *) NULL, &icnt, NULL, "dror32",
7493 "d,w,<", dreg, sreg, rot - 32);
7495 macro_build ((char *) NULL, &icnt, NULL, "dror",
7496 "d,w,<", dreg, sreg, rot);
7501 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "dsrl",
7502 "d,w,<", dreg, sreg, 0);
7505 r = (rot < 0x20) ? "dsrl" : "dsrl32";
7506 l = ((0x40 - rot) < 0x20) ? "dsll" : "dsll32";
7508 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, r,
7509 "d,w,<", AT, sreg, rot);
7510 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, l,
7511 "d,w,<", dreg, sreg, (0x20 - rot) & 0x1f);
7512 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or",
7513 "d,v,t", dreg, dreg, AT);
7521 if (imm_expr.X_op != O_constant)
7522 as_bad (_("Improper rotate count"));
7523 rot = imm_expr.X_add_number & 0x1f;
7524 if (ISA_HAS_ROR (mips_opts.isa) || CPU_HAS_ROR (mips_arch))
7526 macro_build ((char *) NULL, &icnt, NULL, "ror",
7527 "d,w,<", dreg, sreg, rot);
7532 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "srl",
7533 "d,w,<", dreg, sreg, 0);
7536 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "srl",
7537 "d,w,<", AT, sreg, rot);
7538 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sll",
7539 "d,w,<", dreg, sreg, (0x20 - rot) & 0x1f);
7540 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or",
7541 "d,v,t", dreg, dreg, AT);
7546 if (mips_arch == CPU_R4650)
7548 as_bad (_("opcode not supported on this processor"));
7551 assert (mips_opts.isa == ISA_MIPS1);
7552 /* Even on a big endian machine $fn comes before $fn+1. We have
7553 to adjust when storing to memory. */
7554 macro_build ((char *) NULL, &icnt, &offset_expr, "swc1", "T,o(b)",
7555 target_big_endian ? treg + 1 : treg,
7556 (int) BFD_RELOC_LO16, breg);
7557 offset_expr.X_add_number += 4;
7558 macro_build ((char *) NULL, &icnt, &offset_expr, "swc1", "T,o(b)",
7559 target_big_endian ? treg : treg + 1,
7560 (int) BFD_RELOC_LO16, breg);
7565 macro_build ((char *) NULL, &icnt, &expr1, "sltiu", "t,r,j", dreg,
7566 treg, (int) BFD_RELOC_LO16);
7568 macro_build ((char *) NULL, &icnt, &expr1, "sltiu", "t,r,j", dreg,
7569 sreg, (int) BFD_RELOC_LO16);
7572 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "xor",
7573 "d,v,t", dreg, sreg, treg);
7574 macro_build ((char *) NULL, &icnt, &expr1, "sltiu", "t,r,j", dreg,
7575 dreg, (int) BFD_RELOC_LO16);
7580 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
7582 macro_build ((char *) NULL, &icnt, &expr1, "sltiu", "t,r,j", dreg,
7583 sreg, (int) BFD_RELOC_LO16);
7588 as_warn (_("Instruction %s: result is always false"),
7590 move_register (&icnt, dreg, 0);
7593 if (imm_expr.X_op == O_constant
7594 && imm_expr.X_add_number >= 0
7595 && imm_expr.X_add_number < 0x10000)
7597 macro_build ((char *) NULL, &icnt, &imm_expr, "xori", "t,r,i", dreg,
7598 sreg, (int) BFD_RELOC_LO16);
7601 else if (imm_expr.X_op == O_constant
7602 && imm_expr.X_add_number > -0x8000
7603 && imm_expr.X_add_number < 0)
7605 imm_expr.X_add_number = -imm_expr.X_add_number;
7606 macro_build ((char *) NULL, &icnt, &imm_expr,
7607 HAVE_32BIT_GPRS ? "addiu" : "daddiu",
7608 "t,r,j", dreg, sreg, (int) BFD_RELOC_LO16);
7613 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_GPRS);
7614 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "xor",
7615 "d,v,t", dreg, sreg, AT);
7618 macro_build ((char *) NULL, &icnt, &expr1, "sltiu", "t,r,j", dreg, dreg,
7619 (int) BFD_RELOC_LO16);
7624 case M_SGE: /* sreg >= treg <==> not (sreg < treg) */
7630 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "d,v,t",
7632 macro_build ((char *) NULL, &icnt, &expr1, "xori", "t,r,i", dreg, dreg,
7633 (int) BFD_RELOC_LO16);
7636 case M_SGE_I: /* sreg >= I <==> not (sreg < I) */
7638 if (imm_expr.X_op == O_constant
7639 && imm_expr.X_add_number >= -0x8000
7640 && imm_expr.X_add_number < 0x8000)
7642 macro_build ((char *) NULL, &icnt, &imm_expr,
7643 mask == M_SGE_I ? "slti" : "sltiu",
7644 "t,r,j", dreg, sreg, (int) BFD_RELOC_LO16);
7649 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_GPRS);
7650 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7651 mask == M_SGE_I ? "slt" : "sltu", "d,v,t", dreg, sreg,
7655 macro_build ((char *) NULL, &icnt, &expr1, "xori", "t,r,i", dreg, dreg,
7656 (int) BFD_RELOC_LO16);
7661 case M_SGT: /* sreg > treg <==> treg < sreg */
7667 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "d,v,t",
7671 case M_SGT_I: /* sreg > I <==> I < sreg */
7677 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_GPRS);
7678 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "d,v,t",
7682 case M_SLE: /* sreg <= treg <==> treg >= sreg <==> not (treg < sreg) */
7688 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "d,v,t",
7690 macro_build ((char *) NULL, &icnt, &expr1, "xori", "t,r,i", dreg, dreg,
7691 (int) BFD_RELOC_LO16);
7694 case M_SLE_I: /* sreg <= I <==> I >= sreg <==> not (I < sreg) */
7700 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_GPRS);
7701 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "d,v,t",
7703 macro_build ((char *) NULL, &icnt, &expr1, "xori", "t,r,i", dreg, dreg,
7704 (int) BFD_RELOC_LO16);
7708 if (imm_expr.X_op == O_constant
7709 && imm_expr.X_add_number >= -0x8000
7710 && imm_expr.X_add_number < 0x8000)
7712 macro_build ((char *) NULL, &icnt, &imm_expr, "slti", "t,r,j",
7713 dreg, sreg, (int) BFD_RELOC_LO16);
7716 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_GPRS);
7717 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "slt", "d,v,t",
7722 if (imm_expr.X_op == O_constant
7723 && imm_expr.X_add_number >= -0x8000
7724 && imm_expr.X_add_number < 0x8000)
7726 macro_build ((char *) NULL, &icnt, &imm_expr, "sltiu", "t,r,j",
7727 dreg, sreg, (int) BFD_RELOC_LO16);
7730 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_GPRS);
7731 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sltu",
7732 "d,v,t", dreg, sreg, AT);
7737 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sltu",
7738 "d,v,t", dreg, 0, treg);
7740 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sltu",
7741 "d,v,t", dreg, 0, sreg);
7744 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "xor",
7745 "d,v,t", dreg, sreg, treg);
7746 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sltu",
7747 "d,v,t", dreg, 0, dreg);
7752 if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
7754 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sltu",
7755 "d,v,t", dreg, 0, sreg);
7760 as_warn (_("Instruction %s: result is always true"),
7762 macro_build ((char *) NULL, &icnt, &expr1,
7763 HAVE_32BIT_GPRS ? "addiu" : "daddiu",
7764 "t,r,j", dreg, 0, (int) BFD_RELOC_LO16);
7767 if (imm_expr.X_op == O_constant
7768 && imm_expr.X_add_number >= 0
7769 && imm_expr.X_add_number < 0x10000)
7771 macro_build ((char *) NULL, &icnt, &imm_expr, "xori", "t,r,i",
7772 dreg, sreg, (int) BFD_RELOC_LO16);
7775 else if (imm_expr.X_op == O_constant
7776 && imm_expr.X_add_number > -0x8000
7777 && imm_expr.X_add_number < 0)
7779 imm_expr.X_add_number = -imm_expr.X_add_number;
7780 macro_build ((char *) NULL, &icnt, &imm_expr,
7781 HAVE_32BIT_GPRS ? "addiu" : "daddiu",
7782 "t,r,j", dreg, sreg, (int) BFD_RELOC_LO16);
7787 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_GPRS);
7788 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "xor",
7789 "d,v,t", dreg, sreg, AT);
7792 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sltu",
7793 "d,v,t", dreg, 0, dreg);
7801 if (imm_expr.X_op == O_constant
7802 && imm_expr.X_add_number > -0x8000
7803 && imm_expr.X_add_number <= 0x8000)
7805 imm_expr.X_add_number = -imm_expr.X_add_number;
7806 macro_build ((char *) NULL, &icnt, &imm_expr,
7807 dbl ? "daddi" : "addi",
7808 "t,r,j", dreg, sreg, (int) BFD_RELOC_LO16);
7811 load_register (&icnt, AT, &imm_expr, dbl);
7812 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7813 dbl ? "dsub" : "sub", "d,v,t", dreg, sreg, AT);
7819 if (imm_expr.X_op == O_constant
7820 && imm_expr.X_add_number > -0x8000
7821 && imm_expr.X_add_number <= 0x8000)
7823 imm_expr.X_add_number = -imm_expr.X_add_number;
7824 macro_build ((char *) NULL, &icnt, &imm_expr,
7825 dbl ? "daddiu" : "addiu",
7826 "t,r,j", dreg, sreg, (int) BFD_RELOC_LO16);
7829 load_register (&icnt, AT, &imm_expr, dbl);
7830 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7831 dbl ? "dsubu" : "subu", "d,v,t", dreg, sreg, AT);
7852 load_register (&icnt, AT, &imm_expr, HAVE_64BIT_GPRS);
7853 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "s,t", sreg,
7859 assert (mips_opts.isa == ISA_MIPS1);
7860 sreg = (ip->insn_opcode >> 11) & 0x1f; /* floating reg */
7861 dreg = (ip->insn_opcode >> 06) & 0x1f; /* floating reg */
7864 * Is the double cfc1 instruction a bug in the mips assembler;
7865 * or is there a reason for it?
7867 mips_emit_delays (TRUE);
7868 ++mips_opts.noreorder;
7869 mips_any_noreorder = 1;
7870 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "cfc1", "t,G",
7872 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "cfc1", "t,G",
7874 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "");
7875 expr1.X_add_number = 3;
7876 macro_build ((char *) NULL, &icnt, &expr1, "ori", "t,r,i", AT, treg,
7877 (int) BFD_RELOC_LO16);
7878 expr1.X_add_number = 2;
7879 macro_build ((char *) NULL, &icnt, &expr1, "xori", "t,r,i", AT, AT,
7880 (int) BFD_RELOC_LO16);
7881 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "ctc1", "t,G",
7883 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "");
7884 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7885 mask == M_TRUNCWD ? "cvt.w.d" : "cvt.w.s", "D,S", dreg, sreg);
7886 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "ctc1", "t,G",
7888 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "");
7889 --mips_opts.noreorder;
7898 if (offset_expr.X_add_number >= 0x7fff)
7899 as_bad (_("operand overflow"));
7900 if (! target_big_endian)
7901 ++offset_expr.X_add_number;
7902 macro_build ((char *) NULL, &icnt, &offset_expr, s, "t,o(b)", AT,
7903 (int) BFD_RELOC_LO16, breg);
7904 if (! target_big_endian)
7905 --offset_expr.X_add_number;
7907 ++offset_expr.X_add_number;
7908 macro_build ((char *) NULL, &icnt, &offset_expr, "lbu", "t,o(b)", treg,
7909 (int) BFD_RELOC_LO16, breg);
7910 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sll", "d,w,<",
7912 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or", "d,v,t",
7926 if (offset_expr.X_add_number >= 0x8000 - off)
7927 as_bad (_("operand overflow"));
7932 if (! target_big_endian)
7933 offset_expr.X_add_number += off;
7934 macro_build ((char *) NULL, &icnt, &offset_expr, s, "t,o(b)", tempreg,
7935 (int) BFD_RELOC_LO16, breg);
7936 if (! target_big_endian)
7937 offset_expr.X_add_number -= off;
7939 offset_expr.X_add_number += off;
7940 macro_build ((char *) NULL, &icnt, &offset_expr, s2, "t,o(b)", tempreg,
7941 (int) BFD_RELOC_LO16, breg);
7943 /* If necessary, move the result in tempreg the final destination. */
7944 if (treg == tempreg)
7946 /* Protect second load's delay slot. */
7947 if (!gpr_interlocks)
7948 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "nop", "");
7949 move_register (&icnt, treg, tempreg);
7963 load_address (&icnt, AT, &offset_expr, &used_at);
7965 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7966 ADDRESS_ADD_INSN, "d,v,t", AT, AT, breg);
7967 if (! target_big_endian)
7968 expr1.X_add_number = off;
7970 expr1.X_add_number = 0;
7971 macro_build ((char *) NULL, &icnt, &expr1, s, "t,o(b)", treg,
7972 (int) BFD_RELOC_LO16, AT);
7973 if (! target_big_endian)
7974 expr1.X_add_number = 0;
7976 expr1.X_add_number = off;
7977 macro_build ((char *) NULL, &icnt, &expr1, s2, "t,o(b)", treg,
7978 (int) BFD_RELOC_LO16, AT);
7984 load_address (&icnt, AT, &offset_expr, &used_at);
7986 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
7987 ADDRESS_ADD_INSN, "d,v,t", AT, AT, breg);
7988 if (target_big_endian)
7989 expr1.X_add_number = 0;
7990 macro_build ((char *) NULL, &icnt, &expr1,
7991 mask == M_ULH_A ? "lb" : "lbu", "t,o(b)", treg,
7992 (int) BFD_RELOC_LO16, AT);
7993 if (target_big_endian)
7994 expr1.X_add_number = 1;
7996 expr1.X_add_number = 0;
7997 macro_build ((char *) NULL, &icnt, &expr1, "lbu", "t,o(b)", AT,
7998 (int) BFD_RELOC_LO16, AT);
7999 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sll", "d,w,<",
8001 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or", "d,v,t",
8006 if (offset_expr.X_add_number >= 0x7fff)
8007 as_bad (_("operand overflow"));
8008 if (target_big_endian)
8009 ++offset_expr.X_add_number;
8010 macro_build ((char *) NULL, &icnt, &offset_expr, "sb", "t,o(b)", treg,
8011 (int) BFD_RELOC_LO16, breg);
8012 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "srl", "d,w,<",
8014 if (target_big_endian)
8015 --offset_expr.X_add_number;
8017 ++offset_expr.X_add_number;
8018 macro_build ((char *) NULL, &icnt, &offset_expr, "sb", "t,o(b)", AT,
8019 (int) BFD_RELOC_LO16, breg);
8032 if (offset_expr.X_add_number >= 0x8000 - off)
8033 as_bad (_("operand overflow"));
8034 if (! target_big_endian)
8035 offset_expr.X_add_number += off;
8036 macro_build ((char *) NULL, &icnt, &offset_expr, s, "t,o(b)", treg,
8037 (int) BFD_RELOC_LO16, breg);
8038 if (! target_big_endian)
8039 offset_expr.X_add_number -= off;
8041 offset_expr.X_add_number += off;
8042 macro_build ((char *) NULL, &icnt, &offset_expr, s2, "t,o(b)", treg,
8043 (int) BFD_RELOC_LO16, breg);
8057 load_address (&icnt, AT, &offset_expr, &used_at);
8059 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
8060 ADDRESS_ADD_INSN, "d,v,t", AT, AT, breg);
8061 if (! target_big_endian)
8062 expr1.X_add_number = off;
8064 expr1.X_add_number = 0;
8065 macro_build ((char *) NULL, &icnt, &expr1, s, "t,o(b)", treg,
8066 (int) BFD_RELOC_LO16, AT);
8067 if (! target_big_endian)
8068 expr1.X_add_number = 0;
8070 expr1.X_add_number = off;
8071 macro_build ((char *) NULL, &icnt, &expr1, s2, "t,o(b)", treg,
8072 (int) BFD_RELOC_LO16, AT);
8077 load_address (&icnt, AT, &offset_expr, &used_at);
8079 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
8080 ADDRESS_ADD_INSN, "d,v,t", AT, AT, breg);
8081 if (! target_big_endian)
8082 expr1.X_add_number = 0;
8083 macro_build ((char *) NULL, &icnt, &expr1, "sb", "t,o(b)", treg,
8084 (int) BFD_RELOC_LO16, AT);
8085 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "srl", "d,w,<",
8087 if (! target_big_endian)
8088 expr1.X_add_number = 1;
8090 expr1.X_add_number = 0;
8091 macro_build ((char *) NULL, &icnt, &expr1, "sb", "t,o(b)", treg,
8092 (int) BFD_RELOC_LO16, AT);
8093 if (! target_big_endian)
8094 expr1.X_add_number = 0;
8096 expr1.X_add_number = 1;
8097 macro_build ((char *) NULL, &icnt, &expr1, "lbu", "t,o(b)", AT,
8098 (int) BFD_RELOC_LO16, AT);
8099 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "sll", "d,w,<",
8101 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "or", "d,v,t",
8106 /* FIXME: Check if this is one of the itbl macros, since they
8107 are added dynamically. */
8108 as_bad (_("Macro %s not implemented yet"), ip->insn_mo->name);
8112 as_warn (_("Macro used $at after \".set noat\""));
8115 /* Implement macros in mips16 mode. */
8119 struct mips_cl_insn *ip;
8122 int xreg, yreg, zreg, tmp;
8126 const char *s, *s2, *s3;
8128 mask = ip->insn_mo->mask;
8130 xreg = (ip->insn_opcode >> MIPS16OP_SH_RX) & MIPS16OP_MASK_RX;
8131 yreg = (ip->insn_opcode >> MIPS16OP_SH_RY) & MIPS16OP_MASK_RY;
8132 zreg = (ip->insn_opcode >> MIPS16OP_SH_RZ) & MIPS16OP_MASK_RZ;
8136 expr1.X_op = O_constant;
8137 expr1.X_op_symbol = NULL;
8138 expr1.X_add_symbol = NULL;
8139 expr1.X_add_number = 1;
8158 mips_emit_delays (TRUE);
8159 ++mips_opts.noreorder;
8160 mips_any_noreorder = 1;
8161 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
8162 dbl ? "ddiv" : "div",
8163 "0,x,y", xreg, yreg);
8164 expr1.X_add_number = 2;
8165 macro_build ((char *) NULL, &icnt, &expr1, "bnez", "x,p", yreg);
8166 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "break", "6",
8169 /* FIXME: The normal code checks for of -1 / -0x80000000 here,
8170 since that causes an overflow. We should do that as well,
8171 but I don't see how to do the comparisons without a temporary
8173 --mips_opts.noreorder;
8174 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "x", zreg);
8193 mips_emit_delays (TRUE);
8194 ++mips_opts.noreorder;
8195 mips_any_noreorder = 1;
8196 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "0,x,y",
8198 expr1.X_add_number = 2;
8199 macro_build ((char *) NULL, &icnt, &expr1, "bnez", "x,p", yreg);
8200 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "break",
8202 --mips_opts.noreorder;
8203 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s2, "x", zreg);
8209 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
8210 dbl ? "dmultu" : "multu", "x,y", xreg, yreg);
8211 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "mflo", "x",
8220 if (imm_expr.X_op != O_constant)
8221 as_bad (_("Unsupported large constant"));
8222 imm_expr.X_add_number = -imm_expr.X_add_number;
8223 macro_build ((char *) NULL, &icnt, &imm_expr,
8224 dbl ? "daddiu" : "addiu", "y,x,4", yreg, xreg);
8228 if (imm_expr.X_op != O_constant)
8229 as_bad (_("Unsupported large constant"));
8230 imm_expr.X_add_number = -imm_expr.X_add_number;
8231 macro_build ((char *) NULL, &icnt, &imm_expr, "addiu",
8236 if (imm_expr.X_op != O_constant)
8237 as_bad (_("Unsupported large constant"));
8238 imm_expr.X_add_number = -imm_expr.X_add_number;
8239 macro_build ((char *) NULL, &icnt, &imm_expr, "daddiu",
8262 goto do_reverse_branch;
8266 goto do_reverse_branch;
8278 goto do_reverse_branch;
8289 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, s, "x,y",
8291 macro_build ((char *) NULL, &icnt, &offset_expr, s2, "p");
8318 goto do_addone_branch_i;
8323 goto do_addone_branch_i;
8338 goto do_addone_branch_i;
8345 if (imm_expr.X_op != O_constant)
8346 as_bad (_("Unsupported large constant"));
8347 ++imm_expr.X_add_number;
8350 macro_build ((char *) NULL, &icnt, &imm_expr, s, s3, xreg);
8351 macro_build ((char *) NULL, &icnt, &offset_expr, s2, "p");
8355 expr1.X_add_number = 0;
8356 macro_build ((char *) NULL, &icnt, &expr1, "slti", "x,8", yreg);
8358 move_register (&icnt, xreg, yreg);
8359 expr1.X_add_number = 2;
8360 macro_build ((char *) NULL, &icnt, &expr1, "bteqz", "p");
8361 macro_build ((char *) NULL, &icnt, (expressionS *) NULL,
8362 "neg", "x,w", xreg, xreg);
8366 /* For consistency checking, verify that all bits are specified either
8367 by the match/mask part of the instruction definition, or by the
8370 validate_mips_insn (opc)
8371 const struct mips_opcode *opc;
8373 const char *p = opc->args;
8375 unsigned long used_bits = opc->mask;
8377 if ((used_bits & opc->match) != opc->match)
8379 as_bad (_("internal: bad mips opcode (mask error): %s %s"),
8380 opc->name, opc->args);
8383 #define USE_BITS(mask,shift) (used_bits |= ((mask) << (shift)))
8393 case 'A': USE_BITS (OP_MASK_SHAMT, OP_SH_SHAMT); break;
8394 case 'B': USE_BITS (OP_MASK_INSMSB, OP_SH_INSMSB); break;
8395 case 'C': USE_BITS (OP_MASK_EXTMSBD, OP_SH_EXTMSBD); break;
8396 case 'D': USE_BITS (OP_MASK_RD, OP_SH_RD);
8397 USE_BITS (OP_MASK_SEL, OP_SH_SEL); break;
8399 as_bad (_("internal: bad mips opcode (unknown extension operand type `+%c'): %s %s"),
8400 c, opc->name, opc->args);
8404 case '<': USE_BITS (OP_MASK_SHAMT, OP_SH_SHAMT); break;
8405 case '>': USE_BITS (OP_MASK_SHAMT, OP_SH_SHAMT); break;
8407 case 'B': USE_BITS (OP_MASK_CODE20, OP_SH_CODE20); break;
8408 case 'C': USE_BITS (OP_MASK_COPZ, OP_SH_COPZ); break;
8409 case 'D': USE_BITS (OP_MASK_FD, OP_SH_FD); break;
8410 case 'E': USE_BITS (OP_MASK_RT, OP_SH_RT); break;
8412 case 'G': USE_BITS (OP_MASK_RD, OP_SH_RD); break;
8413 case 'H': USE_BITS (OP_MASK_SEL, OP_SH_SEL); break;
8415 case 'J': USE_BITS (OP_MASK_CODE19, OP_SH_CODE19); break;
8416 case 'K': USE_BITS (OP_MASK_RD, OP_SH_RD); break;
8418 case 'M': USE_BITS (OP_MASK_CCC, OP_SH_CCC); break;
8419 case 'N': USE_BITS (OP_MASK_BCC, OP_SH_BCC); break;
8420 case 'O': USE_BITS (OP_MASK_ALN, OP_SH_ALN); break;
8421 case 'Q': USE_BITS (OP_MASK_VSEL, OP_SH_VSEL);
8422 USE_BITS (OP_MASK_FT, OP_SH_FT); break;
8423 case 'R': USE_BITS (OP_MASK_FR, OP_SH_FR); break;
8424 case 'S': USE_BITS (OP_MASK_FS, OP_SH_FS); break;
8425 case 'T': USE_BITS (OP_MASK_FT, OP_SH_FT); break;
8426 case 'V': USE_BITS (OP_MASK_FS, OP_SH_FS); break;
8427 case 'W': USE_BITS (OP_MASK_FT, OP_SH_FT); break;
8428 case 'X': USE_BITS (OP_MASK_FD, OP_SH_FD); break;
8429 case 'Y': USE_BITS (OP_MASK_FS, OP_SH_FS); break;
8430 case 'Z': USE_BITS (OP_MASK_FT, OP_SH_FT); break;
8431 case 'a': USE_BITS (OP_MASK_TARGET, OP_SH_TARGET); break;
8432 case 'b': USE_BITS (OP_MASK_RS, OP_SH_RS); break;
8433 case 'c': USE_BITS (OP_MASK_CODE, OP_SH_CODE); break;
8434 case 'd': USE_BITS (OP_MASK_RD, OP_SH_RD); break;
8436 case 'h': USE_BITS (OP_MASK_PREFX, OP_SH_PREFX); break;
8437 case 'i': USE_BITS (OP_MASK_IMMEDIATE, OP_SH_IMMEDIATE); break;
8438 case 'j': USE_BITS (OP_MASK_DELTA, OP_SH_DELTA); break;
8439 case 'k': USE_BITS (OP_MASK_CACHE, OP_SH_CACHE); break;
8441 case 'o': USE_BITS (OP_MASK_DELTA, OP_SH_DELTA); break;
8442 case 'p': USE_BITS (OP_MASK_DELTA, OP_SH_DELTA); break;
8443 case 'q': USE_BITS (OP_MASK_CODE2, OP_SH_CODE2); break;
8444 case 'r': USE_BITS (OP_MASK_RS, OP_SH_RS); break;
8445 case 's': USE_BITS (OP_MASK_RS, OP_SH_RS); break;
8446 case 't': USE_BITS (OP_MASK_RT, OP_SH_RT); break;
8447 case 'u': USE_BITS (OP_MASK_IMMEDIATE, OP_SH_IMMEDIATE); break;
8448 case 'v': USE_BITS (OP_MASK_RS, OP_SH_RS); break;
8449 case 'w': USE_BITS (OP_MASK_RT, OP_SH_RT); break;
8452 case 'P': USE_BITS (OP_MASK_PERFREG, OP_SH_PERFREG); break;
8453 case 'U': USE_BITS (OP_MASK_RD, OP_SH_RD);
8454 USE_BITS (OP_MASK_RT, OP_SH_RT); break;
8455 case 'e': USE_BITS (OP_MASK_VECBYTE, OP_SH_VECBYTE); break;
8456 case '%': USE_BITS (OP_MASK_VECALIGN, OP_SH_VECALIGN); break;
8460 as_bad (_("internal: bad mips opcode (unknown operand type `%c'): %s %s"),
8461 c, opc->name, opc->args);
8465 if (used_bits != 0xffffffff)
8467 as_bad (_("internal: bad mips opcode (bits 0x%lx undefined): %s %s"),
8468 ~used_bits & 0xffffffff, opc->name, opc->args);
8474 /* This routine assembles an instruction into its binary format. As a
8475 side effect, it sets one of the global variables imm_reloc or
8476 offset_reloc to the type of relocation to do if one of the operands
8477 is an address expression. */
8482 struct mips_cl_insn *ip;
8487 struct mips_opcode *insn;
8490 unsigned int lastregno = 0;
8491 unsigned int lastpos = 0;
8492 unsigned int limlo, limhi;
8498 /* If the instruction contains a '.', we first try to match an instruction
8499 including the '.'. Then we try again without the '.'. */
8501 for (s = str; *s != '\0' && !ISSPACE (*s); ++s)
8504 /* If we stopped on whitespace, then replace the whitespace with null for
8505 the call to hash_find. Save the character we replaced just in case we
8506 have to re-parse the instruction. */
8513 insn = (struct mips_opcode *) hash_find (op_hash, str);
8515 /* If we didn't find the instruction in the opcode table, try again, but
8516 this time with just the instruction up to, but not including the
8520 /* Restore the character we overwrite above (if any). */
8524 /* Scan up to the first '.' or whitespace. */
8526 *s != '\0' && *s != '.' && !ISSPACE (*s);
8530 /* If we did not find a '.', then we can quit now. */
8533 insn_error = "unrecognized opcode";
8537 /* Lookup the instruction in the hash table. */
8539 if ((insn = (struct mips_opcode *) hash_find (op_hash, str)) == NULL)
8541 insn_error = "unrecognized opcode";
8551 assert (strcmp (insn->name, str) == 0);
8553 if (OPCODE_IS_MEMBER (insn,
8555 | (file_ase_mips16 ? INSN_MIPS16 : 0)
8556 | (mips_opts.ase_mdmx ? INSN_MDMX : 0)
8557 | (mips_opts.ase_mips3d ? INSN_MIPS3D : 0)),
8563 if (insn->pinfo != INSN_MACRO)
8565 if (mips_arch == CPU_R4650 && (insn->pinfo & FP_D) != 0)
8571 if (insn + 1 < &mips_opcodes[NUMOPCODES]
8572 && strcmp (insn->name, insn[1].name) == 0)
8581 static char buf[100];
8582 if (mips_arch_info->is_isa)
8584 _("opcode not supported at this ISA level (%s)"),
8585 mips_cpu_info_from_isa (mips_opts.isa)->name);
8588 _("opcode not supported on this processor: %s (%s)"),
8589 mips_arch_info->name,
8590 mips_cpu_info_from_isa (mips_opts.isa)->name);
8600 ip->insn_opcode = insn->match;
8602 for (args = insn->args;; ++args)
8606 s += strspn (s, " \t");
8610 case '\0': /* end of args */
8623 ip->insn_opcode |= lastregno << OP_SH_RS;
8627 ip->insn_opcode |= lastregno << OP_SH_RT;
8631 ip->insn_opcode |= lastregno << OP_SH_FT;
8635 ip->insn_opcode |= lastregno << OP_SH_FS;
8641 /* Handle optional base register.
8642 Either the base register is omitted or
8643 we must have a left paren. */
8644 /* This is dependent on the next operand specifier
8645 is a base register specification. */
8646 assert (args[1] == 'b' || args[1] == '5'
8647 || args[1] == '-' || args[1] == '4');
8651 case ')': /* these must match exactly */
8658 case '+': /* Opcode extension character. */
8661 case 'A': /* ins/ext position, becomes LSB. */
8664 my_getExpression (&imm_expr, s);
8665 check_absolute_expr (ip, &imm_expr);
8666 if ((unsigned long) imm_expr.X_add_number < limlo
8667 || (unsigned long) imm_expr.X_add_number > limhi)
8669 as_bad (_("Improper position (%lu)"),
8670 (unsigned long) imm_expr.X_add_number);
8671 imm_expr.X_add_number = limlo;
8673 lastpos = imm_expr.X_add_number;
8674 ip->insn_opcode |= (imm_expr.X_add_number
8675 & OP_MASK_SHAMT) << OP_SH_SHAMT;
8676 imm_expr.X_op = O_absent;
8680 case 'B': /* ins size, becomes MSB. */
8683 my_getExpression (&imm_expr, s);
8684 check_absolute_expr (ip, &imm_expr);
8685 /* Check for negative input so that small negative numbers
8686 will not succeed incorrectly. The checks against
8687 (pos+size) transitively check "size" itself,
8688 assuming that "pos" is reasonable. */
8689 if ((long) imm_expr.X_add_number < 0
8690 || ((unsigned long) imm_expr.X_add_number
8692 || ((unsigned long) imm_expr.X_add_number
8695 as_bad (_("Improper insert size (%lu, position %lu)"),
8696 (unsigned long) imm_expr.X_add_number,
8697 (unsigned long) lastpos);
8698 imm_expr.X_add_number = limlo - lastpos;
8700 ip->insn_opcode |= ((lastpos + imm_expr.X_add_number - 1)
8701 & OP_MASK_INSMSB) << OP_SH_INSMSB;
8702 imm_expr.X_op = O_absent;
8706 case 'C': /* ext size, becomes MSBD. */
8709 my_getExpression (&imm_expr, s);
8710 check_absolute_expr (ip, &imm_expr);
8711 /* Check for negative input so that small negative numbers
8712 will not succeed incorrectly. The checks against
8713 (pos+size) transitively check "size" itself,
8714 assuming that "pos" is reasonable. */
8715 if ((long) imm_expr.X_add_number < 0
8716 || ((unsigned long) imm_expr.X_add_number
8718 || ((unsigned long) imm_expr.X_add_number
8721 as_bad (_("Improper extract size (%lu, position %lu)"),
8722 (unsigned long) imm_expr.X_add_number,
8723 (unsigned long) lastpos);
8724 imm_expr.X_add_number = limlo - lastpos;
8726 ip->insn_opcode |= ((imm_expr.X_add_number - 1)
8727 & OP_MASK_EXTMSBD) << OP_SH_EXTMSBD;
8728 imm_expr.X_op = O_absent;
8733 /* +D is for disassembly only; never match. */
8737 as_bad (_("internal: bad mips opcode (unknown extension operand type `+%c'): %s %s"),
8738 *args, insn->name, insn->args);
8739 /* Further processing is fruitless. */
8744 case '<': /* must be at least one digit */
8746 * According to the manual, if the shift amount is greater
8747 * than 31 or less than 0, then the shift amount should be
8748 * mod 32. In reality the mips assembler issues an error.
8749 * We issue a warning and mask out all but the low 5 bits.
8751 my_getExpression (&imm_expr, s);
8752 check_absolute_expr (ip, &imm_expr);
8753 if ((unsigned long) imm_expr.X_add_number > 31)
8755 as_warn (_("Improper shift amount (%lu)"),
8756 (unsigned long) imm_expr.X_add_number);
8757 imm_expr.X_add_number &= OP_MASK_SHAMT;
8759 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_SHAMT;
8760 imm_expr.X_op = O_absent;
8764 case '>': /* shift amount minus 32 */
8765 my_getExpression (&imm_expr, s);
8766 check_absolute_expr (ip, &imm_expr);
8767 if ((unsigned long) imm_expr.X_add_number < 32
8768 || (unsigned long) imm_expr.X_add_number > 63)
8770 ip->insn_opcode |= (imm_expr.X_add_number - 32) << OP_SH_SHAMT;
8771 imm_expr.X_op = O_absent;
8775 case 'k': /* cache code */
8776 case 'h': /* prefx code */
8777 my_getExpression (&imm_expr, s);
8778 check_absolute_expr (ip, &imm_expr);
8779 if ((unsigned long) imm_expr.X_add_number > 31)
8781 as_warn (_("Invalid value for `%s' (%lu)"),
8783 (unsigned long) imm_expr.X_add_number);
8784 imm_expr.X_add_number &= 0x1f;
8787 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_CACHE;
8789 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_PREFX;
8790 imm_expr.X_op = O_absent;
8794 case 'c': /* break code */
8795 my_getExpression (&imm_expr, s);
8796 check_absolute_expr (ip, &imm_expr);
8797 if ((unsigned long) imm_expr.X_add_number > 1023)
8799 as_warn (_("Illegal break code (%lu)"),
8800 (unsigned long) imm_expr.X_add_number);
8801 imm_expr.X_add_number &= OP_MASK_CODE;
8803 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_CODE;
8804 imm_expr.X_op = O_absent;
8808 case 'q': /* lower break code */
8809 my_getExpression (&imm_expr, s);
8810 check_absolute_expr (ip, &imm_expr);
8811 if ((unsigned long) imm_expr.X_add_number > 1023)
8813 as_warn (_("Illegal lower break code (%lu)"),
8814 (unsigned long) imm_expr.X_add_number);
8815 imm_expr.X_add_number &= OP_MASK_CODE2;
8817 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_CODE2;
8818 imm_expr.X_op = O_absent;
8822 case 'B': /* 20-bit syscall/break code. */
8823 my_getExpression (&imm_expr, s);
8824 check_absolute_expr (ip, &imm_expr);
8825 if ((unsigned long) imm_expr.X_add_number > OP_MASK_CODE20)
8826 as_warn (_("Illegal 20-bit code (%lu)"),
8827 (unsigned long) imm_expr.X_add_number);
8828 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_CODE20;
8829 imm_expr.X_op = O_absent;
8833 case 'C': /* Coprocessor code */
8834 my_getExpression (&imm_expr, s);
8835 check_absolute_expr (ip, &imm_expr);
8836 if ((unsigned long) imm_expr.X_add_number >= (1 << 25))
8838 as_warn (_("Coproccesor code > 25 bits (%lu)"),
8839 (unsigned long) imm_expr.X_add_number);
8840 imm_expr.X_add_number &= ((1 << 25) - 1);
8842 ip->insn_opcode |= imm_expr.X_add_number;
8843 imm_expr.X_op = O_absent;
8847 case 'J': /* 19-bit wait code. */
8848 my_getExpression (&imm_expr, s);
8849 check_absolute_expr (ip, &imm_expr);
8850 if ((unsigned long) imm_expr.X_add_number > OP_MASK_CODE19)
8851 as_warn (_("Illegal 19-bit code (%lu)"),
8852 (unsigned long) imm_expr.X_add_number);
8853 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_CODE19;
8854 imm_expr.X_op = O_absent;
8858 case 'P': /* Performance register */
8859 my_getExpression (&imm_expr, s);
8860 check_absolute_expr (ip, &imm_expr);
8861 if (imm_expr.X_add_number != 0 && imm_expr.X_add_number != 1)
8863 as_warn (_("Invalid performance register (%lu)"),
8864 (unsigned long) imm_expr.X_add_number);
8865 imm_expr.X_add_number &= OP_MASK_PERFREG;
8867 ip->insn_opcode |= (imm_expr.X_add_number << OP_SH_PERFREG);
8868 imm_expr.X_op = O_absent;
8872 case 'b': /* base register */
8873 case 'd': /* destination register */
8874 case 's': /* source register */
8875 case 't': /* target register */
8876 case 'r': /* both target and source */
8877 case 'v': /* both dest and source */
8878 case 'w': /* both dest and target */
8879 case 'E': /* coprocessor target register */
8880 case 'G': /* coprocessor destination register */
8881 case 'K': /* 'rdhwr' destination register */
8882 case 'x': /* ignore register name */
8883 case 'z': /* must be zero register */
8884 case 'U': /* destination register (clo/clz). */
8899 while (ISDIGIT (*s));
8901 as_bad (_("Invalid register number (%d)"), regno);
8903 else if (*args == 'E' || *args == 'G' || *args == 'K')
8907 if (s[1] == 'r' && s[2] == 'a')
8912 else if (s[1] == 'f' && s[2] == 'p')
8917 else if (s[1] == 's' && s[2] == 'p')
8922 else if (s[1] == 'g' && s[2] == 'p')
8927 else if (s[1] == 'a' && s[2] == 't')
8932 else if (s[1] == 'k' && s[2] == 't' && s[3] == '0')
8937 else if (s[1] == 'k' && s[2] == 't' && s[3] == '1')
8942 else if (s[1] == 'z' && s[2] == 'e' && s[3] == 'r' && s[4] == 'o')
8947 else if (itbl_have_entries)
8952 p = s + 1; /* advance past '$' */
8953 n = itbl_get_field (&p); /* n is name */
8955 /* See if this is a register defined in an
8957 if (itbl_get_reg_val (n, &r))
8959 /* Get_field advances to the start of
8960 the next field, so we need to back
8961 rack to the end of the last field. */
8965 s = strchr (s, '\0');
8979 as_warn (_("Used $at without \".set noat\""));
8985 if (c == 'r' || c == 'v' || c == 'w')
8992 /* 'z' only matches $0. */
8993 if (c == 'z' && regno != 0)
8996 /* Now that we have assembled one operand, we use the args string
8997 * to figure out where it goes in the instruction. */
9004 ip->insn_opcode |= regno << OP_SH_RS;
9009 ip->insn_opcode |= regno << OP_SH_RD;
9012 ip->insn_opcode |= regno << OP_SH_RD;
9013 ip->insn_opcode |= regno << OP_SH_RT;
9018 ip->insn_opcode |= regno << OP_SH_RT;
9021 /* This case exists because on the r3000 trunc
9022 expands into a macro which requires a gp
9023 register. On the r6000 or r4000 it is
9024 assembled into a single instruction which
9025 ignores the register. Thus the insn version
9026 is MIPS_ISA2 and uses 'x', and the macro
9027 version is MIPS_ISA1 and uses 't'. */
9030 /* This case is for the div instruction, which
9031 acts differently if the destination argument
9032 is $0. This only matches $0, and is checked
9033 outside the switch. */
9036 /* Itbl operand; not yet implemented. FIXME ?? */
9038 /* What about all other operands like 'i', which
9039 can be specified in the opcode table? */
9049 ip->insn_opcode |= lastregno << OP_SH_RS;
9052 ip->insn_opcode |= lastregno << OP_SH_RT;
9057 case 'O': /* MDMX alignment immediate constant. */
9058 my_getExpression (&imm_expr, s);
9059 check_absolute_expr (ip, &imm_expr);
9060 if ((unsigned long) imm_expr.X_add_number > OP_MASK_ALN)
9062 as_warn ("Improper align amount (%ld), using low bits",
9063 (long) imm_expr.X_add_number);
9064 imm_expr.X_add_number &= OP_MASK_ALN;
9066 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_ALN;
9067 imm_expr.X_op = O_absent;
9071 case 'Q': /* MDMX vector, element sel, or const. */
9074 /* MDMX Immediate. */
9075 my_getExpression (&imm_expr, s);
9076 check_absolute_expr (ip, &imm_expr);
9077 if ((unsigned long) imm_expr.X_add_number > OP_MASK_FT)
9079 as_warn (_("Invalid MDMX Immediate (%ld)"),
9080 (long) imm_expr.X_add_number);
9081 imm_expr.X_add_number &= OP_MASK_FT;
9083 imm_expr.X_add_number &= OP_MASK_FT;
9084 if (ip->insn_opcode & (OP_MASK_VSEL << OP_SH_VSEL))
9085 ip->insn_opcode |= MDMX_FMTSEL_IMM_QH << OP_SH_VSEL;
9087 ip->insn_opcode |= MDMX_FMTSEL_IMM_OB << OP_SH_VSEL;
9088 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_FT;
9089 imm_expr.X_op = O_absent;
9093 /* Not MDMX Immediate. Fall through. */
9094 case 'X': /* MDMX destination register. */
9095 case 'Y': /* MDMX source register. */
9096 case 'Z': /* MDMX target register. */
9098 case 'D': /* floating point destination register */
9099 case 'S': /* floating point source register */
9100 case 'T': /* floating point target register */
9101 case 'R': /* floating point source register */
9105 /* Accept $fN for FP and MDMX register numbers, and in
9106 addition accept $vN for MDMX register numbers. */
9107 if ((s[0] == '$' && s[1] == 'f' && ISDIGIT (s[2]))
9108 || (is_mdmx != 0 && s[0] == '$' && s[1] == 'v'
9119 while (ISDIGIT (*s));
9122 as_bad (_("Invalid float register number (%d)"), regno);
9124 if ((regno & 1) != 0
9126 && ! (strcmp (str, "mtc1") == 0
9127 || strcmp (str, "mfc1") == 0
9128 || strcmp (str, "lwc1") == 0
9129 || strcmp (str, "swc1") == 0
9130 || strcmp (str, "l.s") == 0
9131 || strcmp (str, "s.s") == 0))
9132 as_warn (_("Float register should be even, was %d"),
9140 if (c == 'V' || c == 'W')
9151 ip->insn_opcode |= regno << OP_SH_FD;
9156 ip->insn_opcode |= regno << OP_SH_FS;
9159 /* This is like 'Z', but also needs to fix the MDMX
9160 vector/scalar select bits. Note that the
9161 scalar immediate case is handled above. */
9164 int is_qh = (ip->insn_opcode & (1 << OP_SH_VSEL));
9165 int max_el = (is_qh ? 3 : 7);
9167 my_getExpression(&imm_expr, s);
9168 check_absolute_expr (ip, &imm_expr);
9170 if (imm_expr.X_add_number > max_el)
9171 as_bad(_("Bad element selector %ld"),
9172 (long) imm_expr.X_add_number);
9173 imm_expr.X_add_number &= max_el;
9174 ip->insn_opcode |= (imm_expr.X_add_number
9178 as_warn(_("Expecting ']' found '%s'"), s);
9184 if (ip->insn_opcode & (OP_MASK_VSEL << OP_SH_VSEL))
9185 ip->insn_opcode |= (MDMX_FMTSEL_VEC_QH
9188 ip->insn_opcode |= (MDMX_FMTSEL_VEC_OB <<
9195 ip->insn_opcode |= regno << OP_SH_FT;
9198 ip->insn_opcode |= regno << OP_SH_FR;
9208 ip->insn_opcode |= lastregno << OP_SH_FS;
9211 ip->insn_opcode |= lastregno << OP_SH_FT;
9217 my_getExpression (&imm_expr, s);
9218 if (imm_expr.X_op != O_big
9219 && imm_expr.X_op != O_constant)
9220 insn_error = _("absolute expression required");
9225 my_getExpression (&offset_expr, s);
9226 *imm_reloc = BFD_RELOC_32;
9239 unsigned char temp[8];
9241 unsigned int length;
9246 /* These only appear as the last operand in an
9247 instruction, and every instruction that accepts
9248 them in any variant accepts them in all variants.
9249 This means we don't have to worry about backing out
9250 any changes if the instruction does not match.
9252 The difference between them is the size of the
9253 floating point constant and where it goes. For 'F'
9254 and 'L' the constant is 64 bits; for 'f' and 'l' it
9255 is 32 bits. Where the constant is placed is based
9256 on how the MIPS assembler does things:
9259 f -- immediate value
9262 The .lit4 and .lit8 sections are only used if
9263 permitted by the -G argument.
9265 When generating embedded PIC code, we use the
9266 .lit8 section but not the .lit4 section (we can do
9267 .lit4 inline easily; we need to put .lit8
9268 somewhere in the data segment, and using .lit8
9269 permits the linker to eventually combine identical
9272 The code below needs to know whether the target register
9273 is 32 or 64 bits wide. It relies on the fact 'f' and
9274 'F' are used with GPR-based instructions and 'l' and
9275 'L' are used with FPR-based instructions. */
9277 f64 = *args == 'F' || *args == 'L';
9278 using_gprs = *args == 'F' || *args == 'f';
9280 save_in = input_line_pointer;
9281 input_line_pointer = s;
9282 err = md_atof (f64 ? 'd' : 'f', (char *) temp, &len);
9284 s = input_line_pointer;
9285 input_line_pointer = save_in;
9286 if (err != NULL && *err != '\0')
9288 as_bad (_("Bad floating point constant: %s"), err);
9289 memset (temp, '\0', sizeof temp);
9290 length = f64 ? 8 : 4;
9293 assert (length == (unsigned) (f64 ? 8 : 4));
9297 && (! USE_GLOBAL_POINTER_OPT
9298 || mips_pic == EMBEDDED_PIC
9299 || g_switch_value < 4
9300 || (temp[0] == 0 && temp[1] == 0)
9301 || (temp[2] == 0 && temp[3] == 0))))
9303 imm_expr.X_op = O_constant;
9304 if (! target_big_endian)
9305 imm_expr.X_add_number = bfd_getl32 (temp);
9307 imm_expr.X_add_number = bfd_getb32 (temp);
9310 && ! mips_disable_float_construction
9311 /* Constants can only be constructed in GPRs and
9312 copied to FPRs if the GPRs are at least as wide
9313 as the FPRs. Force the constant into memory if
9314 we are using 64-bit FPRs but the GPRs are only
9317 || ! (HAVE_64BIT_FPRS && HAVE_32BIT_GPRS))
9318 && ((temp[0] == 0 && temp[1] == 0)
9319 || (temp[2] == 0 && temp[3] == 0))
9320 && ((temp[4] == 0 && temp[5] == 0)
9321 || (temp[6] == 0 && temp[7] == 0)))
9323 /* The value is simple enough to load with a couple of
9324 instructions. If using 32-bit registers, set
9325 imm_expr to the high order 32 bits and offset_expr to
9326 the low order 32 bits. Otherwise, set imm_expr to
9327 the entire 64 bit constant. */
9328 if (using_gprs ? HAVE_32BIT_GPRS : HAVE_32BIT_FPRS)
9330 imm_expr.X_op = O_constant;
9331 offset_expr.X_op = O_constant;
9332 if (! target_big_endian)
9334 imm_expr.X_add_number = bfd_getl32 (temp + 4);
9335 offset_expr.X_add_number = bfd_getl32 (temp);
9339 imm_expr.X_add_number = bfd_getb32 (temp);
9340 offset_expr.X_add_number = bfd_getb32 (temp + 4);
9342 if (offset_expr.X_add_number == 0)
9343 offset_expr.X_op = O_absent;
9345 else if (sizeof (imm_expr.X_add_number) > 4)
9347 imm_expr.X_op = O_constant;
9348 if (! target_big_endian)
9349 imm_expr.X_add_number = bfd_getl64 (temp);
9351 imm_expr.X_add_number = bfd_getb64 (temp);
9355 imm_expr.X_op = O_big;
9356 imm_expr.X_add_number = 4;
9357 if (! target_big_endian)
9359 generic_bignum[0] = bfd_getl16 (temp);
9360 generic_bignum[1] = bfd_getl16 (temp + 2);
9361 generic_bignum[2] = bfd_getl16 (temp + 4);
9362 generic_bignum[3] = bfd_getl16 (temp + 6);
9366 generic_bignum[0] = bfd_getb16 (temp + 6);
9367 generic_bignum[1] = bfd_getb16 (temp + 4);
9368 generic_bignum[2] = bfd_getb16 (temp + 2);
9369 generic_bignum[3] = bfd_getb16 (temp);
9375 const char *newname;
9378 /* Switch to the right section. */
9380 subseg = now_subseg;
9383 default: /* unused default case avoids warnings. */
9385 newname = RDATA_SECTION_NAME;
9386 if ((USE_GLOBAL_POINTER_OPT && g_switch_value >= 8)
9387 || mips_pic == EMBEDDED_PIC)
9391 if (mips_pic == EMBEDDED_PIC)
9394 newname = RDATA_SECTION_NAME;
9397 assert (!USE_GLOBAL_POINTER_OPT
9398 || g_switch_value >= 4);
9402 new_seg = subseg_new (newname, (subsegT) 0);
9403 if (OUTPUT_FLAVOR == bfd_target_elf_flavour)
9404 bfd_set_section_flags (stdoutput, new_seg,
9409 frag_align (*args == 'l' ? 2 : 3, 0, 0);
9410 if (OUTPUT_FLAVOR == bfd_target_elf_flavour
9411 && strcmp (TARGET_OS, "elf") != 0)
9412 record_alignment (new_seg, 4);
9414 record_alignment (new_seg, *args == 'l' ? 2 : 3);
9416 as_bad (_("Can't use floating point insn in this section"));
9418 /* Set the argument to the current address in the
9420 offset_expr.X_op = O_symbol;
9421 offset_expr.X_add_symbol =
9422 symbol_new ("L0\001", now_seg,
9423 (valueT) frag_now_fix (), frag_now);
9424 offset_expr.X_add_number = 0;
9426 /* Put the floating point number into the section. */
9427 p = frag_more ((int) length);
9428 memcpy (p, temp, length);
9430 /* Switch back to the original section. */
9431 subseg_set (seg, subseg);
9436 case 'i': /* 16 bit unsigned immediate */
9437 case 'j': /* 16 bit signed immediate */
9438 *imm_reloc = BFD_RELOC_LO16;
9439 if (my_getSmallExpression (&imm_expr, imm_reloc, s) == 0)
9442 offsetT minval, maxval;
9444 more = (insn + 1 < &mips_opcodes[NUMOPCODES]
9445 && strcmp (insn->name, insn[1].name) == 0);
9447 /* If the expression was written as an unsigned number,
9448 only treat it as signed if there are no more
9452 && sizeof (imm_expr.X_add_number) <= 4
9453 && imm_expr.X_op == O_constant
9454 && imm_expr.X_add_number < 0
9455 && imm_expr.X_unsigned
9459 /* For compatibility with older assemblers, we accept
9460 0x8000-0xffff as signed 16-bit numbers when only
9461 signed numbers are allowed. */
9463 minval = 0, maxval = 0xffff;
9465 minval = -0x8000, maxval = 0x7fff;
9467 minval = -0x8000, maxval = 0xffff;
9469 if (imm_expr.X_op != O_constant
9470 || imm_expr.X_add_number < minval
9471 || imm_expr.X_add_number > maxval)
9475 if (imm_expr.X_op == O_constant
9476 || imm_expr.X_op == O_big)
9477 as_bad (_("expression out of range"));
9483 case 'o': /* 16 bit offset */
9484 /* Check whether there is only a single bracketed expression
9485 left. If so, it must be the base register and the
9486 constant must be zero. */
9487 if (*s == '(' && strchr (s + 1, '(') == 0)
9489 offset_expr.X_op = O_constant;
9490 offset_expr.X_add_number = 0;
9494 /* If this value won't fit into a 16 bit offset, then go
9495 find a macro that will generate the 32 bit offset
9497 if (my_getSmallExpression (&offset_expr, offset_reloc, s) == 0
9498 && (offset_expr.X_op != O_constant
9499 || offset_expr.X_add_number >= 0x8000
9500 || offset_expr.X_add_number < -0x8000))
9506 case 'p': /* pc relative offset */
9507 *offset_reloc = BFD_RELOC_16_PCREL_S2;
9508 my_getExpression (&offset_expr, s);
9512 case 'u': /* upper 16 bits */
9513 if (my_getSmallExpression (&imm_expr, imm_reloc, s) == 0
9514 && imm_expr.X_op == O_constant
9515 && (imm_expr.X_add_number < 0
9516 || imm_expr.X_add_number >= 0x10000))
9517 as_bad (_("lui expression not in range 0..65535"));
9521 case 'a': /* 26 bit address */
9522 my_getExpression (&offset_expr, s);
9524 *offset_reloc = BFD_RELOC_MIPS_JMP;
9527 case 'N': /* 3 bit branch condition code */
9528 case 'M': /* 3 bit compare condition code */
9529 if (strncmp (s, "$fcc", 4) != 0)
9539 while (ISDIGIT (*s));
9541 as_bad (_("invalid condition code register $fcc%d"), regno);
9543 ip->insn_opcode |= regno << OP_SH_BCC;
9545 ip->insn_opcode |= regno << OP_SH_CCC;
9549 if (s[0] == '0' && (s[1] == 'x' || s[1] == 'X'))
9560 while (ISDIGIT (*s));
9563 c = 8; /* Invalid sel value. */
9566 as_bad (_("invalid coprocessor sub-selection value (0-7)"));
9567 ip->insn_opcode |= c;
9571 /* Must be at least one digit. */
9572 my_getExpression (&imm_expr, s);
9573 check_absolute_expr (ip, &imm_expr);
9575 if ((unsigned long) imm_expr.X_add_number
9576 > (unsigned long) OP_MASK_VECBYTE)
9578 as_bad (_("bad byte vector index (%ld)"),
9579 (long) imm_expr.X_add_number);
9580 imm_expr.X_add_number = 0;
9583 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_VECBYTE;
9584 imm_expr.X_op = O_absent;
9589 my_getExpression (&imm_expr, s);
9590 check_absolute_expr (ip, &imm_expr);
9592 if ((unsigned long) imm_expr.X_add_number
9593 > (unsigned long) OP_MASK_VECALIGN)
9595 as_bad (_("bad byte vector index (%ld)"),
9596 (long) imm_expr.X_add_number);
9597 imm_expr.X_add_number = 0;
9600 ip->insn_opcode |= imm_expr.X_add_number << OP_SH_VECALIGN;
9601 imm_expr.X_op = O_absent;
9606 as_bad (_("bad char = '%c'\n"), *args);
9611 /* Args don't match. */
9612 if (insn + 1 < &mips_opcodes[NUMOPCODES] &&
9613 !strcmp (insn->name, insn[1].name))
9617 insn_error = _("illegal operands");
9622 insn_error = _("illegal operands");
9627 /* This routine assembles an instruction into its binary format when
9628 assembling for the mips16. As a side effect, it sets one of the
9629 global variables imm_reloc or offset_reloc to the type of
9630 relocation to do if one of the operands is an address expression.
9631 It also sets mips16_small and mips16_ext if the user explicitly
9632 requested a small or extended instruction. */
9637 struct mips_cl_insn *ip;
9641 struct mips_opcode *insn;
9644 unsigned int lastregno = 0;
9649 mips16_small = FALSE;
9652 for (s = str; ISLOWER (*s); ++s)
9664 if (s[1] == 't' && s[2] == ' ')
9667 mips16_small = TRUE;
9671 else if (s[1] == 'e' && s[2] == ' ')
9680 insn_error = _("unknown opcode");
9684 if (mips_opts.noautoextend && ! mips16_ext)
9685 mips16_small = TRUE;
9687 if ((insn = (struct mips_opcode *) hash_find (mips16_op_hash, str)) == NULL)
9689 insn_error = _("unrecognized opcode");
9696 assert (strcmp (insn->name, str) == 0);
9699 ip->insn_opcode = insn->match;
9700 ip->use_extend = FALSE;
9701 imm_expr.X_op = O_absent;
9702 imm_reloc[0] = BFD_RELOC_UNUSED;
9703 imm_reloc[1] = BFD_RELOC_UNUSED;
9704 imm_reloc[2] = BFD_RELOC_UNUSED;
9705 offset_expr.X_op = O_absent;
9706 offset_reloc[0] = BFD_RELOC_UNUSED;
9707 offset_reloc[1] = BFD_RELOC_UNUSED;
9708 offset_reloc[2] = BFD_RELOC_UNUSED;
9709 for (args = insn->args; 1; ++args)
9716 /* In this switch statement we call break if we did not find
9717 a match, continue if we did find a match, or return if we
9726 /* Stuff the immediate value in now, if we can. */
9727 if (imm_expr.X_op == O_constant
9728 && *imm_reloc > BFD_RELOC_UNUSED
9729 && insn->pinfo != INSN_MACRO)
9731 mips16_immed (NULL, 0, *imm_reloc - BFD_RELOC_UNUSED,
9732 imm_expr.X_add_number, TRUE, mips16_small,
9733 mips16_ext, &ip->insn_opcode,
9734 &ip->use_extend, &ip->extend);
9735 imm_expr.X_op = O_absent;
9736 *imm_reloc = BFD_RELOC_UNUSED;
9750 ip->insn_opcode |= lastregno << MIPS16OP_SH_RX;
9753 ip->insn_opcode |= lastregno << MIPS16OP_SH_RY;
9769 ip->insn_opcode |= lastregno << MIPS16OP_SH_RX;
9771 ip->insn_opcode |= lastregno << MIPS16OP_SH_RY;
9798 while (ISDIGIT (*s));
9801 as_bad (_("invalid register number (%d)"), regno);
9807 if (s[1] == 'r' && s[2] == 'a')
9812 else if (s[1] == 'f' && s[2] == 'p')
9817 else if (s[1] == 's' && s[2] == 'p')
9822 else if (s[1] == 'g' && s[2] == 'p')
9827 else if (s[1] == 'a' && s[2] == 't')
9832 else if (s[1] == 'k' && s[2] == 't' && s[3] == '0')
9837 else if (s[1] == 'k' && s[2] == 't' && s[3] == '1')
9842 else if (s[1] == 'z' && s[2] == 'e' && s[3] == 'r' && s[4] == 'o')
9855 if (c == 'v' || c == 'w')
9857 regno = mips16_to_32_reg_map[lastregno];
9871 regno = mips32_to_16_reg_map[regno];
9876 regno = ILLEGAL_REG;
9881 regno = ILLEGAL_REG;
9886 regno = ILLEGAL_REG;
9891 if (regno == AT && ! mips_opts.noat)
9892 as_warn (_("used $at without \".set noat\""));
9899 if (regno == ILLEGAL_REG)
9906 ip->insn_opcode |= regno << MIPS16OP_SH_RX;
9910 ip->insn_opcode |= regno << MIPS16OP_SH_RY;
9913 ip->insn_opcode |= regno << MIPS16OP_SH_RZ;
9916 ip->insn_opcode |= regno << MIPS16OP_SH_MOVE32Z;
9922 ip->insn_opcode |= regno << MIPS16OP_SH_REGR32;
9925 regno = ((regno & 7) << 2) | ((regno & 0x18) >> 3);
9926 ip->insn_opcode |= regno << MIPS16OP_SH_REG32R;
9936 if (strncmp (s, "$pc", 3) == 0)
9960 && strncmp (s + 1, "gprel(", sizeof "gprel(" - 1) == 0)
9962 /* This is %gprel(SYMBOL). We need to read SYMBOL,
9963 and generate the appropriate reloc. If the text
9964 inside %gprel is not a symbol name with an
9965 optional offset, then we generate a normal reloc
9966 and will probably fail later. */
9967 my_getExpression (&imm_expr, s + sizeof "%gprel" - 1);
9968 if (imm_expr.X_op == O_symbol)
9971 *imm_reloc = BFD_RELOC_MIPS16_GPREL;
9973 ip->use_extend = TRUE;
9980 /* Just pick up a normal expression. */
9981 my_getExpression (&imm_expr, s);
9984 if (imm_expr.X_op == O_register)
9986 /* What we thought was an expression turned out to
9989 if (s[0] == '(' && args[1] == '(')
9991 /* It looks like the expression was omitted
9992 before a register indirection, which means
9993 that the expression is implicitly zero. We
9994 still set up imm_expr, so that we handle
9995 explicit extensions correctly. */
9996 imm_expr.X_op = O_constant;
9997 imm_expr.X_add_number = 0;
9998 *imm_reloc = (int) BFD_RELOC_UNUSED + c;
10005 /* We need to relax this instruction. */
10006 *imm_reloc = (int) BFD_RELOC_UNUSED + c;
10015 /* We use offset_reloc rather than imm_reloc for the PC
10016 relative operands. This lets macros with both
10017 immediate and address operands work correctly. */
10018 my_getExpression (&offset_expr, s);
10020 if (offset_expr.X_op == O_register)
10023 /* We need to relax this instruction. */
10024 *offset_reloc = (int) BFD_RELOC_UNUSED + c;
10028 case '6': /* break code */
10029 my_getExpression (&imm_expr, s);
10030 check_absolute_expr (ip, &imm_expr);
10031 if ((unsigned long) imm_expr.X_add_number > 63)
10033 as_warn (_("Invalid value for `%s' (%lu)"),
10035 (unsigned long) imm_expr.X_add_number);
10036 imm_expr.X_add_number &= 0x3f;
10038 ip->insn_opcode |= imm_expr.X_add_number << MIPS16OP_SH_IMM6;
10039 imm_expr.X_op = O_absent;
10043 case 'a': /* 26 bit address */
10044 my_getExpression (&offset_expr, s);
10046 *offset_reloc = BFD_RELOC_MIPS16_JMP;
10047 ip->insn_opcode <<= 16;
10050 case 'l': /* register list for entry macro */
10051 case 'L': /* register list for exit macro */
10061 int freg, reg1, reg2;
10063 while (*s == ' ' || *s == ',')
10067 as_bad (_("can't parse register list"));
10079 while (ISDIGIT (*s))
10101 as_bad (_("invalid register list"));
10106 while (ISDIGIT (*s))
10113 if (freg && reg1 == 0 && reg2 == 0 && c == 'L')
10115 mask &= ~ (7 << 3);
10118 else if (freg && reg1 == 0 && reg2 == 1 && c == 'L')
10120 mask &= ~ (7 << 3);
10123 else if (reg1 == 4 && reg2 >= 4 && reg2 <= 7 && c != 'L')
10124 mask |= (reg2 - 3) << 3;
10125 else if (reg1 == 16 && reg2 >= 16 && reg2 <= 17)
10126 mask |= (reg2 - 15) << 1;
10127 else if (reg1 == RA && reg2 == RA)
10131 as_bad (_("invalid register list"));
10135 /* The mask is filled in in the opcode table for the
10136 benefit of the disassembler. We remove it before
10137 applying the actual mask. */
10138 ip->insn_opcode &= ~ ((7 << 3) << MIPS16OP_SH_IMM6);
10139 ip->insn_opcode |= mask << MIPS16OP_SH_IMM6;
10143 case 'e': /* extend code */
10144 my_getExpression (&imm_expr, s);
10145 check_absolute_expr (ip, &imm_expr);
10146 if ((unsigned long) imm_expr.X_add_number > 0x7ff)
10148 as_warn (_("Invalid value for `%s' (%lu)"),
10150 (unsigned long) imm_expr.X_add_number);
10151 imm_expr.X_add_number &= 0x7ff;
10153 ip->insn_opcode |= imm_expr.X_add_number;
10154 imm_expr.X_op = O_absent;
10164 /* Args don't match. */
10165 if (insn + 1 < &mips16_opcodes[bfd_mips16_num_opcodes] &&
10166 strcmp (insn->name, insn[1].name) == 0)
10173 insn_error = _("illegal operands");
10179 /* This structure holds information we know about a mips16 immediate
10182 struct mips16_immed_operand
10184 /* The type code used in the argument string in the opcode table. */
10186 /* The number of bits in the short form of the opcode. */
10188 /* The number of bits in the extended form of the opcode. */
10190 /* The amount by which the short form is shifted when it is used;
10191 for example, the sw instruction has a shift count of 2. */
10193 /* The amount by which the short form is shifted when it is stored
10194 into the instruction code. */
10196 /* Non-zero if the short form is unsigned. */
10198 /* Non-zero if the extended form is unsigned. */
10200 /* Non-zero if the value is PC relative. */
10204 /* The mips16 immediate operand types. */
10206 static const struct mips16_immed_operand mips16_immed_operands[] =
10208 { '<', 3, 5, 0, MIPS16OP_SH_RZ, 1, 1, 0 },
10209 { '>', 3, 5, 0, MIPS16OP_SH_RX, 1, 1, 0 },
10210 { '[', 3, 6, 0, MIPS16OP_SH_RZ, 1, 1, 0 },
10211 { ']', 3, 6, 0, MIPS16OP_SH_RX, 1, 1, 0 },
10212 { '4', 4, 15, 0, MIPS16OP_SH_IMM4, 0, 0, 0 },
10213 { '5', 5, 16, 0, MIPS16OP_SH_IMM5, 1, 0, 0 },
10214 { 'H', 5, 16, 1, MIPS16OP_SH_IMM5, 1, 0, 0 },
10215 { 'W', 5, 16, 2, MIPS16OP_SH_IMM5, 1, 0, 0 },
10216 { 'D', 5, 16, 3, MIPS16OP_SH_IMM5, 1, 0, 0 },
10217 { 'j', 5, 16, 0, MIPS16OP_SH_IMM5, 0, 0, 0 },
10218 { '8', 8, 16, 0, MIPS16OP_SH_IMM8, 1, 0, 0 },
10219 { 'V', 8, 16, 2, MIPS16OP_SH_IMM8, 1, 0, 0 },
10220 { 'C', 8, 16, 3, MIPS16OP_SH_IMM8, 1, 0, 0 },
10221 { 'U', 8, 16, 0, MIPS16OP_SH_IMM8, 1, 1, 0 },
10222 { 'k', 8, 16, 0, MIPS16OP_SH_IMM8, 0, 0, 0 },
10223 { 'K', 8, 16, 3, MIPS16OP_SH_IMM8, 0, 0, 0 },
10224 { 'p', 8, 16, 0, MIPS16OP_SH_IMM8, 0, 0, 1 },
10225 { 'q', 11, 16, 0, MIPS16OP_SH_IMM8, 0, 0, 1 },
10226 { 'A', 8, 16, 2, MIPS16OP_SH_IMM8, 1, 0, 1 },
10227 { 'B', 5, 16, 3, MIPS16OP_SH_IMM5, 1, 0, 1 },
10228 { 'E', 5, 16, 2, MIPS16OP_SH_IMM5, 1, 0, 1 }
10231 #define MIPS16_NUM_IMMED \
10232 (sizeof mips16_immed_operands / sizeof mips16_immed_operands[0])
10234 /* Handle a mips16 instruction with an immediate value. This or's the
10235 small immediate value into *INSN. It sets *USE_EXTEND to indicate
10236 whether an extended value is needed; if one is needed, it sets
10237 *EXTEND to the value. The argument type is TYPE. The value is VAL.
10238 If SMALL is true, an unextended opcode was explicitly requested.
10239 If EXT is true, an extended opcode was explicitly requested. If
10240 WARN is true, warn if EXT does not match reality. */
10243 mips16_immed (file, line, type, val, warn, small, ext, insn, use_extend,
10252 unsigned long *insn;
10253 bfd_boolean *use_extend;
10254 unsigned short *extend;
10256 register const struct mips16_immed_operand *op;
10257 int mintiny, maxtiny;
10258 bfd_boolean needext;
10260 op = mips16_immed_operands;
10261 while (op->type != type)
10264 assert (op < mips16_immed_operands + MIPS16_NUM_IMMED);
10269 if (type == '<' || type == '>' || type == '[' || type == ']')
10272 maxtiny = 1 << op->nbits;
10277 maxtiny = (1 << op->nbits) - 1;
10282 mintiny = - (1 << (op->nbits - 1));
10283 maxtiny = (1 << (op->nbits - 1)) - 1;
10286 /* Branch offsets have an implicit 0 in the lowest bit. */
10287 if (type == 'p' || type == 'q')
10290 if ((val & ((1 << op->shift) - 1)) != 0
10291 || val < (mintiny << op->shift)
10292 || val > (maxtiny << op->shift))
10297 if (warn && ext && ! needext)
10298 as_warn_where (file, line,
10299 _("extended operand requested but not required"));
10300 if (small && needext)
10301 as_bad_where (file, line, _("invalid unextended operand value"));
10303 if (small || (! ext && ! needext))
10307 *use_extend = FALSE;
10308 insnval = ((val >> op->shift) & ((1 << op->nbits) - 1));
10309 insnval <<= op->op_shift;
10314 long minext, maxext;
10320 maxext = (1 << op->extbits) - 1;
10324 minext = - (1 << (op->extbits - 1));
10325 maxext = (1 << (op->extbits - 1)) - 1;
10327 if (val < minext || val > maxext)
10328 as_bad_where (file, line,
10329 _("operand value out of range for instruction"));
10331 *use_extend = TRUE;
10332 if (op->extbits == 16)
10334 extval = ((val >> 11) & 0x1f) | (val & 0x7e0);
10337 else if (op->extbits == 15)
10339 extval = ((val >> 11) & 0xf) | (val & 0x7f0);
10344 extval = ((val & 0x1f) << 6) | (val & 0x20);
10348 *extend = (unsigned short) extval;
10353 static const struct percent_op_match
10356 bfd_reloc_code_real_type reloc;
10359 {"%lo", BFD_RELOC_LO16},
10361 {"%call_hi", BFD_RELOC_MIPS_CALL_HI16},
10362 {"%call_lo", BFD_RELOC_MIPS_CALL_LO16},
10363 {"%call16", BFD_RELOC_MIPS_CALL16},
10364 {"%got_disp", BFD_RELOC_MIPS_GOT_DISP},
10365 {"%got_page", BFD_RELOC_MIPS_GOT_PAGE},
10366 {"%got_ofst", BFD_RELOC_MIPS_GOT_OFST},
10367 {"%got_hi", BFD_RELOC_MIPS_GOT_HI16},
10368 {"%got_lo", BFD_RELOC_MIPS_GOT_LO16},
10369 {"%got", BFD_RELOC_MIPS_GOT16},
10370 {"%gp_rel", BFD_RELOC_GPREL16},
10371 {"%half", BFD_RELOC_16},
10372 {"%highest", BFD_RELOC_MIPS_HIGHEST},
10373 {"%higher", BFD_RELOC_MIPS_HIGHER},
10374 {"%neg", BFD_RELOC_MIPS_SUB},
10376 {"%hi", BFD_RELOC_HI16_S}
10380 /* Return true if *STR points to a relocation operator. When returning true,
10381 move *STR over the operator and store its relocation code in *RELOC.
10382 Leave both *STR and *RELOC alone when returning false. */
10385 parse_relocation (str, reloc)
10387 bfd_reloc_code_real_type *reloc;
10391 for (i = 0; i < ARRAY_SIZE (percent_op); i++)
10392 if (strncasecmp (*str, percent_op[i].str, strlen (percent_op[i].str)) == 0)
10394 *str += strlen (percent_op[i].str);
10395 *reloc = percent_op[i].reloc;
10397 /* Check whether the output BFD supports this relocation.
10398 If not, issue an error and fall back on something safe. */
10399 if (!bfd_reloc_type_lookup (stdoutput, percent_op[i].reloc))
10401 as_bad ("relocation %s isn't supported by the current ABI",
10402 percent_op[i].str);
10403 *reloc = BFD_RELOC_LO16;
10411 /* Parse string STR as a 16-bit relocatable operand. Store the
10412 expression in *EP and the relocations in the array starting
10413 at RELOC. Return the number of relocation operators used.
10415 On exit, EXPR_END points to the first character after the expression.
10416 If no relocation operators are used, RELOC[0] is set to BFD_RELOC_LO16. */
10419 my_getSmallExpression (ep, reloc, str)
10421 bfd_reloc_code_real_type *reloc;
10424 bfd_reloc_code_real_type reversed_reloc[3];
10425 size_t reloc_index, i;
10426 int crux_depth, str_depth;
10429 /* Search for the start of the main expression, recoding relocations
10430 in REVERSED_RELOC. End the loop with CRUX pointing to the start
10431 of the main expression and with CRUX_DEPTH containing the number
10432 of open brackets at that point. */
10439 crux_depth = str_depth;
10441 /* Skip over whitespace and brackets, keeping count of the number
10443 while (*str == ' ' || *str == '\t' || *str == '(')
10448 && reloc_index < (HAVE_NEWABI ? 3 : 1)
10449 && parse_relocation (&str, &reversed_reloc[reloc_index]));
10451 my_getExpression (ep, crux);
10454 /* Match every open bracket. */
10455 while (crux_depth > 0 && (*str == ')' || *str == ' ' || *str == '\t'))
10459 if (crux_depth > 0)
10460 as_bad ("unclosed '('");
10464 if (reloc_index == 0)
10465 reloc[0] = BFD_RELOC_LO16;
10468 prev_reloc_op_frag = frag_now;
10469 for (i = 0; i < reloc_index; i++)
10470 reloc[i] = reversed_reloc[reloc_index - 1 - i];
10473 return reloc_index;
10477 my_getExpression (ep, str)
10484 save_in = input_line_pointer;
10485 input_line_pointer = str;
10487 expr_end = input_line_pointer;
10488 input_line_pointer = save_in;
10490 /* If we are in mips16 mode, and this is an expression based on `.',
10491 then we bump the value of the symbol by 1 since that is how other
10492 text symbols are handled. We don't bother to handle complex
10493 expressions, just `.' plus or minus a constant. */
10494 if (mips_opts.mips16
10495 && ep->X_op == O_symbol
10496 && strcmp (S_GET_NAME (ep->X_add_symbol), FAKE_LABEL_NAME) == 0
10497 && S_GET_SEGMENT (ep->X_add_symbol) == now_seg
10498 && symbol_get_frag (ep->X_add_symbol) == frag_now
10499 && symbol_constant_p (ep->X_add_symbol)
10500 && (val = S_GET_VALUE (ep->X_add_symbol)) == frag_now_fix ())
10501 S_SET_VALUE (ep->X_add_symbol, val + 1);
10504 /* Turn a string in input_line_pointer into a floating point constant
10505 of type TYPE, and store the appropriate bytes in *LITP. The number
10506 of LITTLENUMS emitted is stored in *SIZEP. An error message is
10507 returned, or NULL on OK. */
10510 md_atof (type, litP, sizeP)
10516 LITTLENUM_TYPE words[4];
10532 return _("bad call to md_atof");
10535 t = atof_ieee (input_line_pointer, type, words);
10537 input_line_pointer = t;
10541 if (! target_big_endian)
10543 for (i = prec - 1; i >= 0; i--)
10545 md_number_to_chars (litP, (valueT) words[i], 2);
10551 for (i = 0; i < prec; i++)
10553 md_number_to_chars (litP, (valueT) words[i], 2);
10562 md_number_to_chars (buf, val, n)
10567 if (target_big_endian)
10568 number_to_chars_bigendian (buf, val, n);
10570 number_to_chars_littleendian (buf, val, n);
10574 static int support_64bit_objects(void)
10576 const char **list, **l;
10579 list = bfd_target_list ();
10580 for (l = list; *l != NULL; l++)
10582 /* This is traditional mips */
10583 if (strcmp (*l, "elf64-tradbigmips") == 0
10584 || strcmp (*l, "elf64-tradlittlemips") == 0)
10586 if (strcmp (*l, "elf64-bigmips") == 0
10587 || strcmp (*l, "elf64-littlemips") == 0)
10590 yes = (*l != NULL);
10594 #endif /* OBJ_ELF */
10596 const char *md_shortopts = "nO::g::G:";
10598 struct option md_longopts[] =
10600 /* Options which specify architecture. */
10601 #define OPTION_ARCH_BASE (OPTION_MD_BASE)
10602 #define OPTION_MARCH (OPTION_ARCH_BASE + 0)
10603 {"march", required_argument, NULL, OPTION_MARCH},
10604 #define OPTION_MTUNE (OPTION_ARCH_BASE + 1)
10605 {"mtune", required_argument, NULL, OPTION_MTUNE},
10606 #define OPTION_MIPS1 (OPTION_ARCH_BASE + 2)
10607 {"mips0", no_argument, NULL, OPTION_MIPS1},
10608 {"mips1", no_argument, NULL, OPTION_MIPS1},
10609 #define OPTION_MIPS2 (OPTION_ARCH_BASE + 3)
10610 {"mips2", no_argument, NULL, OPTION_MIPS2},
10611 #define OPTION_MIPS3 (OPTION_ARCH_BASE + 4)
10612 {"mips3", no_argument, NULL, OPTION_MIPS3},
10613 #define OPTION_MIPS4 (OPTION_ARCH_BASE + 5)
10614 {"mips4", no_argument, NULL, OPTION_MIPS4},
10615 #define OPTION_MIPS5 (OPTION_ARCH_BASE + 6)
10616 {"mips5", no_argument, NULL, OPTION_MIPS5},
10617 #define OPTION_MIPS32 (OPTION_ARCH_BASE + 7)
10618 {"mips32", no_argument, NULL, OPTION_MIPS32},
10619 #define OPTION_MIPS64 (OPTION_ARCH_BASE + 8)
10620 {"mips64", no_argument, NULL, OPTION_MIPS64},
10621 #define OPTION_MIPS32R2 (OPTION_ARCH_BASE + 9)
10622 {"mips32r2", no_argument, NULL, OPTION_MIPS32R2},
10624 /* Options which specify Application Specific Extensions (ASEs). */
10625 #define OPTION_ASE_BASE (OPTION_ARCH_BASE + 10)
10626 #define OPTION_MIPS16 (OPTION_ASE_BASE + 0)
10627 {"mips16", no_argument, NULL, OPTION_MIPS16},
10628 #define OPTION_NO_MIPS16 (OPTION_ASE_BASE + 1)
10629 {"no-mips16", no_argument, NULL, OPTION_NO_MIPS16},
10630 #define OPTION_MIPS3D (OPTION_ASE_BASE + 2)
10631 {"mips3d", no_argument, NULL, OPTION_MIPS3D},
10632 #define OPTION_NO_MIPS3D (OPTION_ASE_BASE + 3)
10633 {"no-mips3d", no_argument, NULL, OPTION_NO_MIPS3D},
10634 #define OPTION_MDMX (OPTION_ASE_BASE + 4)
10635 {"mdmx", no_argument, NULL, OPTION_MDMX},
10636 #define OPTION_NO_MDMX (OPTION_ASE_BASE + 5)
10637 {"no-mdmx", no_argument, NULL, OPTION_NO_MDMX},
10639 /* Old-style architecture options. Don't add more of these. */
10640 #define OPTION_COMPAT_ARCH_BASE (OPTION_ASE_BASE + 6)
10641 #define OPTION_M4650 (OPTION_COMPAT_ARCH_BASE + 0)
10642 {"m4650", no_argument, NULL, OPTION_M4650},
10643 #define OPTION_NO_M4650 (OPTION_COMPAT_ARCH_BASE + 1)
10644 {"no-m4650", no_argument, NULL, OPTION_NO_M4650},
10645 #define OPTION_M4010 (OPTION_COMPAT_ARCH_BASE + 2)
10646 {"m4010", no_argument, NULL, OPTION_M4010},
10647 #define OPTION_NO_M4010 (OPTION_COMPAT_ARCH_BASE + 3)
10648 {"no-m4010", no_argument, NULL, OPTION_NO_M4010},
10649 #define OPTION_M4100 (OPTION_COMPAT_ARCH_BASE + 4)
10650 {"m4100", no_argument, NULL, OPTION_M4100},
10651 #define OPTION_NO_M4100 (OPTION_COMPAT_ARCH_BASE + 5)
10652 {"no-m4100", no_argument, NULL, OPTION_NO_M4100},
10653 #define OPTION_M3900 (OPTION_COMPAT_ARCH_BASE + 6)
10654 {"m3900", no_argument, NULL, OPTION_M3900},
10655 #define OPTION_NO_M3900 (OPTION_COMPAT_ARCH_BASE + 7)
10656 {"no-m3900", no_argument, NULL, OPTION_NO_M3900},
10658 /* Options which enable bug fixes. */
10659 #define OPTION_FIX_BASE (OPTION_COMPAT_ARCH_BASE + 8)
10660 #define OPTION_M7000_HILO_FIX (OPTION_FIX_BASE + 0)
10661 {"mfix7000", no_argument, NULL, OPTION_M7000_HILO_FIX},
10662 #define OPTION_MNO_7000_HILO_FIX (OPTION_FIX_BASE + 1)
10663 {"no-fix-7000", no_argument, NULL, OPTION_MNO_7000_HILO_FIX},
10664 {"mno-fix7000", no_argument, NULL, OPTION_MNO_7000_HILO_FIX},
10665 #define OPTION_FIX_VR4122 (OPTION_FIX_BASE + 2)
10666 #define OPTION_NO_FIX_VR4122 (OPTION_FIX_BASE + 3)
10667 {"mfix-vr4122-bugs", no_argument, NULL, OPTION_FIX_VR4122},
10668 {"no-mfix-vr4122-bugs", no_argument, NULL, OPTION_NO_FIX_VR4122},
10670 /* Miscellaneous options. */
10671 #define OPTION_MISC_BASE (OPTION_FIX_BASE + 4)
10672 #define OPTION_MEMBEDDED_PIC (OPTION_MISC_BASE + 0)
10673 {"membedded-pic", no_argument, NULL, OPTION_MEMBEDDED_PIC},
10674 #define OPTION_TRAP (OPTION_MISC_BASE + 1)
10675 {"trap", no_argument, NULL, OPTION_TRAP},
10676 {"no-break", no_argument, NULL, OPTION_TRAP},
10677 #define OPTION_BREAK (OPTION_MISC_BASE + 2)
10678 {"break", no_argument, NULL, OPTION_BREAK},
10679 {"no-trap", no_argument, NULL, OPTION_BREAK},
10680 #define OPTION_EB (OPTION_MISC_BASE + 3)
10681 {"EB", no_argument, NULL, OPTION_EB},
10682 #define OPTION_EL (OPTION_MISC_BASE + 4)
10683 {"EL", no_argument, NULL, OPTION_EL},
10684 #define OPTION_FP32 (OPTION_MISC_BASE + 5)
10685 {"mfp32", no_argument, NULL, OPTION_FP32},
10686 #define OPTION_GP32 (OPTION_MISC_BASE + 6)
10687 {"mgp32", no_argument, NULL, OPTION_GP32},
10688 #define OPTION_CONSTRUCT_FLOATS (OPTION_MISC_BASE + 7)
10689 {"construct-floats", no_argument, NULL, OPTION_CONSTRUCT_FLOATS},
10690 #define OPTION_NO_CONSTRUCT_FLOATS (OPTION_MISC_BASE + 8)
10691 {"no-construct-floats", no_argument, NULL, OPTION_NO_CONSTRUCT_FLOATS},
10692 #define OPTION_FP64 (OPTION_MISC_BASE + 9)
10693 {"mfp64", no_argument, NULL, OPTION_FP64},
10694 #define OPTION_GP64 (OPTION_MISC_BASE + 10)
10695 {"mgp64", no_argument, NULL, OPTION_GP64},
10696 #define OPTION_RELAX_BRANCH (OPTION_MISC_BASE + 11)
10697 #define OPTION_NO_RELAX_BRANCH (OPTION_MISC_BASE + 12)
10698 {"relax-branch", no_argument, NULL, OPTION_RELAX_BRANCH},
10699 {"no-relax-branch", no_argument, NULL, OPTION_NO_RELAX_BRANCH},
10701 /* ELF-specific options. */
10703 #define OPTION_ELF_BASE (OPTION_MISC_BASE + 13)
10704 #define OPTION_CALL_SHARED (OPTION_ELF_BASE + 0)
10705 {"KPIC", no_argument, NULL, OPTION_CALL_SHARED},
10706 {"call_shared", no_argument, NULL, OPTION_CALL_SHARED},
10707 #define OPTION_NON_SHARED (OPTION_ELF_BASE + 1)
10708 {"non_shared", no_argument, NULL, OPTION_NON_SHARED},
10709 #define OPTION_XGOT (OPTION_ELF_BASE + 2)
10710 {"xgot", no_argument, NULL, OPTION_XGOT},
10711 #define OPTION_MABI (OPTION_ELF_BASE + 3)
10712 {"mabi", required_argument, NULL, OPTION_MABI},
10713 #define OPTION_32 (OPTION_ELF_BASE + 4)
10714 {"32", no_argument, NULL, OPTION_32},
10715 #define OPTION_N32 (OPTION_ELF_BASE + 5)
10716 {"n32", no_argument, NULL, OPTION_N32},
10717 #define OPTION_64 (OPTION_ELF_BASE + 6)
10718 {"64", no_argument, NULL, OPTION_64},
10719 #define OPTION_MDEBUG (OPTION_ELF_BASE + 7)
10720 {"mdebug", no_argument, NULL, OPTION_MDEBUG},
10721 #define OPTION_NO_MDEBUG (OPTION_ELF_BASE + 8)
10722 {"no-mdebug", no_argument, NULL, OPTION_NO_MDEBUG},
10723 #endif /* OBJ_ELF */
10725 {NULL, no_argument, NULL, 0}
10727 size_t md_longopts_size = sizeof (md_longopts);
10729 /* Set STRING_PTR (either &mips_arch_string or &mips_tune_string) to
10730 NEW_VALUE. Warn if another value was already specified. Note:
10731 we have to defer parsing the -march and -mtune arguments in order
10732 to handle 'from-abi' correctly, since the ABI might be specified
10733 in a later argument. */
10736 mips_set_option_string (string_ptr, new_value)
10737 const char **string_ptr, *new_value;
10739 if (*string_ptr != 0 && strcasecmp (*string_ptr, new_value) != 0)
10740 as_warn (_("A different %s was already specified, is now %s"),
10741 string_ptr == &mips_arch_string ? "-march" : "-mtune",
10744 *string_ptr = new_value;
10748 md_parse_option (c, arg)
10754 case OPTION_CONSTRUCT_FLOATS:
10755 mips_disable_float_construction = 0;
10758 case OPTION_NO_CONSTRUCT_FLOATS:
10759 mips_disable_float_construction = 1;
10771 target_big_endian = 1;
10775 target_big_endian = 0;
10783 if (arg && arg[1] == '0')
10793 mips_debug = atoi (arg);
10794 /* When the MIPS assembler sees -g or -g2, it does not do
10795 optimizations which limit full symbolic debugging. We take
10796 that to be equivalent to -O0. */
10797 if (mips_debug == 2)
10802 file_mips_isa = ISA_MIPS1;
10806 file_mips_isa = ISA_MIPS2;
10810 file_mips_isa = ISA_MIPS3;
10814 file_mips_isa = ISA_MIPS4;
10818 file_mips_isa = ISA_MIPS5;
10821 case OPTION_MIPS32:
10822 file_mips_isa = ISA_MIPS32;
10825 case OPTION_MIPS32R2:
10826 file_mips_isa = ISA_MIPS32R2;
10829 case OPTION_MIPS64:
10830 file_mips_isa = ISA_MIPS64;
10834 mips_set_option_string (&mips_tune_string, arg);
10838 mips_set_option_string (&mips_arch_string, arg);
10842 mips_set_option_string (&mips_arch_string, "4650");
10843 mips_set_option_string (&mips_tune_string, "4650");
10846 case OPTION_NO_M4650:
10850 mips_set_option_string (&mips_arch_string, "4010");
10851 mips_set_option_string (&mips_tune_string, "4010");
10854 case OPTION_NO_M4010:
10858 mips_set_option_string (&mips_arch_string, "4100");
10859 mips_set_option_string (&mips_tune_string, "4100");
10862 case OPTION_NO_M4100:
10866 mips_set_option_string (&mips_arch_string, "3900");
10867 mips_set_option_string (&mips_tune_string, "3900");
10870 case OPTION_NO_M3900:
10874 mips_opts.ase_mdmx = 1;
10877 case OPTION_NO_MDMX:
10878 mips_opts.ase_mdmx = 0;
10881 case OPTION_MIPS16:
10882 mips_opts.mips16 = 1;
10883 mips_no_prev_insn (FALSE);
10886 case OPTION_NO_MIPS16:
10887 mips_opts.mips16 = 0;
10888 mips_no_prev_insn (FALSE);
10891 case OPTION_MIPS3D:
10892 mips_opts.ase_mips3d = 1;
10895 case OPTION_NO_MIPS3D:
10896 mips_opts.ase_mips3d = 0;
10899 case OPTION_MEMBEDDED_PIC:
10900 mips_pic = EMBEDDED_PIC;
10901 if (USE_GLOBAL_POINTER_OPT && g_switch_seen)
10903 as_bad (_("-G may not be used with embedded PIC code"));
10906 g_switch_value = 0x7fffffff;
10909 case OPTION_FIX_VR4122:
10910 mips_fix_4122_bugs = 1;
10913 case OPTION_NO_FIX_VR4122:
10914 mips_fix_4122_bugs = 0;
10917 case OPTION_RELAX_BRANCH:
10918 mips_relax_branch = 1;
10921 case OPTION_NO_RELAX_BRANCH:
10922 mips_relax_branch = 0;
10926 /* When generating ELF code, we permit -KPIC and -call_shared to
10927 select SVR4_PIC, and -non_shared to select no PIC. This is
10928 intended to be compatible with Irix 5. */
10929 case OPTION_CALL_SHARED:
10930 if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
10932 as_bad (_("-call_shared is supported only for ELF format"));
10935 mips_pic = SVR4_PIC;
10936 mips_abicalls = TRUE;
10937 if (g_switch_seen && g_switch_value != 0)
10939 as_bad (_("-G may not be used with SVR4 PIC code"));
10942 g_switch_value = 0;
10945 case OPTION_NON_SHARED:
10946 if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
10948 as_bad (_("-non_shared is supported only for ELF format"));
10952 mips_abicalls = FALSE;
10955 /* The -xgot option tells the assembler to use 32 offsets when
10956 accessing the got in SVR4_PIC mode. It is for Irix
10961 #endif /* OBJ_ELF */
10964 if (! USE_GLOBAL_POINTER_OPT)
10966 as_bad (_("-G is not supported for this configuration"));
10969 else if (mips_pic == SVR4_PIC || mips_pic == EMBEDDED_PIC)
10971 as_bad (_("-G may not be used with SVR4 or embedded PIC code"));
10975 g_switch_value = atoi (arg);
10980 /* The -32, -n32 and -64 options are shortcuts for -mabi=32, -mabi=n32
10983 if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
10985 as_bad (_("-32 is supported for ELF format only"));
10988 mips_abi = O32_ABI;
10992 if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
10994 as_bad (_("-n32 is supported for ELF format only"));
10997 mips_abi = N32_ABI;
11001 if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
11003 as_bad (_("-64 is supported for ELF format only"));
11006 mips_abi = N64_ABI;
11007 if (! support_64bit_objects())
11008 as_fatal (_("No compiled in support for 64 bit object file format"));
11010 #endif /* OBJ_ELF */
11013 file_mips_gp32 = 1;
11017 file_mips_gp32 = 0;
11021 file_mips_fp32 = 1;
11025 file_mips_fp32 = 0;
11030 if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
11032 as_bad (_("-mabi is supported for ELF format only"));
11035 if (strcmp (arg, "32") == 0)
11036 mips_abi = O32_ABI;
11037 else if (strcmp (arg, "o64") == 0)
11038 mips_abi = O64_ABI;
11039 else if (strcmp (arg, "n32") == 0)
11040 mips_abi = N32_ABI;
11041 else if (strcmp (arg, "64") == 0)
11043 mips_abi = N64_ABI;
11044 if (! support_64bit_objects())
11045 as_fatal (_("No compiled in support for 64 bit object file "
11048 else if (strcmp (arg, "eabi") == 0)
11049 mips_abi = EABI_ABI;
11052 as_fatal (_("invalid abi -mabi=%s"), arg);
11056 #endif /* OBJ_ELF */
11058 case OPTION_M7000_HILO_FIX:
11059 mips_7000_hilo_fix = TRUE;
11062 case OPTION_MNO_7000_HILO_FIX:
11063 mips_7000_hilo_fix = FALSE;
11067 case OPTION_MDEBUG:
11068 mips_flag_mdebug = TRUE;
11071 case OPTION_NO_MDEBUG:
11072 mips_flag_mdebug = FALSE;
11074 #endif /* OBJ_ELF */
11083 /* Set up globals to generate code for the ISA or processor
11084 described by INFO. */
11087 mips_set_architecture (info)
11088 const struct mips_cpu_info *info;
11092 mips_arch_info = info;
11093 mips_arch = info->cpu;
11094 mips_opts.isa = info->isa;
11099 /* Likewise for tuning. */
11102 mips_set_tune (info)
11103 const struct mips_cpu_info *info;
11107 mips_tune_info = info;
11108 mips_tune = info->cpu;
11114 mips_after_parse_args ()
11116 /* GP relative stuff not working for PE */
11117 if (strncmp (TARGET_OS, "pe", 2) == 0
11118 && g_switch_value != 0)
11121 as_bad (_("-G not supported in this configuration."));
11122 g_switch_value = 0;
11125 if (mips_abi == NO_ABI)
11126 mips_abi = MIPS_DEFAULT_ABI;
11128 /* The following code determines the architecture and register size.
11129 Similar code was added to GCC 3.3 (see override_options() in
11130 config/mips/mips.c). The GAS and GCC code should be kept in sync
11131 as much as possible. */
11133 if (mips_arch_string != 0)
11134 mips_set_architecture (mips_parse_cpu ("-march", mips_arch_string));
11136 if (mips_tune_string != 0)
11137 mips_set_tune (mips_parse_cpu ("-mtune", mips_tune_string));
11139 if (file_mips_isa != ISA_UNKNOWN)
11141 /* Handle -mipsN. At this point, file_mips_isa contains the
11142 ISA level specified by -mipsN, while mips_opts.isa contains
11143 the -march selection (if any). */
11144 if (mips_arch_info != 0)
11146 /* -march takes precedence over -mipsN, since it is more descriptive.
11147 There's no harm in specifying both as long as the ISA levels
11149 if (file_mips_isa != mips_opts.isa)
11150 as_bad (_("-%s conflicts with the other architecture options, which imply -%s"),
11151 mips_cpu_info_from_isa (file_mips_isa)->name,
11152 mips_cpu_info_from_isa (mips_opts.isa)->name);
11155 mips_set_architecture (mips_cpu_info_from_isa (file_mips_isa));
11158 if (mips_arch_info == 0)
11159 mips_set_architecture (mips_parse_cpu ("default CPU",
11160 MIPS_CPU_STRING_DEFAULT));
11162 if (ABI_NEEDS_64BIT_REGS (mips_abi) && !ISA_HAS_64BIT_REGS (mips_opts.isa))
11163 as_bad ("-march=%s is not compatible with the selected ABI",
11164 mips_arch_info->name);
11166 /* Optimize for mips_arch, unless -mtune selects a different processor. */
11167 if (mips_tune_info == 0)
11168 mips_set_tune (mips_arch_info);
11170 if (file_mips_gp32 >= 0)
11172 /* The user specified the size of the integer registers. Make sure
11173 it agrees with the ABI and ISA. */
11174 if (file_mips_gp32 == 0 && !ISA_HAS_64BIT_REGS (mips_opts.isa))
11175 as_bad (_("-mgp64 used with a 32-bit processor"));
11176 else if (file_mips_gp32 == 1 && ABI_NEEDS_64BIT_REGS (mips_abi))
11177 as_bad (_("-mgp32 used with a 64-bit ABI"));
11178 else if (file_mips_gp32 == 0 && ABI_NEEDS_32BIT_REGS (mips_abi))
11179 as_bad (_("-mgp64 used with a 32-bit ABI"));
11183 /* Infer the integer register size from the ABI and processor.
11184 Restrict ourselves to 32-bit registers if that's all the
11185 processor has, or if the ABI cannot handle 64-bit registers. */
11186 file_mips_gp32 = (ABI_NEEDS_32BIT_REGS (mips_abi)
11187 || !ISA_HAS_64BIT_REGS (mips_opts.isa));
11190 /* ??? GAS treats single-float processors as though they had 64-bit
11191 float registers (although it complains when double-precision
11192 instructions are used). As things stand, saying they have 32-bit
11193 registers would lead to spurious "register must be even" messages.
11194 So here we assume float registers are always the same size as
11195 integer ones, unless the user says otherwise. */
11196 if (file_mips_fp32 < 0)
11197 file_mips_fp32 = file_mips_gp32;
11199 /* End of GCC-shared inference code. */
11201 /* ??? When do we want this flag to be set? Who uses it? */
11202 if (file_mips_gp32 == 1
11203 && mips_abi == NO_ABI
11204 && ISA_HAS_64BIT_REGS (mips_opts.isa))
11205 mips_32bitmode = 1;
11207 if (mips_opts.isa == ISA_MIPS1 && mips_trap)
11208 as_bad (_("trap exception not supported at ISA 1"));
11210 /* If the selected architecture includes support for ASEs, enable
11211 generation of code for them. */
11212 if (mips_opts.mips16 == -1)
11213 mips_opts.mips16 = (CPU_HAS_MIPS16 (mips_arch)) ? 1 : 0;
11214 if (mips_opts.ase_mips3d == -1)
11215 mips_opts.ase_mips3d = (CPU_HAS_MIPS3D (mips_arch)) ? 1 : 0;
11216 if (mips_opts.ase_mdmx == -1)
11217 mips_opts.ase_mdmx = (CPU_HAS_MDMX (mips_arch)) ? 1 : 0;
11219 file_mips_isa = mips_opts.isa;
11220 file_ase_mips16 = mips_opts.mips16;
11221 file_ase_mips3d = mips_opts.ase_mips3d;
11222 file_ase_mdmx = mips_opts.ase_mdmx;
11223 mips_opts.gp32 = file_mips_gp32;
11224 mips_opts.fp32 = file_mips_fp32;
11226 if (mips_flag_mdebug < 0)
11228 #ifdef OBJ_MAYBE_ECOFF
11229 if (OUTPUT_FLAVOR == bfd_target_ecoff_flavour)
11230 mips_flag_mdebug = 1;
11232 #endif /* OBJ_MAYBE_ECOFF */
11233 mips_flag_mdebug = 0;
11238 mips_init_after_args ()
11240 /* initialize opcodes */
11241 bfd_mips_num_opcodes = bfd_mips_num_builtin_opcodes;
11242 mips_opcodes = (struct mips_opcode *) mips_builtin_opcodes;
11246 md_pcrel_from (fixP)
11249 valueT addr = fixP->fx_where + fixP->fx_frag->fr_address;
11250 switch (fixP->fx_r_type)
11252 case BFD_RELOC_16_PCREL_S2:
11253 case BFD_RELOC_MIPS_JMP:
11254 /* Return the address of the delay slot. */
11261 /* This is called before the symbol table is processed. In order to
11262 work with gcc when using mips-tfile, we must keep all local labels.
11263 However, in other cases, we want to discard them. If we were
11264 called with -g, but we didn't see any debugging information, it may
11265 mean that gcc is smuggling debugging information through to
11266 mips-tfile, in which case we must generate all local labels. */
11269 mips_frob_file_before_adjust ()
11271 #ifndef NO_ECOFF_DEBUGGING
11272 if (ECOFF_DEBUGGING
11274 && ! ecoff_debugging_seen)
11275 flag_keep_locals = 1;
11279 /* Sort any unmatched HI16_S relocs so that they immediately precede
11280 the corresponding LO reloc. This is called before md_apply_fix3 and
11281 tc_gen_reloc. Unmatched HI16_S relocs can only be generated by
11282 explicit use of the %hi modifier. */
11287 struct mips_hi_fixup *l;
11289 for (l = mips_hi_fixup_list; l != NULL; l = l->next)
11291 segment_info_type *seginfo;
11294 assert (reloc_needs_lo_p (l->fixp->fx_r_type));
11296 /* If a GOT16 relocation turns out to be against a global symbol,
11297 there isn't supposed to be a matching LO. */
11298 if (l->fixp->fx_r_type == BFD_RELOC_MIPS_GOT16
11299 && !pic_need_relax (l->fixp->fx_addsy, l->seg))
11302 /* Check quickly whether the next fixup happens to be a matching %lo. */
11303 if (fixup_has_matching_lo_p (l->fixp))
11306 /* Look through the fixups for this segment for a matching %lo.
11307 When we find one, move the %hi just in front of it. We do
11308 this in two passes. In the first pass, we try to find a
11309 unique %lo. In the second pass, we permit multiple %hi
11310 relocs for a single %lo (this is a GNU extension). */
11311 seginfo = seg_info (l->seg);
11312 for (pass = 0; pass < 2; pass++)
11317 for (f = seginfo->fix_root; f != NULL; f = f->fx_next)
11319 /* Check whether this is a %lo fixup which matches l->fixp. */
11320 if (f->fx_r_type == BFD_RELOC_LO16
11321 && f->fx_addsy == l->fixp->fx_addsy
11322 && f->fx_offset == l->fixp->fx_offset
11325 || !reloc_needs_lo_p (prev->fx_r_type)
11326 || !fixup_has_matching_lo_p (prev)))
11330 /* Move l->fixp before f. */
11331 for (pf = &seginfo->fix_root;
11333 pf = &(*pf)->fx_next)
11334 assert (*pf != NULL);
11336 *pf = l->fixp->fx_next;
11338 l->fixp->fx_next = f;
11340 seginfo->fix_root = l->fixp;
11342 prev->fx_next = l->fixp;
11353 #if 0 /* GCC code motion plus incomplete dead code elimination
11354 can leave a %hi without a %lo. */
11356 as_warn_where (l->fixp->fx_file, l->fixp->fx_line,
11357 _("Unmatched %%hi reloc"));
11363 /* When generating embedded PIC code we need to use a special
11364 relocation to represent the difference of two symbols in the .text
11365 section (switch tables use a difference of this sort). See
11366 include/coff/mips.h for details. This macro checks whether this
11367 fixup requires the special reloc. */
11368 #define SWITCH_TABLE(fixp) \
11369 ((fixp)->fx_r_type == BFD_RELOC_32 \
11370 && OUTPUT_FLAVOR != bfd_target_elf_flavour \
11371 && (fixp)->fx_addsy != NULL \
11372 && (fixp)->fx_subsy != NULL \
11373 && S_GET_SEGMENT ((fixp)->fx_addsy) == text_section \
11374 && S_GET_SEGMENT ((fixp)->fx_subsy) == text_section)
11376 /* When generating embedded PIC code we must keep all PC relative
11377 relocations, in case the linker has to relax a call. We also need
11378 to keep relocations for switch table entries.
11380 We may have combined relocations without symbols in the N32/N64 ABI.
11381 We have to prevent gas from dropping them. */
11384 mips_force_relocation (fixp)
11387 if (generic_force_reloc (fixp))
11391 && S_GET_SEGMENT (fixp->fx_addsy) == bfd_abs_section_ptr
11392 && (fixp->fx_r_type == BFD_RELOC_MIPS_SUB
11393 || fixp->fx_r_type == BFD_RELOC_HI16_S
11394 || fixp->fx_r_type == BFD_RELOC_LO16))
11397 return (mips_pic == EMBEDDED_PIC
11399 || SWITCH_TABLE (fixp)
11400 || fixp->fx_r_type == BFD_RELOC_PCREL_HI16_S
11401 || fixp->fx_r_type == BFD_RELOC_PCREL_LO16));
11404 /* This hook is called before a fix is simplified. We don't really
11405 decide whether to skip a fix here. Rather, we turn global symbols
11406 used as branch targets into local symbols, such that they undergo
11407 simplification. We can only do this if the symbol is defined and
11408 it is in the same section as the branch. If this doesn't hold, we
11409 emit a better error message than just saying the relocation is not
11410 valid for the selected object format.
11412 FIXP is the fix-up we're going to try to simplify, SEG is the
11413 segment in which the fix up occurs. The return value should be
11414 non-zero to indicate the fix-up is valid for further
11415 simplifications. */
11418 mips_validate_fix (fixP, seg)
11422 /* There's a lot of discussion on whether it should be possible to
11423 use R_MIPS_PC16 to represent branch relocations. The outcome
11424 seems to be that it can, but gas/bfd are very broken in creating
11425 RELA relocations for this, so for now we only accept branches to
11426 symbols in the same section. Anything else is of dubious value,
11427 since there's no guarantee that at link time the symbol would be
11428 in range. Even for branches to local symbols this is arguably
11429 wrong, since it we assume the symbol is not going to be
11430 overridden, which should be possible per ELF library semantics,
11431 but then, there isn't a dynamic relocation that could be used to
11432 this effect, and the target would likely be out of range as well.
11434 Unfortunately, it seems that there is too much code out there
11435 that relies on branches to symbols that are global to be resolved
11436 as if they were local, like the IRIX tools do, so we do it as
11437 well, but with a warning so that people are reminded to fix their
11438 code. If we ever get back to using R_MIPS_PC16 for branch
11439 targets, this entire block should go away (and probably the
11440 whole function). */
11442 if (fixP->fx_r_type == BFD_RELOC_16_PCREL_S2
11443 && (((OUTPUT_FLAVOR == bfd_target_ecoff_flavour
11444 || OUTPUT_FLAVOR == bfd_target_elf_flavour)
11445 && mips_pic != EMBEDDED_PIC)
11446 || bfd_reloc_type_lookup (stdoutput, BFD_RELOC_16_PCREL_S2) == NULL)
11449 if (! S_IS_DEFINED (fixP->fx_addsy))
11451 as_bad_where (fixP->fx_file, fixP->fx_line,
11452 _("Cannot branch to undefined symbol."));
11453 /* Avoid any further errors about this fixup. */
11456 else if (S_GET_SEGMENT (fixP->fx_addsy) != seg)
11458 as_bad_where (fixP->fx_file, fixP->fx_line,
11459 _("Cannot branch to symbol in another section."));
11462 else if (S_IS_EXTERNAL (fixP->fx_addsy))
11464 symbolS *sym = fixP->fx_addsy;
11466 as_warn_where (fixP->fx_file, fixP->fx_line,
11467 _("Pretending global symbol used as branch target is local."));
11469 fixP->fx_addsy = symbol_create (S_GET_NAME (sym),
11470 S_GET_SEGMENT (sym),
11472 symbol_get_frag (sym));
11473 copy_symbol_attributes (fixP->fx_addsy, sym);
11474 S_CLEAR_EXTERNAL (fixP->fx_addsy);
11475 assert (symbol_resolved_p (sym));
11476 symbol_mark_resolved (fixP->fx_addsy);
11485 mips_need_elf_addend_fixup (fixP)
11488 if (S_GET_OTHER (fixP->fx_addsy) == STO_MIPS16)
11490 if (mips_pic == EMBEDDED_PIC
11491 && S_IS_WEAK (fixP->fx_addsy))
11493 if (mips_pic != EMBEDDED_PIC
11494 && (S_IS_WEAK (fixP->fx_addsy)
11495 || S_IS_EXTERNAL (fixP->fx_addsy))
11496 && !S_IS_COMMON (fixP->fx_addsy))
11498 if (((bfd_get_section_flags (stdoutput,
11499 S_GET_SEGMENT (fixP->fx_addsy))
11500 & (SEC_LINK_ONCE | SEC_MERGE)) != 0)
11501 || !strncmp (segment_name (S_GET_SEGMENT (fixP->fx_addsy)),
11503 sizeof (".gnu.linkonce") - 1))
11509 /* Apply a fixup to the object file. */
11512 md_apply_fix3 (fixP, valP, seg)
11515 segT seg ATTRIBUTE_UNUSED;
11519 static int previous_fx_r_type = 0;
11520 reloc_howto_type *howto;
11522 /* We ignore generic BFD relocations we don't know about. */
11523 howto = bfd_reloc_type_lookup (stdoutput, fixP->fx_r_type);
11527 assert (fixP->fx_size == 4
11528 || fixP->fx_r_type == BFD_RELOC_16
11529 || fixP->fx_r_type == BFD_RELOC_64
11530 || fixP->fx_r_type == BFD_RELOC_CTOR
11531 || fixP->fx_r_type == BFD_RELOC_MIPS_SUB
11532 || fixP->fx_r_type == BFD_RELOC_VTABLE_INHERIT
11533 || fixP->fx_r_type == BFD_RELOC_VTABLE_ENTRY);
11535 buf = (bfd_byte *) (fixP->fx_frag->fr_literal + fixP->fx_where);
11537 /* If we aren't adjusting this fixup to be against the section
11538 symbol, we need to adjust the value. */
11540 if (fixP->fx_addsy != NULL && OUTPUT_FLAVOR == bfd_target_elf_flavour)
11542 if (mips_need_elf_addend_fixup (fixP)
11543 && howto->partial_inplace
11544 && fixP->fx_r_type != BFD_RELOC_GPREL16
11545 && fixP->fx_r_type != BFD_RELOC_GPREL32
11546 && fixP->fx_r_type != BFD_RELOC_MIPS16_GPREL)
11548 /* In this case, the bfd_install_relocation routine will
11549 incorrectly add the symbol value back in. We just want
11550 the addend to appear in the object file.
11552 The condition above used to include
11553 "&& (! fixP->fx_pcrel || howto->pcrel_offset)".
11555 However, howto can't be trusted here, because we
11556 might change the reloc type in tc_gen_reloc. We can
11557 check howto->partial_inplace because that conversion
11558 happens to preserve howto->partial_inplace; but it
11559 does not preserve howto->pcrel_offset. I've just
11560 eliminated the check, because all MIPS PC-relative
11561 relocations are marked howto->pcrel_offset.
11563 howto->pcrel_offset was originally added for
11564 R_MIPS_PC16, which is generated for code like
11573 *valP -= S_GET_VALUE (fixP->fx_addsy);
11576 /* This code was generated using trial and error and so is
11577 fragile and not trustworthy. If you change it, you should
11578 rerun the elf-rel, elf-rel2, and empic testcases and ensure
11579 they still pass. */
11580 if (fixP->fx_pcrel)
11582 *valP += fixP->fx_frag->fr_address + fixP->fx_where;
11584 /* BFD's REL handling, for MIPS, is _very_ weird.
11585 This gives the right results, but it can't possibly
11586 be the way things are supposed to work. */
11587 *valP += fixP->fx_frag->fr_address + fixP->fx_where;
11592 /* We are not done if this is a composite relocation to set up gp. */
11593 if (fixP->fx_addsy == NULL && ! fixP->fx_pcrel
11594 && !(fixP->fx_r_type == BFD_RELOC_MIPS_SUB
11595 || (fixP->fx_r_type == BFD_RELOC_64
11596 && (previous_fx_r_type == BFD_RELOC_GPREL32
11597 || previous_fx_r_type == BFD_RELOC_GPREL16))
11598 || (previous_fx_r_type == BFD_RELOC_MIPS_SUB
11599 && (fixP->fx_r_type == BFD_RELOC_HI16_S
11600 || fixP->fx_r_type == BFD_RELOC_LO16))))
11602 previous_fx_r_type = fixP->fx_r_type;
11604 switch (fixP->fx_r_type)
11606 case BFD_RELOC_MIPS_JMP:
11607 case BFD_RELOC_MIPS_SHIFT5:
11608 case BFD_RELOC_MIPS_SHIFT6:
11609 case BFD_RELOC_MIPS_GOT_DISP:
11610 case BFD_RELOC_MIPS_GOT_PAGE:
11611 case BFD_RELOC_MIPS_GOT_OFST:
11612 case BFD_RELOC_MIPS_SUB:
11613 case BFD_RELOC_MIPS_INSERT_A:
11614 case BFD_RELOC_MIPS_INSERT_B:
11615 case BFD_RELOC_MIPS_DELETE:
11616 case BFD_RELOC_MIPS_HIGHEST:
11617 case BFD_RELOC_MIPS_HIGHER:
11618 case BFD_RELOC_MIPS_SCN_DISP:
11619 case BFD_RELOC_MIPS_REL16:
11620 case BFD_RELOC_MIPS_RELGOT:
11621 case BFD_RELOC_MIPS_JALR:
11622 case BFD_RELOC_HI16:
11623 case BFD_RELOC_HI16_S:
11624 case BFD_RELOC_GPREL16:
11625 case BFD_RELOC_MIPS_LITERAL:
11626 case BFD_RELOC_MIPS_CALL16:
11627 case BFD_RELOC_MIPS_GOT16:
11628 case BFD_RELOC_GPREL32:
11629 case BFD_RELOC_MIPS_GOT_HI16:
11630 case BFD_RELOC_MIPS_GOT_LO16:
11631 case BFD_RELOC_MIPS_CALL_HI16:
11632 case BFD_RELOC_MIPS_CALL_LO16:
11633 case BFD_RELOC_MIPS16_GPREL:
11634 if (fixP->fx_pcrel)
11635 as_bad_where (fixP->fx_file, fixP->fx_line,
11636 _("Invalid PC relative reloc"));
11637 /* Nothing needed to do. The value comes from the reloc entry */
11640 case BFD_RELOC_MIPS16_JMP:
11641 /* We currently always generate a reloc against a symbol, which
11642 means that we don't want an addend even if the symbol is
11647 case BFD_RELOC_PCREL_HI16_S:
11648 /* The addend for this is tricky if it is internal, so we just
11649 do everything here rather than in bfd_install_relocation. */
11650 if (OUTPUT_FLAVOR == bfd_target_elf_flavour && !fixP->fx_done)
11653 && (symbol_get_bfdsym (fixP->fx_addsy)->flags & BSF_SECTION_SYM) == 0)
11655 /* For an external symbol adjust by the address to make it
11656 pcrel_offset. We use the address of the RELLO reloc
11657 which follows this one. */
11658 *valP += (fixP->fx_next->fx_frag->fr_address
11659 + fixP->fx_next->fx_where);
11661 *valP = ((*valP + 0x8000) >> 16) & 0xffff;
11662 if (target_big_endian)
11664 md_number_to_chars ((char *) buf, *valP, 2);
11667 case BFD_RELOC_PCREL_LO16:
11668 /* The addend for this is tricky if it is internal, so we just
11669 do everything here rather than in bfd_install_relocation. */
11670 if (OUTPUT_FLAVOR == bfd_target_elf_flavour && !fixP->fx_done)
11673 && (symbol_get_bfdsym (fixP->fx_addsy)->flags & BSF_SECTION_SYM) == 0)
11674 *valP += fixP->fx_frag->fr_address + fixP->fx_where;
11675 if (target_big_endian)
11677 md_number_to_chars ((char *) buf, *valP, 2);
11681 /* This is handled like BFD_RELOC_32, but we output a sign
11682 extended value if we are only 32 bits. */
11684 || (mips_pic == EMBEDDED_PIC && SWITCH_TABLE (fixP)))
11686 if (8 <= sizeof (valueT))
11687 md_number_to_chars (buf, *valP, 8);
11692 if ((*valP & 0x80000000) != 0)
11696 md_number_to_chars ((char *)(buf + target_big_endian ? 4 : 0),
11698 md_number_to_chars ((char *)(buf + target_big_endian ? 0 : 4),
11704 case BFD_RELOC_RVA:
11706 /* If we are deleting this reloc entry, we must fill in the
11707 value now. This can happen if we have a .word which is not
11708 resolved when it appears but is later defined. We also need
11709 to fill in the value if this is an embedded PIC switch table
11712 || (mips_pic == EMBEDDED_PIC && SWITCH_TABLE (fixP)))
11713 md_number_to_chars (buf, *valP, 4);
11717 /* If we are deleting this reloc entry, we must fill in the
11719 assert (fixP->fx_size == 2);
11721 md_number_to_chars (buf, *valP, 2);
11724 case BFD_RELOC_LO16:
11725 /* When handling an embedded PIC switch statement, we can wind
11726 up deleting a LO16 reloc. See the 'o' case in mips_ip. */
11729 if (*valP + 0x8000 > 0xffff)
11730 as_bad_where (fixP->fx_file, fixP->fx_line,
11731 _("relocation overflow"));
11732 if (target_big_endian)
11734 md_number_to_chars ((char *) buf, *valP, 2);
11738 case BFD_RELOC_16_PCREL_S2:
11739 if ((*valP & 0x3) != 0)
11740 as_bad_where (fixP->fx_file, fixP->fx_line,
11741 _("Branch to odd address (%lx)"), (long) *valP);
11744 * We need to save the bits in the instruction since fixup_segment()
11745 * might be deleting the relocation entry (i.e., a branch within
11746 * the current segment).
11748 if (! fixP->fx_done)
11751 /* update old instruction data */
11752 if (target_big_endian)
11753 insn = (buf[0] << 24) | (buf[1] << 16) | (buf[2] << 8) | buf[3];
11755 insn = (buf[3] << 24) | (buf[2] << 16) | (buf[1] << 8) | buf[0];
11757 if (*valP + 0x20000 <= 0x3ffff)
11759 insn |= (*valP >> 2) & 0xffff;
11760 md_number_to_chars ((char *) buf, (valueT) insn, 4);
11762 else if (mips_pic == NO_PIC
11764 && fixP->fx_frag->fr_address >= text_section->vma
11765 && (fixP->fx_frag->fr_address
11766 < text_section->vma + text_section->_raw_size)
11767 && ((insn & 0xffff0000) == 0x10000000 /* beq $0,$0 */
11768 || (insn & 0xffff0000) == 0x04010000 /* bgez $0 */
11769 || (insn & 0xffff0000) == 0x04110000)) /* bgezal $0 */
11771 /* The branch offset is too large. If this is an
11772 unconditional branch, and we are not generating PIC code,
11773 we can convert it to an absolute jump instruction. */
11774 if ((insn & 0xffff0000) == 0x04110000) /* bgezal $0 */
11775 insn = 0x0c000000; /* jal */
11777 insn = 0x08000000; /* j */
11778 fixP->fx_r_type = BFD_RELOC_MIPS_JMP;
11780 fixP->fx_addsy = section_symbol (text_section);
11781 *valP += md_pcrel_from (fixP);
11782 md_number_to_chars ((char *) buf, (valueT) insn, 4);
11786 /* If we got here, we have branch-relaxation disabled,
11787 and there's nothing we can do to fix this instruction
11788 without turning it into a longer sequence. */
11789 as_bad_where (fixP->fx_file, fixP->fx_line,
11790 _("Branch out of range"));
11794 case BFD_RELOC_VTABLE_INHERIT:
11797 && !S_IS_DEFINED (fixP->fx_addsy)
11798 && !S_IS_WEAK (fixP->fx_addsy))
11799 S_SET_WEAK (fixP->fx_addsy);
11802 case BFD_RELOC_VTABLE_ENTRY:
11810 /* Remember value for tc_gen_reloc. */
11811 fixP->fx_addnumber = *valP;
11819 const struct mips_opcode *p;
11820 int treg, sreg, dreg, shamt;
11825 for (i = 0; i < NUMOPCODES; ++i)
11827 p = &mips_opcodes[i];
11828 if (((oc & p->mask) == p->match) && (p->pinfo != INSN_MACRO))
11830 printf ("%08lx %s\t", oc, p->name);
11831 treg = (oc >> 16) & 0x1f;
11832 sreg = (oc >> 21) & 0x1f;
11833 dreg = (oc >> 11) & 0x1f;
11834 shamt = (oc >> 6) & 0x1f;
11836 for (args = p->args;; ++args)
11847 printf ("%c", *args);
11851 assert (treg == sreg);
11852 printf ("$%d,$%d", treg, sreg);
11857 printf ("$%d", dreg);
11862 printf ("$%d", treg);
11866 printf ("0x%x", treg);
11871 printf ("$%d", sreg);
11875 printf ("0x%08lx", oc & 0x1ffffff);
11882 printf ("%d", imm);
11887 printf ("$%d", shamt);
11898 printf (_("%08lx UNDEFINED\n"), oc);
11909 name = input_line_pointer;
11910 c = get_symbol_end ();
11911 p = (symbolS *) symbol_find_or_make (name);
11912 *input_line_pointer = c;
11916 /* Align the current frag to a given power of two. The MIPS assembler
11917 also automatically adjusts any preceding label. */
11920 mips_align (to, fill, label)
11925 mips_emit_delays (FALSE);
11926 frag_align (to, fill, 0);
11927 record_alignment (now_seg, to);
11930 assert (S_GET_SEGMENT (label) == now_seg);
11931 symbol_set_frag (label, frag_now);
11932 S_SET_VALUE (label, (valueT) frag_now_fix ());
11936 /* Align to a given power of two. .align 0 turns off the automatic
11937 alignment used by the data creating pseudo-ops. */
11941 int x ATTRIBUTE_UNUSED;
11944 register long temp_fill;
11945 long max_alignment = 15;
11949 o Note that the assembler pulls down any immediately preceeding label
11950 to the aligned address.
11951 o It's not documented but auto alignment is reinstated by
11952 a .align pseudo instruction.
11953 o Note also that after auto alignment is turned off the mips assembler
11954 issues an error on attempt to assemble an improperly aligned data item.
11959 temp = get_absolute_expression ();
11960 if (temp > max_alignment)
11961 as_bad (_("Alignment too large: %d. assumed."), temp = max_alignment);
11964 as_warn (_("Alignment negative: 0 assumed."));
11967 if (*input_line_pointer == ',')
11969 ++input_line_pointer;
11970 temp_fill = get_absolute_expression ();
11977 mips_align (temp, (int) temp_fill,
11978 insn_labels != NULL ? insn_labels->label : NULL);
11985 demand_empty_rest_of_line ();
11989 mips_flush_pending_output ()
11991 mips_emit_delays (FALSE);
11992 mips_clear_insn_labels ();
12001 /* When generating embedded PIC code, we only use the .text, .lit8,
12002 .sdata and .sbss sections. We change the .data and .rdata
12003 pseudo-ops to use .sdata. */
12004 if (mips_pic == EMBEDDED_PIC
12005 && (sec == 'd' || sec == 'r'))
12009 /* The ELF backend needs to know that we are changing sections, so
12010 that .previous works correctly. We could do something like check
12011 for an obj_section_change_hook macro, but that might be confusing
12012 as it would not be appropriate to use it in the section changing
12013 functions in read.c, since obj-elf.c intercepts those. FIXME:
12014 This should be cleaner, somehow. */
12015 obj_elf_section_change_hook ();
12018 mips_emit_delays (FALSE);
12028 subseg_set (bss_section, (subsegT) get_absolute_expression ());
12029 demand_empty_rest_of_line ();
12033 if (USE_GLOBAL_POINTER_OPT)
12035 seg = subseg_new (RDATA_SECTION_NAME,
12036 (subsegT) get_absolute_expression ());
12037 if (OUTPUT_FLAVOR == bfd_target_elf_flavour)
12039 bfd_set_section_flags (stdoutput, seg,
12045 if (strcmp (TARGET_OS, "elf") != 0)
12046 record_alignment (seg, 4);
12048 demand_empty_rest_of_line ();
12052 as_bad (_("No read only data section in this object file format"));
12053 demand_empty_rest_of_line ();
12059 if (USE_GLOBAL_POINTER_OPT)
12061 seg = subseg_new (".sdata", (subsegT) get_absolute_expression ());
12062 if (OUTPUT_FLAVOR == bfd_target_elf_flavour)
12064 bfd_set_section_flags (stdoutput, seg,
12065 SEC_ALLOC | SEC_LOAD | SEC_RELOC
12067 if (strcmp (TARGET_OS, "elf") != 0)
12068 record_alignment (seg, 4);
12070 demand_empty_rest_of_line ();
12075 as_bad (_("Global pointers not supported; recompile -G 0"));
12076 demand_empty_rest_of_line ();
12085 s_change_section (ignore)
12086 int ignore ATTRIBUTE_UNUSED;
12089 char *section_name;
12094 int section_entry_size;
12095 int section_alignment;
12097 if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
12100 section_name = input_line_pointer;
12101 c = get_symbol_end ();
12103 next_c = *(input_line_pointer + 1);
12105 /* Do we have .section Name<,"flags">? */
12106 if (c != ',' || (c == ',' && next_c == '"'))
12108 /* just after name is now '\0'. */
12109 *input_line_pointer = c;
12110 input_line_pointer = section_name;
12111 obj_elf_section (ignore);
12114 input_line_pointer++;
12116 /* Do we have .section Name<,type><,flag><,entry_size><,alignment> */
12118 section_type = get_absolute_expression ();
12121 if (*input_line_pointer++ == ',')
12122 section_flag = get_absolute_expression ();
12125 if (*input_line_pointer++ == ',')
12126 section_entry_size = get_absolute_expression ();
12128 section_entry_size = 0;
12129 if (*input_line_pointer++ == ',')
12130 section_alignment = get_absolute_expression ();
12132 section_alignment = 0;
12134 section_name = xstrdup (section_name);
12136 obj_elf_change_section (section_name, section_type, section_flag,
12137 section_entry_size, 0, 0, 0);
12139 if (now_seg->name != section_name)
12140 free (section_name);
12141 #endif /* OBJ_ELF */
12145 mips_enable_auto_align ()
12156 label = insn_labels != NULL ? insn_labels->label : NULL;
12157 mips_emit_delays (FALSE);
12158 if (log_size > 0 && auto_align)
12159 mips_align (log_size, 0, label);
12160 mips_clear_insn_labels ();
12161 cons (1 << log_size);
12165 s_float_cons (type)
12170 label = insn_labels != NULL ? insn_labels->label : NULL;
12172 mips_emit_delays (FALSE);
12177 mips_align (3, 0, label);
12179 mips_align (2, 0, label);
12182 mips_clear_insn_labels ();
12187 /* Handle .globl. We need to override it because on Irix 5 you are
12190 where foo is an undefined symbol, to mean that foo should be
12191 considered to be the address of a function. */
12195 int x ATTRIBUTE_UNUSED;
12202 name = input_line_pointer;
12203 c = get_symbol_end ();
12204 symbolP = symbol_find_or_make (name);
12205 *input_line_pointer = c;
12206 SKIP_WHITESPACE ();
12208 /* On Irix 5, every global symbol that is not explicitly labelled as
12209 being a function is apparently labelled as being an object. */
12212 if (! is_end_of_line[(unsigned char) *input_line_pointer])
12217 secname = input_line_pointer;
12218 c = get_symbol_end ();
12219 sec = bfd_get_section_by_name (stdoutput, secname);
12221 as_bad (_("%s: no such section"), secname);
12222 *input_line_pointer = c;
12224 if (sec != NULL && (sec->flags & SEC_CODE) != 0)
12225 flag = BSF_FUNCTION;
12228 symbol_get_bfdsym (symbolP)->flags |= flag;
12230 S_SET_EXTERNAL (symbolP);
12231 demand_empty_rest_of_line ();
12236 int x ATTRIBUTE_UNUSED;
12241 opt = input_line_pointer;
12242 c = get_symbol_end ();
12246 /* FIXME: What does this mean? */
12248 else if (strncmp (opt, "pic", 3) == 0)
12252 i = atoi (opt + 3);
12257 mips_pic = SVR4_PIC;
12258 mips_abicalls = TRUE;
12261 as_bad (_(".option pic%d not supported"), i);
12263 if (USE_GLOBAL_POINTER_OPT && mips_pic == SVR4_PIC)
12265 if (g_switch_seen && g_switch_value != 0)
12266 as_warn (_("-G may not be used with SVR4 PIC code"));
12267 g_switch_value = 0;
12268 bfd_set_gp_size (stdoutput, 0);
12272 as_warn (_("Unrecognized option \"%s\""), opt);
12274 *input_line_pointer = c;
12275 demand_empty_rest_of_line ();
12278 /* This structure is used to hold a stack of .set values. */
12280 struct mips_option_stack
12282 struct mips_option_stack *next;
12283 struct mips_set_options options;
12286 static struct mips_option_stack *mips_opts_stack;
12288 /* Handle the .set pseudo-op. */
12292 int x ATTRIBUTE_UNUSED;
12294 char *name = input_line_pointer, ch;
12296 while (!is_end_of_line[(unsigned char) *input_line_pointer])
12297 ++input_line_pointer;
12298 ch = *input_line_pointer;
12299 *input_line_pointer = '\0';
12301 if (strcmp (name, "reorder") == 0)
12303 if (mips_opts.noreorder && prev_nop_frag != NULL)
12305 /* If we still have pending nops, we can discard them. The
12306 usual nop handling will insert any that are still
12308 prev_nop_frag->fr_fix -= (prev_nop_frag_holds
12309 * (mips_opts.mips16 ? 2 : 4));
12310 prev_nop_frag = NULL;
12312 mips_opts.noreorder = 0;
12314 else if (strcmp (name, "noreorder") == 0)
12316 mips_emit_delays (TRUE);
12317 mips_opts.noreorder = 1;
12318 mips_any_noreorder = 1;
12320 else if (strcmp (name, "at") == 0)
12322 mips_opts.noat = 0;
12324 else if (strcmp (name, "noat") == 0)
12326 mips_opts.noat = 1;
12328 else if (strcmp (name, "macro") == 0)
12330 mips_opts.warn_about_macros = 0;
12332 else if (strcmp (name, "nomacro") == 0)
12334 if (mips_opts.noreorder == 0)
12335 as_bad (_("`noreorder' must be set before `nomacro'"));
12336 mips_opts.warn_about_macros = 1;
12338 else if (strcmp (name, "move") == 0 || strcmp (name, "novolatile") == 0)
12340 mips_opts.nomove = 0;
12342 else if (strcmp (name, "nomove") == 0 || strcmp (name, "volatile") == 0)
12344 mips_opts.nomove = 1;
12346 else if (strcmp (name, "bopt") == 0)
12348 mips_opts.nobopt = 0;
12350 else if (strcmp (name, "nobopt") == 0)
12352 mips_opts.nobopt = 1;
12354 else if (strcmp (name, "mips16") == 0
12355 || strcmp (name, "MIPS-16") == 0)
12356 mips_opts.mips16 = 1;
12357 else if (strcmp (name, "nomips16") == 0
12358 || strcmp (name, "noMIPS-16") == 0)
12359 mips_opts.mips16 = 0;
12360 else if (strcmp (name, "mips3d") == 0)
12361 mips_opts.ase_mips3d = 1;
12362 else if (strcmp (name, "nomips3d") == 0)
12363 mips_opts.ase_mips3d = 0;
12364 else if (strcmp (name, "mdmx") == 0)
12365 mips_opts.ase_mdmx = 1;
12366 else if (strcmp (name, "nomdmx") == 0)
12367 mips_opts.ase_mdmx = 0;
12368 else if (strncmp (name, "mips", 4) == 0)
12372 /* Permit the user to change the ISA on the fly. Needless to
12373 say, misuse can cause serious problems. */
12374 if (strcmp (name, "mips0") == 0)
12377 mips_opts.isa = file_mips_isa;
12379 else if (strcmp (name, "mips1") == 0)
12380 mips_opts.isa = ISA_MIPS1;
12381 else if (strcmp (name, "mips2") == 0)
12382 mips_opts.isa = ISA_MIPS2;
12383 else if (strcmp (name, "mips3") == 0)
12384 mips_opts.isa = ISA_MIPS3;
12385 else if (strcmp (name, "mips4") == 0)
12386 mips_opts.isa = ISA_MIPS4;
12387 else if (strcmp (name, "mips5") == 0)
12388 mips_opts.isa = ISA_MIPS5;
12389 else if (strcmp (name, "mips32") == 0)
12390 mips_opts.isa = ISA_MIPS32;
12391 else if (strcmp (name, "mips32r2") == 0)
12392 mips_opts.isa = ISA_MIPS32R2;
12393 else if (strcmp (name, "mips64") == 0)
12394 mips_opts.isa = ISA_MIPS64;
12396 as_bad (_("unknown ISA level %s"), name + 4);
12398 switch (mips_opts.isa)
12406 mips_opts.gp32 = 1;
12407 mips_opts.fp32 = 1;
12413 mips_opts.gp32 = 0;
12414 mips_opts.fp32 = 0;
12417 as_bad (_("unknown ISA level %s"), name + 4);
12422 mips_opts.gp32 = file_mips_gp32;
12423 mips_opts.fp32 = file_mips_fp32;
12426 else if (strcmp (name, "autoextend") == 0)
12427 mips_opts.noautoextend = 0;
12428 else if (strcmp (name, "noautoextend") == 0)
12429 mips_opts.noautoextend = 1;
12430 else if (strcmp (name, "push") == 0)
12432 struct mips_option_stack *s;
12434 s = (struct mips_option_stack *) xmalloc (sizeof *s);
12435 s->next = mips_opts_stack;
12436 s->options = mips_opts;
12437 mips_opts_stack = s;
12439 else if (strcmp (name, "pop") == 0)
12441 struct mips_option_stack *s;
12443 s = mips_opts_stack;
12445 as_bad (_(".set pop with no .set push"));
12448 /* If we're changing the reorder mode we need to handle
12449 delay slots correctly. */
12450 if (s->options.noreorder && ! mips_opts.noreorder)
12451 mips_emit_delays (TRUE);
12452 else if (! s->options.noreorder && mips_opts.noreorder)
12454 if (prev_nop_frag != NULL)
12456 prev_nop_frag->fr_fix -= (prev_nop_frag_holds
12457 * (mips_opts.mips16 ? 2 : 4));
12458 prev_nop_frag = NULL;
12462 mips_opts = s->options;
12463 mips_opts_stack = s->next;
12469 as_warn (_("Tried to set unrecognized symbol: %s\n"), name);
12471 *input_line_pointer = ch;
12472 demand_empty_rest_of_line ();
12475 /* Handle the .abicalls pseudo-op. I believe this is equivalent to
12476 .option pic2. It means to generate SVR4 PIC calls. */
12479 s_abicalls (ignore)
12480 int ignore ATTRIBUTE_UNUSED;
12482 mips_pic = SVR4_PIC;
12483 mips_abicalls = TRUE;
12484 if (USE_GLOBAL_POINTER_OPT)
12486 if (g_switch_seen && g_switch_value != 0)
12487 as_warn (_("-G may not be used with SVR4 PIC code"));
12488 g_switch_value = 0;
12490 bfd_set_gp_size (stdoutput, 0);
12491 demand_empty_rest_of_line ();
12494 /* Handle the .cpload pseudo-op. This is used when generating SVR4
12495 PIC code. It sets the $gp register for the function based on the
12496 function address, which is in the register named in the argument.
12497 This uses a relocation against _gp_disp, which is handled specially
12498 by the linker. The result is:
12499 lui $gp,%hi(_gp_disp)
12500 addiu $gp,$gp,%lo(_gp_disp)
12501 addu $gp,$gp,.cpload argument
12502 The .cpload argument is normally $25 == $t9. */
12506 int ignore ATTRIBUTE_UNUSED;
12511 /* If we are not generating SVR4 PIC code, or if this is NewABI code,
12512 .cpload is ignored. */
12513 if (mips_pic != SVR4_PIC || HAVE_NEWABI)
12519 /* .cpload should be in a .set noreorder section. */
12520 if (mips_opts.noreorder == 0)
12521 as_warn (_(".cpload not in noreorder section"));
12523 ex.X_op = O_symbol;
12524 ex.X_add_symbol = symbol_find_or_make ("_gp_disp");
12525 ex.X_op_symbol = NULL;
12526 ex.X_add_number = 0;
12528 /* In ELF, this symbol is implicitly an STT_OBJECT symbol. */
12529 symbol_get_bfdsym (ex.X_add_symbol)->flags |= BSF_OBJECT;
12531 macro_build_lui (NULL, &icnt, &ex, mips_gp_register);
12532 macro_build ((char *) NULL, &icnt, &ex, "addiu", "t,r,j",
12533 mips_gp_register, mips_gp_register, (int) BFD_RELOC_LO16);
12535 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "addu", "d,v,t",
12536 mips_gp_register, mips_gp_register, tc_get_register (0));
12538 demand_empty_rest_of_line ();
12541 /* Handle the .cpsetup pseudo-op defined for NewABI PIC code. The syntax is:
12542 .cpsetup $reg1, offset|$reg2, label
12544 If offset is given, this results in:
12545 sd $gp, offset($sp)
12546 lui $gp, %hi(%neg(%gp_rel(label)))
12547 addiu $gp, $gp, %lo(%neg(%gp_rel(label)))
12548 daddu $gp, $gp, $reg1
12550 If $reg2 is given, this results in:
12551 daddu $reg2, $gp, $0
12552 lui $gp, %hi(%neg(%gp_rel(label)))
12553 addiu $gp, $gp, %lo(%neg(%gp_rel(label)))
12554 daddu $gp, $gp, $reg1
12555 $reg1 is normally $25 == $t9. */
12558 int ignore ATTRIBUTE_UNUSED;
12560 expressionS ex_off;
12561 expressionS ex_sym;
12566 /* If we are not generating SVR4 PIC code, .cpsetup is ignored.
12567 We also need NewABI support. */
12568 if (mips_pic != SVR4_PIC || ! HAVE_NEWABI)
12574 reg1 = tc_get_register (0);
12575 SKIP_WHITESPACE ();
12576 if (*input_line_pointer != ',')
12578 as_bad (_("missing argument separator ',' for .cpsetup"));
12582 ++input_line_pointer;
12583 SKIP_WHITESPACE ();
12584 if (*input_line_pointer == '$')
12586 mips_cpreturn_register = tc_get_register (0);
12587 mips_cpreturn_offset = -1;
12591 mips_cpreturn_offset = get_absolute_expression ();
12592 mips_cpreturn_register = -1;
12594 SKIP_WHITESPACE ();
12595 if (*input_line_pointer != ',')
12597 as_bad (_("missing argument separator ',' for .cpsetup"));
12601 ++input_line_pointer;
12602 SKIP_WHITESPACE ();
12603 expression (&ex_sym);
12605 if (mips_cpreturn_register == -1)
12607 ex_off.X_op = O_constant;
12608 ex_off.X_add_symbol = NULL;
12609 ex_off.X_op_symbol = NULL;
12610 ex_off.X_add_number = mips_cpreturn_offset;
12612 macro_build ((char *) NULL, &icnt, &ex_off, "sd", "t,o(b)",
12613 mips_gp_register, (int) BFD_RELOC_LO16, SP);
12616 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "daddu",
12617 "d,v,t", mips_cpreturn_register, mips_gp_register, 0);
12619 /* Ensure there's room for the next two instructions, so that `f'
12620 doesn't end up with an address in the wrong frag. */
12623 macro_build ((char *) NULL, &icnt, &ex_sym, "lui", "t,u", mips_gp_register,
12624 (int) BFD_RELOC_GPREL16);
12625 fix_new (frag_now, f - frag_now->fr_literal,
12626 8, NULL, 0, 0, BFD_RELOC_MIPS_SUB);
12627 fix_new (frag_now, f - frag_now->fr_literal,
12628 4, NULL, 0, 0, BFD_RELOC_HI16_S);
12631 macro_build ((char *) NULL, &icnt, &ex_sym, "addiu", "t,r,j",
12632 mips_gp_register, mips_gp_register, (int) BFD_RELOC_GPREL16);
12633 fix_new (frag_now, f - frag_now->fr_literal,
12634 8, NULL, 0, 0, BFD_RELOC_MIPS_SUB);
12635 fix_new (frag_now, f - frag_now->fr_literal,
12636 4, NULL, 0, 0, BFD_RELOC_LO16);
12638 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, ADDRESS_ADD_INSN,
12639 "d,v,t", mips_gp_register, mips_gp_register, reg1);
12641 demand_empty_rest_of_line ();
12646 int ignore ATTRIBUTE_UNUSED;
12648 /* If we are not generating SVR4 PIC code, or if this is not NewABI code,
12649 .cplocal is ignored. */
12650 if (mips_pic != SVR4_PIC || ! HAVE_NEWABI)
12656 mips_gp_register = tc_get_register (0);
12657 demand_empty_rest_of_line ();
12660 /* Handle the .cprestore pseudo-op. This stores $gp into a given
12661 offset from $sp. The offset is remembered, and after making a PIC
12662 call $gp is restored from that location. */
12665 s_cprestore (ignore)
12666 int ignore ATTRIBUTE_UNUSED;
12671 /* If we are not generating SVR4 PIC code, or if this is NewABI code,
12672 .cprestore is ignored. */
12673 if (mips_pic != SVR4_PIC || HAVE_NEWABI)
12679 mips_cprestore_offset = get_absolute_expression ();
12680 mips_cprestore_valid = 1;
12682 ex.X_op = O_constant;
12683 ex.X_add_symbol = NULL;
12684 ex.X_op_symbol = NULL;
12685 ex.X_add_number = mips_cprestore_offset;
12687 macro_build_ldst_constoffset ((char *) NULL, &icnt, &ex, ADDRESS_STORE_INSN,
12688 mips_gp_register, SP);
12690 demand_empty_rest_of_line ();
12693 /* Handle the .cpreturn pseudo-op defined for NewABI PIC code. If an offset
12694 was given in the preceeding .gpsetup, it results in:
12695 ld $gp, offset($sp)
12697 If a register $reg2 was given there, it results in:
12698 daddiu $gp, $gp, $reg2
12701 s_cpreturn (ignore)
12702 int ignore ATTRIBUTE_UNUSED;
12707 /* If we are not generating SVR4 PIC code, .cpreturn is ignored.
12708 We also need NewABI support. */
12709 if (mips_pic != SVR4_PIC || ! HAVE_NEWABI)
12715 if (mips_cpreturn_register == -1)
12717 ex.X_op = O_constant;
12718 ex.X_add_symbol = NULL;
12719 ex.X_op_symbol = NULL;
12720 ex.X_add_number = mips_cpreturn_offset;
12722 macro_build ((char *) NULL, &icnt, &ex, "ld", "t,o(b)",
12723 mips_gp_register, (int) BFD_RELOC_LO16, SP);
12726 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, "daddu",
12727 "d,v,t", mips_gp_register, mips_cpreturn_register, 0);
12729 demand_empty_rest_of_line ();
12732 /* Handle the .gpvalue pseudo-op. This is used when generating NewABI PIC
12733 code. It sets the offset to use in gp_rel relocations. */
12737 int ignore ATTRIBUTE_UNUSED;
12739 /* If we are not generating SVR4 PIC code, .gpvalue is ignored.
12740 We also need NewABI support. */
12741 if (mips_pic != SVR4_PIC || ! HAVE_NEWABI)
12747 mips_gprel_offset = get_absolute_expression ();
12749 demand_empty_rest_of_line ();
12752 /* Handle the .gpword pseudo-op. This is used when generating PIC
12753 code. It generates a 32 bit GP relative reloc. */
12757 int ignore ATTRIBUTE_UNUSED;
12763 /* When not generating PIC code, this is treated as .word. */
12764 if (mips_pic != SVR4_PIC)
12770 label = insn_labels != NULL ? insn_labels->label : NULL;
12771 mips_emit_delays (TRUE);
12773 mips_align (2, 0, label);
12774 mips_clear_insn_labels ();
12778 if (ex.X_op != O_symbol || ex.X_add_number != 0)
12780 as_bad (_("Unsupported use of .gpword"));
12781 ignore_rest_of_line ();
12785 md_number_to_chars (p, (valueT) 0, 4);
12786 fix_new_exp (frag_now, p - frag_now->fr_literal, 4, &ex, FALSE,
12787 BFD_RELOC_GPREL32);
12789 demand_empty_rest_of_line ();
12794 int ignore ATTRIBUTE_UNUSED;
12800 /* When not generating PIC code, this is treated as .dword. */
12801 if (mips_pic != SVR4_PIC)
12807 label = insn_labels != NULL ? insn_labels->label : NULL;
12808 mips_emit_delays (TRUE);
12810 mips_align (3, 0, label);
12811 mips_clear_insn_labels ();
12815 if (ex.X_op != O_symbol || ex.X_add_number != 0)
12817 as_bad (_("Unsupported use of .gpdword"));
12818 ignore_rest_of_line ();
12822 md_number_to_chars (p, (valueT) 0, 8);
12823 fix_new_exp (frag_now, p - frag_now->fr_literal, 4, &ex, FALSE,
12824 BFD_RELOC_GPREL32);
12826 /* GPREL32 composed with 64 gives a 64-bit GP offset. */
12827 ex.X_op = O_absent;
12828 ex.X_add_symbol = 0;
12829 ex.X_add_number = 0;
12830 fix_new_exp (frag_now, p - frag_now->fr_literal, 8, &ex, FALSE,
12833 demand_empty_rest_of_line ();
12836 /* Handle the .cpadd pseudo-op. This is used when dealing with switch
12837 tables in SVR4 PIC code. */
12841 int ignore ATTRIBUTE_UNUSED;
12846 /* This is ignored when not generating SVR4 PIC code. */
12847 if (mips_pic != SVR4_PIC)
12853 /* Add $gp to the register named as an argument. */
12854 reg = tc_get_register (0);
12855 macro_build ((char *) NULL, &icnt, (expressionS *) NULL, ADDRESS_ADD_INSN,
12856 "d,v,t", reg, reg, mips_gp_register);
12858 demand_empty_rest_of_line ();
12861 /* Handle the .insn pseudo-op. This marks instruction labels in
12862 mips16 mode. This permits the linker to handle them specially,
12863 such as generating jalx instructions when needed. We also make
12864 them odd for the duration of the assembly, in order to generate the
12865 right sort of code. We will make them even in the adjust_symtab
12866 routine, while leaving them marked. This is convenient for the
12867 debugger and the disassembler. The linker knows to make them odd
12872 int ignore ATTRIBUTE_UNUSED;
12874 mips16_mark_labels ();
12876 demand_empty_rest_of_line ();
12879 /* Handle a .stabn directive. We need these in order to mark a label
12880 as being a mips16 text label correctly. Sometimes the compiler
12881 will emit a label, followed by a .stabn, and then switch sections.
12882 If the label and .stabn are in mips16 mode, then the label is
12883 really a mips16 text label. */
12890 mips16_mark_labels ();
12895 /* Handle the .weakext pseudo-op as defined in Kane and Heinrich.
12899 s_mips_weakext (ignore)
12900 int ignore ATTRIBUTE_UNUSED;
12907 name = input_line_pointer;
12908 c = get_symbol_end ();
12909 symbolP = symbol_find_or_make (name);
12910 S_SET_WEAK (symbolP);
12911 *input_line_pointer = c;
12913 SKIP_WHITESPACE ();
12915 if (! is_end_of_line[(unsigned char) *input_line_pointer])
12917 if (S_IS_DEFINED (symbolP))
12919 as_bad ("ignoring attempt to redefine symbol %s",
12920 S_GET_NAME (symbolP));
12921 ignore_rest_of_line ();
12925 if (*input_line_pointer == ',')
12927 ++input_line_pointer;
12928 SKIP_WHITESPACE ();
12932 if (exp.X_op != O_symbol)
12934 as_bad ("bad .weakext directive");
12935 ignore_rest_of_line ();
12938 symbol_set_value_expression (symbolP, &exp);
12941 demand_empty_rest_of_line ();
12944 /* Parse a register string into a number. Called from the ECOFF code
12945 to parse .frame. The argument is non-zero if this is the frame
12946 register, so that we can record it in mips_frame_reg. */
12949 tc_get_register (frame)
12954 SKIP_WHITESPACE ();
12955 if (*input_line_pointer++ != '$')
12957 as_warn (_("expected `$'"));
12960 else if (ISDIGIT (*input_line_pointer))
12962 reg = get_absolute_expression ();
12963 if (reg < 0 || reg >= 32)
12965 as_warn (_("Bad register number"));
12971 if (strncmp (input_line_pointer, "ra", 2) == 0)
12974 input_line_pointer += 2;
12976 else if (strncmp (input_line_pointer, "fp", 2) == 0)
12979 input_line_pointer += 2;
12981 else if (strncmp (input_line_pointer, "sp", 2) == 0)
12984 input_line_pointer += 2;
12986 else if (strncmp (input_line_pointer, "gp", 2) == 0)
12989 input_line_pointer += 2;
12991 else if (strncmp (input_line_pointer, "at", 2) == 0)
12994 input_line_pointer += 2;
12996 else if (strncmp (input_line_pointer, "kt0", 3) == 0)
12999 input_line_pointer += 3;
13001 else if (strncmp (input_line_pointer, "kt1", 3) == 0)
13004 input_line_pointer += 3;
13006 else if (strncmp (input_line_pointer, "zero", 4) == 0)
13009 input_line_pointer += 4;
13013 as_warn (_("Unrecognized register name"));
13015 while (ISALNUM(*input_line_pointer))
13016 input_line_pointer++;
13021 mips_frame_reg = reg != 0 ? reg : SP;
13022 mips_frame_reg_valid = 1;
13023 mips_cprestore_valid = 0;
13029 md_section_align (seg, addr)
13033 int align = bfd_get_section_alignment (stdoutput, seg);
13036 /* We don't need to align ELF sections to the full alignment.
13037 However, Irix 5 may prefer that we align them at least to a 16
13038 byte boundary. We don't bother to align the sections if we are
13039 targeted for an embedded system. */
13040 if (strcmp (TARGET_OS, "elf") == 0)
13046 return ((addr + (1 << align) - 1) & (-1 << align));
13049 /* Utility routine, called from above as well. If called while the
13050 input file is still being read, it's only an approximation. (For
13051 example, a symbol may later become defined which appeared to be
13052 undefined earlier.) */
13055 nopic_need_relax (sym, before_relaxing)
13057 int before_relaxing;
13062 if (USE_GLOBAL_POINTER_OPT && g_switch_value > 0)
13064 const char *symname;
13067 /* Find out whether this symbol can be referenced off the $gp
13068 register. It can be if it is smaller than the -G size or if
13069 it is in the .sdata or .sbss section. Certain symbols can
13070 not be referenced off the $gp, although it appears as though
13072 symname = S_GET_NAME (sym);
13073 if (symname != (const char *) NULL
13074 && (strcmp (symname, "eprol") == 0
13075 || strcmp (symname, "etext") == 0
13076 || strcmp (symname, "_gp") == 0
13077 || strcmp (symname, "edata") == 0
13078 || strcmp (symname, "_fbss") == 0
13079 || strcmp (symname, "_fdata") == 0
13080 || strcmp (symname, "_ftext") == 0
13081 || strcmp (symname, "end") == 0
13082 || strcmp (symname, "_gp_disp") == 0))
13084 else if ((! S_IS_DEFINED (sym) || S_IS_COMMON (sym))
13086 #ifndef NO_ECOFF_DEBUGGING
13087 || (symbol_get_obj (sym)->ecoff_extern_size != 0
13088 && (symbol_get_obj (sym)->ecoff_extern_size
13089 <= g_switch_value))
13091 /* We must defer this decision until after the whole
13092 file has been read, since there might be a .extern
13093 after the first use of this symbol. */
13094 || (before_relaxing
13095 #ifndef NO_ECOFF_DEBUGGING
13096 && symbol_get_obj (sym)->ecoff_extern_size == 0
13098 && S_GET_VALUE (sym) == 0)
13099 || (S_GET_VALUE (sym) != 0
13100 && S_GET_VALUE (sym) <= g_switch_value)))
13104 const char *segname;
13106 segname = segment_name (S_GET_SEGMENT (sym));
13107 assert (strcmp (segname, ".lit8") != 0
13108 && strcmp (segname, ".lit4") != 0);
13109 change = (strcmp (segname, ".sdata") != 0
13110 && strcmp (segname, ".sbss") != 0
13111 && strncmp (segname, ".sdata.", 7) != 0
13112 && strncmp (segname, ".gnu.linkonce.s.", 16) != 0);
13117 /* We are not optimizing for the $gp register. */
13122 /* Return true if the given symbol should be considered local for SVR4 PIC. */
13125 pic_need_relax (sym, segtype)
13130 bfd_boolean linkonce;
13132 /* Handle the case of a symbol equated to another symbol. */
13133 while (symbol_equated_reloc_p (sym))
13137 /* It's possible to get a loop here in a badly written
13139 n = symbol_get_value_expression (sym)->X_add_symbol;
13145 symsec = S_GET_SEGMENT (sym);
13147 /* duplicate the test for LINK_ONCE sections as in adjust_reloc_syms */
13149 if (symsec != segtype && ! S_IS_LOCAL (sym))
13151 if ((bfd_get_section_flags (stdoutput, symsec) & SEC_LINK_ONCE)
13155 /* The GNU toolchain uses an extension for ELF: a section
13156 beginning with the magic string .gnu.linkonce is a linkonce
13158 if (strncmp (segment_name (symsec), ".gnu.linkonce",
13159 sizeof ".gnu.linkonce" - 1) == 0)
13163 /* This must duplicate the test in adjust_reloc_syms. */
13164 return (symsec != &bfd_und_section
13165 && symsec != &bfd_abs_section
13166 && ! bfd_is_com_section (symsec)
13169 /* A global or weak symbol is treated as external. */
13170 && (OUTPUT_FLAVOR != bfd_target_elf_flavour
13171 || (! S_IS_WEAK (sym)
13172 && (! S_IS_EXTERNAL (sym)
13173 || mips_pic == EMBEDDED_PIC)))
13179 /* Given a mips16 variant frag FRAGP, return non-zero if it needs an
13180 extended opcode. SEC is the section the frag is in. */
13183 mips16_extended_frag (fragp, sec, stretch)
13189 register const struct mips16_immed_operand *op;
13191 int mintiny, maxtiny;
13195 if (RELAX_MIPS16_USER_SMALL (fragp->fr_subtype))
13197 if (RELAX_MIPS16_USER_EXT (fragp->fr_subtype))
13200 type = RELAX_MIPS16_TYPE (fragp->fr_subtype);
13201 op = mips16_immed_operands;
13202 while (op->type != type)
13205 assert (op < mips16_immed_operands + MIPS16_NUM_IMMED);
13210 if (type == '<' || type == '>' || type == '[' || type == ']')
13213 maxtiny = 1 << op->nbits;
13218 maxtiny = (1 << op->nbits) - 1;
13223 mintiny = - (1 << (op->nbits - 1));
13224 maxtiny = (1 << (op->nbits - 1)) - 1;
13227 sym_frag = symbol_get_frag (fragp->fr_symbol);
13228 val = S_GET_VALUE (fragp->fr_symbol);
13229 symsec = S_GET_SEGMENT (fragp->fr_symbol);
13235 /* We won't have the section when we are called from
13236 mips_relax_frag. However, we will always have been called
13237 from md_estimate_size_before_relax first. If this is a
13238 branch to a different section, we mark it as such. If SEC is
13239 NULL, and the frag is not marked, then it must be a branch to
13240 the same section. */
13243 if (RELAX_MIPS16_LONG_BRANCH (fragp->fr_subtype))
13248 /* Must have been called from md_estimate_size_before_relax. */
13251 fragp->fr_subtype =
13252 RELAX_MIPS16_MARK_LONG_BRANCH (fragp->fr_subtype);
13254 /* FIXME: We should support this, and let the linker
13255 catch branches and loads that are out of range. */
13256 as_bad_where (fragp->fr_file, fragp->fr_line,
13257 _("unsupported PC relative reference to different section"));
13261 if (fragp != sym_frag && sym_frag->fr_address == 0)
13262 /* Assume non-extended on the first relaxation pass.
13263 The address we have calculated will be bogus if this is
13264 a forward branch to another frag, as the forward frag
13265 will have fr_address == 0. */
13269 /* In this case, we know for sure that the symbol fragment is in
13270 the same section. If the relax_marker of the symbol fragment
13271 differs from the relax_marker of this fragment, we have not
13272 yet adjusted the symbol fragment fr_address. We want to add
13273 in STRETCH in order to get a better estimate of the address.
13274 This particularly matters because of the shift bits. */
13276 && sym_frag->relax_marker != fragp->relax_marker)
13280 /* Adjust stretch for any alignment frag. Note that if have
13281 been expanding the earlier code, the symbol may be
13282 defined in what appears to be an earlier frag. FIXME:
13283 This doesn't handle the fr_subtype field, which specifies
13284 a maximum number of bytes to skip when doing an
13286 for (f = fragp; f != NULL && f != sym_frag; f = f->fr_next)
13288 if (f->fr_type == rs_align || f->fr_type == rs_align_code)
13291 stretch = - ((- stretch)
13292 & ~ ((1 << (int) f->fr_offset) - 1));
13294 stretch &= ~ ((1 << (int) f->fr_offset) - 1);
13303 addr = fragp->fr_address + fragp->fr_fix;
13305 /* The base address rules are complicated. The base address of
13306 a branch is the following instruction. The base address of a
13307 PC relative load or add is the instruction itself, but if it
13308 is in a delay slot (in which case it can not be extended) use
13309 the address of the instruction whose delay slot it is in. */
13310 if (type == 'p' || type == 'q')
13314 /* If we are currently assuming that this frag should be
13315 extended, then, the current address is two bytes
13317 if (RELAX_MIPS16_EXTENDED (fragp->fr_subtype))
13320 /* Ignore the low bit in the target, since it will be set
13321 for a text label. */
13322 if ((val & 1) != 0)
13325 else if (RELAX_MIPS16_JAL_DSLOT (fragp->fr_subtype))
13327 else if (RELAX_MIPS16_DSLOT (fragp->fr_subtype))
13330 val -= addr & ~ ((1 << op->shift) - 1);
13332 /* Branch offsets have an implicit 0 in the lowest bit. */
13333 if (type == 'p' || type == 'q')
13336 /* If any of the shifted bits are set, we must use an extended
13337 opcode. If the address depends on the size of this
13338 instruction, this can lead to a loop, so we arrange to always
13339 use an extended opcode. We only check this when we are in
13340 the main relaxation loop, when SEC is NULL. */
13341 if ((val & ((1 << op->shift) - 1)) != 0 && sec == NULL)
13343 fragp->fr_subtype =
13344 RELAX_MIPS16_MARK_LONG_BRANCH (fragp->fr_subtype);
13348 /* If we are about to mark a frag as extended because the value
13349 is precisely maxtiny + 1, then there is a chance of an
13350 infinite loop as in the following code:
13355 In this case when the la is extended, foo is 0x3fc bytes
13356 away, so the la can be shrunk, but then foo is 0x400 away, so
13357 the la must be extended. To avoid this loop, we mark the
13358 frag as extended if it was small, and is about to become
13359 extended with a value of maxtiny + 1. */
13360 if (val == ((maxtiny + 1) << op->shift)
13361 && ! RELAX_MIPS16_EXTENDED (fragp->fr_subtype)
13364 fragp->fr_subtype =
13365 RELAX_MIPS16_MARK_LONG_BRANCH (fragp->fr_subtype);
13369 else if (symsec != absolute_section && sec != NULL)
13370 as_bad_where (fragp->fr_file, fragp->fr_line, _("unsupported relocation"));
13372 if ((val & ((1 << op->shift) - 1)) != 0
13373 || val < (mintiny << op->shift)
13374 || val > (maxtiny << op->shift))
13380 /* Compute the length of a branch sequence, and adjust the
13381 RELAX_BRANCH_TOOFAR bit accordingly. If FRAGP is NULL, the
13382 worst-case length is computed, with UPDATE being used to indicate
13383 whether an unconditional (-1), branch-likely (+1) or regular (0)
13384 branch is to be computed. */
13386 relaxed_branch_length (fragp, sec, update)
13391 bfd_boolean toofar;
13395 && S_IS_DEFINED (fragp->fr_symbol)
13396 && sec == S_GET_SEGMENT (fragp->fr_symbol))
13401 val = S_GET_VALUE (fragp->fr_symbol) + fragp->fr_offset;
13403 addr = fragp->fr_address + fragp->fr_fix + 4;
13407 toofar = val < - (0x8000 << 2) || val >= (0x8000 << 2);
13410 /* If the symbol is not defined or it's in a different segment,
13411 assume the user knows what's going on and emit a short
13417 if (fragp && update && toofar != RELAX_BRANCH_TOOFAR (fragp->fr_subtype))
13419 = RELAX_BRANCH_ENCODE (RELAX_BRANCH_UNCOND (fragp->fr_subtype),
13420 RELAX_BRANCH_LIKELY (fragp->fr_subtype),
13421 RELAX_BRANCH_LINK (fragp->fr_subtype),
13427 if (fragp ? RELAX_BRANCH_LIKELY (fragp->fr_subtype) : (update > 0))
13430 if (mips_pic != NO_PIC)
13432 /* Additional space for PIC loading of target address. */
13434 if (mips_opts.isa == ISA_MIPS1)
13435 /* Additional space for $at-stabilizing nop. */
13439 /* If branch is conditional. */
13440 if (fragp ? !RELAX_BRANCH_UNCOND (fragp->fr_subtype) : (update >= 0))
13447 /* Estimate the size of a frag before relaxing. Unless this is the
13448 mips16, we are not really relaxing here, and the final size is
13449 encoded in the subtype information. For the mips16, we have to
13450 decide whether we are using an extended opcode or not. */
13453 md_estimate_size_before_relax (fragp, segtype)
13459 if (RELAX_BRANCH_P (fragp->fr_subtype))
13462 fragp->fr_var = relaxed_branch_length (fragp, segtype, FALSE);
13464 return fragp->fr_var;
13467 if (RELAX_MIPS16_P (fragp->fr_subtype))
13468 /* We don't want to modify the EXTENDED bit here; it might get us
13469 into infinite loops. We change it only in mips_relax_frag(). */
13470 return (RELAX_MIPS16_EXTENDED (fragp->fr_subtype) ? 4 : 2);
13472 if (mips_pic == NO_PIC)
13473 change = nopic_need_relax (fragp->fr_symbol, 0);
13474 else if (mips_pic == SVR4_PIC)
13475 change = pic_need_relax (fragp->fr_symbol, segtype);
13481 /* Record the offset to the first reloc in the fr_opcode field.
13482 This lets md_convert_frag and tc_gen_reloc know that the code
13483 must be expanded. */
13484 fragp->fr_opcode = (fragp->fr_literal
13486 - RELAX_OLD (fragp->fr_subtype)
13487 + RELAX_RELOC1 (fragp->fr_subtype));
13488 /* FIXME: This really needs as_warn_where. */
13489 if (RELAX_WARN (fragp->fr_subtype))
13490 as_warn (_("AT used after \".set noat\" or macro used after "
13491 "\".set nomacro\""));
13493 return RELAX_NEW (fragp->fr_subtype) - RELAX_OLD (fragp->fr_subtype);
13499 /* This is called to see whether a reloc against a defined symbol
13500 should be converted into a reloc against a section. Don't adjust
13501 MIPS16 jump relocations, so we don't have to worry about the format
13502 of the offset in the .o file. Don't adjust relocations against
13503 mips16 symbols, so that the linker can find them if it needs to set
13507 mips_fix_adjustable (fixp)
13510 if (fixp->fx_r_type == BFD_RELOC_MIPS16_JMP)
13513 if (fixp->fx_r_type == BFD_RELOC_VTABLE_INHERIT
13514 || fixp->fx_r_type == BFD_RELOC_VTABLE_ENTRY)
13517 if (fixp->fx_addsy == NULL)
13521 if (OUTPUT_FLAVOR == bfd_target_elf_flavour
13522 && S_GET_OTHER (fixp->fx_addsy) == STO_MIPS16
13523 && fixp->fx_subsy == NULL)
13530 /* Translate internal representation of relocation info to BFD target
13534 tc_gen_reloc (section, fixp)
13535 asection *section ATTRIBUTE_UNUSED;
13538 static arelent *retval[4];
13540 bfd_reloc_code_real_type code;
13542 memset (retval, 0, sizeof(retval));
13543 reloc = retval[0] = (arelent *) xcalloc (1, sizeof (arelent));
13544 reloc->sym_ptr_ptr = (asymbol **) xmalloc (sizeof (asymbol *));
13545 *reloc->sym_ptr_ptr = symbol_get_bfdsym (fixp->fx_addsy);
13546 reloc->address = fixp->fx_frag->fr_address + fixp->fx_where;
13548 if (mips_pic == EMBEDDED_PIC
13549 && SWITCH_TABLE (fixp))
13551 /* For a switch table entry we use a special reloc. The addend
13552 is actually the difference between the reloc address and the
13554 reloc->addend = reloc->address - S_GET_VALUE (fixp->fx_subsy);
13555 if (OUTPUT_FLAVOR != bfd_target_ecoff_flavour)
13556 as_fatal (_("Double check fx_r_type in tc-mips.c:tc_gen_reloc"));
13557 fixp->fx_r_type = BFD_RELOC_GPREL32;
13559 else if (fixp->fx_r_type == BFD_RELOC_PCREL_LO16)
13561 if (OUTPUT_FLAVOR == bfd_target_elf_flavour)
13562 reloc->addend = fixp->fx_addnumber;
13565 /* We use a special addend for an internal RELLO reloc. */
13566 if (symbol_section_p (fixp->fx_addsy))
13567 reloc->addend = reloc->address - S_GET_VALUE (fixp->fx_subsy);
13569 reloc->addend = fixp->fx_addnumber + reloc->address;
13572 else if (fixp->fx_r_type == BFD_RELOC_PCREL_HI16_S)
13574 assert (fixp->fx_next != NULL
13575 && fixp->fx_next->fx_r_type == BFD_RELOC_PCREL_LO16);
13577 /* The reloc is relative to the RELLO; adjust the addend
13579 if (OUTPUT_FLAVOR == bfd_target_elf_flavour)
13580 reloc->addend = fixp->fx_next->fx_addnumber;
13583 /* We use a special addend for an internal RELHI reloc. */
13584 if (symbol_section_p (fixp->fx_addsy))
13585 reloc->addend = (fixp->fx_next->fx_frag->fr_address
13586 + fixp->fx_next->fx_where
13587 - S_GET_VALUE (fixp->fx_subsy));
13589 reloc->addend = (fixp->fx_addnumber
13590 + fixp->fx_next->fx_frag->fr_address
13591 + fixp->fx_next->fx_where);
13594 else if (fixp->fx_pcrel == 0 || OUTPUT_FLAVOR == bfd_target_elf_flavour)
13595 reloc->addend = fixp->fx_addnumber;
13598 if (OUTPUT_FLAVOR != bfd_target_aout_flavour)
13599 /* A gruesome hack which is a result of the gruesome gas reloc
13601 reloc->addend = reloc->address;
13603 reloc->addend = -reloc->address;
13606 /* If this is a variant frag, we may need to adjust the existing
13607 reloc and generate a new one. */
13608 if (fixp->fx_frag->fr_opcode != NULL
13609 && ((fixp->fx_r_type == BFD_RELOC_GPREL16
13611 || (fixp->fx_r_type == BFD_RELOC_MIPS_GOT_DISP
13613 || fixp->fx_r_type == BFD_RELOC_MIPS_GOT16
13614 || fixp->fx_r_type == BFD_RELOC_MIPS_CALL16
13615 || fixp->fx_r_type == BFD_RELOC_MIPS_GOT_HI16
13616 || fixp->fx_r_type == BFD_RELOC_MIPS_GOT_LO16
13617 || fixp->fx_r_type == BFD_RELOC_MIPS_CALL_HI16
13618 || fixp->fx_r_type == BFD_RELOC_MIPS_CALL_LO16)
13623 assert (! RELAX_MIPS16_P (fixp->fx_frag->fr_subtype));
13625 /* If this is not the last reloc in this frag, then we have two
13626 GPREL relocs, or a GOT_HI16/GOT_LO16 pair, or a
13627 CALL_HI16/CALL_LO16, both of which are being replaced. Let
13628 the second one handle all of them. */
13629 if (fixp->fx_next != NULL
13630 && fixp->fx_frag == fixp->fx_next->fx_frag)
13632 assert ((fixp->fx_r_type == BFD_RELOC_GPREL16
13633 && fixp->fx_next->fx_r_type == BFD_RELOC_GPREL16)
13634 || (fixp->fx_r_type == BFD_RELOC_MIPS_GOT_HI16
13635 && (fixp->fx_next->fx_r_type
13636 == BFD_RELOC_MIPS_GOT_LO16))
13637 || (fixp->fx_r_type == BFD_RELOC_MIPS_CALL_HI16
13638 && (fixp->fx_next->fx_r_type
13639 == BFD_RELOC_MIPS_CALL_LO16)));
13644 fixp->fx_where = fixp->fx_frag->fr_opcode - fixp->fx_frag->fr_literal;
13645 reloc->address = fixp->fx_frag->fr_address + fixp->fx_where;
13646 reloc->addend += fixp->fx_frag->tc_frag_data.tc_fr_offset;
13647 reloc2 = retval[1] = (arelent *) xmalloc (sizeof (arelent));
13648 reloc2->sym_ptr_ptr = (asymbol **) xmalloc (sizeof (asymbol *));
13649 *reloc2->sym_ptr_ptr = symbol_get_bfdsym (fixp->fx_addsy);
13650 reloc2->address = (reloc->address
13651 + (RELAX_RELOC2 (fixp->fx_frag->fr_subtype)
13652 - RELAX_RELOC1 (fixp->fx_frag->fr_subtype)));
13653 reloc2->addend = fixp->fx_addnumber - S_GET_VALUE (fixp->fx_addsy)
13654 + fixp->fx_frag->tc_frag_data.tc_fr_offset;
13655 reloc2->howto = bfd_reloc_type_lookup (stdoutput, BFD_RELOC_LO16);
13656 assert (reloc2->howto != NULL);
13658 if (RELAX_RELOC3 (fixp->fx_frag->fr_subtype))
13662 reloc3 = retval[2] = (arelent *) xmalloc (sizeof (arelent));
13664 reloc3->address += 4;
13667 if (mips_pic == NO_PIC)
13669 assert (fixp->fx_r_type == BFD_RELOC_GPREL16);
13670 fixp->fx_r_type = BFD_RELOC_HI16_S;
13672 else if (mips_pic == SVR4_PIC)
13674 switch (fixp->fx_r_type)
13678 case BFD_RELOC_MIPS_GOT16:
13680 case BFD_RELOC_MIPS_GOT_LO16:
13681 case BFD_RELOC_MIPS_CALL_LO16:
13684 fixp->fx_r_type = BFD_RELOC_MIPS_GOT_PAGE;
13685 reloc2->howto = bfd_reloc_type_lookup
13686 (stdoutput, BFD_RELOC_MIPS_GOT_OFST);
13689 fixp->fx_r_type = BFD_RELOC_MIPS_GOT16;
13691 case BFD_RELOC_MIPS_CALL16:
13692 case BFD_RELOC_MIPS_GOT_OFST:
13693 case BFD_RELOC_MIPS_GOT_DISP:
13696 /* It may seem nonsensical to relax GOT_DISP to
13697 GOT_DISP, but we're actually turning a GOT_DISP
13698 without offset into a GOT_DISP with an offset,
13699 getting rid of the separate addition, which we can
13700 do when the symbol is found to be local. */
13701 fixp->fx_r_type = BFD_RELOC_MIPS_GOT_DISP;
13705 fixp->fx_r_type = BFD_RELOC_MIPS_GOT16;
13713 /* Since the old MIPS ELF ABI uses Rel instead of Rela, encode the vtable
13714 entry to be used in the relocation's section offset. */
13715 if (! HAVE_NEWABI && fixp->fx_r_type == BFD_RELOC_VTABLE_ENTRY)
13717 reloc->address = reloc->addend;
13721 /* Since DIFF_EXPR_OK is defined in tc-mips.h, it is possible that
13722 fixup_segment converted a non-PC relative reloc into a PC
13723 relative reloc. In such a case, we need to convert the reloc
13725 code = fixp->fx_r_type;
13726 if (fixp->fx_pcrel)
13731 code = BFD_RELOC_8_PCREL;
13734 code = BFD_RELOC_16_PCREL;
13737 code = BFD_RELOC_32_PCREL;
13740 code = BFD_RELOC_64_PCREL;
13742 case BFD_RELOC_8_PCREL:
13743 case BFD_RELOC_16_PCREL:
13744 case BFD_RELOC_32_PCREL:
13745 case BFD_RELOC_64_PCREL:
13746 case BFD_RELOC_16_PCREL_S2:
13747 case BFD_RELOC_PCREL_HI16_S:
13748 case BFD_RELOC_PCREL_LO16:
13751 as_bad_where (fixp->fx_file, fixp->fx_line,
13752 _("Cannot make %s relocation PC relative"),
13753 bfd_get_reloc_code_name (code));
13757 /* To support a PC relative reloc when generating embedded PIC code
13758 for ECOFF, we use a Cygnus extension. We check for that here to
13759 make sure that we don't let such a reloc escape normally. */
13760 if ((OUTPUT_FLAVOR == bfd_target_ecoff_flavour
13761 || OUTPUT_FLAVOR == bfd_target_elf_flavour)
13762 && code == BFD_RELOC_16_PCREL_S2
13763 && mips_pic != EMBEDDED_PIC)
13764 reloc->howto = NULL;
13766 reloc->howto = bfd_reloc_type_lookup (stdoutput, code);
13768 if (reloc->howto == NULL)
13770 as_bad_where (fixp->fx_file, fixp->fx_line,
13771 _("Can not represent %s relocation in this object file format"),
13772 bfd_get_reloc_code_name (code));
13779 /* Relax a machine dependent frag. This returns the amount by which
13780 the current size of the frag should change. */
13783 mips_relax_frag (sec, fragp, stretch)
13788 if (RELAX_BRANCH_P (fragp->fr_subtype))
13790 offsetT old_var = fragp->fr_var;
13792 fragp->fr_var = relaxed_branch_length (fragp, sec, TRUE);
13794 return fragp->fr_var - old_var;
13797 if (! RELAX_MIPS16_P (fragp->fr_subtype))
13800 if (mips16_extended_frag (fragp, NULL, stretch))
13802 if (RELAX_MIPS16_EXTENDED (fragp->fr_subtype))
13804 fragp->fr_subtype = RELAX_MIPS16_MARK_EXTENDED (fragp->fr_subtype);
13809 if (! RELAX_MIPS16_EXTENDED (fragp->fr_subtype))
13811 fragp->fr_subtype = RELAX_MIPS16_CLEAR_EXTENDED (fragp->fr_subtype);
13818 /* Convert a machine dependent frag. */
13821 md_convert_frag (abfd, asec, fragp)
13822 bfd *abfd ATTRIBUTE_UNUSED;
13829 if (RELAX_BRANCH_P (fragp->fr_subtype))
13832 unsigned long insn;
13836 buf = (bfd_byte *)fragp->fr_literal + fragp->fr_fix;
13838 if (target_big_endian)
13839 insn = bfd_getb32 (buf);
13841 insn = bfd_getl32 (buf);
13843 if (!RELAX_BRANCH_TOOFAR (fragp->fr_subtype))
13845 /* We generate a fixup instead of applying it right now
13846 because, if there are linker relaxations, we're going to
13847 need the relocations. */
13848 exp.X_op = O_symbol;
13849 exp.X_add_symbol = fragp->fr_symbol;
13850 exp.X_add_number = fragp->fr_offset;
13852 fixp = fix_new_exp (fragp, buf - (bfd_byte *)fragp->fr_literal,
13854 BFD_RELOC_16_PCREL_S2);
13855 fixp->fx_file = fragp->fr_file;
13856 fixp->fx_line = fragp->fr_line;
13858 md_number_to_chars ((char *)buf, insn, 4);
13865 as_warn_where (fragp->fr_file, fragp->fr_line,
13866 _("relaxed out-of-range branch into a jump"));
13868 if (RELAX_BRANCH_UNCOND (fragp->fr_subtype))
13871 if (!RELAX_BRANCH_LIKELY (fragp->fr_subtype))
13873 /* Reverse the branch. */
13874 switch ((insn >> 28) & 0xf)
13877 /* bc[0-3][tf]l? and bc1any[24][ft] instructions can
13878 have the condition reversed by tweaking a single
13879 bit, and their opcodes all have 0x4???????. */
13880 assert ((insn & 0xf1000000) == 0x41000000);
13881 insn ^= 0x00010000;
13885 /* bltz 0x04000000 bgez 0x04010000
13886 bltzal 0x04100000 bgezal 0x04110000 */
13887 assert ((insn & 0xfc0e0000) == 0x04000000);
13888 insn ^= 0x00010000;
13892 /* beq 0x10000000 bne 0x14000000
13893 blez 0x18000000 bgtz 0x1c000000 */
13894 insn ^= 0x04000000;
13902 if (RELAX_BRANCH_LINK (fragp->fr_subtype))
13904 /* Clear the and-link bit. */
13905 assert ((insn & 0xfc1c0000) == 0x04100000);
13907 /* bltzal 0x04100000 bgezal 0x04110000
13908 bltzall 0x04120000 bgezall 0x04130000 */
13909 insn &= ~0x00100000;
13912 /* Branch over the branch (if the branch was likely) or the
13913 full jump (not likely case). Compute the offset from the
13914 current instruction to branch to. */
13915 if (RELAX_BRANCH_LIKELY (fragp->fr_subtype))
13919 /* How many bytes in instructions we've already emitted? */
13920 i = buf - (bfd_byte *)fragp->fr_literal - fragp->fr_fix;
13921 /* How many bytes in instructions from here to the end? */
13922 i = fragp->fr_var - i;
13924 /* Convert to instruction count. */
13926 /* Branch counts from the next instruction. */
13929 /* Branch over the jump. */
13930 md_number_to_chars ((char *)buf, insn, 4);
13934 md_number_to_chars ((char*)buf, 0, 4);
13937 if (RELAX_BRANCH_LIKELY (fragp->fr_subtype))
13939 /* beql $0, $0, 2f */
13941 /* Compute the PC offset from the current instruction to
13942 the end of the variable frag. */
13943 /* How many bytes in instructions we've already emitted? */
13944 i = buf - (bfd_byte *)fragp->fr_literal - fragp->fr_fix;
13945 /* How many bytes in instructions from here to the end? */
13946 i = fragp->fr_var - i;
13947 /* Convert to instruction count. */
13949 /* Don't decrement i, because we want to branch over the
13953 md_number_to_chars ((char *)buf, insn, 4);
13956 md_number_to_chars ((char *)buf, 0, 4);
13961 if (mips_pic == NO_PIC)
13964 insn = (RELAX_BRANCH_LINK (fragp->fr_subtype)
13965 ? 0x0c000000 : 0x08000000);
13966 exp.X_op = O_symbol;
13967 exp.X_add_symbol = fragp->fr_symbol;
13968 exp.X_add_number = fragp->fr_offset;
13970 fixp = fix_new_exp (fragp, buf - (bfd_byte *)fragp->fr_literal,
13971 4, &exp, 0, BFD_RELOC_MIPS_JMP);
13972 fixp->fx_file = fragp->fr_file;
13973 fixp->fx_line = fragp->fr_line;
13975 md_number_to_chars ((char*)buf, insn, 4);
13980 /* lw/ld $at, <sym>($gp) R_MIPS_GOT16 */
13981 insn = HAVE_64BIT_ADDRESSES ? 0xdf810000 : 0x8f810000;
13982 exp.X_op = O_symbol;
13983 exp.X_add_symbol = fragp->fr_symbol;
13984 exp.X_add_number = fragp->fr_offset;
13986 if (fragp->fr_offset)
13988 exp.X_add_symbol = make_expr_symbol (&exp);
13989 exp.X_add_number = 0;
13992 fixp = fix_new_exp (fragp, buf - (bfd_byte *)fragp->fr_literal,
13993 4, &exp, 0, BFD_RELOC_MIPS_GOT16);
13994 fixp->fx_file = fragp->fr_file;
13995 fixp->fx_line = fragp->fr_line;
13997 md_number_to_chars ((char*)buf, insn, 4);
14000 if (mips_opts.isa == ISA_MIPS1)
14003 md_number_to_chars ((char*)buf, 0, 4);
14007 /* d/addiu $at, $at, <sym> R_MIPS_LO16 */
14008 insn = HAVE_64BIT_ADDRESSES ? 0x64210000 : 0x24210000;
14010 fixp = fix_new_exp (fragp, buf - (bfd_byte *)fragp->fr_literal,
14011 4, &exp, 0, BFD_RELOC_LO16);
14012 fixp->fx_file = fragp->fr_file;
14013 fixp->fx_line = fragp->fr_line;
14015 md_number_to_chars ((char*)buf, insn, 4);
14019 if (RELAX_BRANCH_LINK (fragp->fr_subtype))
14024 md_number_to_chars ((char*)buf, insn, 4);
14029 assert (buf == (bfd_byte *)fragp->fr_literal
14030 + fragp->fr_fix + fragp->fr_var);
14032 fragp->fr_fix += fragp->fr_var;
14037 if (RELAX_MIPS16_P (fragp->fr_subtype))
14040 register const struct mips16_immed_operand *op;
14041 bfd_boolean small, ext;
14044 unsigned long insn;
14045 bfd_boolean use_extend;
14046 unsigned short extend;
14048 type = RELAX_MIPS16_TYPE (fragp->fr_subtype);
14049 op = mips16_immed_operands;
14050 while (op->type != type)
14053 if (RELAX_MIPS16_EXTENDED (fragp->fr_subtype))
14064 resolve_symbol_value (fragp->fr_symbol);
14065 val = S_GET_VALUE (fragp->fr_symbol);
14070 addr = fragp->fr_address + fragp->fr_fix;
14072 /* The rules for the base address of a PC relative reloc are
14073 complicated; see mips16_extended_frag. */
14074 if (type == 'p' || type == 'q')
14079 /* Ignore the low bit in the target, since it will be
14080 set for a text label. */
14081 if ((val & 1) != 0)
14084 else if (RELAX_MIPS16_JAL_DSLOT (fragp->fr_subtype))
14086 else if (RELAX_MIPS16_DSLOT (fragp->fr_subtype))
14089 addr &= ~ (addressT) ((1 << op->shift) - 1);
14092 /* Make sure the section winds up with the alignment we have
14095 record_alignment (asec, op->shift);
14099 && (RELAX_MIPS16_JAL_DSLOT (fragp->fr_subtype)
14100 || RELAX_MIPS16_DSLOT (fragp->fr_subtype)))
14101 as_warn_where (fragp->fr_file, fragp->fr_line,
14102 _("extended instruction in delay slot"));
14104 buf = (bfd_byte *) (fragp->fr_literal + fragp->fr_fix);
14106 if (target_big_endian)
14107 insn = bfd_getb16 (buf);
14109 insn = bfd_getl16 (buf);
14111 mips16_immed (fragp->fr_file, fragp->fr_line, type, val,
14112 RELAX_MIPS16_USER_EXT (fragp->fr_subtype),
14113 small, ext, &insn, &use_extend, &extend);
14117 md_number_to_chars ((char *) buf, 0xf000 | extend, 2);
14118 fragp->fr_fix += 2;
14122 md_number_to_chars ((char *) buf, insn, 2);
14123 fragp->fr_fix += 2;
14128 if (fragp->fr_opcode == NULL)
14131 old = RELAX_OLD (fragp->fr_subtype);
14132 new = RELAX_NEW (fragp->fr_subtype);
14133 fixptr = fragp->fr_literal + fragp->fr_fix;
14136 memmove (fixptr - old, fixptr, new);
14138 fragp->fr_fix += new - old;
14144 /* This function is called after the relocs have been generated.
14145 We've been storing mips16 text labels as odd. Here we convert them
14146 back to even for the convenience of the debugger. */
14149 mips_frob_file_after_relocs ()
14152 unsigned int count, i;
14154 if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
14157 syms = bfd_get_outsymbols (stdoutput);
14158 count = bfd_get_symcount (stdoutput);
14159 for (i = 0; i < count; i++, syms++)
14161 if (elf_symbol (*syms)->internal_elf_sym.st_other == STO_MIPS16
14162 && ((*syms)->value & 1) != 0)
14164 (*syms)->value &= ~1;
14165 /* If the symbol has an odd size, it was probably computed
14166 incorrectly, so adjust that as well. */
14167 if ((elf_symbol (*syms)->internal_elf_sym.st_size & 1) != 0)
14168 ++elf_symbol (*syms)->internal_elf_sym.st_size;
14175 /* This function is called whenever a label is defined. It is used
14176 when handling branch delays; if a branch has a label, we assume we
14177 can not move it. */
14180 mips_define_label (sym)
14183 struct insn_label_list *l;
14185 if (free_insn_labels == NULL)
14186 l = (struct insn_label_list *) xmalloc (sizeof *l);
14189 l = free_insn_labels;
14190 free_insn_labels = l->next;
14194 l->next = insn_labels;
14198 #if defined (OBJ_ELF) || defined (OBJ_MAYBE_ELF)
14200 /* Some special processing for a MIPS ELF file. */
14203 mips_elf_final_processing ()
14205 /* Write out the register information. */
14206 if (mips_abi != N64_ABI)
14210 s.ri_gprmask = mips_gprmask;
14211 s.ri_cprmask[0] = mips_cprmask[0];
14212 s.ri_cprmask[1] = mips_cprmask[1];
14213 s.ri_cprmask[2] = mips_cprmask[2];
14214 s.ri_cprmask[3] = mips_cprmask[3];
14215 /* The gp_value field is set by the MIPS ELF backend. */
14217 bfd_mips_elf32_swap_reginfo_out (stdoutput, &s,
14218 ((Elf32_External_RegInfo *)
14219 mips_regmask_frag));
14223 Elf64_Internal_RegInfo s;
14225 s.ri_gprmask = mips_gprmask;
14227 s.ri_cprmask[0] = mips_cprmask[0];
14228 s.ri_cprmask[1] = mips_cprmask[1];
14229 s.ri_cprmask[2] = mips_cprmask[2];
14230 s.ri_cprmask[3] = mips_cprmask[3];
14231 /* The gp_value field is set by the MIPS ELF backend. */
14233 bfd_mips_elf64_swap_reginfo_out (stdoutput, &s,
14234 ((Elf64_External_RegInfo *)
14235 mips_regmask_frag));
14238 /* Set the MIPS ELF flag bits. FIXME: There should probably be some
14239 sort of BFD interface for this. */
14240 if (mips_any_noreorder)
14241 elf_elfheader (stdoutput)->e_flags |= EF_MIPS_NOREORDER;
14242 if (mips_pic != NO_PIC)
14244 elf_elfheader (stdoutput)->e_flags |= EF_MIPS_PIC;
14245 elf_elfheader (stdoutput)->e_flags |= EF_MIPS_CPIC;
14248 elf_elfheader (stdoutput)->e_flags |= EF_MIPS_CPIC;
14250 /* Set MIPS ELF flags for ASEs. */
14251 if (file_ase_mips16)
14252 elf_elfheader (stdoutput)->e_flags |= EF_MIPS_ARCH_ASE_M16;
14253 #if 0 /* XXX FIXME */
14254 if (file_ase_mips3d)
14255 elf_elfheader (stdoutput)->e_flags |= ???;
14258 elf_elfheader (stdoutput)->e_flags |= EF_MIPS_ARCH_ASE_MDMX;
14260 /* Set the MIPS ELF ABI flags. */
14261 if (mips_abi == O32_ABI && USE_E_MIPS_ABI_O32)
14262 elf_elfheader (stdoutput)->e_flags |= E_MIPS_ABI_O32;
14263 else if (mips_abi == O64_ABI)
14264 elf_elfheader (stdoutput)->e_flags |= E_MIPS_ABI_O64;
14265 else if (mips_abi == EABI_ABI)
14267 if (!file_mips_gp32)
14268 elf_elfheader (stdoutput)->e_flags |= E_MIPS_ABI_EABI64;
14270 elf_elfheader (stdoutput)->e_flags |= E_MIPS_ABI_EABI32;
14272 else if (mips_abi == N32_ABI)
14273 elf_elfheader (stdoutput)->e_flags |= EF_MIPS_ABI2;
14275 /* Nothing to do for N64_ABI. */
14277 if (mips_32bitmode)
14278 elf_elfheader (stdoutput)->e_flags |= EF_MIPS_32BITMODE;
14281 #endif /* OBJ_ELF || OBJ_MAYBE_ELF */
14283 typedef struct proc {
14285 unsigned long reg_mask;
14286 unsigned long reg_offset;
14287 unsigned long fpreg_mask;
14288 unsigned long fpreg_offset;
14289 unsigned long frame_offset;
14290 unsigned long frame_reg;
14291 unsigned long pc_reg;
14294 static procS cur_proc;
14295 static procS *cur_proc_ptr;
14296 static int numprocs;
14298 /* Fill in an rs_align_code fragment. */
14301 mips_handle_align (fragp)
14304 if (fragp->fr_type != rs_align_code)
14307 if (mips_opts.mips16)
14309 static const unsigned char be_nop[] = { 0x65, 0x00 };
14310 static const unsigned char le_nop[] = { 0x00, 0x65 };
14315 bytes = fragp->fr_next->fr_address - fragp->fr_address - fragp->fr_fix;
14316 p = fragp->fr_literal + fragp->fr_fix;
14324 memcpy (p, (target_big_endian ? be_nop : le_nop), 2);
14328 /* For mips32, a nop is a zero, which we trivially get by doing nothing. */
14339 /* check for premature end, nesting errors, etc */
14341 as_warn (_("missing .end at end of assembly"));
14350 if (*input_line_pointer == '-')
14352 ++input_line_pointer;
14355 if (!ISDIGIT (*input_line_pointer))
14356 as_bad (_("expected simple number"));
14357 if (input_line_pointer[0] == '0')
14359 if (input_line_pointer[1] == 'x')
14361 input_line_pointer += 2;
14362 while (ISXDIGIT (*input_line_pointer))
14365 val |= hex_value (*input_line_pointer++);
14367 return negative ? -val : val;
14371 ++input_line_pointer;
14372 while (ISDIGIT (*input_line_pointer))
14375 val |= *input_line_pointer++ - '0';
14377 return negative ? -val : val;
14380 if (!ISDIGIT (*input_line_pointer))
14382 printf (_(" *input_line_pointer == '%c' 0x%02x\n"),
14383 *input_line_pointer, *input_line_pointer);
14384 as_warn (_("invalid number"));
14387 while (ISDIGIT (*input_line_pointer))
14390 val += *input_line_pointer++ - '0';
14392 return negative ? -val : val;
14395 /* The .file directive; just like the usual .file directive, but there
14396 is an initial number which is the ECOFF file index. In the non-ECOFF
14397 case .file implies DWARF-2. */
14401 int x ATTRIBUTE_UNUSED;
14403 static int first_file_directive = 0;
14405 if (ECOFF_DEBUGGING)
14414 filename = dwarf2_directive_file (0);
14416 /* Versions of GCC up to 3.1 start files with a ".file"
14417 directive even for stabs output. Make sure that this
14418 ".file" is handled. Note that you need a version of GCC
14419 after 3.1 in order to support DWARF-2 on MIPS. */
14420 if (filename != NULL && ! first_file_directive)
14422 (void) new_logical_line (filename, -1);
14423 s_app_file_string (filename);
14425 first_file_directive = 1;
14429 /* The .loc directive, implying DWARF-2. */
14433 int x ATTRIBUTE_UNUSED;
14435 if (!ECOFF_DEBUGGING)
14436 dwarf2_directive_loc (0);
14439 /* The .end directive. */
14443 int x ATTRIBUTE_UNUSED;
14447 /* Following functions need their own .frame and .cprestore directives. */
14448 mips_frame_reg_valid = 0;
14449 mips_cprestore_valid = 0;
14451 if (!is_end_of_line[(unsigned char) *input_line_pointer])
14454 demand_empty_rest_of_line ();
14459 if ((bfd_get_section_flags (stdoutput, now_seg) & SEC_CODE) == 0)
14460 as_warn (_(".end not in text section"));
14464 as_warn (_(".end directive without a preceding .ent directive."));
14465 demand_empty_rest_of_line ();
14471 assert (S_GET_NAME (p));
14472 if (strcmp (S_GET_NAME (p), S_GET_NAME (cur_proc_ptr->isym)))
14473 as_warn (_(".end symbol does not match .ent symbol."));
14475 if (debug_type == DEBUG_STABS)
14476 stabs_generate_asm_endfunc (S_GET_NAME (p),
14480 as_warn (_(".end directive missing or unknown symbol"));
14483 /* Generate a .pdr section. */
14484 if (OUTPUT_FLAVOR == bfd_target_elf_flavour && ! ECOFF_DEBUGGING)
14486 segT saved_seg = now_seg;
14487 subsegT saved_subseg = now_subseg;
14492 dot = frag_now_fix ();
14494 #ifdef md_flush_pending_output
14495 md_flush_pending_output ();
14499 subseg_set (pdr_seg, 0);
14501 /* Write the symbol. */
14502 exp.X_op = O_symbol;
14503 exp.X_add_symbol = p;
14504 exp.X_add_number = 0;
14505 emit_expr (&exp, 4);
14507 fragp = frag_more (7 * 4);
14509 md_number_to_chars (fragp, (valueT) cur_proc_ptr->reg_mask, 4);
14510 md_number_to_chars (fragp + 4, (valueT) cur_proc_ptr->reg_offset, 4);
14511 md_number_to_chars (fragp + 8, (valueT) cur_proc_ptr->fpreg_mask, 4);
14512 md_number_to_chars (fragp + 12, (valueT) cur_proc_ptr->fpreg_offset, 4);
14513 md_number_to_chars (fragp + 16, (valueT) cur_proc_ptr->frame_offset, 4);
14514 md_number_to_chars (fragp + 20, (valueT) cur_proc_ptr->frame_reg, 4);
14515 md_number_to_chars (fragp + 24, (valueT) cur_proc_ptr->pc_reg, 4);
14517 subseg_set (saved_seg, saved_subseg);
14519 #endif /* OBJ_ELF */
14521 cur_proc_ptr = NULL;
14524 /* The .aent and .ent directives. */
14532 symbolP = get_symbol ();
14533 if (*input_line_pointer == ',')
14534 ++input_line_pointer;
14535 SKIP_WHITESPACE ();
14536 if (ISDIGIT (*input_line_pointer)
14537 || *input_line_pointer == '-')
14540 if ((bfd_get_section_flags (stdoutput, now_seg) & SEC_CODE) == 0)
14541 as_warn (_(".ent or .aent not in text section."));
14543 if (!aent && cur_proc_ptr)
14544 as_warn (_("missing .end"));
14548 /* This function needs its own .frame and .cprestore directives. */
14549 mips_frame_reg_valid = 0;
14550 mips_cprestore_valid = 0;
14552 cur_proc_ptr = &cur_proc;
14553 memset (cur_proc_ptr, '\0', sizeof (procS));
14555 cur_proc_ptr->isym = symbolP;
14557 symbol_get_bfdsym (symbolP)->flags |= BSF_FUNCTION;
14561 if (debug_type == DEBUG_STABS)
14562 stabs_generate_asm_func (S_GET_NAME (symbolP),
14563 S_GET_NAME (symbolP));
14566 demand_empty_rest_of_line ();
14569 /* The .frame directive. If the mdebug section is present (IRIX 5 native)
14570 then ecoff.c (ecoff_directive_frame) is used. For embedded targets,
14571 s_mips_frame is used so that we can set the PDR information correctly.
14572 We can't use the ecoff routines because they make reference to the ecoff
14573 symbol table (in the mdebug section). */
14576 s_mips_frame (ignore)
14577 int ignore ATTRIBUTE_UNUSED;
14580 if (OUTPUT_FLAVOR == bfd_target_elf_flavour && ! ECOFF_DEBUGGING)
14584 if (cur_proc_ptr == (procS *) NULL)
14586 as_warn (_(".frame outside of .ent"));
14587 demand_empty_rest_of_line ();
14591 cur_proc_ptr->frame_reg = tc_get_register (1);
14593 SKIP_WHITESPACE ();
14594 if (*input_line_pointer++ != ','
14595 || get_absolute_expression_and_terminator (&val) != ',')
14597 as_warn (_("Bad .frame directive"));
14598 --input_line_pointer;
14599 demand_empty_rest_of_line ();
14603 cur_proc_ptr->frame_offset = val;
14604 cur_proc_ptr->pc_reg = tc_get_register (0);
14606 demand_empty_rest_of_line ();
14609 #endif /* OBJ_ELF */
14613 /* The .fmask and .mask directives. If the mdebug section is present
14614 (IRIX 5 native) then ecoff.c (ecoff_directive_mask) is used. For
14615 embedded targets, s_mips_mask is used so that we can set the PDR
14616 information correctly. We can't use the ecoff routines because they
14617 make reference to the ecoff symbol table (in the mdebug section). */
14620 s_mips_mask (reg_type)
14624 if (OUTPUT_FLAVOR == bfd_target_elf_flavour && ! ECOFF_DEBUGGING)
14628 if (cur_proc_ptr == (procS *) NULL)
14630 as_warn (_(".mask/.fmask outside of .ent"));
14631 demand_empty_rest_of_line ();
14635 if (get_absolute_expression_and_terminator (&mask) != ',')
14637 as_warn (_("Bad .mask/.fmask directive"));
14638 --input_line_pointer;
14639 demand_empty_rest_of_line ();
14643 off = get_absolute_expression ();
14645 if (reg_type == 'F')
14647 cur_proc_ptr->fpreg_mask = mask;
14648 cur_proc_ptr->fpreg_offset = off;
14652 cur_proc_ptr->reg_mask = mask;
14653 cur_proc_ptr->reg_offset = off;
14656 demand_empty_rest_of_line ();
14659 #endif /* OBJ_ELF */
14660 s_ignore (reg_type);
14663 /* The .loc directive. */
14674 assert (now_seg == text_section);
14676 lineno = get_number ();
14677 addroff = frag_now_fix ();
14679 symbolP = symbol_new ("", N_SLINE, addroff, frag_now);
14680 S_SET_TYPE (symbolP, N_SLINE);
14681 S_SET_OTHER (symbolP, 0);
14682 S_SET_DESC (symbolP, lineno);
14683 symbolP->sy_segment = now_seg;
14687 /* A table describing all the processors gas knows about. Names are
14688 matched in the order listed.
14690 To ease comparison, please keep this table in the same order as
14691 gcc's mips_cpu_info_table[]. */
14692 static const struct mips_cpu_info mips_cpu_info_table[] =
14694 /* Entries for generic ISAs */
14695 { "mips1", 1, ISA_MIPS1, CPU_R3000 },
14696 { "mips2", 1, ISA_MIPS2, CPU_R6000 },
14697 { "mips3", 1, ISA_MIPS3, CPU_R4000 },
14698 { "mips4", 1, ISA_MIPS4, CPU_R8000 },
14699 { "mips5", 1, ISA_MIPS5, CPU_MIPS5 },
14700 { "mips32", 1, ISA_MIPS32, CPU_MIPS32 },
14701 { "mips32r2", 1, ISA_MIPS32R2, CPU_MIPS32R2 },
14702 { "mips64", 1, ISA_MIPS64, CPU_MIPS64 },
14705 { "r3000", 0, ISA_MIPS1, CPU_R3000 },
14706 { "r2000", 0, ISA_MIPS1, CPU_R3000 },
14707 { "r3900", 0, ISA_MIPS1, CPU_R3900 },
14710 { "r6000", 0, ISA_MIPS2, CPU_R6000 },
14713 { "r4000", 0, ISA_MIPS3, CPU_R4000 },
14714 { "r4010", 0, ISA_MIPS2, CPU_R4010 },
14715 { "vr4100", 0, ISA_MIPS3, CPU_VR4100 },
14716 { "vr4111", 0, ISA_MIPS3, CPU_R4111 },
14717 { "vr4120", 0, ISA_MIPS3, CPU_VR4120 },
14718 { "vr4130", 0, ISA_MIPS3, CPU_VR4120 },
14719 { "vr4181", 0, ISA_MIPS3, CPU_R4111 },
14720 { "vr4300", 0, ISA_MIPS3, CPU_R4300 },
14721 { "r4400", 0, ISA_MIPS3, CPU_R4400 },
14722 { "r4600", 0, ISA_MIPS3, CPU_R4600 },
14723 { "orion", 0, ISA_MIPS3, CPU_R4600 },
14724 { "r4650", 0, ISA_MIPS3, CPU_R4650 },
14727 { "r8000", 0, ISA_MIPS4, CPU_R8000 },
14728 { "r10000", 0, ISA_MIPS4, CPU_R10000 },
14729 { "r12000", 0, ISA_MIPS4, CPU_R12000 },
14730 { "vr5000", 0, ISA_MIPS4, CPU_R5000 },
14731 { "vr5400", 0, ISA_MIPS4, CPU_VR5400 },
14732 { "vr5500", 0, ISA_MIPS4, CPU_VR5500 },
14733 { "rm5200", 0, ISA_MIPS4, CPU_R5000 },
14734 { "rm5230", 0, ISA_MIPS4, CPU_R5000 },
14735 { "rm5231", 0, ISA_MIPS4, CPU_R5000 },
14736 { "rm5261", 0, ISA_MIPS4, CPU_R5000 },
14737 { "rm5721", 0, ISA_MIPS4, CPU_R5000 },
14738 { "r7000", 0, ISA_MIPS4, CPU_R5000 },
14741 { "4kc", 0, ISA_MIPS32, CPU_MIPS32, },
14742 { "4km", 0, ISA_MIPS32, CPU_MIPS32 },
14743 { "4kp", 0, ISA_MIPS32, CPU_MIPS32 },
14746 { "5kc", 0, ISA_MIPS64, CPU_MIPS64 },
14747 { "20kc", 0, ISA_MIPS64, CPU_MIPS64 },
14749 /* Broadcom SB-1 CPU core */
14750 { "sb1", 0, ISA_MIPS64, CPU_SB1 },
14757 /* Return true if GIVEN is the same as CANONICAL, or if it is CANONICAL
14758 with a final "000" replaced by "k". Ignore case.
14760 Note: this function is shared between GCC and GAS. */
14763 mips_strict_matching_cpu_name_p (canonical, given)
14764 const char *canonical, *given;
14766 while (*given != 0 && TOLOWER (*given) == TOLOWER (*canonical))
14767 given++, canonical++;
14769 return ((*given == 0 && *canonical == 0)
14770 || (strcmp (canonical, "000") == 0 && strcasecmp (given, "k") == 0));
14774 /* Return true if GIVEN matches CANONICAL, where GIVEN is a user-supplied
14775 CPU name. We've traditionally allowed a lot of variation here.
14777 Note: this function is shared between GCC and GAS. */
14780 mips_matching_cpu_name_p (canonical, given)
14781 const char *canonical, *given;
14783 /* First see if the name matches exactly, or with a final "000"
14784 turned into "k". */
14785 if (mips_strict_matching_cpu_name_p (canonical, given))
14788 /* If not, try comparing based on numerical designation alone.
14789 See if GIVEN is an unadorned number, or 'r' followed by a number. */
14790 if (TOLOWER (*given) == 'r')
14792 if (!ISDIGIT (*given))
14795 /* Skip over some well-known prefixes in the canonical name,
14796 hoping to find a number there too. */
14797 if (TOLOWER (canonical[0]) == 'v' && TOLOWER (canonical[1]) == 'r')
14799 else if (TOLOWER (canonical[0]) == 'r' && TOLOWER (canonical[1]) == 'm')
14801 else if (TOLOWER (canonical[0]) == 'r')
14804 return mips_strict_matching_cpu_name_p (canonical, given);
14808 /* Parse an option that takes the name of a processor as its argument.
14809 OPTION is the name of the option and CPU_STRING is the argument.
14810 Return the corresponding processor enumeration if the CPU_STRING is
14811 recognized, otherwise report an error and return null.
14813 A similar function exists in GCC. */
14815 static const struct mips_cpu_info *
14816 mips_parse_cpu (option, cpu_string)
14817 const char *option, *cpu_string;
14819 const struct mips_cpu_info *p;
14821 /* 'from-abi' selects the most compatible architecture for the given
14822 ABI: MIPS I for 32-bit ABIs and MIPS III for 64-bit ABIs. For the
14823 EABIs, we have to decide whether we're using the 32-bit or 64-bit
14824 version. Look first at the -mgp options, if given, otherwise base
14825 the choice on MIPS_DEFAULT_64BIT.
14827 Treat NO_ABI like the EABIs. One reason to do this is that the
14828 plain 'mips' and 'mips64' configs have 'from-abi' as their default
14829 architecture. This code picks MIPS I for 'mips' and MIPS III for
14830 'mips64', just as we did in the days before 'from-abi'. */
14831 if (strcasecmp (cpu_string, "from-abi") == 0)
14833 if (ABI_NEEDS_32BIT_REGS (mips_abi))
14834 return mips_cpu_info_from_isa (ISA_MIPS1);
14836 if (ABI_NEEDS_64BIT_REGS (mips_abi))
14837 return mips_cpu_info_from_isa (ISA_MIPS3);
14839 if (file_mips_gp32 >= 0)
14840 return mips_cpu_info_from_isa (file_mips_gp32 ? ISA_MIPS1 : ISA_MIPS3);
14842 return mips_cpu_info_from_isa (MIPS_DEFAULT_64BIT
14847 /* 'default' has traditionally been a no-op. Probably not very useful. */
14848 if (strcasecmp (cpu_string, "default") == 0)
14851 for (p = mips_cpu_info_table; p->name != 0; p++)
14852 if (mips_matching_cpu_name_p (p->name, cpu_string))
14855 as_bad ("Bad value (%s) for %s", cpu_string, option);
14859 /* Return the canonical processor information for ISA (a member of the
14860 ISA_MIPS* enumeration). */
14862 static const struct mips_cpu_info *
14863 mips_cpu_info_from_isa (isa)
14868 for (i = 0; mips_cpu_info_table[i].name != NULL; i++)
14869 if (mips_cpu_info_table[i].is_isa
14870 && isa == mips_cpu_info_table[i].isa)
14871 return (&mips_cpu_info_table[i]);
14877 show (stream, string, col_p, first_p)
14879 const char *string;
14885 fprintf (stream, "%24s", "");
14890 fprintf (stream, ", ");
14894 if (*col_p + strlen (string) > 72)
14896 fprintf (stream, "\n%24s", "");
14900 fprintf (stream, "%s", string);
14901 *col_p += strlen (string);
14907 md_show_usage (stream)
14913 fprintf (stream, _("\
14915 -membedded-pic generate embedded position independent code\n\
14916 -EB generate big endian output\n\
14917 -EL generate little endian output\n\
14918 -g, -g2 do not remove unneeded NOPs or swap branches\n\
14919 -G NUM allow referencing objects up to NUM bytes\n\
14920 implicitly with the gp register [default 8]\n"));
14921 fprintf (stream, _("\
14922 -mips1 generate MIPS ISA I instructions\n\
14923 -mips2 generate MIPS ISA II instructions\n\
14924 -mips3 generate MIPS ISA III instructions\n\
14925 -mips4 generate MIPS ISA IV instructions\n\
14926 -mips5 generate MIPS ISA V instructions\n\
14927 -mips32 generate MIPS32 ISA instructions\n\
14928 -mips32r2 generate MIPS32 release 2 ISA instructions\n\
14929 -mips64 generate MIPS64 ISA instructions\n\
14930 -march=CPU/-mtune=CPU generate code/schedule for CPU, where CPU is one of:\n"));
14934 for (i = 0; mips_cpu_info_table[i].name != NULL; i++)
14935 show (stream, mips_cpu_info_table[i].name, &column, &first);
14936 show (stream, "from-abi", &column, &first);
14937 fputc ('\n', stream);
14939 fprintf (stream, _("\
14940 -mCPU equivalent to -march=CPU -mtune=CPU. Deprecated.\n\
14941 -no-mCPU don't generate code specific to CPU.\n\
14942 For -mCPU and -no-mCPU, CPU must be one of:\n"));
14946 show (stream, "3900", &column, &first);
14947 show (stream, "4010", &column, &first);
14948 show (stream, "4100", &column, &first);
14949 show (stream, "4650", &column, &first);
14950 fputc ('\n', stream);
14952 fprintf (stream, _("\
14953 -mips16 generate mips16 instructions\n\
14954 -no-mips16 do not generate mips16 instructions\n"));
14955 fprintf (stream, _("\
14956 -mgp32 use 32-bit GPRs, regardless of the chosen ISA\n\
14957 -mfp32 use 32-bit FPRs, regardless of the chosen ISA\n\
14958 -O0 remove unneeded NOPs, do not swap branches\n\
14959 -O remove unneeded NOPs and swap branches\n\
14960 -n warn about NOPs generated from macros\n\
14961 --[no-]construct-floats [dis]allow floating point values to be constructed\n\
14962 --trap, --no-break trap exception on div by 0 and mult overflow\n\
14963 --break, --no-trap break exception on div by 0 and mult overflow\n"));
14965 fprintf (stream, _("\
14966 -KPIC, -call_shared generate SVR4 position independent code\n\
14967 -non_shared do not generate position independent code\n\
14968 -xgot assume a 32 bit GOT\n\
14969 -mabi=ABI create ABI conformant object file for:\n"));
14973 show (stream, "32", &column, &first);
14974 show (stream, "o64", &column, &first);
14975 show (stream, "n32", &column, &first);
14976 show (stream, "64", &column, &first);
14977 show (stream, "eabi", &column, &first);
14979 fputc ('\n', stream);
14981 fprintf (stream, _("\
14982 -32 create o32 ABI object file (default)\n\
14983 -n32 create n32 ABI object file\n\
14984 -64 create 64 ABI object file\n"));
14989 mips_dwarf2_format ()
14991 if (mips_abi == N64_ABI)
14994 return dwarf2_format_64bit_irix;
14996 return dwarf2_format_64bit;
15000 return dwarf2_format_32bit;