tc-mips.c revision 208737
1/* tc-mips.c -- assemble code for a MIPS chip.
2   Copyright 1993, 1994, 1995, 1996, 1997, 1998, 1999, 2000, 2001, 2002,
3   2003, 2004, 2005 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
7   Support.
8
9   This file is part of GAS.
10
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)
14   any later version.
15
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.
20
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, 51 Franklin Street - Fifth Floor, Boston, MA
24   02110-1301, USA.  */
25
26#include "as.h"
27#include "config.h"
28#include "subsegs.h"
29#include "safe-ctype.h"
30
31#include <stdarg.h>
32
33#include "opcode/mips.h"
34#include "itbl-ops.h"
35#include "dwarf2dbg.h"
36#include "dw2gencfi.h"
37
38#ifdef DEBUG
39#define DBG(x) printf x
40#else
41#define DBG(x)
42#endif
43
44#ifdef OBJ_MAYBE_ELF
45/* Clean up namespace so we can include obj-elf.h too.  */
46static int mips_output_flavor (void);
47static int mips_output_flavor (void) { return OUTPUT_FLAVOR; }
48#undef OBJ_PROCESS_STAB
49#undef OUTPUT_FLAVOR
50#undef S_GET_ALIGN
51#undef S_GET_SIZE
52#undef S_SET_ALIGN
53#undef S_SET_SIZE
54#undef obj_frob_file
55#undef obj_frob_file_after_relocs
56#undef obj_frob_symbol
57#undef obj_pop_insert
58#undef obj_sec_sym_ok_for_reloc
59#undef OBJ_COPY_SYMBOL_ATTRIBUTES
60
61#include "obj-elf.h"
62/* Fix any of them that we actually care about.  */
63#undef OUTPUT_FLAVOR
64#define OUTPUT_FLAVOR mips_output_flavor()
65#endif
66
67#if defined (OBJ_ELF)
68#include "elf/mips.h"
69#endif
70
71#ifndef ECOFF_DEBUGGING
72#define NO_ECOFF_DEBUGGING
73#define ECOFF_DEBUGGING 0
74#endif
75
76int mips_flag_mdebug = -1;
77
78/* Control generation of .pdr sections.  Off by default on IRIX: the native
79   linker doesn't know about and discards them, but relocations against them
80   remain, leading to rld crashes.  */
81#ifdef TE_IRIX
82int mips_flag_pdr = FALSE;
83#else
84int mips_flag_pdr = TRUE;
85#endif
86
87/* Control generation of error message for unsupported instructions in
88   Octeon. Octeon does not have floating point, and all the instructions
89   that use floating point registers are not allowed in Elf targets but
90   are allowed in Linux targets by default.  */
91#ifdef OCTEON_ERROR_ON_UNSUPPORTED
92static int octeon_error_on_unsupported = 1;
93#else
94static int octeon_error_on_unsupported = 0;
95#endif
96
97/* Control generation of Octeon/MIPS unaligned load/store instructions.
98   For ELF target, default to Octeon load/store instructions.
99   For Linux target, default to MIPS load/store instructions.  */
100#ifdef OCTEON_USE_UNALIGN
101static int octeon_use_unalign = 1;
102#else
103static int octeon_use_unalign = 0;
104#endif
105
106#include "ecoff.h"
107
108#if defined (OBJ_ELF) || defined (OBJ_MAYBE_ELF)
109static char *mips_regmask_frag;
110#endif
111
112#define ZERO 0
113#define AT  1
114#define TREG 24
115#define PIC_CALL_REG 25
116#define KT0 26
117#define KT1 27
118#define GP  28
119#define SP  29
120#define FP  30
121#define RA  31
122
123#define ILLEGAL_REG (32)
124
125/* Allow override of standard little-endian ECOFF format.  */
126
127#ifndef ECOFF_LITTLE_FORMAT
128#define ECOFF_LITTLE_FORMAT "ecoff-littlemips"
129#endif
130
131extern int target_big_endian;
132
133/* The name of the readonly data section.  */
134#define RDATA_SECTION_NAME (OUTPUT_FLAVOR == bfd_target_ecoff_flavour \
135			    ? ".rdata" \
136			    : OUTPUT_FLAVOR == bfd_target_coff_flavour \
137			    ? ".rdata" \
138			    : OUTPUT_FLAVOR == bfd_target_elf_flavour \
139			    ? ".rodata" \
140			    : (abort (), ""))
141
142/* Information about an instruction, including its format, operands
143   and fixups.  */
144struct mips_cl_insn
145{
146  /* The opcode's entry in mips_opcodes or mips16_opcodes.  */
147  const struct mips_opcode *insn_mo;
148
149  /* True if this is a mips16 instruction and if we want the extended
150     form of INSN_MO.  */
151  bfd_boolean use_extend;
152
153  /* The 16-bit extension instruction to use when USE_EXTEND is true.  */
154  unsigned short extend;
155
156  /* The 16-bit or 32-bit bitstring of the instruction itself.  This is
157     a copy of INSN_MO->match with the operands filled in.  */
158  unsigned long insn_opcode;
159
160  /* The frag that contains the instruction.  */
161  struct frag *frag;
162
163  /* The offset into FRAG of the first instruction byte.  */
164  long where;
165
166  /* The relocs associated with the instruction, if any.  */
167  fixS *fixp[3];
168
169  /* True if this entry cannot be moved from its current position.  */
170  unsigned int fixed_p : 1;
171
172  /* True if this instruction occured in a .set noreorder block.  */
173  unsigned int noreorder_p : 1;
174
175  /* True for mips16 instructions that jump to an absolute address.  */
176  unsigned int mips16_absolute_jump_p : 1;
177};
178
179/* The ABI to use.  */
180enum mips_abi_level
181{
182  NO_ABI = 0,
183  O32_ABI,
184  O64_ABI,
185  N32_ABI,
186  N64_ABI,
187  EABI_ABI
188};
189
190/* MIPS ABI we are using for this output file.  */
191static enum mips_abi_level mips_abi = NO_ABI;
192
193/* Whether or not we have code that can call pic code.  */
194int mips_abicalls = FALSE;
195
196/* Whether or not we have code which can be put into a shared
197   library.  */
198static bfd_boolean mips_in_shared = TRUE;
199
200/* This is the set of options which may be modified by the .set
201   pseudo-op.  We use a struct so that .set push and .set pop are more
202   reliable.  */
203
204struct mips_set_options
205{
206  /* MIPS ISA (Instruction Set Architecture) level.  This is set to -1
207     if it has not been initialized.  Changed by `.set mipsN', and the
208     -mipsN command line option, and the default CPU.  */
209  int isa;
210  /* Enabled Application Specific Extensions (ASEs).  These are set to -1
211     if they have not been initialized.  Changed by `.set <asename>', by
212     command line options, and based on the default architecture.  */
213  int ase_mips3d;
214  int ase_mdmx;
215  int ase_dsp;
216  int ase_mt;
217  /* Whether we are assembling for the mips16 processor.  0 if we are
218     not, 1 if we are, and -1 if the value has not been initialized.
219     Changed by `.set mips16' and `.set nomips16', and the -mips16 and
220     -nomips16 command line options, and the default CPU.  */
221  int mips16;
222  /* Non-zero if we should not reorder instructions.  Changed by `.set
223     reorder' and `.set noreorder'.  */
224  int noreorder;
225  /* Non-zero if we should not permit the $at ($1) register to be used
226     in instructions.  Changed by `.set at' and `.set noat'.  */
227  int noat;
228  /* Non-zero if we should warn when a macro instruction expands into
229     more than one machine instruction.  Changed by `.set nomacro' and
230     `.set macro'.  */
231  int warn_about_macros;
232  /* Non-zero if we should not move instructions.  Changed by `.set
233     move', `.set volatile', `.set nomove', and `.set novolatile'.  */
234  int nomove;
235  /* Non-zero if we should not optimize branches by moving the target
236     of the branch into the delay slot.  Actually, we don't perform
237     this optimization anyhow.  Changed by `.set bopt' and `.set
238     nobopt'.  */
239  int nobopt;
240  /* Non-zero if we should not autoextend mips16 instructions.
241     Changed by `.set autoextend' and `.set noautoextend'.  */
242  int noautoextend;
243  /* Restrict general purpose registers and floating point registers
244     to 32 bit.  This is initially determined when -mgp32 or -mfp32
245     is passed but can changed if the assembler code uses .set mipsN.  */
246  int gp32;
247  int fp32;
248  /* MIPS architecture (CPU) type.  Changed by .set arch=FOO, the -march
249     command line option, and the default CPU.  */
250  int arch;
251  /* True if ".set sym32" is in effect.  */
252  bfd_boolean sym32;
253};
254
255/* True if -mgp32 was passed.  */
256static int file_mips_gp32 = -1;
257
258/* True if -mfp32 was passed.  */
259static int file_mips_fp32 = -1;
260
261/* This is the struct we use to hold the current set of options.  Note
262   that we must set the isa field to ISA_UNKNOWN and the ASE fields to
263   -1 to indicate that they have not been initialized.  */
264
265static struct mips_set_options mips_opts =
266{
267  ISA_UNKNOWN, -1, -1, -1, -1, -1, 0, 0, 0, 0, 0, 0, 0, 0, CPU_UNKNOWN, FALSE
268};
269
270/* These variables are filled in with the masks of registers used.
271   The object format code reads them and puts them in the appropriate
272   place.  */
273unsigned long mips_gprmask;
274unsigned long mips_cprmask[4];
275
276/* MIPS ISA we are using for this output file.  */
277static int file_mips_isa = ISA_UNKNOWN;
278
279/* True if -mips16 was passed or implied by arguments passed on the
280   command line (e.g., by -march).  */
281static int file_ase_mips16;
282
283/* True if -mips3d was passed or implied by arguments passed on the
284   command line (e.g., by -march).  */
285static int file_ase_mips3d;
286
287/* True if -mdmx was passed or implied by arguments passed on the
288   command line (e.g., by -march).  */
289static int file_ase_mdmx;
290
291/* True if -mdsp was passed or implied by arguments passed on the
292   command line (e.g., by -march).  */
293static int file_ase_dsp;
294
295/* True if -mmt was passed or implied by arguments passed on the
296   command line (e.g., by -march).  */
297static int file_ase_mt;
298
299/* The argument of the -march= flag.  The architecture we are assembling.  */
300static int file_mips_arch = CPU_UNKNOWN;
301static const char *mips_arch_string;
302
303/* The argument of the -mtune= flag.  The architecture for which we
304   are optimizing.  */
305static int mips_tune = CPU_UNKNOWN;
306static const char *mips_tune_string;
307
308/* True when generating 32-bit code for a 64-bit processor.  */
309static int mips_32bitmode = 0;
310
311/* True if the given ABI requires 32-bit registers.  */
312#define ABI_NEEDS_32BIT_REGS(ABI) ((ABI) == O32_ABI)
313
314/* Likewise 64-bit registers.  */
315#define ABI_NEEDS_64BIT_REGS(ABI) \
316  ((ABI) == N32_ABI 		  \
317   || (ABI) == N64_ABI		  \
318   || (ABI) == O64_ABI)
319
320/*  Return true if ISA supports 64 bit gp register instructions.  */
321#define ISA_HAS_64BIT_REGS(ISA) (    \
322   (ISA) == ISA_MIPS3                \
323   || (ISA) == ISA_MIPS4             \
324   || (ISA) == ISA_MIPS5             \
325   || (ISA) == ISA_MIPS64            \
326   || (ISA) == ISA_MIPS64R2          \
327   )
328
329/* Return true if ISA supports 64-bit right rotate (dror et al.)
330   instructions.  */
331#define ISA_HAS_DROR(ISA) (	\
332   (ISA) == ISA_MIPS64R2	\
333   )
334
335/* Return true if ISA supports 32-bit right rotate (ror et al.)
336   instructions.  */
337#define ISA_HAS_ROR(ISA) (	\
338   (ISA) == ISA_MIPS32R2	\
339   || (ISA) == ISA_MIPS64R2	\
340   )
341
342/* Return true if ISA supports ins instructions. */
343#define ISA_HAS_INS(ISA) ( \
344  (ISA) == ISA_MIPS32R2    \
345  || (ISA) == ISA_MIPS64R2 \
346  )
347
348#define HAVE_32BIT_GPRS		                   \
349    (mips_opts.gp32 || ! ISA_HAS_64BIT_REGS (mips_opts.isa))
350
351#define HAVE_32BIT_FPRS                            \
352    (mips_opts.fp32 || ! ISA_HAS_64BIT_REGS (mips_opts.isa))
353
354#define HAVE_64BIT_GPRS (! HAVE_32BIT_GPRS)
355#define HAVE_64BIT_FPRS (! HAVE_32BIT_FPRS)
356
357#define HAVE_NEWABI (mips_abi == N32_ABI || mips_abi == N64_ABI)
358
359#define HAVE_64BIT_OBJECTS (mips_abi == N64_ABI)
360
361/* True if relocations are stored in-place.  */
362#define HAVE_IN_PLACE_ADDENDS (!HAVE_NEWABI)
363
364/* The ABI-derived address size.  */
365#define HAVE_64BIT_ADDRESSES \
366  (HAVE_64BIT_GPRS && (mips_abi == EABI_ABI || mips_abi == N64_ABI))
367#define HAVE_32BIT_ADDRESSES (!HAVE_64BIT_ADDRESSES)
368
369/* The size of symbolic constants (i.e., expressions of the form
370   "SYMBOL" or "SYMBOL + OFFSET").  */
371#define HAVE_32BIT_SYMBOLS \
372  (HAVE_32BIT_ADDRESSES || !HAVE_64BIT_OBJECTS || mips_opts.sym32)
373#define HAVE_64BIT_SYMBOLS (!HAVE_32BIT_SYMBOLS)
374
375/* Addresses are loaded in different ways, depending on the address size
376   in use.  The n32 ABI Documentation also mandates the use of additions
377   with overflow checking, but existing implementations don't follow it.  */
378#define ADDRESS_ADD_INSN						\
379   (HAVE_32BIT_ADDRESSES ? "addu" : "daddu")
380
381#define ADDRESS_ADDI_INSN						\
382   (HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu")
383
384#define ADDRESS_LOAD_INSN						\
385   (HAVE_32BIT_ADDRESSES ? "lw" : "ld")
386
387#define ADDRESS_STORE_INSN						\
388   (HAVE_32BIT_ADDRESSES ? "sw" : "sd")
389
390/* Return true if the given CPU supports the MIPS16 ASE.  */
391#define CPU_HAS_MIPS16(cpu)						\
392   (strncmp (TARGET_CPU, "mips16", sizeof ("mips16") - 1) == 0		\
393    || strncmp (TARGET_CANONICAL, "mips-lsi-elf", sizeof ("mips-lsi-elf") - 1) == 0)
394
395/* Return true if the given CPU supports the MIPS3D ASE.  */
396#define CPU_HAS_MIPS3D(cpu)	((cpu) == CPU_SB1      \
397				 )
398
399/* Return true if the given CPU supports the MDMX ASE.  */
400#define CPU_HAS_MDMX(cpu)	(FALSE                 \
401				 )
402
403/* Return true if the given CPU supports the DSP ASE.  */
404#define CPU_HAS_DSP(cpu)	(FALSE                 \
405				 )
406
407/* Return true if the given CPU supports the MT ASE.  */
408#define CPU_HAS_MT(cpu)		(FALSE                 \
409				 )
410
411/* True if CPU has a dror instruction.  */
412#define CPU_HAS_DROR(CPU)	((CPU) == CPU_VR5400 || (CPU) == CPU_VR5500)
413
414/* True if CPU has a ror instruction.  */
415#define CPU_HAS_ROR(CPU)	CPU_HAS_DROR (CPU)
416
417/* True if mflo and mfhi can be immediately followed by instructions
418   which write to the HI and LO registers.
419
420   According to MIPS specifications, MIPS ISAs I, II, and III need
421   (at least) two instructions between the reads of HI/LO and
422   instructions which write them, and later ISAs do not.  Contradicting
423   the MIPS specifications, some MIPS IV processor user manuals (e.g.
424   the UM for the NEC Vr5000) document needing the instructions between
425   HI/LO reads and writes, as well.  Therefore, we declare only MIPS32,
426   MIPS64 and later ISAs to have the interlocks, plus any specific
427   earlier-ISA CPUs for which CPU documentation declares that the
428   instructions are really interlocked.  */
429#define hilo_interlocks \
430  (mips_opts.isa == ISA_MIPS32                        \
431   || mips_opts.isa == ISA_MIPS32R2                   \
432   || mips_opts.isa == ISA_MIPS64                     \
433   || mips_opts.isa == ISA_MIPS64R2                   \
434   || mips_opts.arch == CPU_R4010                     \
435   || mips_opts.arch == CPU_R10000                    \
436   || mips_opts.arch == CPU_R12000                    \
437   || mips_opts.arch == CPU_RM7000                    \
438   || mips_opts.arch == CPU_VR5500                    \
439   )
440
441/* Whether the processor uses hardware interlocks to protect reads
442   from the GPRs after they are loaded from memory, and thus does not
443   require nops to be inserted.  This applies to instructions marked
444   INSN_LOAD_MEMORY_DELAY.  These nops are only required at MIPS ISA
445   level I.  */
446#define gpr_interlocks \
447  (mips_opts.isa != ISA_MIPS1  \
448   || mips_opts.arch == CPU_R3900)
449
450/* Whether the processor uses hardware interlocks to avoid delays
451   required by coprocessor instructions, and thus does not require
452   nops to be inserted.  This applies to instructions marked
453   INSN_LOAD_COPROC_DELAY, INSN_COPROC_MOVE_DELAY, and to delays
454   between instructions marked INSN_WRITE_COND_CODE and ones marked
455   INSN_READ_COND_CODE.  These nops are only required at MIPS ISA
456   levels I, II, and III.  */
457/* Itbl support may require additional care here.  */
458#define cop_interlocks                                \
459  ((mips_opts.isa != ISA_MIPS1                        \
460    && mips_opts.isa != ISA_MIPS2                     \
461    && mips_opts.isa != ISA_MIPS3)                    \
462   || mips_opts.arch == CPU_R4300                     \
463   )
464
465/* Whether the processor uses hardware interlocks to protect reads
466   from coprocessor registers after they are loaded from memory, and
467   thus does not require nops to be inserted.  This applies to
468   instructions marked INSN_COPROC_MEMORY_DELAY.  These nops are only
469   requires at MIPS ISA level I.  */
470#define cop_mem_interlocks (mips_opts.isa != ISA_MIPS1)
471
472/* Is this a mfhi or mflo instruction?  */
473#define MF_HILO_INSN(PINFO) \
474          ((PINFO & INSN_READ_HI) || (PINFO & INSN_READ_LO))
475
476/* MIPS PIC level.  */
477
478enum mips_pic_level mips_pic;
479
480/* 1 if we should generate 32 bit offsets from the $gp register in
481   SVR4_PIC mode.  Currently has no meaning in other modes.  */
482static int mips_big_got = 0;
483
484/* 1 if trap instructions should used for overflow rather than break
485   instructions.  */
486static int mips_trap = 0;
487
488/* 1 if double width floating point constants should not be constructed
489   by assembling two single width halves into two single width floating
490   point registers which just happen to alias the double width destination
491   register.  On some architectures this aliasing can be disabled by a bit
492   in the status register, and the setting of this bit cannot be determined
493   automatically at assemble time.  */
494static int mips_disable_float_construction;
495
496/* Non-zero if any .set noreorder directives were used.  */
497
498static int mips_any_noreorder;
499
500/* Non-zero if nops should be inserted when the register referenced in
501   an mfhi/mflo instruction is read in the next two instructions.  */
502static int mips_7000_hilo_fix;
503
504/* The size of the small data section.  */
505static unsigned int g_switch_value = 8;
506/* Whether the -G option was used.  */
507static int g_switch_seen = 0;
508
509#define N_RMASK 0xc4
510#define N_VFP   0xd4
511
512/* If we can determine in advance that GP optimization won't be
513   possible, we can skip the relaxation stuff that tries to produce
514   GP-relative references.  This makes delay slot optimization work
515   better.
516
517   This function can only provide a guess, but it seems to work for
518   gcc output.  It needs to guess right for gcc, otherwise gcc
519   will put what it thinks is a GP-relative instruction in a branch
520   delay slot.
521
522   I don't know if a fix is needed for the SVR4_PIC mode.  I've only
523   fixed it for the non-PIC mode.  KR 95/04/07  */
524static int nopic_need_relax (symbolS *, int);
525
526/* handle of the OPCODE hash table */
527static struct hash_control *op_hash = NULL;
528
529/* The opcode hash table we use for the mips16.  */
530static struct hash_control *mips16_op_hash = NULL;
531
532/* This array holds the chars that always start a comment.  If the
533    pre-processor is disabled, these aren't very useful */
534const char comment_chars[] = "#";
535
536/* This array holds the chars that only start a comment at the beginning of
537   a line.  If the line seems to have the form '# 123 filename'
538   .line and .file directives will appear in the pre-processed output */
539/* Note that input_file.c hand checks for '#' at the beginning of the
540   first line of the input file.  This is because the compiler outputs
541   #NO_APP at the beginning of its output.  */
542/* Also note that C style comments are always supported.  */
543const char line_comment_chars[] = "#";
544
545/* This array holds machine specific line separator characters.  */
546const char line_separator_chars[] = ";";
547
548/* Chars that can be used to separate mant from exp in floating point nums */
549const char EXP_CHARS[] = "eE";
550
551/* Chars that mean this number is a floating point constant */
552/* As in 0f12.456 */
553/* or    0d1.2345e12 */
554const char FLT_CHARS[] = "rRsSfFdDxXpP";
555
556/* Also be aware that MAXIMUM_NUMBER_OF_CHARS_FOR_FLOAT may have to be
557   changed in read.c .  Ideally it shouldn't have to know about it at all,
558   but nothing is ideal around here.
559 */
560
561static char *insn_error;
562
563static int auto_align = 1;
564
565/* When outputting SVR4 PIC code, the assembler needs to know the
566   offset in the stack frame from which to restore the $gp register.
567   This is set by the .cprestore pseudo-op, and saved in this
568   variable.  */
569static offsetT mips_cprestore_offset = -1;
570
571/* Similar for NewABI PIC code, where $gp is callee-saved.  NewABI has some
572   more optimizations, it can use a register value instead of a memory-saved
573   offset and even an other register than $gp as global pointer.  */
574static offsetT mips_cpreturn_offset = -1;
575static int mips_cpreturn_register = -1;
576static int mips_gp_register = GP;
577static int mips_gprel_offset = 0;
578
579/* Whether mips_cprestore_offset has been set in the current function
580   (or whether it has already been warned about, if not).  */
581static int mips_cprestore_valid = 0;
582
583/* This is the register which holds the stack frame, as set by the
584   .frame pseudo-op.  This is needed to implement .cprestore.  */
585static int mips_frame_reg = SP;
586
587/* Whether mips_frame_reg has been set in the current function
588   (or whether it has already been warned about, if not).  */
589static int mips_frame_reg_valid = 0;
590
591/* To output NOP instructions correctly, we need to keep information
592   about the previous two instructions.  */
593
594/* Whether we are optimizing.  The default value of 2 means to remove
595   unneeded NOPs and swap branch instructions when possible.  A value
596   of 1 means to not swap branches.  A value of 0 means to always
597   insert NOPs.  */
598static int mips_optimize = 2;
599
600/* Debugging level.  -g sets this to 2.  -gN sets this to N.  -g0 is
601   equivalent to seeing no -g option at all.  */
602static int mips_debug = 0;
603
604/* The maximum number of NOPs needed to avoid the VR4130 mflo/mfhi errata.  */
605#define MAX_VR4130_NOPS 4
606
607/* The maximum number of NOPs needed to fill delay slots.  */
608#define MAX_DELAY_NOPS 2
609
610/* The maximum number of NOPs needed for any purpose.  */
611#define MAX_NOPS 4
612
613/* A list of previous instructions, with index 0 being the most recent.
614   We need to look back MAX_NOPS instructions when filling delay slots
615   or working around processor errata.  We need to look back one
616   instruction further if we're thinking about using history[0] to
617   fill a branch delay slot.  */
618static struct mips_cl_insn history[1 + MAX_NOPS];
619
620/* Nop instructions used by emit_nop.  */
621static struct mips_cl_insn nop_insn, mips16_nop_insn;
622
623/* The appropriate nop for the current mode.  */
624#define NOP_INSN (mips_opts.mips16 ? &mips16_nop_insn : &nop_insn)
625
626/* If this is set, it points to a frag holding nop instructions which
627   were inserted before the start of a noreorder section.  If those
628   nops turn out to be unnecessary, the size of the frag can be
629   decreased.  */
630static fragS *prev_nop_frag;
631
632/* The number of nop instructions we created in prev_nop_frag.  */
633static int prev_nop_frag_holds;
634
635/* The number of nop instructions that we know we need in
636   prev_nop_frag.  */
637static int prev_nop_frag_required;
638
639/* The number of instructions we've seen since prev_nop_frag.  */
640static int prev_nop_frag_since;
641
642/* For ECOFF and ELF, relocations against symbols are done in two
643   parts, with a HI relocation and a LO relocation.  Each relocation
644   has only 16 bits of space to store an addend.  This means that in
645   order for the linker to handle carries correctly, it must be able
646   to locate both the HI and the LO relocation.  This means that the
647   relocations must appear in order in the relocation table.
648
649   In order to implement this, we keep track of each unmatched HI
650   relocation.  We then sort them so that they immediately precede the
651   corresponding LO relocation.  */
652
653struct mips_hi_fixup
654{
655  /* Next HI fixup.  */
656  struct mips_hi_fixup *next;
657  /* This fixup.  */
658  fixS *fixp;
659  /* The section this fixup is in.  */
660  segT seg;
661};
662
663/* The list of unmatched HI relocs.  */
664
665static struct mips_hi_fixup *mips_hi_fixup_list;
666
667/* The frag containing the last explicit relocation operator.
668   Null if explicit relocations have not been used.  */
669
670static fragS *prev_reloc_op_frag;
671
672/* Map normal MIPS register numbers to mips16 register numbers.  */
673
674#define X ILLEGAL_REG
675static const int mips32_to_16_reg_map[] =
676{
677  X, X, 2, 3, 4, 5, 6, 7,
678  X, X, X, X, X, X, X, X,
679  0, 1, X, X, X, X, X, X,
680  X, X, X, X, X, X, X, X
681};
682#undef X
683
684/* Map mips16 register numbers to normal MIPS register numbers.  */
685
686static const unsigned int mips16_to_32_reg_map[] =
687{
688  16, 17, 2, 3, 4, 5, 6, 7
689};
690
691/* Classifies the kind of instructions we're interested in when
692   implementing -mfix-vr4120.  */
693enum fix_vr4120_class {
694  FIX_VR4120_MACC,
695  FIX_VR4120_DMACC,
696  FIX_VR4120_MULT,
697  FIX_VR4120_DMULT,
698  FIX_VR4120_DIV,
699  FIX_VR4120_MTHILO,
700  NUM_FIX_VR4120_CLASSES
701};
702
703/* Given two FIX_VR4120_* values X and Y, bit Y of element X is set if
704   there must be at least one other instruction between an instruction
705   of type X and an instruction of type Y.  */
706static unsigned int vr4120_conflicts[NUM_FIX_VR4120_CLASSES];
707
708/* True if -mfix-vr4120 is in force.  */
709static int mips_fix_vr4120;
710
711/* ...likewise -mfix-vr4130.  */
712static int mips_fix_vr4130;
713
714/* We don't relax branches by default, since this causes us to expand
715   `la .l2 - .l1' if there's a branch between .l1 and .l2, because we
716   fail to compute the offset before expanding the macro to the most
717   efficient expansion.  */
718
719static int mips_relax_branch;
720
721/* The expansion of many macros depends on the type of symbol that
722   they refer to.  For example, when generating position-dependent code,
723   a macro that refers to a symbol may have two different expansions,
724   one which uses GP-relative addresses and one which uses absolute
725   addresses.  When generating SVR4-style PIC, a macro may have
726   different expansions for local and global symbols.
727
728   We handle these situations by generating both sequences and putting
729   them in variant frags.  In position-dependent code, the first sequence
730   will be the GP-relative one and the second sequence will be the
731   absolute one.  In SVR4 PIC, the first sequence will be for global
732   symbols and the second will be for local symbols.
733
734   The frag's "subtype" is RELAX_ENCODE (FIRST, SECOND), where FIRST and
735   SECOND are the lengths of the two sequences in bytes.  These fields
736   can be extracted using RELAX_FIRST() and RELAX_SECOND().  In addition,
737   the subtype has the following flags:
738
739   RELAX_USE_SECOND
740	Set if it has been decided that we should use the second
741	sequence instead of the first.
742
743   RELAX_SECOND_LONGER
744	Set in the first variant frag if the macro's second implementation
745	is longer than its first.  This refers to the macro as a whole,
746	not an individual relaxation.
747
748   RELAX_NOMACRO
749	Set in the first variant frag if the macro appeared in a .set nomacro
750	block and if one alternative requires a warning but the other does not.
751
752   RELAX_DELAY_SLOT
753	Like RELAX_NOMACRO, but indicates that the macro appears in a branch
754	delay slot.
755
756   The frag's "opcode" points to the first fixup for relaxable code.
757
758   Relaxable macros are generated using a sequence such as:
759
760      relax_start (SYMBOL);
761      ... generate first expansion ...
762      relax_switch ();
763      ... generate second expansion ...
764      relax_end ();
765
766   The code and fixups for the unwanted alternative are discarded
767   by md_convert_frag.  */
768#define RELAX_ENCODE(FIRST, SECOND) (((FIRST) << 8) | (SECOND))
769
770#define RELAX_FIRST(X) (((X) >> 8) & 0xff)
771#define RELAX_SECOND(X) ((X) & 0xff)
772#define RELAX_USE_SECOND 0x10000
773#define RELAX_SECOND_LONGER 0x20000
774#define RELAX_NOMACRO 0x40000
775#define RELAX_DELAY_SLOT 0x80000
776
777/* Branch without likely bit.  If label is out of range, we turn:
778
779 	beq reg1, reg2, label
780	delay slot
781
782   into
783
784        bne reg1, reg2, 0f
785        nop
786        j label
787     0: delay slot
788
789   with the following opcode replacements:
790
791	beq <-> bne
792	blez <-> bgtz
793	bltz <-> bgez
794	bc1f <-> bc1t
795
796	bltzal <-> bgezal  (with jal label instead of j label)
797
798   Even though keeping the delay slot instruction in the delay slot of
799   the branch would be more efficient, it would be very tricky to do
800   correctly, because we'd have to introduce a variable frag *after*
801   the delay slot instruction, and expand that instead.  Let's do it
802   the easy way for now, even if the branch-not-taken case now costs
803   one additional instruction.  Out-of-range branches are not supposed
804   to be common, anyway.
805
806   Branch likely.  If label is out of range, we turn:
807
808	beql reg1, reg2, label
809	delay slot (annulled if branch not taken)
810
811   into
812
813        beql reg1, reg2, 1f
814        nop
815        beql $0, $0, 2f
816        nop
817     1: j[al] label
818        delay slot (executed only if branch taken)
819     2:
820
821   It would be possible to generate a shorter sequence by losing the
822   likely bit, generating something like:
823
824	bne reg1, reg2, 0f
825	nop
826	j[al] label
827	delay slot (executed only if branch taken)
828     0:
829
830	beql -> bne
831	bnel -> beq
832	blezl -> bgtz
833	bgtzl -> blez
834	bltzl -> bgez
835	bgezl -> bltz
836	bc1fl -> bc1t
837	bc1tl -> bc1f
838
839	bltzall -> bgezal  (with jal label instead of j label)
840	bgezall -> bltzal  (ditto)
841
842
843   but it's not clear that it would actually improve performance.  */
844#define RELAX_BRANCH_ENCODE(uncond, likely, link, toofar) \
845  ((relax_substateT) \
846   (0xc0000000 \
847    | ((toofar) ? 1 : 0) \
848    | ((link) ? 2 : 0) \
849    | ((likely) ? 4 : 0) \
850    | ((uncond) ? 8 : 0)))
851#define RELAX_BRANCH_P(i) (((i) & 0xf0000000) == 0xc0000000)
852#define RELAX_BRANCH_UNCOND(i) (((i) & 8) != 0)
853#define RELAX_BRANCH_LIKELY(i) (((i) & 4) != 0)
854#define RELAX_BRANCH_LINK(i) (((i) & 2) != 0)
855#define RELAX_BRANCH_TOOFAR(i) (((i) & 1) != 0)
856
857/* For mips16 code, we use an entirely different form of relaxation.
858   mips16 supports two versions of most instructions which take
859   immediate values: a small one which takes some small value, and a
860   larger one which takes a 16 bit value.  Since branches also follow
861   this pattern, relaxing these values is required.
862
863   We can assemble both mips16 and normal MIPS code in a single
864   object.  Therefore, we need to support this type of relaxation at
865   the same time that we support the relaxation described above.  We
866   use the high bit of the subtype field to distinguish these cases.
867
868   The information we store for this type of relaxation is the
869   argument code found in the opcode file for this relocation, whether
870   the user explicitly requested a small or extended form, and whether
871   the relocation is in a jump or jal delay slot.  That tells us the
872   size of the value, and how it should be stored.  We also store
873   whether the fragment is considered to be extended or not.  We also
874   store whether this is known to be a branch to a different section,
875   whether we have tried to relax this frag yet, and whether we have
876   ever extended a PC relative fragment because of a shift count.  */
877#define RELAX_MIPS16_ENCODE(type, small, ext, dslot, jal_dslot)	\
878  (0x80000000							\
879   | ((type) & 0xff)						\
880   | ((small) ? 0x100 : 0)					\
881   | ((ext) ? 0x200 : 0)					\
882   | ((dslot) ? 0x400 : 0)					\
883   | ((jal_dslot) ? 0x800 : 0))
884#define RELAX_MIPS16_P(i) (((i) & 0xc0000000) == 0x80000000)
885#define RELAX_MIPS16_TYPE(i) ((i) & 0xff)
886#define RELAX_MIPS16_USER_SMALL(i) (((i) & 0x100) != 0)
887#define RELAX_MIPS16_USER_EXT(i) (((i) & 0x200) != 0)
888#define RELAX_MIPS16_DSLOT(i) (((i) & 0x400) != 0)
889#define RELAX_MIPS16_JAL_DSLOT(i) (((i) & 0x800) != 0)
890#define RELAX_MIPS16_EXTENDED(i) (((i) & 0x1000) != 0)
891#define RELAX_MIPS16_MARK_EXTENDED(i) ((i) | 0x1000)
892#define RELAX_MIPS16_CLEAR_EXTENDED(i) ((i) &~ 0x1000)
893#define RELAX_MIPS16_LONG_BRANCH(i) (((i) & 0x2000) != 0)
894#define RELAX_MIPS16_MARK_LONG_BRANCH(i) ((i) | 0x2000)
895#define RELAX_MIPS16_CLEAR_LONG_BRANCH(i) ((i) &~ 0x2000)
896
897/* Is the given value a sign-extended 32-bit value?  */
898#define IS_SEXT_32BIT_NUM(x)						\
899  (((x) &~ (offsetT) 0x7fffffff) == 0					\
900   || (((x) &~ (offsetT) 0x7fffffff) == ~ (offsetT) 0x7fffffff))
901
902/* Is the given value a sign-extended 16-bit value?  */
903#define IS_SEXT_16BIT_NUM(x)						\
904  (((x) &~ (offsetT) 0x7fff) == 0					\
905   || (((x) &~ (offsetT) 0x7fff) == ~ (offsetT) 0x7fff))
906
907/* Is the given value a zero-extended 32-bit value?  Or a negated one?  */
908#define IS_ZEXT_32BIT_NUM(x)						\
909  (((x) &~ (offsetT) 0xffffffff) == 0					\
910   || (((x) &~ (offsetT) 0xffffffff) == ~ (offsetT) 0xffffffff))
911
912/* Replace bits MASK << SHIFT of STRUCT with the equivalent bits in
913   VALUE << SHIFT.  VALUE is evaluated exactly once.  */
914#define INSERT_BITS(STRUCT, VALUE, MASK, SHIFT) \
915  (STRUCT) = (((STRUCT) & ~((MASK) << (SHIFT))) \
916	      | (((VALUE) & (MASK)) << (SHIFT)))
917
918/* Extract bits MASK << SHIFT from STRUCT and shift them right
919   SHIFT places.  */
920#define EXTRACT_BITS(STRUCT, MASK, SHIFT) \
921  (((STRUCT) >> (SHIFT)) & (MASK))
922
923/* Change INSN's opcode so that the operand given by FIELD has value VALUE.
924   INSN is a mips_cl_insn structure and VALUE is evaluated exactly once.
925
926   include/opcode/mips.h specifies operand fields using the macros
927   OP_MASK_<FIELD> and OP_SH_<FIELD>.  The MIPS16 equivalents start
928   with "MIPS16OP" instead of "OP".  */
929#define INSERT_OPERAND(FIELD, INSN, VALUE) \
930  INSERT_BITS ((INSN).insn_opcode, VALUE, OP_MASK_##FIELD, OP_SH_##FIELD)
931#define MIPS16_INSERT_OPERAND(FIELD, INSN, VALUE) \
932  INSERT_BITS ((INSN).insn_opcode, VALUE, \
933		MIPS16OP_MASK_##FIELD, MIPS16OP_SH_##FIELD)
934
935/* Extract the operand given by FIELD from mips_cl_insn INSN.  */
936#define EXTRACT_OPERAND(FIELD, INSN) \
937  EXTRACT_BITS ((INSN).insn_opcode, OP_MASK_##FIELD, OP_SH_##FIELD)
938#define MIPS16_EXTRACT_OPERAND(FIELD, INSN) \
939  EXTRACT_BITS ((INSN).insn_opcode, \
940		MIPS16OP_MASK_##FIELD, \
941		MIPS16OP_SH_##FIELD)
942
943/* Global variables used when generating relaxable macros.  See the
944   comment above RELAX_ENCODE for more details about how relaxation
945   is used.  */
946static struct {
947  /* 0 if we're not emitting a relaxable macro.
948     1 if we're emitting the first of the two relaxation alternatives.
949     2 if we're emitting the second alternative.  */
950  int sequence;
951
952  /* The first relaxable fixup in the current frag.  (In other words,
953     the first fixup that refers to relaxable code.)  */
954  fixS *first_fixup;
955
956  /* sizes[0] says how many bytes of the first alternative are stored in
957     the current frag.  Likewise sizes[1] for the second alternative.  */
958  unsigned int sizes[2];
959
960  /* The symbol on which the choice of sequence depends.  */
961  symbolS *symbol;
962} mips_relax;
963
964/* Global variables used to decide whether a macro needs a warning.  */
965static struct {
966  /* True if the macro is in a branch delay slot.  */
967  bfd_boolean delay_slot_p;
968
969  /* For relaxable macros, sizes[0] is the length of the first alternative
970     in bytes and sizes[1] is the length of the second alternative.
971     For non-relaxable macros, both elements give the length of the
972     macro in bytes.  */
973  unsigned int sizes[2];
974
975  /* The first variant frag for this macro.  */
976  fragS *first_frag;
977} mips_macro_warning;
978
979/* Prototypes for static functions.  */
980
981#define internalError()							\
982    as_fatal (_("internal Error, line %d, %s"), __LINE__, __FILE__)
983
984enum mips_regclass { MIPS_GR_REG, MIPS_FP_REG, MIPS16_REG };
985
986static void append_insn
987  (struct mips_cl_insn *ip, expressionS *p, bfd_reloc_code_real_type *r);
988static void mips_no_prev_insn (void);
989static void mips16_macro_build
990  (expressionS *, const char *, const char *, va_list);
991static void load_register (int, expressionS *, int);
992static void macro_start (void);
993static void macro_end (void);
994static void macro (struct mips_cl_insn * ip);
995static void mips16_macro (struct mips_cl_insn * ip);
996#ifdef LOSING_COMPILER
997static void macro2 (struct mips_cl_insn * ip);
998#endif
999static void mips_ip (char *str, struct mips_cl_insn * ip);
1000static void mips16_ip (char *str, struct mips_cl_insn * ip);
1001static void mips16_immed
1002  (char *, unsigned int, int, offsetT, bfd_boolean, bfd_boolean, bfd_boolean,
1003   unsigned long *, bfd_boolean *, unsigned short *);
1004static size_t my_getSmallExpression
1005  (expressionS *, bfd_reloc_code_real_type *, char *);
1006static void my_getExpression (expressionS *, char *);
1007static void s_align (int);
1008static void s_change_sec (int);
1009static void s_change_section (int);
1010static void s_cons (int);
1011static void s_float_cons (int);
1012static void s_mips_globl (int);
1013static void s_option (int);
1014static void s_mipsset (int);
1015static void s_abicalls (int);
1016static void s_cpload (int);
1017static void s_cpsetup (int);
1018static void s_cplocal (int);
1019static void s_cprestore (int);
1020static void s_cpreturn (int);
1021static void s_gpvalue (int);
1022static void s_gpword (int);
1023static void s_gpdword (int);
1024static void s_cpadd (int);
1025static void s_insn (int);
1026static void md_obj_begin (void);
1027static void md_obj_end (void);
1028static void s_mips_ent (int);
1029static void s_mips_end (int);
1030static void s_mips_frame (int);
1031static void s_mips_mask (int reg_type);
1032static void s_mips_stab (int);
1033static void s_mips_weakext (int);
1034static void s_mips_file (int);
1035static void s_mips_loc (int);
1036static bfd_boolean pic_need_relax (symbolS *, asection *);
1037static int relaxed_branch_length (fragS *, asection *, int);
1038static int validate_mips_insn (const struct mips_opcode *);
1039
1040/* Table and functions used to map between CPU/ISA names, and
1041   ISA levels, and CPU numbers.  */
1042
1043struct mips_cpu_info
1044{
1045  const char *name;           /* CPU or ISA name.  */
1046  int is_isa;                 /* Is this an ISA?  (If 0, a CPU.) */
1047  int isa;                    /* ISA level.  */
1048  int cpu;                    /* CPU number (default CPU if ISA).  */
1049};
1050
1051static const struct mips_cpu_info *mips_parse_cpu (const char *, const char *);
1052static const struct mips_cpu_info *mips_cpu_info_from_isa (int);
1053static const struct mips_cpu_info *mips_cpu_info_from_arch (int);
1054
1055/* Pseudo-op table.
1056
1057   The following pseudo-ops from the Kane and Heinrich MIPS book
1058   should be defined here, but are currently unsupported: .alias,
1059   .galive, .gjaldef, .gjrlive, .livereg, .noalias.
1060
1061   The following pseudo-ops from the Kane and Heinrich MIPS book are
1062   specific to the type of debugging information being generated, and
1063   should be defined by the object format: .aent, .begin, .bend,
1064   .bgnb, .end, .endb, .ent, .fmask, .frame, .loc, .mask, .verstamp,
1065   .vreg.
1066
1067   The following pseudo-ops from the Kane and Heinrich MIPS book are
1068   not MIPS CPU specific, but are also not specific to the object file
1069   format.  This file is probably the best place to define them, but
1070   they are not currently supported: .asm0, .endr, .lab, .repeat,
1071   .struct.  */
1072
1073static const pseudo_typeS mips_pseudo_table[] =
1074{
1075  /* MIPS specific pseudo-ops.  */
1076  {"option", s_option, 0},
1077  {"set", s_mipsset, 0},
1078  {"rdata", s_change_sec, 'r'},
1079  {"sdata", s_change_sec, 's'},
1080  {"livereg", s_ignore, 0},
1081  {"abicalls", s_abicalls, 0},
1082  {"cpload", s_cpload, 0},
1083  {"cpsetup", s_cpsetup, 0},
1084  {"cplocal", s_cplocal, 0},
1085  {"cprestore", s_cprestore, 0},
1086  {"cpreturn", s_cpreturn, 0},
1087  {"gpvalue", s_gpvalue, 0},
1088  {"gpword", s_gpword, 0},
1089  {"gpdword", s_gpdword, 0},
1090  {"cpadd", s_cpadd, 0},
1091  {"insn", s_insn, 0},
1092
1093  /* Relatively generic pseudo-ops that happen to be used on MIPS
1094     chips.  */
1095  {"asciiz", stringer, 1},
1096  {"bss", s_change_sec, 'b'},
1097  {"err", s_err, 0},
1098  {"half", s_cons, 1},
1099  {"dword", s_cons, 3},
1100  {"weakext", s_mips_weakext, 0},
1101
1102  /* These pseudo-ops are defined in read.c, but must be overridden
1103     here for one reason or another.  */
1104  {"align", s_align, 0},
1105  {"byte", s_cons, 0},
1106  {"data", s_change_sec, 'd'},
1107  {"double", s_float_cons, 'd'},
1108  {"float", s_float_cons, 'f'},
1109  {"globl", s_mips_globl, 0},
1110  {"global", s_mips_globl, 0},
1111  {"hword", s_cons, 1},
1112  {"int", s_cons, 2},
1113  {"long", s_cons, 2},
1114  {"octa", s_cons, 4},
1115  {"quad", s_cons, 3},
1116  {"section", s_change_section, 0},
1117  {"short", s_cons, 1},
1118  {"single", s_float_cons, 'f'},
1119  {"stabn", s_mips_stab, 'n'},
1120  {"text", s_change_sec, 't'},
1121  {"word", s_cons, 2},
1122
1123  { "extern", ecoff_directive_extern, 0},
1124
1125  { NULL, NULL, 0 },
1126};
1127
1128static const pseudo_typeS mips_nonecoff_pseudo_table[] =
1129{
1130  /* These pseudo-ops should be defined by the object file format.
1131     However, a.out doesn't support them, so we have versions here.  */
1132  {"aent", s_mips_ent, 1},
1133  {"bgnb", s_ignore, 0},
1134  {"end", s_mips_end, 0},
1135  {"endb", s_ignore, 0},
1136  {"ent", s_mips_ent, 0},
1137  {"file", s_mips_file, 0},
1138  {"fmask", s_mips_mask, 'F'},
1139  {"frame", s_mips_frame, 0},
1140  {"loc", s_mips_loc, 0},
1141  {"mask", s_mips_mask, 'R'},
1142  {"verstamp", s_ignore, 0},
1143  { NULL, NULL, 0 },
1144};
1145
1146extern void pop_insert (const pseudo_typeS *);
1147
1148void
1149mips_pop_insert (void)
1150{
1151  pop_insert (mips_pseudo_table);
1152  if (! ECOFF_DEBUGGING)
1153    pop_insert (mips_nonecoff_pseudo_table);
1154}
1155
1156/* Symbols labelling the current insn.  */
1157
1158struct insn_label_list
1159{
1160  struct insn_label_list *next;
1161  symbolS *label;
1162};
1163
1164static struct insn_label_list *insn_labels;
1165static struct insn_label_list *free_insn_labels;
1166
1167static void mips_clear_insn_labels (void);
1168
1169static inline void
1170mips_clear_insn_labels (void)
1171{
1172  register struct insn_label_list **pl;
1173
1174  for (pl = &free_insn_labels; *pl != NULL; pl = &(*pl)->next)
1175    ;
1176  *pl = insn_labels;
1177  insn_labels = NULL;
1178}
1179
1180static char *expr_end;
1181
1182/* Expressions which appear in instructions.  These are set by
1183   mips_ip.  */
1184
1185static expressionS imm_expr;
1186static expressionS imm2_expr;
1187static expressionS offset_expr;
1188
1189/* Relocs associated with imm_expr and offset_expr.  */
1190
1191static bfd_reloc_code_real_type imm_reloc[3]
1192  = {BFD_RELOC_UNUSED, BFD_RELOC_UNUSED, BFD_RELOC_UNUSED};
1193static bfd_reloc_code_real_type offset_reloc[3]
1194  = {BFD_RELOC_UNUSED, BFD_RELOC_UNUSED, BFD_RELOC_UNUSED};
1195
1196/* These are set by mips16_ip if an explicit extension is used.  */
1197
1198static bfd_boolean mips16_small, mips16_ext;
1199
1200#ifdef OBJ_ELF
1201/* The pdr segment for per procedure frame/regmask info.  Not used for
1202   ECOFF debugging.  */
1203
1204static segT pdr_seg;
1205#endif
1206
1207/* The default target format to use.  */
1208
1209const char *
1210mips_target_format (void)
1211{
1212  switch (OUTPUT_FLAVOR)
1213    {
1214    case bfd_target_ecoff_flavour:
1215      return target_big_endian ? "ecoff-bigmips" : ECOFF_LITTLE_FORMAT;
1216    case bfd_target_coff_flavour:
1217      return "pe-mips";
1218    case bfd_target_elf_flavour:
1219#ifdef TE_TMIPS
1220      /* This is traditional mips.  */
1221      return (target_big_endian
1222	      ? (HAVE_64BIT_OBJECTS
1223		 ? "elf64-tradbigmips"
1224		 : (HAVE_NEWABI
1225		    ? "elf32-ntradbigmips" : "elf32-tradbigmips"))
1226	      : (HAVE_64BIT_OBJECTS
1227		 ? "elf64-tradlittlemips"
1228		 : (HAVE_NEWABI
1229		    ? "elf32-ntradlittlemips" : "elf32-tradlittlemips")));
1230#else
1231      return (target_big_endian
1232	      ? (HAVE_64BIT_OBJECTS
1233		 ? "elf64-bigmips"
1234		 : (HAVE_NEWABI
1235		    ? "elf32-nbigmips" : "elf32-bigmips"))
1236	      : (HAVE_64BIT_OBJECTS
1237		 ? "elf64-littlemips"
1238		 : (HAVE_NEWABI
1239		    ? "elf32-nlittlemips" : "elf32-littlemips")));
1240#endif
1241    default:
1242      abort ();
1243      return NULL;
1244    }
1245}
1246
1247/* Return the length of instruction INSN.  */
1248
1249static inline unsigned int
1250insn_length (const struct mips_cl_insn *insn)
1251{
1252  if (!mips_opts.mips16)
1253    return 4;
1254  return insn->mips16_absolute_jump_p || insn->use_extend ? 4 : 2;
1255}
1256
1257/* Initialise INSN from opcode entry MO.  Leave its position unspecified.  */
1258
1259static void
1260create_insn (struct mips_cl_insn *insn, const struct mips_opcode *mo)
1261{
1262  size_t i;
1263
1264  insn->insn_mo = mo;
1265  insn->use_extend = FALSE;
1266  insn->extend = 0;
1267  insn->insn_opcode = mo->match;
1268  insn->frag = NULL;
1269  insn->where = 0;
1270  for (i = 0; i < ARRAY_SIZE (insn->fixp); i++)
1271    insn->fixp[i] = NULL;
1272  insn->fixed_p = (mips_opts.noreorder > 0);
1273  insn->noreorder_p = (mips_opts.noreorder > 0);
1274  insn->mips16_absolute_jump_p = 0;
1275}
1276
1277/* Install INSN at the location specified by its "frag" and "where" fields.  */
1278
1279static void
1280install_insn (const struct mips_cl_insn *insn)
1281{
1282  char *f = insn->frag->fr_literal + insn->where;
1283  if (!mips_opts.mips16)
1284    md_number_to_chars (f, insn->insn_opcode, 4);
1285  else if (insn->mips16_absolute_jump_p)
1286    {
1287      md_number_to_chars (f, insn->insn_opcode >> 16, 2);
1288      md_number_to_chars (f + 2, insn->insn_opcode & 0xffff, 2);
1289    }
1290  else
1291    {
1292      if (insn->use_extend)
1293	{
1294	  md_number_to_chars (f, 0xf000 | insn->extend, 2);
1295	  f += 2;
1296	}
1297      md_number_to_chars (f, insn->insn_opcode, 2);
1298    }
1299}
1300
1301/* Move INSN to offset WHERE in FRAG.  Adjust the fixups accordingly
1302   and install the opcode in the new location.  */
1303
1304static void
1305move_insn (struct mips_cl_insn *insn, fragS *frag, long where)
1306{
1307  size_t i;
1308
1309  insn->frag = frag;
1310  insn->where = where;
1311  for (i = 0; i < ARRAY_SIZE (insn->fixp); i++)
1312    if (insn->fixp[i] != NULL)
1313      {
1314	insn->fixp[i]->fx_frag = frag;
1315	insn->fixp[i]->fx_where = where;
1316      }
1317  install_insn (insn);
1318}
1319
1320/* Add INSN to the end of the output.  */
1321
1322static void
1323add_fixed_insn (struct mips_cl_insn *insn)
1324{
1325  char *f = frag_more (insn_length (insn));
1326  move_insn (insn, frag_now, f - frag_now->fr_literal);
1327}
1328
1329/* Start a variant frag and move INSN to the start of the variant part,
1330   marking it as fixed.  The other arguments are as for frag_var.  */
1331
1332static void
1333add_relaxed_insn (struct mips_cl_insn *insn, int max_chars, int var,
1334		  relax_substateT subtype, symbolS *symbol, offsetT offset)
1335{
1336  frag_grow (max_chars);
1337  move_insn (insn, frag_now, frag_more (0) - frag_now->fr_literal);
1338  insn->fixed_p = 1;
1339  frag_var (rs_machine_dependent, max_chars, var,
1340	    subtype, symbol, offset, NULL);
1341}
1342
1343/* Insert N copies of INSN into the history buffer, starting at
1344   position FIRST.  Neither FIRST nor N need to be clipped.  */
1345
1346static void
1347insert_into_history (unsigned int first, unsigned int n,
1348		     const struct mips_cl_insn *insn)
1349{
1350  if (mips_relax.sequence != 2)
1351    {
1352      unsigned int i;
1353
1354      for (i = ARRAY_SIZE (history); i-- > first;)
1355	if (i >= first + n)
1356	  history[i] = history[i - n];
1357	else
1358	  history[i] = *insn;
1359    }
1360}
1361
1362/* Emit a nop instruction, recording it in the history buffer.  */
1363
1364static void
1365emit_nop (void)
1366{
1367  add_fixed_insn (NOP_INSN);
1368  insert_into_history (0, 1, NOP_INSN);
1369}
1370
1371/* Initialize vr4120_conflicts.  There is a bit of duplication here:
1372   the idea is to make it obvious at a glance that each errata is
1373   included.  */
1374
1375static void
1376init_vr4120_conflicts (void)
1377{
1378#define CONFLICT(FIRST, SECOND) \
1379    vr4120_conflicts[FIX_VR4120_##FIRST] |= 1 << FIX_VR4120_##SECOND
1380
1381  /* Errata 21 - [D]DIV[U] after [D]MACC */
1382  CONFLICT (MACC, DIV);
1383  CONFLICT (DMACC, DIV);
1384
1385  /* Errata 23 - Continuous DMULT[U]/DMACC instructions.  */
1386  CONFLICT (DMULT, DMULT);
1387  CONFLICT (DMULT, DMACC);
1388  CONFLICT (DMACC, DMULT);
1389  CONFLICT (DMACC, DMACC);
1390
1391  /* Errata 24 - MT{LO,HI} after [D]MACC */
1392  CONFLICT (MACC, MTHILO);
1393  CONFLICT (DMACC, MTHILO);
1394
1395  /* VR4181A errata MD(1): "If a MULT, MULTU, DMULT or DMULTU
1396     instruction is executed immediately after a MACC or DMACC
1397     instruction, the result of [either instruction] is incorrect."  */
1398  CONFLICT (MACC, MULT);
1399  CONFLICT (MACC, DMULT);
1400  CONFLICT (DMACC, MULT);
1401  CONFLICT (DMACC, DMULT);
1402
1403  /* VR4181A errata MD(4): "If a MACC or DMACC instruction is
1404     executed immediately after a DMULT, DMULTU, DIV, DIVU,
1405     DDIV or DDIVU instruction, the result of the MACC or
1406     DMACC instruction is incorrect.".  */
1407  CONFLICT (DMULT, MACC);
1408  CONFLICT (DMULT, DMACC);
1409  CONFLICT (DIV, MACC);
1410  CONFLICT (DIV, DMACC);
1411
1412#undef CONFLICT
1413}
1414
1415/* This function is called once, at assembler startup time.  It should
1416   set up all the tables, etc. that the MD part of the assembler will need.  */
1417
1418void
1419md_begin (void)
1420{
1421  register const char *retval = NULL;
1422  int i = 0;
1423  int broken = 0;
1424
1425  if (mips_pic != NO_PIC)
1426    {
1427      if (g_switch_seen && g_switch_value != 0)
1428	as_bad (_("-G may not be used in position-independent code"));
1429      g_switch_value = 0;
1430    }
1431
1432  if (! bfd_set_arch_mach (stdoutput, bfd_arch_mips, file_mips_arch))
1433    as_warn (_("Could not set architecture and machine"));
1434
1435  op_hash = hash_new ();
1436
1437  for (i = 0; i < NUMOPCODES;)
1438    {
1439      const char *name = mips_opcodes[i].name;
1440
1441      retval = hash_insert (op_hash, name, (void *) &mips_opcodes[i]);
1442      if (retval != NULL)
1443	{
1444	  fprintf (stderr, _("internal error: can't hash `%s': %s\n"),
1445		   mips_opcodes[i].name, retval);
1446	  /* Probably a memory allocation problem?  Give up now.  */
1447	  as_fatal (_("Broken assembler.  No assembly attempted."));
1448	}
1449      do
1450	{
1451	  if (mips_opcodes[i].pinfo != INSN_MACRO)
1452	    {
1453	      if (!validate_mips_insn (&mips_opcodes[i]))
1454		broken = 1;
1455	      if (nop_insn.insn_mo == NULL && strcmp (name, "nop") == 0)
1456		{
1457		  create_insn (&nop_insn, mips_opcodes + i);
1458		  nop_insn.fixed_p = 1;
1459		}
1460	    }
1461	  ++i;
1462	}
1463      while ((i < NUMOPCODES) && !strcmp (mips_opcodes[i].name, name));
1464    }
1465
1466  mips16_op_hash = hash_new ();
1467
1468  i = 0;
1469  while (i < bfd_mips16_num_opcodes)
1470    {
1471      const char *name = mips16_opcodes[i].name;
1472
1473      retval = hash_insert (mips16_op_hash, name, (void *) &mips16_opcodes[i]);
1474      if (retval != NULL)
1475	as_fatal (_("internal: can't hash `%s': %s"),
1476		  mips16_opcodes[i].name, retval);
1477      do
1478	{
1479	  if (mips16_opcodes[i].pinfo != INSN_MACRO
1480	      && ((mips16_opcodes[i].match & mips16_opcodes[i].mask)
1481		  != mips16_opcodes[i].match))
1482	    {
1483	      fprintf (stderr, _("internal error: bad mips16 opcode: %s %s\n"),
1484		       mips16_opcodes[i].name, mips16_opcodes[i].args);
1485	      broken = 1;
1486	    }
1487	  if (mips16_nop_insn.insn_mo == NULL && strcmp (name, "nop") == 0)
1488	    {
1489	      create_insn (&mips16_nop_insn, mips16_opcodes + i);
1490	      mips16_nop_insn.fixed_p = 1;
1491	    }
1492	  ++i;
1493	}
1494      while (i < bfd_mips16_num_opcodes
1495	     && strcmp (mips16_opcodes[i].name, name) == 0);
1496    }
1497
1498  if (broken)
1499    as_fatal (_("Broken assembler.  No assembly attempted."));
1500
1501  /* We add all the general register names to the symbol table.  This
1502     helps us detect invalid uses of them.  */
1503  for (i = 0; i < 32; i++)
1504    {
1505      char buf[5];
1506
1507      sprintf (buf, "$%d", i);
1508      symbol_table_insert (symbol_new (buf, reg_section, i,
1509				       &zero_address_frag));
1510    }
1511  symbol_table_insert (symbol_new ("$ra", reg_section, RA,
1512				   &zero_address_frag));
1513  symbol_table_insert (symbol_new ("$fp", reg_section, FP,
1514				   &zero_address_frag));
1515  symbol_table_insert (symbol_new ("$sp", reg_section, SP,
1516				   &zero_address_frag));
1517  symbol_table_insert (symbol_new ("$gp", reg_section, GP,
1518				   &zero_address_frag));
1519  symbol_table_insert (symbol_new ("$at", reg_section, AT,
1520				   &zero_address_frag));
1521  symbol_table_insert (symbol_new ("$kt0", reg_section, KT0,
1522				   &zero_address_frag));
1523  symbol_table_insert (symbol_new ("$kt1", reg_section, KT1,
1524				   &zero_address_frag));
1525  symbol_table_insert (symbol_new ("$zero", reg_section, ZERO,
1526				   &zero_address_frag));
1527  symbol_table_insert (symbol_new ("$pc", reg_section, -1,
1528				   &zero_address_frag));
1529
1530  /* If we don't add these register names to the symbol table, they
1531     may end up being added as regular symbols by operand(), and then
1532     make it to the object file as undefined in case they're not
1533     regarded as local symbols.  They're local in o32, since `$' is a
1534     local symbol prefix, but not in n32 or n64.  */
1535  for (i = 0; i < 8; i++)
1536    {
1537      char buf[6];
1538
1539      sprintf (buf, "$fcc%i", i);
1540      symbol_table_insert (symbol_new (buf, reg_section, -1,
1541				       &zero_address_frag));
1542    }
1543
1544  mips_no_prev_insn ();
1545
1546  mips_gprmask = 0;
1547  mips_cprmask[0] = 0;
1548  mips_cprmask[1] = 0;
1549  mips_cprmask[2] = 0;
1550  mips_cprmask[3] = 0;
1551
1552  /* set the default alignment for the text section (2**2) */
1553  record_alignment (text_section, 2);
1554
1555  bfd_set_gp_size (stdoutput, g_switch_value);
1556
1557  if (OUTPUT_FLAVOR == bfd_target_elf_flavour)
1558    {
1559      /* On a native system, sections must be aligned to 16 byte
1560         boundaries.  When configured for an embedded ELF target, we
1561	 don't bother.  */
1562      if (strcmp (TARGET_OS, "elf") != 0
1563	  && strcmp (TARGET_OS, "vxworks") != 0)
1564	{
1565	  (void) bfd_set_section_alignment (stdoutput, text_section, 4);
1566	  (void) bfd_set_section_alignment (stdoutput, data_section, 4);
1567	  (void) bfd_set_section_alignment (stdoutput, bss_section, 4);
1568	}
1569
1570      /* Create a .reginfo section for register masks and a .mdebug
1571	 section for debugging information.  */
1572      {
1573	segT seg;
1574	subsegT subseg;
1575	flagword flags;
1576	segT sec;
1577
1578	seg = now_seg;
1579	subseg = now_subseg;
1580
1581	/* The ABI says this section should be loaded so that the
1582	   running program can access it.  However, we don't load it
1583	   if we are configured for an embedded target */
1584	flags = SEC_READONLY | SEC_DATA;
1585	if (strcmp (TARGET_OS, "elf") != 0)
1586	  flags |= SEC_ALLOC | SEC_LOAD;
1587
1588	if (mips_abi != N64_ABI)
1589	  {
1590	    sec = subseg_new (".reginfo", (subsegT) 0);
1591
1592	    bfd_set_section_flags (stdoutput, sec, flags);
1593	    bfd_set_section_alignment (stdoutput, sec, HAVE_NEWABI ? 3 : 2);
1594
1595#ifdef OBJ_ELF
1596	    mips_regmask_frag = frag_more (sizeof (Elf32_External_RegInfo));
1597#endif
1598	  }
1599	else
1600	  {
1601	    /* The 64-bit ABI uses a .MIPS.options section rather than
1602               .reginfo section.  */
1603	    sec = subseg_new (".MIPS.options", (subsegT) 0);
1604	    bfd_set_section_flags (stdoutput, sec, flags);
1605	    bfd_set_section_alignment (stdoutput, sec, 3);
1606
1607#ifdef OBJ_ELF
1608	    /* Set up the option header.  */
1609	    {
1610	      Elf_Internal_Options opthdr;
1611	      char *f;
1612
1613	      opthdr.kind = ODK_REGINFO;
1614	      opthdr.size = (sizeof (Elf_External_Options)
1615			     + sizeof (Elf64_External_RegInfo));
1616	      opthdr.section = 0;
1617	      opthdr.info = 0;
1618	      f = frag_more (sizeof (Elf_External_Options));
1619	      bfd_mips_elf_swap_options_out (stdoutput, &opthdr,
1620					     (Elf_External_Options *) f);
1621
1622	      mips_regmask_frag = frag_more (sizeof (Elf64_External_RegInfo));
1623	    }
1624#endif
1625	  }
1626
1627	if (ECOFF_DEBUGGING)
1628	  {
1629	    sec = subseg_new (".mdebug", (subsegT) 0);
1630	    (void) bfd_set_section_flags (stdoutput, sec,
1631					  SEC_HAS_CONTENTS | SEC_READONLY);
1632	    (void) bfd_set_section_alignment (stdoutput, sec, 2);
1633	  }
1634#ifdef OBJ_ELF
1635	else if (OUTPUT_FLAVOR == bfd_target_elf_flavour && mips_flag_pdr)
1636	  {
1637	    pdr_seg = subseg_new (".pdr", (subsegT) 0);
1638	    (void) bfd_set_section_flags (stdoutput, pdr_seg,
1639					  SEC_READONLY | SEC_RELOC
1640					  | SEC_DEBUGGING);
1641	    (void) bfd_set_section_alignment (stdoutput, pdr_seg, 2);
1642	  }
1643#endif
1644
1645	subseg_set (seg, subseg);
1646      }
1647    }
1648
1649  if (! ECOFF_DEBUGGING)
1650    md_obj_begin ();
1651
1652  if (mips_fix_vr4120)
1653    init_vr4120_conflicts ();
1654}
1655
1656void
1657md_mips_end (void)
1658{
1659  if (! ECOFF_DEBUGGING)
1660    md_obj_end ();
1661}
1662
1663void
1664md_assemble (char *str)
1665{
1666  struct mips_cl_insn insn;
1667  bfd_reloc_code_real_type unused_reloc[3]
1668    = {BFD_RELOC_UNUSED, BFD_RELOC_UNUSED, BFD_RELOC_UNUSED};
1669
1670  imm_expr.X_op = O_absent;
1671  imm2_expr.X_op = O_absent;
1672  offset_expr.X_op = O_absent;
1673  imm_reloc[0] = BFD_RELOC_UNUSED;
1674  imm_reloc[1] = BFD_RELOC_UNUSED;
1675  imm_reloc[2] = BFD_RELOC_UNUSED;
1676  offset_reloc[0] = BFD_RELOC_UNUSED;
1677  offset_reloc[1] = BFD_RELOC_UNUSED;
1678  offset_reloc[2] = BFD_RELOC_UNUSED;
1679
1680  if (mips_opts.mips16)
1681    mips16_ip (str, &insn);
1682  else
1683    {
1684      mips_ip (str, &insn);
1685      DBG ((_("returned from mips_ip(%s) insn_opcode = 0x%x\n"),
1686	    str, insn.insn_opcode));
1687    }
1688
1689  if (insn_error)
1690    {
1691      as_bad ("%s `%s'", insn_error, str);
1692      return;
1693    }
1694
1695  if (insn.insn_mo->pinfo == INSN_MACRO)
1696    {
1697      macro_start ();
1698      if (mips_opts.mips16)
1699	mips16_macro (&insn);
1700      else
1701	macro (&insn);
1702      macro_end ();
1703    }
1704  else
1705    {
1706      if (imm_expr.X_op != O_absent)
1707	append_insn (&insn, &imm_expr, imm_reloc);
1708      else if (offset_expr.X_op != O_absent)
1709	append_insn (&insn, &offset_expr, offset_reloc);
1710      else
1711	append_insn (&insn, NULL, unused_reloc);
1712    }
1713}
1714
1715/* Return true if the given relocation might need a matching %lo().
1716   This is only "might" because SVR4 R_MIPS_GOT16 relocations only
1717   need a matching %lo() when applied to local symbols.  */
1718
1719static inline bfd_boolean
1720reloc_needs_lo_p (bfd_reloc_code_real_type reloc)
1721{
1722  return (reloc == BFD_RELOC_HI16_S
1723	  || reloc == BFD_RELOC_MIPS_GOT16);
1724}
1725
1726/* Return true if the given fixup is followed by a matching R_MIPS_LO16
1727   relocation.  */
1728
1729static inline bfd_boolean
1730fixup_has_matching_lo_p (fixS *fixp)
1731{
1732  return (fixp->fx_next != NULL
1733	  && fixp->fx_next->fx_r_type == BFD_RELOC_LO16
1734	  && fixp->fx_addsy == fixp->fx_next->fx_addsy
1735	  && fixp->fx_offset == fixp->fx_next->fx_offset);
1736}
1737
1738/* See whether instruction IP reads register REG.  CLASS is the type
1739   of register.  */
1740
1741static int
1742insn_uses_reg (const struct mips_cl_insn *ip, unsigned int reg,
1743	       enum mips_regclass class)
1744{
1745  if (class == MIPS16_REG)
1746    {
1747      assert (mips_opts.mips16);
1748      reg = mips16_to_32_reg_map[reg];
1749      class = MIPS_GR_REG;
1750    }
1751
1752  /* Don't report on general register ZERO, since it never changes.  */
1753  if (class == MIPS_GR_REG && reg == ZERO)
1754    return 0;
1755
1756  if (class == MIPS_FP_REG)
1757    {
1758      assert (! mips_opts.mips16);
1759      /* If we are called with either $f0 or $f1, we must check $f0.
1760	 This is not optimal, because it will introduce an unnecessary
1761	 NOP between "lwc1 $f0" and "swc1 $f1".  To fix this we would
1762	 need to distinguish reading both $f0 and $f1 or just one of
1763	 them.  Note that we don't have to check the other way,
1764	 because there is no instruction that sets both $f0 and $f1
1765	 and requires a delay.  */
1766      if ((ip->insn_mo->pinfo & INSN_READ_FPR_S)
1767	  && ((EXTRACT_OPERAND (FS, *ip) & ~(unsigned) 1)
1768	      == (reg &~ (unsigned) 1)))
1769	return 1;
1770      if ((ip->insn_mo->pinfo & INSN_READ_FPR_T)
1771	  && ((EXTRACT_OPERAND (FT, *ip) & ~(unsigned) 1)
1772	      == (reg &~ (unsigned) 1)))
1773	return 1;
1774    }
1775  else if (! mips_opts.mips16)
1776    {
1777      if ((ip->insn_mo->pinfo & INSN_READ_GPR_S)
1778	  && EXTRACT_OPERAND (RS, *ip) == reg)
1779	return 1;
1780      if ((ip->insn_mo->pinfo & INSN_READ_GPR_T)
1781	  && EXTRACT_OPERAND (RT, *ip) == reg)
1782	return 1;
1783    }
1784  else
1785    {
1786      if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_X)
1787	  && mips16_to_32_reg_map[MIPS16_EXTRACT_OPERAND (RX, *ip)] == reg)
1788	return 1;
1789      if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_Y)
1790	  && mips16_to_32_reg_map[MIPS16_EXTRACT_OPERAND (RY, *ip)] == reg)
1791	return 1;
1792      if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_Z)
1793	  && (mips16_to_32_reg_map[MIPS16_EXTRACT_OPERAND (MOVE32Z, *ip)]
1794	      == reg))
1795	return 1;
1796      if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_T) && reg == TREG)
1797	return 1;
1798      if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_SP) && reg == SP)
1799	return 1;
1800      if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_31) && reg == RA)
1801	return 1;
1802      if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_GPR_X)
1803	  && MIPS16_EXTRACT_OPERAND (REGR32, *ip) == reg)
1804	return 1;
1805    }
1806
1807  return 0;
1808}
1809
1810/* This function returns true if modifying a register requires a
1811   delay.  */
1812
1813static int
1814reg_needs_delay (unsigned int reg)
1815{
1816  unsigned long prev_pinfo;
1817
1818  prev_pinfo = history[0].insn_mo->pinfo;
1819  if (! mips_opts.noreorder
1820      && (((prev_pinfo & INSN_LOAD_MEMORY_DELAY)
1821	   && ! gpr_interlocks)
1822	  || ((prev_pinfo & INSN_LOAD_COPROC_DELAY)
1823	      && ! cop_interlocks)))
1824    {
1825      /* A load from a coprocessor or from memory.  All load delays
1826	 delay the use of general register rt for one instruction.  */
1827      /* Itbl support may require additional care here.  */
1828      know (prev_pinfo & INSN_WRITE_GPR_T);
1829      if (reg == EXTRACT_OPERAND (RT, history[0]))
1830	return 1;
1831    }
1832
1833  return 0;
1834}
1835
1836/* Move all labels in insn_labels to the current insertion point.  */
1837
1838static void
1839mips_move_labels (void)
1840{
1841  struct insn_label_list *l;
1842  valueT val;
1843
1844  for (l = insn_labels; l != NULL; l = l->next)
1845    {
1846      assert (S_GET_SEGMENT (l->label) == now_seg);
1847      symbol_set_frag (l->label, frag_now);
1848      val = (valueT) frag_now_fix ();
1849      /* mips16 text labels are stored as odd.  */
1850      if (mips_opts.mips16)
1851	++val;
1852      S_SET_VALUE (l->label, val);
1853    }
1854}
1855
1856/* Mark instruction labels in mips16 mode.  This permits the linker to
1857   handle them specially, such as generating jalx instructions when
1858   needed.  We also make them odd for the duration of the assembly, in
1859   order to generate the right sort of code.  We will make them even
1860   in the adjust_symtab routine, while leaving them marked.  This is
1861   convenient for the debugger and the disassembler.  The linker knows
1862   to make them odd again.  */
1863
1864static void
1865mips16_mark_labels (void)
1866{
1867  if (mips_opts.mips16)
1868    {
1869      struct insn_label_list *l;
1870      valueT val;
1871
1872      for (l = insn_labels; l != NULL; l = l->next)
1873	{
1874#ifdef OBJ_ELF
1875	  if (OUTPUT_FLAVOR == bfd_target_elf_flavour)
1876	    S_SET_OTHER (l->label, STO_MIPS16);
1877#endif
1878	  val = S_GET_VALUE (l->label);
1879	  if ((val & 1) == 0)
1880	    S_SET_VALUE (l->label, val + 1);
1881	}
1882    }
1883}
1884
1885/* End the current frag.  Make it a variant frag and record the
1886   relaxation info.  */
1887
1888static void
1889relax_close_frag (void)
1890{
1891  mips_macro_warning.first_frag = frag_now;
1892  frag_var (rs_machine_dependent, 0, 0,
1893	    RELAX_ENCODE (mips_relax.sizes[0], mips_relax.sizes[1]),
1894	    mips_relax.symbol, 0, (char *) mips_relax.first_fixup);
1895
1896  memset (&mips_relax.sizes, 0, sizeof (mips_relax.sizes));
1897  mips_relax.first_fixup = 0;
1898}
1899
1900/* Start a new relaxation sequence whose expansion depends on SYMBOL.
1901   See the comment above RELAX_ENCODE for more details.  */
1902
1903static void
1904relax_start (symbolS *symbol)
1905{
1906  assert (mips_relax.sequence == 0);
1907  mips_relax.sequence = 1;
1908  mips_relax.symbol = symbol;
1909}
1910
1911/* Start generating the second version of a relaxable sequence.
1912   See the comment above RELAX_ENCODE for more details.  */
1913
1914static void
1915relax_switch (void)
1916{
1917  assert (mips_relax.sequence == 1);
1918  mips_relax.sequence = 2;
1919}
1920
1921/* End the current relaxable sequence.  */
1922
1923static void
1924relax_end (void)
1925{
1926  assert (mips_relax.sequence == 2);
1927  relax_close_frag ();
1928  mips_relax.sequence = 0;
1929}
1930
1931/* Classify an instruction according to the FIX_VR4120_* enumeration.
1932   Return NUM_FIX_VR4120_CLASSES if the instruction isn't affected
1933   by VR4120 errata.  */
1934
1935static unsigned int
1936classify_vr4120_insn (const char *name)
1937{
1938  if (strncmp (name, "macc", 4) == 0)
1939    return FIX_VR4120_MACC;
1940  if (strncmp (name, "dmacc", 5) == 0)
1941    return FIX_VR4120_DMACC;
1942  if (strncmp (name, "mult", 4) == 0)
1943    return FIX_VR4120_MULT;
1944  if (strncmp (name, "dmult", 5) == 0)
1945    return FIX_VR4120_DMULT;
1946  if (strstr (name, "div"))
1947    return FIX_VR4120_DIV;
1948  if (strcmp (name, "mtlo") == 0 || strcmp (name, "mthi") == 0)
1949    return FIX_VR4120_MTHILO;
1950  return NUM_FIX_VR4120_CLASSES;
1951}
1952
1953/* Return the number of instructions that must separate INSN1 and INSN2,
1954   where INSN1 is the earlier instruction.  Return the worst-case value
1955   for any INSN2 if INSN2 is null.  */
1956
1957static unsigned int
1958insns_between (const struct mips_cl_insn *insn1,
1959	       const struct mips_cl_insn *insn2)
1960{
1961  unsigned long pinfo1, pinfo2;
1962
1963  /* This function needs to know which pinfo flags are set for INSN2
1964     and which registers INSN2 uses.  The former is stored in PINFO2 and
1965     the latter is tested via INSN2_USES_REG.  If INSN2 is null, PINFO2
1966     will have every flag set and INSN2_USES_REG will always return true.  */
1967  pinfo1 = insn1->insn_mo->pinfo;
1968  pinfo2 = insn2 ? insn2->insn_mo->pinfo : ~0U;
1969
1970#define INSN2_USES_REG(REG, CLASS) \
1971   (insn2 == NULL || insn_uses_reg (insn2, REG, CLASS))
1972
1973  /* For most targets, write-after-read dependencies on the HI and LO
1974     registers must be separated by at least two instructions.  */
1975  if (!hilo_interlocks)
1976    {
1977      if ((pinfo1 & INSN_READ_LO) && (pinfo2 & INSN_WRITE_LO))
1978	return 2;
1979      if ((pinfo1 & INSN_READ_HI) && (pinfo2 & INSN_WRITE_HI))
1980	return 2;
1981    }
1982
1983  /* If we're working around r7000 errata, there must be two instructions
1984     between an mfhi or mflo and any instruction that uses the result.  */
1985  if (mips_7000_hilo_fix
1986      && MF_HILO_INSN (pinfo1)
1987      && INSN2_USES_REG (EXTRACT_OPERAND (RD, *insn1), MIPS_GR_REG))
1988    return 2;
1989
1990  /* If working around VR4120 errata, check for combinations that need
1991     a single intervening instruction.  */
1992  if (mips_fix_vr4120)
1993    {
1994      unsigned int class1, class2;
1995
1996      class1 = classify_vr4120_insn (insn1->insn_mo->name);
1997      if (class1 != NUM_FIX_VR4120_CLASSES && vr4120_conflicts[class1] != 0)
1998	{
1999	  if (insn2 == NULL)
2000	    return 1;
2001	  class2 = classify_vr4120_insn (insn2->insn_mo->name);
2002	  if (vr4120_conflicts[class1] & (1 << class2))
2003	    return 1;
2004	}
2005    }
2006
2007  if (!mips_opts.mips16)
2008    {
2009      /* Check for GPR or coprocessor load delays.  All such delays
2010	 are on the RT register.  */
2011      /* Itbl support may require additional care here.  */
2012      if ((!gpr_interlocks && (pinfo1 & INSN_LOAD_MEMORY_DELAY))
2013	  || (!cop_interlocks && (pinfo1 & INSN_LOAD_COPROC_DELAY)))
2014	{
2015	  know (pinfo1 & INSN_WRITE_GPR_T);
2016	  if (INSN2_USES_REG (EXTRACT_OPERAND (RT, *insn1), MIPS_GR_REG))
2017	    return 1;
2018	}
2019
2020      /* Check for generic coprocessor hazards.
2021
2022	 This case is not handled very well.  There is no special
2023	 knowledge of CP0 handling, and the coprocessors other than
2024	 the floating point unit are not distinguished at all.  */
2025      /* Itbl support may require additional care here. FIXME!
2026	 Need to modify this to include knowledge about
2027	 user specified delays!  */
2028      else if ((!cop_interlocks && (pinfo1 & INSN_COPROC_MOVE_DELAY))
2029	       || (!cop_mem_interlocks && (pinfo1 & INSN_COPROC_MEMORY_DELAY)))
2030	{
2031	  /* Handle cases where INSN1 writes to a known general coprocessor
2032	     register.  There must be a one instruction delay before INSN2
2033	     if INSN2 reads that register, otherwise no delay is needed.  */
2034	  if (pinfo1 & INSN_WRITE_FPR_T)
2035	    {
2036	      if (INSN2_USES_REG (EXTRACT_OPERAND (FT, *insn1), MIPS_FP_REG))
2037		return 1;
2038	    }
2039	  else if (pinfo1 & INSN_WRITE_FPR_S)
2040	    {
2041	      if (INSN2_USES_REG (EXTRACT_OPERAND (FS, *insn1), MIPS_FP_REG))
2042		return 1;
2043	    }
2044	  else
2045	    {
2046	      /* Read-after-write dependencies on the control registers
2047		 require a two-instruction gap.  */
2048	      if ((pinfo1 & INSN_WRITE_COND_CODE)
2049		  && (pinfo2 & INSN_READ_COND_CODE))
2050		return 2;
2051
2052	      /* We don't know exactly what INSN1 does.  If INSN2 is
2053		 also a coprocessor instruction, assume there must be
2054		 a one instruction gap.  */
2055	      if (pinfo2 & INSN_COP)
2056		return 1;
2057	    }
2058	}
2059
2060      /* Check for read-after-write dependencies on the coprocessor
2061	 control registers in cases where INSN1 does not need a general
2062	 coprocessor delay.  This means that INSN1 is a floating point
2063	 comparison instruction.  */
2064      /* Itbl support may require additional care here.  */
2065      else if (!cop_interlocks
2066	       && (pinfo1 & INSN_WRITE_COND_CODE)
2067	       && (pinfo2 & INSN_READ_COND_CODE))
2068	return 1;
2069    }
2070
2071#undef INSN2_USES_REG
2072
2073  return 0;
2074}
2075
2076/* Return the number of nops that would be needed to work around the
2077   VR4130 mflo/mfhi errata if instruction INSN immediately followed
2078   the MAX_VR4130_NOPS instructions described by HISTORY.  */
2079
2080static int
2081nops_for_vr4130 (const struct mips_cl_insn *history,
2082		 const struct mips_cl_insn *insn)
2083{
2084  int i, j, reg;
2085
2086  /* Check if the instruction writes to HI or LO.  MTHI and MTLO
2087     are not affected by the errata.  */
2088  if (insn != 0
2089      && ((insn->insn_mo->pinfo & (INSN_WRITE_HI | INSN_WRITE_LO)) == 0
2090	  || strcmp (insn->insn_mo->name, "mtlo") == 0
2091	  || strcmp (insn->insn_mo->name, "mthi") == 0))
2092    return 0;
2093
2094  /* Search for the first MFLO or MFHI.  */
2095  for (i = 0; i < MAX_VR4130_NOPS; i++)
2096    if (!history[i].noreorder_p && MF_HILO_INSN (history[i].insn_mo->pinfo))
2097      {
2098	/* Extract the destination register.  */
2099	if (mips_opts.mips16)
2100	  reg = mips16_to_32_reg_map[MIPS16_EXTRACT_OPERAND (RX, history[i])];
2101	else
2102	  reg = EXTRACT_OPERAND (RD, history[i]);
2103
2104	/* No nops are needed if INSN reads that register.  */
2105	if (insn != NULL && insn_uses_reg (insn, reg, MIPS_GR_REG))
2106	  return 0;
2107
2108	/* ...or if any of the intervening instructions do.  */
2109	for (j = 0; j < i; j++)
2110	  if (insn_uses_reg (&history[j], reg, MIPS_GR_REG))
2111	    return 0;
2112
2113	return MAX_VR4130_NOPS - i;
2114      }
2115  return 0;
2116}
2117
2118/* Return the number of nops that would be needed if instruction INSN
2119   immediately followed the MAX_NOPS instructions given by HISTORY,
2120   where HISTORY[0] is the most recent instruction.  If INSN is null,
2121   return the worse-case number of nops for any instruction.  */
2122
2123static int
2124nops_for_insn (const struct mips_cl_insn *history,
2125	       const struct mips_cl_insn *insn)
2126{
2127  int i, nops, tmp_nops;
2128
2129  nops = 0;
2130  for (i = 0; i < MAX_DELAY_NOPS; i++)
2131    if (!history[i].noreorder_p)
2132      {
2133	tmp_nops = insns_between (history + i, insn) - i;
2134	if (tmp_nops > nops)
2135	  nops = tmp_nops;
2136      }
2137
2138  if (mips_fix_vr4130)
2139    {
2140      tmp_nops = nops_for_vr4130 (history, insn);
2141      if (tmp_nops > nops)
2142	nops = tmp_nops;
2143    }
2144
2145  return nops;
2146}
2147
2148/* The variable arguments provide NUM_INSNS extra instructions that
2149   might be added to HISTORY.  Return the largest number of nops that
2150   would be needed after the extended sequence.  */
2151
2152static int
2153nops_for_sequence (int num_insns, const struct mips_cl_insn *history, ...)
2154{
2155  va_list args;
2156  struct mips_cl_insn buffer[MAX_NOPS];
2157  struct mips_cl_insn *cursor;
2158  int nops;
2159
2160  va_start (args, history);
2161  cursor = buffer + num_insns;
2162  memcpy (cursor, history, (MAX_NOPS - num_insns) * sizeof (*cursor));
2163  while (cursor > buffer)
2164    *--cursor = *va_arg (args, const struct mips_cl_insn *);
2165
2166  nops = nops_for_insn (buffer, NULL);
2167  va_end (args);
2168  return nops;
2169}
2170
2171/* Like nops_for_insn, but if INSN is a branch, take into account the
2172   worst-case delay for the branch target.  */
2173
2174static int
2175nops_for_insn_or_target (const struct mips_cl_insn *history,
2176			 const struct mips_cl_insn *insn)
2177{
2178  int nops, tmp_nops;
2179
2180  nops = nops_for_insn (history, insn);
2181  if (insn->insn_mo->pinfo & (INSN_UNCOND_BRANCH_DELAY
2182			      | INSN_COND_BRANCH_DELAY
2183			      | INSN_COND_BRANCH_LIKELY))
2184    {
2185      tmp_nops = nops_for_sequence (2, history, insn, NOP_INSN);
2186      if (tmp_nops > nops)
2187	nops = tmp_nops;
2188    }
2189  else if (mips_opts.mips16 && (insn->insn_mo->pinfo & MIPS16_INSN_BRANCH))
2190    {
2191      tmp_nops = nops_for_sequence (1, history, insn);
2192      if (tmp_nops > nops)
2193	nops = tmp_nops;
2194    }
2195  return nops;
2196}
2197
2198/* Output an instruction.  IP is the instruction information.
2199   ADDRESS_EXPR is an operand of the instruction to be used with
2200   RELOC_TYPE.  */
2201
2202static void
2203append_insn (struct mips_cl_insn *ip, expressionS *address_expr,
2204	     bfd_reloc_code_real_type *reloc_type)
2205{
2206  register unsigned long prev_pinfo, pinfo;
2207  relax_stateT prev_insn_frag_type = 0;
2208  bfd_boolean relaxed_branch = FALSE;
2209
2210  /* Mark instruction labels in mips16 mode.  */
2211  mips16_mark_labels ();
2212
2213  prev_pinfo = history[0].insn_mo->pinfo;
2214  pinfo = ip->insn_mo->pinfo;
2215
2216  if (mips_relax.sequence != 2 && !mips_opts.noreorder)
2217    {
2218      /* There are a lot of optimizations we could do that we don't.
2219	 In particular, we do not, in general, reorder instructions.
2220	 If you use gcc with optimization, it will reorder
2221	 instructions and generally do much more optimization then we
2222	 do here; repeating all that work in the assembler would only
2223	 benefit hand written assembly code, and does not seem worth
2224	 it.  */
2225      int nops = (mips_optimize == 0
2226		  ? nops_for_insn (history, NULL)
2227		  : nops_for_insn_or_target (history, ip));
2228      if (nops > 0)
2229	{
2230	  fragS *old_frag;
2231	  unsigned long old_frag_offset;
2232	  int i;
2233
2234	  old_frag = frag_now;
2235	  old_frag_offset = frag_now_fix ();
2236
2237	  for (i = 0; i < nops; i++)
2238	    emit_nop ();
2239
2240	  if (listing)
2241	    {
2242	      listing_prev_line ();
2243	      /* We may be at the start of a variant frag.  In case we
2244                 are, make sure there is enough space for the frag
2245                 after the frags created by listing_prev_line.  The
2246                 argument to frag_grow here must be at least as large
2247                 as the argument to all other calls to frag_grow in
2248                 this file.  We don't have to worry about being in the
2249                 middle of a variant frag, because the variants insert
2250                 all needed nop instructions themselves.  */
2251	      frag_grow (40);
2252	    }
2253
2254	  mips_move_labels ();
2255
2256#ifndef NO_ECOFF_DEBUGGING
2257	  if (ECOFF_DEBUGGING)
2258	    ecoff_fix_loc (old_frag, old_frag_offset);
2259#endif
2260	}
2261    }
2262  else if (mips_relax.sequence != 2 && prev_nop_frag != NULL)
2263    {
2264      /* Work out how many nops in prev_nop_frag are needed by IP.  */
2265      int nops = nops_for_insn_or_target (history, ip);
2266      assert (nops <= prev_nop_frag_holds);
2267
2268      /* Enforce NOPS as a minimum.  */
2269      if (nops > prev_nop_frag_required)
2270	prev_nop_frag_required = nops;
2271
2272      if (prev_nop_frag_holds == prev_nop_frag_required)
2273	{
2274	  /* Settle for the current number of nops.  Update the history
2275	     accordingly (for the benefit of any future .set reorder code).  */
2276	  prev_nop_frag = NULL;
2277	  insert_into_history (prev_nop_frag_since,
2278			       prev_nop_frag_holds, NOP_INSN);
2279	}
2280      else
2281	{
2282	  /* Allow this instruction to replace one of the nops that was
2283	     tentatively added to prev_nop_frag.  */
2284	  prev_nop_frag->fr_fix -= mips_opts.mips16 ? 2 : 4;
2285	  prev_nop_frag_holds--;
2286	  prev_nop_frag_since++;
2287	}
2288    }
2289
2290#ifdef OBJ_ELF
2291  /* The value passed to dwarf2_emit_insn is the distance between
2292     the beginning of the current instruction and the address that
2293     should be recorded in the debug tables.  For MIPS16 debug info
2294     we want to use ISA-encoded addresses, so we pass -1 for an
2295     address higher by one than the current.  */
2296  dwarf2_emit_insn (mips_opts.mips16 ? -1 : 0);
2297#endif
2298
2299  /* Record the frag type before frag_var.  */
2300  if (history[0].frag)
2301    prev_insn_frag_type = history[0].frag->fr_type;
2302
2303  if (address_expr
2304      && *reloc_type == BFD_RELOC_16_PCREL_S2
2305      && (pinfo & INSN_UNCOND_BRANCH_DELAY || pinfo & INSN_COND_BRANCH_DELAY
2306	  || pinfo & INSN_COND_BRANCH_LIKELY)
2307      && mips_relax_branch
2308      /* Don't try branch relaxation within .set nomacro, or within
2309	 .set noat if we use $at for PIC computations.  If it turns
2310	 out that the branch was out-of-range, we'll get an error.  */
2311      && !mips_opts.warn_about_macros
2312      && !(mips_opts.noat && mips_pic != NO_PIC)
2313      && !mips_opts.mips16)
2314    {
2315      relaxed_branch = TRUE;
2316      add_relaxed_insn (ip, (relaxed_branch_length
2317			     (NULL, NULL,
2318			      (pinfo & INSN_UNCOND_BRANCH_DELAY) ? -1
2319			      : (pinfo & INSN_COND_BRANCH_LIKELY) ? 1
2320			      : 0)), 4,
2321			RELAX_BRANCH_ENCODE
2322			(pinfo & INSN_UNCOND_BRANCH_DELAY,
2323			 pinfo & INSN_COND_BRANCH_LIKELY,
2324			 pinfo & INSN_WRITE_GPR_31,
2325			 0),
2326			address_expr->X_add_symbol,
2327			address_expr->X_add_number);
2328      *reloc_type = BFD_RELOC_UNUSED;
2329    }
2330  else if (*reloc_type > BFD_RELOC_UNUSED)
2331    {
2332      /* We need to set up a variant frag.  */
2333      assert (mips_opts.mips16 && address_expr != NULL);
2334      add_relaxed_insn (ip, 4, 0,
2335			RELAX_MIPS16_ENCODE
2336			(*reloc_type - BFD_RELOC_UNUSED,
2337			 mips16_small, mips16_ext,
2338			 prev_pinfo & INSN_UNCOND_BRANCH_DELAY,
2339			 history[0].mips16_absolute_jump_p),
2340			make_expr_symbol (address_expr), 0);
2341    }
2342  else if (mips_opts.mips16
2343	   && ! ip->use_extend
2344	   && *reloc_type != BFD_RELOC_MIPS16_JMP)
2345    {
2346      if ((pinfo & INSN_UNCOND_BRANCH_DELAY) == 0)
2347	/* Make sure there is enough room to swap this instruction with
2348	   a following jump instruction.  */
2349	frag_grow (6);
2350      add_fixed_insn (ip);
2351    }
2352  else
2353    {
2354      if (mips_opts.mips16
2355	  && mips_opts.noreorder
2356	  && (prev_pinfo & INSN_UNCOND_BRANCH_DELAY) != 0)
2357	as_warn (_("extended instruction in delay slot"));
2358
2359      if (mips_relax.sequence)
2360	{
2361	  /* If we've reached the end of this frag, turn it into a variant
2362	     frag and record the information for the instructions we've
2363	     written so far.  */
2364	  if (frag_room () < 4)
2365	    relax_close_frag ();
2366	  mips_relax.sizes[mips_relax.sequence - 1] += 4;
2367	}
2368
2369      if (mips_relax.sequence != 2)
2370	mips_macro_warning.sizes[0] += 4;
2371      if (mips_relax.sequence != 1)
2372	mips_macro_warning.sizes[1] += 4;
2373
2374      if (mips_opts.mips16)
2375	{
2376	  ip->fixed_p = 1;
2377	  ip->mips16_absolute_jump_p = (*reloc_type == BFD_RELOC_MIPS16_JMP);
2378	}
2379      add_fixed_insn (ip);
2380    }
2381
2382  if (address_expr != NULL && *reloc_type <= BFD_RELOC_UNUSED)
2383    {
2384      if (address_expr->X_op == O_constant)
2385	{
2386	  unsigned int tmp;
2387
2388	  switch (*reloc_type)
2389	    {
2390	    case BFD_RELOC_32:
2391	      ip->insn_opcode |= address_expr->X_add_number;
2392	      break;
2393
2394	    case BFD_RELOC_MIPS_HIGHEST:
2395	      tmp = (address_expr->X_add_number + 0x800080008000ull) >> 48;
2396	      ip->insn_opcode |= tmp & 0xffff;
2397	      break;
2398
2399	    case BFD_RELOC_MIPS_HIGHER:
2400	      tmp = (address_expr->X_add_number + 0x80008000ull) >> 32;
2401	      ip->insn_opcode |= tmp & 0xffff;
2402	      break;
2403
2404	    case BFD_RELOC_HI16_S:
2405	      tmp = (address_expr->X_add_number + 0x8000) >> 16;
2406	      ip->insn_opcode |= tmp & 0xffff;
2407	      break;
2408
2409	    case BFD_RELOC_HI16:
2410	      ip->insn_opcode |= (address_expr->X_add_number >> 16) & 0xffff;
2411	      break;
2412
2413	    case BFD_RELOC_UNUSED:
2414	    case BFD_RELOC_LO16:
2415	    case BFD_RELOC_MIPS_GOT_DISP:
2416	      ip->insn_opcode |= address_expr->X_add_number & 0xffff;
2417	      break;
2418
2419	    case BFD_RELOC_MIPS_JMP:
2420	      if ((address_expr->X_add_number & 3) != 0)
2421		as_bad (_("jump to misaligned address (0x%lx)"),
2422			(unsigned long) address_expr->X_add_number);
2423	      ip->insn_opcode |= (address_expr->X_add_number >> 2) & 0x3ffffff;
2424	      break;
2425
2426	    case BFD_RELOC_MIPS16_JMP:
2427	      if ((address_expr->X_add_number & 3) != 0)
2428		as_bad (_("jump to misaligned address (0x%lx)"),
2429			(unsigned long) address_expr->X_add_number);
2430	      ip->insn_opcode |=
2431		(((address_expr->X_add_number & 0x7c0000) << 3)
2432		 | ((address_expr->X_add_number & 0xf800000) >> 7)
2433		 | ((address_expr->X_add_number & 0x3fffc) >> 2));
2434	      break;
2435
2436	    case BFD_RELOC_16_PCREL_S2:
2437	      if ((address_expr->X_add_number & 3) != 0)
2438		as_bad (_("branch to misaligned address (0x%lx)"),
2439			(unsigned long) address_expr->X_add_number);
2440	      if (mips_relax_branch)
2441		goto need_reloc;
2442	      if ((address_expr->X_add_number + 0x20000) & ~0x3ffff)
2443		as_bad (_("branch address range overflow (0x%lx)"),
2444			(unsigned long) address_expr->X_add_number);
2445	      ip->insn_opcode |= (address_expr->X_add_number >> 2) & 0xffff;
2446	      break;
2447
2448	    default:
2449	      internalError ();
2450	    }
2451	}
2452      else if (*reloc_type < BFD_RELOC_UNUSED)
2453	need_reloc:
2454	{
2455	  reloc_howto_type *howto;
2456	  int i;
2457
2458	  /* In a compound relocation, it is the final (outermost)
2459	     operator that determines the relocated field.  */
2460	  for (i = 1; i < 3; i++)
2461	    if (reloc_type[i] == BFD_RELOC_UNUSED)
2462	      break;
2463
2464	  howto = bfd_reloc_type_lookup (stdoutput, reloc_type[i - 1]);
2465	  ip->fixp[0] = fix_new_exp (ip->frag, ip->where,
2466				     bfd_get_reloc_size (howto),
2467				     address_expr,
2468				     reloc_type[0] == BFD_RELOC_16_PCREL_S2,
2469				     reloc_type[0]);
2470
2471	  /* These relocations can have an addend that won't fit in
2472	     4 octets for 64bit assembly.  */
2473	  if (HAVE_64BIT_GPRS
2474	      && ! howto->partial_inplace
2475	      && (reloc_type[0] == BFD_RELOC_16
2476		  || reloc_type[0] == BFD_RELOC_32
2477		  || reloc_type[0] == BFD_RELOC_MIPS_JMP
2478		  || reloc_type[0] == BFD_RELOC_HI16_S
2479		  || reloc_type[0] == BFD_RELOC_LO16
2480		  || reloc_type[0] == BFD_RELOC_GPREL16
2481		  || reloc_type[0] == BFD_RELOC_MIPS_LITERAL
2482		  || reloc_type[0] == BFD_RELOC_GPREL32
2483		  || reloc_type[0] == BFD_RELOC_64
2484		  || reloc_type[0] == BFD_RELOC_CTOR
2485		  || reloc_type[0] == BFD_RELOC_MIPS_SUB
2486		  || reloc_type[0] == BFD_RELOC_MIPS_HIGHEST
2487		  || reloc_type[0] == BFD_RELOC_MIPS_HIGHER
2488		  || reloc_type[0] == BFD_RELOC_MIPS_SCN_DISP
2489		  || reloc_type[0] == BFD_RELOC_MIPS_REL16
2490		  || reloc_type[0] == BFD_RELOC_MIPS_RELGOT))
2491	    ip->fixp[0]->fx_no_overflow = 1;
2492
2493	  if (mips_relax.sequence)
2494	    {
2495	      if (mips_relax.first_fixup == 0)
2496		mips_relax.first_fixup = ip->fixp[0];
2497	    }
2498	  else if (reloc_needs_lo_p (*reloc_type))
2499	    {
2500	      struct mips_hi_fixup *hi_fixup;
2501
2502	      /* Reuse the last entry if it already has a matching %lo.  */
2503	      hi_fixup = mips_hi_fixup_list;
2504	      if (hi_fixup == 0
2505		  || !fixup_has_matching_lo_p (hi_fixup->fixp))
2506		{
2507		  hi_fixup = ((struct mips_hi_fixup *)
2508			      xmalloc (sizeof (struct mips_hi_fixup)));
2509		  hi_fixup->next = mips_hi_fixup_list;
2510		  mips_hi_fixup_list = hi_fixup;
2511		}
2512	      hi_fixup->fixp = ip->fixp[0];
2513	      hi_fixup->seg = now_seg;
2514	    }
2515
2516	  /* Add fixups for the second and third relocations, if given.
2517	     Note that the ABI allows the second relocation to be
2518	     against RSS_UNDEF, RSS_GP, RSS_GP0 or RSS_LOC.  At the
2519	     moment we only use RSS_UNDEF, but we could add support
2520	     for the others if it ever becomes necessary.  */
2521	  for (i = 1; i < 3; i++)
2522	    if (reloc_type[i] != BFD_RELOC_UNUSED)
2523	      {
2524		ip->fixp[i] = fix_new (ip->frag, ip->where,
2525				       ip->fixp[0]->fx_size, NULL, 0,
2526				       FALSE, reloc_type[i]);
2527
2528		/* Use fx_tcbit to mark compound relocs.  */
2529		ip->fixp[0]->fx_tcbit = 1;
2530		ip->fixp[i]->fx_tcbit = 1;
2531	      }
2532	}
2533    }
2534  install_insn (ip);
2535
2536  /* Update the register mask information.  */
2537  if (! mips_opts.mips16)
2538    {
2539      if (pinfo & INSN_WRITE_GPR_D)
2540	mips_gprmask |= 1 << EXTRACT_OPERAND (RD, *ip);
2541      if ((pinfo & (INSN_WRITE_GPR_T | INSN_READ_GPR_T)) != 0)
2542	mips_gprmask |= 1 << EXTRACT_OPERAND (RT, *ip);
2543      if (pinfo & INSN_READ_GPR_S)
2544	mips_gprmask |= 1 << EXTRACT_OPERAND (RS, *ip);
2545      if (pinfo & INSN_WRITE_GPR_31)
2546	mips_gprmask |= 1 << RA;
2547      if (pinfo & INSN_WRITE_FPR_D)
2548	mips_cprmask[1] |= 1 << EXTRACT_OPERAND (FD, *ip);
2549      if ((pinfo & (INSN_WRITE_FPR_S | INSN_READ_FPR_S)) != 0)
2550	mips_cprmask[1] |= 1 << EXTRACT_OPERAND (FS, *ip);
2551      if ((pinfo & (INSN_WRITE_FPR_T | INSN_READ_FPR_T)) != 0)
2552	mips_cprmask[1] |= 1 << EXTRACT_OPERAND (FT, *ip);
2553      if ((pinfo & INSN_READ_FPR_R) != 0)
2554	mips_cprmask[1] |= 1 << EXTRACT_OPERAND (FR, *ip);
2555      if (pinfo & INSN_COP)
2556	{
2557	  /* We don't keep enough information to sort these cases out.
2558	     The itbl support does keep this information however, although
2559	     we currently don't support itbl fprmats as part of the cop
2560	     instruction.  May want to add this support in the future.  */
2561	}
2562      /* Never set the bit for $0, which is always zero.  */
2563      mips_gprmask &= ~1 << 0;
2564    }
2565  else
2566    {
2567      if (pinfo & (MIPS16_INSN_WRITE_X | MIPS16_INSN_READ_X))
2568	mips_gprmask |= 1 << MIPS16_EXTRACT_OPERAND (RX, *ip);
2569      if (pinfo & (MIPS16_INSN_WRITE_Y | MIPS16_INSN_READ_Y))
2570	mips_gprmask |= 1 << MIPS16_EXTRACT_OPERAND (RY, *ip);
2571      if (pinfo & MIPS16_INSN_WRITE_Z)
2572	mips_gprmask |= 1 << MIPS16_EXTRACT_OPERAND (RZ, *ip);
2573      if (pinfo & (MIPS16_INSN_WRITE_T | MIPS16_INSN_READ_T))
2574	mips_gprmask |= 1 << TREG;
2575      if (pinfo & (MIPS16_INSN_WRITE_SP | MIPS16_INSN_READ_SP))
2576	mips_gprmask |= 1 << SP;
2577      if (pinfo & (MIPS16_INSN_WRITE_31 | MIPS16_INSN_READ_31))
2578	mips_gprmask |= 1 << RA;
2579      if (pinfo & MIPS16_INSN_WRITE_GPR_Y)
2580	mips_gprmask |= 1 << MIPS16OP_EXTRACT_REG32R (ip->insn_opcode);
2581      if (pinfo & MIPS16_INSN_READ_Z)
2582	mips_gprmask |= 1 << MIPS16_EXTRACT_OPERAND (MOVE32Z, *ip);
2583      if (pinfo & MIPS16_INSN_READ_GPR_X)
2584	mips_gprmask |= 1 << MIPS16_EXTRACT_OPERAND (REGR32, *ip);
2585    }
2586
2587  if (mips_relax.sequence != 2 && !mips_opts.noreorder)
2588    {
2589      /* Filling the branch delay slot is more complex.  We try to
2590	 switch the branch with the previous instruction, which we can
2591	 do if the previous instruction does not set up a condition
2592	 that the branch tests and if the branch is not itself the
2593	 target of any branch.  */
2594      if ((pinfo & INSN_UNCOND_BRANCH_DELAY)
2595	  || (pinfo & INSN_COND_BRANCH_DELAY))
2596	{
2597	  if (mips_optimize < 2
2598	      /* If we have seen .set volatile or .set nomove, don't
2599		 optimize.  */
2600	      || mips_opts.nomove != 0
2601	      /* We can't swap if the previous instruction's position
2602		 is fixed.  */
2603	      || history[0].fixed_p
2604	      /* If the previous previous insn was in a .set
2605		 noreorder, we can't swap.  Actually, the MIPS
2606		 assembler will swap in this situation.  However, gcc
2607		 configured -with-gnu-as will generate code like
2608		   .set noreorder
2609		   lw	$4,XXX
2610		   .set	reorder
2611		   INSN
2612		   bne	$4,$0,foo
2613		 in which we can not swap the bne and INSN.  If gcc is
2614		 not configured -with-gnu-as, it does not output the
2615		 .set pseudo-ops.  */
2616	      || history[1].noreorder_p
2617	      /* If the branch is itself the target of a branch, we
2618		 can not swap.  We cheat on this; all we check for is
2619		 whether there is a label on this instruction.  If
2620		 there are any branches to anything other than a
2621		 label, users must use .set noreorder.  */
2622	      || insn_labels != NULL
2623	      /* If the previous instruction is in a variant frag
2624		 other than this branch's one, we cannot do the swap.
2625		 This does not apply to the mips16, which uses variant
2626		 frags for different purposes.  */
2627	      || (! mips_opts.mips16
2628		  && prev_insn_frag_type == rs_machine_dependent)
2629	      /* Check for conflicts between the branch and the instructions
2630		 before the candidate delay slot.  */
2631	      || nops_for_insn (history + 1, ip) > 0
2632	      /* Check for conflicts between the swapped sequence and the
2633		 target of the branch.  */
2634	      || nops_for_sequence (2, history + 1, ip, history) > 0
2635	      /* We do not swap with a trap instruction, since it
2636		 complicates trap handlers to have the trap
2637		 instruction be in a delay slot.  */
2638	      || (prev_pinfo & INSN_TRAP)
2639	      /* If the branch reads a register that the previous
2640		 instruction sets, we can not swap.  */
2641	      || (! mips_opts.mips16
2642		  && (prev_pinfo & INSN_WRITE_GPR_T)
2643		  && insn_uses_reg (ip, EXTRACT_OPERAND (RT, history[0]),
2644				    MIPS_GR_REG))
2645	      || (! mips_opts.mips16
2646		  && (prev_pinfo & INSN_WRITE_GPR_D)
2647		  && insn_uses_reg (ip, EXTRACT_OPERAND (RD, history[0]),
2648				    MIPS_GR_REG))
2649	      || (mips_opts.mips16
2650		  && (((prev_pinfo & MIPS16_INSN_WRITE_X)
2651		       && (insn_uses_reg
2652			   (ip, MIPS16_EXTRACT_OPERAND (RX, history[0]),
2653			    MIPS16_REG)))
2654		      || ((prev_pinfo & MIPS16_INSN_WRITE_Y)
2655			  && (insn_uses_reg
2656			      (ip, MIPS16_EXTRACT_OPERAND (RY, history[0]),
2657			       MIPS16_REG)))
2658		      || ((prev_pinfo & MIPS16_INSN_WRITE_Z)
2659			  && (insn_uses_reg
2660			      (ip, MIPS16_EXTRACT_OPERAND (RZ, history[0]),
2661			       MIPS16_REG)))
2662		      || ((prev_pinfo & MIPS16_INSN_WRITE_T)
2663			  && insn_uses_reg (ip, TREG, MIPS_GR_REG))
2664		      || ((prev_pinfo & MIPS16_INSN_WRITE_31)
2665			  && insn_uses_reg (ip, RA, MIPS_GR_REG))
2666		      || ((prev_pinfo & MIPS16_INSN_WRITE_GPR_Y)
2667			  && insn_uses_reg (ip,
2668					    MIPS16OP_EXTRACT_REG32R
2669					      (history[0].insn_opcode),
2670					    MIPS_GR_REG))))
2671	      /* If the branch writes a register that the previous
2672		 instruction sets, we can not swap (we know that
2673		 branches write only to RD or to $31).  */
2674	      || (! mips_opts.mips16
2675		  && (prev_pinfo & INSN_WRITE_GPR_T)
2676		  && (((pinfo & INSN_WRITE_GPR_D)
2677		       && (EXTRACT_OPERAND (RT, history[0])
2678			   == EXTRACT_OPERAND (RD, *ip)))
2679		      || ((pinfo & INSN_WRITE_GPR_31)
2680			  && EXTRACT_OPERAND (RT, history[0]) == RA)))
2681	      || (! mips_opts.mips16
2682		  && (prev_pinfo & INSN_WRITE_GPR_D)
2683		  && (((pinfo & INSN_WRITE_GPR_D)
2684		       && (EXTRACT_OPERAND (RD, history[0])
2685			   == EXTRACT_OPERAND (RD, *ip)))
2686		      || ((pinfo & INSN_WRITE_GPR_31)
2687			  && EXTRACT_OPERAND (RD, history[0]) == RA)))
2688	      || (mips_opts.mips16
2689		  && (pinfo & MIPS16_INSN_WRITE_31)
2690		  && ((prev_pinfo & MIPS16_INSN_WRITE_31)
2691		      || ((prev_pinfo & MIPS16_INSN_WRITE_GPR_Y)
2692			  && (MIPS16OP_EXTRACT_REG32R (history[0].insn_opcode)
2693			      == RA))))
2694	      /* If the branch writes a register that the previous
2695		 instruction reads, we can not swap (we know that
2696		 branches only write to RD or to $31).  */
2697	      || (! mips_opts.mips16
2698		  && (pinfo & INSN_WRITE_GPR_D)
2699		  && insn_uses_reg (&history[0],
2700				    EXTRACT_OPERAND (RD, *ip),
2701				    MIPS_GR_REG))
2702	      || (! mips_opts.mips16
2703		  && (pinfo & INSN_WRITE_GPR_31)
2704		  && insn_uses_reg (&history[0], RA, MIPS_GR_REG))
2705	      || (mips_opts.mips16
2706		  && (pinfo & MIPS16_INSN_WRITE_31)
2707		  && insn_uses_reg (&history[0], RA, MIPS_GR_REG))
2708	      /* If one instruction sets a condition code and the
2709                 other one uses a condition code, we can not swap.  */
2710	      || ((pinfo & INSN_READ_COND_CODE)
2711		  && (prev_pinfo & INSN_WRITE_COND_CODE))
2712	      || ((pinfo & INSN_WRITE_COND_CODE)
2713		  && (prev_pinfo & INSN_READ_COND_CODE))
2714	      /* If the previous instruction uses the PC, we can not
2715                 swap.  */
2716	      || (mips_opts.mips16
2717		  && (prev_pinfo & MIPS16_INSN_READ_PC))
2718	      /* If the previous instruction had a fixup in mips16
2719                 mode, we can not swap.  This normally means that the
2720                 previous instruction was a 4 byte branch anyhow.  */
2721	      || (mips_opts.mips16 && history[0].fixp[0])
2722	      /* If the previous instruction is a sync, sync.l, or
2723		 sync.p, we can not swap.  */
2724	      || (prev_pinfo & INSN_SYNC))
2725	    {
2726	      if (mips_opts.mips16
2727		  && (pinfo & INSN_UNCOND_BRANCH_DELAY)
2728		  && (pinfo & (MIPS16_INSN_READ_X | MIPS16_INSN_READ_31))
2729		  && (mips_opts.isa == ISA_MIPS32
2730		      || mips_opts.isa == ISA_MIPS32R2
2731		      || mips_opts.isa == ISA_MIPS64
2732		      || mips_opts.isa == ISA_MIPS64R2))
2733		{
2734		  /* Convert MIPS16 jr/jalr into a "compact" jump.  */
2735		  ip->insn_opcode |= 0x0080;
2736		  install_insn (ip);
2737		  insert_into_history (0, 1, ip);
2738		}
2739	      else
2740		{
2741		  /* We could do even better for unconditional branches to
2742		     portions of this object file; we could pick up the
2743		     instruction at the destination, put it in the delay
2744		     slot, and bump the destination address.  */
2745		  insert_into_history (0, 1, ip);
2746		  emit_nop ();
2747		}
2748
2749	      if (mips_relax.sequence)
2750		mips_relax.sizes[mips_relax.sequence - 1] += 4;
2751	    }
2752	  else
2753	    {
2754	      /* It looks like we can actually do the swap.  */
2755	      struct mips_cl_insn delay = history[0];
2756	      if (mips_opts.mips16)
2757		{
2758		  know (delay.frag == ip->frag);
2759                  move_insn (ip, delay.frag, delay.where);
2760		  move_insn (&delay, ip->frag, ip->where + insn_length (ip));
2761		}
2762	      else if (relaxed_branch)
2763		{
2764		  /* Add the delay slot instruction to the end of the
2765		     current frag and shrink the fixed part of the
2766		     original frag.  If the branch occupies the tail of
2767		     the latter, move it backwards to cover the gap.  */
2768		  delay.frag->fr_fix -= 4;
2769		  if (delay.frag == ip->frag)
2770		    move_insn (ip, ip->frag, ip->where - 4);
2771		  add_fixed_insn (&delay);
2772		}
2773	      else
2774		{
2775		  move_insn (&delay, ip->frag, ip->where);
2776		  move_insn (ip, history[0].frag, history[0].where);
2777		}
2778	      history[0] = *ip;
2779	      delay.fixed_p = 1;
2780	      insert_into_history (0, 1, &delay);
2781	    }
2782
2783	  /* If that was an unconditional branch, forget the previous
2784	     insn information.  */
2785	  if (pinfo & INSN_UNCOND_BRANCH_DELAY)
2786	    mips_no_prev_insn ();
2787	}
2788      else if (pinfo & INSN_COND_BRANCH_LIKELY)
2789	{
2790	  /* We don't yet optimize a branch likely.  What we should do
2791	     is look at the target, copy the instruction found there
2792	     into the delay slot, and increment the branch to jump to
2793	     the next instruction.  */
2794	  insert_into_history (0, 1, ip);
2795	  emit_nop ();
2796	}
2797      else
2798	insert_into_history (0, 1, ip);
2799    }
2800  else
2801    insert_into_history (0, 1, ip);
2802
2803  /* We just output an insn, so the next one doesn't have a label.  */
2804  mips_clear_insn_labels ();
2805}
2806
2807/* Forget that there was any previous instruction or label.  */
2808
2809static void
2810mips_no_prev_insn (void)
2811{
2812  prev_nop_frag = NULL;
2813  insert_into_history (0, ARRAY_SIZE (history), NOP_INSN);
2814  mips_clear_insn_labels ();
2815}
2816
2817/* This function must be called before we emit something other than
2818   instructions.  It is like mips_no_prev_insn except that it inserts
2819   any NOPS that might be needed by previous instructions.  */
2820
2821void
2822mips_emit_delays (void)
2823{
2824  if (! mips_opts.noreorder)
2825    {
2826      int nops = nops_for_insn (history, NULL);
2827      if (nops > 0)
2828	{
2829	  while (nops-- > 0)
2830	    add_fixed_insn (NOP_INSN);
2831	  mips_move_labels ();
2832	}
2833    }
2834  mips_no_prev_insn ();
2835}
2836
2837/* Start a (possibly nested) noreorder block.  */
2838
2839static void
2840start_noreorder (void)
2841{
2842  if (mips_opts.noreorder == 0)
2843    {
2844      unsigned int i;
2845      int nops;
2846
2847      /* None of the instructions before the .set noreorder can be moved.  */
2848      for (i = 0; i < ARRAY_SIZE (history); i++)
2849	history[i].fixed_p = 1;
2850
2851      /* Insert any nops that might be needed between the .set noreorder
2852	 block and the previous instructions.  We will later remove any
2853	 nops that turn out not to be needed.  */
2854      nops = nops_for_insn (history, NULL);
2855      if (nops > 0)
2856	{
2857	  if (mips_optimize != 0)
2858	    {
2859	      /* Record the frag which holds the nop instructions, so
2860                 that we can remove them if we don't need them.  */
2861	      frag_grow (mips_opts.mips16 ? nops * 2 : nops * 4);
2862	      prev_nop_frag = frag_now;
2863	      prev_nop_frag_holds = nops;
2864	      prev_nop_frag_required = 0;
2865	      prev_nop_frag_since = 0;
2866	    }
2867
2868	  for (; nops > 0; --nops)
2869	    add_fixed_insn (NOP_INSN);
2870
2871	  /* Move on to a new frag, so that it is safe to simply
2872	     decrease the size of prev_nop_frag.  */
2873	  frag_wane (frag_now);
2874	  frag_new (0);
2875	  mips_move_labels ();
2876	}
2877      mips16_mark_labels ();
2878      mips_clear_insn_labels ();
2879    }
2880  mips_opts.noreorder++;
2881  mips_any_noreorder = 1;
2882}
2883
2884/* End a nested noreorder block.  */
2885
2886static void
2887end_noreorder (void)
2888{
2889  mips_opts.noreorder--;
2890  if (mips_opts.noreorder == 0 && prev_nop_frag != NULL)
2891    {
2892      /* Commit to inserting prev_nop_frag_required nops and go back to
2893	 handling nop insertion the .set reorder way.  */
2894      prev_nop_frag->fr_fix -= ((prev_nop_frag_holds - prev_nop_frag_required)
2895				* (mips_opts.mips16 ? 2 : 4));
2896      insert_into_history (prev_nop_frag_since,
2897			   prev_nop_frag_required, NOP_INSN);
2898      prev_nop_frag = NULL;
2899    }
2900}
2901
2902/* Set up global variables for the start of a new macro.  */
2903
2904static void
2905macro_start (void)
2906{
2907  memset (&mips_macro_warning.sizes, 0, sizeof (mips_macro_warning.sizes));
2908  mips_macro_warning.delay_slot_p = (mips_opts.noreorder
2909				     && (history[0].insn_mo->pinfo
2910					 & (INSN_UNCOND_BRANCH_DELAY
2911					    | INSN_COND_BRANCH_DELAY
2912					    | INSN_COND_BRANCH_LIKELY)) != 0);
2913}
2914
2915/* Given that a macro is longer than 4 bytes, return the appropriate warning
2916   for it.  Return null if no warning is needed.  SUBTYPE is a bitmask of
2917   RELAX_DELAY_SLOT and RELAX_NOMACRO.  */
2918
2919static const char *
2920macro_warning (relax_substateT subtype)
2921{
2922  if (subtype & RELAX_DELAY_SLOT)
2923    return _("Macro instruction expanded into multiple instructions"
2924	     " in a branch delay slot");
2925  else if (subtype & RELAX_NOMACRO)
2926    return _("Macro instruction expanded into multiple instructions");
2927  else
2928    return 0;
2929}
2930
2931/* Finish up a macro.  Emit warnings as appropriate.  */
2932
2933static void
2934macro_end (void)
2935{
2936  if (mips_macro_warning.sizes[0] > 4 || mips_macro_warning.sizes[1] > 4)
2937    {
2938      relax_substateT subtype;
2939
2940      /* Set up the relaxation warning flags.  */
2941      subtype = 0;
2942      if (mips_macro_warning.sizes[1] > mips_macro_warning.sizes[0])
2943	subtype |= RELAX_SECOND_LONGER;
2944      if (mips_opts.warn_about_macros)
2945	subtype |= RELAX_NOMACRO;
2946      if (mips_macro_warning.delay_slot_p)
2947	subtype |= RELAX_DELAY_SLOT;
2948
2949      if (mips_macro_warning.sizes[0] > 4 && mips_macro_warning.sizes[1] > 4)
2950	{
2951	  /* Either the macro has a single implementation or both
2952	     implementations are longer than 4 bytes.  Emit the
2953	     warning now.  */
2954	  const char *msg = macro_warning (subtype);
2955	  if (msg != 0)
2956	    as_warn (msg);
2957	}
2958      else
2959	{
2960	  /* One implementation might need a warning but the other
2961	     definitely doesn't.  */
2962	  mips_macro_warning.first_frag->fr_subtype |= subtype;
2963	}
2964    }
2965}
2966
2967/* Read a macro's relocation codes from *ARGS and store them in *R.
2968   The first argument in *ARGS will be either the code for a single
2969   relocation or -1 followed by the three codes that make up a
2970   composite relocation.  */
2971
2972static void
2973macro_read_relocs (va_list *args, bfd_reloc_code_real_type *r)
2974{
2975  int i, next;
2976
2977  next = va_arg (*args, int);
2978  if (next >= 0)
2979    r[0] = (bfd_reloc_code_real_type) next;
2980  else
2981    for (i = 0; i < 3; i++)
2982      r[i] = (bfd_reloc_code_real_type) va_arg (*args, int);
2983}
2984
2985/* Build an instruction created by a macro expansion.  This is passed
2986   a pointer to the count of instructions created so far, an
2987   expression, the name of the instruction to build, an operand format
2988   string, and corresponding arguments.  */
2989
2990static void
2991macro_build (expressionS *ep, const char *name, const char *fmt, ...)
2992{
2993  const struct mips_opcode *mo;
2994  struct mips_cl_insn insn;
2995  bfd_reloc_code_real_type r[3];
2996  va_list args;
2997
2998  va_start (args, fmt);
2999
3000  if (mips_opts.mips16)
3001    {
3002      mips16_macro_build (ep, name, fmt, args);
3003      va_end (args);
3004      return;
3005    }
3006
3007  r[0] = BFD_RELOC_UNUSED;
3008  r[1] = BFD_RELOC_UNUSED;
3009  r[2] = BFD_RELOC_UNUSED;
3010  mo = (struct mips_opcode *) hash_find (op_hash, name);
3011  assert (mo);
3012  assert (strcmp (name, mo->name) == 0);
3013
3014  /* Search until we get a match for NAME.  It is assumed here that
3015     macros will never generate MDMX or MIPS-3D instructions.  */
3016  while (strcmp (fmt, mo->args) != 0
3017	 || mo->pinfo == INSN_MACRO
3018	 || !OPCODE_IS_MEMBER (mo,
3019			       (mips_opts.isa
3020				| (file_ase_mips16 ? INSN_MIPS16 : 0)),
3021			       mips_opts.arch)
3022	 || (mips_opts.arch == CPU_R4650 && (mo->pinfo & FP_D) != 0))
3023    {
3024      ++mo;
3025      assert (mo->name);
3026      assert (strcmp (name, mo->name) == 0);
3027    }
3028
3029  create_insn (&insn, mo);
3030  for (;;)
3031    {
3032      switch (*fmt++)
3033	{
3034	case '\0':
3035	  break;
3036
3037	case ',':
3038	case '(':
3039	case ')':
3040	  continue;
3041
3042	case '+':
3043	  switch (*fmt++)
3044	    {
3045	    case 'A':
3046	    case 'E':
3047	      INSERT_OPERAND (SHAMT, insn, va_arg (args, int));
3048	      continue;
3049
3050	    case 'B':
3051	    case 'F':
3052	      /* Note that in the macro case, these arguments are already
3053		 in MSB form.  (When handling the instruction in the
3054		 non-macro case, these arguments are sizes from which
3055		 MSB values must be calculated.)  */
3056	      INSERT_OPERAND (INSMSB, insn, va_arg (args, int));
3057	      continue;
3058
3059	    case 'C':
3060	    case 'G':
3061	    case 'H':
3062	      /* Note that in the macro case, these arguments are already
3063		 in MSBD form.  (When handling the instruction in the
3064		 non-macro case, these arguments are sizes from which
3065		 MSBD values must be calculated.)  */
3066	      INSERT_OPERAND (EXTMSBD, insn, va_arg (args, int));
3067	      continue;
3068
3069	    default:
3070	      internalError ();
3071	    }
3072	  continue;
3073
3074	case 't':
3075	case 'w':
3076	case 'E':
3077	  INSERT_OPERAND (RT, insn, va_arg (args, int));
3078	  continue;
3079
3080	case 'c':
3081	  INSERT_OPERAND (CODE, insn, va_arg (args, int));
3082	  continue;
3083
3084	case 'T':
3085	case 'W':
3086	  INSERT_OPERAND (FT, insn, va_arg (args, int));
3087	  continue;
3088
3089	case 'd':
3090	case 'G':
3091	case 'K':
3092	  INSERT_OPERAND (RD, insn, va_arg (args, int));
3093	  continue;
3094
3095	case 'U':
3096	  {
3097	    int tmp = va_arg (args, int);
3098
3099	    INSERT_OPERAND (RT, insn, tmp);
3100	    INSERT_OPERAND (RD, insn, tmp);
3101	    continue;
3102	  }
3103
3104	case 'V':
3105	case 'S':
3106	  INSERT_OPERAND (FS, insn, va_arg (args, int));
3107	  continue;
3108
3109	case 'z':
3110	  continue;
3111
3112	case '<':
3113	  INSERT_OPERAND (SHAMT, insn, va_arg (args, int));
3114	  continue;
3115
3116	case 'D':
3117	  INSERT_OPERAND (FD, insn, va_arg (args, int));
3118	  continue;
3119
3120	case 'B':
3121	  INSERT_OPERAND (CODE20, insn, va_arg (args, int));
3122	  continue;
3123
3124	case 'J':
3125	  INSERT_OPERAND (CODE19, insn, va_arg (args, int));
3126	  continue;
3127
3128	case 'q':
3129	  INSERT_OPERAND (CODE2, insn, va_arg (args, int));
3130	  continue;
3131
3132	case 'b':
3133	case 's':
3134	case 'r':
3135	case 'v':
3136	  INSERT_OPERAND (RS, insn, va_arg (args, int));
3137	  continue;
3138
3139	case 'i':
3140	case 'j':
3141	case 'o':
3142	  macro_read_relocs (&args, r);
3143	  assert (*r == BFD_RELOC_GPREL16
3144		  || *r == BFD_RELOC_MIPS_LITERAL
3145		  || *r == BFD_RELOC_MIPS_HIGHER
3146		  || *r == BFD_RELOC_HI16_S
3147		  || *r == BFD_RELOC_LO16
3148		  || *r == BFD_RELOC_MIPS_GOT16
3149		  || *r == BFD_RELOC_MIPS_CALL16
3150		  || *r == BFD_RELOC_MIPS_GOT_DISP
3151		  || *r == BFD_RELOC_MIPS_GOT_PAGE
3152		  || *r == BFD_RELOC_MIPS_GOT_OFST
3153		  || *r == BFD_RELOC_MIPS_GOT_LO16
3154		  || *r == BFD_RELOC_MIPS_CALL_LO16);
3155	  continue;
3156
3157	case 'u':
3158	  macro_read_relocs (&args, r);
3159	  assert (ep != NULL
3160		  && (ep->X_op == O_constant
3161		      || (ep->X_op == O_symbol
3162			  && (*r == BFD_RELOC_MIPS_HIGHEST
3163			      || *r == BFD_RELOC_HI16_S
3164			      || *r == BFD_RELOC_HI16
3165			      || *r == BFD_RELOC_GPREL16
3166			      || *r == BFD_RELOC_MIPS_GOT_HI16
3167			      || *r == BFD_RELOC_MIPS_CALL_HI16))));
3168	  continue;
3169
3170	case 'p':
3171	  assert (ep != NULL);
3172
3173	  /*
3174	   * This allows macro() to pass an immediate expression for
3175	   * creating short branches without creating a symbol.
3176	   *
3177	   * We don't allow branch relaxation for these branches, as
3178	   * they should only appear in ".set nomacro" anyway.
3179	   */
3180	  if (ep->X_op == O_constant)
3181	    {
3182	      if ((ep->X_add_number & 3) != 0)
3183		as_bad (_("branch to misaligned address (0x%lx)"),
3184			(unsigned long) ep->X_add_number);
3185	      if ((ep->X_add_number + 0x20000) & ~0x3ffff)
3186		as_bad (_("branch address range overflow (0x%lx)"),
3187			(unsigned long) ep->X_add_number);
3188	      insn.insn_opcode |= (ep->X_add_number >> 2) & 0xffff;
3189	      ep = NULL;
3190	    }
3191	  else
3192	    *r = BFD_RELOC_16_PCREL_S2;
3193	  continue;
3194
3195	case 'a':
3196	  assert (ep != NULL);
3197	  *r = BFD_RELOC_MIPS_JMP;
3198	  continue;
3199
3200	case 'C':
3201	  insn.insn_opcode |= va_arg (args, unsigned long);
3202	  continue;
3203
3204	default:
3205	  internalError ();
3206	}
3207      break;
3208    }
3209  va_end (args);
3210  assert (*r == BFD_RELOC_UNUSED ? ep == NULL : ep != NULL);
3211
3212  append_insn (&insn, ep, r);
3213}
3214
3215static void
3216mips16_macro_build (expressionS *ep, const char *name, const char *fmt,
3217		    va_list args)
3218{
3219  struct mips_opcode *mo;
3220  struct mips_cl_insn insn;
3221  bfd_reloc_code_real_type r[3]
3222    = {BFD_RELOC_UNUSED, BFD_RELOC_UNUSED, BFD_RELOC_UNUSED};
3223
3224  mo = (struct mips_opcode *) hash_find (mips16_op_hash, name);
3225  assert (mo);
3226  assert (strcmp (name, mo->name) == 0);
3227
3228  while (strcmp (fmt, mo->args) != 0 || mo->pinfo == INSN_MACRO)
3229    {
3230      ++mo;
3231      assert (mo->name);
3232      assert (strcmp (name, mo->name) == 0);
3233    }
3234
3235  create_insn (&insn, mo);
3236  for (;;)
3237    {
3238      int c;
3239
3240      c = *fmt++;
3241      switch (c)
3242	{
3243	case '\0':
3244	  break;
3245
3246	case ',':
3247	case '(':
3248	case ')':
3249	  continue;
3250
3251	case 'y':
3252	case 'w':
3253	  MIPS16_INSERT_OPERAND (RY, insn, va_arg (args, int));
3254	  continue;
3255
3256	case 'x':
3257	case 'v':
3258	  MIPS16_INSERT_OPERAND (RX, insn, va_arg (args, int));
3259	  continue;
3260
3261	case 'z':
3262	  MIPS16_INSERT_OPERAND (RZ, insn, va_arg (args, int));
3263	  continue;
3264
3265	case 'Z':
3266	  MIPS16_INSERT_OPERAND (MOVE32Z, insn, va_arg (args, int));
3267	  continue;
3268
3269	case '0':
3270	case 'S':
3271	case 'P':
3272	case 'R':
3273	  continue;
3274
3275	case 'X':
3276	  MIPS16_INSERT_OPERAND (REGR32, insn, va_arg (args, int));
3277	  continue;
3278
3279	case 'Y':
3280	  {
3281	    int regno;
3282
3283	    regno = va_arg (args, int);
3284	    regno = ((regno & 7) << 2) | ((regno & 0x18) >> 3);
3285	    insn.insn_opcode |= regno << MIPS16OP_SH_REG32R;
3286	  }
3287	  continue;
3288
3289	case '<':
3290	case '>':
3291	case '4':
3292	case '5':
3293	case 'H':
3294	case 'W':
3295	case 'D':
3296	case 'j':
3297	case '8':
3298	case 'V':
3299	case 'C':
3300	case 'U':
3301	case 'k':
3302	case 'K':
3303	case 'p':
3304	case 'q':
3305	  {
3306	    assert (ep != NULL);
3307
3308	    if (ep->X_op != O_constant)
3309	      *r = (int) BFD_RELOC_UNUSED + c;
3310	    else
3311	      {
3312		mips16_immed (NULL, 0, c, ep->X_add_number, FALSE, FALSE,
3313			      FALSE, &insn.insn_opcode, &insn.use_extend,
3314			      &insn.extend);
3315		ep = NULL;
3316		*r = BFD_RELOC_UNUSED;
3317	      }
3318	  }
3319	  continue;
3320
3321	case '6':
3322	  MIPS16_INSERT_OPERAND (IMM6, insn, va_arg (args, int));
3323	  continue;
3324	}
3325
3326      break;
3327    }
3328
3329  assert (*r == BFD_RELOC_UNUSED ? ep == NULL : ep != NULL);
3330
3331  append_insn (&insn, ep, r);
3332}
3333
3334/*
3335 * Sign-extend 32-bit mode constants that have bit 31 set and all
3336 * higher bits unset.
3337 */
3338static void
3339normalize_constant_expr (expressionS *ex)
3340{
3341  if (ex->X_op == O_constant
3342      && IS_ZEXT_32BIT_NUM (ex->X_add_number))
3343    ex->X_add_number = (((ex->X_add_number & 0xffffffff) ^ 0x80000000)
3344			- 0x80000000);
3345}
3346
3347/*
3348 * Sign-extend 32-bit mode address offsets that have bit 31 set and
3349 * all higher bits unset.
3350 */
3351static void
3352normalize_address_expr (expressionS *ex)
3353{
3354  if (((ex->X_op == O_constant && HAVE_32BIT_ADDRESSES)
3355	|| (ex->X_op == O_symbol && HAVE_32BIT_SYMBOLS))
3356      && IS_ZEXT_32BIT_NUM (ex->X_add_number))
3357    ex->X_add_number = (((ex->X_add_number & 0xffffffff) ^ 0x80000000)
3358			- 0x80000000);
3359}
3360
3361/*
3362 * Generate a "jalr" instruction with a relocation hint to the called
3363 * function.  This occurs in NewABI PIC code.
3364 */
3365static void
3366macro_build_jalr (expressionS *ep)
3367{
3368  char *f = NULL;
3369
3370  if (HAVE_NEWABI)
3371    {
3372      frag_grow (8);
3373      f = frag_more (0);
3374    }
3375  macro_build (NULL, "jalr", "d,s", RA, PIC_CALL_REG);
3376  if (HAVE_NEWABI)
3377    fix_new_exp (frag_now, f - frag_now->fr_literal,
3378		 4, ep, FALSE, BFD_RELOC_MIPS_JALR);
3379}
3380
3381/*
3382 * Generate a "lui" instruction.
3383 */
3384static void
3385macro_build_lui (expressionS *ep, int regnum)
3386{
3387  expressionS high_expr;
3388  const struct mips_opcode *mo;
3389  struct mips_cl_insn insn;
3390  bfd_reloc_code_real_type r[3]
3391    = {BFD_RELOC_UNUSED, BFD_RELOC_UNUSED, BFD_RELOC_UNUSED};
3392  const char *name = "lui";
3393  const char *fmt = "t,u";
3394
3395  assert (! mips_opts.mips16);
3396
3397  high_expr = *ep;
3398
3399  if (high_expr.X_op == O_constant)
3400    {
3401      /* we can compute the instruction now without a relocation entry */
3402      high_expr.X_add_number = ((high_expr.X_add_number + 0x8000)
3403				>> 16) & 0xffff;
3404      *r = BFD_RELOC_UNUSED;
3405    }
3406  else
3407    {
3408      assert (ep->X_op == O_symbol);
3409      /* _gp_disp is a special case, used from s_cpload.
3410	 __gnu_local_gp is used if mips_no_shared.  */
3411      assert (mips_pic == NO_PIC
3412	      || (! HAVE_NEWABI
3413		  && strcmp (S_GET_NAME (ep->X_add_symbol), "_gp_disp") == 0)
3414	      || (! mips_in_shared
3415		  && strcmp (S_GET_NAME (ep->X_add_symbol),
3416                             "__gnu_local_gp") == 0));
3417      *r = BFD_RELOC_HI16_S;
3418    }
3419
3420  mo = hash_find (op_hash, name);
3421  assert (strcmp (name, mo->name) == 0);
3422  assert (strcmp (fmt, mo->args) == 0);
3423  create_insn (&insn, mo);
3424
3425  insn.insn_opcode = insn.insn_mo->match;
3426  INSERT_OPERAND (RT, insn, regnum);
3427  if (*r == BFD_RELOC_UNUSED)
3428    {
3429      insn.insn_opcode |= high_expr.X_add_number;
3430      append_insn (&insn, NULL, r);
3431    }
3432  else
3433    append_insn (&insn, &high_expr, r);
3434}
3435
3436/* Generate a sequence of instructions to do a load or store from a constant
3437   offset off of a base register (breg) into/from a target register (treg),
3438   using AT if necessary.  */
3439static void
3440macro_build_ldst_constoffset (expressionS *ep, const char *op,
3441			      int treg, int breg, int dbl)
3442{
3443  assert (ep->X_op == O_constant);
3444
3445  /* Sign-extending 32-bit constants makes their handling easier.  */
3446  if (!dbl)
3447    normalize_constant_expr (ep);
3448
3449  /* Right now, this routine can only handle signed 32-bit constants.  */
3450  if (! IS_SEXT_32BIT_NUM(ep->X_add_number + 0x8000))
3451    as_warn (_("operand overflow"));
3452
3453  if (IS_SEXT_16BIT_NUM(ep->X_add_number))
3454    {
3455      /* Signed 16-bit offset will fit in the op.  Easy!  */
3456      macro_build (ep, op, "t,o(b)", treg, BFD_RELOC_LO16, breg);
3457    }
3458  else
3459    {
3460      /* 32-bit offset, need multiple instructions and AT, like:
3461	   lui      $tempreg,const_hi       (BFD_RELOC_HI16_S)
3462	   addu     $tempreg,$tempreg,$breg
3463           <op>     $treg,const_lo($tempreg)   (BFD_RELOC_LO16)
3464         to handle the complete offset.  */
3465      macro_build_lui (ep, AT);
3466      macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", AT, AT, breg);
3467      macro_build (ep, op, "t,o(b)", treg, BFD_RELOC_LO16, AT);
3468
3469      if (mips_opts.noat)
3470	as_bad (_("Macro used $at after \".set noat\""));
3471    }
3472}
3473
3474/*			set_at()
3475 * Generates code to set the $at register to true (one)
3476 * if reg is less than the immediate expression.
3477 */
3478static void
3479set_at (int reg, int unsignedp)
3480{
3481  if (imm_expr.X_op == O_constant
3482      && imm_expr.X_add_number >= -0x8000
3483      && imm_expr.X_add_number < 0x8000)
3484    macro_build (&imm_expr, unsignedp ? "sltiu" : "slti", "t,r,j",
3485		 AT, reg, BFD_RELOC_LO16);
3486  else
3487    {
3488      load_register (AT, &imm_expr, HAVE_64BIT_GPRS);
3489      macro_build (NULL, unsignedp ? "sltu" : "slt", "d,v,t", AT, reg, AT);
3490    }
3491}
3492
3493/* Warn if an expression is not a constant.  */
3494
3495static void
3496check_absolute_expr (struct mips_cl_insn *ip, expressionS *ex)
3497{
3498  if (ex->X_op == O_big)
3499    as_bad (_("unsupported large constant"));
3500  else if (ex->X_op != O_constant)
3501    as_bad (_("Instruction %s requires absolute expression"),
3502	    ip->insn_mo->name);
3503
3504  if (HAVE_32BIT_GPRS)
3505    normalize_constant_expr (ex);
3506}
3507
3508/* Count the leading zeroes by performing a binary chop. This is a
3509   bulky bit of source, but performance is a LOT better for the
3510   majority of values than a simple loop to count the bits:
3511       for (lcnt = 0; (lcnt < 32); lcnt++)
3512         if ((v) & (1 << (31 - lcnt)))
3513           break;
3514  However it is not code size friendly, and the gain will drop a bit
3515  on certain cached systems.
3516*/
3517#define COUNT_TOP_ZEROES(v)             \
3518  (((v) & ~0xffff) == 0                 \
3519   ? ((v) & ~0xff) == 0                 \
3520     ? ((v) & ~0xf) == 0                \
3521       ? ((v) & ~0x3) == 0              \
3522         ? ((v) & ~0x1) == 0            \
3523           ? !(v)                       \
3524             ? 32                       \
3525             : 31                       \
3526           : 30                         \
3527         : ((v) & ~0x7) == 0            \
3528           ? 29                         \
3529           : 28                         \
3530       : ((v) & ~0x3f) == 0             \
3531         ? ((v) & ~0x1f) == 0           \
3532           ? 27                         \
3533           : 26                         \
3534         : ((v) & ~0x7f) == 0           \
3535           ? 25                         \
3536           : 24                         \
3537     : ((v) & ~0xfff) == 0              \
3538       ? ((v) & ~0x3ff) == 0            \
3539         ? ((v) & ~0x1ff) == 0          \
3540           ? 23                         \
3541           : 22                         \
3542         : ((v) & ~0x7ff) == 0          \
3543           ? 21                         \
3544           : 20                         \
3545       : ((v) & ~0x3fff) == 0           \
3546         ? ((v) & ~0x1fff) == 0         \
3547           ? 19                         \
3548           : 18                         \
3549         : ((v) & ~0x7fff) == 0         \
3550           ? 17                         \
3551           : 16                         \
3552   : ((v) & ~0xffffff) == 0             \
3553     ? ((v) & ~0xfffff) == 0            \
3554       ? ((v) & ~0x3ffff) == 0          \
3555         ? ((v) & ~0x1ffff) == 0        \
3556           ? 15                         \
3557           : 14                         \
3558         : ((v) & ~0x7ffff) == 0        \
3559           ? 13                         \
3560           : 12                         \
3561       : ((v) & ~0x3fffff) == 0         \
3562         ? ((v) & ~0x1fffff) == 0       \
3563           ? 11                         \
3564           : 10                         \
3565         : ((v) & ~0x7fffff) == 0       \
3566           ? 9                          \
3567           : 8                          \
3568     : ((v) & ~0xfffffff) == 0          \
3569       ? ((v) & ~0x3ffffff) == 0        \
3570         ? ((v) & ~0x1ffffff) == 0      \
3571           ? 7                          \
3572           : 6                          \
3573         : ((v) & ~0x7ffffff) == 0      \
3574           ? 5                          \
3575           : 4                          \
3576       : ((v) & ~0x3fffffff) == 0       \
3577         ? ((v) & ~0x1fffffff) == 0     \
3578           ? 3                          \
3579           : 2                          \
3580         : ((v) & ~0x7fffffff) == 0     \
3581           ? 1                          \
3582           : 0)
3583
3584/*			load_register()
3585 *  This routine generates the least number of instructions necessary to load
3586 *  an absolute expression value into a register.
3587 */
3588static void
3589load_register (int reg, expressionS *ep, int dbl)
3590{
3591  int freg;
3592  expressionS hi32, lo32;
3593
3594  if (ep->X_op != O_big)
3595    {
3596      assert (ep->X_op == O_constant);
3597
3598      /* Sign-extending 32-bit constants makes their handling easier.  */
3599      if (!dbl)
3600	normalize_constant_expr (ep);
3601
3602      if (IS_SEXT_16BIT_NUM (ep->X_add_number))
3603	{
3604	  /* We can handle 16 bit signed values with an addiu to
3605	     $zero.  No need to ever use daddiu here, since $zero and
3606	     the result are always correct in 32 bit mode.  */
3607	  macro_build (ep, "addiu", "t,r,j", reg, 0, BFD_RELOC_LO16);
3608	  return;
3609	}
3610      else if (ep->X_add_number >= 0 && ep->X_add_number < 0x10000)
3611	{
3612	  /* We can handle 16 bit unsigned values with an ori to
3613             $zero.  */
3614	  macro_build (ep, "ori", "t,r,i", reg, 0, BFD_RELOC_LO16);
3615	  return;
3616	}
3617      else if ((IS_SEXT_32BIT_NUM (ep->X_add_number)))
3618	{
3619	  /* 32 bit values require an lui.  */
3620	  macro_build (ep, "lui", "t,u", reg, BFD_RELOC_HI16);
3621	  if ((ep->X_add_number & 0xffff) != 0)
3622	    macro_build (ep, "ori", "t,r,i", reg, reg, BFD_RELOC_LO16);
3623	  return;
3624	}
3625    }
3626
3627  /* The value is larger than 32 bits.  */
3628
3629  if (!dbl || HAVE_32BIT_GPRS)
3630    {
3631      char value[32];
3632
3633      sprintf_vma (value, ep->X_add_number);
3634      as_bad (_("Number (0x%s) larger than 32 bits"), value);
3635      macro_build (ep, "addiu", "t,r,j", reg, 0, BFD_RELOC_LO16);
3636      return;
3637    }
3638
3639  if (ep->X_op != O_big)
3640    {
3641      hi32 = *ep;
3642      hi32.X_add_number = (valueT) hi32.X_add_number >> 16;
3643      hi32.X_add_number = (valueT) hi32.X_add_number >> 16;
3644      hi32.X_add_number &= 0xffffffff;
3645      lo32 = *ep;
3646      lo32.X_add_number &= 0xffffffff;
3647    }
3648  else
3649    {
3650      assert (ep->X_add_number > 2);
3651      if (ep->X_add_number == 3)
3652	generic_bignum[3] = 0;
3653      else if (ep->X_add_number > 4)
3654	as_bad (_("Number larger than 64 bits"));
3655      lo32.X_op = O_constant;
3656      lo32.X_add_number = generic_bignum[0] + (generic_bignum[1] << 16);
3657      hi32.X_op = O_constant;
3658      hi32.X_add_number = generic_bignum[2] + (generic_bignum[3] << 16);
3659    }
3660
3661  if (hi32.X_add_number == 0)
3662    freg = 0;
3663  else
3664    {
3665      int shift, bit;
3666      unsigned long hi, lo;
3667
3668      if (hi32.X_add_number == (offsetT) 0xffffffff)
3669	{
3670	  if ((lo32.X_add_number & 0xffff8000) == 0xffff8000)
3671	    {
3672	      macro_build (&lo32, "addiu", "t,r,j", reg, 0, BFD_RELOC_LO16);
3673	      return;
3674	    }
3675	  if (lo32.X_add_number & 0x80000000)
3676	    {
3677	      macro_build (&lo32, "lui", "t,u", reg, BFD_RELOC_HI16);
3678	      if (lo32.X_add_number & 0xffff)
3679		macro_build (&lo32, "ori", "t,r,i", reg, reg, BFD_RELOC_LO16);
3680	      return;
3681	    }
3682	}
3683
3684      /* Check for 16bit shifted constant.  We know that hi32 is
3685         non-zero, so start the mask on the first bit of the hi32
3686         value.  */
3687      shift = 17;
3688      do
3689	{
3690	  unsigned long himask, lomask;
3691
3692	  if (shift < 32)
3693	    {
3694	      himask = 0xffff >> (32 - shift);
3695	      lomask = (0xffff << shift) & 0xffffffff;
3696	    }
3697	  else
3698	    {
3699	      himask = 0xffff << (shift - 32);
3700	      lomask = 0;
3701	    }
3702	  if ((hi32.X_add_number & ~(offsetT) himask) == 0
3703	      && (lo32.X_add_number & ~(offsetT) lomask) == 0)
3704	    {
3705	      expressionS tmp;
3706
3707	      tmp.X_op = O_constant;
3708	      if (shift < 32)
3709		tmp.X_add_number = ((hi32.X_add_number << (32 - shift))
3710				    | (lo32.X_add_number >> shift));
3711	      else
3712		tmp.X_add_number = hi32.X_add_number >> (shift - 32);
3713	      macro_build (&tmp, "ori", "t,r,i", reg, 0, BFD_RELOC_LO16);
3714	      macro_build (NULL, (shift >= 32) ? "dsll32" : "dsll", "d,w,<",
3715			   reg, reg, (shift >= 32) ? shift - 32 : shift);
3716	      return;
3717	    }
3718	  ++shift;
3719	}
3720      while (shift <= (64 - 16));
3721
3722      /* Find the bit number of the lowest one bit, and store the
3723         shifted value in hi/lo.  */
3724      hi = (unsigned long) (hi32.X_add_number & 0xffffffff);
3725      lo = (unsigned long) (lo32.X_add_number & 0xffffffff);
3726      if (lo != 0)
3727	{
3728	  bit = 0;
3729	  while ((lo & 1) == 0)
3730	    {
3731	      lo >>= 1;
3732	      ++bit;
3733	    }
3734	  lo |= (hi & (((unsigned long) 1 << bit) - 1)) << (32 - bit);
3735	  hi >>= bit;
3736	}
3737      else
3738	{
3739	  bit = 32;
3740	  while ((hi & 1) == 0)
3741	    {
3742	      hi >>= 1;
3743	      ++bit;
3744	    }
3745	  lo = hi;
3746	  hi = 0;
3747	}
3748
3749      /* Optimize if the shifted value is a (power of 2) - 1.  */
3750      if ((hi == 0 && ((lo + 1) & lo) == 0)
3751	  || (lo == 0xffffffff && ((hi + 1) & hi) == 0))
3752	{
3753	  shift = COUNT_TOP_ZEROES ((unsigned int) hi32.X_add_number);
3754	  if (shift != 0)
3755	    {
3756	      expressionS tmp;
3757
3758	      /* This instruction will set the register to be all
3759                 ones.  */
3760	      tmp.X_op = O_constant;
3761	      tmp.X_add_number = (offsetT) -1;
3762	      macro_build (&tmp, "addiu", "t,r,j", reg, 0, BFD_RELOC_LO16);
3763	      if (bit != 0)
3764		{
3765		  bit += shift;
3766		  macro_build (NULL, (bit >= 32) ? "dsll32" : "dsll", "d,w,<",
3767			       reg, reg, (bit >= 32) ? bit - 32 : bit);
3768		}
3769	      macro_build (NULL, (shift >= 32) ? "dsrl32" : "dsrl", "d,w,<",
3770			   reg, reg, (shift >= 32) ? shift - 32 : shift);
3771	      return;
3772	    }
3773	}
3774
3775      /* Sign extend hi32 before calling load_register, because we can
3776         generally get better code when we load a sign extended value.  */
3777      if ((hi32.X_add_number & 0x80000000) != 0)
3778	hi32.X_add_number |= ~(offsetT) 0xffffffff;
3779      load_register (reg, &hi32, 0);
3780      freg = reg;
3781    }
3782  if ((lo32.X_add_number & 0xffff0000) == 0)
3783    {
3784      if (freg != 0)
3785	{
3786	  macro_build (NULL, "dsll32", "d,w,<", reg, freg, 0);
3787	  freg = reg;
3788	}
3789    }
3790  else
3791    {
3792      expressionS mid16;
3793
3794      if ((freg == 0) && (lo32.X_add_number == (offsetT) 0xffffffff))
3795	{
3796	  macro_build (&lo32, "lui", "t,u", reg, BFD_RELOC_HI16);
3797	  macro_build (NULL, "dsrl32", "d,w,<", reg, reg, 0);
3798	  return;
3799	}
3800
3801      if (freg != 0)
3802	{
3803	  macro_build (NULL, "dsll", "d,w,<", reg, freg, 16);
3804	  freg = reg;
3805	}
3806      mid16 = lo32;
3807      mid16.X_add_number >>= 16;
3808      macro_build (&mid16, "ori", "t,r,i", reg, freg, BFD_RELOC_LO16);
3809      macro_build (NULL, "dsll", "d,w,<", reg, reg, 16);
3810      freg = reg;
3811    }
3812  if ((lo32.X_add_number & 0xffff) != 0)
3813    macro_build (&lo32, "ori", "t,r,i", reg, freg, BFD_RELOC_LO16);
3814}
3815
3816static inline void
3817load_delay_nop (void)
3818{
3819  if (!gpr_interlocks)
3820    macro_build (NULL, "nop", "");
3821}
3822
3823/* Load an address into a register.  */
3824
3825static void
3826load_address (int reg, expressionS *ep, int *used_at)
3827{
3828  if (ep->X_op != O_constant
3829      && ep->X_op != O_symbol)
3830    {
3831      as_bad (_("expression too complex"));
3832      ep->X_op = O_constant;
3833    }
3834
3835  if (ep->X_op == O_constant)
3836    {
3837      load_register (reg, ep, HAVE_64BIT_ADDRESSES);
3838      return;
3839    }
3840
3841  if (mips_pic == NO_PIC)
3842    {
3843      /* If this is a reference to a GP relative symbol, we want
3844	   addiu	$reg,$gp,<sym>		(BFD_RELOC_GPREL16)
3845	 Otherwise we want
3846	   lui		$reg,<sym>		(BFD_RELOC_HI16_S)
3847	   addiu	$reg,$reg,<sym>		(BFD_RELOC_LO16)
3848	 If we have an addend, we always use the latter form.
3849
3850	 With 64bit address space and a usable $at we want
3851	   lui		$reg,<sym>		(BFD_RELOC_MIPS_HIGHEST)
3852	   lui		$at,<sym>		(BFD_RELOC_HI16_S)
3853	   daddiu	$reg,<sym>		(BFD_RELOC_MIPS_HIGHER)
3854	   daddiu	$at,<sym>		(BFD_RELOC_LO16)
3855	   dsll32	$reg,0
3856	   daddu	$reg,$reg,$at
3857
3858	 If $at is already in use, we use a path which is suboptimal
3859	 on superscalar processors.
3860	   lui		$reg,<sym>		(BFD_RELOC_MIPS_HIGHEST)
3861	   daddiu	$reg,<sym>		(BFD_RELOC_MIPS_HIGHER)
3862	   dsll		$reg,16
3863	   daddiu	$reg,<sym>		(BFD_RELOC_HI16_S)
3864	   dsll		$reg,16
3865	   daddiu	$reg,<sym>		(BFD_RELOC_LO16)
3866
3867	 For GP relative symbols in 64bit address space we can use
3868	 the same sequence as in 32bit address space.  */
3869      if (HAVE_64BIT_SYMBOLS)
3870	{
3871	  if ((valueT) ep->X_add_number <= MAX_GPREL_OFFSET
3872	      && !nopic_need_relax (ep->X_add_symbol, 1))
3873	    {
3874	      relax_start (ep->X_add_symbol);
3875	      macro_build (ep, ADDRESS_ADDI_INSN, "t,r,j", reg,
3876			   mips_gp_register, BFD_RELOC_GPREL16);
3877	      relax_switch ();
3878	    }
3879
3880	  if (*used_at == 0 && !mips_opts.noat)
3881	    {
3882	      macro_build (ep, "lui", "t,u", reg, BFD_RELOC_MIPS_HIGHEST);
3883	      macro_build (ep, "lui", "t,u", AT, BFD_RELOC_HI16_S);
3884	      macro_build (ep, "daddiu", "t,r,j", reg, reg,
3885			   BFD_RELOC_MIPS_HIGHER);
3886	      macro_build (ep, "daddiu", "t,r,j", AT, AT, BFD_RELOC_LO16);
3887	      macro_build (NULL, "dsll32", "d,w,<", reg, reg, 0);
3888	      macro_build (NULL, "daddu", "d,v,t", reg, reg, AT);
3889	      *used_at = 1;
3890	    }
3891	  else
3892	    {
3893	      macro_build (ep, "lui", "t,u", reg, BFD_RELOC_MIPS_HIGHEST);
3894	      macro_build (ep, "daddiu", "t,r,j", reg, reg,
3895			   BFD_RELOC_MIPS_HIGHER);
3896	      macro_build (NULL, "dsll", "d,w,<", reg, reg, 16);
3897	      macro_build (ep, "daddiu", "t,r,j", reg, reg, BFD_RELOC_HI16_S);
3898	      macro_build (NULL, "dsll", "d,w,<", reg, reg, 16);
3899	      macro_build (ep, "daddiu", "t,r,j", reg, reg, BFD_RELOC_LO16);
3900	    }
3901
3902	  if (mips_relax.sequence)
3903	    relax_end ();
3904	}
3905      else
3906	{
3907	  if ((valueT) ep->X_add_number <= MAX_GPREL_OFFSET
3908	      && !nopic_need_relax (ep->X_add_symbol, 1))
3909	    {
3910	      relax_start (ep->X_add_symbol);
3911	      macro_build (ep, ADDRESS_ADDI_INSN, "t,r,j", reg,
3912			   mips_gp_register, BFD_RELOC_GPREL16);
3913	      relax_switch ();
3914	    }
3915	  macro_build_lui (ep, reg);
3916	  macro_build (ep, ADDRESS_ADDI_INSN, "t,r,j",
3917		       reg, reg, BFD_RELOC_LO16);
3918	  if (mips_relax.sequence)
3919	    relax_end ();
3920	}
3921    }
3922  else if (!mips_big_got)
3923    {
3924      expressionS ex;
3925
3926      /* If this is a reference to an external symbol, we want
3927	   lw		$reg,<sym>($gp)		(BFD_RELOC_MIPS_GOT16)
3928	 Otherwise we want
3929	   lw		$reg,<sym>($gp)		(BFD_RELOC_MIPS_GOT16)
3930	   nop
3931	   addiu	$reg,$reg,<sym>		(BFD_RELOC_LO16)
3932	 If there is a constant, it must be added in after.
3933
3934	 If we have NewABI, we want
3935	   lw		$reg,<sym+cst>($gp)	(BFD_RELOC_MIPS_GOT_DISP)
3936         unless we're referencing a global symbol with a non-zero
3937         offset, in which case cst must be added separately.  */
3938      if (HAVE_NEWABI)
3939	{
3940	  if (ep->X_add_number)
3941	    {
3942	      ex.X_add_number = ep->X_add_number;
3943	      ep->X_add_number = 0;
3944	      relax_start (ep->X_add_symbol);
3945	      macro_build (ep, ADDRESS_LOAD_INSN, "t,o(b)", reg,
3946			   BFD_RELOC_MIPS_GOT_DISP, mips_gp_register);
3947	      if (ex.X_add_number < -0x8000 || ex.X_add_number >= 0x8000)
3948		as_bad (_("PIC code offset overflow (max 16 signed bits)"));
3949	      ex.X_op = O_constant;
3950	      macro_build (&ex, ADDRESS_ADDI_INSN, "t,r,j",
3951			   reg, reg, BFD_RELOC_LO16);
3952	      ep->X_add_number = ex.X_add_number;
3953	      relax_switch ();
3954	    }
3955	  macro_build (ep, ADDRESS_LOAD_INSN, "t,o(b)", reg,
3956		       BFD_RELOC_MIPS_GOT_DISP, mips_gp_register);
3957	  if (mips_relax.sequence)
3958	    relax_end ();
3959	}
3960      else
3961	{
3962	  ex.X_add_number = ep->X_add_number;
3963	  ep->X_add_number = 0;
3964	  macro_build (ep, ADDRESS_LOAD_INSN, "t,o(b)", reg,
3965		       BFD_RELOC_MIPS_GOT16, mips_gp_register);
3966	  load_delay_nop ();
3967	  relax_start (ep->X_add_symbol);
3968	  relax_switch ();
3969	  macro_build (ep, ADDRESS_ADDI_INSN, "t,r,j", reg, reg,
3970		       BFD_RELOC_LO16);
3971	  relax_end ();
3972
3973	  if (ex.X_add_number != 0)
3974	    {
3975	      if (ex.X_add_number < -0x8000 || ex.X_add_number >= 0x8000)
3976		as_bad (_("PIC code offset overflow (max 16 signed bits)"));
3977	      ex.X_op = O_constant;
3978	      macro_build (&ex, ADDRESS_ADDI_INSN, "t,r,j",
3979			   reg, reg, BFD_RELOC_LO16);
3980	    }
3981	}
3982    }
3983  else if (mips_big_got)
3984    {
3985      expressionS ex;
3986
3987      /* This is the large GOT case.  If this is a reference to an
3988	 external symbol, we want
3989	   lui		$reg,<sym>		(BFD_RELOC_MIPS_GOT_HI16)
3990	   addu		$reg,$reg,$gp
3991	   lw		$reg,<sym>($reg)	(BFD_RELOC_MIPS_GOT_LO16)
3992
3993	 Otherwise, for a reference to a local symbol in old ABI, we want
3994	   lw		$reg,<sym>($gp)		(BFD_RELOC_MIPS_GOT16)
3995	   nop
3996	   addiu	$reg,$reg,<sym>		(BFD_RELOC_LO16)
3997	 If there is a constant, it must be added in after.
3998
3999	 In the NewABI, for local symbols, with or without offsets, we want:
4000	   lw		$reg,<sym>($gp)		(BFD_RELOC_MIPS_GOT_PAGE)
4001	   addiu	$reg,$reg,<sym>		(BFD_RELOC_MIPS_GOT_OFST)
4002      */
4003      if (HAVE_NEWABI)
4004	{
4005	  ex.X_add_number = ep->X_add_number;
4006	  ep->X_add_number = 0;
4007	  relax_start (ep->X_add_symbol);
4008	  macro_build (ep, "lui", "t,u", reg, BFD_RELOC_MIPS_GOT_HI16);
4009	  macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
4010		       reg, reg, mips_gp_register);
4011	  macro_build (ep, ADDRESS_LOAD_INSN, "t,o(b)",
4012		       reg, BFD_RELOC_MIPS_GOT_LO16, reg);
4013	  if (ex.X_add_number < -0x8000 || ex.X_add_number >= 0x8000)
4014	    as_bad (_("PIC code offset overflow (max 16 signed bits)"));
4015	  else if (ex.X_add_number)
4016	    {
4017	      ex.X_op = O_constant;
4018	      macro_build (&ex, ADDRESS_ADDI_INSN, "t,r,j", reg, reg,
4019			   BFD_RELOC_LO16);
4020	    }
4021
4022	  ep->X_add_number = ex.X_add_number;
4023	  relax_switch ();
4024	  macro_build (ep, ADDRESS_LOAD_INSN, "t,o(b)", reg,
4025		       BFD_RELOC_MIPS_GOT_PAGE, mips_gp_register);
4026	  macro_build (ep, ADDRESS_ADDI_INSN, "t,r,j", reg, reg,
4027		       BFD_RELOC_MIPS_GOT_OFST);
4028	  relax_end ();
4029	}
4030      else
4031	{
4032	  ex.X_add_number = ep->X_add_number;
4033	  ep->X_add_number = 0;
4034	  relax_start (ep->X_add_symbol);
4035	  macro_build (ep, "lui", "t,u", reg, BFD_RELOC_MIPS_GOT_HI16);
4036	  macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
4037		       reg, reg, mips_gp_register);
4038	  macro_build (ep, ADDRESS_LOAD_INSN, "t,o(b)",
4039		       reg, BFD_RELOC_MIPS_GOT_LO16, reg);
4040	  relax_switch ();
4041	  if (reg_needs_delay (mips_gp_register))
4042	    {
4043	      /* We need a nop before loading from $gp.  This special
4044		 check is required because the lui which starts the main
4045		 instruction stream does not refer to $gp, and so will not
4046		 insert the nop which may be required.  */
4047	      macro_build (NULL, "nop", "");
4048	    }
4049	  macro_build (ep, ADDRESS_LOAD_INSN, "t,o(b)", reg,
4050		       BFD_RELOC_MIPS_GOT16, mips_gp_register);
4051	  load_delay_nop ();
4052	  macro_build (ep, ADDRESS_ADDI_INSN, "t,r,j", reg, reg,
4053		       BFD_RELOC_LO16);
4054	  relax_end ();
4055
4056	  if (ex.X_add_number != 0)
4057	    {
4058	      if (ex.X_add_number < -0x8000 || ex.X_add_number >= 0x8000)
4059		as_bad (_("PIC code offset overflow (max 16 signed bits)"));
4060	      ex.X_op = O_constant;
4061	      macro_build (&ex, ADDRESS_ADDI_INSN, "t,r,j", reg, reg,
4062			   BFD_RELOC_LO16);
4063	    }
4064	}
4065    }
4066  else
4067    abort ();
4068
4069  if (mips_opts.noat && *used_at == 1)
4070    as_bad (_("Macro used $at after \".set noat\""));
4071}
4072
4073/* Move the contents of register SOURCE into register DEST.  */
4074
4075static void
4076move_register (int dest, int source)
4077{
4078  macro_build (NULL, HAVE_32BIT_GPRS ? "addu" : "daddu", "d,v,t",
4079	       dest, source, 0);
4080}
4081
4082/* Emit an SVR4 PIC sequence to load address LOCAL into DEST, where
4083   LOCAL is the sum of a symbol and a 16-bit or 32-bit displacement.
4084   The two alternatives are:
4085
4086   Global symbol		Local sybmol
4087   -------------		------------
4088   lw DEST,%got(SYMBOL)		lw DEST,%got(SYMBOL + OFFSET)
4089   ...				...
4090   addiu DEST,DEST,OFFSET	addiu DEST,DEST,%lo(SYMBOL + OFFSET)
4091
4092   load_got_offset emits the first instruction and add_got_offset
4093   emits the second for a 16-bit offset or add_got_offset_hilo emits
4094   a sequence to add a 32-bit offset using a scratch register.  */
4095
4096static void
4097load_got_offset (int dest, expressionS *local)
4098{
4099  expressionS global;
4100
4101  global = *local;
4102  global.X_add_number = 0;
4103
4104  relax_start (local->X_add_symbol);
4105  macro_build (&global, ADDRESS_LOAD_INSN, "t,o(b)", dest,
4106	       BFD_RELOC_MIPS_GOT16, mips_gp_register);
4107  relax_switch ();
4108  macro_build (local, ADDRESS_LOAD_INSN, "t,o(b)", dest,
4109	       BFD_RELOC_MIPS_GOT16, mips_gp_register);
4110  relax_end ();
4111}
4112
4113static void
4114add_got_offset (int dest, expressionS *local)
4115{
4116  expressionS global;
4117
4118  global.X_op = O_constant;
4119  global.X_op_symbol = NULL;
4120  global.X_add_symbol = NULL;
4121  global.X_add_number = local->X_add_number;
4122
4123  relax_start (local->X_add_symbol);
4124  macro_build (&global, ADDRESS_ADDI_INSN, "t,r,j",
4125	       dest, dest, BFD_RELOC_LO16);
4126  relax_switch ();
4127  macro_build (local, ADDRESS_ADDI_INSN, "t,r,j", dest, dest, BFD_RELOC_LO16);
4128  relax_end ();
4129}
4130
4131static void
4132add_got_offset_hilo (int dest, expressionS *local, int tmp)
4133{
4134  expressionS global;
4135  int hold_mips_optimize;
4136
4137  global.X_op = O_constant;
4138  global.X_op_symbol = NULL;
4139  global.X_add_symbol = NULL;
4140  global.X_add_number = local->X_add_number;
4141
4142  relax_start (local->X_add_symbol);
4143  load_register (tmp, &global, HAVE_64BIT_ADDRESSES);
4144  relax_switch ();
4145  /* Set mips_optimize around the lui instruction to avoid
4146     inserting an unnecessary nop after the lw.  */
4147  hold_mips_optimize = mips_optimize;
4148  mips_optimize = 2;
4149  macro_build_lui (&global, tmp);
4150  mips_optimize = hold_mips_optimize;
4151  macro_build (local, ADDRESS_ADDI_INSN, "t,r,j", tmp, tmp, BFD_RELOC_LO16);
4152  relax_end ();
4153
4154  macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", dest, dest, tmp);
4155}
4156
4157/*
4158 *			Build macros
4159 *   This routine implements the seemingly endless macro or synthesized
4160 * instructions and addressing modes in the mips assembly language. Many
4161 * of these macros are simple and are similar to each other. These could
4162 * probably be handled by some kind of table or grammar approach instead of
4163 * this verbose method. Others are not simple macros but are more like
4164 * optimizing code generation.
4165 *   One interesting optimization is when several store macros appear
4166 * consecutively that would load AT with the upper half of the same address.
4167 * The ensuing load upper instructions are ommited. This implies some kind
4168 * of global optimization. We currently only optimize within a single macro.
4169 *   For many of the load and store macros if the address is specified as a
4170 * constant expression in the first 64k of memory (ie ld $2,0x4000c) we
4171 * first load register 'at' with zero and use it as the base register. The
4172 * mips assembler simply uses register $zero. Just one tiny optimization
4173 * we're missing.
4174 */
4175static void
4176macro (struct mips_cl_insn *ip)
4177{
4178  register int treg, sreg, dreg, breg;
4179  int tempreg;
4180  int mask;
4181  int used_at = 0;
4182  expressionS expr1;
4183  const char *s;
4184  const char *s2;
4185  const char *fmt;
4186  int likely = 0;
4187  int dbl = 0;
4188  int coproc = 0;
4189  int lr = 0;
4190  int imm = 0;
4191  int call = 0;
4192  int off;
4193  offsetT maxnum;
4194  bfd_reloc_code_real_type r;
4195  int hold_mips_optimize;
4196
4197  assert (! mips_opts.mips16);
4198
4199  treg = (ip->insn_opcode >> 16) & 0x1f;
4200  dreg = (ip->insn_opcode >> 11) & 0x1f;
4201  sreg = breg = (ip->insn_opcode >> 21) & 0x1f;
4202  mask = ip->insn_mo->mask;
4203
4204  expr1.X_op = O_constant;
4205  expr1.X_op_symbol = NULL;
4206  expr1.X_add_symbol = NULL;
4207  expr1.X_add_number = 1;
4208
4209  switch (mask)
4210    {
4211    case M_DABS:
4212      dbl = 1;
4213    case M_ABS:
4214      /* bgez $a0,.+12
4215	 move v0,$a0
4216	 sub v0,$zero,$a0
4217	 */
4218
4219      start_noreorder ();
4220
4221      expr1.X_add_number = 8;
4222      macro_build (&expr1, "bgez", "s,p", sreg);
4223      if (dreg == sreg)
4224	macro_build (NULL, "nop", "", 0);
4225      else
4226	move_register (dreg, sreg);
4227      macro_build (NULL, dbl ? "dsub" : "sub", "d,v,t", dreg, 0, sreg);
4228
4229      end_noreorder ();
4230      break;
4231
4232    case M_ADD_I:
4233      s = "addi";
4234      s2 = "add";
4235      goto do_addi;
4236    case M_ADDU_I:
4237      s = "addiu";
4238      s2 = "addu";
4239      goto do_addi;
4240    case M_DADD_I:
4241      dbl = 1;
4242      s = "daddi";
4243      s2 = "dadd";
4244      goto do_addi;
4245    case M_DADDU_I:
4246      dbl = 1;
4247      s = "daddiu";
4248      s2 = "daddu";
4249    do_addi:
4250      if (imm_expr.X_op == O_constant
4251	  && imm_expr.X_add_number >= -0x8000
4252	  && imm_expr.X_add_number < 0x8000)
4253	{
4254	  macro_build (&imm_expr, s, "t,r,j", treg, sreg, BFD_RELOC_LO16);
4255	  break;
4256	}
4257      used_at = 1;
4258      load_register (AT, &imm_expr, dbl);
4259      macro_build (NULL, s2, "d,v,t", treg, sreg, AT);
4260      break;
4261
4262    case M_AND_I:
4263      s = "andi";
4264      s2 = "and";
4265      goto do_bit;
4266    case M_OR_I:
4267      s = "ori";
4268      s2 = "or";
4269      goto do_bit;
4270    case M_NOR_I:
4271      s = "";
4272      s2 = "nor";
4273      goto do_bit;
4274    case M_XOR_I:
4275      s = "xori";
4276      s2 = "xor";
4277    do_bit:
4278      if (imm_expr.X_op == O_constant
4279	  && imm_expr.X_add_number >= 0
4280	  && imm_expr.X_add_number < 0x10000)
4281	{
4282	  if (mask != M_NOR_I)
4283	    macro_build (&imm_expr, s, "t,r,i", treg, sreg, BFD_RELOC_LO16);
4284	  else
4285	    {
4286	      macro_build (&imm_expr, "ori", "t,r,i",
4287			   treg, sreg, BFD_RELOC_LO16);
4288	      macro_build (NULL, "nor", "d,v,t", treg, treg, 0);
4289	    }
4290	  break;
4291	}
4292
4293      used_at = 1;
4294      load_register (AT, &imm_expr, HAVE_64BIT_GPRS);
4295      macro_build (NULL, s2, "d,v,t", treg, sreg, AT);
4296      break;
4297
4298    case M_BEQ_I:
4299      s = "beq";
4300      goto beq_i;
4301    case M_BEQL_I:
4302      s = "beql";
4303      likely = 1;
4304      goto beq_i;
4305    case M_BNE_I:
4306      s = "bne";
4307      goto beq_i;
4308    case M_BNEL_I:
4309      s = "bnel";
4310      likely = 1;
4311    beq_i:
4312      if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
4313	{
4314	  macro_build (&offset_expr, s, "s,t,p", sreg, 0);
4315	  break;
4316	}
4317      used_at = 1;
4318      load_register (AT, &imm_expr, HAVE_64BIT_GPRS);
4319      macro_build (&offset_expr, s, "s,t,p", sreg, AT);
4320      break;
4321
4322    case M_BGEL:
4323      likely = 1;
4324    case M_BGE:
4325      if (treg == 0)
4326	{
4327	  macro_build (&offset_expr, likely ? "bgezl" : "bgez", "s,p", sreg);
4328	  break;
4329	}
4330      if (sreg == 0)
4331	{
4332	  macro_build (&offset_expr, likely ? "blezl" : "blez", "s,p", treg);
4333	  break;
4334	}
4335      used_at = 1;
4336      macro_build (NULL, "slt", "d,v,t", AT, sreg, treg);
4337      macro_build (&offset_expr, likely ? "beql" : "beq", "s,t,p", AT, 0);
4338      break;
4339
4340    case M_BGTL_I:
4341      likely = 1;
4342    case M_BGT_I:
4343      /* check for > max integer */
4344      maxnum = 0x7fffffff;
4345      if (HAVE_64BIT_GPRS && sizeof (maxnum) > 4)
4346	{
4347	  maxnum <<= 16;
4348	  maxnum |= 0xffff;
4349	  maxnum <<= 16;
4350	  maxnum |= 0xffff;
4351	}
4352      if (imm_expr.X_op == O_constant
4353	  && imm_expr.X_add_number >= maxnum
4354	  && (HAVE_32BIT_GPRS || sizeof (maxnum) > 4))
4355	{
4356	do_false:
4357	  /* result is always false */
4358	  if (! likely)
4359	    macro_build (NULL, "nop", "", 0);
4360	  else
4361	    macro_build (&offset_expr, "bnel", "s,t,p", 0, 0);
4362	  break;
4363	}
4364      if (imm_expr.X_op != O_constant)
4365	as_bad (_("Unsupported large constant"));
4366      ++imm_expr.X_add_number;
4367      /* FALLTHROUGH */
4368    case M_BGE_I:
4369    case M_BGEL_I:
4370      if (mask == M_BGEL_I)
4371	likely = 1;
4372      if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
4373	{
4374	  macro_build (&offset_expr, likely ? "bgezl" : "bgez", "s,p", sreg);
4375	  break;
4376	}
4377      if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 1)
4378	{
4379	  macro_build (&offset_expr, likely ? "bgtzl" : "bgtz", "s,p", sreg);
4380	  break;
4381	}
4382      maxnum = 0x7fffffff;
4383      if (HAVE_64BIT_GPRS && sizeof (maxnum) > 4)
4384	{
4385	  maxnum <<= 16;
4386	  maxnum |= 0xffff;
4387	  maxnum <<= 16;
4388	  maxnum |= 0xffff;
4389	}
4390      maxnum = - maxnum - 1;
4391      if (imm_expr.X_op == O_constant
4392	  && imm_expr.X_add_number <= maxnum
4393	  && (HAVE_32BIT_GPRS || sizeof (maxnum) > 4))
4394	{
4395	do_true:
4396	  /* result is always true */
4397	  as_warn (_("Branch %s is always true"), ip->insn_mo->name);
4398	  macro_build (&offset_expr, "b", "p");
4399	  break;
4400	}
4401      used_at = 1;
4402      set_at (sreg, 0);
4403      macro_build (&offset_expr, likely ? "beql" : "beq", "s,t,p", AT, 0);
4404      break;
4405
4406    case M_BGEUL:
4407      likely = 1;
4408    case M_BGEU:
4409      if (treg == 0)
4410	goto do_true;
4411      if (sreg == 0)
4412	{
4413	  macro_build (&offset_expr, likely ? "beql" : "beq",
4414		       "s,t,p", 0, treg);
4415	  break;
4416	}
4417      used_at = 1;
4418      macro_build (NULL, "sltu", "d,v,t", AT, sreg, treg);
4419      macro_build (&offset_expr, likely ? "beql" : "beq", "s,t,p", AT, 0);
4420      break;
4421
4422    case M_BGTUL_I:
4423      likely = 1;
4424    case M_BGTU_I:
4425      if (sreg == 0
4426	  || (HAVE_32BIT_GPRS
4427	      && imm_expr.X_op == O_constant
4428	      && imm_expr.X_add_number == (offsetT) 0xffffffff))
4429	goto do_false;
4430      if (imm_expr.X_op != O_constant)
4431	as_bad (_("Unsupported large constant"));
4432      ++imm_expr.X_add_number;
4433      /* FALLTHROUGH */
4434    case M_BGEU_I:
4435    case M_BGEUL_I:
4436      if (mask == M_BGEUL_I)
4437	likely = 1;
4438      if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
4439	goto do_true;
4440      if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 1)
4441	{
4442	  macro_build (&offset_expr, likely ? "bnel" : "bne",
4443		       "s,t,p", sreg, 0);
4444	  break;
4445	}
4446      used_at = 1;
4447      set_at (sreg, 1);
4448      macro_build (&offset_expr, likely ? "beql" : "beq", "s,t,p", AT, 0);
4449      break;
4450
4451    case M_BGTL:
4452      likely = 1;
4453    case M_BGT:
4454      if (treg == 0)
4455	{
4456	  macro_build (&offset_expr, likely ? "bgtzl" : "bgtz", "s,p", sreg);
4457	  break;
4458	}
4459      if (sreg == 0)
4460	{
4461	  macro_build (&offset_expr, likely ? "bltzl" : "bltz", "s,p", treg);
4462	  break;
4463	}
4464      used_at = 1;
4465      macro_build (NULL, "slt", "d,v,t", AT, treg, sreg);
4466      macro_build (&offset_expr, likely ? "bnel" : "bne", "s,t,p", AT, 0);
4467      break;
4468
4469    case M_BGTUL:
4470      likely = 1;
4471    case M_BGTU:
4472      if (treg == 0)
4473	{
4474	  macro_build (&offset_expr, likely ? "bnel" : "bne",
4475		       "s,t,p", sreg, 0);
4476	  break;
4477	}
4478      if (sreg == 0)
4479	goto do_false;
4480      used_at = 1;
4481      macro_build (NULL, "sltu", "d,v,t", AT, treg, sreg);
4482      macro_build (&offset_expr, likely ? "bnel" : "bne", "s,t,p", AT, 0);
4483      break;
4484
4485    case M_BLEL:
4486      likely = 1;
4487    case M_BLE:
4488      if (treg == 0)
4489	{
4490	  macro_build (&offset_expr, likely ? "blezl" : "blez", "s,p", sreg);
4491	  break;
4492	}
4493      if (sreg == 0)
4494	{
4495	  macro_build (&offset_expr, likely ? "bgezl" : "bgez", "s,p", treg);
4496	  break;
4497	}
4498      used_at = 1;
4499      macro_build (NULL, "slt", "d,v,t", AT, treg, sreg);
4500      macro_build (&offset_expr, likely ? "beql" : "beq", "s,t,p", AT, 0);
4501      break;
4502
4503    case M_BLEL_I:
4504      likely = 1;
4505    case M_BLE_I:
4506      maxnum = 0x7fffffff;
4507      if (HAVE_64BIT_GPRS && sizeof (maxnum) > 4)
4508	{
4509	  maxnum <<= 16;
4510	  maxnum |= 0xffff;
4511	  maxnum <<= 16;
4512	  maxnum |= 0xffff;
4513	}
4514      if (imm_expr.X_op == O_constant
4515	  && imm_expr.X_add_number >= maxnum
4516	  && (HAVE_32BIT_GPRS || sizeof (maxnum) > 4))
4517	goto do_true;
4518      if (imm_expr.X_op != O_constant)
4519	as_bad (_("Unsupported large constant"));
4520      ++imm_expr.X_add_number;
4521      /* FALLTHROUGH */
4522    case M_BLT_I:
4523    case M_BLTL_I:
4524      if (mask == M_BLTL_I)
4525	likely = 1;
4526      if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
4527	{
4528	  macro_build (&offset_expr, likely ? "bltzl" : "bltz", "s,p", sreg);
4529	  break;
4530	}
4531      if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 1)
4532	{
4533	  macro_build (&offset_expr, likely ? "blezl" : "blez", "s,p", sreg);
4534	  break;
4535	}
4536      used_at = 1;
4537      set_at (sreg, 0);
4538      macro_build (&offset_expr, likely ? "bnel" : "bne", "s,t,p", AT, 0);
4539      break;
4540
4541    case M_BLEUL:
4542      likely = 1;
4543    case M_BLEU:
4544      if (treg == 0)
4545	{
4546	  macro_build (&offset_expr, likely ? "beql" : "beq",
4547		       "s,t,p", sreg, 0);
4548	  break;
4549	}
4550      if (sreg == 0)
4551	goto do_true;
4552      used_at = 1;
4553      macro_build (NULL, "sltu", "d,v,t", AT, treg, sreg);
4554      macro_build (&offset_expr, likely ? "beql" : "beq", "s,t,p", AT, 0);
4555      break;
4556
4557    case M_BLEUL_I:
4558      likely = 1;
4559    case M_BLEU_I:
4560      if (sreg == 0
4561	  || (HAVE_32BIT_GPRS
4562	      && imm_expr.X_op == O_constant
4563	      && imm_expr.X_add_number == (offsetT) 0xffffffff))
4564	goto do_true;
4565      if (imm_expr.X_op != O_constant)
4566	as_bad (_("Unsupported large constant"));
4567      ++imm_expr.X_add_number;
4568      /* FALLTHROUGH */
4569    case M_BLTU_I:
4570    case M_BLTUL_I:
4571      if (mask == M_BLTUL_I)
4572	likely = 1;
4573      if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
4574	goto do_false;
4575      if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 1)
4576	{
4577	  macro_build (&offset_expr, likely ? "beql" : "beq",
4578		       "s,t,p", sreg, 0);
4579	  break;
4580	}
4581      used_at = 1;
4582      set_at (sreg, 1);
4583      macro_build (&offset_expr, likely ? "bnel" : "bne", "s,t,p", AT, 0);
4584      break;
4585
4586    case M_BLTL:
4587      likely = 1;
4588    case M_BLT:
4589      if (treg == 0)
4590	{
4591	  macro_build (&offset_expr, likely ? "bltzl" : "bltz", "s,p", sreg);
4592	  break;
4593	}
4594      if (sreg == 0)
4595	{
4596	  macro_build (&offset_expr, likely ? "bgtzl" : "bgtz", "s,p", treg);
4597	  break;
4598	}
4599      used_at = 1;
4600      macro_build (NULL, "slt", "d,v,t", AT, sreg, treg);
4601      macro_build (&offset_expr, likely ? "bnel" : "bne", "s,t,p", AT, 0);
4602      break;
4603
4604    case M_BLTUL:
4605      likely = 1;
4606    case M_BLTU:
4607      if (treg == 0)
4608	goto do_false;
4609      if (sreg == 0)
4610	{
4611	  macro_build (&offset_expr, likely ? "bnel" : "bne",
4612		       "s,t,p", 0, treg);
4613	  break;
4614	}
4615      used_at = 1;
4616      macro_build (NULL, "sltu", "d,v,t", AT, sreg, treg);
4617      macro_build (&offset_expr, likely ? "bnel" : "bne", "s,t,p", AT, 0);
4618      break;
4619
4620    case M_DEXT:
4621      {
4622	unsigned long pos;
4623	unsigned long size;
4624
4625        if (imm_expr.X_op != O_constant || imm2_expr.X_op != O_constant)
4626	  {
4627	    as_bad (_("Unsupported large constant"));
4628	    pos = size = 1;
4629	  }
4630	else
4631	  {
4632	    pos = (unsigned long) imm_expr.X_add_number;
4633	    size = (unsigned long) imm2_expr.X_add_number;
4634	  }
4635
4636	if (pos > 63)
4637	  {
4638	    as_bad (_("Improper position (%lu)"), pos);
4639	    pos = 1;
4640	  }
4641        if (size == 0 || size > 64
4642	    || (pos + size - 1) > 63)
4643	  {
4644	    as_bad (_("Improper extract size (%lu, position %lu)"),
4645		    size, pos);
4646	    size = 1;
4647	  }
4648
4649	if (size <= 32 && pos < 32)
4650	  {
4651	    s = "dext";
4652	    fmt = "t,r,+A,+C";
4653	  }
4654	else if (size <= 32)
4655	  {
4656	    s = "dextu";
4657	    fmt = "t,r,+E,+H";
4658	  }
4659	else
4660	  {
4661	    s = "dextm";
4662	    fmt = "t,r,+A,+G";
4663	  }
4664	macro_build ((expressionS *) NULL, s, fmt, treg, sreg, pos, size - 1);
4665      }
4666      break;
4667
4668    case M_DINS:
4669      {
4670	unsigned long pos;
4671	unsigned long size;
4672
4673        if (imm_expr.X_op != O_constant || imm2_expr.X_op != O_constant)
4674	  {
4675	    as_bad (_("Unsupported large constant"));
4676	    pos = size = 1;
4677	  }
4678	else
4679	  {
4680	    pos = (unsigned long) imm_expr.X_add_number;
4681	    size = (unsigned long) imm2_expr.X_add_number;
4682	  }
4683
4684	if (pos > 63)
4685	  {
4686	    as_bad (_("Improper position (%lu)"), pos);
4687	    pos = 1;
4688	  }
4689        if (size == 0 || size > 64
4690	    || (pos + size - 1) > 63)
4691	  {
4692	    as_bad (_("Improper insert size (%lu, position %lu)"),
4693		    size, pos);
4694	    size = 1;
4695	  }
4696
4697	if (pos < 32 && (pos + size - 1) < 32)
4698	  {
4699	    s = "dins";
4700	    fmt = "t,r,+A,+B";
4701	  }
4702	else if (pos >= 32)
4703	  {
4704	    s = "dinsu";
4705	    fmt = "t,r,+E,+F";
4706	  }
4707	else
4708	  {
4709	    s = "dinsm";
4710	    fmt = "t,r,+A,+F";
4711	  }
4712	macro_build ((expressionS *) NULL, s, fmt, treg, sreg, pos,
4713		     pos + size - 1);
4714      }
4715      break;
4716
4717    case M_DDIV_3:
4718      dbl = 1;
4719    case M_DIV_3:
4720      s = "mflo";
4721      goto do_div3;
4722    case M_DREM_3:
4723      dbl = 1;
4724    case M_REM_3:
4725      s = "mfhi";
4726    do_div3:
4727      if (treg == 0)
4728	{
4729	  as_warn (_("Divide by zero."));
4730	  if (mips_trap)
4731	    macro_build (NULL, "teq", "s,t,q", 0, 0, 7);
4732	  else
4733	    macro_build (NULL, "break", "c", 7);
4734	  break;
4735	}
4736
4737      start_noreorder ();
4738      if (mips_trap)
4739	{
4740	  macro_build (NULL, "teq", "s,t,q", treg, 0, 7);
4741	  macro_build (NULL, dbl ? "ddiv" : "div", "z,s,t", sreg, treg);
4742	}
4743      else
4744	{
4745	  expr1.X_add_number = 8;
4746	  macro_build (&expr1, "bne", "s,t,p", treg, 0);
4747	  macro_build (NULL, dbl ? "ddiv" : "div", "z,s,t", sreg, treg);
4748	  macro_build (NULL, "break", "c", 7);
4749	}
4750      expr1.X_add_number = -1;
4751      used_at = 1;
4752      load_register (AT, &expr1, dbl);
4753      expr1.X_add_number = mips_trap ? (dbl ? 12 : 8) : (dbl ? 20 : 16);
4754      macro_build (&expr1, "bne", "s,t,p", treg, AT);
4755      if (dbl)
4756	{
4757	  expr1.X_add_number = 1;
4758	  load_register (AT, &expr1, dbl);
4759	  macro_build (NULL, "dsll32", "d,w,<", AT, AT, 31);
4760	}
4761      else
4762	{
4763	  expr1.X_add_number = 0x80000000;
4764	  macro_build (&expr1, "lui", "t,u", AT, BFD_RELOC_HI16);
4765	}
4766      if (mips_trap)
4767	{
4768	  macro_build (NULL, "teq", "s,t,q", sreg, AT, 6);
4769	  /* We want to close the noreorder block as soon as possible, so
4770	     that later insns are available for delay slot filling.  */
4771	  end_noreorder ();
4772	}
4773      else
4774	{
4775	  expr1.X_add_number = 8;
4776	  macro_build (&expr1, "bne", "s,t,p", sreg, AT);
4777	  macro_build (NULL, "nop", "", 0);
4778
4779	  /* We want to close the noreorder block as soon as possible, so
4780	     that later insns are available for delay slot filling.  */
4781	  end_noreorder ();
4782
4783	  macro_build (NULL, "break", "c", 6);
4784	}
4785      macro_build (NULL, s, "d", dreg);
4786      break;
4787
4788    case M_DIV_3I:
4789      s = "div";
4790      s2 = "mflo";
4791      goto do_divi;
4792    case M_DIVU_3I:
4793      s = "divu";
4794      s2 = "mflo";
4795      goto do_divi;
4796    case M_REM_3I:
4797      s = "div";
4798      s2 = "mfhi";
4799      goto do_divi;
4800    case M_REMU_3I:
4801      s = "divu";
4802      s2 = "mfhi";
4803      goto do_divi;
4804    case M_DDIV_3I:
4805      dbl = 1;
4806      s = "ddiv";
4807      s2 = "mflo";
4808      goto do_divi;
4809    case M_DDIVU_3I:
4810      dbl = 1;
4811      s = "ddivu";
4812      s2 = "mflo";
4813      goto do_divi;
4814    case M_DREM_3I:
4815      dbl = 1;
4816      s = "ddiv";
4817      s2 = "mfhi";
4818      goto do_divi;
4819    case M_DREMU_3I:
4820      dbl = 1;
4821      s = "ddivu";
4822      s2 = "mfhi";
4823    do_divi:
4824      if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
4825	{
4826	  as_warn (_("Divide by zero."));
4827	  if (mips_trap)
4828	    macro_build (NULL, "teq", "s,t,q", 0, 0, 7);
4829	  else
4830	    macro_build (NULL, "break", "c", 7);
4831	  break;
4832	}
4833      if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 1)
4834	{
4835	  if (strcmp (s2, "mflo") == 0)
4836	    move_register (dreg, sreg);
4837	  else
4838	    move_register (dreg, 0);
4839	  break;
4840	}
4841      if (imm_expr.X_op == O_constant
4842	  && imm_expr.X_add_number == -1
4843	  && s[strlen (s) - 1] != 'u')
4844	{
4845	  if (strcmp (s2, "mflo") == 0)
4846	    {
4847	      macro_build (NULL, dbl ? "dneg" : "neg", "d,w", dreg, sreg);
4848	    }
4849	  else
4850	    move_register (dreg, 0);
4851	  break;
4852	}
4853
4854      used_at = 1;
4855      load_register (AT, &imm_expr, dbl);
4856      macro_build (NULL, s, "z,s,t", sreg, AT);
4857      macro_build (NULL, s2, "d", dreg);
4858      break;
4859
4860    case M_DIVU_3:
4861      s = "divu";
4862      s2 = "mflo";
4863      goto do_divu3;
4864    case M_REMU_3:
4865      s = "divu";
4866      s2 = "mfhi";
4867      goto do_divu3;
4868    case M_DDIVU_3:
4869      s = "ddivu";
4870      s2 = "mflo";
4871      goto do_divu3;
4872    case M_DREMU_3:
4873      s = "ddivu";
4874      s2 = "mfhi";
4875    do_divu3:
4876      start_noreorder ();
4877      if (mips_trap)
4878	{
4879	  macro_build (NULL, "teq", "s,t,q", treg, 0, 7);
4880	  macro_build (NULL, s, "z,s,t", sreg, treg);
4881	  /* We want to close the noreorder block as soon as possible, so
4882	     that later insns are available for delay slot filling.  */
4883	  end_noreorder ();
4884	}
4885      else
4886	{
4887	  expr1.X_add_number = 8;
4888	  macro_build (&expr1, "bne", "s,t,p", treg, 0);
4889	  macro_build (NULL, s, "z,s,t", sreg, treg);
4890
4891	  /* We want to close the noreorder block as soon as possible, so
4892	     that later insns are available for delay slot filling.  */
4893	  end_noreorder ();
4894	  macro_build (NULL, "break", "c", 7);
4895	}
4896      macro_build (NULL, s2, "d", dreg);
4897      break;
4898
4899    case M_DLCA_AB:
4900      dbl = 1;
4901    case M_LCA_AB:
4902      call = 1;
4903      goto do_la;
4904    case M_DLA_AB:
4905      dbl = 1;
4906    case M_LA_AB:
4907    do_la:
4908      /* Load the address of a symbol into a register.  If breg is not
4909	 zero, we then add a base register to it.  */
4910
4911      if (dbl && HAVE_32BIT_GPRS)
4912	as_warn (_("dla used to load 32-bit register"));
4913
4914      if (! dbl && HAVE_64BIT_OBJECTS)
4915	as_warn (_("la used to load 64-bit address"));
4916
4917      if (offset_expr.X_op == O_constant
4918	  && offset_expr.X_add_number >= -0x8000
4919	  && offset_expr.X_add_number < 0x8000)
4920	{
4921	  macro_build (&offset_expr, ADDRESS_ADDI_INSN,
4922		       "t,r,j", treg, sreg, BFD_RELOC_LO16);
4923	  break;
4924	}
4925
4926      if (!mips_opts.noat && (treg == breg))
4927	{
4928	  tempreg = AT;
4929	  used_at = 1;
4930	}
4931      else
4932	{
4933	  tempreg = treg;
4934	}
4935
4936      if (offset_expr.X_op != O_symbol
4937	  && offset_expr.X_op != O_constant)
4938	{
4939	  as_bad (_("expression too complex"));
4940	  offset_expr.X_op = O_constant;
4941	}
4942
4943      if (offset_expr.X_op == O_constant)
4944	load_register (tempreg, &offset_expr, HAVE_64BIT_ADDRESSES);
4945      else if (mips_pic == NO_PIC)
4946	{
4947	  /* If this is a reference to a GP relative symbol, we want
4948	       addiu	$tempreg,$gp,<sym>	(BFD_RELOC_GPREL16)
4949	     Otherwise we want
4950	       lui	$tempreg,<sym>		(BFD_RELOC_HI16_S)
4951	       addiu	$tempreg,$tempreg,<sym>	(BFD_RELOC_LO16)
4952	     If we have a constant, we need two instructions anyhow,
4953	     so we may as well always use the latter form.
4954
4955	     With 64bit address space and a usable $at we want
4956	       lui	$tempreg,<sym>		(BFD_RELOC_MIPS_HIGHEST)
4957	       lui	$at,<sym>		(BFD_RELOC_HI16_S)
4958	       daddiu	$tempreg,<sym>		(BFD_RELOC_MIPS_HIGHER)
4959	       daddiu	$at,<sym>		(BFD_RELOC_LO16)
4960	       dsll32	$tempreg,0
4961	       daddu	$tempreg,$tempreg,$at
4962
4963	     If $at is already in use, we use a path which is suboptimal
4964	     on superscalar processors.
4965	       lui	$tempreg,<sym>		(BFD_RELOC_MIPS_HIGHEST)
4966	       daddiu	$tempreg,<sym>		(BFD_RELOC_MIPS_HIGHER)
4967	       dsll	$tempreg,16
4968	       daddiu	$tempreg,<sym>		(BFD_RELOC_HI16_S)
4969	       dsll	$tempreg,16
4970	       daddiu	$tempreg,<sym>		(BFD_RELOC_LO16)
4971
4972	     For GP relative symbols in 64bit address space we can use
4973	     the same sequence as in 32bit address space.  */
4974	  if (HAVE_64BIT_SYMBOLS)
4975	    {
4976	      if ((valueT) offset_expr.X_add_number <= MAX_GPREL_OFFSET
4977		  && !nopic_need_relax (offset_expr.X_add_symbol, 1))
4978		{
4979		  relax_start (offset_expr.X_add_symbol);
4980		  macro_build (&offset_expr, ADDRESS_ADDI_INSN, "t,r,j",
4981			       tempreg, mips_gp_register, BFD_RELOC_GPREL16);
4982		  relax_switch ();
4983		}
4984
4985	      if (used_at == 0 && !mips_opts.noat)
4986		{
4987		  macro_build (&offset_expr, "lui", "t,u",
4988			       tempreg, BFD_RELOC_MIPS_HIGHEST);
4989		  macro_build (&offset_expr, "lui", "t,u",
4990			       AT, BFD_RELOC_HI16_S);
4991		  macro_build (&offset_expr, "daddiu", "t,r,j",
4992			       tempreg, tempreg, BFD_RELOC_MIPS_HIGHER);
4993		  macro_build (&offset_expr, "daddiu", "t,r,j",
4994			       AT, AT, BFD_RELOC_LO16);
4995		  macro_build (NULL, "dsll32", "d,w,<", tempreg, tempreg, 0);
4996		  macro_build (NULL, "daddu", "d,v,t", tempreg, tempreg, AT);
4997		  used_at = 1;
4998		}
4999	      else
5000		{
5001		  macro_build (&offset_expr, "lui", "t,u",
5002			       tempreg, BFD_RELOC_MIPS_HIGHEST);
5003		  macro_build (&offset_expr, "daddiu", "t,r,j",
5004			       tempreg, tempreg, BFD_RELOC_MIPS_HIGHER);
5005		  macro_build (NULL, "dsll", "d,w,<", tempreg, tempreg, 16);
5006		  macro_build (&offset_expr, "daddiu", "t,r,j",
5007			       tempreg, tempreg, BFD_RELOC_HI16_S);
5008		  macro_build (NULL, "dsll", "d,w,<", tempreg, tempreg, 16);
5009		  macro_build (&offset_expr, "daddiu", "t,r,j",
5010			       tempreg, tempreg, BFD_RELOC_LO16);
5011		}
5012
5013	      if (mips_relax.sequence)
5014		relax_end ();
5015	    }
5016	  else
5017	    {
5018	      if ((valueT) offset_expr.X_add_number <= MAX_GPREL_OFFSET
5019		  && !nopic_need_relax (offset_expr.X_add_symbol, 1))
5020		{
5021		  relax_start (offset_expr.X_add_symbol);
5022		  macro_build (&offset_expr, ADDRESS_ADDI_INSN, "t,r,j",
5023			       tempreg, mips_gp_register, BFD_RELOC_GPREL16);
5024		  relax_switch ();
5025		}
5026	      if (!IS_SEXT_32BIT_NUM (offset_expr.X_add_number))
5027		as_bad (_("offset too large"));
5028	      macro_build_lui (&offset_expr, tempreg);
5029	      macro_build (&offset_expr, ADDRESS_ADDI_INSN, "t,r,j",
5030			   tempreg, tempreg, BFD_RELOC_LO16);
5031	      if (mips_relax.sequence)
5032		relax_end ();
5033	    }
5034	}
5035      else if (!mips_big_got && !HAVE_NEWABI)
5036	{
5037	  int lw_reloc_type = (int) BFD_RELOC_MIPS_GOT16;
5038
5039	  /* If this is a reference to an external symbol, and there
5040	     is no constant, we want
5041	       lw	$tempreg,<sym>($gp)	(BFD_RELOC_MIPS_GOT16)
5042	     or for lca or if tempreg is PIC_CALL_REG
5043	       lw	$tempreg,<sym>($gp)	(BFD_RELOC_MIPS_CALL16)
5044	     For a local symbol, we want
5045	       lw	$tempreg,<sym>($gp)	(BFD_RELOC_MIPS_GOT16)
5046	       nop
5047	       addiu	$tempreg,$tempreg,<sym>	(BFD_RELOC_LO16)
5048
5049	     If we have a small constant, and this is a reference to
5050	     an external symbol, we want
5051	       lw	$tempreg,<sym>($gp)	(BFD_RELOC_MIPS_GOT16)
5052	       nop
5053	       addiu	$tempreg,$tempreg,<constant>
5054	     For a local symbol, we want the same instruction
5055	     sequence, but we output a BFD_RELOC_LO16 reloc on the
5056	     addiu instruction.
5057
5058	     If we have a large constant, and this is a reference to
5059	     an external symbol, we want
5060	       lw	$tempreg,<sym>($gp)	(BFD_RELOC_MIPS_GOT16)
5061	       lui	$at,<hiconstant>
5062	       addiu	$at,$at,<loconstant>
5063	       addu	$tempreg,$tempreg,$at
5064	     For a local symbol, we want the same instruction
5065	     sequence, but we output a BFD_RELOC_LO16 reloc on the
5066	     addiu instruction.
5067	   */
5068
5069	  if (offset_expr.X_add_number == 0)
5070	    {
5071	      if (mips_pic == SVR4_PIC
5072		  && breg == 0
5073		  && (call || tempreg == PIC_CALL_REG))
5074		lw_reloc_type = (int) BFD_RELOC_MIPS_CALL16;
5075
5076	      relax_start (offset_expr.X_add_symbol);
5077	      macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)", tempreg,
5078			   lw_reloc_type, mips_gp_register);
5079	      if (breg != 0)
5080		{
5081		  /* We're going to put in an addu instruction using
5082		     tempreg, so we may as well insert the nop right
5083		     now.  */
5084		  load_delay_nop ();
5085		}
5086	      relax_switch ();
5087	      macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)",
5088			   tempreg, BFD_RELOC_MIPS_GOT16, mips_gp_register);
5089	      load_delay_nop ();
5090	      macro_build (&offset_expr, ADDRESS_ADDI_INSN, "t,r,j",
5091			   tempreg, tempreg, BFD_RELOC_LO16);
5092	      relax_end ();
5093	      /* FIXME: If breg == 0, and the next instruction uses
5094		 $tempreg, then if this variant case is used an extra
5095		 nop will be generated.  */
5096	    }
5097	  else if (offset_expr.X_add_number >= -0x8000
5098		   && offset_expr.X_add_number < 0x8000)
5099	    {
5100	      load_got_offset (tempreg, &offset_expr);
5101	      load_delay_nop ();
5102	      add_got_offset (tempreg, &offset_expr);
5103	    }
5104	  else
5105	    {
5106	      expr1.X_add_number = offset_expr.X_add_number;
5107	      offset_expr.X_add_number =
5108		((offset_expr.X_add_number + 0x8000) & 0xffff) - 0x8000;
5109	      load_got_offset (tempreg, &offset_expr);
5110	      offset_expr.X_add_number = expr1.X_add_number;
5111	      /* If we are going to add in a base register, and the
5112		 target register and the base register are the same,
5113		 then we are using AT as a temporary register.  Since
5114		 we want to load the constant into AT, we add our
5115		 current AT (from the global offset table) and the
5116		 register into the register now, and pretend we were
5117		 not using a base register.  */
5118	      if (breg == treg)
5119		{
5120		  load_delay_nop ();
5121		  macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
5122			       treg, AT, breg);
5123		  breg = 0;
5124		  tempreg = treg;
5125		}
5126	      add_got_offset_hilo (tempreg, &offset_expr, AT);
5127	      used_at = 1;
5128	    }
5129	}
5130      else if (!mips_big_got && HAVE_NEWABI)
5131	{
5132	  int add_breg_early = 0;
5133
5134	  /* If this is a reference to an external, and there is no
5135	     constant, or local symbol (*), with or without a
5136	     constant, we want
5137	       lw	$tempreg,<sym>($gp)	(BFD_RELOC_MIPS_GOT_DISP)
5138	     or for lca or if tempreg is PIC_CALL_REG
5139	       lw	$tempreg,<sym>($gp)	(BFD_RELOC_MIPS_CALL16)
5140
5141	     If we have a small constant, and this is a reference to
5142	     an external symbol, we want
5143	       lw	$tempreg,<sym>($gp)	(BFD_RELOC_MIPS_GOT_DISP)
5144	       addiu	$tempreg,$tempreg,<constant>
5145
5146	     If we have a large constant, and this is a reference to
5147	     an external symbol, we want
5148	       lw	$tempreg,<sym>($gp)	(BFD_RELOC_MIPS_GOT_DISP)
5149	       lui	$at,<hiconstant>
5150	       addiu	$at,$at,<loconstant>
5151	       addu	$tempreg,$tempreg,$at
5152
5153	     (*) Other assemblers seem to prefer GOT_PAGE/GOT_OFST for
5154	     local symbols, even though it introduces an additional
5155	     instruction.  */
5156
5157	  if (offset_expr.X_add_number)
5158	    {
5159	      expr1.X_add_number = offset_expr.X_add_number;
5160	      offset_expr.X_add_number = 0;
5161
5162	      relax_start (offset_expr.X_add_symbol);
5163	      macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)", tempreg,
5164			   BFD_RELOC_MIPS_GOT_DISP, mips_gp_register);
5165
5166	      if (expr1.X_add_number >= -0x8000
5167		  && expr1.X_add_number < 0x8000)
5168		{
5169		  macro_build (&expr1, ADDRESS_ADDI_INSN, "t,r,j",
5170			       tempreg, tempreg, BFD_RELOC_LO16);
5171		}
5172	      else if (IS_SEXT_32BIT_NUM (expr1.X_add_number + 0x8000))
5173		{
5174		  int dreg;
5175
5176		  /* If we are going to add in a base register, and the
5177		     target register and the base register are the same,
5178		     then we are using AT as a temporary register.  Since
5179		     we want to load the constant into AT, we add our
5180		     current AT (from the global offset table) and the
5181		     register into the register now, and pretend we were
5182		     not using a base register.  */
5183		  if (breg != treg)
5184		    dreg = tempreg;
5185		  else
5186		    {
5187		      assert (tempreg == AT);
5188		      macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
5189				   treg, AT, breg);
5190		      dreg = treg;
5191		      add_breg_early = 1;
5192		    }
5193
5194		  load_register (AT, &expr1, HAVE_64BIT_ADDRESSES);
5195		  macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
5196			       dreg, dreg, AT);
5197
5198		  used_at = 1;
5199		}
5200	      else
5201		as_bad (_("PIC code offset overflow (max 32 signed bits)"));
5202
5203	      relax_switch ();
5204	      offset_expr.X_add_number = expr1.X_add_number;
5205
5206	      macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)", tempreg,
5207			   BFD_RELOC_MIPS_GOT_DISP, mips_gp_register);
5208	      if (add_breg_early)
5209		{
5210		  macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
5211			       treg, tempreg, breg);
5212		  breg = 0;
5213		  tempreg = treg;
5214		}
5215	      relax_end ();
5216	    }
5217	  else if (breg == 0 && (call || tempreg == PIC_CALL_REG))
5218	    {
5219	      relax_start (offset_expr.X_add_symbol);
5220	      macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)", tempreg,
5221			   BFD_RELOC_MIPS_CALL16, mips_gp_register);
5222	      relax_switch ();
5223	      macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)", tempreg,
5224			   BFD_RELOC_MIPS_GOT_DISP, mips_gp_register);
5225	      relax_end ();
5226	    }
5227	  else
5228	    {
5229	      macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)", tempreg,
5230			   BFD_RELOC_MIPS_GOT_DISP, mips_gp_register);
5231	    }
5232	}
5233      else if (mips_big_got && !HAVE_NEWABI)
5234	{
5235	  int gpdelay;
5236	  int lui_reloc_type = (int) BFD_RELOC_MIPS_GOT_HI16;
5237	  int lw_reloc_type = (int) BFD_RELOC_MIPS_GOT_LO16;
5238	  int local_reloc_type = (int) BFD_RELOC_MIPS_GOT16;
5239
5240	  /* This is the large GOT case.  If this is a reference to an
5241	     external symbol, and there is no constant, we want
5242	       lui	$tempreg,<sym>		(BFD_RELOC_MIPS_GOT_HI16)
5243	       addu	$tempreg,$tempreg,$gp
5244	       lw	$tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_LO16)
5245	     or for lca or if tempreg is PIC_CALL_REG
5246	       lui	$tempreg,<sym>		(BFD_RELOC_MIPS_CALL_HI16)
5247	       addu	$tempreg,$tempreg,$gp
5248	       lw	$tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_CALL_LO16)
5249	     For a local symbol, we want
5250	       lw	$tempreg,<sym>($gp)	(BFD_RELOC_MIPS_GOT16)
5251	       nop
5252	       addiu	$tempreg,$tempreg,<sym>	(BFD_RELOC_LO16)
5253
5254	     If we have a small constant, and this is a reference to
5255	     an external symbol, we want
5256	       lui	$tempreg,<sym>		(BFD_RELOC_MIPS_GOT_HI16)
5257	       addu	$tempreg,$tempreg,$gp
5258	       lw	$tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_LO16)
5259	       nop
5260	       addiu	$tempreg,$tempreg,<constant>
5261	     For a local symbol, we want
5262	       lw	$tempreg,<sym>($gp)	(BFD_RELOC_MIPS_GOT16)
5263	       nop
5264	       addiu	$tempreg,$tempreg,<constant> (BFD_RELOC_LO16)
5265
5266	     If we have a large constant, and this is a reference to
5267	     an external symbol, we want
5268	       lui	$tempreg,<sym>		(BFD_RELOC_MIPS_GOT_HI16)
5269	       addu	$tempreg,$tempreg,$gp
5270	       lw	$tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_LO16)
5271	       lui	$at,<hiconstant>
5272	       addiu	$at,$at,<loconstant>
5273	       addu	$tempreg,$tempreg,$at
5274	     For a local symbol, we want
5275	       lw	$tempreg,<sym>($gp)	(BFD_RELOC_MIPS_GOT16)
5276	       lui	$at,<hiconstant>
5277	       addiu	$at,$at,<loconstant>	(BFD_RELOC_LO16)
5278	       addu	$tempreg,$tempreg,$at
5279	  */
5280
5281	  expr1.X_add_number = offset_expr.X_add_number;
5282	  offset_expr.X_add_number = 0;
5283	  relax_start (offset_expr.X_add_symbol);
5284	  gpdelay = reg_needs_delay (mips_gp_register);
5285	  if (expr1.X_add_number == 0 && breg == 0
5286	      && (call || tempreg == PIC_CALL_REG))
5287	    {
5288	      lui_reloc_type = (int) BFD_RELOC_MIPS_CALL_HI16;
5289	      lw_reloc_type = (int) BFD_RELOC_MIPS_CALL_LO16;
5290	    }
5291	  macro_build (&offset_expr, "lui", "t,u", tempreg, lui_reloc_type);
5292	  macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
5293		       tempreg, tempreg, mips_gp_register);
5294	  macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)",
5295		       tempreg, lw_reloc_type, tempreg);
5296	  if (expr1.X_add_number == 0)
5297	    {
5298	      if (breg != 0)
5299		{
5300		  /* We're going to put in an addu instruction using
5301		     tempreg, so we may as well insert the nop right
5302		     now.  */
5303		  load_delay_nop ();
5304		}
5305	    }
5306	  else if (expr1.X_add_number >= -0x8000
5307		   && expr1.X_add_number < 0x8000)
5308	    {
5309	      load_delay_nop ();
5310	      macro_build (&expr1, ADDRESS_ADDI_INSN, "t,r,j",
5311			   tempreg, tempreg, BFD_RELOC_LO16);
5312	    }
5313	  else
5314	    {
5315	      int dreg;
5316
5317	      /* If we are going to add in a base register, and the
5318		 target register and the base register are the same,
5319		 then we are using AT as a temporary register.  Since
5320		 we want to load the constant into AT, we add our
5321		 current AT (from the global offset table) and the
5322		 register into the register now, and pretend we were
5323		 not using a base register.  */
5324	      if (breg != treg)
5325		dreg = tempreg;
5326	      else
5327		{
5328		  assert (tempreg == AT);
5329		  load_delay_nop ();
5330		  macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
5331			       treg, AT, breg);
5332		  dreg = treg;
5333		}
5334
5335	      load_register (AT, &expr1, HAVE_64BIT_ADDRESSES);
5336	      macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", dreg, dreg, AT);
5337
5338	      used_at = 1;
5339	    }
5340	  offset_expr.X_add_number =
5341	    ((expr1.X_add_number + 0x8000) & 0xffff) - 0x8000;
5342	  relax_switch ();
5343
5344	  if (gpdelay)
5345	    {
5346	      /* This is needed because this instruction uses $gp, but
5347		 the first instruction on the main stream does not.  */
5348	      macro_build (NULL, "nop", "");
5349	    }
5350
5351	  macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)", tempreg,
5352		       local_reloc_type, mips_gp_register);
5353	  if (expr1.X_add_number >= -0x8000
5354	      && expr1.X_add_number < 0x8000)
5355	    {
5356	      load_delay_nop ();
5357	      macro_build (&offset_expr, ADDRESS_ADDI_INSN, "t,r,j",
5358			   tempreg, tempreg, BFD_RELOC_LO16);
5359	      /* FIXME: If add_number is 0, and there was no base
5360		 register, the external symbol case ended with a load,
5361		 so if the symbol turns out to not be external, and
5362		 the next instruction uses tempreg, an unnecessary nop
5363		 will be inserted.  */
5364	    }
5365	  else
5366	    {
5367	      if (breg == treg)
5368		{
5369		  /* We must add in the base register now, as in the
5370		     external symbol case.  */
5371		  assert (tempreg == AT);
5372		  load_delay_nop ();
5373		  macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
5374			       treg, AT, breg);
5375		  tempreg = treg;
5376		  /* We set breg to 0 because we have arranged to add
5377		     it in in both cases.  */
5378		  breg = 0;
5379		}
5380
5381	      macro_build_lui (&expr1, AT);
5382	      macro_build (&offset_expr, ADDRESS_ADDI_INSN, "t,r,j",
5383			   AT, AT, BFD_RELOC_LO16);
5384	      macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
5385			   tempreg, tempreg, AT);
5386	      used_at = 1;
5387	    }
5388	  relax_end ();
5389	}
5390      else if (mips_big_got && HAVE_NEWABI)
5391	{
5392	  int lui_reloc_type = (int) BFD_RELOC_MIPS_GOT_HI16;
5393	  int lw_reloc_type = (int) BFD_RELOC_MIPS_GOT_LO16;
5394	  int add_breg_early = 0;
5395
5396	  /* This is the large GOT case.  If this is a reference to an
5397	     external symbol, and there is no constant, we want
5398	       lui	$tempreg,<sym>		(BFD_RELOC_MIPS_GOT_HI16)
5399	       add	$tempreg,$tempreg,$gp
5400	       lw	$tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_LO16)
5401	     or for lca or if tempreg is PIC_CALL_REG
5402	       lui	$tempreg,<sym>		(BFD_RELOC_MIPS_CALL_HI16)
5403	       add	$tempreg,$tempreg,$gp
5404	       lw	$tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_CALL_LO16)
5405
5406	     If we have a small constant, and this is a reference to
5407	     an external symbol, we want
5408	       lui	$tempreg,<sym>		(BFD_RELOC_MIPS_GOT_HI16)
5409	       add	$tempreg,$tempreg,$gp
5410	       lw	$tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_LO16)
5411	       addi	$tempreg,$tempreg,<constant>
5412
5413	     If we have a large constant, and this is a reference to
5414	     an external symbol, we want
5415	       lui	$tempreg,<sym>		(BFD_RELOC_MIPS_GOT_HI16)
5416	       addu	$tempreg,$tempreg,$gp
5417	       lw	$tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_LO16)
5418	       lui	$at,<hiconstant>
5419	       addi	$at,$at,<loconstant>
5420	       add	$tempreg,$tempreg,$at
5421
5422	     If we have NewABI, and we know it's a local symbol, we want
5423	       lw	$reg,<sym>($gp)		(BFD_RELOC_MIPS_GOT_PAGE)
5424	       addiu	$reg,$reg,<sym>		(BFD_RELOC_MIPS_GOT_OFST)
5425	     otherwise we have to resort to GOT_HI16/GOT_LO16.  */
5426
5427	  relax_start (offset_expr.X_add_symbol);
5428
5429	  expr1.X_add_number = offset_expr.X_add_number;
5430	  offset_expr.X_add_number = 0;
5431
5432	  if (expr1.X_add_number == 0 && breg == 0
5433	      && (call || tempreg == PIC_CALL_REG))
5434	    {
5435	      lui_reloc_type = (int) BFD_RELOC_MIPS_CALL_HI16;
5436	      lw_reloc_type = (int) BFD_RELOC_MIPS_CALL_LO16;
5437	    }
5438	  macro_build (&offset_expr, "lui", "t,u", tempreg, lui_reloc_type);
5439	  macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
5440		       tempreg, tempreg, mips_gp_register);
5441	  macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)",
5442		       tempreg, lw_reloc_type, tempreg);
5443
5444	  if (expr1.X_add_number == 0)
5445	    ;
5446	  else if (expr1.X_add_number >= -0x8000
5447		   && expr1.X_add_number < 0x8000)
5448	    {
5449	      macro_build (&expr1, ADDRESS_ADDI_INSN, "t,r,j",
5450			   tempreg, tempreg, BFD_RELOC_LO16);
5451	    }
5452	  else if (IS_SEXT_32BIT_NUM (expr1.X_add_number + 0x8000))
5453	    {
5454	      int dreg;
5455
5456	      /* If we are going to add in a base register, and the
5457		 target register and the base register are the same,
5458		 then we are using AT as a temporary register.  Since
5459		 we want to load the constant into AT, we add our
5460		 current AT (from the global offset table) and the
5461		 register into the register now, and pretend we were
5462		 not using a base register.  */
5463	      if (breg != treg)
5464		dreg = tempreg;
5465	      else
5466		{
5467		  assert (tempreg == AT);
5468		  macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
5469			       treg, AT, breg);
5470		  dreg = treg;
5471		  add_breg_early = 1;
5472		}
5473
5474	      load_register (AT, &expr1, HAVE_64BIT_ADDRESSES);
5475	      macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", dreg, dreg, AT);
5476
5477	      used_at = 1;
5478	    }
5479	  else
5480	    as_bad (_("PIC code offset overflow (max 32 signed bits)"));
5481
5482	  relax_switch ();
5483	  offset_expr.X_add_number = expr1.X_add_number;
5484	  macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)", tempreg,
5485		       BFD_RELOC_MIPS_GOT_PAGE, mips_gp_register);
5486	  macro_build (&offset_expr, ADDRESS_ADDI_INSN, "t,r,j", tempreg,
5487		       tempreg, BFD_RELOC_MIPS_GOT_OFST);
5488	  if (add_breg_early)
5489	    {
5490	      macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
5491			   treg, tempreg, breg);
5492	      breg = 0;
5493	      tempreg = treg;
5494	    }
5495	  relax_end ();
5496	}
5497      else
5498	abort ();
5499
5500      if (breg != 0)
5501	macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", treg, tempreg, breg);
5502      break;
5503
5504    case M_J_A:
5505      /* The j instruction may not be used in PIC code, since it
5506	 requires an absolute address.  We convert it to a b
5507	 instruction.  */
5508      if (mips_pic == NO_PIC)
5509	macro_build (&offset_expr, "j", "a");
5510      else
5511	macro_build (&offset_expr, "b", "p");
5512      break;
5513
5514      /* The jal instructions must be handled as macros because when
5515	 generating PIC code they expand to multi-instruction
5516	 sequences.  Normally they are simple instructions.  */
5517    case M_JAL_1:
5518      dreg = RA;
5519      /* Fall through.  */
5520    case M_JAL_2:
5521      if (mips_pic == NO_PIC)
5522	macro_build (NULL, "jalr", "d,s", dreg, sreg);
5523      else
5524	{
5525	  if (sreg != PIC_CALL_REG)
5526	    as_warn (_("MIPS PIC call to register other than $25"));
5527
5528	  macro_build (NULL, "jalr", "d,s", dreg, sreg);
5529	  if (mips_pic == SVR4_PIC && !HAVE_NEWABI)
5530	    {
5531	      if (mips_cprestore_offset < 0)
5532		as_warn (_("No .cprestore pseudo-op used in PIC code"));
5533	      else
5534		{
5535		  if (! mips_frame_reg_valid)
5536		    {
5537		      as_warn (_("No .frame pseudo-op used in PIC code"));
5538		      /* Quiet this warning.  */
5539		      mips_frame_reg_valid = 1;
5540		    }
5541		  if (! mips_cprestore_valid)
5542		    {
5543		      as_warn (_("No .cprestore pseudo-op used in PIC code"));
5544		      /* Quiet this warning.  */
5545		      mips_cprestore_valid = 1;
5546		    }
5547		  expr1.X_add_number = mips_cprestore_offset;
5548  		  macro_build_ldst_constoffset (&expr1, ADDRESS_LOAD_INSN,
5549						mips_gp_register,
5550						mips_frame_reg,
5551						HAVE_64BIT_ADDRESSES);
5552		}
5553	    }
5554	}
5555
5556      break;
5557
5558    case M_JAL_A:
5559      if (mips_pic == NO_PIC)
5560	macro_build (&offset_expr, "jal", "a");
5561      else if (mips_pic == SVR4_PIC)
5562	{
5563	  /* If this is a reference to an external symbol, and we are
5564	     using a small GOT, we want
5565	       lw	$25,<sym>($gp)		(BFD_RELOC_MIPS_CALL16)
5566	       nop
5567	       jalr	$ra,$25
5568	       nop
5569	       lw	$gp,cprestore($sp)
5570	     The cprestore value is set using the .cprestore
5571	     pseudo-op.  If we are using a big GOT, we want
5572	       lui	$25,<sym>		(BFD_RELOC_MIPS_CALL_HI16)
5573	       addu	$25,$25,$gp
5574	       lw	$25,<sym>($25)		(BFD_RELOC_MIPS_CALL_LO16)
5575	       nop
5576	       jalr	$ra,$25
5577	       nop
5578	       lw	$gp,cprestore($sp)
5579	     If the symbol is not external, we want
5580	       lw	$25,<sym>($gp)		(BFD_RELOC_MIPS_GOT16)
5581	       nop
5582	       addiu	$25,$25,<sym>		(BFD_RELOC_LO16)
5583	       jalr	$ra,$25
5584	       nop
5585	       lw $gp,cprestore($sp)
5586
5587	     For NewABI, we use the same CALL16 or CALL_HI16/CALL_LO16
5588	     sequences above, minus nops, unless the symbol is local,
5589	     which enables us to use GOT_PAGE/GOT_OFST (big got) or
5590	     GOT_DISP.  */
5591	  if (HAVE_NEWABI)
5592	    {
5593	      if (! mips_big_got)
5594		{
5595		  relax_start (offset_expr.X_add_symbol);
5596		  macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)",
5597			       PIC_CALL_REG, BFD_RELOC_MIPS_CALL16,
5598			       mips_gp_register);
5599		  relax_switch ();
5600		  macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)",
5601			       PIC_CALL_REG, BFD_RELOC_MIPS_GOT_DISP,
5602			       mips_gp_register);
5603		  relax_end ();
5604		}
5605	      else
5606		{
5607		  relax_start (offset_expr.X_add_symbol);
5608		  macro_build (&offset_expr, "lui", "t,u", PIC_CALL_REG,
5609			       BFD_RELOC_MIPS_CALL_HI16);
5610		  macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", PIC_CALL_REG,
5611			       PIC_CALL_REG, mips_gp_register);
5612		  macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)",
5613			       PIC_CALL_REG, BFD_RELOC_MIPS_CALL_LO16,
5614			       PIC_CALL_REG);
5615		  relax_switch ();
5616		  macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)",
5617			       PIC_CALL_REG, BFD_RELOC_MIPS_GOT_PAGE,
5618			       mips_gp_register);
5619		  macro_build (&offset_expr, ADDRESS_ADDI_INSN, "t,r,j",
5620			       PIC_CALL_REG, PIC_CALL_REG,
5621			       BFD_RELOC_MIPS_GOT_OFST);
5622		  relax_end ();
5623		}
5624
5625	      macro_build_jalr (&offset_expr);
5626	    }
5627	  else
5628	    {
5629	      relax_start (offset_expr.X_add_symbol);
5630	      if (! mips_big_got)
5631		{
5632		  macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)",
5633			       PIC_CALL_REG, BFD_RELOC_MIPS_CALL16,
5634			       mips_gp_register);
5635		  load_delay_nop ();
5636		  relax_switch ();
5637		}
5638	      else
5639		{
5640		  int gpdelay;
5641
5642		  gpdelay = reg_needs_delay (mips_gp_register);
5643		  macro_build (&offset_expr, "lui", "t,u", PIC_CALL_REG,
5644			       BFD_RELOC_MIPS_CALL_HI16);
5645		  macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", PIC_CALL_REG,
5646			       PIC_CALL_REG, mips_gp_register);
5647		  macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)",
5648			       PIC_CALL_REG, BFD_RELOC_MIPS_CALL_LO16,
5649			       PIC_CALL_REG);
5650		  load_delay_nop ();
5651		  relax_switch ();
5652		  if (gpdelay)
5653		    macro_build (NULL, "nop", "");
5654		}
5655	      macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)",
5656			   PIC_CALL_REG, BFD_RELOC_MIPS_GOT16,
5657			   mips_gp_register);
5658	      load_delay_nop ();
5659	      macro_build (&offset_expr, ADDRESS_ADDI_INSN, "t,r,j",
5660			   PIC_CALL_REG, PIC_CALL_REG, BFD_RELOC_LO16);
5661	      relax_end ();
5662	      macro_build_jalr (&offset_expr);
5663
5664	      if (mips_cprestore_offset < 0)
5665		as_warn (_("No .cprestore pseudo-op used in PIC code"));
5666	      else
5667		{
5668		  if (! mips_frame_reg_valid)
5669		    {
5670		      as_warn (_("No .frame pseudo-op used in PIC code"));
5671		      /* Quiet this warning.  */
5672		      mips_frame_reg_valid = 1;
5673		    }
5674		  if (! mips_cprestore_valid)
5675		    {
5676		      as_warn (_("No .cprestore pseudo-op used in PIC code"));
5677		      /* Quiet this warning.  */
5678		      mips_cprestore_valid = 1;
5679		    }
5680		  if (mips_opts.noreorder)
5681		    macro_build (NULL, "nop", "");
5682		  expr1.X_add_number = mips_cprestore_offset;
5683  		  macro_build_ldst_constoffset (&expr1, ADDRESS_LOAD_INSN,
5684						mips_gp_register,
5685						mips_frame_reg,
5686						HAVE_64BIT_ADDRESSES);
5687		}
5688	    }
5689	}
5690      else
5691	abort ();
5692
5693      break;
5694
5695    case M_LB_AB:
5696      s = "lb";
5697      goto ld;
5698    case M_LBU_AB:
5699      s = "lbu";
5700      goto ld;
5701    case M_LH_AB:
5702      s = "lh";
5703      goto ld;
5704    case M_LHU_AB:
5705      s = "lhu";
5706      goto ld;
5707    case M_LW_AB:
5708      s = "lw";
5709      goto ld;
5710    case M_LWC0_AB:
5711      s = "lwc0";
5712      /* Itbl support may require additional care here.  */
5713      coproc = 1;
5714      goto ld;
5715    case M_LWC1_AB:
5716      s = "lwc1";
5717      /* Itbl support may require additional care here.  */
5718      coproc = 1;
5719      goto ld;
5720    case M_LWC2_AB:
5721      s = "lwc2";
5722      /* Itbl support may require additional care here.  */
5723      coproc = 1;
5724      goto ld;
5725    case M_LWC3_AB:
5726      s = "lwc3";
5727      /* Itbl support may require additional care here.  */
5728      coproc = 1;
5729      goto ld;
5730    case M_LWL_AB:
5731      s = "lwl";
5732      lr = 1;
5733      goto ld;
5734    case M_LWR_AB:
5735      s = "lwr";
5736      lr = 1;
5737      goto ld;
5738    case M_LDC1_AB:
5739      if (mips_opts.arch == CPU_R4650)
5740	{
5741	  as_bad (_("opcode not supported on this processor"));
5742	  break;
5743	}
5744      s = "ldc1";
5745      /* Itbl support may require additional care here.  */
5746      coproc = 1;
5747      goto ld;
5748    case M_LDC2_AB:
5749      s = "ldc2";
5750      /* Itbl support may require additional care here.  */
5751      coproc = 1;
5752      goto ld;
5753    case M_LDC3_AB:
5754      s = "ldc3";
5755      /* Itbl support may require additional care here.  */
5756      coproc = 1;
5757      goto ld;
5758    case M_LDL_AB:
5759      s = "ldl";
5760      lr = 1;
5761      goto ld;
5762    case M_LDR_AB:
5763      s = "ldr";
5764      lr = 1;
5765      goto ld;
5766    case M_LL_AB:
5767      s = "ll";
5768      goto ld;
5769    case M_LLD_AB:
5770      s = "lld";
5771      goto ld;
5772    case M_LWU_AB:
5773      s = "lwu";
5774    ld:
5775      if (mips_opts.arch == CPU_OCTEON
5776	   && octeon_error_on_unsupported
5777           && (mask == M_LDC1_AB || mask == M_LDC2_AB || mask == M_LDC3_AB
5778               || mask == M_L_DOB || mask == M_L_DAB
5779               || mask == M_LI_D || mask == M_LI_DD
5780               || mask == M_LI_S || mask == M_LI_SS))
5781        {
5782          as_bad (_("opcode not implemented in Octeon `%s'"), ip->insn_mo->name);
5783          return;
5784        }
5785      if (breg == treg || coproc || lr)
5786	{
5787	  tempreg = AT;
5788	  used_at = 1;
5789	}
5790      else
5791	{
5792	  tempreg = treg;
5793	}
5794      goto ld_st;
5795    case M_SB_AB:
5796      s = "sb";
5797      goto st;
5798    case M_SH_AB:
5799      s = "sh";
5800      goto st;
5801    case M_SW_AB:
5802      s = "sw";
5803      goto st;
5804    case M_SWC0_AB:
5805      s = "swc0";
5806      /* Itbl support may require additional care here.  */
5807      coproc = 1;
5808      goto st;
5809    case M_SWC1_AB:
5810      s = "swc1";
5811      /* Itbl support may require additional care here.  */
5812      coproc = 1;
5813      goto st;
5814    case M_SWC2_AB:
5815      s = "swc2";
5816      /* Itbl support may require additional care here.  */
5817      coproc = 1;
5818      goto st;
5819    case M_SWC3_AB:
5820      s = "swc3";
5821      /* Itbl support may require additional care here.  */
5822      coproc = 1;
5823      goto st;
5824    case M_SWL_AB:
5825      s = "swl";
5826      goto st;
5827    case M_SWR_AB:
5828      s = "swr";
5829      goto st;
5830    case M_SC_AB:
5831      s = "sc";
5832      goto st;
5833    case M_SCD_AB:
5834      s = "scd";
5835      goto st;
5836    case M_SDC1_AB:
5837      if (mips_opts.arch == CPU_R4650)
5838	{
5839	  as_bad (_("opcode not supported on this processor"));
5840	  break;
5841	}
5842      s = "sdc1";
5843      coproc = 1;
5844      /* Itbl support may require additional care here.  */
5845      goto st;
5846    case M_SDC2_AB:
5847      s = "sdc2";
5848      /* Itbl support may require additional care here.  */
5849      coproc = 1;
5850      goto st;
5851    case M_SDC3_AB:
5852      s = "sdc3";
5853      /* Itbl support may require additional care here.  */
5854      coproc = 1;
5855      goto st;
5856    case M_SDL_AB:
5857      s = "sdl";
5858      goto st;
5859    case M_SDR_AB:
5860      s = "sdr";
5861    st:
5862      if (mips_opts.arch == CPU_OCTEON
5863	  && octeon_error_on_unsupported
5864          && (mask == M_SWC0_AB || mask == M_SWC1_AB || mask == M_SWC2_AB
5865              || mask == M_SDC1_AB || mask == M_SDC2_AB || mask == M_SDC3_AB
5866              || mask == M_S_DAB || mask == M_S_DOB))
5867        {
5868          as_bad (_("opcode not implemented in Octeon `%s'"), ip->insn_mo->name);
5869          return;
5870        }
5871      tempreg = AT;
5872      used_at = 1;
5873    ld_st:
5874      /* Itbl support may require additional care here.  */
5875      if (mask == M_LWC1_AB
5876	  || mask == M_SWC1_AB
5877	  || mask == M_LDC1_AB
5878	  || mask == M_SDC1_AB
5879	  || mask == M_L_DAB
5880	  || mask == M_S_DAB)
5881	fmt = "T,o(b)";
5882      else if (coproc)
5883	fmt = "E,o(b)";
5884      else
5885	fmt = "t,o(b)";
5886
5887      if (offset_expr.X_op != O_constant
5888	  && offset_expr.X_op != O_symbol)
5889	{
5890	  as_bad (_("expression too complex"));
5891	  offset_expr.X_op = O_constant;
5892	}
5893
5894      if (HAVE_32BIT_ADDRESSES
5895	  && !IS_SEXT_32BIT_NUM (offset_expr.X_add_number))
5896	{
5897	  char value [32];
5898
5899	  sprintf_vma (value, offset_expr.X_add_number);
5900	  as_bad (_("Number (0x%s) larger than 32 bits"), value);
5901	}
5902
5903      /* A constant expression in PIC code can be handled just as it
5904	 is in non PIC code.  */
5905      if (offset_expr.X_op == O_constant)
5906	{
5907	  expr1.X_add_number = ((offset_expr.X_add_number + 0x8000)
5908				& ~(bfd_vma) 0xffff);
5909	  normalize_address_expr (&expr1);
5910	  load_register (tempreg, &expr1, HAVE_64BIT_ADDRESSES);
5911	  if (breg != 0)
5912	    macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
5913			 tempreg, tempreg, breg);
5914	  macro_build (&offset_expr, s, fmt, treg, BFD_RELOC_LO16, tempreg);
5915	}
5916      else if (mips_pic == NO_PIC)
5917	{
5918	  /* If this is a reference to a GP relative symbol, and there
5919	     is no base register, we want
5920	       <op>	$treg,<sym>($gp)	(BFD_RELOC_GPREL16)
5921	     Otherwise, if there is no base register, we want
5922	       lui	$tempreg,<sym>		(BFD_RELOC_HI16_S)
5923	       <op>	$treg,<sym>($tempreg)	(BFD_RELOC_LO16)
5924	     If we have a constant, we need two instructions anyhow,
5925	     so we always use the latter form.
5926
5927	     If we have a base register, and this is a reference to a
5928	     GP relative symbol, we want
5929	       addu	$tempreg,$breg,$gp
5930	       <op>	$treg,<sym>($tempreg)	(BFD_RELOC_GPREL16)
5931	     Otherwise we want
5932	       lui	$tempreg,<sym>		(BFD_RELOC_HI16_S)
5933	       addu	$tempreg,$tempreg,$breg
5934	       <op>	$treg,<sym>($tempreg)	(BFD_RELOC_LO16)
5935	     With a constant we always use the latter case.
5936
5937	     With 64bit address space and no base register and $at usable,
5938	     we want
5939	       lui	$tempreg,<sym>		(BFD_RELOC_MIPS_HIGHEST)
5940	       lui	$at,<sym>		(BFD_RELOC_HI16_S)
5941	       daddiu	$tempreg,<sym>		(BFD_RELOC_MIPS_HIGHER)
5942	       dsll32	$tempreg,0
5943	       daddu	$tempreg,$at
5944	       <op>	$treg,<sym>($tempreg)	(BFD_RELOC_LO16)
5945	     If we have a base register, we want
5946	       lui	$tempreg,<sym>		(BFD_RELOC_MIPS_HIGHEST)
5947	       lui	$at,<sym>		(BFD_RELOC_HI16_S)
5948	       daddiu	$tempreg,<sym>		(BFD_RELOC_MIPS_HIGHER)
5949	       daddu	$at,$breg
5950	       dsll32	$tempreg,0
5951	       daddu	$tempreg,$at
5952	       <op>	$treg,<sym>($tempreg)	(BFD_RELOC_LO16)
5953
5954	     Without $at we can't generate the optimal path for superscalar
5955	     processors here since this would require two temporary registers.
5956	       lui	$tempreg,<sym>		(BFD_RELOC_MIPS_HIGHEST)
5957	       daddiu	$tempreg,<sym>		(BFD_RELOC_MIPS_HIGHER)
5958	       dsll	$tempreg,16
5959	       daddiu	$tempreg,<sym>		(BFD_RELOC_HI16_S)
5960	       dsll	$tempreg,16
5961	       <op>	$treg,<sym>($tempreg)	(BFD_RELOC_LO16)
5962	     If we have a base register, we want
5963	       lui	$tempreg,<sym>		(BFD_RELOC_MIPS_HIGHEST)
5964	       daddiu	$tempreg,<sym>		(BFD_RELOC_MIPS_HIGHER)
5965	       dsll	$tempreg,16
5966	       daddiu	$tempreg,<sym>		(BFD_RELOC_HI16_S)
5967	       dsll	$tempreg,16
5968	       daddu	$tempreg,$tempreg,$breg
5969	       <op>	$treg,<sym>($tempreg)	(BFD_RELOC_LO16)
5970
5971	     For GP relative symbols in 64bit address space we can use
5972	     the same sequence as in 32bit address space.  */
5973	  if (HAVE_64BIT_SYMBOLS)
5974	    {
5975	      if ((valueT) offset_expr.X_add_number <= MAX_GPREL_OFFSET
5976		  && !nopic_need_relax (offset_expr.X_add_symbol, 1))
5977		{
5978		  relax_start (offset_expr.X_add_symbol);
5979		  if (breg == 0)
5980		    {
5981		      macro_build (&offset_expr, s, fmt, treg,
5982				   BFD_RELOC_GPREL16, mips_gp_register);
5983		    }
5984		  else
5985		    {
5986		      macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
5987				   tempreg, breg, mips_gp_register);
5988		      macro_build (&offset_expr, s, fmt, treg,
5989				   BFD_RELOC_GPREL16, tempreg);
5990		    }
5991		  relax_switch ();
5992		}
5993
5994	      if (used_at == 0 && !mips_opts.noat)
5995		{
5996		  macro_build (&offset_expr, "lui", "t,u", tempreg,
5997			       BFD_RELOC_MIPS_HIGHEST);
5998		  macro_build (&offset_expr, "lui", "t,u", AT,
5999			       BFD_RELOC_HI16_S);
6000		  macro_build (&offset_expr, "daddiu", "t,r,j", tempreg,
6001			       tempreg, BFD_RELOC_MIPS_HIGHER);
6002		  if (breg != 0)
6003		    macro_build (NULL, "daddu", "d,v,t", AT, AT, breg);
6004		  macro_build (NULL, "dsll32", "d,w,<", tempreg, tempreg, 0);
6005		  macro_build (NULL, "daddu", "d,v,t", tempreg, tempreg, AT);
6006		  macro_build (&offset_expr, s, fmt, treg, BFD_RELOC_LO16,
6007			       tempreg);
6008		  used_at = 1;
6009		}
6010	      else
6011		{
6012		  macro_build (&offset_expr, "lui", "t,u", tempreg,
6013			       BFD_RELOC_MIPS_HIGHEST);
6014		  macro_build (&offset_expr, "daddiu", "t,r,j", tempreg,
6015			       tempreg, BFD_RELOC_MIPS_HIGHER);
6016		  macro_build (NULL, "dsll", "d,w,<", tempreg, tempreg, 16);
6017		  macro_build (&offset_expr, "daddiu", "t,r,j", tempreg,
6018			       tempreg, BFD_RELOC_HI16_S);
6019		  macro_build (NULL, "dsll", "d,w,<", tempreg, tempreg, 16);
6020		  if (breg != 0)
6021		    macro_build (NULL, "daddu", "d,v,t",
6022				 tempreg, tempreg, breg);
6023		  macro_build (&offset_expr, s, fmt, treg,
6024			       BFD_RELOC_LO16, tempreg);
6025		}
6026
6027	      if (mips_relax.sequence)
6028		relax_end ();
6029	      break;
6030	    }
6031
6032	  if (breg == 0)
6033	    {
6034	      if ((valueT) offset_expr.X_add_number <= MAX_GPREL_OFFSET
6035		  && !nopic_need_relax (offset_expr.X_add_symbol, 1))
6036		{
6037		  relax_start (offset_expr.X_add_symbol);
6038		  macro_build (&offset_expr, s, fmt, treg, BFD_RELOC_GPREL16,
6039			       mips_gp_register);
6040		  relax_switch ();
6041		}
6042	      macro_build_lui (&offset_expr, tempreg);
6043	      macro_build (&offset_expr, s, fmt, treg,
6044			   BFD_RELOC_LO16, tempreg);
6045	      if (mips_relax.sequence)
6046		relax_end ();
6047	    }
6048	  else
6049	    {
6050	      if ((valueT) offset_expr.X_add_number <= MAX_GPREL_OFFSET
6051		  && !nopic_need_relax (offset_expr.X_add_symbol, 1))
6052		{
6053		  relax_start (offset_expr.X_add_symbol);
6054		  macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
6055			       tempreg, breg, mips_gp_register);
6056		  macro_build (&offset_expr, s, fmt, treg,
6057			       BFD_RELOC_GPREL16, tempreg);
6058		  relax_switch ();
6059		}
6060	      macro_build_lui (&offset_expr, tempreg);
6061	      macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
6062			   tempreg, tempreg, breg);
6063	      macro_build (&offset_expr, s, fmt, treg,
6064			   BFD_RELOC_LO16, tempreg);
6065	      if (mips_relax.sequence)
6066		relax_end ();
6067	    }
6068	}
6069      else if (!mips_big_got)
6070	{
6071	  int lw_reloc_type = (int) BFD_RELOC_MIPS_GOT16;
6072
6073	  /* If this is a reference to an external symbol, we want
6074	       lw	$tempreg,<sym>($gp)	(BFD_RELOC_MIPS_GOT16)
6075	       nop
6076	       <op>	$treg,0($tempreg)
6077	     Otherwise we want
6078	       lw	$tempreg,<sym>($gp)	(BFD_RELOC_MIPS_GOT16)
6079	       nop
6080	       addiu	$tempreg,$tempreg,<sym>	(BFD_RELOC_LO16)
6081	       <op>	$treg,0($tempreg)
6082
6083	     For NewABI, we want
6084	       lw	$tempreg,<sym>($gp)	(BFD_RELOC_MIPS_GOT_PAGE)
6085	       <op>	$treg,<sym>($tempreg)   (BFD_RELOC_MIPS_GOT_OFST)
6086
6087	     If there is a base register, we add it to $tempreg before
6088	     the <op>.  If there is a constant, we stick it in the
6089	     <op> instruction.  We don't handle constants larger than
6090	     16 bits, because we have no way to load the upper 16 bits
6091	     (actually, we could handle them for the subset of cases
6092	     in which we are not using $at).  */
6093	  assert (offset_expr.X_op == O_symbol);
6094	  if (HAVE_NEWABI)
6095	    {
6096	      macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)", tempreg,
6097			   BFD_RELOC_MIPS_GOT_PAGE, mips_gp_register);
6098	      if (breg != 0)
6099		macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
6100			     tempreg, tempreg, breg);
6101	      macro_build (&offset_expr, s, fmt, treg,
6102			   BFD_RELOC_MIPS_GOT_OFST, tempreg);
6103	      break;
6104	    }
6105	  expr1.X_add_number = offset_expr.X_add_number;
6106	  offset_expr.X_add_number = 0;
6107	  if (expr1.X_add_number < -0x8000
6108	      || expr1.X_add_number >= 0x8000)
6109	    as_bad (_("PIC code offset overflow (max 16 signed bits)"));
6110	  macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)", tempreg,
6111		       lw_reloc_type, mips_gp_register);
6112	  load_delay_nop ();
6113	  relax_start (offset_expr.X_add_symbol);
6114	  relax_switch ();
6115	  macro_build (&offset_expr, ADDRESS_ADDI_INSN, "t,r,j", tempreg,
6116		       tempreg, BFD_RELOC_LO16);
6117	  relax_end ();
6118	  if (breg != 0)
6119	    macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
6120			 tempreg, tempreg, breg);
6121	  macro_build (&expr1, s, fmt, treg, BFD_RELOC_LO16, tempreg);
6122	}
6123      else if (mips_big_got && !HAVE_NEWABI)
6124	{
6125	  int gpdelay;
6126
6127	  /* If this is a reference to an external symbol, we want
6128	       lui	$tempreg,<sym>		(BFD_RELOC_MIPS_GOT_HI16)
6129	       addu	$tempreg,$tempreg,$gp
6130	       lw	$tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_LO16)
6131	       <op>	$treg,0($tempreg)
6132	     Otherwise we want
6133	       lw	$tempreg,<sym>($gp)	(BFD_RELOC_MIPS_GOT16)
6134	       nop
6135	       addiu	$tempreg,$tempreg,<sym>	(BFD_RELOC_LO16)
6136	       <op>	$treg,0($tempreg)
6137	     If there is a base register, we add it to $tempreg before
6138	     the <op>.  If there is a constant, we stick it in the
6139	     <op> instruction.  We don't handle constants larger than
6140	     16 bits, because we have no way to load the upper 16 bits
6141	     (actually, we could handle them for the subset of cases
6142	     in which we are not using $at).  */
6143	  assert (offset_expr.X_op == O_symbol);
6144	  expr1.X_add_number = offset_expr.X_add_number;
6145	  offset_expr.X_add_number = 0;
6146	  if (expr1.X_add_number < -0x8000
6147	      || expr1.X_add_number >= 0x8000)
6148	    as_bad (_("PIC code offset overflow (max 16 signed bits)"));
6149	  gpdelay = reg_needs_delay (mips_gp_register);
6150	  relax_start (offset_expr.X_add_symbol);
6151	  macro_build (&offset_expr, "lui", "t,u", tempreg,
6152		       BFD_RELOC_MIPS_GOT_HI16);
6153	  macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", tempreg, tempreg,
6154		       mips_gp_register);
6155	  macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)", tempreg,
6156		       BFD_RELOC_MIPS_GOT_LO16, tempreg);
6157	  relax_switch ();
6158	  if (gpdelay)
6159	    macro_build (NULL, "nop", "");
6160	  macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)", tempreg,
6161		       BFD_RELOC_MIPS_GOT16, mips_gp_register);
6162	  load_delay_nop ();
6163	  macro_build (&offset_expr, ADDRESS_ADDI_INSN, "t,r,j", tempreg,
6164		       tempreg, BFD_RELOC_LO16);
6165	  relax_end ();
6166
6167	  if (breg != 0)
6168	    macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
6169			 tempreg, tempreg, breg);
6170	  macro_build (&expr1, s, fmt, treg, BFD_RELOC_LO16, tempreg);
6171	}
6172      else if (mips_big_got && HAVE_NEWABI)
6173	{
6174	  /* If this is a reference to an external symbol, we want
6175	       lui	$tempreg,<sym>		(BFD_RELOC_MIPS_GOT_HI16)
6176	       add	$tempreg,$tempreg,$gp
6177	       lw	$tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_LO16)
6178	       <op>	$treg,<ofst>($tempreg)
6179	     Otherwise, for local symbols, we want:
6180	       lw	$tempreg,<sym>($gp)	(BFD_RELOC_MIPS_GOT_PAGE)
6181	       <op>	$treg,<sym>($tempreg)   (BFD_RELOC_MIPS_GOT_OFST)  */
6182	  assert (offset_expr.X_op == O_symbol);
6183	  expr1.X_add_number = offset_expr.X_add_number;
6184	  offset_expr.X_add_number = 0;
6185	  if (expr1.X_add_number < -0x8000
6186	      || expr1.X_add_number >= 0x8000)
6187	    as_bad (_("PIC code offset overflow (max 16 signed bits)"));
6188	  relax_start (offset_expr.X_add_symbol);
6189	  macro_build (&offset_expr, "lui", "t,u", tempreg,
6190		       BFD_RELOC_MIPS_GOT_HI16);
6191	  macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", tempreg, tempreg,
6192		       mips_gp_register);
6193	  macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)", tempreg,
6194		       BFD_RELOC_MIPS_GOT_LO16, tempreg);
6195	  if (breg != 0)
6196	    macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
6197			 tempreg, tempreg, breg);
6198	  macro_build (&expr1, s, fmt, treg, BFD_RELOC_LO16, tempreg);
6199
6200	  relax_switch ();
6201	  offset_expr.X_add_number = expr1.X_add_number;
6202	  macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)", tempreg,
6203		       BFD_RELOC_MIPS_GOT_PAGE, mips_gp_register);
6204	  if (breg != 0)
6205	    macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
6206			 tempreg, tempreg, breg);
6207	  macro_build (&offset_expr, s, fmt, treg,
6208		       BFD_RELOC_MIPS_GOT_OFST, tempreg);
6209	  relax_end ();
6210	}
6211      else
6212	abort ();
6213
6214      break;
6215
6216    case M_LI:
6217    case M_LI_S:
6218      load_register (treg, &imm_expr, 0);
6219      break;
6220
6221    case M_DLI:
6222      load_register (treg, &imm_expr, 1);
6223      break;
6224
6225    case M_LI_SS:
6226      if (imm_expr.X_op == O_constant)
6227	{
6228	  used_at = 1;
6229	  load_register (AT, &imm_expr, 0);
6230	  macro_build (NULL, "mtc1", "t,G", AT, treg);
6231	  break;
6232	}
6233      else
6234	{
6235	  assert (offset_expr.X_op == O_symbol
6236		  && strcmp (segment_name (S_GET_SEGMENT
6237					   (offset_expr.X_add_symbol)),
6238			     ".lit4") == 0
6239		  && offset_expr.X_add_number == 0);
6240	  macro_build (&offset_expr, "lwc1", "T,o(b)", treg,
6241		       BFD_RELOC_MIPS_LITERAL, mips_gp_register);
6242	  break;
6243	}
6244
6245    case M_LI_D:
6246      /* Check if we have a constant in IMM_EXPR.  If the GPRs are 64 bits
6247         wide, IMM_EXPR is the entire value.  Otherwise IMM_EXPR is the high
6248         order 32 bits of the value and the low order 32 bits are either
6249         zero or in OFFSET_EXPR.  */
6250      if (imm_expr.X_op == O_constant || imm_expr.X_op == O_big)
6251	{
6252	  if (HAVE_64BIT_GPRS)
6253	    load_register (treg, &imm_expr, 1);
6254	  else
6255	    {
6256	      int hreg, lreg;
6257
6258	      if (target_big_endian)
6259		{
6260		  hreg = treg;
6261		  lreg = treg + 1;
6262		}
6263	      else
6264		{
6265		  hreg = treg + 1;
6266		  lreg = treg;
6267		}
6268
6269	      if (hreg <= 31)
6270		load_register (hreg, &imm_expr, 0);
6271	      if (lreg <= 31)
6272		{
6273		  if (offset_expr.X_op == O_absent)
6274		    move_register (lreg, 0);
6275		  else
6276		    {
6277		      assert (offset_expr.X_op == O_constant);
6278		      load_register (lreg, &offset_expr, 0);
6279		    }
6280		}
6281	    }
6282	  break;
6283	}
6284
6285      /* We know that sym is in the .rdata section.  First we get the
6286	 upper 16 bits of the address.  */
6287      if (mips_pic == NO_PIC)
6288	{
6289	  macro_build_lui (&offset_expr, AT);
6290	  used_at = 1;
6291	}
6292      else
6293	{
6294	  macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)", AT,
6295		       BFD_RELOC_MIPS_GOT16, mips_gp_register);
6296	  used_at = 1;
6297	}
6298
6299      /* Now we load the register(s).  */
6300      if (HAVE_64BIT_GPRS)
6301	{
6302	  used_at = 1;
6303	  macro_build (&offset_expr, "ld", "t,o(b)", treg, BFD_RELOC_LO16, AT);
6304	}
6305      else
6306	{
6307	  used_at = 1;
6308	  macro_build (&offset_expr, "lw", "t,o(b)", treg, BFD_RELOC_LO16, AT);
6309	  if (treg != RA)
6310	    {
6311	      /* FIXME: How in the world do we deal with the possible
6312		 overflow here?  */
6313	      offset_expr.X_add_number += 4;
6314	      macro_build (&offset_expr, "lw", "t,o(b)",
6315			   treg + 1, BFD_RELOC_LO16, AT);
6316	    }
6317	}
6318      break;
6319
6320    case M_LI_DD:
6321      /* Check if we have a constant in IMM_EXPR.  If the FPRs are 64 bits
6322         wide, IMM_EXPR is the entire value and the GPRs are known to be 64
6323         bits wide as well.  Otherwise IMM_EXPR is the high order 32 bits of
6324         the value and the low order 32 bits are either zero or in
6325         OFFSET_EXPR.  */
6326      if (imm_expr.X_op == O_constant || imm_expr.X_op == O_big)
6327	{
6328	  used_at = 1;
6329	  load_register (AT, &imm_expr, HAVE_64BIT_FPRS);
6330	  if (HAVE_64BIT_FPRS)
6331	    {
6332	      assert (HAVE_64BIT_GPRS);
6333	      macro_build (NULL, "dmtc1", "t,S", AT, treg);
6334	    }
6335	  else
6336	    {
6337	      macro_build (NULL, "mtc1", "t,G", AT, treg + 1);
6338	      if (offset_expr.X_op == O_absent)
6339		macro_build (NULL, "mtc1", "t,G", 0, treg);
6340	      else
6341		{
6342		  assert (offset_expr.X_op == O_constant);
6343		  load_register (AT, &offset_expr, 0);
6344		  macro_build (NULL, "mtc1", "t,G", AT, treg);
6345		}
6346	    }
6347	  break;
6348	}
6349
6350      assert (offset_expr.X_op == O_symbol
6351	      && offset_expr.X_add_number == 0);
6352      s = segment_name (S_GET_SEGMENT (offset_expr.X_add_symbol));
6353      if (strcmp (s, ".lit8") == 0)
6354	{
6355	  if (mips_opts.isa != ISA_MIPS1)
6356	    {
6357	      macro_build (&offset_expr, "ldc1", "T,o(b)", treg,
6358			   BFD_RELOC_MIPS_LITERAL, mips_gp_register);
6359	      break;
6360	    }
6361	  breg = mips_gp_register;
6362	  r = BFD_RELOC_MIPS_LITERAL;
6363	  goto dob;
6364	}
6365      else
6366	{
6367	  assert (strcmp (s, RDATA_SECTION_NAME) == 0);
6368	  used_at = 1;
6369	  if (mips_pic != NO_PIC)
6370	    macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)", AT,
6371			 BFD_RELOC_MIPS_GOT16, mips_gp_register);
6372	  else
6373	    {
6374	      /* FIXME: This won't work for a 64 bit address.  */
6375	      macro_build_lui (&offset_expr, AT);
6376	    }
6377
6378	  if (mips_opts.isa != ISA_MIPS1)
6379	    {
6380	      macro_build (&offset_expr, "ldc1", "T,o(b)",
6381			   treg, BFD_RELOC_LO16, AT);
6382	      break;
6383	    }
6384	  breg = AT;
6385	  r = BFD_RELOC_LO16;
6386	  goto dob;
6387	}
6388
6389    case M_L_DOB:
6390      if (mips_opts.arch == CPU_R4650)
6391	{
6392	  as_bad (_("opcode not supported on this processor"));
6393	  break;
6394	}
6395      /* Even on a big endian machine $fn comes before $fn+1.  We have
6396	 to adjust when loading from memory.  */
6397      r = BFD_RELOC_LO16;
6398    dob:
6399      assert (mips_opts.isa == ISA_MIPS1);
6400      macro_build (&offset_expr, "lwc1", "T,o(b)",
6401		   target_big_endian ? treg + 1 : treg, r, breg);
6402      /* FIXME: A possible overflow which I don't know how to deal
6403	 with.  */
6404      offset_expr.X_add_number += 4;
6405      macro_build (&offset_expr, "lwc1", "T,o(b)",
6406		   target_big_endian ? treg : treg + 1, r, breg);
6407      break;
6408
6409    case M_L_DAB:
6410      /*
6411       * The MIPS assembler seems to check for X_add_number not
6412       * being double aligned and generating:
6413       *	lui	at,%hi(foo+1)
6414       *	addu	at,at,v1
6415       *	addiu	at,at,%lo(foo+1)
6416       *	lwc1	f2,0(at)
6417       *	lwc1	f3,4(at)
6418       * But, the resulting address is the same after relocation so why
6419       * generate the extra instruction?
6420       */
6421      if (mips_opts.arch == CPU_R4650)
6422	{
6423	  as_bad (_("opcode not supported on this processor"));
6424	  break;
6425	}
6426      /* Itbl support may require additional care here.  */
6427      coproc = 1;
6428      if (mips_opts.isa != ISA_MIPS1)
6429	{
6430	  s = "ldc1";
6431	  goto ld;
6432	}
6433
6434      s = "lwc1";
6435      fmt = "T,o(b)";
6436      goto ldd_std;
6437
6438    case M_S_DAB:
6439      if (mips_opts.arch == CPU_R4650)
6440	{
6441	  as_bad (_("opcode not supported on this processor"));
6442	  break;
6443	}
6444
6445      if (mips_opts.isa != ISA_MIPS1)
6446	{
6447	  s = "sdc1";
6448	  goto st;
6449	}
6450
6451      s = "swc1";
6452      fmt = "T,o(b)";
6453      /* Itbl support may require additional care here.  */
6454      coproc = 1;
6455      goto ldd_std;
6456
6457    case M_LD_AB:
6458      if (HAVE_64BIT_GPRS)
6459	{
6460	  s = "ld";
6461	  goto ld;
6462	}
6463
6464      s = "lw";
6465      fmt = "t,o(b)";
6466      goto ldd_std;
6467
6468    case M_SD_AB:
6469      if (HAVE_64BIT_GPRS)
6470	{
6471	  s = "sd";
6472	  goto st;
6473	}
6474
6475      s = "sw";
6476      fmt = "t,o(b)";
6477
6478    ldd_std:
6479      if (offset_expr.X_op != O_symbol
6480	  && offset_expr.X_op != O_constant)
6481	{
6482	  as_bad (_("expression too complex"));
6483	  offset_expr.X_op = O_constant;
6484	}
6485
6486      if (HAVE_32BIT_ADDRESSES
6487	  && !IS_SEXT_32BIT_NUM (offset_expr.X_add_number))
6488	{
6489	  char value [32];
6490
6491	  sprintf_vma (value, offset_expr.X_add_number);
6492	  as_bad (_("Number (0x%s) larger than 32 bits"), value);
6493	}
6494
6495      /* Even on a big endian machine $fn comes before $fn+1.  We have
6496	 to adjust when loading from memory.  We set coproc if we must
6497	 load $fn+1 first.  */
6498      /* Itbl support may require additional care here.  */
6499      if (! target_big_endian)
6500	coproc = 0;
6501
6502      if (mips_pic == NO_PIC
6503	  || offset_expr.X_op == O_constant)
6504	{
6505	  /* If this is a reference to a GP relative symbol, we want
6506	       <op>	$treg,<sym>($gp)	(BFD_RELOC_GPREL16)
6507	       <op>	$treg+1,<sym>+4($gp)	(BFD_RELOC_GPREL16)
6508	     If we have a base register, we use this
6509	       addu	$at,$breg,$gp
6510	       <op>	$treg,<sym>($at)	(BFD_RELOC_GPREL16)
6511	       <op>	$treg+1,<sym>+4($at)	(BFD_RELOC_GPREL16)
6512	     If this is not a GP relative symbol, we want
6513	       lui	$at,<sym>		(BFD_RELOC_HI16_S)
6514	       <op>	$treg,<sym>($at)	(BFD_RELOC_LO16)
6515	       <op>	$treg+1,<sym>+4($at)	(BFD_RELOC_LO16)
6516	     If there is a base register, we add it to $at after the
6517	     lui instruction.  If there is a constant, we always use
6518	     the last case.  */
6519	  if (offset_expr.X_op == O_symbol
6520	      && (valueT) offset_expr.X_add_number <= MAX_GPREL_OFFSET
6521	      && !nopic_need_relax (offset_expr.X_add_symbol, 1))
6522	    {
6523	      relax_start (offset_expr.X_add_symbol);
6524	      if (breg == 0)
6525		{
6526		  tempreg = mips_gp_register;
6527		}
6528	      else
6529		{
6530		  macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
6531			       AT, breg, mips_gp_register);
6532		  tempreg = AT;
6533		  used_at = 1;
6534		}
6535
6536	      /* Itbl support may require additional care here.  */
6537	      macro_build (&offset_expr, s, fmt, coproc ? treg + 1 : treg,
6538			   BFD_RELOC_GPREL16, tempreg);
6539	      offset_expr.X_add_number += 4;
6540
6541	      /* Set mips_optimize to 2 to avoid inserting an
6542                 undesired nop.  */
6543	      hold_mips_optimize = mips_optimize;
6544	      mips_optimize = 2;
6545	      /* Itbl support may require additional care here.  */
6546	      macro_build (&offset_expr, s, fmt, coproc ? treg : treg + 1,
6547			   BFD_RELOC_GPREL16, tempreg);
6548	      mips_optimize = hold_mips_optimize;
6549
6550	      relax_switch ();
6551
6552	      /* We just generated two relocs.  When tc_gen_reloc
6553		 handles this case, it will skip the first reloc and
6554		 handle the second.  The second reloc already has an
6555		 extra addend of 4, which we added above.  We must
6556		 subtract it out, and then subtract another 4 to make
6557		 the first reloc come out right.  The second reloc
6558		 will come out right because we are going to add 4 to
6559		 offset_expr when we build its instruction below.
6560
6561		 If we have a symbol, then we don't want to include
6562		 the offset, because it will wind up being included
6563		 when we generate the reloc.  */
6564
6565	      if (offset_expr.X_op == O_constant)
6566		offset_expr.X_add_number -= 8;
6567	      else
6568		{
6569		  offset_expr.X_add_number = -4;
6570		  offset_expr.X_op = O_constant;
6571		}
6572	    }
6573	  used_at = 1;
6574	  macro_build_lui (&offset_expr, AT);
6575	  if (breg != 0)
6576	    macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", AT, breg, AT);
6577	  /* Itbl support may require additional care here.  */
6578	  macro_build (&offset_expr, s, fmt, coproc ? treg + 1 : treg,
6579		       BFD_RELOC_LO16, AT);
6580	  /* FIXME: How do we handle overflow here?  */
6581	  offset_expr.X_add_number += 4;
6582	  /* Itbl support may require additional care here.  */
6583	  macro_build (&offset_expr, s, fmt, coproc ? treg : treg + 1,
6584		       BFD_RELOC_LO16, AT);
6585	  if (mips_relax.sequence)
6586	    relax_end ();
6587	}
6588      else if (!mips_big_got)
6589	{
6590	  /* If this is a reference to an external symbol, we want
6591	       lw	$at,<sym>($gp)		(BFD_RELOC_MIPS_GOT16)
6592	       nop
6593	       <op>	$treg,0($at)
6594	       <op>	$treg+1,4($at)
6595	     Otherwise we want
6596	       lw	$at,<sym>($gp)		(BFD_RELOC_MIPS_GOT16)
6597	       nop
6598	       <op>	$treg,<sym>($at)	(BFD_RELOC_LO16)
6599	       <op>	$treg+1,<sym>+4($at)	(BFD_RELOC_LO16)
6600	     If there is a base register we add it to $at before the
6601	     lwc1 instructions.  If there is a constant we include it
6602	     in the lwc1 instructions.  */
6603	  used_at = 1;
6604	  expr1.X_add_number = offset_expr.X_add_number;
6605	  if (expr1.X_add_number < -0x8000
6606	      || expr1.X_add_number >= 0x8000 - 4)
6607	    as_bad (_("PIC code offset overflow (max 16 signed bits)"));
6608	  load_got_offset (AT, &offset_expr);
6609	  load_delay_nop ();
6610	  if (breg != 0)
6611	    macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", AT, breg, AT);
6612
6613	  /* Set mips_optimize to 2 to avoid inserting an undesired
6614             nop.  */
6615	  hold_mips_optimize = mips_optimize;
6616	  mips_optimize = 2;
6617
6618	  /* Itbl support may require additional care here.  */
6619	  relax_start (offset_expr.X_add_symbol);
6620	  macro_build (&expr1, s, fmt, coproc ? treg + 1 : treg,
6621		       BFD_RELOC_LO16, AT);
6622	  expr1.X_add_number += 4;
6623	  macro_build (&expr1, s, fmt, coproc ? treg : treg + 1,
6624		       BFD_RELOC_LO16, AT);
6625	  relax_switch ();
6626	  macro_build (&offset_expr, s, fmt, coproc ? treg + 1 : treg,
6627		       BFD_RELOC_LO16, AT);
6628	  offset_expr.X_add_number += 4;
6629	  macro_build (&offset_expr, s, fmt, coproc ? treg : treg + 1,
6630		       BFD_RELOC_LO16, AT);
6631	  relax_end ();
6632
6633	  mips_optimize = hold_mips_optimize;
6634	}
6635      else if (mips_big_got)
6636	{
6637	  int gpdelay;
6638
6639	  /* If this is a reference to an external symbol, we want
6640	       lui	$at,<sym>		(BFD_RELOC_MIPS_GOT_HI16)
6641	       addu	$at,$at,$gp
6642	       lw	$at,<sym>($at)		(BFD_RELOC_MIPS_GOT_LO16)
6643	       nop
6644	       <op>	$treg,0($at)
6645	       <op>	$treg+1,4($at)
6646	     Otherwise we want
6647	       lw	$at,<sym>($gp)		(BFD_RELOC_MIPS_GOT16)
6648	       nop
6649	       <op>	$treg,<sym>($at)	(BFD_RELOC_LO16)
6650	       <op>	$treg+1,<sym>+4($at)	(BFD_RELOC_LO16)
6651	     If there is a base register we add it to $at before the
6652	     lwc1 instructions.  If there is a constant we include it
6653	     in the lwc1 instructions.  */
6654	  used_at = 1;
6655	  expr1.X_add_number = offset_expr.X_add_number;
6656	  offset_expr.X_add_number = 0;
6657	  if (expr1.X_add_number < -0x8000
6658	      || expr1.X_add_number >= 0x8000 - 4)
6659	    as_bad (_("PIC code offset overflow (max 16 signed bits)"));
6660	  gpdelay = reg_needs_delay (mips_gp_register);
6661	  relax_start (offset_expr.X_add_symbol);
6662	  macro_build (&offset_expr, "lui", "t,u",
6663		       AT, BFD_RELOC_MIPS_GOT_HI16);
6664	  macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
6665		       AT, AT, mips_gp_register);
6666	  macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)",
6667		       AT, BFD_RELOC_MIPS_GOT_LO16, AT);
6668	  load_delay_nop ();
6669	  if (breg != 0)
6670	    macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", AT, breg, AT);
6671	  /* Itbl support may require additional care here.  */
6672	  macro_build (&expr1, s, fmt, coproc ? treg + 1 : treg,
6673		       BFD_RELOC_LO16, AT);
6674	  expr1.X_add_number += 4;
6675
6676	  /* Set mips_optimize to 2 to avoid inserting an undesired
6677             nop.  */
6678	  hold_mips_optimize = mips_optimize;
6679	  mips_optimize = 2;
6680	  /* Itbl support may require additional care here.  */
6681	  macro_build (&expr1, s, fmt, coproc ? treg : treg + 1,
6682		       BFD_RELOC_LO16, AT);
6683	  mips_optimize = hold_mips_optimize;
6684	  expr1.X_add_number -= 4;
6685
6686	  relax_switch ();
6687	  offset_expr.X_add_number = expr1.X_add_number;
6688	  if (gpdelay)
6689	    macro_build (NULL, "nop", "");
6690	  macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)", AT,
6691		       BFD_RELOC_MIPS_GOT16, mips_gp_register);
6692	  load_delay_nop ();
6693	  if (breg != 0)
6694	    macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", AT, breg, AT);
6695	  /* Itbl support may require additional care here.  */
6696	  macro_build (&offset_expr, s, fmt, coproc ? treg + 1 : treg,
6697		       BFD_RELOC_LO16, AT);
6698	  offset_expr.X_add_number += 4;
6699
6700	  /* Set mips_optimize to 2 to avoid inserting an undesired
6701             nop.  */
6702	  hold_mips_optimize = mips_optimize;
6703	  mips_optimize = 2;
6704	  /* Itbl support may require additional care here.  */
6705	  macro_build (&offset_expr, s, fmt, coproc ? treg : treg + 1,
6706		       BFD_RELOC_LO16, AT);
6707	  mips_optimize = hold_mips_optimize;
6708	  relax_end ();
6709	}
6710      else
6711	abort ();
6712
6713      break;
6714
6715    case M_LD_OB:
6716      s = "lw";
6717      goto sd_ob;
6718    case M_SD_OB:
6719      s = "sw";
6720    sd_ob:
6721      assert (HAVE_32BIT_ADDRESSES);
6722      macro_build (&offset_expr, s, "t,o(b)", treg, BFD_RELOC_LO16, breg);
6723      offset_expr.X_add_number += 4;
6724      macro_build (&offset_expr, s, "t,o(b)", treg + 1, BFD_RELOC_LO16, breg);
6725      break;
6726
6727    case M_SAA_AB:
6728      s = "saa";
6729      goto saa_saad;
6730
6731    case M_SAAD_AB:
6732      s = "saad";
6733
6734      saa_saad:
6735      /* The "saa/saad" instructions are new in CN58XX. These instructions
6736	 do not specify offset. When invoked with address or symbol, then
6737	 load the address or value of symbol in a register using the dla macro
6738	 into AT, and pass the register for emitting "saa/saad" instruction.
6739	 This will get expanded to
6740
6741	    dla AT, constant/label
6742	    saa/saad $treg,(AT)  */
6743      {
6744	char *name = "dla";
6745	char *fmt = "t,A(b)";
6746	const struct mips_opcode *mo;
6747  	struct mips_cl_insn insn;
6748
6749	mo = hash_find (op_hash, name);
6750	assert (strcmp (name, mo->name) == 0);
6751	assert (strcmp (fmt, mo->args) == 0);
6752	create_insn (&insn, mo);
6753
6754	insn.insn_opcode = insn.insn_mo->match;
6755
6756	used_at = 1;
6757	INSERT_OPERAND (RT, insn, AT);
6758	if (breg)
6759	  INSERT_OPERAND (RS, insn, breg);
6760
6761	/* The address part is forwarded through the global offset_expr. */
6762	macro (&insn);
6763
6764	macro_build (NULL, s, "t,(b)", treg, AT);
6765	break;
6766     }
6767
6768   /* New code added to support COPZ instructions.
6769      This code builds table entries out of the macros in mip_opcodes.
6770      R4000 uses interlocks to handle coproc delays.
6771      Other chips (like the R3000) require nops to be inserted for delays.
6772
6773      FIXME: Currently, we require that the user handle delays.
6774      In order to fill delay slots for non-interlocked chips,
6775      we must have a way to specify delays based on the coprocessor.
6776      Eg. 4 cycles if load coproc reg from memory, 1 if in cache, etc.
6777      What are the side-effects of the cop instruction?
6778      What cache support might we have and what are its effects?
6779      Both coprocessor & memory require delays. how long???
6780      What registers are read/set/modified?
6781
6782      If an itbl is provided to interpret cop instructions,
6783      this knowledge can be encoded in the itbl spec.  */
6784
6785    case M_COP0:
6786      s = "c0";
6787      goto copz;
6788    case M_COP1:
6789      s = "c1";
6790      goto copz;
6791    case M_COP2:
6792      s = "c2";
6793      goto copz;
6794    case M_COP3:
6795      s = "c3";
6796    copz:
6797      if (!strcmp (s,"c2") && mips_opts.arch == CPU_OCTEON
6798	  && octeon_error_on_unsupported)
6799        {
6800          as_bad (_("opcode not implemented in Octeon `%s'"), ip->insn_mo->name);
6801          return;
6802        }
6803      /* For now we just do C (same as Cz).  The parameter will be
6804         stored in insn_opcode by mips_ip.  */
6805      macro_build (NULL, s, "C", ip->insn_opcode);
6806      break;
6807
6808    case M_MOVE:
6809      move_register (dreg, sreg);
6810      break;
6811
6812#ifdef LOSING_COMPILER
6813    default:
6814      /* Try and see if this is a new itbl instruction.
6815         This code builds table entries out of the macros in mip_opcodes.
6816         FIXME: For now we just assemble the expression and pass it's
6817         value along as a 32-bit immediate.
6818         We may want to have the assembler assemble this value,
6819         so that we gain the assembler's knowledge of delay slots,
6820         symbols, etc.
6821         Would it be more efficient to use mask (id) here? */
6822      if (itbl_have_entries
6823	  && (immed_expr = itbl_assemble (ip->insn_mo->name, "")))
6824	{
6825	  s = ip->insn_mo->name;
6826	  s2 = "cop3";
6827	  coproc = ITBL_DECODE_PNUM (immed_expr);;
6828	  macro_build (&immed_expr, s, "C");
6829	  break;
6830	}
6831      macro2 (ip);
6832      break;
6833    }
6834  if (mips_opts.noat && used_at)
6835    as_bad (_("Macro used $at after \".set noat\""));
6836}
6837
6838static void
6839macro2 (struct mips_cl_insn *ip)
6840{
6841  register int treg, sreg, dreg, breg;
6842  int tempreg;
6843  int mask;
6844  int used_at;
6845  expressionS expr1;
6846  const char *s;
6847  const char *s2;
6848  const char *fmt;
6849  int likely = 0;
6850  int dbl = 0;
6851  int coproc = 0;
6852  int lr = 0;
6853  int imm = 0;
6854  int off;
6855  offsetT maxnum;
6856  bfd_reloc_code_real_type r;
6857
6858  treg = (ip->insn_opcode >> 16) & 0x1f;
6859  dreg = (ip->insn_opcode >> 11) & 0x1f;
6860  sreg = breg = (ip->insn_opcode >> 21) & 0x1f;
6861  mask = ip->insn_mo->mask;
6862
6863  expr1.X_op = O_constant;
6864  expr1.X_op_symbol = NULL;
6865  expr1.X_add_symbol = NULL;
6866  expr1.X_add_number = 1;
6867
6868  switch (mask)
6869    {
6870#endif /* LOSING_COMPILER */
6871
6872    case M_DMUL:
6873      dbl = 1;
6874    case M_MUL:
6875      macro_build (NULL, dbl ? "dmultu" : "multu", "s,t", sreg, treg);
6876      macro_build (NULL, "mflo", "d", dreg);
6877      break;
6878
6879    case M_DMUL_I:
6880      dbl = 1;
6881    case M_MUL_I:
6882      /* The MIPS assembler some times generates shifts and adds.  I'm
6883	 not trying to be that fancy. GCC should do this for us
6884	 anyway.  */
6885      used_at = 1;
6886      load_register (AT, &imm_expr, dbl);
6887      macro_build (NULL, dbl ? "dmult" : "mult", "s,t", sreg, AT);
6888      macro_build (NULL, "mflo", "d", dreg);
6889      break;
6890
6891    case M_DMULO_I:
6892      dbl = 1;
6893    case M_MULO_I:
6894      imm = 1;
6895      goto do_mulo;
6896
6897    case M_DMULO:
6898      dbl = 1;
6899    case M_MULO:
6900    do_mulo:
6901      start_noreorder ();
6902      used_at = 1;
6903      if (imm)
6904	load_register (AT, &imm_expr, dbl);
6905      macro_build (NULL, dbl ? "dmult" : "mult", "s,t", sreg, imm ? AT : treg);
6906      macro_build (NULL, "mflo", "d", dreg);
6907      macro_build (NULL, dbl ? "dsra32" : "sra", "d,w,<", dreg, dreg, RA);
6908      macro_build (NULL, "mfhi", "d", AT);
6909      if (mips_trap)
6910	macro_build (NULL, "tne", "s,t,q", dreg, AT, 6);
6911      else
6912	{
6913	  expr1.X_add_number = 8;
6914	  macro_build (&expr1, "beq", "s,t,p", dreg, AT);
6915	  macro_build (NULL, "nop", "", 0);
6916	  macro_build (NULL, "break", "c", 6);
6917	}
6918      end_noreorder ();
6919      macro_build (NULL, "mflo", "d", dreg);
6920      break;
6921
6922    case M_DMULOU_I:
6923      dbl = 1;
6924    case M_MULOU_I:
6925      imm = 1;
6926      goto do_mulou;
6927
6928    case M_DMULOU:
6929      dbl = 1;
6930    case M_MULOU:
6931    do_mulou:
6932      start_noreorder ();
6933      used_at = 1;
6934      if (imm)
6935	load_register (AT, &imm_expr, dbl);
6936      macro_build (NULL, dbl ? "dmultu" : "multu", "s,t",
6937		   sreg, imm ? AT : treg);
6938      macro_build (NULL, "mfhi", "d", AT);
6939      macro_build (NULL, "mflo", "d", dreg);
6940      if (mips_trap)
6941	macro_build (NULL, "tne", "s,t,q", AT, 0, 6);
6942      else
6943	{
6944	  expr1.X_add_number = 8;
6945	  macro_build (&expr1, "beq", "s,t,p", AT, 0);
6946	  macro_build (NULL, "nop", "", 0);
6947	  macro_build (NULL, "break", "c", 6);
6948	}
6949      end_noreorder ();
6950      break;
6951
6952    case M_DROL:
6953      if (ISA_HAS_DROR (mips_opts.isa) || CPU_HAS_DROR (mips_opts.arch))
6954	{
6955	  if (dreg == sreg)
6956	    {
6957	      tempreg = AT;
6958	      used_at = 1;
6959	    }
6960	  else
6961	    {
6962	      tempreg = dreg;
6963	    }
6964	  macro_build (NULL, "dnegu", "d,w", tempreg, treg);
6965	  macro_build (NULL, "drorv", "d,t,s", dreg, sreg, tempreg);
6966	  break;
6967	}
6968      used_at = 1;
6969      macro_build (NULL, "dsubu", "d,v,t", AT, 0, treg);
6970      macro_build (NULL, "dsrlv", "d,t,s", AT, sreg, AT);
6971      macro_build (NULL, "dsllv", "d,t,s", dreg, sreg, treg);
6972      macro_build (NULL, "or", "d,v,t", dreg, dreg, AT);
6973      break;
6974
6975    case M_ROL:
6976      if (ISA_HAS_ROR (mips_opts.isa) || CPU_HAS_ROR (mips_opts.arch))
6977	{
6978	  if (dreg == sreg)
6979	    {
6980	      tempreg = AT;
6981	      used_at = 1;
6982	    }
6983	  else
6984	    {
6985	      tempreg = dreg;
6986	    }
6987	  macro_build (NULL, "negu", "d,w", tempreg, treg);
6988	  macro_build (NULL, "rorv", "d,t,s", dreg, sreg, tempreg);
6989	  break;
6990	}
6991      used_at = 1;
6992      macro_build (NULL, "subu", "d,v,t", AT, 0, treg);
6993      macro_build (NULL, "srlv", "d,t,s", AT, sreg, AT);
6994      macro_build (NULL, "sllv", "d,t,s", dreg, sreg, treg);
6995      macro_build (NULL, "or", "d,v,t", dreg, dreg, AT);
6996      break;
6997
6998    case M_DROL_I:
6999      {
7000	unsigned int rot;
7001	char *l, *r;
7002
7003	if (imm_expr.X_op != O_constant)
7004	  as_bad (_("Improper rotate count"));
7005	rot = imm_expr.X_add_number & 0x3f;
7006	if (ISA_HAS_DROR (mips_opts.isa) || CPU_HAS_DROR (mips_opts.arch))
7007	  {
7008	    rot = (64 - rot) & 0x3f;
7009	    if (rot >= 32)
7010	      macro_build (NULL, "dror32", "d,w,<", dreg, sreg, rot - 32);
7011	    else
7012	      macro_build (NULL, "dror", "d,w,<", dreg, sreg, rot);
7013	    break;
7014	  }
7015	if (rot == 0)
7016	  {
7017	    macro_build (NULL, "dsrl", "d,w,<", dreg, sreg, 0);
7018	    break;
7019	  }
7020	l = (rot < 0x20) ? "dsll" : "dsll32";
7021	r = ((0x40 - rot) < 0x20) ? "dsrl" : "dsrl32";
7022	rot &= 0x1f;
7023	used_at = 1;
7024	macro_build (NULL, l, "d,w,<", AT, sreg, rot);
7025	macro_build (NULL, r, "d,w,<", dreg, sreg, (0x20 - rot) & 0x1f);
7026	macro_build (NULL, "or", "d,v,t", dreg, dreg, AT);
7027      }
7028      break;
7029
7030    case M_ROL_I:
7031      {
7032	unsigned int rot;
7033
7034	if (imm_expr.X_op != O_constant)
7035	  as_bad (_("Improper rotate count"));
7036	rot = imm_expr.X_add_number & 0x1f;
7037	if (ISA_HAS_ROR (mips_opts.isa) || CPU_HAS_ROR (mips_opts.arch))
7038	  {
7039	    macro_build (NULL, "ror", "d,w,<", dreg, sreg, (32 - rot) & 0x1f);
7040	    break;
7041	  }
7042	if (rot == 0)
7043	  {
7044	    macro_build (NULL, "srl", "d,w,<", dreg, sreg, 0);
7045	    break;
7046	  }
7047	used_at = 1;
7048	macro_build (NULL, "sll", "d,w,<", AT, sreg, rot);
7049	macro_build (NULL, "srl", "d,w,<", dreg, sreg, (0x20 - rot) & 0x1f);
7050	macro_build (NULL, "or", "d,v,t", dreg, dreg, AT);
7051      }
7052      break;
7053
7054    case M_DROR:
7055      if (ISA_HAS_DROR (mips_opts.isa) || CPU_HAS_DROR (mips_opts.arch))
7056	{
7057	  macro_build (NULL, "drorv", "d,t,s", dreg, sreg, treg);
7058	  break;
7059	}
7060      used_at = 1;
7061      macro_build (NULL, "dsubu", "d,v,t", AT, 0, treg);
7062      macro_build (NULL, "dsllv", "d,t,s", AT, sreg, AT);
7063      macro_build (NULL, "dsrlv", "d,t,s", dreg, sreg, treg);
7064      macro_build (NULL, "or", "d,v,t", dreg, dreg, AT);
7065      break;
7066
7067    case M_ROR:
7068      if (ISA_HAS_ROR (mips_opts.isa) || CPU_HAS_ROR (mips_opts.arch))
7069	{
7070	  macro_build (NULL, "rorv", "d,t,s", dreg, sreg, treg);
7071	  break;
7072	}
7073      used_at = 1;
7074      macro_build (NULL, "subu", "d,v,t", AT, 0, treg);
7075      macro_build (NULL, "sllv", "d,t,s", AT, sreg, AT);
7076      macro_build (NULL, "srlv", "d,t,s", dreg, sreg, treg);
7077      macro_build (NULL, "or", "d,v,t", dreg, dreg, AT);
7078      break;
7079
7080    case M_DROR_I:
7081      {
7082	unsigned int rot;
7083	char *l, *r;
7084
7085	if (imm_expr.X_op != O_constant)
7086	  as_bad (_("Improper rotate count"));
7087	rot = imm_expr.X_add_number & 0x3f;
7088	if (ISA_HAS_DROR (mips_opts.isa) || CPU_HAS_DROR (mips_opts.arch))
7089	  {
7090	    if (rot >= 32)
7091	      macro_build (NULL, "dror32", "d,w,<", dreg, sreg, rot - 32);
7092	    else
7093	      macro_build (NULL, "dror", "d,w,<", dreg, sreg, rot);
7094	    break;
7095	  }
7096	if (rot == 0)
7097	  {
7098	    macro_build (NULL, "dsrl", "d,w,<", dreg, sreg, 0);
7099	    break;
7100	  }
7101	r = (rot < 0x20) ? "dsrl" : "dsrl32";
7102	l = ((0x40 - rot) < 0x20) ? "dsll" : "dsll32";
7103	rot &= 0x1f;
7104	used_at = 1;
7105	macro_build (NULL, r, "d,w,<", AT, sreg, rot);
7106	macro_build (NULL, l, "d,w,<", dreg, sreg, (0x20 - rot) & 0x1f);
7107	macro_build (NULL, "or", "d,v,t", dreg, dreg, AT);
7108      }
7109      break;
7110
7111    case M_ROR_I:
7112      {
7113	unsigned int rot;
7114
7115	if (imm_expr.X_op != O_constant)
7116	  as_bad (_("Improper rotate count"));
7117	rot = imm_expr.X_add_number & 0x1f;
7118	if (ISA_HAS_ROR (mips_opts.isa) || CPU_HAS_ROR (mips_opts.arch))
7119	  {
7120	    macro_build (NULL, "ror", "d,w,<", dreg, sreg, rot);
7121	    break;
7122	  }
7123	if (rot == 0)
7124	  {
7125	    macro_build (NULL, "srl", "d,w,<", dreg, sreg, 0);
7126	    break;
7127	  }
7128	used_at = 1;
7129	macro_build (NULL, "srl", "d,w,<", AT, sreg, rot);
7130	macro_build (NULL, "sll", "d,w,<", dreg, sreg, (0x20 - rot) & 0x1f);
7131	macro_build (NULL, "or", "d,v,t", dreg, dreg, AT);
7132      }
7133      break;
7134
7135    case M_S_DOB:
7136      if (mips_opts.arch == CPU_R4650)
7137	{
7138	  as_bad (_("opcode not supported on this processor"));
7139	  break;
7140	}
7141      assert (mips_opts.isa == ISA_MIPS1);
7142      /* Even on a big endian machine $fn comes before $fn+1.  We have
7143	 to adjust when storing to memory.  */
7144      macro_build (&offset_expr, "swc1", "T,o(b)",
7145		   target_big_endian ? treg + 1 : treg, BFD_RELOC_LO16, breg);
7146      offset_expr.X_add_number += 4;
7147      macro_build (&offset_expr, "swc1", "T,o(b)",
7148		   target_big_endian ? treg : treg + 1, BFD_RELOC_LO16, breg);
7149      break;
7150
7151    case M_SEQ:
7152      if (sreg == 0)
7153	macro_build (&expr1, "sltiu", "t,r,j", dreg, treg, BFD_RELOC_LO16);
7154      else if (treg == 0)
7155	macro_build (&expr1, "sltiu", "t,r,j", dreg, sreg, BFD_RELOC_LO16);
7156      else
7157	{
7158	  macro_build (NULL, "xor", "d,v,t", dreg, sreg, treg);
7159	  macro_build (&expr1, "sltiu", "t,r,j", dreg, dreg, BFD_RELOC_LO16);
7160	}
7161      break;
7162
7163    case M_SEQ_I:
7164      if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
7165	{
7166	  macro_build (&expr1, "sltiu", "t,r,j", dreg, sreg, BFD_RELOC_LO16);
7167	  break;
7168	}
7169      if (sreg == 0)
7170	{
7171	  as_warn (_("Instruction %s: result is always false"),
7172		   ip->insn_mo->name);
7173	  move_register (dreg, 0);
7174	  break;
7175	}
7176      if (imm_expr.X_op == O_constant
7177	  && imm_expr.X_add_number >= 0
7178	  && imm_expr.X_add_number < 0x10000)
7179	{
7180	  macro_build (&imm_expr, "xori", "t,r,i", dreg, sreg, BFD_RELOC_LO16);
7181	}
7182      else if (imm_expr.X_op == O_constant
7183	       && imm_expr.X_add_number > -0x8000
7184	       && imm_expr.X_add_number < 0)
7185	{
7186	  imm_expr.X_add_number = -imm_expr.X_add_number;
7187	  macro_build (&imm_expr, HAVE_32BIT_GPRS ? "addiu" : "daddiu",
7188		       "t,r,j", dreg, sreg, BFD_RELOC_LO16);
7189	}
7190      else
7191	{
7192	  load_register (AT, &imm_expr, HAVE_64BIT_GPRS);
7193	  macro_build (NULL, "xor", "d,v,t", dreg, sreg, AT);
7194	  used_at = 1;
7195	}
7196      macro_build (&expr1, "sltiu", "t,r,j", dreg, dreg, BFD_RELOC_LO16);
7197      break;
7198
7199    case M_SGE:		/* sreg >= treg <==> not (sreg < treg) */
7200      s = "slt";
7201      goto sge;
7202    case M_SGEU:
7203      s = "sltu";
7204    sge:
7205      macro_build (NULL, s, "d,v,t", dreg, sreg, treg);
7206      macro_build (&expr1, "xori", "t,r,i", dreg, dreg, BFD_RELOC_LO16);
7207      break;
7208
7209    case M_SGE_I:		/* sreg >= I <==> not (sreg < I) */
7210    case M_SGEU_I:
7211      if (imm_expr.X_op == O_constant
7212	  && imm_expr.X_add_number >= -0x8000
7213	  && imm_expr.X_add_number < 0x8000)
7214	{
7215	  macro_build (&imm_expr, mask == M_SGE_I ? "slti" : "sltiu", "t,r,j",
7216		       dreg, sreg, BFD_RELOC_LO16);
7217	}
7218      else
7219	{
7220	  load_register (AT, &imm_expr, HAVE_64BIT_GPRS);
7221	  macro_build (NULL, mask == M_SGE_I ? "slt" : "sltu", "d,v,t",
7222		       dreg, sreg, AT);
7223	  used_at = 1;
7224	}
7225      macro_build (&expr1, "xori", "t,r,i", dreg, dreg, BFD_RELOC_LO16);
7226      break;
7227
7228    case M_SGT:		/* sreg > treg  <==>  treg < sreg */
7229      s = "slt";
7230      goto sgt;
7231    case M_SGTU:
7232      s = "sltu";
7233    sgt:
7234      macro_build (NULL, s, "d,v,t", dreg, treg, sreg);
7235      break;
7236
7237    case M_SGT_I:		/* sreg > I  <==>  I < sreg */
7238      s = "slt";
7239      goto sgti;
7240    case M_SGTU_I:
7241      s = "sltu";
7242    sgti:
7243      used_at = 1;
7244      load_register (AT, &imm_expr, HAVE_64BIT_GPRS);
7245      macro_build (NULL, s, "d,v,t", dreg, AT, sreg);
7246      break;
7247
7248    case M_SLE:	/* sreg <= treg  <==>  treg >= sreg  <==>  not (treg < sreg) */
7249      s = "slt";
7250      goto sle;
7251    case M_SLEU:
7252      s = "sltu";
7253    sle:
7254      macro_build (NULL, s, "d,v,t", dreg, treg, sreg);
7255      macro_build (&expr1, "xori", "t,r,i", dreg, dreg, BFD_RELOC_LO16);
7256      break;
7257
7258    case M_SLE_I:	/* sreg <= I <==> I >= sreg <==> not (I < sreg) */
7259      s = "slt";
7260      goto slei;
7261    case M_SLEU_I:
7262      s = "sltu";
7263    slei:
7264      used_at = 1;
7265      load_register (AT, &imm_expr, HAVE_64BIT_GPRS);
7266      macro_build (NULL, s, "d,v,t", dreg, AT, sreg);
7267      macro_build (&expr1, "xori", "t,r,i", dreg, dreg, BFD_RELOC_LO16);
7268      break;
7269
7270    case M_SLT_I:
7271      if (imm_expr.X_op == O_constant
7272	  && imm_expr.X_add_number >= -0x8000
7273	  && imm_expr.X_add_number < 0x8000)
7274	{
7275	  macro_build (&imm_expr, "slti", "t,r,j", dreg, sreg, BFD_RELOC_LO16);
7276	  break;
7277	}
7278      used_at = 1;
7279      load_register (AT, &imm_expr, HAVE_64BIT_GPRS);
7280      macro_build (NULL, "slt", "d,v,t", dreg, sreg, AT);
7281      break;
7282
7283    case M_SLTU_I:
7284      if (imm_expr.X_op == O_constant
7285	  && imm_expr.X_add_number >= -0x8000
7286	  && imm_expr.X_add_number < 0x8000)
7287	{
7288	  macro_build (&imm_expr, "sltiu", "t,r,j", dreg, sreg,
7289		       BFD_RELOC_LO16);
7290	  break;
7291	}
7292      used_at = 1;
7293      load_register (AT, &imm_expr, HAVE_64BIT_GPRS);
7294      macro_build (NULL, "sltu", "d,v,t", dreg, sreg, AT);
7295      break;
7296
7297    case M_SNE:
7298      if (sreg == 0)
7299	macro_build (NULL, "sltu", "d,v,t", dreg, 0, treg);
7300      else if (treg == 0)
7301	macro_build (NULL, "sltu", "d,v,t", dreg, 0, sreg);
7302      else
7303	{
7304	  macro_build (NULL, "xor", "d,v,t", dreg, sreg, treg);
7305	  macro_build (NULL, "sltu", "d,v,t", dreg, 0, dreg);
7306	}
7307      break;
7308
7309    case M_SNE_I:
7310      if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
7311	{
7312	  macro_build (NULL, "sltu", "d,v,t", dreg, 0, sreg);
7313	  break;
7314	}
7315      if (sreg == 0)
7316	{
7317	  as_warn (_("Instruction %s: result is always true"),
7318		   ip->insn_mo->name);
7319	  macro_build (&expr1, HAVE_32BIT_GPRS ? "addiu" : "daddiu", "t,r,j",
7320		       dreg, 0, BFD_RELOC_LO16);
7321	  break;
7322	}
7323      if (imm_expr.X_op == O_constant
7324	  && imm_expr.X_add_number >= 0
7325	  && imm_expr.X_add_number < 0x10000)
7326	{
7327	  macro_build (&imm_expr, "xori", "t,r,i", dreg, sreg, BFD_RELOC_LO16);
7328	}
7329      else if (imm_expr.X_op == O_constant
7330	       && imm_expr.X_add_number > -0x8000
7331	       && imm_expr.X_add_number < 0)
7332	{
7333	  imm_expr.X_add_number = -imm_expr.X_add_number;
7334	  macro_build (&imm_expr, HAVE_32BIT_GPRS ? "addiu" : "daddiu",
7335		       "t,r,j", dreg, sreg, BFD_RELOC_LO16);
7336	}
7337      else
7338	{
7339	  load_register (AT, &imm_expr, HAVE_64BIT_GPRS);
7340	  macro_build (NULL, "xor", "d,v,t", dreg, sreg, AT);
7341	  used_at = 1;
7342	}
7343      macro_build (NULL, "sltu", "d,v,t", dreg, 0, dreg);
7344      break;
7345
7346    case M_DSUB_I:
7347      dbl = 1;
7348    case M_SUB_I:
7349      if (imm_expr.X_op == O_constant
7350	  && imm_expr.X_add_number > -0x8000
7351	  && imm_expr.X_add_number <= 0x8000)
7352	{
7353	  imm_expr.X_add_number = -imm_expr.X_add_number;
7354	  macro_build (&imm_expr, dbl ? "daddi" : "addi", "t,r,j",
7355		       dreg, sreg, BFD_RELOC_LO16);
7356	  break;
7357	}
7358      used_at = 1;
7359      load_register (AT, &imm_expr, dbl);
7360      macro_build (NULL, dbl ? "dsub" : "sub", "d,v,t", dreg, sreg, AT);
7361      break;
7362
7363    case M_DSUBU_I:
7364      dbl = 1;
7365    case M_SUBU_I:
7366      if (imm_expr.X_op == O_constant
7367	  && imm_expr.X_add_number > -0x8000
7368	  && imm_expr.X_add_number <= 0x8000)
7369	{
7370	  imm_expr.X_add_number = -imm_expr.X_add_number;
7371	  macro_build (&imm_expr, dbl ? "daddiu" : "addiu", "t,r,j",
7372		       dreg, sreg, BFD_RELOC_LO16);
7373	  break;
7374	}
7375      used_at = 1;
7376      load_register (AT, &imm_expr, dbl);
7377      macro_build (NULL, dbl ? "dsubu" : "subu", "d,v,t", dreg, sreg, AT);
7378      break;
7379
7380    case M_TEQ_I:
7381      s = "teq";
7382      goto trap;
7383    case M_TGE_I:
7384      s = "tge";
7385      goto trap;
7386    case M_TGEU_I:
7387      s = "tgeu";
7388      goto trap;
7389    case M_TLT_I:
7390      s = "tlt";
7391      goto trap;
7392    case M_TLTU_I:
7393      s = "tltu";
7394      goto trap;
7395    case M_TNE_I:
7396      s = "tne";
7397    trap:
7398      used_at = 1;
7399      load_register (AT, &imm_expr, HAVE_64BIT_GPRS);
7400      macro_build (NULL, s, "s,t", sreg, AT);
7401      break;
7402
7403    case M_TRUNCWS:
7404    case M_TRUNCWD:
7405      if (mips_opts.arch == CPU_OCTEON && octeon_error_on_unsupported)
7406        {
7407          as_bad (_("opcode not implemented in Octeon `%s'"), ip->insn_mo->name);
7408          return;
7409        }
7410      assert (mips_opts.isa == ISA_MIPS1);
7411      used_at = 1;
7412      sreg = (ip->insn_opcode >> 11) & 0x1f;	/* floating reg */
7413      dreg = (ip->insn_opcode >> 06) & 0x1f;	/* floating reg */
7414
7415      /*
7416       * Is the double cfc1 instruction a bug in the mips assembler;
7417       * or is there a reason for it?
7418       */
7419      start_noreorder ();
7420      macro_build (NULL, "cfc1", "t,G", treg, RA);
7421      macro_build (NULL, "cfc1", "t,G", treg, RA);
7422      macro_build (NULL, "nop", "");
7423      expr1.X_add_number = 3;
7424      macro_build (&expr1, "ori", "t,r,i", AT, treg, BFD_RELOC_LO16);
7425      expr1.X_add_number = 2;
7426      macro_build (&expr1, "xori", "t,r,i", AT, AT, BFD_RELOC_LO16);
7427      macro_build (NULL, "ctc1", "t,G", AT, RA);
7428      macro_build (NULL, "nop", "");
7429      macro_build (NULL, mask == M_TRUNCWD ? "cvt.w.d" : "cvt.w.s", "D,S",
7430		   dreg, sreg);
7431      macro_build (NULL, "ctc1", "t,G", treg, RA);
7432      macro_build (NULL, "nop", "");
7433      end_noreorder ();
7434      break;
7435
7436    case M_ULH:
7437      s = "lb";
7438      goto ulh;
7439    case M_ULHU:
7440      s = "lbu";
7441    ulh:
7442      used_at = 1;
7443      if (offset_expr.X_add_number >= 0x7fff)
7444	as_bad (_("operand overflow"));
7445      /* Expand the ulh to "lb, lbu, ins" instead of "lb, lbu, sll, ori". */
7446      if (! target_big_endian)
7447	++offset_expr.X_add_number;
7448      macro_build (&offset_expr, s, "t,o(b)", AT, BFD_RELOC_LO16, breg);
7449      if (! target_big_endian)
7450	--offset_expr.X_add_number;
7451      else
7452	++offset_expr.X_add_number;
7453      macro_build (&offset_expr, "lbu", "t,o(b)", treg, BFD_RELOC_LO16, breg);
7454      if (ISA_HAS_INS (mips_opts.isa))
7455	macro_build (NULL, "ins", "t,r,+A,+B", treg, AT, 8, 31);
7456      else
7457	{
7458          macro_build (NULL, "sll", "d,w,<", AT, AT, 8);
7459          macro_build (NULL, "or", "d,v,t", treg, treg, AT);
7460	}
7461      break;
7462
7463    case M_ULD:
7464      s = "ldl";
7465      s2 = "ldr";
7466      off = 7;
7467      goto ulw;
7468    case M_ULW:
7469      s = "lwl";
7470      s2 = "lwr";
7471      off = 3;
7472    ulw:
7473      if (offset_expr.X_add_number >= 0x8000 - off)
7474	as_bad (_("operand overflow"));
7475      if (treg != breg)
7476	tempreg = treg;
7477      else
7478	{
7479	  used_at = 1;
7480	  tempreg = AT;
7481	}
7482
7483      /* For small variables the compiler uses gp_rel to load the value of
7484	 the variables. While parsing instructions "uld $2,%gp_rel(var)($28)"
7485	 the offset_reloc[0] is set to BFD_RELOC_GPREL16. Use this relocation
7486	 type while emitting instructions otherwise use BFD_RELOC_LO16.  */
7487      if (offset_reloc[0] == BFD_RELOC_UNUSED)
7488	offset_reloc[0] = BFD_RELOC_LO16;
7489
7490      if (octeon_use_unalign && mips_opts.arch == CPU_OCTEON)
7491	{
7492	  /* Reset used_at as tempreg is not used while generating Octeon
7493	     unaligned load/store.  */
7494	  used_at = 0;
7495	  macro_build (&offset_expr, (mask == M_ULW ? "ulw" : "uld"), "t,o(b)",
7496		       treg, offset_reloc[0], breg);
7497	  break;
7498	}
7499
7500      if (! target_big_endian)
7501	offset_expr.X_add_number += off;
7502      macro_build (&offset_expr, s, "t,o(b)", tempreg, offset_reloc[0], breg);
7503      if (! target_big_endian)
7504	offset_expr.X_add_number -= off;
7505      else
7506	offset_expr.X_add_number += off;
7507      macro_build (&offset_expr, s2, "t,o(b)", tempreg, offset_reloc[0], breg);
7508
7509      /* If necessary, move the result in tempreg the final destination.  */
7510      if (treg == tempreg)
7511        break;
7512      /* Protect second load's delay slot.  */
7513      load_delay_nop ();
7514      move_register (treg, tempreg);
7515      break;
7516
7517    case M_ULD_A:
7518      s = "ldl";
7519      s2 = "ldr";
7520      off = 7;
7521      goto ulwa;
7522    case M_ULW_A:
7523      s = "lwl";
7524      s2 = "lwr";
7525      off = 3;
7526    ulwa:
7527      used_at = 1;
7528      load_address (AT, &offset_expr, &used_at);
7529      if (breg != 0)
7530	macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", AT, AT, breg);
7531
7532      /* For small variables the compiler uses gp_rel to load the value of
7533	 the variables. While parsing instructions "uld $2,%gp_rel(var)($28)"
7534	 the offset_reloc[0] is set to BFD_RELOC_GPREL16. Use this relocation
7535	 type while emitting instructions otherwise use BFD_RELOC_LO16.  */
7536      if (offset_reloc[0] == BFD_RELOC_UNUSED)
7537	offset_reloc[0] = BFD_RELOC_LO16;
7538
7539      if (octeon_use_unalign && mips_opts.arch == CPU_OCTEON)
7540	{
7541	  macro_build (&offset_expr, (mask == M_ULW_A ? "ulw" : "uld"),
7542		       "t,o(b)", treg, offset_reloc[0], AT);
7543	  break;
7544	}
7545
7546      if (! target_big_endian)
7547	expr1.X_add_number = off;
7548      else
7549	expr1.X_add_number = 0;
7550      macro_build (&expr1, s, "t,o(b)", treg, offset_reloc[0], AT);
7551      if (! target_big_endian)
7552	expr1.X_add_number = 0;
7553      else
7554	expr1.X_add_number = off;
7555      macro_build (&expr1, s2, "t,o(b)", treg, offset_reloc[0], AT);
7556      break;
7557
7558    case M_ULH_A:
7559    case M_ULHU_A:
7560      used_at = 1;
7561      load_address (AT, &offset_expr, &used_at);
7562      if (breg != 0)
7563	macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", AT, AT, breg);
7564
7565      if (ISA_HAS_INS (mips_opts.isa))
7566	{
7567	  if (target_big_endian)
7568	    expr1.X_add_number = 1;
7569	  else
7570	    expr1.X_add_number = 0;
7571	  macro_build (&expr1, "lbu", "t,o(b)", treg, BFD_RELOC_LO16, AT);
7572	  if (target_big_endian)
7573	    expr1.X_add_number = 0;
7574	  else
7575	    expr1.X_add_number = 1;
7576	  macro_build (&expr1, mask == M_ULH_A ? "lb" : "lbu", "t,o(b)",
7577		       AT, BFD_RELOC_LO16, AT);
7578	  macro_build (NULL, "ins", "t,r,+A,+B", treg, AT, 8, 31);
7579	  break;
7580	}
7581      if (target_big_endian)
7582	expr1.X_add_number = 0;
7583      macro_build (&expr1, mask == M_ULH_A ? "lb" : "lbu", "t,o(b)",
7584		   treg, BFD_RELOC_LO16, AT);
7585      if (target_big_endian)
7586	expr1.X_add_number = 1;
7587      else
7588	expr1.X_add_number = 0;
7589      macro_build (&expr1, "lbu", "t,o(b)", AT, BFD_RELOC_LO16, AT);
7590      macro_build (NULL, "sll", "d,w,<", treg, treg, 8);
7591      macro_build (NULL, "or", "d,v,t", treg, treg, AT);
7592      break;
7593
7594    case M_USH:
7595      used_at = 1;
7596      if (offset_expr.X_add_number >= 0x7fff)
7597	as_bad (_("operand overflow"));
7598      if (target_big_endian)
7599	++offset_expr.X_add_number;
7600      macro_build (&offset_expr, "sb", "t,o(b)", treg, BFD_RELOC_LO16, breg);
7601      macro_build (NULL, "srl", "d,w,<", AT, treg, 8);
7602      if (target_big_endian)
7603	--offset_expr.X_add_number;
7604      else
7605	++offset_expr.X_add_number;
7606      macro_build (&offset_expr, "sb", "t,o(b)", AT, BFD_RELOC_LO16, breg);
7607      break;
7608
7609    case M_USD:
7610      s = "sdl";
7611      s2 = "sdr";
7612      off = 7;
7613      goto usw;
7614    case M_USW:
7615      s = "swl";
7616      s2 = "swr";
7617      off = 3;
7618    usw:
7619      if (offset_expr.X_add_number >= 0x8000 - off)
7620	as_bad (_("operand overflow"));
7621
7622      /* For small variables the compiler uses gp_rel to load the value of
7623	 the variables. While parsing instructions "uld $2,%gp_rel(var)($28)"
7624	 the offset_reloc[0] is set to BFD_RELOC_GPREL16. Use this relocation
7625	 type while emitting instructions otherwise use BFD_RELOC_LO16.  */
7626      if (offset_reloc[0] == BFD_RELOC_UNUSED)
7627	offset_reloc[0] = BFD_RELOC_LO16;
7628
7629      if (octeon_use_unalign && mips_opts.arch == CPU_OCTEON)
7630	{
7631	  macro_build (&offset_expr, (mask == M_USD ? "usd" : "usw"),
7632		       "t,o(b)", treg, offset_reloc[0], breg);
7633	  break;
7634	}
7635      if (! target_big_endian)
7636	offset_expr.X_add_number += off;
7637      macro_build (&offset_expr, s, "t,o(b)", treg, offset_reloc[0], breg);
7638      if (! target_big_endian)
7639	offset_expr.X_add_number -= off;
7640      else
7641	offset_expr.X_add_number += off;
7642      macro_build (&offset_expr, s2, "t,o(b)", treg, offset_reloc[0], breg);
7643      break;
7644
7645    case M_USD_A:
7646      s = "sdl";
7647      s2 = "sdr";
7648      off = 7;
7649      goto uswa;
7650    case M_USW_A:
7651      s = "swl";
7652      s2 = "swr";
7653      off = 3;
7654    uswa:
7655      used_at = 1;
7656      load_address (AT, &offset_expr, &used_at);
7657      if (breg != 0)
7658	macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", AT, AT, breg);
7659
7660      /* For small variables the compiler uses gp_rel to load the value of
7661	 the variables. While parsing instructions "uld $2,%gp_rel(var)($28)"
7662	 the offset_reloc[0] is set to BFD_RELOC_GPREL16. Use this relocation
7663	 type while emitting instructions otherwise use BFD_RELOC_LO16.  */
7664      if (offset_reloc[0] == BFD_RELOC_UNUSED)
7665	offset_reloc[0] = BFD_RELOC_LO16;
7666
7667      if (octeon_use_unalign && mips_opts.arch == CPU_OCTEON)
7668	{
7669	  macro_build (&offset_expr, (mask == M_USW_A ? "usw" : "usd"),
7670		       "t,o(b)", treg, offset_reloc[0], AT);
7671	  break;
7672	}
7673      if (! target_big_endian)
7674	expr1.X_add_number = off;
7675      else
7676	expr1.X_add_number = 0;
7677      macro_build (&expr1, s, "t,o(b)", treg, offset_reloc[0], AT);
7678      if (! target_big_endian)
7679	expr1.X_add_number = 0;
7680      else
7681	expr1.X_add_number = off;
7682      macro_build (&expr1, s2, "t,o(b)", treg, offset_reloc[0], AT);
7683      break;
7684
7685    case M_USH_A:
7686      used_at = 1;
7687      load_address (AT, &offset_expr, &used_at);
7688      if (breg != 0)
7689	macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", AT, AT, breg);
7690      if (! target_big_endian)
7691	expr1.X_add_number = 0;
7692      macro_build (&expr1, "sb", "t,o(b)", treg, BFD_RELOC_LO16, AT);
7693      macro_build (NULL, "srl", "d,w,<", treg, treg, 8);
7694      if (! target_big_endian)
7695	expr1.X_add_number = 1;
7696      else
7697	expr1.X_add_number = 0;
7698      macro_build (&expr1, "sb", "t,o(b)", treg, BFD_RELOC_LO16, AT);
7699      if (! target_big_endian)
7700	expr1.X_add_number = 0;
7701      else
7702	expr1.X_add_number = 1;
7703      macro_build (&expr1, "lbu", "t,o(b)", AT, BFD_RELOC_LO16, AT);
7704      macro_build (NULL, "sll", "d,w,<", treg, treg, 8);
7705      macro_build (NULL, "or", "d,v,t", treg, treg, AT);
7706      break;
7707
7708    default:
7709      /* FIXME: Check if this is one of the itbl macros, since they
7710	 are added dynamically.  */
7711      as_bad (_("Macro %s not implemented yet"), ip->insn_mo->name);
7712      break;
7713    }
7714  if (mips_opts.noat && used_at)
7715    as_bad (_("Macro used $at after \".set noat\""));
7716}
7717
7718/* Implement macros in mips16 mode.  */
7719
7720static void
7721mips16_macro (struct mips_cl_insn *ip)
7722{
7723  int mask;
7724  int xreg, yreg, zreg, tmp;
7725  expressionS expr1;
7726  int dbl;
7727  const char *s, *s2, *s3;
7728
7729  mask = ip->insn_mo->mask;
7730
7731  xreg = MIPS16_EXTRACT_OPERAND (RX, *ip);
7732  yreg = MIPS16_EXTRACT_OPERAND (RY, *ip);
7733  zreg = MIPS16_EXTRACT_OPERAND (RZ, *ip);
7734
7735  expr1.X_op = O_constant;
7736  expr1.X_op_symbol = NULL;
7737  expr1.X_add_symbol = NULL;
7738  expr1.X_add_number = 1;
7739
7740  dbl = 0;
7741
7742  switch (mask)
7743    {
7744    default:
7745      internalError ();
7746
7747    case M_DDIV_3:
7748      dbl = 1;
7749    case M_DIV_3:
7750      s = "mflo";
7751      goto do_div3;
7752    case M_DREM_3:
7753      dbl = 1;
7754    case M_REM_3:
7755      s = "mfhi";
7756    do_div3:
7757      start_noreorder ();
7758      macro_build (NULL, dbl ? "ddiv" : "div", "0,x,y", xreg, yreg);
7759      expr1.X_add_number = 2;
7760      macro_build (&expr1, "bnez", "x,p", yreg);
7761      macro_build (NULL, "break", "6", 7);
7762
7763      /* FIXME: The normal code checks for of -1 / -0x80000000 here,
7764         since that causes an overflow.  We should do that as well,
7765         but I don't see how to do the comparisons without a temporary
7766         register.  */
7767      end_noreorder ();
7768      macro_build (NULL, s, "x", zreg);
7769      break;
7770
7771    case M_DIVU_3:
7772      s = "divu";
7773      s2 = "mflo";
7774      goto do_divu3;
7775    case M_REMU_3:
7776      s = "divu";
7777      s2 = "mfhi";
7778      goto do_divu3;
7779    case M_DDIVU_3:
7780      s = "ddivu";
7781      s2 = "mflo";
7782      goto do_divu3;
7783    case M_DREMU_3:
7784      s = "ddivu";
7785      s2 = "mfhi";
7786    do_divu3:
7787      start_noreorder ();
7788      macro_build (NULL, s, "0,x,y", xreg, yreg);
7789      expr1.X_add_number = 2;
7790      macro_build (&expr1, "bnez", "x,p", yreg);
7791      macro_build (NULL, "break", "6", 7);
7792      end_noreorder ();
7793      macro_build (NULL, s2, "x", zreg);
7794      break;
7795
7796    case M_DMUL:
7797      dbl = 1;
7798    case M_MUL:
7799      macro_build (NULL, dbl ? "dmultu" : "multu", "x,y", xreg, yreg);
7800      macro_build (NULL, "mflo", "x", zreg);
7801      break;
7802
7803    case M_DSUBU_I:
7804      dbl = 1;
7805      goto do_subu;
7806    case M_SUBU_I:
7807    do_subu:
7808      if (imm_expr.X_op != O_constant)
7809	as_bad (_("Unsupported large constant"));
7810      imm_expr.X_add_number = -imm_expr.X_add_number;
7811      macro_build (&imm_expr, dbl ? "daddiu" : "addiu", "y,x,4", yreg, xreg);
7812      break;
7813
7814    case M_SUBU_I_2:
7815      if (imm_expr.X_op != O_constant)
7816	as_bad (_("Unsupported large constant"));
7817      imm_expr.X_add_number = -imm_expr.X_add_number;
7818      macro_build (&imm_expr, "addiu", "x,k", xreg);
7819      break;
7820
7821    case M_DSUBU_I_2:
7822      if (imm_expr.X_op != O_constant)
7823	as_bad (_("Unsupported large constant"));
7824      imm_expr.X_add_number = -imm_expr.X_add_number;
7825      macro_build (&imm_expr, "daddiu", "y,j", yreg);
7826      break;
7827
7828    case M_BEQ:
7829      s = "cmp";
7830      s2 = "bteqz";
7831      goto do_branch;
7832    case M_BNE:
7833      s = "cmp";
7834      s2 = "btnez";
7835      goto do_branch;
7836    case M_BLT:
7837      s = "slt";
7838      s2 = "btnez";
7839      goto do_branch;
7840    case M_BLTU:
7841      s = "sltu";
7842      s2 = "btnez";
7843      goto do_branch;
7844    case M_BLE:
7845      s = "slt";
7846      s2 = "bteqz";
7847      goto do_reverse_branch;
7848    case M_BLEU:
7849      s = "sltu";
7850      s2 = "bteqz";
7851      goto do_reverse_branch;
7852    case M_BGE:
7853      s = "slt";
7854      s2 = "bteqz";
7855      goto do_branch;
7856    case M_BGEU:
7857      s = "sltu";
7858      s2 = "bteqz";
7859      goto do_branch;
7860    case M_BGT:
7861      s = "slt";
7862      s2 = "btnez";
7863      goto do_reverse_branch;
7864    case M_BGTU:
7865      s = "sltu";
7866      s2 = "btnez";
7867
7868    do_reverse_branch:
7869      tmp = xreg;
7870      xreg = yreg;
7871      yreg = tmp;
7872
7873    do_branch:
7874      macro_build (NULL, s, "x,y", xreg, yreg);
7875      macro_build (&offset_expr, s2, "p");
7876      break;
7877
7878    case M_BEQ_I:
7879      s = "cmpi";
7880      s2 = "bteqz";
7881      s3 = "x,U";
7882      goto do_branch_i;
7883    case M_BNE_I:
7884      s = "cmpi";
7885      s2 = "btnez";
7886      s3 = "x,U";
7887      goto do_branch_i;
7888    case M_BLT_I:
7889      s = "slti";
7890      s2 = "btnez";
7891      s3 = "x,8";
7892      goto do_branch_i;
7893    case M_BLTU_I:
7894      s = "sltiu";
7895      s2 = "btnez";
7896      s3 = "x,8";
7897      goto do_branch_i;
7898    case M_BLE_I:
7899      s = "slti";
7900      s2 = "btnez";
7901      s3 = "x,8";
7902      goto do_addone_branch_i;
7903    case M_BLEU_I:
7904      s = "sltiu";
7905      s2 = "btnez";
7906      s3 = "x,8";
7907      goto do_addone_branch_i;
7908    case M_BGE_I:
7909      s = "slti";
7910      s2 = "bteqz";
7911      s3 = "x,8";
7912      goto do_branch_i;
7913    case M_BGEU_I:
7914      s = "sltiu";
7915      s2 = "bteqz";
7916      s3 = "x,8";
7917      goto do_branch_i;
7918    case M_BGT_I:
7919      s = "slti";
7920      s2 = "bteqz";
7921      s3 = "x,8";
7922      goto do_addone_branch_i;
7923    case M_BGTU_I:
7924      s = "sltiu";
7925      s2 = "bteqz";
7926      s3 = "x,8";
7927
7928    do_addone_branch_i:
7929      if (imm_expr.X_op != O_constant)
7930	as_bad (_("Unsupported large constant"));
7931      ++imm_expr.X_add_number;
7932
7933    do_branch_i:
7934      macro_build (&imm_expr, s, s3, xreg);
7935      macro_build (&offset_expr, s2, "p");
7936      break;
7937
7938    case M_ABS:
7939      expr1.X_add_number = 0;
7940      macro_build (&expr1, "slti", "x,8", yreg);
7941      if (xreg != yreg)
7942	move_register (xreg, yreg);
7943      expr1.X_add_number = 2;
7944      macro_build (&expr1, "bteqz", "p");
7945      macro_build (NULL, "neg", "x,w", xreg, xreg);
7946    }
7947}
7948
7949/* For consistency checking, verify that all bits are specified either
7950   by the match/mask part of the instruction definition, or by the
7951   operand list.  */
7952static int
7953validate_mips_insn (const struct mips_opcode *opc)
7954{
7955  const char *p = opc->args;
7956  char c;
7957  unsigned long used_bits = opc->mask;
7958
7959  if ((used_bits & opc->match) != opc->match)
7960    {
7961      as_bad (_("internal: bad mips opcode (mask error): %s %s"),
7962	      opc->name, opc->args);
7963      return 0;
7964    }
7965#define USE_BITS(mask,shift)	(used_bits |= ((mask) << (shift)))
7966  while (*p)
7967    switch (c = *p++)
7968      {
7969      case ',': break;
7970      case '(': break;
7971      case ')': break;
7972      case '^': USE_BITS (OP_MASK_BITIND,       OP_SH_BITIND);   break;
7973      case '~': USE_BITS (OP_MASK_BITIND,       OP_SH_BITIND);   break;
7974      case '+':
7975    	switch (c = *p++)
7976	  {
7977	  case 'A': USE_BITS (OP_MASK_SHAMT,	OP_SH_SHAMT);	break;
7978	  case 'B': USE_BITS (OP_MASK_INSMSB,	OP_SH_INSMSB);	break;
7979	  case 'C': USE_BITS (OP_MASK_EXTMSBD,	OP_SH_EXTMSBD);	break;
7980	  case 'D': USE_BITS (OP_MASK_RD,	OP_SH_RD);
7981		    USE_BITS (OP_MASK_SEL,	OP_SH_SEL);	break;
7982	  case 'E': USE_BITS (OP_MASK_SHAMT,	OP_SH_SHAMT);	break;
7983	  case 'F': USE_BITS (OP_MASK_INSMSB,	OP_SH_INSMSB);	break;
7984	  case 'G': USE_BITS (OP_MASK_EXTMSBD,	OP_SH_EXTMSBD);	break;
7985	  case 'H': USE_BITS (OP_MASK_EXTMSBD,	OP_SH_EXTMSBD);	break;
7986	  case 'I': break;
7987	  case 't': USE_BITS (OP_MASK_RT,	OP_SH_RT);	break;
7988	  case 'T': USE_BITS (OP_MASK_RT,	OP_SH_RT);
7989		    USE_BITS (OP_MASK_SEL,	OP_SH_SEL);	break;
7990	  default:
7991	    as_bad (_("internal: bad mips opcode (unknown extension operand type `+%c'): %s %s"),
7992		    c, opc->name, opc->args);
7993	    return 0;
7994	  }
7995	break;
7996      case '<': USE_BITS (OP_MASK_SHAMT,	OP_SH_SHAMT);	break;
7997      case '>':	USE_BITS (OP_MASK_SHAMT,	OP_SH_SHAMT);	break;
7998      case 'A': break;
7999      case 'B': USE_BITS (OP_MASK_CODE20,       OP_SH_CODE20);  break;
8000      case 'C':	USE_BITS (OP_MASK_COPZ,		OP_SH_COPZ);	break;
8001      case 'D':	USE_BITS (OP_MASK_FD,		OP_SH_FD);	break;
8002      case 'E':	USE_BITS (OP_MASK_RT,		OP_SH_RT);	break;
8003      case 'F': break;
8004      case 'G':	USE_BITS (OP_MASK_RD,		OP_SH_RD);	break;
8005      case 'H': USE_BITS (OP_MASK_SEL,		OP_SH_SEL);	break;
8006      case 'I': break;
8007      case 'J': USE_BITS (OP_MASK_CODE19,       OP_SH_CODE19);  break;
8008      case 'K':	USE_BITS (OP_MASK_RD,		OP_SH_RD);	break;
8009      case 'L': break;
8010      case 'M':	USE_BITS (OP_MASK_CCC,		OP_SH_CCC);	break;
8011      case 'N':	USE_BITS (OP_MASK_BCC,		OP_SH_BCC);	break;
8012      case 'O':	USE_BITS (OP_MASK_ALN,		OP_SH_ALN);	break;
8013      case 'Q':	USE_BITS (OP_MASK_VSEL,		OP_SH_VSEL);
8014		USE_BITS (OP_MASK_FT,		OP_SH_FT);	break;
8015      case 'R':	USE_BITS (OP_MASK_FR,		OP_SH_FR);	break;
8016      case 'S':	USE_BITS (OP_MASK_FS,		OP_SH_FS);	break;
8017      case 'T':	USE_BITS (OP_MASK_FT,		OP_SH_FT);	break;
8018      case 'V':	USE_BITS (OP_MASK_FS,		OP_SH_FS);	break;
8019      case 'W':	USE_BITS (OP_MASK_FT,		OP_SH_FT);	break;
8020      case 'X':	USE_BITS (OP_MASK_FD,		OP_SH_FD);	break;
8021      case 'Y':	USE_BITS (OP_MASK_FS,		OP_SH_FS);	break;
8022      case 'Z':	USE_BITS (OP_MASK_FT,		OP_SH_FT);	break;
8023      case 'a':	USE_BITS (OP_MASK_TARGET,	OP_SH_TARGET);	break;
8024      case 'b':	USE_BITS (OP_MASK_RS,		OP_SH_RS);	break;
8025      case 'c':	USE_BITS (OP_MASK_CODE,		OP_SH_CODE);	break;
8026      case 'd':	USE_BITS (OP_MASK_RD,		OP_SH_RD);	break;
8027      case 'f': break;
8028      case 'h':	USE_BITS (OP_MASK_PREFX,	OP_SH_PREFX);	break;
8029      case 'i':	USE_BITS (OP_MASK_IMMEDIATE,	OP_SH_IMMEDIATE); break;
8030      case 'j':	USE_BITS (OP_MASK_DELTA,	OP_SH_DELTA);	break;
8031      case 'k':	USE_BITS (OP_MASK_CACHE,	OP_SH_CACHE);	break;
8032      case 'l': break;
8033      case 'o': USE_BITS (OP_MASK_DELTA,	OP_SH_DELTA);	break;
8034      case 'p':	USE_BITS (OP_MASK_DELTA,	OP_SH_DELTA);	break;
8035      case 'q':	USE_BITS (OP_MASK_CODE2,	OP_SH_CODE2);	break;
8036      case 'r': USE_BITS (OP_MASK_RS,		OP_SH_RS);	break;
8037      case 's':	USE_BITS (OP_MASK_RS,		OP_SH_RS);	break;
8038      case 't':	USE_BITS (OP_MASK_RT,		OP_SH_RT);	break;
8039      case 'u':	USE_BITS (OP_MASK_IMMEDIATE,	OP_SH_IMMEDIATE); break;
8040      case 'v':	USE_BITS (OP_MASK_RS,		OP_SH_RS);	break;
8041      case 'w':	USE_BITS (OP_MASK_RT,		OP_SH_RT);	break;
8042      case 'x': break;
8043      case 'y': USE_BITS (OP_MASK_CODE2,        OP_SH_CODE2);   break;
8044      case 'z': break;
8045      case 'P': USE_BITS (OP_MASK_PERFREG,	OP_SH_PERFREG);	break;
8046      case 'U': USE_BITS (OP_MASK_RD,           OP_SH_RD);
8047	        USE_BITS (OP_MASK_RT,           OP_SH_RT);	break;
8048      case 'e': USE_BITS (OP_MASK_VECBYTE,	OP_SH_VECBYTE);	break;
8049      case '%': USE_BITS (OP_MASK_VECALIGN,	OP_SH_VECALIGN); break;
8050      case '[': break;
8051      case ']': break;
8052      case '3': USE_BITS (OP_MASK_SA3,  	OP_SH_SA3);	break;
8053      case '4': USE_BITS (OP_MASK_SA4,  	OP_SH_SA4);	break;
8054      case '5': USE_BITS (OP_MASK_IMM8, 	OP_SH_IMM8);	break;
8055      case '6': USE_BITS (OP_MASK_RS,		OP_SH_RS);	break;
8056      case '7': USE_BITS (OP_MASK_DSPACC,	OP_SH_DSPACC);	break;
8057      case '8': USE_BITS (OP_MASK_WRDSP,	OP_SH_WRDSP);	break;
8058      case '9': USE_BITS (OP_MASK_DSPACC_S,	OP_SH_DSPACC_S);break;
8059      case '0': USE_BITS (OP_MASK_DSPSFT,	OP_SH_DSPSFT);	break;
8060      case '\'': USE_BITS (OP_MASK_RDDSP,	OP_SH_RDDSP);	break;
8061      case ':': USE_BITS (OP_MASK_DSPSFT_7,	OP_SH_DSPSFT_7);break;
8062      case '@': USE_BITS (OP_MASK_IMM10,	OP_SH_IMM10);	break;
8063      case '!': USE_BITS (OP_MASK_MT_U,		OP_SH_MT_U);	break;
8064      case '$': USE_BITS (OP_MASK_MT_H,		OP_SH_MT_H);	break;
8065      case '*': USE_BITS (OP_MASK_MTACC_T,	OP_SH_MTACC_T);	break;
8066      case '&': USE_BITS (OP_MASK_MTACC_D,	OP_SH_MTACC_D);	break;
8067      case 'g': USE_BITS (OP_MASK_RD,		OP_SH_RD);	break;
8068      default:
8069	as_bad (_("internal: bad mips opcode (unknown operand type `%c'): %s %s"),
8070		c, opc->name, opc->args);
8071	return 0;
8072      }
8073#undef USE_BITS
8074  if (used_bits != 0xffffffff)
8075    {
8076      as_bad (_("internal: bad mips opcode (bits 0x%lx undefined): %s %s"),
8077	      ~used_bits & 0xffffffff, opc->name, opc->args);
8078      return 0;
8079    }
8080  return 1;
8081}
8082
8083/* This routine assembles an instruction into its binary format.  As a
8084   side effect, it sets one of the global variables imm_reloc or
8085   offset_reloc to the type of relocation to do if one of the operands
8086   is an address expression.  */
8087
8088static void
8089mips_ip (char *str, struct mips_cl_insn *ip)
8090{
8091  char *s;
8092  const char *args;
8093  char c = 0;
8094  struct mips_opcode *insn;
8095  char *argsStart;
8096  unsigned int regno;
8097  unsigned int lastregno = 0;
8098  unsigned int lastpos = 0;
8099  unsigned int limlo, limhi;
8100  char *s_reset;
8101  char save_c = 0;
8102  offsetT min_range, max_range;
8103
8104  insn_error = NULL;
8105
8106  /* If the instruction contains a '.', we first try to match an instruction
8107     including the '.'.  Then we try again without the '.'.  */
8108  insn = NULL;
8109  for (s = str; *s != '\0' && !ISSPACE (*s); ++s)
8110    continue;
8111
8112  /* If we stopped on whitespace, then replace the whitespace with null for
8113     the call to hash_find.  Save the character we replaced just in case we
8114     have to re-parse the instruction.  */
8115  if (ISSPACE (*s))
8116    {
8117      save_c = *s;
8118      *s++ = '\0';
8119    }
8120
8121  insn = (struct mips_opcode *) hash_find (op_hash, str);
8122
8123  /* If we didn't find the instruction in the opcode table, try again, but
8124     this time with just the instruction up to, but not including the
8125     first '.'.  */
8126  if (insn == NULL)
8127    {
8128      /* Restore the character we overwrite above (if any).  */
8129      if (save_c)
8130	*(--s) = save_c;
8131
8132      /* Scan up to the first '.' or whitespace.  */
8133      for (s = str;
8134	   *s != '\0' && *s != '.' && !ISSPACE (*s);
8135	   ++s)
8136	continue;
8137
8138      /* If we did not find a '.', then we can quit now.  */
8139      if (*s != '.')
8140	{
8141	  insn_error = "unrecognized opcode";
8142	  return;
8143	}
8144
8145      /* Lookup the instruction in the hash table.  */
8146      *s++ = '\0';
8147      if ((insn = (struct mips_opcode *) hash_find (op_hash, str)) == NULL)
8148	{
8149	  insn_error = "unrecognized opcode";
8150	  return;
8151	}
8152    }
8153
8154  argsStart = s;
8155  for (;;)
8156    {
8157      bfd_boolean ok;
8158
8159      assert (strcmp (insn->name, str) == 0);
8160
8161      if (OPCODE_IS_MEMBER (insn,
8162			    (mips_opts.isa
8163			     | (file_ase_mips16 ? INSN_MIPS16 : 0)
8164	      		     | (mips_opts.ase_mdmx ? INSN_MDMX : 0)
8165	      		     | (mips_opts.ase_dsp ? INSN_DSP : 0)
8166	      		     | (mips_opts.ase_mt ? INSN_MT : 0)
8167			     | (mips_opts.ase_mips3d ? INSN_MIPS3D : 0)),
8168			    mips_opts.arch))
8169	ok = TRUE;
8170      else
8171	ok = FALSE;
8172
8173      if (insn->pinfo != INSN_MACRO)
8174	{
8175	  if (mips_opts.arch == CPU_R4650 && (insn->pinfo & FP_D) != 0)
8176	    ok = FALSE;
8177
8178	  if (mips_opts.arch == CPU_OCTEON
8179	      && octeon_error_on_unsupported
8180	      && ((insn->pinfo & FP_D) != 0
8181	          || (insn->pinfo & FP_S) !=0
8182	          || strcmp (insn->name, "prefx") == 0))
8183	    {
8184	      insn_error = "opcode not implemented in Octeon";
8185	      return;
8186	    }
8187
8188	  if (mips_opts.arch == CPU_OCTEON
8189	      && octeon_error_on_unsupported
8190	      && (strcmp (insn->name, "swc2") == 0
8191		  || strcmp (insn->name, "lwc2") == 0
8192		  || strcmp (insn->name, "sdc2") == 0
8193		  || strcmp (insn->name, "ldc2") == 0
8194		  || strcmp (insn->name, "bc2f") == 0
8195		  || strcmp (insn->name, "bc2t") == 0
8196		  || strcmp (insn->name, "mfc2") == 0
8197		  || strcmp (insn->name, "mtc2") == 0
8198		  || strcmp (insn->name, "ctc2") == 0
8199		  || strcmp (insn->name, "cfc2") == 0
8200		  || strcmp (insn->name, "mfhc2") == 0
8201		  || strcmp (insn->name, "mthc2") == 0))
8202	    {
8203	      insn_error = "opcode not implemented in Octeon";
8204	      return;
8205	    }
8206
8207	  /* Issue a warning message for Octeon unaligned load/store
8208	     instructions used when octeon_use_unalign is not set.  */
8209	  if (mips_opts.arch == CPU_OCTEON && ! octeon_use_unalign
8210              && (strcmp (insn->name, "ulw") == 0
8211                  || strcmp (insn->name, "uld") == 0
8212                  || strcmp (insn->name, "usw") == 0
8213                  || strcmp (insn->name, "usd") == 0))
8214            {
8215              static char buf[120];
8216              sprintf (buf, _("Octeon specific unaligned load/store instructions are not allowed with -mno-octeon-useun"));
8217              insn_error = buf;
8218              return;
8219            }
8220
8221	  /* Issue a warning message for MIPS unaligned load/store
8222	     instructions used when octeon_use_unalign is set.  */
8223          if (mips_opts.arch == CPU_OCTEON && octeon_use_unalign
8224              && (strcmp (insn->name, "lwl") == 0
8225                  || strcmp (insn->name, "lwr") == 0
8226                  || strcmp (insn->name, "ldl") == 0
8227                  || strcmp (insn->name, "ldr") == 0
8228                  || strcmp (insn->name, "sdl") == 0
8229                  || strcmp (insn->name, "sdr") == 0
8230                  || strcmp (insn->name, "swr") == 0
8231                  || strcmp (insn->name, "swl") == 0))
8232            {
8233              static char buf[100];
8234              sprintf (buf, _("Unaligned load/store instructions are not allowed with -mocteon-useun"));
8235              insn_error = buf;
8236              return;
8237            }
8238	}
8239
8240      /* Octeon has its own version of dmtc2/dmfc2 instructions, error on
8241	 other formats.  */
8242      if (mips_opts.arch == CPU_OCTEON
8243	  && (strcmp (insn->name, "dmtc2") == 0
8244	      || strcmp (insn->name, "dmfc2") == 0)
8245	  && (insn->membership & INSN_OCTEON) != INSN_OCTEON)
8246	{
8247	  static char buf[100];
8248	  sprintf (buf,
8249		   _("opcode not supported in %s"),
8250		     mips_cpu_info_from_arch (mips_opts.arch)->name);
8251	  insn_error = buf;
8252	  ok = FALSE;
8253	}
8254
8255      if (! ok)
8256	{
8257	  if (insn + 1 < &mips_opcodes[NUMOPCODES]
8258	      && strcmp (insn->name, insn[1].name) == 0)
8259	    {
8260	      ++insn;
8261	      continue;
8262	    }
8263	  else
8264	    {
8265	      if (!insn_error)
8266		{
8267		  static char buf[100];
8268		  sprintf (buf,
8269			   _("opcode not supported on this processor: %s (%s)"),
8270			   mips_cpu_info_from_arch (mips_opts.arch)->name,
8271			   mips_cpu_info_from_isa (mips_opts.isa)->name);
8272		  insn_error = buf;
8273		}
8274	      if (save_c)
8275		*(--s) = save_c;
8276	      return;
8277	    }
8278	}
8279
8280      create_insn (ip, insn);
8281      insn_error = NULL;
8282      for (args = insn->args;; ++args)
8283	{
8284	  int is_mdmx;
8285
8286	  s += strspn (s, " \t");
8287	  is_mdmx = 0;
8288	  switch (*args)
8289	    {
8290	    case '\0':		/* end of args */
8291	      if (*s == '\0')
8292		return;
8293	      break;
8294
8295	    case '3': /* dsp 3-bit unsigned immediate in bit 21 */
8296	      my_getExpression (&imm_expr, s);
8297	      check_absolute_expr (ip, &imm_expr);
8298	      if (imm_expr.X_add_number & ~OP_MASK_SA3)
8299		{
8300		  as_warn (_("DSP immediate not in range 0..%d (%lu)"),
8301			   OP_MASK_SA3, (unsigned long) imm_expr.X_add_number);
8302		  imm_expr.X_add_number &= OP_MASK_SA3;
8303		}
8304	      ip->insn_opcode |= imm_expr.X_add_number << OP_SH_SA3;
8305	      imm_expr.X_op = O_absent;
8306	      s = expr_end;
8307	      continue;
8308
8309	    case '4': /* dsp 4-bit unsigned immediate in bit 21 */
8310	      my_getExpression (&imm_expr, s);
8311	      check_absolute_expr (ip, &imm_expr);
8312	      if (imm_expr.X_add_number & ~OP_MASK_SA4)
8313		{
8314		  as_warn (_("DSP immediate not in range 0..%d (%lu)"),
8315			   OP_MASK_SA4, (unsigned long) imm_expr.X_add_number);
8316		  imm_expr.X_add_number &= OP_MASK_SA4;
8317		}
8318	      ip->insn_opcode |= imm_expr.X_add_number << OP_SH_SA4;
8319	      imm_expr.X_op = O_absent;
8320	      s = expr_end;
8321	      continue;
8322
8323	    case '5': /* dsp 8-bit unsigned immediate in bit 16 */
8324	      my_getExpression (&imm_expr, s);
8325	      check_absolute_expr (ip, &imm_expr);
8326	      if (imm_expr.X_add_number & ~OP_MASK_IMM8)
8327		{
8328		  as_warn (_("DSP immediate not in range 0..%d (%lu)"),
8329			   OP_MASK_IMM8, (unsigned long) imm_expr.X_add_number);
8330		  imm_expr.X_add_number &= OP_MASK_IMM8;
8331		}
8332	      ip->insn_opcode |= imm_expr.X_add_number << OP_SH_IMM8;
8333	      imm_expr.X_op = O_absent;
8334	      s = expr_end;
8335	      continue;
8336
8337	    case '6': /* dsp 5-bit unsigned immediate in bit 21 */
8338	      my_getExpression (&imm_expr, s);
8339	      check_absolute_expr (ip, &imm_expr);
8340	      if (imm_expr.X_add_number & ~OP_MASK_RS)
8341		{
8342		  as_warn (_("DSP immediate not in range 0..%d (%lu)"),
8343			   OP_MASK_RS, (unsigned long) imm_expr.X_add_number);
8344		  imm_expr.X_add_number &= OP_MASK_RS;
8345		}
8346	      ip->insn_opcode |= imm_expr.X_add_number << OP_SH_RS;
8347	      imm_expr.X_op = O_absent;
8348	      s = expr_end;
8349	      continue;
8350
8351	    case '7': /* four dsp accumulators in bits 11,12 */
8352	      if (s[0] == '$' && s[1] == 'a' && s[2] == 'c' &&
8353		  s[3] >= '0' && s[3] <= '3')
8354		{
8355		  regno = s[3] - '0';
8356		  s += 4;
8357		  ip->insn_opcode |= regno << OP_SH_DSPACC;
8358		  continue;
8359		}
8360	      else
8361		as_bad (_("Invalid dsp acc register"));
8362	      break;
8363
8364	    case '8': /* dsp 6-bit unsigned immediate in bit 11 */
8365	      my_getExpression (&imm_expr, s);
8366	      check_absolute_expr (ip, &imm_expr);
8367	      if (imm_expr.X_add_number & ~OP_MASK_WRDSP)
8368		{
8369		  as_warn (_("DSP immediate not in range 0..%d (%lu)"),
8370			   OP_MASK_WRDSP,
8371			   (unsigned long) imm_expr.X_add_number);
8372		  imm_expr.X_add_number &= OP_MASK_WRDSP;
8373		}
8374	      ip->insn_opcode |= imm_expr.X_add_number << OP_SH_WRDSP;
8375	      imm_expr.X_op = O_absent;
8376	      s = expr_end;
8377	      continue;
8378
8379	    case '9': /* four dsp accumulators in bits 21,22 */
8380	      if (s[0] == '$' && s[1] == 'a' && s[2] == 'c' &&
8381		  s[3] >= '0' && s[3] <= '3')
8382		{
8383		  regno = s[3] - '0';
8384		  s += 4;
8385		  ip->insn_opcode |= regno << OP_SH_DSPACC_S;
8386		  continue;
8387		}
8388	      else
8389		as_bad (_("Invalid dsp acc register"));
8390	      break;
8391
8392	    case '0': /* dsp 6-bit signed immediate in bit 20 */
8393	      my_getExpression (&imm_expr, s);
8394	      check_absolute_expr (ip, &imm_expr);
8395	      min_range = -((OP_MASK_DSPSFT + 1) >> 1);
8396	      max_range = ((OP_MASK_DSPSFT + 1) >> 1) - 1;
8397	      if (imm_expr.X_add_number < min_range ||
8398		  imm_expr.X_add_number > max_range)
8399		{
8400		  as_warn (_("DSP immediate not in range %ld..%ld (%ld)"),
8401			   (long) min_range, (long) max_range,
8402			   (long) imm_expr.X_add_number);
8403		}
8404	      imm_expr.X_add_number &= OP_MASK_DSPSFT;
8405	      ip->insn_opcode |= ((unsigned long) imm_expr.X_add_number
8406				  << OP_SH_DSPSFT);
8407	      imm_expr.X_op = O_absent;
8408	      s = expr_end;
8409	      continue;
8410
8411	    case '\'': /* dsp 6-bit unsigned immediate in bit 16 */
8412	      my_getExpression (&imm_expr, s);
8413	      check_absolute_expr (ip, &imm_expr);
8414	      if (imm_expr.X_add_number & ~OP_MASK_RDDSP)
8415		{
8416		  as_warn (_("DSP immediate not in range 0..%d (%lu)"),
8417			   OP_MASK_RDDSP,
8418			   (unsigned long) imm_expr.X_add_number);
8419		  imm_expr.X_add_number &= OP_MASK_RDDSP;
8420		}
8421	      ip->insn_opcode |= imm_expr.X_add_number << OP_SH_RDDSP;
8422	      imm_expr.X_op = O_absent;
8423	      s = expr_end;
8424	      continue;
8425
8426	    case ':': /* dsp 7-bit signed immediate in bit 19 */
8427	      my_getExpression (&imm_expr, s);
8428	      check_absolute_expr (ip, &imm_expr);
8429	      min_range = -((OP_MASK_DSPSFT_7 + 1) >> 1);
8430	      max_range = ((OP_MASK_DSPSFT_7 + 1) >> 1) - 1;
8431	      if (imm_expr.X_add_number < min_range ||
8432		  imm_expr.X_add_number > max_range)
8433		{
8434		  as_warn (_("DSP immediate not in range %ld..%ld (%ld)"),
8435			   (long) min_range, (long) max_range,
8436			   (long) imm_expr.X_add_number);
8437		}
8438	      imm_expr.X_add_number &= OP_MASK_DSPSFT_7;
8439	      ip->insn_opcode |= ((unsigned long) imm_expr.X_add_number
8440				  << OP_SH_DSPSFT_7);
8441	      imm_expr.X_op = O_absent;
8442	      s = expr_end;
8443	      continue;
8444
8445	    case '@': /* dsp 10-bit signed immediate in bit 16 */
8446	      my_getExpression (&imm_expr, s);
8447	      check_absolute_expr (ip, &imm_expr);
8448	      min_range = -((OP_MASK_IMM10 + 1) >> 1);
8449	      max_range = ((OP_MASK_IMM10 + 1) >> 1) - 1;
8450	      if (imm_expr.X_add_number < min_range ||
8451		  imm_expr.X_add_number > max_range)
8452		{
8453		  as_warn (_("DSP immediate not in range %ld..%ld (%ld)"),
8454			   (long) min_range, (long) max_range,
8455			   (long) imm_expr.X_add_number);
8456		}
8457	      imm_expr.X_add_number &= OP_MASK_IMM10;
8458	      ip->insn_opcode |= ((unsigned long) imm_expr.X_add_number
8459				  << OP_SH_IMM10);
8460	      imm_expr.X_op = O_absent;
8461	      s = expr_end;
8462	      continue;
8463
8464            case '!': /* mt 1-bit unsigned immediate in bit 5 */
8465	      my_getExpression (&imm_expr, s);
8466	      check_absolute_expr (ip, &imm_expr);
8467	      if (imm_expr.X_add_number & ~OP_MASK_MT_U)
8468		{
8469		  as_warn (_("MT immediate not in range 0..%d (%lu)"),
8470			   OP_MASK_MT_U, (unsigned long) imm_expr.X_add_number);
8471		  imm_expr.X_add_number &= OP_MASK_MT_U;
8472		}
8473	      ip->insn_opcode |= imm_expr.X_add_number << OP_SH_MT_U;
8474	      imm_expr.X_op = O_absent;
8475	      s = expr_end;
8476	      continue;
8477
8478            case '$': /* mt 1-bit unsigned immediate in bit 4 */
8479	      my_getExpression (&imm_expr, s);
8480	      check_absolute_expr (ip, &imm_expr);
8481	      if (imm_expr.X_add_number & ~OP_MASK_MT_H)
8482		{
8483		  as_warn (_("MT immediate not in range 0..%d (%lu)"),
8484			   OP_MASK_MT_H, (unsigned long) imm_expr.X_add_number);
8485		  imm_expr.X_add_number &= OP_MASK_MT_H;
8486		}
8487	      ip->insn_opcode |= imm_expr.X_add_number << OP_SH_MT_H;
8488	      imm_expr.X_op = O_absent;
8489	      s = expr_end;
8490	      continue;
8491
8492	    case '*': /* four dsp accumulators in bits 18,19 */
8493	      if (s[0] == '$' && s[1] == 'a' && s[2] == 'c' &&
8494		  s[3] >= '0' && s[3] <= '3')
8495		{
8496		  regno = s[3] - '0';
8497		  s += 4;
8498		  ip->insn_opcode |= regno << OP_SH_MTACC_T;
8499		  continue;
8500		}
8501	      else
8502		as_bad (_("Invalid dsp/smartmips acc register"));
8503	      break;
8504
8505	    case '&': /* four dsp accumulators in bits 13,14 */
8506	      if (s[0] == '$' && s[1] == 'a' && s[2] == 'c' &&
8507		  s[3] >= '0' && s[3] <= '3')
8508		{
8509		  regno = s[3] - '0';
8510		  s += 4;
8511		  ip->insn_opcode |= regno << OP_SH_MTACC_D;
8512		  continue;
8513		}
8514	      else
8515		as_bad (_("Invalid dsp/smartmips acc register"));
8516	      break;
8517
8518	    case ',':
8519	      if (*s++ == *args)
8520		continue;
8521	      s--;
8522	      switch (*++args)
8523		{
8524		case 'r':
8525		case 'v':
8526		  INSERT_OPERAND (RS, *ip, lastregno);
8527		  continue;
8528
8529		case 'w':
8530		  INSERT_OPERAND (RT, *ip, lastregno);
8531		  continue;
8532
8533		case 'W':
8534		  INSERT_OPERAND (FT, *ip, lastregno);
8535		  continue;
8536
8537		case 'V':
8538		  INSERT_OPERAND (FS, *ip, lastregno);
8539		  continue;
8540		}
8541	      break;
8542
8543	    case '(':
8544	      /* Handle optional base register.
8545		 Either the base register is omitted or
8546		 we must have a left paren.  */
8547	      /* This is dependent on the next operand specifier
8548		 is a base register specification.  */
8549	      assert (args[1] == 'b' || args[1] == '5'
8550		      || args[1] == '-' || args[1] == '4');
8551	      if (*s == '\0')
8552		return;
8553
8554	    case ')':		/* these must match exactly */
8555	    case '[':
8556	    case ']':
8557	      if (*s++ == *args)
8558		continue;
8559	      break;
8560
8561	    case '+':		/* Opcode extension character.  */
8562	      switch (*++args)
8563		{
8564		case 'A':		/* ins/ext position, becomes LSB.  */
8565		  limlo = 0;
8566		  limhi = 31;
8567		  goto do_lsb;
8568		case 'E':
8569		  limlo = 32;
8570		  limhi = 63;
8571		  goto do_lsb;
8572do_lsb:
8573		  my_getExpression (&imm_expr, s);
8574		  check_absolute_expr (ip, &imm_expr);
8575		  if ((unsigned long) imm_expr.X_add_number < limlo
8576		      || (unsigned long) imm_expr.X_add_number > limhi)
8577		    {
8578		      as_bad (_("Improper position (%lu)"),
8579			      (unsigned long) imm_expr.X_add_number);
8580		      imm_expr.X_add_number = limlo;
8581		    }
8582		  lastpos = imm_expr.X_add_number;
8583		  INSERT_OPERAND (SHAMT, *ip, imm_expr.X_add_number);
8584		  imm_expr.X_op = O_absent;
8585		  s = expr_end;
8586		  continue;
8587
8588		case 'B':		/* ins size, becomes MSB.  */
8589		  limlo = 1;
8590		  limhi = 32;
8591		  goto do_msb;
8592		case 'F':
8593		  limlo = 33;
8594		  limhi = 64;
8595		  goto do_msb;
8596do_msb:
8597		  my_getExpression (&imm_expr, s);
8598		  check_absolute_expr (ip, &imm_expr);
8599		  /* Check for negative input so that small negative numbers
8600		     will not succeed incorrectly.  The checks against
8601		     (pos+size) transitively check "size" itself,
8602		     assuming that "pos" is reasonable.  */
8603		  if ((long) imm_expr.X_add_number < 0
8604		      || ((unsigned long) imm_expr.X_add_number
8605			  + lastpos) < limlo
8606		      || ((unsigned long) imm_expr.X_add_number
8607			  + lastpos) > limhi)
8608		    {
8609		      as_bad (_("Improper insert size (%lu, position %lu)"),
8610			      (unsigned long) imm_expr.X_add_number,
8611			      (unsigned long) lastpos);
8612		      imm_expr.X_add_number = limlo - lastpos;
8613		    }
8614		  INSERT_OPERAND (INSMSB, *ip,
8615				 lastpos + imm_expr.X_add_number - 1);
8616		  imm_expr.X_op = O_absent;
8617		  s = expr_end;
8618		  continue;
8619
8620		case 'C':		/* ext size, becomes MSBD.  */
8621		  limlo = 1;
8622		  limhi = 32;
8623		  goto do_msbd;
8624		case 'G':
8625		  limlo = 33;
8626		  limhi = 64;
8627		  goto do_msbd;
8628		case 'H':
8629		  limlo = 33;
8630		  limhi = 64;
8631		  goto do_msbd;
8632do_msbd:
8633		  my_getExpression (&imm_expr, s);
8634		  check_absolute_expr (ip, &imm_expr);
8635		  /* Check for negative input so that small negative numbers
8636		     will not succeed incorrectly.  The checks against
8637		     (pos+size) transitively check "size" itself,
8638		     assuming that "pos" is reasonable.  */
8639		  if ((long) imm_expr.X_add_number < 0
8640		      || ((unsigned long) imm_expr.X_add_number
8641			  + lastpos) < limlo
8642		      || ((unsigned long) imm_expr.X_add_number
8643			  + lastpos) > limhi)
8644		    {
8645		      as_bad (_("Improper extract size (%lu, position %lu)"),
8646			      (unsigned long) imm_expr.X_add_number,
8647			      (unsigned long) lastpos);
8648		      imm_expr.X_add_number = limlo - lastpos;
8649		    }
8650		  INSERT_OPERAND (EXTMSBD, *ip, imm_expr.X_add_number - 1);
8651		  imm_expr.X_op = O_absent;
8652		  s = expr_end;
8653		  continue;
8654
8655		case 'D':
8656		  /* +D is for disassembly only; never match.  */
8657		  break;
8658
8659		case 'I':
8660		  /* "+I" is like "I", except that imm2_expr is used.  */
8661		  my_getExpression (&imm2_expr, s);
8662		  if (imm2_expr.X_op != O_big
8663		      && imm2_expr.X_op != O_constant)
8664		  insn_error = _("absolute expression required");
8665		  if (HAVE_32BIT_GPRS)
8666		    normalize_constant_expr (&imm2_expr);
8667		  s = expr_end;
8668		  continue;
8669
8670		case 'T': /* Coprocessor register */
8671		  /* +T is for disassembly only; never match.  */
8672		  break;
8673
8674		case 't': /* Coprocessor register number */
8675		  if (s[0] == '$' && ISDIGIT (s[1]))
8676		    {
8677		      ++s;
8678		      regno = 0;
8679		      do
8680		        {
8681			  regno *= 10;
8682			  regno += *s - '0';
8683			  ++s;
8684			}
8685		      while (ISDIGIT (*s));
8686		      if (regno > 31)
8687			as_bad (_("Invalid register number (%d)"), regno);
8688		      else
8689			{
8690			  ip->insn_opcode |= regno << OP_SH_RT;
8691			  continue;
8692			}
8693		    }
8694		  else
8695		    as_bad (_("Invalid coprocessor 0 register number"));
8696		  break;
8697
8698		default:
8699		  as_bad (_("internal: bad mips opcode (unknown extension operand type `+%c'): %s %s"),
8700		    *args, insn->name, insn->args);
8701		  /* Further processing is fruitless.  */
8702		  return;
8703		}
8704	      break;
8705
8706	    case '<':		/* must be at least one digit */
8707	      /*
8708	       * According to the manual, if the shift amount is greater
8709	       * than 31 or less than 0, then the shift amount should be
8710	       * mod 32.  In reality the mips assembler issues an error.
8711	       * We issue a warning and mask out all but the low 5 bits.
8712	       */
8713	      my_getExpression (&imm_expr, s);
8714	      check_absolute_expr (ip, &imm_expr);
8715	      if ((unsigned long) imm_expr.X_add_number > 31)
8716		as_warn (_("Improper shift amount (%lu)"),
8717			 (unsigned long) imm_expr.X_add_number);
8718	      INSERT_OPERAND (SHAMT, *ip, imm_expr.X_add_number);
8719	      imm_expr.X_op = O_absent;
8720	      s = expr_end;
8721	      continue;
8722
8723	    case '>':		/* shift amount minus 32 */
8724	      my_getExpression (&imm_expr, s);
8725	      check_absolute_expr (ip, &imm_expr);
8726	      if ((unsigned long) imm_expr.X_add_number < 32
8727		  || (unsigned long) imm_expr.X_add_number > 63)
8728		break;
8729	      INSERT_OPERAND (SHAMT, *ip, imm_expr.X_add_number - 32);
8730	      imm_expr.X_op = O_absent;
8731	      s = expr_end;
8732	      continue;
8733
8734             case '^':           /* must be at least one digit */
8735	      /* Decode 5-bits of bbit0/1's bit index amount. If the value is
8736		 greater than 31, issue a warning and mask out all but the low
8737		 5 bits.  */
8738	      my_getExpression (&imm_expr, s);
8739	      check_absolute_expr (ip, &imm_expr);
8740	      if ((unsigned long) imm_expr.X_add_number > 31)
8741		{
8742		  as_warn (_("Improper bit index amount (%lu)"),
8743			   (unsigned long) imm_expr.X_add_number);
8744		  imm_expr.X_add_number &= OP_MASK_BITIND;
8745		}
8746	      ip->insn_opcode |= imm_expr.X_add_number << OP_SH_BITIND;
8747	      imm_expr.X_op = O_absent;
8748	      s = expr_end;
8749	      continue;
8750
8751            case '~':           /* bit index minus 32 */
8752	      my_getExpression (&imm_expr, s);
8753	      check_absolute_expr (ip, &imm_expr);
8754	      if ((unsigned long) imm_expr.X_add_number < 32
8755	          || (unsigned long) imm_expr.X_add_number > 63)
8756	        break;
8757	      ip->insn_opcode |= (imm_expr.X_add_number - 32) << OP_SH_BITIND;
8758	      imm_expr.X_op = O_absent;
8759	      s = expr_end;
8760	      continue;
8761
8762	    case 'k':		/* cache code */
8763	    case 'h':		/* prefx code */
8764	      my_getExpression (&imm_expr, s);
8765	      check_absolute_expr (ip, &imm_expr);
8766	      if ((unsigned long) imm_expr.X_add_number > 31)
8767		as_warn (_("Invalid value for `%s' (%lu)"),
8768			 ip->insn_mo->name,
8769			 (unsigned long) imm_expr.X_add_number);
8770	      if (*args == 'k')
8771		INSERT_OPERAND (CACHE, *ip, imm_expr.X_add_number);
8772	      else
8773		INSERT_OPERAND (PREFX, *ip, imm_expr.X_add_number);
8774	      imm_expr.X_op = O_absent;
8775	      s = expr_end;
8776	      continue;
8777
8778	    case 'c':		/* break code */
8779	      my_getExpression (&imm_expr, s);
8780	      check_absolute_expr (ip, &imm_expr);
8781	      if ((unsigned long) imm_expr.X_add_number > 1023)
8782		as_warn (_("Illegal break code (%lu)"),
8783			 (unsigned long) imm_expr.X_add_number);
8784	      INSERT_OPERAND (CODE, *ip, imm_expr.X_add_number);
8785	      imm_expr.X_op = O_absent;
8786	      s = expr_end;
8787	      continue;
8788
8789	    case 'q':		/* lower break code */
8790	      my_getExpression (&imm_expr, s);
8791	      check_absolute_expr (ip, &imm_expr);
8792	      if ((unsigned long) imm_expr.X_add_number > 1023)
8793		as_warn (_("Illegal lower break code (%lu)"),
8794			 (unsigned long) imm_expr.X_add_number);
8795	      INSERT_OPERAND (CODE2, *ip, imm_expr.X_add_number);
8796	      imm_expr.X_op = O_absent;
8797	      s = expr_end;
8798	      continue;
8799
8800	    case 'y':
8801	      /* Decode 10-bits of seqi/snei's signed constant offset. Issue
8802		 a warning message if the value is not within the range.  */
8803	      my_getExpression (&imm_expr, s);
8804	      check_absolute_expr (ip, &imm_expr);
8805	      if (((unsigned long) imm_expr.X_add_number + 0x200) > 1023)
8806		{
8807		  as_warn (_("Illegal 10-bit signed constant (%lu)"),
8808			   (unsigned long) imm_expr.X_add_number);
8809		 	   imm_expr.X_add_number &= OP_MASK_CODE2;
8810		}
8811	      ip->insn_opcode |= (imm_expr.X_add_number & OP_MASK_CODE2)
8812				  << OP_SH_CODE2;
8813	      imm_expr.X_op = O_absent;
8814	      s = expr_end;
8815	      continue;
8816
8817	    case 'B':           /* 20-bit syscall/break code.  */
8818	      my_getExpression (&imm_expr, s);
8819	      check_absolute_expr (ip, &imm_expr);
8820	      if ((unsigned long) imm_expr.X_add_number > OP_MASK_CODE20)
8821		as_warn (_("Illegal 20-bit code (%lu)"),
8822			 (unsigned long) imm_expr.X_add_number);
8823	      INSERT_OPERAND (CODE20, *ip, imm_expr.X_add_number);
8824	      imm_expr.X_op = O_absent;
8825	      s = expr_end;
8826	      continue;
8827
8828	    case 'C':           /* Coprocessor code */
8829	      my_getExpression (&imm_expr, s);
8830	      check_absolute_expr (ip, &imm_expr);
8831	      if ((unsigned long) imm_expr.X_add_number >= (1 << 25))
8832		{
8833		  as_warn (_("Coproccesor code > 25 bits (%lu)"),
8834			   (unsigned long) imm_expr.X_add_number);
8835		  imm_expr.X_add_number &= ((1 << 25) - 1);
8836		}
8837	      ip->insn_opcode |= imm_expr.X_add_number;
8838	      imm_expr.X_op = O_absent;
8839	      s = expr_end;
8840	      continue;
8841
8842	    case 'J':           /* 19-bit wait code.  */
8843	      my_getExpression (&imm_expr, s);
8844	      check_absolute_expr (ip, &imm_expr);
8845	      if ((unsigned long) imm_expr.X_add_number > OP_MASK_CODE19)
8846		as_warn (_("Illegal 19-bit code (%lu)"),
8847			 (unsigned long) imm_expr.X_add_number);
8848	      INSERT_OPERAND (CODE19, *ip, imm_expr.X_add_number);
8849	      imm_expr.X_op = O_absent;
8850	      s = expr_end;
8851	      continue;
8852
8853	    case 'P':		/* Performance register */
8854	      my_getExpression (&imm_expr, s);
8855	      check_absolute_expr (ip, &imm_expr);
8856	      if (imm_expr.X_add_number != 0 && imm_expr.X_add_number != 1)
8857		as_warn (_("Invalid performance register (%lu)"),
8858			 (unsigned long) imm_expr.X_add_number);
8859	      INSERT_OPERAND (PERFREG, *ip, imm_expr.X_add_number);
8860	      imm_expr.X_op = O_absent;
8861	      s = expr_end;
8862	      continue;
8863
8864	    case 'b':		/* base register */
8865	    case 'd':		/* destination register */
8866	    case 's':		/* source register */
8867	    case 't':		/* target register */
8868	    case 'r':		/* both target and source */
8869	    case 'v':		/* both dest and source */
8870	    case 'w':		/* both dest and target */
8871	    case 'E':		/* coprocessor target register */
8872	    case 'G':		/* coprocessor destination register */
8873	    case 'K':		/* 'rdhwr' destination register */
8874	    case 'x':		/* ignore register name */
8875	    case 'z':		/* must be zero register */
8876	    case 'U':           /* destination register (clo/clz).  */
8877	    case 'g':		/* coprocessor destination register */
8878	      s_reset = s;
8879	      if (s[0] == '$')
8880		{
8881		  if (ISDIGIT (s[1]))
8882		    {
8883		      ++s;
8884		      regno = 0;
8885		      do
8886			{
8887			  regno *= 10;
8888			  regno += *s - '0';
8889			  ++s;
8890			}
8891		      while (ISDIGIT (*s));
8892		      if (regno > 31)
8893			as_bad (_("Invalid register number (%d)"), regno);
8894		    }
8895		  else if (*args == 'E' || *args == 'G' || *args == 'K')
8896		    goto notreg;
8897		  else
8898		    {
8899		      if (s[1] == 'r' && s[2] == 'a')
8900			{
8901			  s += 3;
8902			  regno = RA;
8903			}
8904		      else if (s[1] == 'f' && s[2] == 'p')
8905			{
8906			  s += 3;
8907			  regno = FP;
8908			}
8909		      else if (s[1] == 's' && s[2] == 'p')
8910			{
8911			  s += 3;
8912			  regno = SP;
8913			}
8914		      else if (s[1] == 'g' && s[2] == 'p')
8915			{
8916			  s += 3;
8917			  regno = GP;
8918			}
8919		      else if (s[1] == 'a' && s[2] == 't')
8920			{
8921			  s += 3;
8922			  regno = AT;
8923			}
8924		      else if (s[1] == 'k' && s[2] == 't' && s[3] == '0')
8925			{
8926			  s += 4;
8927			  regno = KT0;
8928			}
8929		      else if (s[1] == 'k' && s[2] == 't' && s[3] == '1')
8930			{
8931			  s += 4;
8932			  regno = KT1;
8933			}
8934		      else if (s[1] == 'z' && s[2] == 'e' && s[3] == 'r' && s[4] == 'o')
8935			{
8936			  s += 5;
8937			  regno = ZERO;
8938			}
8939		      else if (itbl_have_entries)
8940			{
8941			  char *p, *n;
8942			  unsigned long r;
8943
8944			  p = s + 1; 	/* advance past '$' */
8945			  n = itbl_get_field (&p);  /* n is name */
8946
8947			  /* See if this is a register defined in an
8948			     itbl entry.  */
8949			  if (itbl_get_reg_val (n, &r))
8950			    {
8951			      /* Get_field advances to the start of
8952				 the next field, so we need to back
8953				 rack to the end of the last field.  */
8954			      if (p)
8955				s = p - 1;
8956			      else
8957				s = strchr (s, '\0');
8958			      regno = r;
8959			    }
8960			  else
8961			    goto notreg;
8962			}
8963		      else
8964			goto notreg;
8965		    }
8966		  if (regno == AT
8967		      && ! mips_opts.noat
8968		      && *args != 'E'
8969		      && *args != 'G'
8970		      && *args != 'K')
8971		    as_warn (_("Used $at without \".set noat\""));
8972		  c = *args;
8973		  if (*s == ' ')
8974		    ++s;
8975		  if (args[1] != *s)
8976		    {
8977		      if (c == 'r' || c == 'v' || c == 'w')
8978			{
8979			  regno = lastregno;
8980			  s = s_reset;
8981			  ++args;
8982			}
8983		    }
8984		  /* 'z' only matches $0.  */
8985		  if (c == 'z' && regno != 0)
8986		    break;
8987
8988	/* Now that we have assembled one operand, we use the args string
8989	 * to figure out where it goes in the instruction.  */
8990		  switch (c)
8991		    {
8992		    case 'r':
8993		    case 's':
8994		    case 'v':
8995		    case 'b':
8996		      INSERT_OPERAND (RS, *ip, regno);
8997		      break;
8998		    case 'd':
8999		    case 'G':
9000		    case 'K':
9001		    case 'g':
9002		      INSERT_OPERAND (RD, *ip, regno);
9003		      break;
9004		    case 'U':
9005		      INSERT_OPERAND (RD, *ip, regno);
9006		      INSERT_OPERAND (RT, *ip, regno);
9007		      break;
9008		    case 'w':
9009		    case 't':
9010		    case 'E':
9011		      INSERT_OPERAND (RT, *ip, regno);
9012		      break;
9013		    case 'x':
9014		      /* This case exists because on the r3000 trunc
9015			 expands into a macro which requires a gp
9016			 register.  On the r6000 or r4000 it is
9017			 assembled into a single instruction which
9018			 ignores the register.  Thus the insn version
9019			 is MIPS_ISA2 and uses 'x', and the macro
9020			 version is MIPS_ISA1 and uses 't'.  */
9021		      break;
9022		    case 'z':
9023		      /* This case is for the div instruction, which
9024			 acts differently if the destination argument
9025			 is $0.  This only matches $0, and is checked
9026			 outside the switch.  */
9027		      break;
9028		    case 'D':
9029		      /* Itbl operand; not yet implemented. FIXME ?? */
9030		      break;
9031		      /* What about all other operands like 'i', which
9032			 can be specified in the opcode table? */
9033		    }
9034		  lastregno = regno;
9035		  continue;
9036		}
9037	    notreg:
9038	      switch (*args++)
9039		{
9040		case 'r':
9041		case 'v':
9042		  INSERT_OPERAND (RS, *ip, lastregno);
9043		  continue;
9044		case 'w':
9045		  INSERT_OPERAND (RT, *ip, lastregno);
9046		  continue;
9047		}
9048	      break;
9049
9050	    case 'O':		/* MDMX alignment immediate constant.  */
9051	      my_getExpression (&imm_expr, s);
9052	      check_absolute_expr (ip, &imm_expr);
9053	      if ((unsigned long) imm_expr.X_add_number > OP_MASK_ALN)
9054		as_warn ("Improper align amount (%ld), using low bits",
9055			 (long) imm_expr.X_add_number);
9056	      INSERT_OPERAND (ALN, *ip, imm_expr.X_add_number);
9057	      imm_expr.X_op = O_absent;
9058	      s = expr_end;
9059	      continue;
9060
9061	    case 'Q':		/* MDMX vector, element sel, or const.  */
9062	      if (s[0] != '$')
9063		{
9064		  /* MDMX Immediate.  */
9065		  my_getExpression (&imm_expr, s);
9066		  check_absolute_expr (ip, &imm_expr);
9067		  if ((unsigned long) imm_expr.X_add_number > OP_MASK_FT)
9068		    as_warn (_("Invalid MDMX Immediate (%ld)"),
9069			     (long) imm_expr.X_add_number);
9070		  INSERT_OPERAND (FT, *ip, imm_expr.X_add_number);
9071		  if (ip->insn_opcode & (OP_MASK_VSEL << OP_SH_VSEL))
9072		    ip->insn_opcode |= MDMX_FMTSEL_IMM_QH << OP_SH_VSEL;
9073		  else
9074		    ip->insn_opcode |= MDMX_FMTSEL_IMM_OB << OP_SH_VSEL;
9075		  imm_expr.X_op = O_absent;
9076		  s = expr_end;
9077		  continue;
9078		}
9079	      /* Not MDMX Immediate.  Fall through.  */
9080	    case 'X':           /* MDMX destination register.  */
9081	    case 'Y':           /* MDMX source register.  */
9082	    case 'Z':           /* MDMX target register.  */
9083	      is_mdmx = 1;
9084	    case 'D':		/* floating point destination register */
9085	    case 'S':		/* floating point source register */
9086	    case 'T':		/* floating point target register */
9087	    case 'R':		/* floating point source register */
9088	    case 'V':
9089	    case 'W':
9090	      s_reset = s;
9091             if (mips_opts.arch == CPU_OCTEON && octeon_error_on_unsupported)
9092               {
9093	         insn_error = "opcode not implemented in Octeon";
9094                 return;
9095               }
9096	      /* Accept $fN for FP and MDMX register numbers, and in
9097                 addition accept $vN for MDMX register numbers.  */
9098	      if ((s[0] == '$' && s[1] == 'f' && ISDIGIT (s[2]))
9099		  || (is_mdmx != 0 && s[0] == '$' && s[1] == 'v'
9100		      && ISDIGIT (s[2])))
9101		{
9102		  s += 2;
9103		  regno = 0;
9104		  do
9105		    {
9106		      regno *= 10;
9107		      regno += *s - '0';
9108		      ++s;
9109		    }
9110		  while (ISDIGIT (*s));
9111
9112		  if (regno > 31)
9113		    as_bad (_("Invalid float register number (%d)"), regno);
9114
9115		  if ((regno & 1) != 0
9116		      && HAVE_32BIT_FPRS
9117		      && ! (strcmp (str, "mtc1") == 0
9118			    || strcmp (str, "mfc1") == 0
9119			    || strcmp (str, "lwc1") == 0
9120			    || strcmp (str, "swc1") == 0
9121			    || strcmp (str, "l.s") == 0
9122			    || strcmp (str, "s.s") == 0
9123			    || strcmp (str, "mftc1") == 0
9124			    || strcmp (str, "mfthc1") == 0
9125			    || strcmp (str, "cftc1") == 0
9126			    || strcmp (str, "mttc1") == 0
9127			    || strcmp (str, "mtthc1") == 0
9128			    || strcmp (str, "cttc1") == 0))
9129		    as_warn (_("Float register should be even, was %d"),
9130			     regno);
9131
9132		  c = *args;
9133		  if (*s == ' ')
9134		    ++s;
9135		  if (args[1] != *s)
9136		    {
9137		      if (c == 'V' || c == 'W')
9138			{
9139			  regno = lastregno;
9140			  s = s_reset;
9141			  ++args;
9142			}
9143		    }
9144		  switch (c)
9145		    {
9146		    case 'D':
9147		    case 'X':
9148		      INSERT_OPERAND (FD, *ip, regno);
9149		      break;
9150		    case 'V':
9151		    case 'S':
9152		    case 'Y':
9153		      INSERT_OPERAND (FS, *ip, regno);
9154		      break;
9155		    case 'Q':
9156		      /* This is like 'Z', but also needs to fix the MDMX
9157			 vector/scalar select bits.  Note that the
9158			 scalar immediate case is handled above.  */
9159		      if (*s == '[')
9160			{
9161			  int is_qh = (ip->insn_opcode & (1 << OP_SH_VSEL));
9162			  int max_el = (is_qh ? 3 : 7);
9163			  s++;
9164			  my_getExpression(&imm_expr, s);
9165			  check_absolute_expr (ip, &imm_expr);
9166			  s = expr_end;
9167			  if (imm_expr.X_add_number > max_el)
9168			    as_bad(_("Bad element selector %ld"),
9169				   (long) imm_expr.X_add_number);
9170			  imm_expr.X_add_number &= max_el;
9171			  ip->insn_opcode |= (imm_expr.X_add_number
9172					      << (OP_SH_VSEL +
9173						  (is_qh ? 2 : 1)));
9174			  imm_expr.X_op = O_absent;
9175			  if (*s != ']')
9176			    as_warn(_("Expecting ']' found '%s'"), s);
9177			  else
9178			    s++;
9179			}
9180		      else
9181                        {
9182                          if (ip->insn_opcode & (OP_MASK_VSEL << OP_SH_VSEL))
9183                            ip->insn_opcode |= (MDMX_FMTSEL_VEC_QH
9184						<< OP_SH_VSEL);
9185			  else
9186			    ip->insn_opcode |= (MDMX_FMTSEL_VEC_OB <<
9187						OP_SH_VSEL);
9188			}
9189                      /* Fall through */
9190		    case 'W':
9191		    case 'T':
9192		    case 'Z':
9193		      INSERT_OPERAND (FT, *ip, regno);
9194		      break;
9195		    case 'R':
9196		      INSERT_OPERAND (FR, *ip, regno);
9197		      break;
9198		    }
9199		  lastregno = regno;
9200		  continue;
9201		}
9202
9203	      switch (*args++)
9204		{
9205		case 'V':
9206		  INSERT_OPERAND (FS, *ip, lastregno);
9207		  continue;
9208		case 'W':
9209		  INSERT_OPERAND (FT, *ip, lastregno);
9210		  continue;
9211		}
9212	      break;
9213
9214	    case 'I':
9215	      my_getExpression (&imm_expr, s);
9216	      if (imm_expr.X_op != O_big
9217		  && imm_expr.X_op != O_constant)
9218		insn_error = _("absolute expression required");
9219	      if (HAVE_32BIT_GPRS)
9220		normalize_constant_expr (&imm_expr);
9221	      s = expr_end;
9222	      continue;
9223
9224	    case 'A':
9225	      my_getExpression (&offset_expr, s);
9226	      normalize_address_expr (&offset_expr);
9227	      *imm_reloc = BFD_RELOC_32;
9228	      s = expr_end;
9229	      continue;
9230
9231	    case 'F':
9232	    case 'L':
9233	    case 'f':
9234	    case 'l':
9235	      {
9236		int f64;
9237		int using_gprs;
9238		char *save_in;
9239		char *err;
9240		unsigned char temp[8];
9241		int len;
9242		unsigned int length;
9243		segT seg;
9244		subsegT subseg;
9245		char *p;
9246
9247		/* These only appear as the last operand in an
9248		   instruction, and every instruction that accepts
9249		   them in any variant accepts them in all variants.
9250		   This means we don't have to worry about backing out
9251		   any changes if the instruction does not match.
9252
9253		   The difference between them is the size of the
9254		   floating point constant and where it goes.  For 'F'
9255		   and 'L' the constant is 64 bits; for 'f' and 'l' it
9256		   is 32 bits.  Where the constant is placed is based
9257		   on how the MIPS assembler does things:
9258		    F -- .rdata
9259		    L -- .lit8
9260		    f -- immediate value
9261		    l -- .lit4
9262
9263		    The .lit4 and .lit8 sections are only used if
9264		    permitted by the -G argument.
9265
9266		    The code below needs to know whether the target register
9267		    is 32 or 64 bits wide.  It relies on the fact 'f' and
9268		    'F' are used with GPR-based instructions and 'l' and
9269		    'L' are used with FPR-based instructions.  */
9270
9271		f64 = *args == 'F' || *args == 'L';
9272		using_gprs = *args == 'F' || *args == 'f';
9273
9274		save_in = input_line_pointer;
9275		input_line_pointer = s;
9276		err = md_atof (f64 ? 'd' : 'f', (char *) temp, &len);
9277		length = len;
9278		s = input_line_pointer;
9279		input_line_pointer = save_in;
9280		if (err != NULL && *err != '\0')
9281		  {
9282		    as_bad (_("Bad floating point constant: %s"), err);
9283		    memset (temp, '\0', sizeof temp);
9284		    length = f64 ? 8 : 4;
9285		  }
9286
9287		assert (length == (unsigned) (f64 ? 8 : 4));
9288
9289		if (*args == 'f'
9290		    || (*args == 'l'
9291			&& (g_switch_value < 4
9292			    || (temp[0] == 0 && temp[1] == 0)
9293			    || (temp[2] == 0 && temp[3] == 0))))
9294		  {
9295		    imm_expr.X_op = O_constant;
9296		    if (! target_big_endian)
9297		      imm_expr.X_add_number = bfd_getl32 (temp);
9298		    else
9299		      imm_expr.X_add_number = bfd_getb32 (temp);
9300		  }
9301		else if (length > 4
9302			 && ! mips_disable_float_construction
9303			 /* Constants can only be constructed in GPRs and
9304			    copied to FPRs if the GPRs are at least as wide
9305			    as the FPRs.  Force the constant into memory if
9306			    we are using 64-bit FPRs but the GPRs are only
9307			    32 bits wide.  */
9308			 && (using_gprs
9309			     || ! (HAVE_64BIT_FPRS && HAVE_32BIT_GPRS))
9310			 && ((temp[0] == 0 && temp[1] == 0)
9311			     || (temp[2] == 0 && temp[3] == 0))
9312			 && ((temp[4] == 0 && temp[5] == 0)
9313			     || (temp[6] == 0 && temp[7] == 0)))
9314		  {
9315		    /* The value is simple enough to load with a couple of
9316                       instructions.  If using 32-bit registers, set
9317                       imm_expr to the high order 32 bits and offset_expr to
9318                       the low order 32 bits.  Otherwise, set imm_expr to
9319                       the entire 64 bit constant.  */
9320		    if (using_gprs ? HAVE_32BIT_GPRS : HAVE_32BIT_FPRS)
9321		      {
9322			imm_expr.X_op = O_constant;
9323			offset_expr.X_op = O_constant;
9324			if (! target_big_endian)
9325			  {
9326			    imm_expr.X_add_number = bfd_getl32 (temp + 4);
9327			    offset_expr.X_add_number = bfd_getl32 (temp);
9328			  }
9329			else
9330			  {
9331			    imm_expr.X_add_number = bfd_getb32 (temp);
9332			    offset_expr.X_add_number = bfd_getb32 (temp + 4);
9333			  }
9334			if (offset_expr.X_add_number == 0)
9335			  offset_expr.X_op = O_absent;
9336		      }
9337		    else if (sizeof (imm_expr.X_add_number) > 4)
9338		      {
9339			imm_expr.X_op = O_constant;
9340			if (! target_big_endian)
9341			  imm_expr.X_add_number = bfd_getl64 (temp);
9342			else
9343			  imm_expr.X_add_number = bfd_getb64 (temp);
9344		      }
9345		    else
9346		      {
9347			imm_expr.X_op = O_big;
9348			imm_expr.X_add_number = 4;
9349			if (! target_big_endian)
9350			  {
9351			    generic_bignum[0] = bfd_getl16 (temp);
9352			    generic_bignum[1] = bfd_getl16 (temp + 2);
9353			    generic_bignum[2] = bfd_getl16 (temp + 4);
9354			    generic_bignum[3] = bfd_getl16 (temp + 6);
9355			  }
9356			else
9357			  {
9358			    generic_bignum[0] = bfd_getb16 (temp + 6);
9359			    generic_bignum[1] = bfd_getb16 (temp + 4);
9360			    generic_bignum[2] = bfd_getb16 (temp + 2);
9361			    generic_bignum[3] = bfd_getb16 (temp);
9362			  }
9363		      }
9364		  }
9365		else
9366		  {
9367		    const char *newname;
9368		    segT new_seg;
9369
9370		    /* Switch to the right section.  */
9371		    seg = now_seg;
9372		    subseg = now_subseg;
9373		    switch (*args)
9374		      {
9375		      default: /* unused default case avoids warnings.  */
9376		      case 'L':
9377			newname = RDATA_SECTION_NAME;
9378			if (g_switch_value >= 8)
9379			  newname = ".lit8";
9380			break;
9381		      case 'F':
9382			newname = RDATA_SECTION_NAME;
9383			break;
9384		      case 'l':
9385			assert (g_switch_value >= 4);
9386			newname = ".lit4";
9387			break;
9388		      }
9389		    new_seg = subseg_new (newname, (subsegT) 0);
9390		    if (OUTPUT_FLAVOR == bfd_target_elf_flavour)
9391		      bfd_set_section_flags (stdoutput, new_seg,
9392					     (SEC_ALLOC
9393					      | SEC_LOAD
9394					      | SEC_READONLY
9395					      | SEC_DATA));
9396		    frag_align (*args == 'l' ? 2 : 3, 0, 0);
9397		    if (OUTPUT_FLAVOR == bfd_target_elf_flavour
9398			&& strcmp (TARGET_OS, "elf") != 0)
9399		      record_alignment (new_seg, 4);
9400		    else
9401		      record_alignment (new_seg, *args == 'l' ? 2 : 3);
9402		    if (seg == now_seg)
9403		      as_bad (_("Can't use floating point insn in this section"));
9404
9405		    /* Set the argument to the current address in the
9406		       section.  */
9407		    offset_expr.X_op = O_symbol;
9408		    offset_expr.X_add_symbol =
9409		      symbol_new ("L0\001", now_seg,
9410				  (valueT) frag_now_fix (), frag_now);
9411		    offset_expr.X_add_number = 0;
9412
9413		    /* Put the floating point number into the section.  */
9414		    p = frag_more ((int) length);
9415		    memcpy (p, temp, length);
9416
9417		    /* Switch back to the original section.  */
9418		    subseg_set (seg, subseg);
9419		  }
9420	      }
9421	      continue;
9422
9423	    case 'i':		/* 16 bit unsigned immediate */
9424	    case 'j':		/* 16 bit signed immediate */
9425	      *imm_reloc = BFD_RELOC_LO16;
9426	      if (my_getSmallExpression (&imm_expr, imm_reloc, s) == 0)
9427		{
9428		  int more;
9429		  offsetT minval, maxval;
9430
9431		  more = (insn + 1 < &mips_opcodes[NUMOPCODES]
9432			  && strcmp (insn->name, insn[1].name) == 0);
9433
9434		  /* If the expression was written as an unsigned number,
9435		     only treat it as signed if there are no more
9436		     alternatives.  */
9437		  if (more
9438		      && *args == 'j'
9439		      && sizeof (imm_expr.X_add_number) <= 4
9440		      && imm_expr.X_op == O_constant
9441		      && imm_expr.X_add_number < 0
9442		      && imm_expr.X_unsigned
9443		      && HAVE_64BIT_GPRS)
9444		    break;
9445
9446		  /* For compatibility with older assemblers, we accept
9447		     0x8000-0xffff as signed 16-bit numbers when only
9448		     signed numbers are allowed.  */
9449		  if (*args == 'i')
9450		    minval = 0, maxval = 0xffff;
9451		  else if (more)
9452		    minval = -0x8000, maxval = 0x7fff;
9453		  else
9454		    minval = -0x8000, maxval = 0xffff;
9455
9456		  if (imm_expr.X_op != O_constant
9457		      || imm_expr.X_add_number < minval
9458		      || imm_expr.X_add_number > maxval)
9459		    {
9460		      if (more)
9461			break;
9462		      if (imm_expr.X_op == O_constant
9463			  || imm_expr.X_op == O_big)
9464			as_bad (_("expression out of range"));
9465		    }
9466		}
9467	      s = expr_end;
9468	      continue;
9469
9470	    case 'o':		/* 16 bit offset */
9471	      /* Check whether there is only a single bracketed expression
9472		 left.  If so, it must be the base register and the
9473		 constant must be zero.  */
9474	      if (*s == '(' && strchr (s + 1, '(') == 0)
9475		{
9476		  offset_expr.X_op = O_constant;
9477		  offset_expr.X_add_number = 0;
9478		  continue;
9479		}
9480
9481	      /* If this value won't fit into a 16 bit offset, then go
9482		 find a macro that will generate the 32 bit offset
9483		 code pattern.  */
9484	      if (my_getSmallExpression (&offset_expr, offset_reloc, s) == 0
9485		  && (offset_expr.X_op != O_constant
9486		      || offset_expr.X_add_number >= 0x8000
9487		      || offset_expr.X_add_number < -0x8000))
9488		break;
9489
9490	      s = expr_end;
9491	      continue;
9492
9493	    case 'p':		/* pc relative offset */
9494	      *offset_reloc = BFD_RELOC_16_PCREL_S2;
9495	      my_getExpression (&offset_expr, s);
9496	      s = expr_end;
9497	      continue;
9498
9499	    case 'u':		/* upper 16 bits */
9500	      if (my_getSmallExpression (&imm_expr, imm_reloc, s) == 0
9501		  && imm_expr.X_op == O_constant
9502		  && (imm_expr.X_add_number < 0
9503		      || imm_expr.X_add_number >= 0x10000))
9504		as_bad (_("lui expression not in range 0..65535"));
9505	      s = expr_end;
9506	      continue;
9507
9508	    case 'a':		/* 26 bit address */
9509	      my_getExpression (&offset_expr, s);
9510	      s = expr_end;
9511	      *offset_reloc = BFD_RELOC_MIPS_JMP;
9512	      continue;
9513
9514	    case 'N':		/* 3 bit branch condition code */
9515	    case 'M':		/* 3 bit compare condition code */
9516	      if (strncmp (s, "$fcc", 4) != 0)
9517		break;
9518	      s += 4;
9519	      regno = 0;
9520	      do
9521		{
9522		  regno *= 10;
9523		  regno += *s - '0';
9524		  ++s;
9525		}
9526	      while (ISDIGIT (*s));
9527	      if (regno > 7)
9528		as_bad (_("Invalid condition code register $fcc%d"), regno);
9529	      if ((strcmp(str + strlen(str) - 3, ".ps") == 0
9530		   || strcmp(str + strlen(str) - 5, "any2f") == 0
9531		   || strcmp(str + strlen(str) - 5, "any2t") == 0)
9532		  && (regno & 1) != 0)
9533		as_warn(_("Condition code register should be even for %s, was %d"),
9534			str, regno);
9535	      if ((strcmp(str + strlen(str) - 5, "any4f") == 0
9536		   || strcmp(str + strlen(str) - 5, "any4t") == 0)
9537		  && (regno & 3) != 0)
9538		as_warn(_("Condition code register should be 0 or 4 for %s, was %d"),
9539			str, regno);
9540	      if (*args == 'N')
9541		INSERT_OPERAND (BCC, *ip, regno);
9542	      else
9543		INSERT_OPERAND (CCC, *ip, regno);
9544	      continue;
9545
9546	    case 'H':
9547	      if (s[0] == '0' && (s[1] == 'x' || s[1] == 'X'))
9548		s += 2;
9549	      if (ISDIGIT (*s))
9550		{
9551		  c = 0;
9552		  do
9553		    {
9554		      c *= 10;
9555		      c += *s - '0';
9556		      ++s;
9557		    }
9558		  while (ISDIGIT (*s));
9559		}
9560	      else
9561		c = 8; /* Invalid sel value.  */
9562
9563	      if (c > 7)
9564		as_bad (_("invalid coprocessor sub-selection value (0-7)"));
9565	      ip->insn_opcode |= c;
9566	      continue;
9567
9568	    case 'e':
9569	      /* Must be at least one digit.  */
9570	      my_getExpression (&imm_expr, s);
9571	      check_absolute_expr (ip, &imm_expr);
9572
9573	      if ((unsigned long) imm_expr.X_add_number
9574		  > (unsigned long) OP_MASK_VECBYTE)
9575		{
9576		  as_bad (_("bad byte vector index (%ld)"),
9577			   (long) imm_expr.X_add_number);
9578		  imm_expr.X_add_number = 0;
9579		}
9580
9581	      INSERT_OPERAND (VECBYTE, *ip, imm_expr.X_add_number);
9582	      imm_expr.X_op = O_absent;
9583	      s = expr_end;
9584	      continue;
9585
9586	    case '%':
9587	      my_getExpression (&imm_expr, s);
9588	      check_absolute_expr (ip, &imm_expr);
9589
9590	      if ((unsigned long) imm_expr.X_add_number
9591		  > (unsigned long) OP_MASK_VECALIGN)
9592		{
9593		  as_bad (_("bad byte vector index (%ld)"),
9594			   (long) imm_expr.X_add_number);
9595		  imm_expr.X_add_number = 0;
9596		}
9597
9598	      INSERT_OPERAND (VECALIGN, *ip, imm_expr.X_add_number);
9599	      imm_expr.X_op = O_absent;
9600	      s = expr_end;
9601	      continue;
9602
9603	    default:
9604	      as_bad (_("bad char = '%c'\n"), *args);
9605	      internalError ();
9606	    }
9607	  break;
9608	}
9609      /* Args don't match.  */
9610      if (insn + 1 < &mips_opcodes[NUMOPCODES] &&
9611	  !strcmp (insn->name, insn[1].name))
9612	{
9613	  ++insn;
9614	  s = argsStart;
9615	  insn_error = _("illegal operands");
9616	  continue;
9617	}
9618      if (save_c)
9619	*(--s) = save_c;
9620      insn_error = _("illegal operands");
9621      return;
9622    }
9623}
9624
9625#define SKIP_SPACE_TABS(S) { while (*(S) == ' ' || *(S) == '\t') ++(S); }
9626
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.  */
9633
9634static void
9635mips16_ip (char *str, struct mips_cl_insn *ip)
9636{
9637  char *s;
9638  const char *args;
9639  struct mips_opcode *insn;
9640  char *argsstart;
9641  unsigned int regno;
9642  unsigned int lastregno = 0;
9643  char *s_reset;
9644  size_t i;
9645
9646  insn_error = NULL;
9647
9648  mips16_small = FALSE;
9649  mips16_ext = FALSE;
9650
9651  for (s = str; ISLOWER (*s); ++s)
9652    ;
9653  switch (*s)
9654    {
9655    case '\0':
9656      break;
9657
9658    case ' ':
9659      *s++ = '\0';
9660      break;
9661
9662    case '.':
9663      if (s[1] == 't' && s[2] == ' ')
9664	{
9665	  *s = '\0';
9666	  mips16_small = TRUE;
9667	  s += 3;
9668	  break;
9669	}
9670      else if (s[1] == 'e' && s[2] == ' ')
9671	{
9672	  *s = '\0';
9673	  mips16_ext = TRUE;
9674	  s += 3;
9675	  break;
9676	}
9677      /* Fall through.  */
9678    default:
9679      insn_error = _("unknown opcode");
9680      return;
9681    }
9682
9683  if (mips_opts.noautoextend && ! mips16_ext)
9684    mips16_small = TRUE;
9685
9686  if ((insn = (struct mips_opcode *) hash_find (mips16_op_hash, str)) == NULL)
9687    {
9688      insn_error = _("unrecognized opcode");
9689      return;
9690    }
9691
9692  argsstart = s;
9693  for (;;)
9694    {
9695      assert (strcmp (insn->name, str) == 0);
9696
9697      create_insn (ip, insn);
9698      imm_expr.X_op = O_absent;
9699      imm_reloc[0] = BFD_RELOC_UNUSED;
9700      imm_reloc[1] = BFD_RELOC_UNUSED;
9701      imm_reloc[2] = BFD_RELOC_UNUSED;
9702      imm2_expr.X_op = O_absent;
9703      offset_expr.X_op = O_absent;
9704      offset_reloc[0] = BFD_RELOC_UNUSED;
9705      offset_reloc[1] = BFD_RELOC_UNUSED;
9706      offset_reloc[2] = BFD_RELOC_UNUSED;
9707      for (args = insn->args; 1; ++args)
9708	{
9709	  int c;
9710
9711	  if (*s == ' ')
9712	    ++s;
9713
9714	  /* In this switch statement we call break if we did not find
9715             a match, continue if we did find a match, or return if we
9716             are done.  */
9717
9718	  c = *args;
9719	  switch (c)
9720	    {
9721	    case '\0':
9722	      if (*s == '\0')
9723		{
9724		  /* Stuff the immediate value in now, if we can.  */
9725		  if (imm_expr.X_op == O_constant
9726		      && *imm_reloc > BFD_RELOC_UNUSED
9727		      && insn->pinfo != INSN_MACRO)
9728		    {
9729		      *offset_reloc = BFD_RELOC_UNUSED;
9730
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;
9737		    }
9738
9739		  return;
9740		}
9741	      break;
9742
9743	    case ',':
9744	      if (*s++ == c)
9745		continue;
9746	      s--;
9747	      switch (*++args)
9748		{
9749		case 'v':
9750		  MIPS16_INSERT_OPERAND (RX, *ip, lastregno);
9751		  continue;
9752		case 'w':
9753		  MIPS16_INSERT_OPERAND (RY, *ip, lastregno);
9754		  continue;
9755		}
9756	      break;
9757
9758	    case '(':
9759	    case ')':
9760	      if (*s++ == c)
9761		continue;
9762	      break;
9763
9764	    case 'v':
9765	    case 'w':
9766	      if (s[0] != '$')
9767		{
9768		  if (c == 'v')
9769		    MIPS16_INSERT_OPERAND (RX, *ip, lastregno);
9770		  else
9771		    MIPS16_INSERT_OPERAND (RY, *ip, lastregno);
9772		  ++args;
9773		  continue;
9774		}
9775	      /* Fall through.  */
9776	    case 'x':
9777	    case 'y':
9778	    case 'z':
9779	    case 'Z':
9780	    case '0':
9781	    case 'S':
9782	    case 'R':
9783	    case 'X':
9784	    case 'Y':
9785	      if (s[0] != '$')
9786		break;
9787	      s_reset = s;
9788	      if (ISDIGIT (s[1]))
9789		{
9790		  ++s;
9791		  regno = 0;
9792		  do
9793		    {
9794		      regno *= 10;
9795		      regno += *s - '0';
9796		      ++s;
9797		    }
9798		  while (ISDIGIT (*s));
9799		  if (regno > 31)
9800		    {
9801		      as_bad (_("invalid register number (%d)"), regno);
9802		      regno = 2;
9803		    }
9804		}
9805	      else
9806		{
9807		  if (s[1] == 'r' && s[2] == 'a')
9808		    {
9809		      s += 3;
9810		      regno = RA;
9811		    }
9812		  else if (s[1] == 'f' && s[2] == 'p')
9813		    {
9814		      s += 3;
9815		      regno = FP;
9816		    }
9817		  else if (s[1] == 's' && s[2] == 'p')
9818		    {
9819		      s += 3;
9820		      regno = SP;
9821		    }
9822		  else if (s[1] == 'g' && s[2] == 'p')
9823		    {
9824		      s += 3;
9825		      regno = GP;
9826		    }
9827		  else if (s[1] == 'a' && s[2] == 't')
9828		    {
9829		      s += 3;
9830		      regno = AT;
9831		    }
9832		  else if (s[1] == 'k' && s[2] == 't' && s[3] == '0')
9833		    {
9834		      s += 4;
9835		      regno = KT0;
9836		    }
9837		  else if (s[1] == 'k' && s[2] == 't' && s[3] == '1')
9838		    {
9839		      s += 4;
9840		      regno = KT1;
9841		    }
9842		  else if (s[1] == 'z' && s[2] == 'e' && s[3] == 'r' && s[4] == 'o')
9843		    {
9844		      s += 5;
9845		      regno = ZERO;
9846		    }
9847		  else
9848		    break;
9849		}
9850
9851	      if (*s == ' ')
9852		++s;
9853	      if (args[1] != *s)
9854		{
9855		  if (c == 'v' || c == 'w')
9856		    {
9857		      regno = mips16_to_32_reg_map[lastregno];
9858		      s = s_reset;
9859		      ++args;
9860		    }
9861		}
9862
9863	      switch (c)
9864		{
9865		case 'x':
9866		case 'y':
9867		case 'z':
9868		case 'v':
9869		case 'w':
9870		case 'Z':
9871		  regno = mips32_to_16_reg_map[regno];
9872		  break;
9873
9874		case '0':
9875		  if (regno != 0)
9876		    regno = ILLEGAL_REG;
9877		  break;
9878
9879		case 'S':
9880		  if (regno != SP)
9881		    regno = ILLEGAL_REG;
9882		  break;
9883
9884		case 'R':
9885		  if (regno != RA)
9886		    regno = ILLEGAL_REG;
9887		  break;
9888
9889		case 'X':
9890		case 'Y':
9891		  if (regno == AT && ! mips_opts.noat)
9892		    as_warn (_("used $at without \".set noat\""));
9893		  break;
9894
9895		default:
9896		  internalError ();
9897		}
9898
9899	      if (regno == ILLEGAL_REG)
9900		break;
9901
9902	      switch (c)
9903		{
9904		case 'x':
9905		case 'v':
9906		  MIPS16_INSERT_OPERAND (RX, *ip, regno);
9907		  break;
9908		case 'y':
9909		case 'w':
9910		  MIPS16_INSERT_OPERAND (RY, *ip, regno);
9911		  break;
9912		case 'z':
9913		  MIPS16_INSERT_OPERAND (RZ, *ip, regno);
9914		  break;
9915		case 'Z':
9916		  MIPS16_INSERT_OPERAND (MOVE32Z, *ip, regno);
9917		case '0':
9918		case 'S':
9919		case 'R':
9920		  break;
9921		case 'X':
9922		  MIPS16_INSERT_OPERAND (REGR32, *ip, regno);
9923		  break;
9924		case 'Y':
9925		  regno = ((regno & 7) << 2) | ((regno & 0x18) >> 3);
9926		  MIPS16_INSERT_OPERAND (REG32R, *ip, regno);
9927		  break;
9928		default:
9929		  internalError ();
9930		}
9931
9932	      lastregno = regno;
9933	      continue;
9934
9935	    case 'P':
9936	      if (strncmp (s, "$pc", 3) == 0)
9937		{
9938		  s += 3;
9939		  continue;
9940		}
9941	      break;
9942
9943	    case '5':
9944	    case 'H':
9945	    case 'W':
9946	    case 'D':
9947	    case 'j':
9948	    case 'V':
9949	    case 'C':
9950	    case 'U':
9951	    case 'k':
9952	    case 'K':
9953	      i = my_getSmallExpression (&imm_expr, imm_reloc, s);
9954	      if (i > 0)
9955		{
9956		  if (imm_expr.X_op != O_constant)
9957		    {
9958		      mips16_ext = TRUE;
9959		      ip->use_extend = TRUE;
9960		      ip->extend = 0;
9961		    }
9962		  else
9963		    {
9964		      /* We need to relax this instruction.  */
9965		      *offset_reloc = *imm_reloc;
9966		      *imm_reloc = (int) BFD_RELOC_UNUSED + c;
9967		    }
9968		  s = expr_end;
9969		  continue;
9970		}
9971	      *imm_reloc = BFD_RELOC_UNUSED;
9972	      /* Fall through.  */
9973	    case '<':
9974	    case '>':
9975	    case '[':
9976	    case ']':
9977	    case '4':
9978	    case '8':
9979	      my_getExpression (&imm_expr, s);
9980	      if (imm_expr.X_op == O_register)
9981		{
9982		  /* What we thought was an expression turned out to
9983                     be a register.  */
9984
9985		  if (s[0] == '(' && args[1] == '(')
9986		    {
9987		      /* It looks like the expression was omitted
9988			 before a register indirection, which means
9989			 that the expression is implicitly zero.  We
9990			 still set up imm_expr, so that we handle
9991			 explicit extensions correctly.  */
9992		      imm_expr.X_op = O_constant;
9993		      imm_expr.X_add_number = 0;
9994		      *imm_reloc = (int) BFD_RELOC_UNUSED + c;
9995		      continue;
9996		    }
9997
9998		  break;
9999		}
10000
10001	      /* We need to relax this instruction.  */
10002	      *imm_reloc = (int) BFD_RELOC_UNUSED + c;
10003	      s = expr_end;
10004	      continue;
10005
10006	    case 'p':
10007	    case 'q':
10008	    case 'A':
10009	    case 'B':
10010	    case 'E':
10011	      /* We use offset_reloc rather than imm_reloc for the PC
10012                 relative operands.  This lets macros with both
10013                 immediate and address operands work correctly.  */
10014	      my_getExpression (&offset_expr, s);
10015
10016	      if (offset_expr.X_op == O_register)
10017		break;
10018
10019	      /* We need to relax this instruction.  */
10020	      *offset_reloc = (int) BFD_RELOC_UNUSED + c;
10021	      s = expr_end;
10022	      continue;
10023
10024	    case '6':		/* break code */
10025	      my_getExpression (&imm_expr, s);
10026	      check_absolute_expr (ip, &imm_expr);
10027	      if ((unsigned long) imm_expr.X_add_number > 63)
10028		as_warn (_("Invalid value for `%s' (%lu)"),
10029			 ip->insn_mo->name,
10030			 (unsigned long) imm_expr.X_add_number);
10031	      MIPS16_INSERT_OPERAND (IMM6, *ip, imm_expr.X_add_number);
10032	      imm_expr.X_op = O_absent;
10033	      s = expr_end;
10034	      continue;
10035
10036	    case 'a':		/* 26 bit address */
10037	      my_getExpression (&offset_expr, s);
10038	      s = expr_end;
10039	      *offset_reloc = BFD_RELOC_MIPS16_JMP;
10040	      ip->insn_opcode <<= 16;
10041	      continue;
10042
10043	    case 'l':		/* register list for entry macro */
10044	    case 'L':		/* register list for exit macro */
10045	      {
10046		int mask;
10047
10048		if (c == 'l')
10049		  mask = 0;
10050		else
10051		  mask = 7 << 3;
10052		while (*s != '\0')
10053		  {
10054		    int freg, reg1, reg2;
10055
10056		    while (*s == ' ' || *s == ',')
10057		      ++s;
10058		    if (*s != '$')
10059		      {
10060			as_bad (_("can't parse register list"));
10061			break;
10062		      }
10063		    ++s;
10064		    if (*s != 'f')
10065		      freg = 0;
10066		    else
10067		      {
10068			freg = 1;
10069			++s;
10070		      }
10071		    reg1 = 0;
10072		    while (ISDIGIT (*s))
10073		      {
10074			reg1 *= 10;
10075			reg1 += *s - '0';
10076			++s;
10077		      }
10078		    if (*s == ' ')
10079		      ++s;
10080		    if (*s != '-')
10081		      reg2 = reg1;
10082		    else
10083		      {
10084			++s;
10085			if (*s != '$')
10086			  break;
10087			++s;
10088			if (freg)
10089			  {
10090			    if (*s == 'f')
10091			      ++s;
10092			    else
10093			      {
10094				as_bad (_("invalid register list"));
10095				break;
10096			      }
10097			  }
10098			reg2 = 0;
10099			while (ISDIGIT (*s))
10100			  {
10101			    reg2 *= 10;
10102			    reg2 += *s - '0';
10103			    ++s;
10104			  }
10105		      }
10106		    if (freg && reg1 == 0 && reg2 == 0 && c == 'L')
10107		      {
10108			mask &= ~ (7 << 3);
10109			mask |= 5 << 3;
10110		      }
10111		    else if (freg && reg1 == 0 && reg2 == 1 && c == 'L')
10112		      {
10113			mask &= ~ (7 << 3);
10114			mask |= 6 << 3;
10115		      }
10116		    else if (reg1 == 4 && reg2 >= 4 && reg2 <= 7 && c != 'L')
10117		      mask |= (reg2 - 3) << 3;
10118		    else if (reg1 == 16 && reg2 >= 16 && reg2 <= 17)
10119		      mask |= (reg2 - 15) << 1;
10120		    else if (reg1 == RA && reg2 == RA)
10121		      mask |= 1;
10122		    else
10123		      {
10124			as_bad (_("invalid register list"));
10125			break;
10126		      }
10127		  }
10128		/* The mask is filled in in the opcode table for the
10129                   benefit of the disassembler.  We remove it before
10130                   applying the actual mask.  */
10131		ip->insn_opcode &= ~ ((7 << 3) << MIPS16OP_SH_IMM6);
10132		ip->insn_opcode |= mask << MIPS16OP_SH_IMM6;
10133	      }
10134	    continue;
10135
10136	    case 'm':		/* Register list for save insn.  */
10137	    case 'M':		/* Register list for restore insn.  */
10138	      {
10139		int opcode = 0;
10140		int framesz = 0, seen_framesz = 0;
10141		int args = 0, statics = 0, sregs = 0;
10142
10143		while (*s != '\0')
10144		  {
10145		    unsigned int reg1, reg2;
10146
10147		    SKIP_SPACE_TABS (s);
10148		    while (*s == ',')
10149		      ++s;
10150		    SKIP_SPACE_TABS (s);
10151
10152		    my_getExpression (&imm_expr, s);
10153		    if (imm_expr.X_op == O_constant)
10154		      {
10155			/* Handle the frame size.  */
10156			if (seen_framesz)
10157			  {
10158			    as_bad (_("more than one frame size in list"));
10159			    break;
10160			  }
10161			seen_framesz = 1;
10162			framesz = imm_expr.X_add_number;
10163			imm_expr.X_op = O_absent;
10164			s = expr_end;
10165			continue;
10166		      }
10167
10168		    if (*s != '$')
10169		      {
10170			as_bad (_("can't parse register list"));
10171			break;
10172		      }
10173		    ++s;
10174
10175		    reg1 = 0;
10176		    while (ISDIGIT (*s))
10177		      {
10178			reg1 *= 10;
10179			reg1 += *s - '0';
10180			++s;
10181		      }
10182		    SKIP_SPACE_TABS (s);
10183		    if (*s != '-')
10184		      reg2 = reg1;
10185		    else
10186		      {
10187			++s;
10188			if (*s != '$')
10189			  {
10190			    as_bad (_("can't parse register list"));
10191			    break;
10192			  }
10193			++s;
10194			reg2 = 0;
10195			while (ISDIGIT (*s))
10196			  {
10197			    reg2 *= 10;
10198			    reg2 += *s - '0';
10199			    ++s;
10200			  }
10201		      }
10202
10203		    while (reg1 <= reg2)
10204		      {
10205			if (reg1 >= 4 && reg1 <= 7)
10206			  {
10207			    if (c == 'm' && !seen_framesz)
10208				/* args $a0-$a3 */
10209				args |= 1 << (reg1 - 4);
10210			    else
10211				/* statics $a0-$a3 */
10212				statics |= 1 << (reg1 - 4);
10213			  }
10214			else if ((reg1 >= 16 && reg1 <= 23) || reg1 == 30)
10215			  {
10216			    /* $s0-$s8 */
10217			    sregs |= 1 << ((reg1 == 30) ? 8 : (reg1 - 16));
10218			  }
10219			else if (reg1 == 31)
10220			  {
10221			    /* Add $ra to insn.  */
10222			    opcode |= 0x40;
10223			  }
10224			else
10225			  {
10226			    as_bad (_("unexpected register in list"));
10227			    break;
10228			  }
10229			if (++reg1 == 24)
10230			  reg1 = 30;
10231		      }
10232		  }
10233
10234		/* Encode args/statics combination.  */
10235		if (args & statics)
10236		  as_bad (_("arg/static registers overlap"));
10237		else if (args == 0xf)
10238		  /* All $a0-$a3 are args.  */
10239		  opcode |= MIPS16_ALL_ARGS << 16;
10240		else if (statics == 0xf)
10241		  /* All $a0-$a3 are statics.  */
10242		  opcode |= MIPS16_ALL_STATICS << 16;
10243		else
10244		  {
10245		    int narg = 0, nstat = 0;
10246
10247		    /* Count arg registers.  */
10248		    while (args & 0x1)
10249		      {
10250			args >>= 1;
10251			narg++;
10252		      }
10253		    if (args != 0)
10254		      as_bad (_("invalid arg register list"));
10255
10256		    /* Count static registers.  */
10257		    while (statics & 0x8)
10258		      {
10259			statics = (statics << 1) & 0xf;
10260			nstat++;
10261		      }
10262		    if (statics != 0)
10263		      as_bad (_("invalid static register list"));
10264
10265		    /* Encode args/statics.  */
10266		    opcode |= ((narg << 2) | nstat) << 16;
10267		  }
10268
10269		/* Encode $s0/$s1.  */
10270		if (sregs & (1 << 0))		/* $s0 */
10271		  opcode |= 0x20;
10272		if (sregs & (1 << 1))		/* $s1 */
10273		  opcode |= 0x10;
10274		sregs >>= 2;
10275
10276		if (sregs != 0)
10277		  {
10278		    /* Count regs $s2-$s8.  */
10279		    int nsreg = 0;
10280		    while (sregs & 1)
10281		      {
10282			sregs >>= 1;
10283			nsreg++;
10284		      }
10285		    if (sregs != 0)
10286		      as_bad (_("invalid static register list"));
10287		    /* Encode $s2-$s8. */
10288		    opcode |= nsreg << 24;
10289		  }
10290
10291		/* Encode frame size.  */
10292		if (!seen_framesz)
10293		  as_bad (_("missing frame size"));
10294		else if ((framesz & 7) != 0 || framesz < 0
10295			 || framesz > 0xff * 8)
10296		  as_bad (_("invalid frame size"));
10297		else if (framesz != 128 || (opcode >> 16) != 0)
10298		  {
10299		    framesz /= 8;
10300		    opcode |= (((framesz & 0xf0) << 16)
10301			     | (framesz & 0x0f));
10302		  }
10303
10304		/* Finally build the instruction.  */
10305		if ((opcode >> 16) != 0 || framesz == 0)
10306		  {
10307		    ip->use_extend = TRUE;
10308		    ip->extend = opcode >> 16;
10309		  }
10310		ip->insn_opcode |= opcode & 0x7f;
10311	      }
10312	    continue;
10313
10314	    case 'e':		/* extend code */
10315	      my_getExpression (&imm_expr, s);
10316	      check_absolute_expr (ip, &imm_expr);
10317	      if ((unsigned long) imm_expr.X_add_number > 0x7ff)
10318		{
10319		  as_warn (_("Invalid value for `%s' (%lu)"),
10320			   ip->insn_mo->name,
10321			   (unsigned long) imm_expr.X_add_number);
10322		  imm_expr.X_add_number &= 0x7ff;
10323		}
10324	      ip->insn_opcode |= imm_expr.X_add_number;
10325	      imm_expr.X_op = O_absent;
10326	      s = expr_end;
10327	      continue;
10328
10329	    default:
10330	      internalError ();
10331	    }
10332	  break;
10333	}
10334
10335      /* Args don't match.  */
10336      if (insn + 1 < &mips16_opcodes[bfd_mips16_num_opcodes] &&
10337	  strcmp (insn->name, insn[1].name) == 0)
10338	{
10339	  ++insn;
10340	  s = argsstart;
10341	  continue;
10342	}
10343
10344      insn_error = _("illegal operands");
10345
10346      return;
10347    }
10348}
10349
10350/* This structure holds information we know about a mips16 immediate
10351   argument type.  */
10352
10353struct mips16_immed_operand
10354{
10355  /* The type code used in the argument string in the opcode table.  */
10356  int type;
10357  /* The number of bits in the short form of the opcode.  */
10358  int nbits;
10359  /* The number of bits in the extended form of the opcode.  */
10360  int extbits;
10361  /* The amount by which the short form is shifted when it is used;
10362     for example, the sw instruction has a shift count of 2.  */
10363  int shift;
10364  /* The amount by which the short form is shifted when it is stored
10365     into the instruction code.  */
10366  int op_shift;
10367  /* Non-zero if the short form is unsigned.  */
10368  int unsp;
10369  /* Non-zero if the extended form is unsigned.  */
10370  int extu;
10371  /* Non-zero if the value is PC relative.  */
10372  int pcrel;
10373};
10374
10375/* The mips16 immediate operand types.  */
10376
10377static const struct mips16_immed_operand mips16_immed_operands[] =
10378{
10379  { '<',  3,  5, 0, MIPS16OP_SH_RZ,   1, 1, 0 },
10380  { '>',  3,  5, 0, MIPS16OP_SH_RX,   1, 1, 0 },
10381  { '[',  3,  6, 0, MIPS16OP_SH_RZ,   1, 1, 0 },
10382  { ']',  3,  6, 0, MIPS16OP_SH_RX,   1, 1, 0 },
10383  { '4',  4, 15, 0, MIPS16OP_SH_IMM4, 0, 0, 0 },
10384  { '5',  5, 16, 0, MIPS16OP_SH_IMM5, 1, 0, 0 },
10385  { 'H',  5, 16, 1, MIPS16OP_SH_IMM5, 1, 0, 0 },
10386  { 'W',  5, 16, 2, MIPS16OP_SH_IMM5, 1, 0, 0 },
10387  { 'D',  5, 16, 3, MIPS16OP_SH_IMM5, 1, 0, 0 },
10388  { 'j',  5, 16, 0, MIPS16OP_SH_IMM5, 0, 0, 0 },
10389  { '8',  8, 16, 0, MIPS16OP_SH_IMM8, 1, 0, 0 },
10390  { 'V',  8, 16, 2, MIPS16OP_SH_IMM8, 1, 0, 0 },
10391  { 'C',  8, 16, 3, MIPS16OP_SH_IMM8, 1, 0, 0 },
10392  { 'U',  8, 16, 0, MIPS16OP_SH_IMM8, 1, 1, 0 },
10393  { 'k',  8, 16, 0, MIPS16OP_SH_IMM8, 0, 0, 0 },
10394  { 'K',  8, 16, 3, MIPS16OP_SH_IMM8, 0, 0, 0 },
10395  { 'p',  8, 16, 0, MIPS16OP_SH_IMM8, 0, 0, 1 },
10396  { 'q', 11, 16, 0, MIPS16OP_SH_IMM8, 0, 0, 1 },
10397  { 'A',  8, 16, 2, MIPS16OP_SH_IMM8, 1, 0, 1 },
10398  { 'B',  5, 16, 3, MIPS16OP_SH_IMM5, 1, 0, 1 },
10399  { 'E',  5, 16, 2, MIPS16OP_SH_IMM5, 1, 0, 1 }
10400};
10401
10402#define MIPS16_NUM_IMMED \
10403  (sizeof mips16_immed_operands / sizeof mips16_immed_operands[0])
10404
10405/* Handle a mips16 instruction with an immediate value.  This or's the
10406   small immediate value into *INSN.  It sets *USE_EXTEND to indicate
10407   whether an extended value is needed; if one is needed, it sets
10408   *EXTEND to the value.  The argument type is TYPE.  The value is VAL.
10409   If SMALL is true, an unextended opcode was explicitly requested.
10410   If EXT is true, an extended opcode was explicitly requested.  If
10411   WARN is true, warn if EXT does not match reality.  */
10412
10413static void
10414mips16_immed (char *file, unsigned int line, int type, offsetT val,
10415	      bfd_boolean warn, bfd_boolean small, bfd_boolean ext,
10416	      unsigned long *insn, bfd_boolean *use_extend,
10417	      unsigned short *extend)
10418{
10419  register const struct mips16_immed_operand *op;
10420  int mintiny, maxtiny;
10421  bfd_boolean needext;
10422
10423  op = mips16_immed_operands;
10424  while (op->type != type)
10425    {
10426      ++op;
10427      assert (op < mips16_immed_operands + MIPS16_NUM_IMMED);
10428    }
10429
10430  if (op->unsp)
10431    {
10432      if (type == '<' || type == '>' || type == '[' || type == ']')
10433	{
10434	  mintiny = 1;
10435	  maxtiny = 1 << op->nbits;
10436	}
10437      else
10438	{
10439	  mintiny = 0;
10440	  maxtiny = (1 << op->nbits) - 1;
10441	}
10442    }
10443  else
10444    {
10445      mintiny = - (1 << (op->nbits - 1));
10446      maxtiny = (1 << (op->nbits - 1)) - 1;
10447    }
10448
10449  /* Branch offsets have an implicit 0 in the lowest bit.  */
10450  if (type == 'p' || type == 'q')
10451    val /= 2;
10452
10453  if ((val & ((1 << op->shift) - 1)) != 0
10454      || val < (mintiny << op->shift)
10455      || val > (maxtiny << op->shift))
10456    needext = TRUE;
10457  else
10458    needext = FALSE;
10459
10460  if (warn && ext && ! needext)
10461    as_warn_where (file, line,
10462		   _("extended operand requested but not required"));
10463  if (small && needext)
10464    as_bad_where (file, line, _("invalid unextended operand value"));
10465
10466  if (small || (! ext && ! needext))
10467    {
10468      int insnval;
10469
10470      *use_extend = FALSE;
10471      insnval = ((val >> op->shift) & ((1 << op->nbits) - 1));
10472      insnval <<= op->op_shift;
10473      *insn |= insnval;
10474    }
10475  else
10476    {
10477      long minext, maxext;
10478      int extval;
10479
10480      if (op->extu)
10481	{
10482	  minext = 0;
10483	  maxext = (1 << op->extbits) - 1;
10484	}
10485      else
10486	{
10487	  minext = - (1 << (op->extbits - 1));
10488	  maxext = (1 << (op->extbits - 1)) - 1;
10489	}
10490      if (val < minext || val > maxext)
10491	as_bad_where (file, line,
10492		      _("operand value out of range for instruction"));
10493
10494      *use_extend = TRUE;
10495      if (op->extbits == 16)
10496	{
10497	  extval = ((val >> 11) & 0x1f) | (val & 0x7e0);
10498	  val &= 0x1f;
10499	}
10500      else if (op->extbits == 15)
10501	{
10502	  extval = ((val >> 11) & 0xf) | (val & 0x7f0);
10503	  val &= 0xf;
10504	}
10505      else
10506	{
10507	  extval = ((val & 0x1f) << 6) | (val & 0x20);
10508	  val = 0;
10509	}
10510
10511      *extend = (unsigned short) extval;
10512      *insn |= val;
10513    }
10514}
10515
10516struct percent_op_match
10517{
10518  const char *str;
10519  bfd_reloc_code_real_type reloc;
10520};
10521
10522static const struct percent_op_match mips_percent_op[] =
10523{
10524  {"%lo", BFD_RELOC_LO16},
10525#ifdef OBJ_ELF
10526  {"%call_hi", BFD_RELOC_MIPS_CALL_HI16},
10527  {"%call_lo", BFD_RELOC_MIPS_CALL_LO16},
10528  {"%call16", BFD_RELOC_MIPS_CALL16},
10529  {"%got_disp", BFD_RELOC_MIPS_GOT_DISP},
10530  {"%got_page", BFD_RELOC_MIPS_GOT_PAGE},
10531  {"%got_ofst", BFD_RELOC_MIPS_GOT_OFST},
10532  {"%got_hi", BFD_RELOC_MIPS_GOT_HI16},
10533  {"%got_lo", BFD_RELOC_MIPS_GOT_LO16},
10534  {"%got", BFD_RELOC_MIPS_GOT16},
10535  {"%gp_rel", BFD_RELOC_GPREL16},
10536  {"%half", BFD_RELOC_16},
10537  {"%highest", BFD_RELOC_MIPS_HIGHEST},
10538  {"%higher", BFD_RELOC_MIPS_HIGHER},
10539  {"%neg", BFD_RELOC_MIPS_SUB},
10540#endif
10541  {"%hi", BFD_RELOC_HI16_S}
10542};
10543
10544/* Return true if *STR points to a relocation operator.  When returning true,
10545   move *STR over the operator and store its relocation code in *RELOC.
10546   Leave both *STR and *RELOC alone when returning false.  */
10547
10548static bfd_boolean
10549parse_relocation (char **str, bfd_reloc_code_real_type *reloc)
10550{
10551  const struct percent_op_match *percent_op;
10552  size_t limit, i;
10553
10554  percent_op = mips_percent_op;
10555  limit = ARRAY_SIZE (mips_percent_op);
10556
10557  for (i = 0; i < limit; i++)
10558    if (strncasecmp (*str, percent_op[i].str, strlen (percent_op[i].str)) == 0)
10559      {
10560	int len = strlen (percent_op[i].str);
10561
10562	if (!ISSPACE ((*str)[len]) && (*str)[len] != '(')
10563	  continue;
10564
10565	*str += strlen (percent_op[i].str);
10566	*reloc = percent_op[i].reloc;
10567
10568	/* Check whether the output BFD supports this relocation.
10569	   If not, issue an error and fall back on something safe.  */
10570	if (!bfd_reloc_type_lookup (stdoutput, percent_op[i].reloc))
10571	  {
10572	    as_bad ("relocation %s isn't supported by the current ABI",
10573		    percent_op[i].str);
10574	    *reloc = BFD_RELOC_UNUSED;
10575	  }
10576	return TRUE;
10577      }
10578  return FALSE;
10579}
10580
10581
10582/* Parse string STR as a 16-bit relocatable operand.  Store the
10583   expression in *EP and the relocations in the array starting
10584   at RELOC.  Return the number of relocation operators used.
10585
10586   On exit, EXPR_END points to the first character after the expression.  */
10587
10588static size_t
10589my_getSmallExpression (expressionS *ep, bfd_reloc_code_real_type *reloc,
10590		       char *str)
10591{
10592  bfd_reloc_code_real_type reversed_reloc[3];
10593  size_t reloc_index, i;
10594  int crux_depth, str_depth;
10595  char *crux;
10596
10597  /* Search for the start of the main expression, recoding relocations
10598     in REVERSED_RELOC.  End the loop with CRUX pointing to the start
10599     of the main expression and with CRUX_DEPTH containing the number
10600     of open brackets at that point.  */
10601  reloc_index = -1;
10602  str_depth = 0;
10603  do
10604    {
10605      reloc_index++;
10606      crux = str;
10607      crux_depth = str_depth;
10608
10609      /* Skip over whitespace and brackets, keeping count of the number
10610	 of brackets.  */
10611      while (*str == ' ' || *str == '\t' || *str == '(')
10612	if (*str++ == '(')
10613	  str_depth++;
10614    }
10615  while (*str == '%'
10616	 && reloc_index < (HAVE_NEWABI ? 3 : 1)
10617	 && parse_relocation (&str, &reversed_reloc[reloc_index]));
10618
10619  my_getExpression (ep, crux);
10620  str = expr_end;
10621
10622  /* Match every open bracket.  */
10623  while (crux_depth > 0 && (*str == ')' || *str == ' ' || *str == '\t'))
10624    if (*str++ == ')')
10625      crux_depth--;
10626
10627  if (crux_depth > 0)
10628    as_bad ("unclosed '('");
10629
10630  expr_end = str;
10631
10632  if (reloc_index != 0)
10633    {
10634      prev_reloc_op_frag = frag_now;
10635      for (i = 0; i < reloc_index; i++)
10636	reloc[i] = reversed_reloc[reloc_index - 1 - i];
10637    }
10638
10639  return reloc_index;
10640}
10641
10642static void
10643my_getExpression (expressionS *ep, char *str)
10644{
10645  char *save_in;
10646  valueT val;
10647
10648  save_in = input_line_pointer;
10649  input_line_pointer = str;
10650  expression (ep);
10651  expr_end = input_line_pointer;
10652  input_line_pointer = save_in;
10653
10654  /* If we are in mips16 mode, and this is an expression based on `.',
10655     then we bump the value of the symbol by 1 since that is how other
10656     text symbols are handled.  We don't bother to handle complex
10657     expressions, just `.' plus or minus a constant.  */
10658  if (mips_opts.mips16
10659      && ep->X_op == O_symbol
10660      && strcmp (S_GET_NAME (ep->X_add_symbol), FAKE_LABEL_NAME) == 0
10661      && S_GET_SEGMENT (ep->X_add_symbol) == now_seg
10662      && symbol_get_frag (ep->X_add_symbol) == frag_now
10663      && symbol_constant_p (ep->X_add_symbol)
10664      && (val = S_GET_VALUE (ep->X_add_symbol)) == frag_now_fix ())
10665    S_SET_VALUE (ep->X_add_symbol, val + 1);
10666}
10667
10668/* Turn a string in input_line_pointer into a floating point constant
10669   of type TYPE, and store the appropriate bytes in *LITP.  The number
10670   of LITTLENUMS emitted is stored in *SIZEP.  An error message is
10671   returned, or NULL on OK.  */
10672
10673char *
10674md_atof (int type, char *litP, int *sizeP)
10675{
10676  int prec;
10677  LITTLENUM_TYPE words[4];
10678  char *t;
10679  int i;
10680
10681  switch (type)
10682    {
10683    case 'f':
10684      prec = 2;
10685      break;
10686
10687    case 'd':
10688      prec = 4;
10689      break;
10690
10691    default:
10692      *sizeP = 0;
10693      return _("bad call to md_atof");
10694    }
10695
10696  t = atof_ieee (input_line_pointer, type, words);
10697  if (t)
10698    input_line_pointer = t;
10699
10700  *sizeP = prec * 2;
10701
10702  if (! target_big_endian)
10703    {
10704      for (i = prec - 1; i >= 0; i--)
10705	{
10706	  md_number_to_chars (litP, words[i], 2);
10707	  litP += 2;
10708	}
10709    }
10710  else
10711    {
10712      for (i = 0; i < prec; i++)
10713	{
10714	  md_number_to_chars (litP, words[i], 2);
10715	  litP += 2;
10716	}
10717    }
10718
10719  return NULL;
10720}
10721
10722void
10723md_number_to_chars (char *buf, valueT val, int n)
10724{
10725  if (target_big_endian)
10726    number_to_chars_bigendian (buf, val, n);
10727  else
10728    number_to_chars_littleendian (buf, val, n);
10729}
10730
10731#ifdef OBJ_ELF
10732static int support_64bit_objects(void)
10733{
10734  const char **list, **l;
10735  int yes;
10736
10737  list = bfd_target_list ();
10738  for (l = list; *l != NULL; l++)
10739#ifdef TE_TMIPS
10740    /* This is traditional mips */
10741    if (strcmp (*l, "elf64-tradbigmips") == 0
10742	|| strcmp (*l, "elf64-tradlittlemips") == 0)
10743#else
10744    if (strcmp (*l, "elf64-bigmips") == 0
10745	|| strcmp (*l, "elf64-littlemips") == 0)
10746#endif
10747      break;
10748  yes = (*l != NULL);
10749  free (list);
10750  return yes;
10751}
10752#endif /* OBJ_ELF */
10753
10754const char *md_shortopts = "O::g::G:";
10755
10756struct option md_longopts[] =
10757{
10758  /* Options which specify architecture.  */
10759#define OPTION_ARCH_BASE    (OPTION_MD_BASE)
10760#define OPTION_MARCH (OPTION_ARCH_BASE + 0)
10761  {"march", required_argument, NULL, OPTION_MARCH},
10762#define OPTION_MTUNE (OPTION_ARCH_BASE + 1)
10763  {"mtune", required_argument, NULL, OPTION_MTUNE},
10764#define OPTION_MIPS1 (OPTION_ARCH_BASE + 2)
10765  {"mips0", no_argument, NULL, OPTION_MIPS1},
10766  {"mips1", no_argument, NULL, OPTION_MIPS1},
10767#define OPTION_MIPS2 (OPTION_ARCH_BASE + 3)
10768  {"mips2", no_argument, NULL, OPTION_MIPS2},
10769#define OPTION_MIPS3 (OPTION_ARCH_BASE + 4)
10770  {"mips3", no_argument, NULL, OPTION_MIPS3},
10771#define OPTION_MIPS4 (OPTION_ARCH_BASE + 5)
10772  {"mips4", no_argument, NULL, OPTION_MIPS4},
10773#define OPTION_MIPS5 (OPTION_ARCH_BASE + 6)
10774  {"mips5", no_argument, NULL, OPTION_MIPS5},
10775#define OPTION_MIPS32 (OPTION_ARCH_BASE + 7)
10776  {"mips32", no_argument, NULL, OPTION_MIPS32},
10777#define OPTION_MIPS64 (OPTION_ARCH_BASE + 8)
10778  {"mips64", no_argument, NULL, OPTION_MIPS64},
10779#define OPTION_MIPS32R2 (OPTION_ARCH_BASE + 9)
10780  {"mips32r2", no_argument, NULL, OPTION_MIPS32R2},
10781#define OPTION_MIPS64R2 (OPTION_ARCH_BASE + 10)
10782  {"mips64r2", no_argument, NULL, OPTION_MIPS64R2},
10783
10784  /* Options which specify Application Specific Extensions (ASEs).  */
10785#define OPTION_ASE_BASE (OPTION_ARCH_BASE + 11)
10786#define OPTION_MIPS16 (OPTION_ASE_BASE + 0)
10787  {"mips16", no_argument, NULL, OPTION_MIPS16},
10788#define OPTION_NO_MIPS16 (OPTION_ASE_BASE + 1)
10789  {"no-mips16", no_argument, NULL, OPTION_NO_MIPS16},
10790#define OPTION_MIPS3D (OPTION_ASE_BASE + 2)
10791  {"mips3d", no_argument, NULL, OPTION_MIPS3D},
10792#define OPTION_NO_MIPS3D (OPTION_ASE_BASE + 3)
10793  {"no-mips3d", no_argument, NULL, OPTION_NO_MIPS3D},
10794#define OPTION_MDMX (OPTION_ASE_BASE + 4)
10795  {"mdmx", no_argument, NULL, OPTION_MDMX},
10796#define OPTION_NO_MDMX (OPTION_ASE_BASE + 5)
10797  {"no-mdmx", no_argument, NULL, OPTION_NO_MDMX},
10798#define OPTION_DSP (OPTION_ASE_BASE + 6)
10799  {"mdsp", no_argument, NULL, OPTION_DSP},
10800#define OPTION_NO_DSP (OPTION_ASE_BASE + 7)
10801  {"mno-dsp", no_argument, NULL, OPTION_NO_DSP},
10802#define OPTION_MT (OPTION_ASE_BASE + 8)
10803  {"mmt", no_argument, NULL, OPTION_MT},
10804#define OPTION_NO_MT (OPTION_ASE_BASE + 9)
10805  {"mno-mt", no_argument, NULL, OPTION_NO_MT},
10806
10807  /* Old-style architecture options.  Don't add more of these.  */
10808#define OPTION_COMPAT_ARCH_BASE (OPTION_ASE_BASE + 10)
10809#define OPTION_M4650 (OPTION_COMPAT_ARCH_BASE + 0)
10810  {"m4650", no_argument, NULL, OPTION_M4650},
10811#define OPTION_NO_M4650 (OPTION_COMPAT_ARCH_BASE + 1)
10812  {"no-m4650", no_argument, NULL, OPTION_NO_M4650},
10813#define OPTION_M4010 (OPTION_COMPAT_ARCH_BASE + 2)
10814  {"m4010", no_argument, NULL, OPTION_M4010},
10815#define OPTION_NO_M4010 (OPTION_COMPAT_ARCH_BASE + 3)
10816  {"no-m4010", no_argument, NULL, OPTION_NO_M4010},
10817#define OPTION_M4100 (OPTION_COMPAT_ARCH_BASE + 4)
10818  {"m4100", no_argument, NULL, OPTION_M4100},
10819#define OPTION_NO_M4100 (OPTION_COMPAT_ARCH_BASE + 5)
10820  {"no-m4100", no_argument, NULL, OPTION_NO_M4100},
10821#define OPTION_M3900 (OPTION_COMPAT_ARCH_BASE + 6)
10822  {"m3900", no_argument, NULL, OPTION_M3900},
10823#define OPTION_NO_M3900 (OPTION_COMPAT_ARCH_BASE + 7)
10824  {"no-m3900", no_argument, NULL, OPTION_NO_M3900},
10825
10826  /* Options which enable bug fixes.  */
10827#define OPTION_FIX_BASE    (OPTION_COMPAT_ARCH_BASE + 8)
10828#define OPTION_M7000_HILO_FIX (OPTION_FIX_BASE + 0)
10829  {"mfix7000", no_argument, NULL, OPTION_M7000_HILO_FIX},
10830#define OPTION_MNO_7000_HILO_FIX (OPTION_FIX_BASE + 1)
10831  {"no-fix-7000", no_argument, NULL, OPTION_MNO_7000_HILO_FIX},
10832  {"mno-fix7000", no_argument, NULL, OPTION_MNO_7000_HILO_FIX},
10833#define OPTION_FIX_VR4120 (OPTION_FIX_BASE + 2)
10834#define OPTION_NO_FIX_VR4120 (OPTION_FIX_BASE + 3)
10835  {"mfix-vr4120",    no_argument, NULL, OPTION_FIX_VR4120},
10836  {"mno-fix-vr4120", no_argument, NULL, OPTION_NO_FIX_VR4120},
10837#define OPTION_FIX_VR4130 (OPTION_FIX_BASE + 4)
10838#define OPTION_NO_FIX_VR4130 (OPTION_FIX_BASE + 5)
10839  {"mfix-vr4130",    no_argument, NULL, OPTION_FIX_VR4130},
10840  {"mno-fix-vr4130", no_argument, NULL, OPTION_NO_FIX_VR4130},
10841
10842  /* Miscellaneous options.  */
10843#define OPTION_MISC_BASE (OPTION_FIX_BASE + 6)
10844#define OPTION_TRAP (OPTION_MISC_BASE + 0)
10845  {"trap", no_argument, NULL, OPTION_TRAP},
10846  {"no-break", no_argument, NULL, OPTION_TRAP},
10847#define OPTION_BREAK (OPTION_MISC_BASE + 1)
10848  {"break", no_argument, NULL, OPTION_BREAK},
10849  {"no-trap", no_argument, NULL, OPTION_BREAK},
10850#define OPTION_EB (OPTION_MISC_BASE + 2)
10851  {"EB", no_argument, NULL, OPTION_EB},
10852#define OPTION_EL (OPTION_MISC_BASE + 3)
10853  {"EL", no_argument, NULL, OPTION_EL},
10854#define OPTION_FP32 (OPTION_MISC_BASE + 4)
10855  {"mfp32", no_argument, NULL, OPTION_FP32},
10856#define OPTION_GP32 (OPTION_MISC_BASE + 5)
10857  {"mgp32", no_argument, NULL, OPTION_GP32},
10858#define OPTION_CONSTRUCT_FLOATS (OPTION_MISC_BASE + 6)
10859  {"construct-floats", no_argument, NULL, OPTION_CONSTRUCT_FLOATS},
10860#define OPTION_NO_CONSTRUCT_FLOATS (OPTION_MISC_BASE + 7)
10861  {"no-construct-floats", no_argument, NULL, OPTION_NO_CONSTRUCT_FLOATS},
10862#define OPTION_FP64 (OPTION_MISC_BASE + 8)
10863  {"mfp64", no_argument, NULL, OPTION_FP64},
10864#define OPTION_GP64 (OPTION_MISC_BASE + 9)
10865  {"mgp64", no_argument, NULL, OPTION_GP64},
10866#define OPTION_RELAX_BRANCH (OPTION_MISC_BASE + 10)
10867#define OPTION_NO_RELAX_BRANCH (OPTION_MISC_BASE + 11)
10868  {"relax-branch", no_argument, NULL, OPTION_RELAX_BRANCH},
10869  {"no-relax-branch", no_argument, NULL, OPTION_NO_RELAX_BRANCH},
10870#define OPTION_MSHARED (OPTION_MISC_BASE + 12)
10871#define OPTION_MNO_SHARED (OPTION_MISC_BASE + 13)
10872  {"mshared", no_argument, NULL, OPTION_MSHARED},
10873  {"mno-shared", no_argument, NULL, OPTION_MNO_SHARED},
10874#define OPTION_MSYM32 (OPTION_MISC_BASE + 14)
10875#define OPTION_MNO_SYM32 (OPTION_MISC_BASE + 15)
10876  {"msym32", no_argument, NULL, OPTION_MSYM32},
10877  {"mno-sym32", no_argument, NULL, OPTION_MNO_SYM32},
10878
10879  /* ELF-specific options.  */
10880#ifdef OBJ_ELF
10881#define OPTION_ELF_BASE    (OPTION_MISC_BASE + 16)
10882#define OPTION_CALL_SHARED (OPTION_ELF_BASE + 0)
10883  {"KPIC",        no_argument, NULL, OPTION_CALL_SHARED},
10884  {"call_shared", no_argument, NULL, OPTION_CALL_SHARED},
10885#define OPTION_NON_SHARED  (OPTION_ELF_BASE + 1)
10886  {"non_shared",  no_argument, NULL, OPTION_NON_SHARED},
10887#define OPTION_XGOT        (OPTION_ELF_BASE + 2)
10888  {"xgot",        no_argument, NULL, OPTION_XGOT},
10889#define OPTION_MABI        (OPTION_ELF_BASE + 3)
10890  {"mabi", required_argument, NULL, OPTION_MABI},
10891#define OPTION_32 	   (OPTION_ELF_BASE + 4)
10892  {"32",          no_argument, NULL, OPTION_32},
10893#define OPTION_N32 	   (OPTION_ELF_BASE + 5)
10894  {"n32",         no_argument, NULL, OPTION_N32},
10895#define OPTION_64          (OPTION_ELF_BASE + 6)
10896  {"64",          no_argument, NULL, OPTION_64},
10897#define OPTION_MDEBUG      (OPTION_ELF_BASE + 7)
10898  {"mdebug", no_argument, NULL, OPTION_MDEBUG},
10899#define OPTION_NO_MDEBUG   (OPTION_ELF_BASE + 8)
10900  {"no-mdebug", no_argument, NULL, OPTION_NO_MDEBUG},
10901#define OPTION_PDR	   (OPTION_ELF_BASE + 9)
10902  {"mpdr", no_argument, NULL, OPTION_PDR},
10903#define OPTION_NO_PDR	   (OPTION_ELF_BASE + 10)
10904  {"mno-pdr", no_argument, NULL, OPTION_NO_PDR},
10905#endif /* OBJ_ELF */
10906
10907#define OPTION_MOCTEON_UNSUPPORTED (OPTION_MISC_BASE + 28)
10908#define OPTION_NO_MOCTEON_UNSUPPORTED (OPTION_MISC_BASE + 29)
10909  {"mocteon-unsupported", no_argument, NULL, OPTION_MOCTEON_UNSUPPORTED},
10910  {"mno-octeon-unsupported", no_argument, NULL, OPTION_NO_MOCTEON_UNSUPPORTED},
10911
10912#define OPTION_MOCTEON_USEUN (OPTION_MISC_BASE + 30)
10913#define OPTION_NO_MOCTEON_USEUN (OPTION_MISC_BASE + 31)
10914  {"mocteon-useun", no_argument, NULL, OPTION_MOCTEON_USEUN},
10915  {"mno-octeon-useun", no_argument, NULL, OPTION_NO_MOCTEON_USEUN},
10916
10917  {NULL, no_argument, NULL, 0}
10918};
10919size_t md_longopts_size = sizeof (md_longopts);
10920
10921/* Set STRING_PTR (either &mips_arch_string or &mips_tune_string) to
10922   NEW_VALUE.  Warn if another value was already specified.  Note:
10923   we have to defer parsing the -march and -mtune arguments in order
10924   to handle 'from-abi' correctly, since the ABI might be specified
10925   in a later argument.  */
10926
10927static void
10928mips_set_option_string (const char **string_ptr, const char *new_value)
10929{
10930  if (*string_ptr != 0 && strcasecmp (*string_ptr, new_value) != 0)
10931    as_warn (_("A different %s was already specified, is now %s"),
10932	     string_ptr == &mips_arch_string ? "-march" : "-mtune",
10933	     new_value);
10934
10935  *string_ptr = new_value;
10936}
10937
10938int
10939md_parse_option (int c, char *arg)
10940{
10941  switch (c)
10942    {
10943    case OPTION_CONSTRUCT_FLOATS:
10944      mips_disable_float_construction = 0;
10945      break;
10946
10947    case OPTION_NO_CONSTRUCT_FLOATS:
10948      mips_disable_float_construction = 1;
10949      break;
10950
10951    case OPTION_TRAP:
10952      mips_trap = 1;
10953      break;
10954
10955    case OPTION_BREAK:
10956      mips_trap = 0;
10957      break;
10958
10959    case OPTION_EB:
10960      target_big_endian = 1;
10961      break;
10962
10963    case OPTION_EL:
10964      target_big_endian = 0;
10965      break;
10966
10967    case OPTION_MOCTEON_UNSUPPORTED:
10968      octeon_error_on_unsupported = 1;
10969      break;
10970
10971    case OPTION_NO_MOCTEON_UNSUPPORTED:
10972      octeon_error_on_unsupported = 0;
10973      break;
10974
10975    case OPTION_MOCTEON_USEUN:
10976      octeon_use_unalign = 1;
10977      break;
10978
10979    case OPTION_NO_MOCTEON_USEUN:
10980      octeon_use_unalign = 0;
10981      break;
10982
10983    case 'O':
10984      if (arg && arg[1] == '0')
10985	mips_optimize = 1;
10986      else
10987	mips_optimize = 2;
10988      break;
10989
10990    case 'g':
10991      if (arg == NULL)
10992	mips_debug = 2;
10993      else
10994	mips_debug = atoi (arg);
10995      /* When the MIPS assembler sees -g or -g2, it does not do
10996         optimizations which limit full symbolic debugging.  We take
10997         that to be equivalent to -O0.  */
10998      if (mips_debug == 2)
10999	mips_optimize = 1;
11000      break;
11001
11002    case OPTION_MIPS1:
11003      file_mips_isa = ISA_MIPS1;
11004      break;
11005
11006    case OPTION_MIPS2:
11007      file_mips_isa = ISA_MIPS2;
11008      break;
11009
11010    case OPTION_MIPS3:
11011      file_mips_isa = ISA_MIPS3;
11012      break;
11013
11014    case OPTION_MIPS4:
11015      file_mips_isa = ISA_MIPS4;
11016      break;
11017
11018    case OPTION_MIPS5:
11019      file_mips_isa = ISA_MIPS5;
11020      break;
11021
11022    case OPTION_MIPS32:
11023      file_mips_isa = ISA_MIPS32;
11024      break;
11025
11026    case OPTION_MIPS32R2:
11027      file_mips_isa = ISA_MIPS32R2;
11028      break;
11029
11030    case OPTION_MIPS64R2:
11031      file_mips_isa = ISA_MIPS64R2;
11032      break;
11033
11034    case OPTION_MIPS64:
11035      file_mips_isa = ISA_MIPS64;
11036      break;
11037
11038    case OPTION_MTUNE:
11039      mips_set_option_string (&mips_tune_string, arg);
11040      break;
11041
11042    case OPTION_MARCH:
11043      mips_set_option_string (&mips_arch_string, arg);
11044      break;
11045
11046    case OPTION_M4650:
11047      mips_set_option_string (&mips_arch_string, "4650");
11048      mips_set_option_string (&mips_tune_string, "4650");
11049      break;
11050
11051    case OPTION_NO_M4650:
11052      break;
11053
11054    case OPTION_M4010:
11055      mips_set_option_string (&mips_arch_string, "4010");
11056      mips_set_option_string (&mips_tune_string, "4010");
11057      break;
11058
11059    case OPTION_NO_M4010:
11060      break;
11061
11062    case OPTION_M4100:
11063      mips_set_option_string (&mips_arch_string, "4100");
11064      mips_set_option_string (&mips_tune_string, "4100");
11065      break;
11066
11067    case OPTION_NO_M4100:
11068      break;
11069
11070    case OPTION_M3900:
11071      mips_set_option_string (&mips_arch_string, "3900");
11072      mips_set_option_string (&mips_tune_string, "3900");
11073      break;
11074
11075    case OPTION_NO_M3900:
11076      break;
11077
11078    case OPTION_MDMX:
11079      mips_opts.ase_mdmx = 1;
11080      break;
11081
11082    case OPTION_NO_MDMX:
11083      mips_opts.ase_mdmx = 0;
11084      break;
11085
11086    case OPTION_DSP:
11087      mips_opts.ase_dsp = 1;
11088      break;
11089
11090    case OPTION_NO_DSP:
11091      mips_opts.ase_dsp = 0;
11092      break;
11093
11094    case OPTION_MT:
11095      mips_opts.ase_mt = 1;
11096      break;
11097
11098    case OPTION_NO_MT:
11099      mips_opts.ase_mt = 0;
11100      break;
11101
11102    case OPTION_MIPS16:
11103      mips_opts.mips16 = 1;
11104      mips_no_prev_insn ();
11105      break;
11106
11107    case OPTION_NO_MIPS16:
11108      mips_opts.mips16 = 0;
11109      mips_no_prev_insn ();
11110      break;
11111
11112    case OPTION_MIPS3D:
11113      mips_opts.ase_mips3d = 1;
11114      break;
11115
11116    case OPTION_NO_MIPS3D:
11117      mips_opts.ase_mips3d = 0;
11118      break;
11119
11120    case OPTION_FIX_VR4120:
11121      mips_fix_vr4120 = 1;
11122      break;
11123
11124    case OPTION_NO_FIX_VR4120:
11125      mips_fix_vr4120 = 0;
11126      break;
11127
11128    case OPTION_FIX_VR4130:
11129      mips_fix_vr4130 = 1;
11130      break;
11131
11132    case OPTION_NO_FIX_VR4130:
11133      mips_fix_vr4130 = 0;
11134      break;
11135
11136    case OPTION_RELAX_BRANCH:
11137      mips_relax_branch = 1;
11138      break;
11139
11140    case OPTION_NO_RELAX_BRANCH:
11141      mips_relax_branch = 0;
11142      break;
11143
11144    case OPTION_MSHARED:
11145      mips_in_shared = TRUE;
11146      break;
11147
11148    case OPTION_MNO_SHARED:
11149      mips_in_shared = FALSE;
11150      break;
11151
11152    case OPTION_MSYM32:
11153      mips_opts.sym32 = TRUE;
11154      break;
11155
11156    case OPTION_MNO_SYM32:
11157      mips_opts.sym32 = FALSE;
11158      break;
11159
11160#ifdef OBJ_ELF
11161      /* When generating ELF code, we permit -KPIC and -call_shared to
11162	 select SVR4_PIC, and -non_shared to select no PIC.  This is
11163	 intended to be compatible with Irix 5.  */
11164    case OPTION_CALL_SHARED:
11165      if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
11166	{
11167	  as_bad (_("-call_shared is supported only for ELF format"));
11168	  return 0;
11169	}
11170      mips_pic = SVR4_PIC;
11171      mips_abicalls = TRUE;
11172      break;
11173
11174    case OPTION_NON_SHARED:
11175      if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
11176	{
11177	  as_bad (_("-non_shared is supported only for ELF format"));
11178	  return 0;
11179	}
11180      mips_pic = NO_PIC;
11181      mips_abicalls = FALSE;
11182      break;
11183
11184      /* The -xgot option tells the assembler to use 32 bit offsets
11185         when accessing the got in SVR4_PIC mode.  It is for Irix
11186         compatibility.  */
11187    case OPTION_XGOT:
11188      mips_big_got = 1;
11189      break;
11190#endif /* OBJ_ELF */
11191
11192    case 'G':
11193      g_switch_value = atoi (arg);
11194      g_switch_seen = 1;
11195      break;
11196
11197#ifdef OBJ_ELF
11198      /* The -32, -n32 and -64 options are shortcuts for -mabi=32, -mabi=n32
11199	 and -mabi=64.  */
11200    case OPTION_32:
11201      if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
11202	{
11203	  as_bad (_("-32 is supported for ELF format only"));
11204	  return 0;
11205	}
11206      mips_abi = O32_ABI;
11207      break;
11208
11209    case OPTION_N32:
11210      if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
11211	{
11212	  as_bad (_("-n32 is supported for ELF format only"));
11213	  return 0;
11214	}
11215      mips_abi = N32_ABI;
11216      break;
11217
11218    case OPTION_64:
11219      if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
11220	{
11221	  as_bad (_("-64 is supported for ELF format only"));
11222	  return 0;
11223	}
11224      mips_abi = N64_ABI;
11225      if (! support_64bit_objects())
11226	as_fatal (_("No compiled in support for 64 bit object file format"));
11227      break;
11228#endif /* OBJ_ELF */
11229
11230    case OPTION_GP32:
11231      file_mips_gp32 = 1;
11232      break;
11233
11234    case OPTION_GP64:
11235      file_mips_gp32 = 0;
11236      break;
11237
11238    case OPTION_FP32:
11239      file_mips_fp32 = 1;
11240      break;
11241
11242    case OPTION_FP64:
11243      file_mips_fp32 = 0;
11244      break;
11245
11246#ifdef OBJ_ELF
11247    case OPTION_MABI:
11248      if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
11249	{
11250	  as_bad (_("-mabi is supported for ELF format only"));
11251	  return 0;
11252	}
11253      if (strcmp (arg, "32") == 0)
11254	mips_abi = O32_ABI;
11255      else if (strcmp (arg, "o64") == 0)
11256	mips_abi = O64_ABI;
11257      else if (strcmp (arg, "n32") == 0)
11258	mips_abi = N32_ABI;
11259      else if (strcmp (arg, "64") == 0)
11260	{
11261	  mips_abi = N64_ABI;
11262	  if (! support_64bit_objects())
11263	    as_fatal (_("No compiled in support for 64 bit object file "
11264			"format"));
11265	}
11266      else if (strcmp (arg, "eabi") == 0)
11267	mips_abi = EABI_ABI;
11268      else
11269	{
11270	  as_fatal (_("invalid abi -mabi=%s"), arg);
11271	  return 0;
11272	}
11273      break;
11274#endif /* OBJ_ELF */
11275
11276    case OPTION_M7000_HILO_FIX:
11277      mips_7000_hilo_fix = TRUE;
11278      break;
11279
11280    case OPTION_MNO_7000_HILO_FIX:
11281      mips_7000_hilo_fix = FALSE;
11282      break;
11283
11284#ifdef OBJ_ELF
11285    case OPTION_MDEBUG:
11286      mips_flag_mdebug = TRUE;
11287      break;
11288
11289    case OPTION_NO_MDEBUG:
11290      mips_flag_mdebug = FALSE;
11291      break;
11292
11293    case OPTION_PDR:
11294      mips_flag_pdr = TRUE;
11295      break;
11296
11297    case OPTION_NO_PDR:
11298      mips_flag_pdr = FALSE;
11299      break;
11300#endif /* OBJ_ELF */
11301
11302    default:
11303      return 0;
11304    }
11305
11306  return 1;
11307}
11308
11309/* Set up globals to generate code for the ISA or processor
11310   described by INFO.  */
11311
11312static void
11313mips_set_architecture (const struct mips_cpu_info *info)
11314{
11315  if (info != 0)
11316    {
11317      file_mips_arch = info->cpu;
11318      mips_opts.arch = info->cpu;
11319      mips_opts.isa = info->isa;
11320    }
11321}
11322
11323
11324/* Likewise for tuning.  */
11325
11326static void
11327mips_set_tune (const struct mips_cpu_info *info)
11328{
11329  if (info != 0)
11330    mips_tune = info->cpu;
11331}
11332
11333
11334void
11335mips_after_parse_args (void)
11336{
11337  const struct mips_cpu_info *arch_info = 0;
11338  const struct mips_cpu_info *tune_info = 0;
11339
11340  /* GP relative stuff not working for PE */
11341  if (strncmp (TARGET_OS, "pe", 2) == 0)
11342    {
11343      if (g_switch_seen && g_switch_value != 0)
11344	as_bad (_("-G not supported in this configuration."));
11345      g_switch_value = 0;
11346    }
11347
11348  if (mips_abi == NO_ABI)
11349    mips_abi = MIPS_DEFAULT_ABI;
11350
11351  /* The following code determines the architecture and register size.
11352     Similar code was added to GCC 3.3 (see override_options() in
11353     config/mips/mips.c).  The GAS and GCC code should be kept in sync
11354     as much as possible.  */
11355
11356  if (mips_arch_string != 0)
11357    arch_info = mips_parse_cpu ("-march", mips_arch_string);
11358
11359  if (file_mips_isa != ISA_UNKNOWN)
11360    {
11361      /* Handle -mipsN.  At this point, file_mips_isa contains the
11362	 ISA level specified by -mipsN, while arch_info->isa contains
11363	 the -march selection (if any).  */
11364      if (arch_info != 0)
11365	{
11366	  /* -march takes precedence over -mipsN, since it is more descriptive.
11367	     There's no harm in specifying both as long as the ISA levels
11368	     are the same.  */
11369	  if (file_mips_isa != arch_info->isa)
11370	    as_bad (_("-%s conflicts with the other architecture options, which imply -%s"),
11371		    mips_cpu_info_from_isa (file_mips_isa)->name,
11372		    mips_cpu_info_from_isa (arch_info->isa)->name);
11373	}
11374      else
11375	arch_info = mips_cpu_info_from_isa (file_mips_isa);
11376    }
11377
11378  if (arch_info == 0)
11379    arch_info = mips_parse_cpu ("default CPU", MIPS_CPU_STRING_DEFAULT);
11380
11381  if (ABI_NEEDS_64BIT_REGS (mips_abi) && !ISA_HAS_64BIT_REGS (arch_info->isa))
11382    as_bad ("-march=%s is not compatible with the selected ABI",
11383	    arch_info->name);
11384
11385  mips_set_architecture (arch_info);
11386
11387  /* Optimize for file_mips_arch, unless -mtune selects a different processor.  */
11388  if (mips_tune_string != 0)
11389    tune_info = mips_parse_cpu ("-mtune", mips_tune_string);
11390
11391  if (tune_info == 0)
11392    mips_set_tune (arch_info);
11393  else
11394    mips_set_tune (tune_info);
11395
11396  if (file_mips_gp32 >= 0)
11397    {
11398      /* The user specified the size of the integer registers.  Make sure
11399	 it agrees with the ABI and ISA.  */
11400      if (file_mips_gp32 == 0 && !ISA_HAS_64BIT_REGS (mips_opts.isa))
11401	as_bad (_("-mgp64 used with a 32-bit processor"));
11402      else if (file_mips_gp32 == 1 && ABI_NEEDS_64BIT_REGS (mips_abi))
11403	as_bad (_("-mgp32 used with a 64-bit ABI"));
11404      else if (file_mips_gp32 == 0 && ABI_NEEDS_32BIT_REGS (mips_abi))
11405	as_bad (_("-mgp64 used with a 32-bit ABI"));
11406    }
11407  else
11408    {
11409      /* Infer the integer register size from the ABI and processor.
11410	 Restrict ourselves to 32-bit registers if that's all the
11411	 processor has, or if the ABI cannot handle 64-bit registers.  */
11412      file_mips_gp32 = (ABI_NEEDS_32BIT_REGS (mips_abi)
11413			|| !ISA_HAS_64BIT_REGS (mips_opts.isa));
11414    }
11415
11416  /* ??? GAS treats single-float processors as though they had 64-bit
11417     float registers (although it complains when double-precision
11418     instructions are used).  As things stand, saying they have 32-bit
11419     registers would lead to spurious "register must be even" messages.
11420     So here we assume float registers are always the same size as
11421     integer ones, unless the user says otherwise.  */
11422  if (file_mips_fp32 < 0)
11423    file_mips_fp32 = file_mips_gp32;
11424
11425  /* End of GCC-shared inference code.  */
11426
11427  /* This flag is set when we have a 64-bit capable CPU but use only
11428     32-bit wide registers.  Note that EABI does not use it.  */
11429  if (ISA_HAS_64BIT_REGS (mips_opts.isa)
11430      && ((mips_abi == NO_ABI && file_mips_gp32 == 1)
11431	  || mips_abi == O32_ABI))
11432    mips_32bitmode = 1;
11433
11434  if (mips_opts.isa == ISA_MIPS1 && mips_trap)
11435    as_bad (_("trap exception not supported at ISA 1"));
11436
11437  /* If the selected architecture includes support for ASEs, enable
11438     generation of code for them.  */
11439  if (mips_opts.mips16 == -1)
11440    mips_opts.mips16 = (CPU_HAS_MIPS16 (file_mips_arch)) ? 1 : 0;
11441  if (mips_opts.ase_mips3d == -1)
11442    mips_opts.ase_mips3d = (CPU_HAS_MIPS3D (file_mips_arch)) ? 1 : 0;
11443  if (mips_opts.ase_mdmx == -1)
11444    mips_opts.ase_mdmx = (CPU_HAS_MDMX (file_mips_arch)) ? 1 : 0;
11445  if (mips_opts.ase_dsp == -1)
11446    mips_opts.ase_dsp = (CPU_HAS_DSP (file_mips_arch)) ? 1 : 0;
11447  if (mips_opts.ase_mt == -1)
11448    mips_opts.ase_mt = (CPU_HAS_MT (file_mips_arch)) ? 1 : 0;
11449
11450  file_mips_isa = mips_opts.isa;
11451  file_ase_mips16 = mips_opts.mips16;
11452  file_ase_mips3d = mips_opts.ase_mips3d;
11453  file_ase_mdmx = mips_opts.ase_mdmx;
11454  file_ase_dsp = mips_opts.ase_dsp;
11455  file_ase_mt = mips_opts.ase_mt;
11456  mips_opts.gp32 = file_mips_gp32;
11457  mips_opts.fp32 = file_mips_fp32;
11458
11459  if (mips_flag_mdebug < 0)
11460    {
11461#ifdef OBJ_MAYBE_ECOFF
11462      if (OUTPUT_FLAVOR == bfd_target_ecoff_flavour)
11463	mips_flag_mdebug = 1;
11464      else
11465#endif /* OBJ_MAYBE_ECOFF */
11466	mips_flag_mdebug = 0;
11467    }
11468}
11469
11470void
11471mips_init_after_args (void)
11472{
11473  /* initialize opcodes */
11474  bfd_mips_num_opcodes = bfd_mips_num_builtin_opcodes;
11475  mips_opcodes = (struct mips_opcode *) mips_builtin_opcodes;
11476}
11477
11478long
11479md_pcrel_from (fixS *fixP)
11480{
11481  valueT addr = fixP->fx_where + fixP->fx_frag->fr_address;
11482  switch (fixP->fx_r_type)
11483    {
11484    case BFD_RELOC_16_PCREL_S2:
11485    case BFD_RELOC_MIPS_JMP:
11486      /* Return the address of the delay slot.  */
11487      return addr + 4;
11488    default:
11489      return addr;
11490    }
11491}
11492
11493/* This is called before the symbol table is processed.  In order to
11494   work with gcc when using mips-tfile, we must keep all local labels.
11495   However, in other cases, we want to discard them.  If we were
11496   called with -g, but we didn't see any debugging information, it may
11497   mean that gcc is smuggling debugging information through to
11498   mips-tfile, in which case we must generate all local labels.  */
11499
11500void
11501mips_frob_file_before_adjust (void)
11502{
11503#ifndef NO_ECOFF_DEBUGGING
11504  if (ECOFF_DEBUGGING
11505      && mips_debug != 0
11506      && ! ecoff_debugging_seen)
11507    flag_keep_locals = 1;
11508#endif
11509}
11510
11511/* Sort any unmatched HI16 and GOT16 relocs so that they immediately precede
11512   the corresponding LO16 reloc.  This is called before md_apply_fix3 and
11513   tc_gen_reloc.  Unmatched relocs can only be generated by use of explicit
11514   relocation operators.
11515
11516   For our purposes, a %lo() expression matches a %got() or %hi()
11517   expression if:
11518
11519      (a) it refers to the same symbol; and
11520      (b) the offset applied in the %lo() expression is no lower than
11521	  the offset applied in the %got() or %hi().
11522
11523   (b) allows us to cope with code like:
11524
11525	lui	$4,%hi(foo)
11526	lh	$4,%lo(foo+2)($4)
11527
11528   ...which is legal on RELA targets, and has a well-defined behaviour
11529   if the user knows that adding 2 to "foo" will not induce a carry to
11530   the high 16 bits.
11531
11532   When several %lo()s match a particular %got() or %hi(), we use the
11533   following rules to distinguish them:
11534
11535     (1) %lo()s with smaller offsets are a better match than %lo()s with
11536         higher offsets.
11537
11538     (2) %lo()s with no matching %got() or %hi() are better than those
11539         that already have a matching %got() or %hi().
11540
11541     (3) later %lo()s are better than earlier %lo()s.
11542
11543   These rules are applied in order.
11544
11545   (1) means, among other things, that %lo()s with identical offsets are
11546   chosen if they exist.
11547
11548   (2) means that we won't associate several high-part relocations with
11549   the same low-part relocation unless there's no alternative.  Having
11550   several high parts for the same low part is a GNU extension; this rule
11551   allows careful users to avoid it.
11552
11553   (3) is purely cosmetic.  mips_hi_fixup_list is is in reverse order,
11554   with the last high-part relocation being at the front of the list.
11555   It therefore makes sense to choose the last matching low-part
11556   relocation, all other things being equal.  It's also easier
11557   to code that way.  */
11558
11559void
11560mips_frob_file (void)
11561{
11562  struct mips_hi_fixup *l;
11563
11564  for (l = mips_hi_fixup_list; l != NULL; l = l->next)
11565    {
11566      segment_info_type *seginfo;
11567      bfd_boolean matched_lo_p;
11568      fixS **hi_pos, **lo_pos, **pos;
11569
11570      assert (reloc_needs_lo_p (l->fixp->fx_r_type));
11571
11572      /* If a GOT16 relocation turns out to be against a global symbol,
11573	 there isn't supposed to be a matching LO.  */
11574      if (l->fixp->fx_r_type == BFD_RELOC_MIPS_GOT16
11575	  && !pic_need_relax (l->fixp->fx_addsy, l->seg))
11576	continue;
11577
11578      /* Check quickly whether the next fixup happens to be a matching %lo.  */
11579      if (fixup_has_matching_lo_p (l->fixp))
11580	continue;
11581
11582      seginfo = seg_info (l->seg);
11583
11584      /* Set HI_POS to the position of this relocation in the chain.
11585	 Set LO_POS to the position of the chosen low-part relocation.
11586	 MATCHED_LO_P is true on entry to the loop if *POS is a low-part
11587	 relocation that matches an immediately-preceding high-part
11588	 relocation.  */
11589      hi_pos = NULL;
11590      lo_pos = NULL;
11591      matched_lo_p = FALSE;
11592      for (pos = &seginfo->fix_root; *pos != NULL; pos = &(*pos)->fx_next)
11593	{
11594	  if (*pos == l->fixp)
11595	    hi_pos = pos;
11596
11597	  if ((*pos)->fx_r_type == BFD_RELOC_LO16
11598	      && (*pos)->fx_addsy == l->fixp->fx_addsy
11599	      && (*pos)->fx_offset >= l->fixp->fx_offset
11600	      && (lo_pos == NULL
11601		  || (*pos)->fx_offset < (*lo_pos)->fx_offset
11602		  || (!matched_lo_p
11603		      && (*pos)->fx_offset == (*lo_pos)->fx_offset)))
11604	    lo_pos = pos;
11605
11606	  matched_lo_p = (reloc_needs_lo_p ((*pos)->fx_r_type)
11607			  && fixup_has_matching_lo_p (*pos));
11608	}
11609
11610      /* If we found a match, remove the high-part relocation from its
11611	 current position and insert it before the low-part relocation.
11612	 Make the offsets match so that fixup_has_matching_lo_p()
11613	 will return true.
11614
11615	 We don't warn about unmatched high-part relocations since some
11616	 versions of gcc have been known to emit dead "lui ...%hi(...)"
11617	 instructions.  */
11618      if (lo_pos != NULL)
11619	{
11620	  l->fixp->fx_offset = (*lo_pos)->fx_offset;
11621	  if (l->fixp->fx_next != *lo_pos)
11622	    {
11623	      *hi_pos = l->fixp->fx_next;
11624	      l->fixp->fx_next = *lo_pos;
11625	      *lo_pos = l->fixp;
11626	    }
11627	}
11628    }
11629}
11630
11631/* We may have combined relocations without symbols in the N32/N64 ABI.
11632   We have to prevent gas from dropping them.  */
11633
11634int
11635mips_force_relocation (fixS *fixp)
11636{
11637  if (generic_force_reloc (fixp))
11638    return 1;
11639
11640  if (HAVE_NEWABI
11641      && S_GET_SEGMENT (fixp->fx_addsy) == bfd_abs_section_ptr
11642      && (fixp->fx_r_type == BFD_RELOC_MIPS_SUB
11643	  || fixp->fx_r_type == BFD_RELOC_HI16_S
11644	  || fixp->fx_r_type == BFD_RELOC_LO16))
11645    return 1;
11646
11647  return 0;
11648}
11649
11650/* Apply a fixup to the object file.  */
11651
11652void
11653md_apply_fix3 (fixS *fixP, valueT *valP, segT seg ATTRIBUTE_UNUSED)
11654{
11655  bfd_byte *buf;
11656  long insn;
11657  reloc_howto_type *howto;
11658
11659  /* We ignore generic BFD relocations we don't know about.  */
11660  howto = bfd_reloc_type_lookup (stdoutput, fixP->fx_r_type);
11661  if (! howto)
11662    return;
11663
11664  assert (fixP->fx_size == 4
11665	  || fixP->fx_r_type == BFD_RELOC_16
11666	  || fixP->fx_r_type == BFD_RELOC_64
11667	  || fixP->fx_r_type == BFD_RELOC_CTOR
11668	  || fixP->fx_r_type == BFD_RELOC_MIPS_SUB
11669	  || fixP->fx_r_type == BFD_RELOC_VTABLE_INHERIT
11670	  || fixP->fx_r_type == BFD_RELOC_VTABLE_ENTRY);
11671
11672  buf = (bfd_byte *) (fixP->fx_frag->fr_literal + fixP->fx_where);
11673
11674  assert (! fixP->fx_pcrel || fixP->fx_r_type == BFD_RELOC_16_PCREL_S2);
11675
11676  /* Don't treat parts of a composite relocation as done.  There are two
11677     reasons for this:
11678
11679     (1) The second and third parts will be against 0 (RSS_UNDEF) but
11680	 should nevertheless be emitted if the first part is.
11681
11682     (2) In normal usage, composite relocations are never assembly-time
11683	 constants.  The easiest way of dealing with the pathological
11684	 exceptions is to generate a relocation against STN_UNDEF and
11685	 leave everything up to the linker.  */
11686  if (fixP->fx_addsy == NULL && ! fixP->fx_pcrel && fixP->fx_tcbit == 0)
11687    fixP->fx_done = 1;
11688
11689  switch (fixP->fx_r_type)
11690    {
11691    case BFD_RELOC_MIPS_JMP:
11692    case BFD_RELOC_MIPS_SHIFT5:
11693    case BFD_RELOC_MIPS_SHIFT6:
11694    case BFD_RELOC_MIPS_GOT_DISP:
11695    case BFD_RELOC_MIPS_GOT_PAGE:
11696    case BFD_RELOC_MIPS_GOT_OFST:
11697    case BFD_RELOC_MIPS_SUB:
11698    case BFD_RELOC_MIPS_INSERT_A:
11699    case BFD_RELOC_MIPS_INSERT_B:
11700    case BFD_RELOC_MIPS_DELETE:
11701    case BFD_RELOC_MIPS_HIGHEST:
11702    case BFD_RELOC_MIPS_HIGHER:
11703    case BFD_RELOC_MIPS_SCN_DISP:
11704    case BFD_RELOC_MIPS_REL16:
11705    case BFD_RELOC_MIPS_RELGOT:
11706    case BFD_RELOC_MIPS_JALR:
11707    case BFD_RELOC_HI16:
11708    case BFD_RELOC_HI16_S:
11709    case BFD_RELOC_GPREL16:
11710    case BFD_RELOC_MIPS_LITERAL:
11711    case BFD_RELOC_MIPS_CALL16:
11712    case BFD_RELOC_MIPS_GOT16:
11713    case BFD_RELOC_GPREL32:
11714    case BFD_RELOC_MIPS_GOT_HI16:
11715    case BFD_RELOC_MIPS_GOT_LO16:
11716    case BFD_RELOC_MIPS_CALL_HI16:
11717    case BFD_RELOC_MIPS_CALL_LO16:
11718    case BFD_RELOC_MIPS16_GPREL:
11719      /* Nothing needed to do. The value comes from the reloc entry */
11720      break;
11721
11722    case BFD_RELOC_MIPS16_JMP:
11723      /* We currently always generate a reloc against a symbol, which
11724         means that we don't want an addend even if the symbol is
11725         defined.  */
11726      *valP = 0;
11727      break;
11728
11729    case BFD_RELOC_64:
11730      /* This is handled like BFD_RELOC_32, but we output a sign
11731         extended value if we are only 32 bits.  */
11732      if (fixP->fx_done)
11733	{
11734	  if (8 <= sizeof (valueT))
11735	    md_number_to_chars ((char *) buf, *valP, 8);
11736	  else
11737	    {
11738	      valueT hiv;
11739
11740	      if ((*valP & 0x80000000) != 0)
11741		hiv = 0xffffffff;
11742	      else
11743		hiv = 0;
11744	      md_number_to_chars ((char *)(buf + (target_big_endian ? 4 : 0)),
11745				  *valP, 4);
11746	      md_number_to_chars ((char *)(buf + (target_big_endian ? 0 : 4)),
11747				  hiv, 4);
11748	    }
11749	}
11750      break;
11751
11752    case BFD_RELOC_RVA:
11753    case BFD_RELOC_32:
11754      /* If we are deleting this reloc entry, we must fill in the
11755	 value now.  This can happen if we have a .word which is not
11756	 resolved when it appears but is later defined.   */
11757      if (fixP->fx_done)
11758	md_number_to_chars ((char *) buf, *valP, 4);
11759      break;
11760
11761    case BFD_RELOC_16:
11762      /* If we are deleting this reloc entry, we must fill in the
11763         value now.  */
11764      if (fixP->fx_done)
11765	md_number_to_chars ((char *) buf, *valP, 2);
11766      break;
11767
11768    case BFD_RELOC_LO16:
11769      /* FIXME: Now that embedded-PIC is gone, some of this code/comment
11770	 may be safe to remove, but if so it's not obvious.  */
11771      /* When handling an embedded PIC switch statement, we can wind
11772	 up deleting a LO16 reloc.  See the 'o' case in mips_ip.  */
11773      if (fixP->fx_done)
11774	{
11775	  if (*valP + 0x8000 > 0xffff)
11776	    as_bad_where (fixP->fx_file, fixP->fx_line,
11777			  _("relocation overflow"));
11778	  if (target_big_endian)
11779	    buf += 2;
11780	  md_number_to_chars ((char *) buf, *valP, 2);
11781	}
11782      break;
11783
11784    case BFD_RELOC_16_PCREL_S2:
11785      if ((*valP & 0x3) != 0)
11786	as_bad_where (fixP->fx_file, fixP->fx_line,
11787		      _("Branch to misaligned address (%lx)"), (long) *valP);
11788
11789      /*
11790       * We need to save the bits in the instruction since fixup_segment()
11791       * might be deleting the relocation entry (i.e., a branch within
11792       * the current segment).
11793       */
11794      if (! fixP->fx_done)
11795	break;
11796
11797      /* update old instruction data */
11798      if (target_big_endian)
11799	insn = (buf[0] << 24) | (buf[1] << 16) | (buf[2] << 8) | buf[3];
11800      else
11801	insn = (buf[3] << 24) | (buf[2] << 16) | (buf[1] << 8) | buf[0];
11802
11803      if (*valP + 0x20000 <= 0x3ffff)
11804	{
11805	  insn |= (*valP >> 2) & 0xffff;
11806	  md_number_to_chars ((char *) buf, insn, 4);
11807	}
11808      else if (mips_pic == NO_PIC
11809	       && fixP->fx_done
11810	       && fixP->fx_frag->fr_address >= text_section->vma
11811	       && (fixP->fx_frag->fr_address
11812		   < text_section->vma + text_section->_raw_size)
11813	       && ((insn & 0xffff0000) == 0x10000000	 /* beq $0,$0 */
11814		   || (insn & 0xffff0000) == 0x04010000	 /* bgez $0 */
11815		   || (insn & 0xffff0000) == 0x04110000)) /* bgezal $0 */
11816	{
11817	  /* The branch offset is too large.  If this is an
11818             unconditional branch, and we are not generating PIC code,
11819             we can convert it to an absolute jump instruction.  */
11820	  if ((insn & 0xffff0000) == 0x04110000)	 /* bgezal $0 */
11821	    insn = 0x0c000000;	/* jal */
11822	  else
11823	    insn = 0x08000000;	/* j */
11824	  fixP->fx_r_type = BFD_RELOC_MIPS_JMP;
11825	  fixP->fx_done = 0;
11826	  fixP->fx_addsy = section_symbol (text_section);
11827	  *valP += md_pcrel_from (fixP);
11828	  md_number_to_chars ((char *) buf, insn, 4);
11829	}
11830      else
11831	{
11832	  /* If we got here, we have branch-relaxation disabled,
11833	     and there's nothing we can do to fix this instruction
11834	     without turning it into a longer sequence.  */
11835	  as_bad_where (fixP->fx_file, fixP->fx_line,
11836			_("Branch out of range"));
11837	}
11838      break;
11839
11840    case BFD_RELOC_VTABLE_INHERIT:
11841      fixP->fx_done = 0;
11842      if (fixP->fx_addsy
11843          && !S_IS_DEFINED (fixP->fx_addsy)
11844          && !S_IS_WEAK (fixP->fx_addsy))
11845        S_SET_WEAK (fixP->fx_addsy);
11846      break;
11847
11848    case BFD_RELOC_VTABLE_ENTRY:
11849      fixP->fx_done = 0;
11850      break;
11851
11852    default:
11853      internalError ();
11854    }
11855
11856  /* Remember value for tc_gen_reloc.  */
11857  fixP->fx_addnumber = *valP;
11858}
11859
11860static symbolS *
11861get_symbol (void)
11862{
11863  int c;
11864  char *name;
11865  symbolS *p;
11866
11867  name = input_line_pointer;
11868  c = get_symbol_end ();
11869  p = (symbolS *) symbol_find_or_make (name);
11870  *input_line_pointer = c;
11871  return p;
11872}
11873
11874/* Align the current frag to a given power of two.  The MIPS assembler
11875   also automatically adjusts any preceding label.  */
11876
11877static void
11878mips_align (int to, int fill, symbolS *label)
11879{
11880  mips_emit_delays ();
11881  frag_align (to, fill, 0);
11882  record_alignment (now_seg, to);
11883  if (label != NULL)
11884    {
11885      assert (S_GET_SEGMENT (label) == now_seg);
11886      symbol_set_frag (label, frag_now);
11887      S_SET_VALUE (label, (valueT) frag_now_fix ());
11888    }
11889}
11890
11891/* Align to a given power of two.  .align 0 turns off the automatic
11892   alignment used by the data creating pseudo-ops.  */
11893
11894static void
11895s_align (int x ATTRIBUTE_UNUSED)
11896{
11897  register int temp;
11898  register long temp_fill;
11899  long max_alignment = 15;
11900
11901  /*
11902
11903    o  Note that the assembler pulls down any immediately preceding label
11904       to the aligned address.
11905    o  It's not documented but auto alignment is reinstated by
11906       a .align pseudo instruction.
11907    o  Note also that after auto alignment is turned off the mips assembler
11908       issues an error on attempt to assemble an improperly aligned data item.
11909       We don't.
11910
11911    */
11912
11913  temp = get_absolute_expression ();
11914  if (temp > max_alignment)
11915    as_bad (_("Alignment too large: %d. assumed."), temp = max_alignment);
11916  else if (temp < 0)
11917    {
11918      as_warn (_("Alignment negative: 0 assumed."));
11919      temp = 0;
11920    }
11921  if (*input_line_pointer == ',')
11922    {
11923      ++input_line_pointer;
11924      temp_fill = get_absolute_expression ();
11925    }
11926  else
11927    temp_fill = 0;
11928  if (temp)
11929    {
11930      auto_align = 1;
11931      mips_align (temp, (int) temp_fill,
11932		  insn_labels != NULL ? insn_labels->label : NULL);
11933    }
11934  else
11935    {
11936      auto_align = 0;
11937    }
11938
11939  demand_empty_rest_of_line ();
11940}
11941
11942static void
11943s_change_sec (int sec)
11944{
11945  segT seg;
11946
11947#ifdef OBJ_ELF
11948  /* The ELF backend needs to know that we are changing sections, so
11949     that .previous works correctly.  We could do something like check
11950     for an obj_section_change_hook macro, but that might be confusing
11951     as it would not be appropriate to use it in the section changing
11952     functions in read.c, since obj-elf.c intercepts those.  FIXME:
11953     This should be cleaner, somehow.  */
11954  obj_elf_section_change_hook ();
11955#endif
11956
11957  mips_emit_delays ();
11958  switch (sec)
11959    {
11960    case 't':
11961      s_text (0);
11962      break;
11963    case 'd':
11964      s_data (0);
11965      break;
11966    case 'b':
11967      subseg_set (bss_section, (subsegT) get_absolute_expression ());
11968      demand_empty_rest_of_line ();
11969      break;
11970
11971    case 'r':
11972      seg = subseg_new (RDATA_SECTION_NAME,
11973			(subsegT) get_absolute_expression ());
11974      if (OUTPUT_FLAVOR == bfd_target_elf_flavour)
11975	{
11976	  bfd_set_section_flags (stdoutput, seg, (SEC_ALLOC | SEC_LOAD
11977						  | SEC_READONLY | SEC_RELOC
11978						  | SEC_DATA));
11979	  if (strcmp (TARGET_OS, "elf") != 0)
11980	    record_alignment (seg, 4);
11981	}
11982      demand_empty_rest_of_line ();
11983      break;
11984
11985    case 's':
11986      seg = subseg_new (".sdata", (subsegT) get_absolute_expression ());
11987      if (OUTPUT_FLAVOR == bfd_target_elf_flavour)
11988	{
11989	  bfd_set_section_flags (stdoutput, seg,
11990				 SEC_ALLOC | SEC_LOAD | SEC_RELOC | SEC_DATA);
11991	  if (strcmp (TARGET_OS, "elf") != 0)
11992	    record_alignment (seg, 4);
11993	}
11994      demand_empty_rest_of_line ();
11995      break;
11996    }
11997
11998  auto_align = 1;
11999}
12000
12001void
12002s_change_section (int ignore ATTRIBUTE_UNUSED)
12003{
12004#ifdef OBJ_ELF
12005  char *section_name;
12006  char c;
12007  char next_c = 0;
12008  int section_type;
12009  int section_flag;
12010  int section_entry_size;
12011  int section_alignment;
12012
12013  if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
12014    return;
12015
12016  section_name = input_line_pointer;
12017  c = get_symbol_end ();
12018  if (c)
12019    next_c = *(input_line_pointer + 1);
12020
12021  /* Do we have .section Name<,"flags">?  */
12022  if (c != ',' || (c == ',' && next_c == '"'))
12023    {
12024      /* just after name is now '\0'.  */
12025      *input_line_pointer = c;
12026      input_line_pointer = section_name;
12027      obj_elf_section (ignore);
12028      return;
12029    }
12030  input_line_pointer++;
12031
12032  /* Do we have .section Name<,type><,flag><,entry_size><,alignment>  */
12033  if (c == ',')
12034    section_type = get_absolute_expression ();
12035  else
12036    section_type = 0;
12037  if (*input_line_pointer++ == ',')
12038    section_flag = get_absolute_expression ();
12039  else
12040    section_flag = 0;
12041  if (*input_line_pointer++ == ',')
12042    section_entry_size = get_absolute_expression ();
12043  else
12044    section_entry_size = 0;
12045  if (*input_line_pointer++ == ',')
12046    section_alignment = get_absolute_expression ();
12047  else
12048    section_alignment = 0;
12049
12050  section_name = xstrdup (section_name);
12051
12052  /* When using the generic form of .section (as implemented by obj-elf.c),
12053     there's no way to set the section type to SHT_MIPS_DWARF.  Users have
12054     traditionally had to fall back on the more common @progbits instead.
12055
12056     There's nothing really harmful in this, since bfd will correct
12057     SHT_PROGBITS to SHT_MIPS_DWARF before writing out the file.  But it
12058     means that, for backwards compatibiltiy, the special_section entries
12059     for dwarf sections must use SHT_PROGBITS rather than SHT_MIPS_DWARF.
12060
12061     Even so, we shouldn't force users of the MIPS .section syntax to
12062     incorrectly label the sections as SHT_PROGBITS.  The best compromise
12063     seems to be to map SHT_MIPS_DWARF to SHT_PROGBITS before calling the
12064     generic type-checking code.  */
12065  if (section_type == SHT_MIPS_DWARF)
12066    section_type = SHT_PROGBITS;
12067
12068  obj_elf_change_section (section_name, section_type, section_flag,
12069			  section_entry_size, 0, 0, 0);
12070
12071  if (now_seg->name != section_name)
12072    free (section_name);
12073#endif /* OBJ_ELF */
12074}
12075
12076void
12077mips_enable_auto_align (void)
12078{
12079  auto_align = 1;
12080}
12081
12082static void
12083s_cons (int log_size)
12084{
12085  symbolS *label;
12086
12087  label = insn_labels != NULL ? insn_labels->label : NULL;
12088  mips_emit_delays ();
12089  if (log_size > 0 && auto_align)
12090    mips_align (log_size, 0, label);
12091  mips_clear_insn_labels ();
12092  cons (1 << log_size);
12093}
12094
12095static void
12096s_float_cons (int type)
12097{
12098  symbolS *label;
12099
12100  label = insn_labels != NULL ? insn_labels->label : NULL;
12101
12102  mips_emit_delays ();
12103
12104  if (auto_align)
12105    {
12106      if (type == 'd')
12107	mips_align (3, 0, label);
12108      else
12109	mips_align (2, 0, label);
12110    }
12111
12112  mips_clear_insn_labels ();
12113
12114  float_cons (type);
12115}
12116
12117/* Handle .globl.  We need to override it because on Irix 5 you are
12118   permitted to say
12119       .globl foo .text
12120   where foo is an undefined symbol, to mean that foo should be
12121   considered to be the address of a function.  */
12122
12123static void
12124s_mips_globl (int x ATTRIBUTE_UNUSED)
12125{
12126  char *name;
12127  int c;
12128  symbolS *symbolP;
12129  flagword flag;
12130
12131  do
12132    {
12133      name = input_line_pointer;
12134      c = get_symbol_end ();
12135      symbolP = symbol_find_or_make (name);
12136      S_SET_EXTERNAL (symbolP);
12137
12138      *input_line_pointer = c;
12139      SKIP_WHITESPACE ();
12140
12141      /* On Irix 5, every global symbol that is not explicitly labelled as
12142         being a function is apparently labelled as being an object.  */
12143      flag = BSF_OBJECT;
12144
12145      if (!is_end_of_line[(unsigned char) *input_line_pointer]
12146	  && (*input_line_pointer != ','))
12147	{
12148	  char *secname;
12149	  asection *sec;
12150
12151	  secname = input_line_pointer;
12152	  c = get_symbol_end ();
12153	  sec = bfd_get_section_by_name (stdoutput, secname);
12154	  if (sec == NULL)
12155	    as_bad (_("%s: no such section"), secname);
12156	  *input_line_pointer = c;
12157
12158	  if (sec != NULL && (sec->flags & SEC_CODE) != 0)
12159	    flag = BSF_FUNCTION;
12160	}
12161
12162      symbol_get_bfdsym (symbolP)->flags |= flag;
12163
12164      c = *input_line_pointer;
12165      if (c == ',')
12166	{
12167	  input_line_pointer++;
12168	  SKIP_WHITESPACE ();
12169	  if (is_end_of_line[(unsigned char) *input_line_pointer])
12170	    c = '\n';
12171	}
12172    }
12173  while (c == ',');
12174
12175  demand_empty_rest_of_line ();
12176}
12177
12178static void
12179s_option (int x ATTRIBUTE_UNUSED)
12180{
12181  char *opt;
12182  char c;
12183
12184  opt = input_line_pointer;
12185  c = get_symbol_end ();
12186
12187  if (*opt == 'O')
12188    {
12189      /* FIXME: What does this mean?  */
12190    }
12191  else if (strncmp (opt, "pic", 3) == 0)
12192    {
12193      int i;
12194
12195      i = atoi (opt + 3);
12196      if (i == 0)
12197	mips_pic = NO_PIC;
12198      else if (i == 2)
12199	{
12200	mips_pic = SVR4_PIC;
12201	  mips_abicalls = TRUE;
12202	}
12203      else
12204	as_bad (_(".option pic%d not supported"), i);
12205
12206      if (mips_pic == SVR4_PIC)
12207	{
12208	  if (g_switch_seen && g_switch_value != 0)
12209	    as_warn (_("-G may not be used with SVR4 PIC code"));
12210	  g_switch_value = 0;
12211	  bfd_set_gp_size (stdoutput, 0);
12212	}
12213    }
12214  else
12215    as_warn (_("Unrecognized option \"%s\""), opt);
12216
12217  *input_line_pointer = c;
12218  demand_empty_rest_of_line ();
12219}
12220
12221/* This structure is used to hold a stack of .set values.  */
12222
12223struct mips_option_stack
12224{
12225  struct mips_option_stack *next;
12226  struct mips_set_options options;
12227};
12228
12229static struct mips_option_stack *mips_opts_stack;
12230
12231/* Handle the .set pseudo-op.  */
12232
12233static void
12234s_mipsset (int x ATTRIBUTE_UNUSED)
12235{
12236  char *name = input_line_pointer, ch;
12237
12238  while (!is_end_of_line[(unsigned char) *input_line_pointer])
12239    ++input_line_pointer;
12240  ch = *input_line_pointer;
12241  *input_line_pointer = '\0';
12242
12243  if (strcmp (name, "reorder") == 0)
12244    {
12245      if (mips_opts.noreorder)
12246	end_noreorder ();
12247    }
12248  else if (strcmp (name, "noreorder") == 0)
12249    {
12250      if (!mips_opts.noreorder)
12251	start_noreorder ();
12252    }
12253  else if (strcmp (name, "at") == 0)
12254    {
12255      mips_opts.noat = 0;
12256    }
12257  else if (strcmp (name, "noat") == 0)
12258    {
12259      mips_opts.noat = 1;
12260    }
12261  else if (strcmp (name, "macro") == 0)
12262    {
12263      mips_opts.warn_about_macros = 0;
12264    }
12265  else if (strcmp (name, "nomacro") == 0)
12266    {
12267      if (mips_opts.noreorder == 0)
12268	as_bad (_("`noreorder' must be set before `nomacro'"));
12269      mips_opts.warn_about_macros = 1;
12270    }
12271  else if (strcmp (name, "move") == 0 || strcmp (name, "novolatile") == 0)
12272    {
12273      mips_opts.nomove = 0;
12274    }
12275  else if (strcmp (name, "nomove") == 0 || strcmp (name, "volatile") == 0)
12276    {
12277      mips_opts.nomove = 1;
12278    }
12279  else if (strcmp (name, "bopt") == 0)
12280    {
12281      mips_opts.nobopt = 0;
12282    }
12283  else if (strcmp (name, "nobopt") == 0)
12284    {
12285      mips_opts.nobopt = 1;
12286    }
12287  else if (strcmp (name, "mips16") == 0
12288	   || strcmp (name, "MIPS-16") == 0)
12289    mips_opts.mips16 = 1;
12290  else if (strcmp (name, "nomips16") == 0
12291	   || strcmp (name, "noMIPS-16") == 0)
12292    mips_opts.mips16 = 0;
12293  else if (strcmp (name, "mips3d") == 0)
12294    mips_opts.ase_mips3d = 1;
12295  else if (strcmp (name, "nomips3d") == 0)
12296    mips_opts.ase_mips3d = 0;
12297  else if (strcmp (name, "mdmx") == 0)
12298    mips_opts.ase_mdmx = 1;
12299  else if (strcmp (name, "nomdmx") == 0)
12300    mips_opts.ase_mdmx = 0;
12301  else if (strcmp (name, "dsp") == 0)
12302    mips_opts.ase_dsp = 1;
12303  else if (strcmp (name, "nodsp") == 0)
12304    mips_opts.ase_dsp = 0;
12305  else if (strcmp (name, "mt") == 0)
12306    mips_opts.ase_mt = 1;
12307  else if (strcmp (name, "nomt") == 0)
12308    mips_opts.ase_mt = 0;
12309  else if (strncmp (name, "mips", 4) == 0 || strncmp (name, "arch=", 5) == 0)
12310    {
12311      int reset = 0;
12312
12313      /* Permit the user to change the ISA and architecture on the fly.
12314	 Needless to say, misuse can cause serious problems.  */
12315      if (strcmp (name, "mips0") == 0 || strcmp (name, "arch=default") == 0)
12316	{
12317	  reset = 1;
12318	  mips_opts.isa = file_mips_isa;
12319	  mips_opts.arch = file_mips_arch;
12320	}
12321      else if (strncmp (name, "arch=", 5) == 0)
12322	{
12323	  const struct mips_cpu_info *p;
12324
12325	  p = mips_parse_cpu("internal use", name + 5);
12326	  if (!p)
12327	    as_bad (_("unknown architecture %s"), name + 5);
12328	  else
12329	    {
12330	      mips_opts.arch = p->cpu;
12331	      mips_opts.isa = p->isa;
12332	    }
12333	}
12334      else if (strncmp (name, "mips", 4) == 0)
12335	{
12336	  const struct mips_cpu_info *p;
12337
12338	  p = mips_parse_cpu("internal use", name);
12339	  if (!p)
12340	    as_bad (_("unknown ISA level %s"), name + 4);
12341	  else
12342	    {
12343	      mips_opts.arch = p->cpu;
12344	      mips_opts.isa = p->isa;
12345	    }
12346	}
12347      else
12348	as_bad (_("unknown ISA or architecture %s"), name);
12349
12350      switch (mips_opts.isa)
12351	{
12352	case  0:
12353	  break;
12354	case ISA_MIPS1:
12355	case ISA_MIPS2:
12356	case ISA_MIPS32:
12357	case ISA_MIPS32R2:
12358	  mips_opts.gp32 = 1;
12359	  mips_opts.fp32 = 1;
12360	  break;
12361	case ISA_MIPS3:
12362	case ISA_MIPS4:
12363	case ISA_MIPS5:
12364	case ISA_MIPS64:
12365	case ISA_MIPS64R2:
12366	  mips_opts.gp32 = 0;
12367	  mips_opts.fp32 = 0;
12368	  break;
12369	default:
12370	  as_bad (_("unknown ISA level %s"), name + 4);
12371	  break;
12372	}
12373      if (reset)
12374	{
12375	  mips_opts.gp32 = file_mips_gp32;
12376	  mips_opts.fp32 = file_mips_fp32;
12377	}
12378    }
12379  else if (strcmp (name, "autoextend") == 0)
12380    mips_opts.noautoextend = 0;
12381  else if (strcmp (name, "noautoextend") == 0)
12382    mips_opts.noautoextend = 1;
12383  else if (strcmp (name, "push") == 0)
12384    {
12385      struct mips_option_stack *s;
12386
12387      s = (struct mips_option_stack *) xmalloc (sizeof *s);
12388      s->next = mips_opts_stack;
12389      s->options = mips_opts;
12390      mips_opts_stack = s;
12391    }
12392  else if (strcmp (name, "pop") == 0)
12393    {
12394      struct mips_option_stack *s;
12395
12396      s = mips_opts_stack;
12397      if (s == NULL)
12398	as_bad (_(".set pop with no .set push"));
12399      else
12400	{
12401	  /* If we're changing the reorder mode we need to handle
12402             delay slots correctly.  */
12403	  if (s->options.noreorder && ! mips_opts.noreorder)
12404	    start_noreorder ();
12405	  else if (! s->options.noreorder && mips_opts.noreorder)
12406	    end_noreorder ();
12407
12408	  mips_opts = s->options;
12409	  mips_opts_stack = s->next;
12410	  free (s);
12411	}
12412    }
12413  else if (strcmp (name, "sym32") == 0)
12414    mips_opts.sym32 = TRUE;
12415  else if (strcmp (name, "nosym32") == 0)
12416    mips_opts.sym32 = FALSE;
12417  else
12418    {
12419      as_warn (_("Tried to set unrecognized symbol: %s\n"), name);
12420    }
12421  *input_line_pointer = ch;
12422  demand_empty_rest_of_line ();
12423}
12424
12425/* Handle the .abicalls pseudo-op.  I believe this is equivalent to
12426   .option pic2.  It means to generate SVR4 PIC calls.  */
12427
12428static void
12429s_abicalls (int ignore ATTRIBUTE_UNUSED)
12430{
12431  mips_pic = SVR4_PIC;
12432  mips_abicalls = TRUE;
12433
12434  if (g_switch_seen && g_switch_value != 0)
12435    as_warn (_("-G may not be used with SVR4 PIC code"));
12436  g_switch_value = 0;
12437
12438  bfd_set_gp_size (stdoutput, 0);
12439  demand_empty_rest_of_line ();
12440}
12441
12442/* Handle the .cpload pseudo-op.  This is used when generating SVR4
12443   PIC code.  It sets the $gp register for the function based on the
12444   function address, which is in the register named in the argument.
12445   This uses a relocation against _gp_disp, which is handled specially
12446   by the linker.  The result is:
12447	lui	$gp,%hi(_gp_disp)
12448	addiu	$gp,$gp,%lo(_gp_disp)
12449	addu	$gp,$gp,.cpload argument
12450   The .cpload argument is normally $25 == $t9.
12451
12452   The -mno-shared option changes this to:
12453	lui	$gp,%hi(__gnu_local_gp)
12454	addiu	$gp,$gp,%lo(__gnu_local_gp)
12455   and the argument is ignored.  This saves an instruction, but the
12456   resulting code is not position independent; it uses an absolute
12457   address for __gnu_local_gp.  Thus code assembled with -mno-shared
12458   can go into an ordinary executable, but not into a shared library.  */
12459
12460static void
12461s_cpload (int ignore ATTRIBUTE_UNUSED)
12462{
12463  expressionS ex;
12464  int reg;
12465  int in_shared;
12466
12467  /* If we are not generating SVR4 PIC code, or if this is NewABI code,
12468     .cpload is ignored.  */
12469  if (mips_pic != SVR4_PIC || HAVE_NEWABI)
12470    {
12471      s_ignore (0);
12472      return;
12473    }
12474
12475  /* .cpload should be in a .set noreorder section.  */
12476  if (mips_opts.noreorder == 0)
12477    as_warn (_(".cpload not in noreorder section"));
12478
12479  reg = tc_get_register (0);
12480
12481  /* If we need to produce a 64-bit address, we are better off using
12482     the default instruction sequence.  */
12483  in_shared = mips_in_shared || HAVE_64BIT_SYMBOLS;
12484
12485  ex.X_op = O_symbol;
12486  ex.X_add_symbol = symbol_find_or_make (in_shared ? "_gp_disp" :
12487                                         "__gnu_local_gp");
12488  ex.X_op_symbol = NULL;
12489  ex.X_add_number = 0;
12490
12491  /* In ELF, this symbol is implicitly an STT_OBJECT symbol.  */
12492  symbol_get_bfdsym (ex.X_add_symbol)->flags |= BSF_OBJECT;
12493
12494  macro_start ();
12495  macro_build_lui (&ex, mips_gp_register);
12496  macro_build (&ex, "addiu", "t,r,j", mips_gp_register,
12497	       mips_gp_register, BFD_RELOC_LO16);
12498  if (in_shared)
12499    macro_build (NULL, "addu", "d,v,t", mips_gp_register,
12500		 mips_gp_register, reg);
12501  macro_end ();
12502
12503  demand_empty_rest_of_line ();
12504}
12505
12506/* Handle the .cpsetup pseudo-op defined for NewABI PIC code.  The syntax is:
12507     .cpsetup $reg1, offset|$reg2, label
12508
12509   If offset is given, this results in:
12510     sd		$gp, offset($sp)
12511     lui	$gp, %hi(%neg(%gp_rel(label)))
12512     addiu	$gp, $gp, %lo(%neg(%gp_rel(label)))
12513     daddu	$gp, $gp, $reg1
12514
12515   If $reg2 is given, this results in:
12516     daddu	$reg2, $gp, $0
12517     lui	$gp, %hi(%neg(%gp_rel(label)))
12518     addiu	$gp, $gp, %lo(%neg(%gp_rel(label)))
12519     daddu	$gp, $gp, $reg1
12520   $reg1 is normally $25 == $t9.
12521
12522   The -mno-shared option replaces the last three instructions with
12523	lui	$gp,%hi(_gp)
12524	addiu	$gp,$gp,%lo(_gp)
12525   */
12526
12527static void
12528s_cpsetup (int ignore ATTRIBUTE_UNUSED)
12529{
12530  expressionS ex_off;
12531  expressionS ex_sym;
12532  int reg1;
12533
12534  /* If we are not generating SVR4 PIC code, .cpsetup is ignored.
12535     We also need NewABI support.  */
12536  if (mips_pic != SVR4_PIC || ! HAVE_NEWABI)
12537    {
12538      s_ignore (0);
12539      return;
12540    }
12541
12542  reg1 = tc_get_register (0);
12543  SKIP_WHITESPACE ();
12544  if (*input_line_pointer != ',')
12545    {
12546      as_bad (_("missing argument separator ',' for .cpsetup"));
12547      return;
12548    }
12549  else
12550    ++input_line_pointer;
12551  SKIP_WHITESPACE ();
12552  if (*input_line_pointer == '$')
12553    {
12554      mips_cpreturn_register = tc_get_register (0);
12555      mips_cpreturn_offset = -1;
12556    }
12557  else
12558    {
12559      mips_cpreturn_offset = get_absolute_expression ();
12560      mips_cpreturn_register = -1;
12561    }
12562  SKIP_WHITESPACE ();
12563  if (*input_line_pointer != ',')
12564    {
12565      as_bad (_("missing argument separator ',' for .cpsetup"));
12566      return;
12567    }
12568  else
12569    ++input_line_pointer;
12570  SKIP_WHITESPACE ();
12571  expression (&ex_sym);
12572
12573  macro_start ();
12574  if (mips_cpreturn_register == -1)
12575    {
12576      ex_off.X_op = O_constant;
12577      ex_off.X_add_symbol = NULL;
12578      ex_off.X_op_symbol = NULL;
12579      ex_off.X_add_number = mips_cpreturn_offset;
12580
12581      macro_build (&ex_off, "sd", "t,o(b)", mips_gp_register,
12582		   BFD_RELOC_LO16, SP);
12583    }
12584  else
12585    macro_build (NULL, "daddu", "d,v,t", mips_cpreturn_register,
12586		 mips_gp_register, 0);
12587
12588  if (mips_in_shared || HAVE_64BIT_SYMBOLS)
12589    {
12590      macro_build (&ex_sym, "lui", "t,u", mips_gp_register,
12591		   -1, BFD_RELOC_GPREL16, BFD_RELOC_MIPS_SUB,
12592		   BFD_RELOC_HI16_S);
12593
12594      macro_build (&ex_sym, "addiu", "t,r,j", mips_gp_register,
12595		   mips_gp_register, -1, BFD_RELOC_GPREL16,
12596		   BFD_RELOC_MIPS_SUB, BFD_RELOC_LO16);
12597
12598      macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", mips_gp_register,
12599		   mips_gp_register, reg1);
12600    }
12601  else
12602    {
12603      expressionS ex;
12604
12605      ex.X_op = O_symbol;
12606      ex.X_add_symbol = symbol_find_or_make ("__gnu_local_gp");
12607      ex.X_op_symbol = NULL;
12608      ex.X_add_number = 0;
12609
12610      /* In ELF, this symbol is implicitly an STT_OBJECT symbol.  */
12611      symbol_get_bfdsym (ex.X_add_symbol)->flags |= BSF_OBJECT;
12612
12613      macro_build_lui (&ex, mips_gp_register);
12614      macro_build (&ex, "addiu", "t,r,j", mips_gp_register,
12615		   mips_gp_register, BFD_RELOC_LO16);
12616    }
12617
12618  macro_end ();
12619
12620  demand_empty_rest_of_line ();
12621}
12622
12623static void
12624s_cplocal (int ignore ATTRIBUTE_UNUSED)
12625{
12626  /* If we are not generating SVR4 PIC code, or if this is not NewABI code,
12627   .cplocal is ignored.  */
12628  if (mips_pic != SVR4_PIC || ! HAVE_NEWABI)
12629    {
12630      s_ignore (0);
12631      return;
12632    }
12633
12634  mips_gp_register = tc_get_register (0);
12635  demand_empty_rest_of_line ();
12636}
12637
12638/* Handle the .cprestore pseudo-op.  This stores $gp into a given
12639   offset from $sp.  The offset is remembered, and after making a PIC
12640   call $gp is restored from that location.  */
12641
12642static void
12643s_cprestore (int ignore ATTRIBUTE_UNUSED)
12644{
12645  expressionS ex;
12646
12647  /* If we are not generating SVR4 PIC code, or if this is NewABI code,
12648     .cprestore is ignored.  */
12649  if (mips_pic != SVR4_PIC || HAVE_NEWABI)
12650    {
12651      s_ignore (0);
12652      return;
12653    }
12654
12655  mips_cprestore_offset = get_absolute_expression ();
12656  mips_cprestore_valid = 1;
12657
12658  ex.X_op = O_constant;
12659  ex.X_add_symbol = NULL;
12660  ex.X_op_symbol = NULL;
12661  ex.X_add_number = mips_cprestore_offset;
12662
12663  macro_start ();
12664  macro_build_ldst_constoffset (&ex, ADDRESS_STORE_INSN, mips_gp_register,
12665				SP, HAVE_64BIT_ADDRESSES);
12666  macro_end ();
12667
12668  demand_empty_rest_of_line ();
12669}
12670
12671/* Handle the .cpreturn pseudo-op defined for NewABI PIC code. If an offset
12672   was given in the preceding .cpsetup, it results in:
12673     ld		$gp, offset($sp)
12674
12675   If a register $reg2 was given there, it results in:
12676     daddu	$gp, $reg2, $0
12677 */
12678static void
12679s_cpreturn (int ignore ATTRIBUTE_UNUSED)
12680{
12681  expressionS ex;
12682
12683  /* If we are not generating SVR4 PIC code, .cpreturn is ignored.
12684     We also need NewABI support.  */
12685  if (mips_pic != SVR4_PIC || ! HAVE_NEWABI)
12686    {
12687      s_ignore (0);
12688      return;
12689    }
12690
12691  macro_start ();
12692  if (mips_cpreturn_register == -1)
12693    {
12694      ex.X_op = O_constant;
12695      ex.X_add_symbol = NULL;
12696      ex.X_op_symbol = NULL;
12697      ex.X_add_number = mips_cpreturn_offset;
12698
12699      macro_build (&ex, "ld", "t,o(b)", mips_gp_register, BFD_RELOC_LO16, SP);
12700    }
12701  else
12702    macro_build (NULL, "daddu", "d,v,t", mips_gp_register,
12703		 mips_cpreturn_register, 0);
12704  macro_end ();
12705
12706  demand_empty_rest_of_line ();
12707}
12708
12709/* Handle the .gpvalue pseudo-op.  This is used when generating NewABI PIC
12710   code.  It sets the offset to use in gp_rel relocations.  */
12711
12712static void
12713s_gpvalue (int ignore ATTRIBUTE_UNUSED)
12714{
12715  /* If we are not generating SVR4 PIC code, .gpvalue is ignored.
12716     We also need NewABI support.  */
12717  if (mips_pic != SVR4_PIC || ! HAVE_NEWABI)
12718    {
12719      s_ignore (0);
12720      return;
12721    }
12722
12723  mips_gprel_offset = get_absolute_expression ();
12724
12725  demand_empty_rest_of_line ();
12726}
12727
12728/* Handle the .gpword pseudo-op.  This is used when generating PIC
12729   code.  It generates a 32 bit GP relative reloc.  */
12730
12731static void
12732s_gpword (int ignore ATTRIBUTE_UNUSED)
12733{
12734  symbolS *label;
12735  expressionS ex;
12736  char *p;
12737
12738  /* When not generating PIC code, this is treated as .word.  */
12739  if (mips_pic != SVR4_PIC)
12740    {
12741      s_cons (2);
12742      return;
12743    }
12744
12745  label = insn_labels != NULL ? insn_labels->label : NULL;
12746  mips_emit_delays ();
12747  if (auto_align)
12748    mips_align (2, 0, label);
12749  mips_clear_insn_labels ();
12750
12751  expression (&ex);
12752
12753  if (ex.X_op != O_symbol || ex.X_add_number != 0)
12754    {
12755      as_bad (_("Unsupported use of .gpword"));
12756      ignore_rest_of_line ();
12757    }
12758
12759  p = frag_more (4);
12760  md_number_to_chars (p, 0, 4);
12761  fix_new_exp (frag_now, p - frag_now->fr_literal, 4, &ex, FALSE,
12762	       BFD_RELOC_GPREL32);
12763
12764  demand_empty_rest_of_line ();
12765}
12766
12767static void
12768s_gpdword (int ignore ATTRIBUTE_UNUSED)
12769{
12770  symbolS *label;
12771  expressionS ex;
12772  char *p;
12773
12774  /* When not generating PIC code, this is treated as .dword.  */
12775  if (mips_pic != SVR4_PIC)
12776    {
12777      s_cons (3);
12778      return;
12779    }
12780
12781  label = insn_labels != NULL ? insn_labels->label : NULL;
12782  mips_emit_delays ();
12783  if (auto_align)
12784    mips_align (3, 0, label);
12785  mips_clear_insn_labels ();
12786
12787  expression (&ex);
12788
12789  if (ex.X_op != O_symbol || ex.X_add_number != 0)
12790    {
12791      as_bad (_("Unsupported use of .gpdword"));
12792      ignore_rest_of_line ();
12793    }
12794
12795  p = frag_more (8);
12796  md_number_to_chars (p, 0, 8);
12797  fix_new_exp (frag_now, p - frag_now->fr_literal, 4, &ex, FALSE,
12798	       BFD_RELOC_GPREL32)->fx_tcbit = 1;
12799
12800  /* GPREL32 composed with 64 gives a 64-bit GP offset.  */
12801  fix_new (frag_now, p - frag_now->fr_literal, 8, NULL, 0,
12802	   FALSE, BFD_RELOC_64)->fx_tcbit = 1;
12803
12804  demand_empty_rest_of_line ();
12805}
12806
12807/* Handle the .cpadd pseudo-op.  This is used when dealing with switch
12808   tables in SVR4 PIC code.  */
12809
12810static void
12811s_cpadd (int ignore ATTRIBUTE_UNUSED)
12812{
12813  int reg;
12814
12815  /* This is ignored when not generating SVR4 PIC code.  */
12816  if (mips_pic != SVR4_PIC)
12817    {
12818      s_ignore (0);
12819      return;
12820    }
12821
12822  /* Add $gp to the register named as an argument.  */
12823  macro_start ();
12824  reg = tc_get_register (0);
12825  macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", reg, reg, mips_gp_register);
12826  macro_end ();
12827
12828  demand_empty_rest_of_line ();
12829}
12830
12831/* Handle the .insn pseudo-op.  This marks instruction labels in
12832   mips16 mode.  This permits the linker to handle them specially,
12833   such as generating jalx instructions when needed.  We also make
12834   them odd for the duration of the assembly, in order to generate the
12835   right sort of code.  We will make them even in the adjust_symtab
12836   routine, while leaving them marked.  This is convenient for the
12837   debugger and the disassembler.  The linker knows to make them odd
12838   again.  */
12839
12840static void
12841s_insn (int ignore ATTRIBUTE_UNUSED)
12842{
12843  mips16_mark_labels ();
12844
12845  demand_empty_rest_of_line ();
12846}
12847
12848/* Handle a .stabn directive.  We need these in order to mark a label
12849   as being a mips16 text label correctly.  Sometimes the compiler
12850   will emit a label, followed by a .stabn, and then switch sections.
12851   If the label and .stabn are in mips16 mode, then the label is
12852   really a mips16 text label.  */
12853
12854static void
12855s_mips_stab (int type)
12856{
12857  if (type == 'n')
12858    mips16_mark_labels ();
12859
12860  s_stab (type);
12861}
12862
12863/* Handle the .weakext pseudo-op as defined in Kane and Heinrich.
12864 */
12865
12866static void
12867s_mips_weakext (int ignore ATTRIBUTE_UNUSED)
12868{
12869  char *name;
12870  int c;
12871  symbolS *symbolP;
12872  expressionS exp;
12873
12874  name = input_line_pointer;
12875  c = get_symbol_end ();
12876  symbolP = symbol_find_or_make (name);
12877  S_SET_WEAK (symbolP);
12878  *input_line_pointer = c;
12879
12880  SKIP_WHITESPACE ();
12881
12882  if (! is_end_of_line[(unsigned char) *input_line_pointer])
12883    {
12884      if (S_IS_DEFINED (symbolP))
12885	{
12886	  as_bad ("ignoring attempt to redefine symbol %s",
12887		  S_GET_NAME (symbolP));
12888	  ignore_rest_of_line ();
12889	  return;
12890	}
12891
12892      if (*input_line_pointer == ',')
12893	{
12894	  ++input_line_pointer;
12895	  SKIP_WHITESPACE ();
12896	}
12897
12898      expression (&exp);
12899      if (exp.X_op != O_symbol)
12900	{
12901	  as_bad ("bad .weakext directive");
12902	  ignore_rest_of_line ();
12903	  return;
12904	}
12905      symbol_set_value_expression (symbolP, &exp);
12906    }
12907
12908  demand_empty_rest_of_line ();
12909}
12910
12911/* Parse a register string into a number.  Called from the ECOFF code
12912   to parse .frame.  The argument is non-zero if this is the frame
12913   register, so that we can record it in mips_frame_reg.  */
12914
12915int
12916tc_get_register (int frame)
12917{
12918  int reg;
12919
12920  SKIP_WHITESPACE ();
12921  if (*input_line_pointer++ != '$')
12922    {
12923      as_warn (_("expected `$'"));
12924      reg = ZERO;
12925    }
12926  else if (ISDIGIT (*input_line_pointer))
12927    {
12928      reg = get_absolute_expression ();
12929      if (reg < 0 || reg >= 32)
12930	{
12931	  as_warn (_("Bad register number"));
12932	  reg = ZERO;
12933	}
12934    }
12935  else
12936    {
12937      if (strncmp (input_line_pointer, "ra", 2) == 0)
12938	{
12939	  reg = RA;
12940	  input_line_pointer += 2;
12941	}
12942      else if (strncmp (input_line_pointer, "fp", 2) == 0)
12943	{
12944	  reg = FP;
12945	  input_line_pointer += 2;
12946	}
12947      else if (strncmp (input_line_pointer, "sp", 2) == 0)
12948	{
12949	  reg = SP;
12950	  input_line_pointer += 2;
12951	}
12952      else if (strncmp (input_line_pointer, "gp", 2) == 0)
12953	{
12954	  reg = GP;
12955	  input_line_pointer += 2;
12956	}
12957      else if (strncmp (input_line_pointer, "at", 2) == 0)
12958	{
12959	  reg = AT;
12960	  input_line_pointer += 2;
12961	}
12962      else if (strncmp (input_line_pointer, "kt0", 3) == 0)
12963	{
12964	  reg = KT0;
12965	  input_line_pointer += 3;
12966	}
12967      else if (strncmp (input_line_pointer, "kt1", 3) == 0)
12968	{
12969	  reg = KT1;
12970	  input_line_pointer += 3;
12971	}
12972      else if (strncmp (input_line_pointer, "zero", 4) == 0)
12973	{
12974	  reg = ZERO;
12975	  input_line_pointer += 4;
12976	}
12977      else
12978	{
12979	  as_warn (_("Unrecognized register name"));
12980	  reg = ZERO;
12981	  while (ISALNUM(*input_line_pointer))
12982	   input_line_pointer++;
12983	}
12984    }
12985  if (frame)
12986    {
12987      mips_frame_reg = reg != 0 ? reg : SP;
12988      mips_frame_reg_valid = 1;
12989      mips_cprestore_valid = 0;
12990    }
12991  return reg;
12992}
12993
12994valueT
12995md_section_align (asection *seg, valueT addr)
12996{
12997  int align = bfd_get_section_alignment (stdoutput, seg);
12998
12999#ifdef OBJ_ELF
13000  /* We don't need to align ELF sections to the full alignment.
13001     However, Irix 5 may prefer that we align them at least to a 16
13002     byte boundary.  We don't bother to align the sections if we are
13003     targeted for an embedded system.  */
13004  if (strcmp (TARGET_OS, "elf") == 0)
13005    return addr;
13006  if (align > 4)
13007    align = 4;
13008#endif
13009
13010  return ((addr + (1 << align) - 1) & (-1 << align));
13011}
13012
13013/* Utility routine, called from above as well.  If called while the
13014   input file is still being read, it's only an approximation.  (For
13015   example, a symbol may later become defined which appeared to be
13016   undefined earlier.)  */
13017
13018static int
13019nopic_need_relax (symbolS *sym, int before_relaxing)
13020{
13021  if (sym == 0)
13022    return 0;
13023
13024  if (g_switch_value > 0)
13025    {
13026      const char *symname;
13027      int change;
13028
13029      /* Find out whether this symbol can be referenced off the $gp
13030	 register.  It can be if it is smaller than the -G size or if
13031	 it is in the .sdata or .sbss section.  Certain symbols can
13032	 not be referenced off the $gp, although it appears as though
13033	 they can.  */
13034      symname = S_GET_NAME (sym);
13035      if (symname != (const char *) NULL
13036	  && (strcmp (symname, "eprol") == 0
13037	      || strcmp (symname, "etext") == 0
13038	      || strcmp (symname, "_gp") == 0
13039	      || strcmp (symname, "edata") == 0
13040	      || strcmp (symname, "_fbss") == 0
13041	      || strcmp (symname, "_fdata") == 0
13042	      || strcmp (symname, "_ftext") == 0
13043	      || strcmp (symname, "end") == 0
13044	      || strcmp (symname, "_gp_disp") == 0))
13045	change = 1;
13046      else if ((! S_IS_DEFINED (sym) || S_IS_COMMON (sym))
13047	       && (0
13048#ifndef NO_ECOFF_DEBUGGING
13049		   || (symbol_get_obj (sym)->ecoff_extern_size != 0
13050		       && (symbol_get_obj (sym)->ecoff_extern_size
13051			   <= g_switch_value))
13052#endif
13053		   /* We must defer this decision until after the whole
13054		      file has been read, since there might be a .extern
13055		      after the first use of this symbol.  */
13056		   || (before_relaxing
13057#ifndef NO_ECOFF_DEBUGGING
13058		       && symbol_get_obj (sym)->ecoff_extern_size == 0
13059#endif
13060		       && S_GET_VALUE (sym) == 0)
13061		   || (S_GET_VALUE (sym) != 0
13062		       && S_GET_VALUE (sym) <= g_switch_value)))
13063	change = 0;
13064      else
13065	{
13066	  const char *segname;
13067
13068	  segname = segment_name (S_GET_SEGMENT (sym));
13069	  assert (strcmp (segname, ".lit8") != 0
13070		  && strcmp (segname, ".lit4") != 0);
13071	  change = (strcmp (segname, ".sdata") != 0
13072		    && strcmp (segname, ".sbss") != 0
13073		    && strncmp (segname, ".sdata.", 7) != 0
13074		    && strncmp (segname, ".gnu.linkonce.s.", 16) != 0);
13075	}
13076      return change;
13077    }
13078  else
13079    /* We are not optimizing for the $gp register.  */
13080    return 1;
13081}
13082
13083
13084/* Return true if the given symbol should be considered local for SVR4 PIC.  */
13085
13086static bfd_boolean
13087pic_need_relax (symbolS *sym, asection *segtype)
13088{
13089  asection *symsec;
13090  bfd_boolean linkonce;
13091
13092  /* Handle the case of a symbol equated to another symbol.  */
13093  while (symbol_equated_reloc_p (sym))
13094    {
13095      symbolS *n;
13096
13097      /* It's possible to get a loop here in a badly written
13098	 program.  */
13099      n = symbol_get_value_expression (sym)->X_add_symbol;
13100      if (n == sym)
13101	break;
13102      sym = n;
13103    }
13104
13105  symsec = S_GET_SEGMENT (sym);
13106
13107  /* duplicate the test for LINK_ONCE sections as in adjust_reloc_syms */
13108  linkonce = FALSE;
13109  if (symsec != segtype && ! S_IS_LOCAL (sym))
13110    {
13111      if ((bfd_get_section_flags (stdoutput, symsec) & SEC_LINK_ONCE)
13112	  != 0)
13113	linkonce = TRUE;
13114
13115      /* The GNU toolchain uses an extension for ELF: a section
13116	 beginning with the magic string .gnu.linkonce is a linkonce
13117	 section.  */
13118      if (strncmp (segment_name (symsec), ".gnu.linkonce",
13119		   sizeof ".gnu.linkonce" - 1) == 0)
13120	linkonce = TRUE;
13121    }
13122
13123  /* This must duplicate the test in adjust_reloc_syms.  */
13124  return (symsec != &bfd_und_section
13125	  && symsec != &bfd_abs_section
13126	  && ! bfd_is_com_section (symsec)
13127	  && !linkonce
13128#ifdef OBJ_ELF
13129	  /* A global or weak symbol is treated as external.  */
13130	  && (OUTPUT_FLAVOR != bfd_target_elf_flavour
13131	      || (! S_IS_WEAK (sym) && ! S_IS_EXTERNAL (sym)))
13132#endif
13133	  );
13134}
13135
13136
13137/* Given a mips16 variant frag FRAGP, return non-zero if it needs an
13138   extended opcode.  SEC is the section the frag is in.  */
13139
13140static int
13141mips16_extended_frag (fragS *fragp, asection *sec, long stretch)
13142{
13143  int type;
13144  register const struct mips16_immed_operand *op;
13145  offsetT val;
13146  int mintiny, maxtiny;
13147  segT symsec;
13148  fragS *sym_frag;
13149
13150  if (RELAX_MIPS16_USER_SMALL (fragp->fr_subtype))
13151    return 0;
13152  if (RELAX_MIPS16_USER_EXT (fragp->fr_subtype))
13153    return 1;
13154
13155  type = RELAX_MIPS16_TYPE (fragp->fr_subtype);
13156  op = mips16_immed_operands;
13157  while (op->type != type)
13158    {
13159      ++op;
13160      assert (op < mips16_immed_operands + MIPS16_NUM_IMMED);
13161    }
13162
13163  if (op->unsp)
13164    {
13165      if (type == '<' || type == '>' || type == '[' || type == ']')
13166	{
13167	  mintiny = 1;
13168	  maxtiny = 1 << op->nbits;
13169	}
13170      else
13171	{
13172	  mintiny = 0;
13173	  maxtiny = (1 << op->nbits) - 1;
13174	}
13175    }
13176  else
13177    {
13178      mintiny = - (1 << (op->nbits - 1));
13179      maxtiny = (1 << (op->nbits - 1)) - 1;
13180    }
13181
13182  sym_frag = symbol_get_frag (fragp->fr_symbol);
13183  val = S_GET_VALUE (fragp->fr_symbol);
13184  symsec = S_GET_SEGMENT (fragp->fr_symbol);
13185
13186  if (op->pcrel)
13187    {
13188      addressT addr;
13189
13190      /* We won't have the section when we are called from
13191         mips_relax_frag.  However, we will always have been called
13192         from md_estimate_size_before_relax first.  If this is a
13193         branch to a different section, we mark it as such.  If SEC is
13194         NULL, and the frag is not marked, then it must be a branch to
13195         the same section.  */
13196      if (sec == NULL)
13197	{
13198	  if (RELAX_MIPS16_LONG_BRANCH (fragp->fr_subtype))
13199	    return 1;
13200	}
13201      else
13202	{
13203	  /* Must have been called from md_estimate_size_before_relax.  */
13204	  if (symsec != sec)
13205	    {
13206	      fragp->fr_subtype =
13207		RELAX_MIPS16_MARK_LONG_BRANCH (fragp->fr_subtype);
13208
13209	      /* FIXME: We should support this, and let the linker
13210                 catch branches and loads that are out of range.  */
13211	      as_bad_where (fragp->fr_file, fragp->fr_line,
13212			    _("unsupported PC relative reference to different section"));
13213
13214	      return 1;
13215	    }
13216	  if (fragp != sym_frag && sym_frag->fr_address == 0)
13217	    /* Assume non-extended on the first relaxation pass.
13218	       The address we have calculated will be bogus if this is
13219	       a forward branch to another frag, as the forward frag
13220	       will have fr_address == 0.  */
13221	    return 0;
13222	}
13223
13224      /* In this case, we know for sure that the symbol fragment is in
13225	 the same section.  If the relax_marker of the symbol fragment
13226	 differs from the relax_marker of this fragment, we have not
13227	 yet adjusted the symbol fragment fr_address.  We want to add
13228	 in STRETCH in order to get a better estimate of the address.
13229	 This particularly matters because of the shift bits.  */
13230      if (stretch != 0
13231	  && sym_frag->relax_marker != fragp->relax_marker)
13232	{
13233	  fragS *f;
13234
13235	  /* Adjust stretch for any alignment frag.  Note that if have
13236             been expanding the earlier code, the symbol may be
13237             defined in what appears to be an earlier frag.  FIXME:
13238             This doesn't handle the fr_subtype field, which specifies
13239             a maximum number of bytes to skip when doing an
13240             alignment.  */
13241	  for (f = fragp; f != NULL && f != sym_frag; f = f->fr_next)
13242	    {
13243	      if (f->fr_type == rs_align || f->fr_type == rs_align_code)
13244		{
13245		  if (stretch < 0)
13246		    stretch = - ((- stretch)
13247				 & ~ ((1 << (int) f->fr_offset) - 1));
13248		  else
13249		    stretch &= ~ ((1 << (int) f->fr_offset) - 1);
13250		  if (stretch == 0)
13251		    break;
13252		}
13253	    }
13254	  if (f != NULL)
13255	    val += stretch;
13256	}
13257
13258      addr = fragp->fr_address + fragp->fr_fix;
13259
13260      /* The base address rules are complicated.  The base address of
13261         a branch is the following instruction.  The base address of a
13262         PC relative load or add is the instruction itself, but if it
13263         is in a delay slot (in which case it can not be extended) use
13264         the address of the instruction whose delay slot it is in.  */
13265      if (type == 'p' || type == 'q')
13266	{
13267	  addr += 2;
13268
13269	  /* If we are currently assuming that this frag should be
13270	     extended, then, the current address is two bytes
13271	     higher.  */
13272	  if (RELAX_MIPS16_EXTENDED (fragp->fr_subtype))
13273	    addr += 2;
13274
13275	  /* Ignore the low bit in the target, since it will be set
13276             for a text label.  */
13277	  if ((val & 1) != 0)
13278	    --val;
13279	}
13280      else if (RELAX_MIPS16_JAL_DSLOT (fragp->fr_subtype))
13281	addr -= 4;
13282      else if (RELAX_MIPS16_DSLOT (fragp->fr_subtype))
13283	addr -= 2;
13284
13285      val -= addr & ~ ((1 << op->shift) - 1);
13286
13287      /* Branch offsets have an implicit 0 in the lowest bit.  */
13288      if (type == 'p' || type == 'q')
13289	val /= 2;
13290
13291      /* If any of the shifted bits are set, we must use an extended
13292         opcode.  If the address depends on the size of this
13293         instruction, this can lead to a loop, so we arrange to always
13294         use an extended opcode.  We only check this when we are in
13295         the main relaxation loop, when SEC is NULL.  */
13296      if ((val & ((1 << op->shift) - 1)) != 0 && sec == NULL)
13297	{
13298	  fragp->fr_subtype =
13299	    RELAX_MIPS16_MARK_LONG_BRANCH (fragp->fr_subtype);
13300	  return 1;
13301	}
13302
13303      /* If we are about to mark a frag as extended because the value
13304         is precisely maxtiny + 1, then there is a chance of an
13305         infinite loop as in the following code:
13306	     la	$4,foo
13307	     .skip	1020
13308	     .align	2
13309	   foo:
13310	 In this case when the la is extended, foo is 0x3fc bytes
13311	 away, so the la can be shrunk, but then foo is 0x400 away, so
13312	 the la must be extended.  To avoid this loop, we mark the
13313	 frag as extended if it was small, and is about to become
13314	 extended with a value of maxtiny + 1.  */
13315      if (val == ((maxtiny + 1) << op->shift)
13316	  && ! RELAX_MIPS16_EXTENDED (fragp->fr_subtype)
13317	  && sec == NULL)
13318	{
13319	  fragp->fr_subtype =
13320	    RELAX_MIPS16_MARK_LONG_BRANCH (fragp->fr_subtype);
13321	  return 1;
13322	}
13323    }
13324  else if (symsec != absolute_section && sec != NULL)
13325    as_bad_where (fragp->fr_file, fragp->fr_line, _("unsupported relocation"));
13326
13327  if ((val & ((1 << op->shift) - 1)) != 0
13328      || val < (mintiny << op->shift)
13329      || val > (maxtiny << op->shift))
13330    return 1;
13331  else
13332    return 0;
13333}
13334
13335/* Compute the length of a branch sequence, and adjust the
13336   RELAX_BRANCH_TOOFAR bit accordingly.  If FRAGP is NULL, the
13337   worst-case length is computed, with UPDATE being used to indicate
13338   whether an unconditional (-1), branch-likely (+1) or regular (0)
13339   branch is to be computed.  */
13340static int
13341relaxed_branch_length (fragS *fragp, asection *sec, int update)
13342{
13343  bfd_boolean toofar;
13344  int length;
13345
13346  if (fragp
13347      && S_IS_DEFINED (fragp->fr_symbol)
13348      && sec == S_GET_SEGMENT (fragp->fr_symbol))
13349    {
13350      addressT addr;
13351      offsetT val;
13352
13353      val = S_GET_VALUE (fragp->fr_symbol) + fragp->fr_offset;
13354
13355      addr = fragp->fr_address + fragp->fr_fix + 4;
13356
13357      val -= addr;
13358
13359      toofar = val < - (0x8000 << 2) || val >= (0x8000 << 2);
13360    }
13361  else if (fragp)
13362    /* If the symbol is not defined or it's in a different segment,
13363       assume the user knows what's going on and emit a short
13364       branch.  */
13365    toofar = FALSE;
13366  else
13367    toofar = TRUE;
13368
13369  if (fragp && update && toofar != RELAX_BRANCH_TOOFAR (fragp->fr_subtype))
13370    fragp->fr_subtype
13371      = RELAX_BRANCH_ENCODE (RELAX_BRANCH_UNCOND (fragp->fr_subtype),
13372			     RELAX_BRANCH_LIKELY (fragp->fr_subtype),
13373			     RELAX_BRANCH_LINK (fragp->fr_subtype),
13374			     toofar);
13375
13376  length = 4;
13377  if (toofar)
13378    {
13379      if (fragp ? RELAX_BRANCH_LIKELY (fragp->fr_subtype) : (update > 0))
13380	length += 8;
13381
13382      if (mips_pic != NO_PIC)
13383	{
13384	  /* Additional space for PIC loading of target address.  */
13385	  length += 8;
13386	  if (mips_opts.isa == ISA_MIPS1)
13387	    /* Additional space for $at-stabilizing nop.  */
13388	    length += 4;
13389	}
13390
13391      /* If branch is conditional.  */
13392      if (fragp ? !RELAX_BRANCH_UNCOND (fragp->fr_subtype) : (update >= 0))
13393	length += 8;
13394    }
13395
13396  return length;
13397}
13398
13399/* Estimate the size of a frag before relaxing.  Unless this is the
13400   mips16, we are not really relaxing here, and the final size is
13401   encoded in the subtype information.  For the mips16, we have to
13402   decide whether we are using an extended opcode or not.  */
13403
13404int
13405md_estimate_size_before_relax (fragS *fragp, asection *segtype)
13406{
13407  int change;
13408
13409  if (RELAX_BRANCH_P (fragp->fr_subtype))
13410    {
13411
13412      fragp->fr_var = relaxed_branch_length (fragp, segtype, FALSE);
13413
13414      return fragp->fr_var;
13415    }
13416
13417  if (RELAX_MIPS16_P (fragp->fr_subtype))
13418    /* We don't want to modify the EXTENDED bit here; it might get us
13419       into infinite loops.  We change it only in mips_relax_frag().  */
13420    return (RELAX_MIPS16_EXTENDED (fragp->fr_subtype) ? 4 : 2);
13421
13422  if (mips_pic == NO_PIC)
13423    change = nopic_need_relax (fragp->fr_symbol, 0);
13424  else if (mips_pic == SVR4_PIC)
13425    change = pic_need_relax (fragp->fr_symbol, segtype);
13426  else
13427    abort ();
13428
13429  if (change)
13430    {
13431      fragp->fr_subtype |= RELAX_USE_SECOND;
13432      return -RELAX_FIRST (fragp->fr_subtype);
13433    }
13434  else
13435    return -RELAX_SECOND (fragp->fr_subtype);
13436}
13437
13438/* This is called to see whether a reloc against a defined symbol
13439   should be converted into a reloc against a section.  */
13440
13441int
13442mips_fix_adjustable (fixS *fixp)
13443{
13444  /* Don't adjust MIPS16 jump relocations, so we don't have to worry
13445     about the format of the offset in the .o file. */
13446  if (fixp->fx_r_type == BFD_RELOC_MIPS16_JMP)
13447    return 0;
13448
13449  if (fixp->fx_r_type == BFD_RELOC_VTABLE_INHERIT
13450      || fixp->fx_r_type == BFD_RELOC_VTABLE_ENTRY)
13451    return 0;
13452
13453  if (fixp->fx_addsy == NULL)
13454    return 1;
13455
13456  /* If symbol SYM is in a mergeable section, relocations of the form
13457     SYM + 0 can usually be made section-relative.  The mergeable data
13458     is then identified by the section offset rather than by the symbol.
13459
13460     However, if we're generating REL LO16 relocations, the offset is split
13461     between the LO16 and parterning high part relocation.  The linker will
13462     need to recalculate the complete offset in order to correctly identify
13463     the merge data.
13464
13465     The linker has traditionally not looked for the parterning high part
13466     relocation, and has thus allowed orphaned R_MIPS_LO16 relocations to be
13467     placed anywhere.  Rather than break backwards compatibility by changing
13468     this, it seems better not to force the issue, and instead keep the
13469     original symbol.  This will work with either linker behavior.  */
13470  if ((fixp->fx_r_type == BFD_RELOC_LO16
13471       || reloc_needs_lo_p (fixp->fx_r_type))
13472      && HAVE_IN_PLACE_ADDENDS
13473      && (S_GET_SEGMENT (fixp->fx_addsy)->flags & SEC_MERGE) != 0)
13474    return 0;
13475
13476#ifdef OBJ_ELF
13477  /* Don't adjust relocations against mips16 symbols, so that the linker
13478     can find them if it needs to set up a stub.  */
13479  if (OUTPUT_FLAVOR == bfd_target_elf_flavour
13480      && S_GET_OTHER (fixp->fx_addsy) == STO_MIPS16
13481      && fixp->fx_subsy == NULL)
13482    return 0;
13483#endif
13484
13485  return 1;
13486}
13487
13488/* Translate internal representation of relocation info to BFD target
13489   format.  */
13490
13491arelent **
13492tc_gen_reloc (asection *section ATTRIBUTE_UNUSED, fixS *fixp)
13493{
13494  static arelent *retval[4];
13495  arelent *reloc;
13496  bfd_reloc_code_real_type code;
13497
13498  memset (retval, 0, sizeof(retval));
13499  reloc = retval[0] = (arelent *) xcalloc (1, sizeof (arelent));
13500  reloc->sym_ptr_ptr = (asymbol **) xmalloc (sizeof (asymbol *));
13501  *reloc->sym_ptr_ptr = symbol_get_bfdsym (fixp->fx_addsy);
13502  reloc->address = fixp->fx_frag->fr_address + fixp->fx_where;
13503
13504  if (fixp->fx_pcrel)
13505    {
13506      assert (fixp->fx_r_type == BFD_RELOC_16_PCREL_S2);
13507
13508      /* At this point, fx_addnumber is "symbol offset - pcrel address".
13509	 Relocations want only the symbol offset.  */
13510      reloc->addend = fixp->fx_addnumber + reloc->address;
13511      if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
13512	{
13513	  /* A gruesome hack which is a result of the gruesome gas
13514	     reloc handling.  What's worse, for COFF (as opposed to
13515	     ECOFF), we might need yet another copy of reloc->address.
13516	     See bfd_install_relocation.  */
13517	  reloc->addend += reloc->address;
13518	}
13519    }
13520  else
13521    reloc->addend = fixp->fx_addnumber;
13522
13523  /* Since the old MIPS ELF ABI uses Rel instead of Rela, encode the vtable
13524     entry to be used in the relocation's section offset.  */
13525  if (! HAVE_NEWABI && fixp->fx_r_type == BFD_RELOC_VTABLE_ENTRY)
13526    {
13527      reloc->address = reloc->addend;
13528      reloc->addend = 0;
13529    }
13530
13531  code = fixp->fx_r_type;
13532
13533  reloc->howto = bfd_reloc_type_lookup (stdoutput, code);
13534  if (reloc->howto == NULL)
13535    {
13536      as_bad_where (fixp->fx_file, fixp->fx_line,
13537		    _("Can not represent %s relocation in this object file format"),
13538		    bfd_get_reloc_code_name (code));
13539      retval[0] = NULL;
13540    }
13541
13542  return retval;
13543}
13544
13545/* Relax a machine dependent frag.  This returns the amount by which
13546   the current size of the frag should change.  */
13547
13548int
13549mips_relax_frag (asection *sec, fragS *fragp, long stretch)
13550{
13551  if (RELAX_BRANCH_P (fragp->fr_subtype))
13552    {
13553      offsetT old_var = fragp->fr_var;
13554
13555      fragp->fr_var = relaxed_branch_length (fragp, sec, TRUE);
13556
13557      return fragp->fr_var - old_var;
13558    }
13559
13560  if (! RELAX_MIPS16_P (fragp->fr_subtype))
13561    return 0;
13562
13563  if (mips16_extended_frag (fragp, NULL, stretch))
13564    {
13565      if (RELAX_MIPS16_EXTENDED (fragp->fr_subtype))
13566	return 0;
13567      fragp->fr_subtype = RELAX_MIPS16_MARK_EXTENDED (fragp->fr_subtype);
13568      return 2;
13569    }
13570  else
13571    {
13572      if (! RELAX_MIPS16_EXTENDED (fragp->fr_subtype))
13573	return 0;
13574      fragp->fr_subtype = RELAX_MIPS16_CLEAR_EXTENDED (fragp->fr_subtype);
13575      return -2;
13576    }
13577
13578  return 0;
13579}
13580
13581/* Convert a machine dependent frag.  */
13582
13583void
13584md_convert_frag (bfd *abfd ATTRIBUTE_UNUSED, segT asec, fragS *fragp)
13585{
13586  if (RELAX_BRANCH_P (fragp->fr_subtype))
13587    {
13588      bfd_byte *buf;
13589      unsigned long insn;
13590      expressionS exp;
13591      fixS *fixp;
13592
13593      buf = (bfd_byte *)fragp->fr_literal + fragp->fr_fix;
13594
13595      if (target_big_endian)
13596	insn = bfd_getb32 (buf);
13597      else
13598	insn = bfd_getl32 (buf);
13599
13600      if (!RELAX_BRANCH_TOOFAR (fragp->fr_subtype))
13601	{
13602	  /* We generate a fixup instead of applying it right now
13603	     because, if there are linker relaxations, we're going to
13604	     need the relocations.  */
13605	  exp.X_op = O_symbol;
13606	  exp.X_add_symbol = fragp->fr_symbol;
13607	  exp.X_add_number = fragp->fr_offset;
13608
13609	  fixp = fix_new_exp (fragp, buf - (bfd_byte *)fragp->fr_literal,
13610			      4, &exp, 1, BFD_RELOC_16_PCREL_S2);
13611	  fixp->fx_file = fragp->fr_file;
13612	  fixp->fx_line = fragp->fr_line;
13613
13614	  md_number_to_chars ((char *) buf, insn, 4);
13615	  buf += 4;
13616	}
13617      else
13618	{
13619	  int i;
13620
13621	  as_warn_where (fragp->fr_file, fragp->fr_line,
13622			 _("relaxed out-of-range branch into a jump"));
13623
13624	  if (RELAX_BRANCH_UNCOND (fragp->fr_subtype))
13625	    goto uncond;
13626
13627	  if (!RELAX_BRANCH_LIKELY (fragp->fr_subtype))
13628	    {
13629	      /* Reverse the branch.  */
13630	      switch ((insn >> 28) & 0xf)
13631		{
13632		case 4:
13633		  /* bc[0-3][tf]l? and bc1any[24][ft] instructions can
13634		     have the condition reversed by tweaking a single
13635		     bit, and their opcodes all have 0x4???????.  */
13636		  assert ((insn & 0xf1000000) == 0x41000000);
13637		  insn ^= 0x00010000;
13638		  break;
13639
13640		case 0:
13641		  /* bltz	0x04000000	bgez	0x04010000
13642		     bltzal	0x04100000	bgezal	0x04110000 */
13643		  assert ((insn & 0xfc0e0000) == 0x04000000);
13644		  insn ^= 0x00010000;
13645		  break;
13646
13647		case 1:
13648		  /* beq	0x10000000	bne	0x14000000
13649		     blez	0x18000000	bgtz	0x1c000000 */
13650		  insn ^= 0x04000000;
13651		  break;
13652
13653		default:
13654		  abort ();
13655		}
13656	    }
13657
13658	  if (RELAX_BRANCH_LINK (fragp->fr_subtype))
13659	    {
13660	      /* Clear the and-link bit.  */
13661	      assert ((insn & 0xfc1c0000) == 0x04100000);
13662
13663	      /* bltzal	0x04100000	bgezal	0x04110000
13664		bltzall	0x04120000     bgezall	0x04130000 */
13665	      insn &= ~0x00100000;
13666	    }
13667
13668	  /* Branch over the branch (if the branch was likely) or the
13669	     full jump (not likely case).  Compute the offset from the
13670	     current instruction to branch to.  */
13671	  if (RELAX_BRANCH_LIKELY (fragp->fr_subtype))
13672	    i = 16;
13673	  else
13674	    {
13675	      /* How many bytes in instructions we've already emitted?  */
13676	      i = buf - (bfd_byte *)fragp->fr_literal - fragp->fr_fix;
13677	      /* How many bytes in instructions from here to the end?  */
13678	      i = fragp->fr_var - i;
13679	    }
13680	  /* Convert to instruction count.  */
13681	  i >>= 2;
13682	  /* Branch counts from the next instruction.  */
13683	  i--;
13684	  insn |= i;
13685	  /* Branch over the jump.  */
13686	  md_number_to_chars ((char *) buf, insn, 4);
13687	  buf += 4;
13688
13689	  /* Nop */
13690	  md_number_to_chars ((char *) buf, 0, 4);
13691	  buf += 4;
13692
13693	  if (RELAX_BRANCH_LIKELY (fragp->fr_subtype))
13694	    {
13695	      /* beql $0, $0, 2f */
13696	      insn = 0x50000000;
13697	      /* Compute the PC offset from the current instruction to
13698		 the end of the variable frag.  */
13699	      /* How many bytes in instructions we've already emitted?  */
13700	      i = buf - (bfd_byte *)fragp->fr_literal - fragp->fr_fix;
13701	      /* How many bytes in instructions from here to the end?  */
13702	      i = fragp->fr_var - i;
13703	      /* Convert to instruction count.  */
13704	      i >>= 2;
13705	      /* Don't decrement i, because we want to branch over the
13706		 delay slot.  */
13707
13708	      insn |= i;
13709	      md_number_to_chars ((char *) buf, insn, 4);
13710	      buf += 4;
13711
13712	      md_number_to_chars ((char *) buf, 0, 4);
13713	      buf += 4;
13714	    }
13715
13716	uncond:
13717	  if (mips_pic == NO_PIC)
13718	    {
13719	      /* j or jal.  */
13720	      insn = (RELAX_BRANCH_LINK (fragp->fr_subtype)
13721		      ? 0x0c000000 : 0x08000000);
13722	      exp.X_op = O_symbol;
13723	      exp.X_add_symbol = fragp->fr_symbol;
13724	      exp.X_add_number = fragp->fr_offset;
13725
13726	      fixp = fix_new_exp (fragp, buf - (bfd_byte *)fragp->fr_literal,
13727				  4, &exp, 0, BFD_RELOC_MIPS_JMP);
13728	      fixp->fx_file = fragp->fr_file;
13729	      fixp->fx_line = fragp->fr_line;
13730
13731	      md_number_to_chars ((char *) buf, insn, 4);
13732	      buf += 4;
13733	    }
13734	  else
13735	    {
13736	      /* lw/ld $at, <sym>($gp)  R_MIPS_GOT16 */
13737	      insn = HAVE_64BIT_ADDRESSES ? 0xdf810000 : 0x8f810000;
13738	      exp.X_op = O_symbol;
13739	      exp.X_add_symbol = fragp->fr_symbol;
13740	      exp.X_add_number = fragp->fr_offset;
13741
13742	      if (fragp->fr_offset)
13743		{
13744		  exp.X_add_symbol = make_expr_symbol (&exp);
13745		  exp.X_add_number = 0;
13746		}
13747
13748	      fixp = fix_new_exp (fragp, buf - (bfd_byte *)fragp->fr_literal,
13749				  4, &exp, 0, BFD_RELOC_MIPS_GOT16);
13750	      fixp->fx_file = fragp->fr_file;
13751	      fixp->fx_line = fragp->fr_line;
13752
13753	      md_number_to_chars ((char *) buf, insn, 4);
13754	      buf += 4;
13755
13756	      if (mips_opts.isa == ISA_MIPS1)
13757		{
13758		  /* nop */
13759		  md_number_to_chars ((char *) buf, 0, 4);
13760		  buf += 4;
13761		}
13762
13763	      /* d/addiu $at, $at, <sym>  R_MIPS_LO16 */
13764	      insn = HAVE_64BIT_ADDRESSES ? 0x64210000 : 0x24210000;
13765
13766	      fixp = fix_new_exp (fragp, buf - (bfd_byte *)fragp->fr_literal,
13767				  4, &exp, 0, BFD_RELOC_LO16);
13768	      fixp->fx_file = fragp->fr_file;
13769	      fixp->fx_line = fragp->fr_line;
13770
13771	      md_number_to_chars ((char *) buf, insn, 4);
13772	      buf += 4;
13773
13774	      /* j(al)r $at.  */
13775	      if (RELAX_BRANCH_LINK (fragp->fr_subtype))
13776		insn = 0x0020f809;
13777	      else
13778		insn = 0x00200008;
13779
13780	      md_number_to_chars ((char *) buf, insn, 4);
13781	      buf += 4;
13782	    }
13783	}
13784
13785      assert (buf == (bfd_byte *)fragp->fr_literal
13786	      + fragp->fr_fix + fragp->fr_var);
13787
13788      fragp->fr_fix += fragp->fr_var;
13789
13790      return;
13791    }
13792
13793  if (RELAX_MIPS16_P (fragp->fr_subtype))
13794    {
13795      int type;
13796      register const struct mips16_immed_operand *op;
13797      bfd_boolean small, ext;
13798      offsetT val;
13799      bfd_byte *buf;
13800      unsigned long insn;
13801      bfd_boolean use_extend;
13802      unsigned short extend;
13803
13804      type = RELAX_MIPS16_TYPE (fragp->fr_subtype);
13805      op = mips16_immed_operands;
13806      while (op->type != type)
13807	++op;
13808
13809      if (RELAX_MIPS16_EXTENDED (fragp->fr_subtype))
13810	{
13811	  small = FALSE;
13812	  ext = TRUE;
13813	}
13814      else
13815	{
13816	  small = TRUE;
13817	  ext = FALSE;
13818	}
13819
13820      resolve_symbol_value (fragp->fr_symbol);
13821      val = S_GET_VALUE (fragp->fr_symbol);
13822      if (op->pcrel)
13823	{
13824	  addressT addr;
13825
13826	  addr = fragp->fr_address + fragp->fr_fix;
13827
13828	  /* The rules for the base address of a PC relative reloc are
13829             complicated; see mips16_extended_frag.  */
13830	  if (type == 'p' || type == 'q')
13831	    {
13832	      addr += 2;
13833	      if (ext)
13834		addr += 2;
13835	      /* Ignore the low bit in the target, since it will be
13836                 set for a text label.  */
13837	      if ((val & 1) != 0)
13838		--val;
13839	    }
13840	  else if (RELAX_MIPS16_JAL_DSLOT (fragp->fr_subtype))
13841	    addr -= 4;
13842	  else if (RELAX_MIPS16_DSLOT (fragp->fr_subtype))
13843	    addr -= 2;
13844
13845	  addr &= ~ (addressT) ((1 << op->shift) - 1);
13846	  val -= addr;
13847
13848	  /* Make sure the section winds up with the alignment we have
13849             assumed.  */
13850	  if (op->shift > 0)
13851	    record_alignment (asec, op->shift);
13852	}
13853
13854      if (ext
13855	  && (RELAX_MIPS16_JAL_DSLOT (fragp->fr_subtype)
13856	      || RELAX_MIPS16_DSLOT (fragp->fr_subtype)))
13857	as_warn_where (fragp->fr_file, fragp->fr_line,
13858		       _("extended instruction in delay slot"));
13859
13860      buf = (bfd_byte *) (fragp->fr_literal + fragp->fr_fix);
13861
13862      if (target_big_endian)
13863	insn = bfd_getb16 (buf);
13864      else
13865	insn = bfd_getl16 (buf);
13866
13867      mips16_immed (fragp->fr_file, fragp->fr_line, type, val,
13868		    RELAX_MIPS16_USER_EXT (fragp->fr_subtype),
13869		    small, ext, &insn, &use_extend, &extend);
13870
13871      if (use_extend)
13872	{
13873	  md_number_to_chars ((char *) buf, 0xf000 | extend, 2);
13874	  fragp->fr_fix += 2;
13875	  buf += 2;
13876	}
13877
13878      md_number_to_chars ((char *) buf, insn, 2);
13879      fragp->fr_fix += 2;
13880      buf += 2;
13881    }
13882  else
13883    {
13884      int first, second;
13885      fixS *fixp;
13886
13887      first = RELAX_FIRST (fragp->fr_subtype);
13888      second = RELAX_SECOND (fragp->fr_subtype);
13889      fixp = (fixS *) fragp->fr_opcode;
13890
13891      /* Possibly emit a warning if we've chosen the longer option.  */
13892      if (((fragp->fr_subtype & RELAX_USE_SECOND) != 0)
13893	  == ((fragp->fr_subtype & RELAX_SECOND_LONGER) != 0))
13894	{
13895	  const char *msg = macro_warning (fragp->fr_subtype);
13896	  if (msg != 0)
13897	    as_warn_where (fragp->fr_file, fragp->fr_line, msg);
13898	}
13899
13900      /* Go through all the fixups for the first sequence.  Disable them
13901	 (by marking them as done) if we're going to use the second
13902	 sequence instead.  */
13903      while (fixp
13904	     && fixp->fx_frag == fragp
13905	     && fixp->fx_where < fragp->fr_fix - second)
13906	{
13907	  if (fragp->fr_subtype & RELAX_USE_SECOND)
13908	    fixp->fx_done = 1;
13909	  fixp = fixp->fx_next;
13910	}
13911
13912      /* Go through the fixups for the second sequence.  Disable them if
13913	 we're going to use the first sequence, otherwise adjust their
13914	 addresses to account for the relaxation.  */
13915      while (fixp && fixp->fx_frag == fragp)
13916	{
13917	  if (fragp->fr_subtype & RELAX_USE_SECOND)
13918	    fixp->fx_where -= first;
13919	  else
13920	    fixp->fx_done = 1;
13921	  fixp = fixp->fx_next;
13922	}
13923
13924      /* Now modify the frag contents.  */
13925      if (fragp->fr_subtype & RELAX_USE_SECOND)
13926	{
13927	  char *start;
13928
13929	  start = fragp->fr_literal + fragp->fr_fix - first - second;
13930	  memmove (start, start + first, second);
13931	  fragp->fr_fix -= first;
13932	}
13933      else
13934	fragp->fr_fix -= second;
13935    }
13936}
13937
13938#ifdef OBJ_ELF
13939
13940/* This function is called after the relocs have been generated.
13941   We've been storing mips16 text labels as odd.  Here we convert them
13942   back to even for the convenience of the debugger.  */
13943
13944void
13945mips_frob_file_after_relocs (void)
13946{
13947  asymbol **syms;
13948  unsigned int count, i;
13949
13950  if (OUTPUT_FLAVOR != bfd_target_elf_flavour)
13951    return;
13952
13953  syms = bfd_get_outsymbols (stdoutput);
13954  count = bfd_get_symcount (stdoutput);
13955  for (i = 0; i < count; i++, syms++)
13956    {
13957      if (elf_symbol (*syms)->internal_elf_sym.st_other == STO_MIPS16
13958	  && ((*syms)->value & 1) != 0)
13959	{
13960	  (*syms)->value &= ~1;
13961	  /* If the symbol has an odd size, it was probably computed
13962	     incorrectly, so adjust that as well.  */
13963	  if ((elf_symbol (*syms)->internal_elf_sym.st_size & 1) != 0)
13964	    ++elf_symbol (*syms)->internal_elf_sym.st_size;
13965	}
13966    }
13967}
13968
13969#endif
13970
13971/* This function is called whenever a label is defined.  It is used
13972   when handling branch delays; if a branch has a label, we assume we
13973   can not move it.  */
13974
13975void
13976mips_define_label (symbolS *sym)
13977{
13978  struct insn_label_list *l;
13979
13980  if (free_insn_labels == NULL)
13981    l = (struct insn_label_list *) xmalloc (sizeof *l);
13982  else
13983    {
13984      l = free_insn_labels;
13985      free_insn_labels = l->next;
13986    }
13987
13988  l->label = sym;
13989  l->next = insn_labels;
13990  insn_labels = l;
13991}
13992
13993#if defined (OBJ_ELF) || defined (OBJ_MAYBE_ELF)
13994
13995/* Some special processing for a MIPS ELF file.  */
13996
13997void
13998mips_elf_final_processing (void)
13999{
14000  /* Write out the register information.  */
14001  if (mips_abi != N64_ABI)
14002    {
14003      Elf32_RegInfo s;
14004
14005      s.ri_gprmask = mips_gprmask;
14006      s.ri_cprmask[0] = mips_cprmask[0];
14007      s.ri_cprmask[1] = mips_cprmask[1];
14008      s.ri_cprmask[2] = mips_cprmask[2];
14009      s.ri_cprmask[3] = mips_cprmask[3];
14010      /* The gp_value field is set by the MIPS ELF backend.  */
14011
14012      bfd_mips_elf32_swap_reginfo_out (stdoutput, &s,
14013				       ((Elf32_External_RegInfo *)
14014					mips_regmask_frag));
14015    }
14016  else
14017    {
14018      Elf64_Internal_RegInfo s;
14019
14020      s.ri_gprmask = mips_gprmask;
14021      s.ri_pad = 0;
14022      s.ri_cprmask[0] = mips_cprmask[0];
14023      s.ri_cprmask[1] = mips_cprmask[1];
14024      s.ri_cprmask[2] = mips_cprmask[2];
14025      s.ri_cprmask[3] = mips_cprmask[3];
14026      /* The gp_value field is set by the MIPS ELF backend.  */
14027
14028      bfd_mips_elf64_swap_reginfo_out (stdoutput, &s,
14029				       ((Elf64_External_RegInfo *)
14030					mips_regmask_frag));
14031    }
14032
14033  /* Set the MIPS ELF flag bits.  FIXME: There should probably be some
14034     sort of BFD interface for this.  */
14035  if (mips_any_noreorder)
14036    elf_elfheader (stdoutput)->e_flags |= EF_MIPS_NOREORDER;
14037  if (mips_pic != NO_PIC)
14038    {
14039    elf_elfheader (stdoutput)->e_flags |= EF_MIPS_PIC;
14040      elf_elfheader (stdoutput)->e_flags |= EF_MIPS_CPIC;
14041    }
14042  if (mips_abicalls)
14043    elf_elfheader (stdoutput)->e_flags |= EF_MIPS_CPIC;
14044
14045  /* Set MIPS ELF flags for ASEs.  */
14046  /* We may need to define a new flag for DSP ASE, and set this flag when
14047     file_ase_dsp is true.  */
14048  /* We may need to define a new flag for MT ASE, and set this flag when
14049     file_ase_mt is true.  */
14050  if (file_ase_mips16)
14051    elf_elfheader (stdoutput)->e_flags |= EF_MIPS_ARCH_ASE_M16;
14052#if 0 /* XXX FIXME */
14053  if (file_ase_mips3d)
14054    elf_elfheader (stdoutput)->e_flags |= ???;
14055#endif
14056  if (file_ase_mdmx)
14057    elf_elfheader (stdoutput)->e_flags |= EF_MIPS_ARCH_ASE_MDMX;
14058
14059  /* Set the MIPS ELF ABI flags.  */
14060  if (mips_abi == O32_ABI && USE_E_MIPS_ABI_O32)
14061    elf_elfheader (stdoutput)->e_flags |= E_MIPS_ABI_O32;
14062  else if (mips_abi == O64_ABI)
14063    elf_elfheader (stdoutput)->e_flags |= E_MIPS_ABI_O64;
14064  else if (mips_abi == EABI_ABI)
14065    {
14066      if (!file_mips_gp32)
14067	elf_elfheader (stdoutput)->e_flags |= E_MIPS_ABI_EABI64;
14068      else
14069	elf_elfheader (stdoutput)->e_flags |= E_MIPS_ABI_EABI32;
14070    }
14071  else if (mips_abi == N32_ABI)
14072    elf_elfheader (stdoutput)->e_flags |= EF_MIPS_ABI2;
14073
14074  /* Nothing to do for N64_ABI.  */
14075
14076  if (mips_32bitmode)
14077    elf_elfheader (stdoutput)->e_flags |= EF_MIPS_32BITMODE;
14078}
14079
14080#endif /* OBJ_ELF || OBJ_MAYBE_ELF */
14081
14082typedef struct proc {
14083  symbolS *func_sym;
14084  symbolS *func_end_sym;
14085  unsigned long reg_mask;
14086  unsigned long reg_offset;
14087  unsigned long fpreg_mask;
14088  unsigned long fpreg_offset;
14089  unsigned long frame_offset;
14090  unsigned long frame_reg;
14091  unsigned long pc_reg;
14092} procS;
14093
14094static procS cur_proc;
14095static procS *cur_proc_ptr;
14096static int numprocs;
14097
14098/* Fill in an rs_align_code fragment.  */
14099
14100void
14101mips_handle_align (fragS *fragp)
14102{
14103  if (fragp->fr_type != rs_align_code)
14104    return;
14105
14106  if (mips_opts.mips16)
14107    {
14108      static const unsigned char be_nop[] = { 0x65, 0x00 };
14109      static const unsigned char le_nop[] = { 0x00, 0x65 };
14110
14111      int bytes;
14112      char *p;
14113
14114      bytes = fragp->fr_next->fr_address - fragp->fr_address - fragp->fr_fix;
14115      p = fragp->fr_literal + fragp->fr_fix;
14116
14117      if (bytes & 1)
14118	{
14119	  *p++ = 0;
14120	  fragp->fr_fix++;
14121	}
14122
14123      memcpy (p, (target_big_endian ? be_nop : le_nop), 2);
14124      fragp->fr_var = 2;
14125    }
14126
14127  /* For mips32, a nop is a zero, which we trivially get by doing nothing.  */
14128}
14129
14130static void
14131md_obj_begin (void)
14132{
14133}
14134
14135static void
14136md_obj_end (void)
14137{
14138  /* check for premature end, nesting errors, etc */
14139  if (cur_proc_ptr)
14140    as_warn (_("missing .end at end of assembly"));
14141}
14142
14143static long
14144get_number (void)
14145{
14146  int negative = 0;
14147  long val = 0;
14148
14149  if (*input_line_pointer == '-')
14150    {
14151      ++input_line_pointer;
14152      negative = 1;
14153    }
14154  if (!ISDIGIT (*input_line_pointer))
14155    as_bad (_("expected simple number"));
14156  if (input_line_pointer[0] == '0')
14157    {
14158      if (input_line_pointer[1] == 'x')
14159	{
14160	  input_line_pointer += 2;
14161	  while (ISXDIGIT (*input_line_pointer))
14162	    {
14163	      val <<= 4;
14164	      val |= hex_value (*input_line_pointer++);
14165	    }
14166	  return negative ? -val : val;
14167	}
14168      else
14169	{
14170	  ++input_line_pointer;
14171	  while (ISDIGIT (*input_line_pointer))
14172	    {
14173	      val <<= 3;
14174	      val |= *input_line_pointer++ - '0';
14175	    }
14176	  return negative ? -val : val;
14177	}
14178    }
14179  if (!ISDIGIT (*input_line_pointer))
14180    {
14181      printf (_(" *input_line_pointer == '%c' 0x%02x\n"),
14182	      *input_line_pointer, *input_line_pointer);
14183      as_warn (_("invalid number"));
14184      return -1;
14185    }
14186  while (ISDIGIT (*input_line_pointer))
14187    {
14188      val *= 10;
14189      val += *input_line_pointer++ - '0';
14190    }
14191  return negative ? -val : val;
14192}
14193
14194/* The .file directive; just like the usual .file directive, but there
14195   is an initial number which is the ECOFF file index.  In the non-ECOFF
14196   case .file implies DWARF-2.  */
14197
14198static void
14199s_mips_file (int x ATTRIBUTE_UNUSED)
14200{
14201  static int first_file_directive = 0;
14202
14203  if (ECOFF_DEBUGGING)
14204    {
14205      get_number ();
14206      s_app_file (0);
14207    }
14208  else
14209    {
14210      char *filename;
14211
14212      filename = dwarf2_directive_file (0);
14213
14214      /* Versions of GCC up to 3.1 start files with a ".file"
14215	 directive even for stabs output.  Make sure that this
14216	 ".file" is handled.  Note that you need a version of GCC
14217         after 3.1 in order to support DWARF-2 on MIPS.  */
14218      if (filename != NULL && ! first_file_directive)
14219	{
14220	  (void) new_logical_line (filename, -1);
14221	  s_app_file_string (filename);
14222	}
14223      first_file_directive = 1;
14224    }
14225}
14226
14227/* The .loc directive, implying DWARF-2.  */
14228
14229static void
14230s_mips_loc (int x ATTRIBUTE_UNUSED)
14231{
14232  if (!ECOFF_DEBUGGING)
14233    dwarf2_directive_loc (0);
14234}
14235
14236/* The .end directive.  */
14237
14238static void
14239s_mips_end (int x ATTRIBUTE_UNUSED)
14240{
14241  symbolS *p;
14242
14243  /* Following functions need their own .frame and .cprestore directives.  */
14244  mips_frame_reg_valid = 0;
14245  mips_cprestore_valid = 0;
14246
14247  if (!is_end_of_line[(unsigned char) *input_line_pointer])
14248    {
14249      p = get_symbol ();
14250      demand_empty_rest_of_line ();
14251    }
14252  else
14253    p = NULL;
14254
14255  if ((bfd_get_section_flags (stdoutput, now_seg) & SEC_CODE) == 0)
14256    as_warn (_(".end not in text section"));
14257
14258  if (!cur_proc_ptr)
14259    {
14260      as_warn (_(".end directive without a preceding .ent directive."));
14261      demand_empty_rest_of_line ();
14262      return;
14263    }
14264
14265  if (p != NULL)
14266    {
14267      assert (S_GET_NAME (p));
14268      if (strcmp (S_GET_NAME (p), S_GET_NAME (cur_proc_ptr->func_sym)))
14269	as_warn (_(".end symbol does not match .ent symbol."));
14270
14271      if (debug_type == DEBUG_STABS)
14272	stabs_generate_asm_endfunc (S_GET_NAME (p),
14273				    S_GET_NAME (p));
14274    }
14275  else
14276    as_warn (_(".end directive missing or unknown symbol"));
14277
14278#ifdef OBJ_ELF
14279  /* Create an expression to calculate the size of the function.  */
14280  if (p && cur_proc_ptr)
14281    {
14282      OBJ_SYMFIELD_TYPE *obj = symbol_get_obj (p);
14283      expressionS *exp = xmalloc (sizeof (expressionS));
14284
14285      obj->size = exp;
14286      exp->X_op = O_subtract;
14287      exp->X_add_symbol = symbol_temp_new_now ();
14288      exp->X_op_symbol = p;
14289      exp->X_add_number = 0;
14290
14291      cur_proc_ptr->func_end_sym = exp->X_add_symbol;
14292    }
14293
14294  /* Generate a .pdr section.  */
14295  if (OUTPUT_FLAVOR == bfd_target_elf_flavour && ! ECOFF_DEBUGGING
14296      && mips_flag_pdr)
14297    {
14298      segT saved_seg = now_seg;
14299      subsegT saved_subseg = now_subseg;
14300      valueT dot;
14301      expressionS exp;
14302      char *fragp;
14303
14304      dot = frag_now_fix ();
14305
14306#ifdef md_flush_pending_output
14307      md_flush_pending_output ();
14308#endif
14309
14310      assert (pdr_seg);
14311      subseg_set (pdr_seg, 0);
14312
14313      /* Write the symbol.  */
14314      exp.X_op = O_symbol;
14315      exp.X_add_symbol = p;
14316      exp.X_add_number = 0;
14317      emit_expr (&exp, 4);
14318
14319      fragp = frag_more (7 * 4);
14320
14321      md_number_to_chars (fragp, cur_proc_ptr->reg_mask, 4);
14322      md_number_to_chars (fragp + 4, cur_proc_ptr->reg_offset, 4);
14323      md_number_to_chars (fragp + 8, cur_proc_ptr->fpreg_mask, 4);
14324      md_number_to_chars (fragp + 12, cur_proc_ptr->fpreg_offset, 4);
14325      md_number_to_chars (fragp + 16, cur_proc_ptr->frame_offset, 4);
14326      md_number_to_chars (fragp + 20, cur_proc_ptr->frame_reg, 4);
14327      md_number_to_chars (fragp + 24, cur_proc_ptr->pc_reg, 4);
14328
14329      subseg_set (saved_seg, saved_subseg);
14330    }
14331#endif /* OBJ_ELF */
14332
14333  cur_proc_ptr = NULL;
14334}
14335
14336/* The .aent and .ent directives.  */
14337
14338static void
14339s_mips_ent (int aent)
14340{
14341  symbolS *symbolP;
14342
14343  symbolP = get_symbol ();
14344  if (*input_line_pointer == ',')
14345    ++input_line_pointer;
14346  SKIP_WHITESPACE ();
14347  if (ISDIGIT (*input_line_pointer)
14348      || *input_line_pointer == '-')
14349    get_number ();
14350
14351  if ((bfd_get_section_flags (stdoutput, now_seg) & SEC_CODE) == 0)
14352    as_warn (_(".ent or .aent not in text section."));
14353
14354  if (!aent && cur_proc_ptr)
14355    as_warn (_("missing .end"));
14356
14357  if (!aent)
14358    {
14359      /* This function needs its own .frame and .cprestore directives.  */
14360      mips_frame_reg_valid = 0;
14361      mips_cprestore_valid = 0;
14362
14363      cur_proc_ptr = &cur_proc;
14364      memset (cur_proc_ptr, '\0', sizeof (procS));
14365
14366      cur_proc_ptr->func_sym = symbolP;
14367
14368      symbol_get_bfdsym (symbolP)->flags |= BSF_FUNCTION;
14369
14370      ++numprocs;
14371
14372      if (debug_type == DEBUG_STABS)
14373        stabs_generate_asm_func (S_GET_NAME (symbolP),
14374				 S_GET_NAME (symbolP));
14375    }
14376
14377  demand_empty_rest_of_line ();
14378}
14379
14380/* The .frame directive. If the mdebug section is present (IRIX 5 native)
14381   then ecoff.c (ecoff_directive_frame) is used. For embedded targets,
14382   s_mips_frame is used so that we can set the PDR information correctly.
14383   We can't use the ecoff routines because they make reference to the ecoff
14384   symbol table (in the mdebug section).  */
14385
14386static void
14387s_mips_frame (int ignore ATTRIBUTE_UNUSED)
14388{
14389#ifdef OBJ_ELF
14390  if (OUTPUT_FLAVOR == bfd_target_elf_flavour && ! ECOFF_DEBUGGING)
14391    {
14392      long val;
14393
14394      if (cur_proc_ptr == (procS *) NULL)
14395	{
14396	  as_warn (_(".frame outside of .ent"));
14397	  demand_empty_rest_of_line ();
14398	  return;
14399	}
14400
14401      cur_proc_ptr->frame_reg = tc_get_register (1);
14402
14403      SKIP_WHITESPACE ();
14404      if (*input_line_pointer++ != ','
14405	  || get_absolute_expression_and_terminator (&val) != ',')
14406	{
14407	  as_warn (_("Bad .frame directive"));
14408	  --input_line_pointer;
14409	  demand_empty_rest_of_line ();
14410	  return;
14411	}
14412
14413      cur_proc_ptr->frame_offset = val;
14414      cur_proc_ptr->pc_reg = tc_get_register (0);
14415
14416      demand_empty_rest_of_line ();
14417    }
14418  else
14419#endif /* OBJ_ELF */
14420    s_ignore (ignore);
14421}
14422
14423/* The .fmask and .mask directives. If the mdebug section is present
14424   (IRIX 5 native) then ecoff.c (ecoff_directive_mask) is used. For
14425   embedded targets, s_mips_mask is used so that we can set the PDR
14426   information correctly. We can't use the ecoff routines because they
14427   make reference to the ecoff symbol table (in the mdebug section).  */
14428
14429static void
14430s_mips_mask (int reg_type)
14431{
14432#ifdef OBJ_ELF
14433  if (OUTPUT_FLAVOR == bfd_target_elf_flavour && ! ECOFF_DEBUGGING)
14434    {
14435      long mask, off;
14436
14437      if (cur_proc_ptr == (procS *) NULL)
14438	{
14439	  as_warn (_(".mask/.fmask outside of .ent"));
14440	  demand_empty_rest_of_line ();
14441	  return;
14442	}
14443
14444      if (get_absolute_expression_and_terminator (&mask) != ',')
14445	{
14446	  as_warn (_("Bad .mask/.fmask directive"));
14447	  --input_line_pointer;
14448	  demand_empty_rest_of_line ();
14449	  return;
14450	}
14451
14452      off = get_absolute_expression ();
14453
14454      if (reg_type == 'F')
14455	{
14456	  cur_proc_ptr->fpreg_mask = mask;
14457	  cur_proc_ptr->fpreg_offset = off;
14458	}
14459      else
14460	{
14461	  cur_proc_ptr->reg_mask = mask;
14462	  cur_proc_ptr->reg_offset = off;
14463	}
14464
14465      demand_empty_rest_of_line ();
14466    }
14467  else
14468#endif /* OBJ_ELF */
14469    s_ignore (reg_type);
14470}
14471
14472/* A table describing all the processors gas knows about.  Names are
14473   matched in the order listed.
14474
14475   To ease comparison, please keep this table in the same order as
14476   gcc's mips_cpu_info_table[].  */
14477static const struct mips_cpu_info mips_cpu_info_table[] =
14478{
14479  /* Entries for generic ISAs */
14480  { "mips1",          1,      ISA_MIPS1,      CPU_R3000 },
14481  { "mips2",          1,      ISA_MIPS2,      CPU_R6000 },
14482  { "mips3",          1,      ISA_MIPS3,      CPU_R4000 },
14483  { "mips4",          1,      ISA_MIPS4,      CPU_R8000 },
14484  { "mips5",          1,      ISA_MIPS5,      CPU_MIPS5 },
14485  { "mips32",         1,      ISA_MIPS32,     CPU_MIPS32 },
14486  { "mips32r2",       1,      ISA_MIPS32R2,   CPU_MIPS32R2 },
14487  { "mips64",         1,      ISA_MIPS64,     CPU_MIPS64 },
14488  { "mips64r2",       1,      ISA_MIPS64R2,   CPU_MIPS64R2 },
14489
14490  /* MIPS I */
14491  { "r3000",          0,      ISA_MIPS1,      CPU_R3000 },
14492  { "r2000",          0,      ISA_MIPS1,      CPU_R3000 },
14493  { "r3900",          0,      ISA_MIPS1,      CPU_R3900 },
14494
14495  /* MIPS II */
14496  { "r6000",          0,      ISA_MIPS2,      CPU_R6000 },
14497
14498  /* MIPS III */
14499  { "r4000",          0,      ISA_MIPS3,      CPU_R4000 },
14500  { "r4010",          0,      ISA_MIPS2,      CPU_R4010 },
14501  { "vr4100",         0,      ISA_MIPS3,      CPU_VR4100 },
14502  { "vr4111",         0,      ISA_MIPS3,      CPU_R4111 },
14503  { "vr4120",         0,      ISA_MIPS3,      CPU_VR4120 },
14504  { "vr4130",         0,      ISA_MIPS3,      CPU_VR4120 },
14505  { "vr4181",         0,      ISA_MIPS3,      CPU_R4111 },
14506  { "vr4300",         0,      ISA_MIPS3,      CPU_R4300 },
14507  { "r4400",          0,      ISA_MIPS3,      CPU_R4400 },
14508  { "r4600",          0,      ISA_MIPS3,      CPU_R4600 },
14509  { "orion",          0,      ISA_MIPS3,      CPU_R4600 },
14510  { "r4650",          0,      ISA_MIPS3,      CPU_R4650 },
14511
14512  /* MIPS IV */
14513  { "r8000",          0,      ISA_MIPS4,      CPU_R8000 },
14514  { "r10000",         0,      ISA_MIPS4,      CPU_R10000 },
14515  { "r12000",         0,      ISA_MIPS4,      CPU_R12000 },
14516  { "vr5000",         0,      ISA_MIPS4,      CPU_R5000 },
14517  { "vr5400",         0,      ISA_MIPS4,      CPU_VR5400 },
14518  { "vr5500",         0,      ISA_MIPS4,      CPU_VR5500 },
14519  { "rm5200",         0,      ISA_MIPS4,      CPU_R5000 },
14520  { "rm5230",         0,      ISA_MIPS4,      CPU_R5000 },
14521  { "rm5231",         0,      ISA_MIPS4,      CPU_R5000 },
14522  { "rm5261",         0,      ISA_MIPS4,      CPU_R5000 },
14523  { "rm5721",         0,      ISA_MIPS4,      CPU_R5000 },
14524  { "rm7000",         0,      ISA_MIPS4,      CPU_RM7000 },
14525  { "rm9000",         0,      ISA_MIPS4,      CPU_RM9000 },
14526
14527  /* MIPS 32 */
14528  { "4kc",            0,      ISA_MIPS32,     CPU_MIPS32 },
14529  { "4km",            0,      ISA_MIPS32,     CPU_MIPS32 },
14530  { "4kp",            0,      ISA_MIPS32,     CPU_MIPS32 },
14531
14532  /* MIPS32 Release 2 */
14533  { "m4k",            0,      ISA_MIPS32R2,   CPU_MIPS32R2 },
14534  { "24k",            0,      ISA_MIPS32R2,   CPU_MIPS32R2 },
14535  { "24kc",           0,      ISA_MIPS32R2,   CPU_MIPS32R2 },
14536  { "24kf",           0,      ISA_MIPS32R2,   CPU_MIPS32R2 },
14537  { "24kx",           0,      ISA_MIPS32R2,   CPU_MIPS32R2 },
14538
14539  /* MIPS 64 */
14540  { "5kc",            0,      ISA_MIPS64,     CPU_MIPS64 },
14541  { "5kf",            0,      ISA_MIPS64,     CPU_MIPS64 },
14542  { "20kc",           0,      ISA_MIPS64,     CPU_MIPS64 },
14543
14544  /* Broadcom SB-1 CPU core */
14545  { "sb1",            0,      ISA_MIPS64,     CPU_SB1 },
14546
14547  /* Cavium Networks Octeon CPU core */
14548  { "octeon",         0,      ISA_MIPS64R2,   CPU_OCTEON },
14549
14550  /* End marker */
14551  { NULL, 0, 0, 0 }
14552};
14553
14554
14555/* Return true if GIVEN is the same as CANONICAL, or if it is CANONICAL
14556   with a final "000" replaced by "k".  Ignore case.
14557
14558   Note: this function is shared between GCC and GAS.  */
14559
14560static bfd_boolean
14561mips_strict_matching_cpu_name_p (const char *canonical, const char *given)
14562{
14563  while (*given != 0 && TOLOWER (*given) == TOLOWER (*canonical))
14564    given++, canonical++;
14565
14566  return ((*given == 0 && *canonical == 0)
14567	  || (strcmp (canonical, "000") == 0 && strcasecmp (given, "k") == 0));
14568}
14569
14570
14571/* Return true if GIVEN matches CANONICAL, where GIVEN is a user-supplied
14572   CPU name.  We've traditionally allowed a lot of variation here.
14573
14574   Note: this function is shared between GCC and GAS.  */
14575
14576static bfd_boolean
14577mips_matching_cpu_name_p (const char *canonical, const char *given)
14578{
14579  /* First see if the name matches exactly, or with a final "000"
14580     turned into "k".  */
14581  if (mips_strict_matching_cpu_name_p (canonical, given))
14582    return TRUE;
14583
14584  /* If not, try comparing based on numerical designation alone.
14585     See if GIVEN is an unadorned number, or 'r' followed by a number.  */
14586  if (TOLOWER (*given) == 'r')
14587    given++;
14588  if (!ISDIGIT (*given))
14589    return FALSE;
14590
14591  /* Skip over some well-known prefixes in the canonical name,
14592     hoping to find a number there too.  */
14593  if (TOLOWER (canonical[0]) == 'v' && TOLOWER (canonical[1]) == 'r')
14594    canonical += 2;
14595  else if (TOLOWER (canonical[0]) == 'r' && TOLOWER (canonical[1]) == 'm')
14596    canonical += 2;
14597  else if (TOLOWER (canonical[0]) == 'r')
14598    canonical += 1;
14599
14600  return mips_strict_matching_cpu_name_p (canonical, given);
14601}
14602
14603
14604/* Parse an option that takes the name of a processor as its argument.
14605   OPTION is the name of the option and CPU_STRING is the argument.
14606   Return the corresponding processor enumeration if the CPU_STRING is
14607   recognized, otherwise report an error and return null.
14608
14609   A similar function exists in GCC.  */
14610
14611static const struct mips_cpu_info *
14612mips_parse_cpu (const char *option, const char *cpu_string)
14613{
14614  const struct mips_cpu_info *p;
14615
14616  /* 'from-abi' selects the most compatible architecture for the given
14617     ABI: MIPS I for 32-bit ABIs and MIPS III for 64-bit ABIs.  For the
14618     EABIs, we have to decide whether we're using the 32-bit or 64-bit
14619     version.  Look first at the -mgp options, if given, otherwise base
14620     the choice on MIPS_DEFAULT_64BIT.
14621
14622     Treat NO_ABI like the EABIs.  One reason to do this is that the
14623     plain 'mips' and 'mips64' configs have 'from-abi' as their default
14624     architecture.  This code picks MIPS I for 'mips' and MIPS III for
14625     'mips64', just as we did in the days before 'from-abi'.  */
14626  if (strcasecmp (cpu_string, "from-abi") == 0)
14627    {
14628      if (ABI_NEEDS_32BIT_REGS (mips_abi))
14629	return mips_cpu_info_from_isa (ISA_MIPS1);
14630
14631      if (ABI_NEEDS_64BIT_REGS (mips_abi))
14632	return mips_cpu_info_from_isa (ISA_MIPS3);
14633
14634      if (file_mips_gp32 >= 0)
14635	return mips_cpu_info_from_isa (file_mips_gp32 ? ISA_MIPS1 : ISA_MIPS3);
14636
14637      return mips_cpu_info_from_isa (MIPS_DEFAULT_64BIT
14638				     ? ISA_MIPS3
14639				     : ISA_MIPS1);
14640    }
14641
14642  /* 'default' has traditionally been a no-op.  Probably not very useful.  */
14643  if (strcasecmp (cpu_string, "default") == 0)
14644    return 0;
14645
14646  for (p = mips_cpu_info_table; p->name != 0; p++)
14647    if (mips_matching_cpu_name_p (p->name, cpu_string))
14648      return p;
14649
14650  as_bad ("Bad value (%s) for %s", cpu_string, option);
14651  return 0;
14652}
14653
14654/* Return the canonical processor information for ISA (a member of the
14655   ISA_MIPS* enumeration).  */
14656
14657static const struct mips_cpu_info *
14658mips_cpu_info_from_isa (int isa)
14659{
14660  int i;
14661
14662  for (i = 0; mips_cpu_info_table[i].name != NULL; i++)
14663    if (mips_cpu_info_table[i].is_isa
14664	&& isa == mips_cpu_info_table[i].isa)
14665      return (&mips_cpu_info_table[i]);
14666
14667  return NULL;
14668}
14669
14670static const struct mips_cpu_info *
14671mips_cpu_info_from_arch (int arch)
14672{
14673  int i;
14674
14675  for (i = 0; mips_cpu_info_table[i].name != NULL; i++)
14676    if (arch == mips_cpu_info_table[i].cpu)
14677      return (&mips_cpu_info_table[i]);
14678
14679  return NULL;
14680}
14681
14682static void
14683show (FILE *stream, const char *string, int *col_p, int *first_p)
14684{
14685  if (*first_p)
14686    {
14687      fprintf (stream, "%24s", "");
14688      *col_p = 24;
14689    }
14690  else
14691    {
14692      fprintf (stream, ", ");
14693      *col_p += 2;
14694    }
14695
14696  if (*col_p + strlen (string) > 72)
14697    {
14698      fprintf (stream, "\n%24s", "");
14699      *col_p = 24;
14700    }
14701
14702  fprintf (stream, "%s", string);
14703  *col_p += strlen (string);
14704
14705  *first_p = 0;
14706}
14707
14708void
14709md_show_usage (FILE *stream)
14710{
14711  int column, first;
14712  size_t i;
14713
14714  fprintf (stream, _("\
14715MIPS options:\n\
14716-EB			generate big endian output\n\
14717-EL			generate little endian output\n\
14718-g, -g2			do not remove unneeded NOPs or swap branches\n\
14719-G NUM			allow referencing objects up to NUM bytes\n\
14720			implicitly with the gp register [default 8]\n"));
14721  fprintf (stream, _("\
14722-mips1			generate MIPS ISA I instructions\n\
14723-mips2			generate MIPS ISA II instructions\n\
14724-mips3			generate MIPS ISA III instructions\n\
14725-mips4			generate MIPS ISA IV instructions\n\
14726-mips5                  generate MIPS ISA V instructions\n\
14727-mips32                 generate MIPS32 ISA instructions\n\
14728-mips32r2               generate MIPS32 release 2 ISA instructions\n\
14729-mips64                 generate MIPS64 ISA instructions\n\
14730-mips64r2               generate MIPS64 release 2 ISA instructions\n\
14731-march=CPU/-mtune=CPU	generate code/schedule for CPU, where CPU is one of:\n"));
14732
14733  first = 1;
14734
14735  for (i = 0; mips_cpu_info_table[i].name != NULL; i++)
14736    show (stream, mips_cpu_info_table[i].name, &column, &first);
14737  show (stream, "from-abi", &column, &first);
14738  fputc ('\n', stream);
14739
14740  fprintf (stream, _("\
14741-mCPU			equivalent to -march=CPU -mtune=CPU. Deprecated.\n\
14742-no-mCPU		don't generate code specific to CPU.\n\
14743			For -mCPU and -no-mCPU, CPU must be one of:\n"));
14744
14745  first = 1;
14746
14747  show (stream, "3900", &column, &first);
14748  show (stream, "4010", &column, &first);
14749  show (stream, "4100", &column, &first);
14750  show (stream, "4650", &column, &first);
14751  fputc ('\n', stream);
14752
14753  fprintf (stream, _("\
14754-mips16			generate mips16 instructions\n\
14755-no-mips16		do not generate mips16 instructions\n"));
14756  fprintf (stream, _("\
14757-mdsp			generate DSP instructions\n\
14758-mno-dsp		do not generate DSP instructions\n"));
14759  fprintf (stream, _("\
14760-mmt			generate MT instructions\n\
14761-mno-mt			do not generate MT instructions\n"));
14762  fprintf (stream, _("\
14763-mfix-vr4120		work around certain VR4120 errata\n\
14764-mfix-vr4130		work around VR4130 mflo/mfhi errata\n\
14765-mgp32			use 32-bit GPRs, regardless of the chosen ISA\n\
14766-mfp32			use 32-bit FPRs, regardless of the chosen ISA\n\
14767-mno-shared		optimize output for executables\n\
14768-msym32			assume all symbols have 32-bit values\n\
14769-O0			remove unneeded NOPs, do not swap branches\n\
14770-O			remove unneeded NOPs and swap branches\n\
14771--[no-]construct-floats [dis]allow floating point values to be constructed\n\
14772--trap, --no-break	trap exception on div by 0 and mult overflow\n\
14773--break, --no-trap	break exception on div by 0 and mult overflow\n"));
14774#ifdef OBJ_ELF
14775  fprintf (stream, _("\
14776-KPIC, -call_shared	generate SVR4 position independent code\n\
14777-non_shared		do not generate position independent code\n\
14778-xgot			assume a 32 bit GOT\n\
14779-mpdr, -mno-pdr		enable/disable creation of .pdr sections\n\
14780-mshared, -mno-shared   disable/enable .cpload optimization for\n\
14781                        non-shared code\n\
14782-mabi=ABI		create ABI conformant object file for:\n"));
14783
14784  first = 1;
14785
14786  show (stream, "32", &column, &first);
14787  show (stream, "o64", &column, &first);
14788  show (stream, "n32", &column, &first);
14789  show (stream, "64", &column, &first);
14790  show (stream, "eabi", &column, &first);
14791
14792  fputc ('\n', stream);
14793
14794  fprintf (stream, _("\
14795-32			create o32 ABI object file (default)\n\
14796-n32			create n32 ABI object file\n\
14797-64			create 64 ABI object file\n"));
14798#endif
14799  fprintf (stream, _("\
14800-mocteon-unsupported    error on unsupported Octeon instructions\n\
14801-mno-octeon-unsupported do not error on unsupported Octeon instructions\n"));
14802  fprintf (stream, _("\
14803-mocteon-useun    generate Octeon unaligned load/store instructions\n\
14804-mno-octeon-useun generate MIPS unaligned load/store instructions\n"));
14805}
14806
14807enum dwarf2_format
14808mips_dwarf2_format (void)
14809{
14810  if (HAVE_64BIT_SYMBOLS)
14811    {
14812#ifdef TE_IRIX
14813      return dwarf2_format_64bit_irix;
14814#else
14815      return dwarf2_format_64bit;
14816#endif
14817    }
14818  else
14819    return dwarf2_format_32bit;
14820}
14821
14822int
14823mips_dwarf2_addr_size (void)
14824{
14825  if (HAVE_64BIT_SYMBOLS)
14826    return 8;
14827  else
14828    return 4;
14829}
14830
14831/* Standard calling conventions leave the CFA at SP on entry.  */
14832void
14833mips_cfi_frame_initial_instructions (void)
14834{
14835  cfi_add_CFA_def_cfa_register (SP);
14836}
14837
14838