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, 2006, 2007, 2008, 2009, 2010
4   Free Software Foundation, Inc.
5   Contributed by the OSF and Ralph Campbell.
6   Written by Keith Knowles and Ralph Campbell, working independently.
7   Modified for ECOFF and R4000 support by Ian Lance Taylor of Cygnus
8   Support.
9
10   This file is part of GAS.
11
12   GAS is free software; you can redistribute it and/or modify
13   it under the terms of the GNU General Public License as published by
14   the Free Software Foundation; either version 3, or (at your option)
15   any later version.
16
17   GAS is distributed in the hope that it will be useful,
18   but WITHOUT ANY WARRANTY; without even the implied warranty of
19   MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
20   GNU General Public License for more details.
21
22   You should have received a copy of the GNU General Public License
23   along with GAS; see the file COPYING.  If not, write to the Free
24   Software Foundation, 51 Franklin Street - Fifth Floor, Boston, MA
25   02110-1301, USA.  */
26
27#include "as.h"
28#include "config.h"
29#include "subsegs.h"
30#include "safe-ctype.h"
31
32#include "opcode/mips.h"
33#include "itbl-ops.h"
34#include "dwarf2dbg.h"
35#include "dw2gencfi.h"
36
37#ifdef DEBUG
38#define DBG(x) printf x
39#else
40#define DBG(x)
41#endif
42
43#ifdef OBJ_MAYBE_ELF
44/* Clean up namespace so we can include obj-elf.h too.  */
45static int mips_output_flavor (void);
46static int mips_output_flavor (void) { return OUTPUT_FLAVOR; }
47#undef OBJ_PROCESS_STAB
48#undef OUTPUT_FLAVOR
49#undef S_GET_ALIGN
50#undef S_GET_SIZE
51#undef S_SET_ALIGN
52#undef S_SET_SIZE
53#undef obj_frob_file
54#undef obj_frob_file_after_relocs
55#undef obj_frob_symbol
56#undef obj_pop_insert
57#undef obj_sec_sym_ok_for_reloc
58#undef OBJ_COPY_SYMBOL_ATTRIBUTES
59
60#include "obj-elf.h"
61/* Fix any of them that we actually care about.  */
62#undef OUTPUT_FLAVOR
63#define OUTPUT_FLAVOR mips_output_flavor()
64#endif
65
66#if defined (OBJ_ELF)
67#include "elf/mips.h"
68#endif
69
70#ifndef ECOFF_DEBUGGING
71#define NO_ECOFF_DEBUGGING
72#define ECOFF_DEBUGGING 0
73#endif
74
75int mips_flag_mdebug = -1;
76
77/* Control generation of .pdr sections.  Off by default on IRIX: the native
78   linker doesn't know about and discards them, but relocations against them
79   remain, leading to rld crashes.  */
80#ifdef TE_IRIX
81int mips_flag_pdr = FALSE;
82#else
83int mips_flag_pdr = TRUE;
84#endif
85
86#include "ecoff.h"
87
88#if defined (OBJ_ELF) || defined (OBJ_MAYBE_ELF)
89static char *mips_regmask_frag;
90#endif
91
92#define ZERO 0
93#define ATREG 1
94#define TREG 24
95#define PIC_CALL_REG 25
96#define KT0 26
97#define KT1 27
98#define GP  28
99#define SP  29
100#define FP  30
101#define RA  31
102
103#define ILLEGAL_REG (32)
104
105#define AT  mips_opts.at
106
107/* Allow override of standard little-endian ECOFF format.  */
108
109#ifndef ECOFF_LITTLE_FORMAT
110#define ECOFF_LITTLE_FORMAT "ecoff-littlemips"
111#endif
112
113extern int target_big_endian;
114
115/* The name of the readonly data section.  */
116#define RDATA_SECTION_NAME (OUTPUT_FLAVOR == bfd_target_ecoff_flavour \
117			    ? ".rdata" \
118			    : OUTPUT_FLAVOR == bfd_target_coff_flavour \
119			    ? ".rdata" \
120			    : OUTPUT_FLAVOR == bfd_target_elf_flavour \
121			    ? ".rodata" \
122			    : (abort (), ""))
123
124/* Information about an instruction, including its format, operands
125   and fixups.  */
126struct mips_cl_insn
127{
128  /* The opcode's entry in mips_opcodes or mips16_opcodes.  */
129  const struct mips_opcode *insn_mo;
130
131  /* True if this is a mips16 instruction and if we want the extended
132     form of INSN_MO.  */
133  bfd_boolean use_extend;
134
135  /* The 16-bit extension instruction to use when USE_EXTEND is true.  */
136  unsigned short extend;
137
138  /* The 16-bit or 32-bit bitstring of the instruction itself.  This is
139     a copy of INSN_MO->match with the operands filled in.  */
140  unsigned long insn_opcode;
141
142  /* The frag that contains the instruction.  */
143  struct frag *frag;
144
145  /* The offset into FRAG of the first instruction byte.  */
146  long where;
147
148  /* The relocs associated with the instruction, if any.  */
149  fixS *fixp[3];
150
151  /* True if this entry cannot be moved from its current position.  */
152  unsigned int fixed_p : 1;
153
154  /* True if this instruction occurred in a .set noreorder block.  */
155  unsigned int noreorder_p : 1;
156
157  /* True for mips16 instructions that jump to an absolute address.  */
158  unsigned int mips16_absolute_jump_p : 1;
159};
160
161/* The ABI to use.  */
162enum mips_abi_level
163{
164  NO_ABI = 0,
165  O32_ABI,
166  O64_ABI,
167  N32_ABI,
168  N64_ABI,
169  EABI_ABI
170};
171
172/* MIPS ABI we are using for this output file.  */
173static enum mips_abi_level mips_abi = NO_ABI;
174
175/* Whether or not we have code that can call pic code.  */
176int mips_abicalls = FALSE;
177
178/* Whether or not we have code which can be put into a shared
179   library.  */
180static bfd_boolean mips_in_shared = TRUE;
181
182/* This is the set of options which may be modified by the .set
183   pseudo-op.  We use a struct so that .set push and .set pop are more
184   reliable.  */
185
186struct mips_set_options
187{
188  /* MIPS ISA (Instruction Set Architecture) level.  This is set to -1
189     if it has not been initialized.  Changed by `.set mipsN', and the
190     -mipsN command line option, and the default CPU.  */
191  int isa;
192  /* Enabled Application Specific Extensions (ASEs).  These are set to -1
193     if they have not been initialized.  Changed by `.set <asename>', by
194     command line options, and based on the default architecture.  */
195  int ase_mips3d;
196  int ase_mdmx;
197  int ase_smartmips;
198  int ase_dsp;
199  int ase_dspr2;
200  int ase_mt;
201  /* Whether we are assembling for the mips16 processor.  0 if we are
202     not, 1 if we are, and -1 if the value has not been initialized.
203     Changed by `.set mips16' and `.set nomips16', and the -mips16 and
204     -nomips16 command line options, and the default CPU.  */
205  int mips16;
206  /* Non-zero if we should not reorder instructions.  Changed by `.set
207     reorder' and `.set noreorder'.  */
208  int noreorder;
209  /* Non-zero if we should not permit the register designated "assembler
210     temporary" to be used in instructions.  The value is the register
211     number, normally $at ($1).  Changed by `.set at=REG', `.set noat'
212     (same as `.set at=$0') and `.set at' (same as `.set at=$1').  */
213  unsigned int at;
214  /* Non-zero if we should warn when a macro instruction expands into
215     more than one machine instruction.  Changed by `.set nomacro' and
216     `.set macro'.  */
217  int warn_about_macros;
218  /* Non-zero if we should not move instructions.  Changed by `.set
219     move', `.set volatile', `.set nomove', and `.set novolatile'.  */
220  int nomove;
221  /* Non-zero if we should not optimize branches by moving the target
222     of the branch into the delay slot.  Actually, we don't perform
223     this optimization anyhow.  Changed by `.set bopt' and `.set
224     nobopt'.  */
225  int nobopt;
226  /* Non-zero if we should not autoextend mips16 instructions.
227     Changed by `.set autoextend' and `.set noautoextend'.  */
228  int noautoextend;
229  /* Restrict general purpose registers and floating point registers
230     to 32 bit.  This is initially determined when -mgp32 or -mfp32
231     is passed but can changed if the assembler code uses .set mipsN.  */
232  int gp32;
233  int fp32;
234  /* MIPS architecture (CPU) type.  Changed by .set arch=FOO, the -march
235     command line option, and the default CPU.  */
236  int arch;
237  /* True if ".set sym32" is in effect.  */
238  bfd_boolean sym32;
239  /* True if floating-point operations are not allowed.  Changed by .set
240     softfloat or .set hardfloat, by command line options -msoft-float or
241     -mhard-float.  The default is false.  */
242  bfd_boolean soft_float;
243
244  /* True if only single-precision floating-point operations are allowed.
245     Changed by .set singlefloat or .set doublefloat, command-line options
246     -msingle-float or -mdouble-float.  The default is false.  */
247  bfd_boolean single_float;
248};
249
250/* This is the struct we use to hold the current set of options.  Note
251   that we must set the isa field to ISA_UNKNOWN and the ASE fields to
252   -1 to indicate that they have not been initialized.  */
253
254/* True if -mgp32 was passed.  */
255static int file_mips_gp32 = -1;
256
257/* True if -mfp32 was passed.  */
258static int file_mips_fp32 = -1;
259
260/* 1 if -msoft-float, 0 if -mhard-float.  The default is 0.  */
261static int file_mips_soft_float = 0;
262
263/* 1 if -msingle-float, 0 if -mdouble-float.  The default is 0.   */
264static int file_mips_single_float = 0;
265
266static struct mips_set_options mips_opts =
267{
268  /* isa */ ISA_UNKNOWN, /* ase_mips3d */ -1, /* ase_mdmx */ -1,
269  /* ase_smartmips */ 0, /* ase_dsp */ -1, /* ase_dspr2 */ -1, /* ase_mt */ -1,
270  /* mips16 */ -1, /* noreorder */ 0, /* at */ ATREG,
271  /* warn_about_macros */ 0, /* nomove */ 0, /* nobopt */ 0,
272  /* noautoextend */ 0, /* gp32 */ 0, /* fp32 */ 0, /* arch */ CPU_UNKNOWN,
273  /* sym32 */ FALSE, /* soft_float */ FALSE, /* single_float */ FALSE
274};
275
276/* These variables are filled in with the masks of registers used.
277   The object format code reads them and puts them in the appropriate
278   place.  */
279unsigned long mips_gprmask;
280unsigned long mips_cprmask[4];
281
282/* MIPS ISA we are using for this output file.  */
283static int file_mips_isa = ISA_UNKNOWN;
284
285/* True if -mips16 was passed or implied by arguments passed on the
286   command line (e.g., by -march).  */
287static int file_ase_mips16;
288
289#define ISA_SUPPORTS_MIPS16E (mips_opts.isa == ISA_MIPS32		\
290			      || mips_opts.isa == ISA_MIPS32R2		\
291			      || mips_opts.isa == ISA_MIPS64		\
292			      || mips_opts.isa == ISA_MIPS64R2)
293
294/* True if we want to create R_MIPS_JALR for jalr $25.  */
295#ifdef TE_IRIX
296#define MIPS_JALR_HINT_P(EXPR) HAVE_NEWABI
297#else
298/* As a GNU extension, we use R_MIPS_JALR for o32 too.  However,
299   because there's no place for any addend, the only acceptable
300   expression is a bare symbol.  */
301#define MIPS_JALR_HINT_P(EXPR) \
302  (!HAVE_IN_PLACE_ADDENDS \
303   || ((EXPR)->X_op == O_symbol && (EXPR)->X_add_number == 0))
304#endif
305
306/* True if -mips3d was passed or implied by arguments passed on the
307   command line (e.g., by -march).  */
308static int file_ase_mips3d;
309
310/* True if -mdmx was passed or implied by arguments passed on the
311   command line (e.g., by -march).  */
312static int file_ase_mdmx;
313
314/* True if -msmartmips was passed or implied by arguments passed on the
315   command line (e.g., by -march).  */
316static int file_ase_smartmips;
317
318#define ISA_SUPPORTS_SMARTMIPS (mips_opts.isa == ISA_MIPS32		\
319				|| mips_opts.isa == ISA_MIPS32R2)
320
321/* True if -mdsp was passed or implied by arguments passed on the
322   command line (e.g., by -march).  */
323static int file_ase_dsp;
324
325#define ISA_SUPPORTS_DSP_ASE (mips_opts.isa == ISA_MIPS32R2		\
326			      || mips_opts.isa == ISA_MIPS64R2)
327
328#define ISA_SUPPORTS_DSP64_ASE (mips_opts.isa == ISA_MIPS64R2)
329
330/* True if -mdspr2 was passed or implied by arguments passed on the
331   command line (e.g., by -march).  */
332static int file_ase_dspr2;
333
334#define ISA_SUPPORTS_DSPR2_ASE (mips_opts.isa == ISA_MIPS32R2		\
335			        || mips_opts.isa == ISA_MIPS64R2)
336
337/* True if -mmt was passed or implied by arguments passed on the
338   command line (e.g., by -march).  */
339static int file_ase_mt;
340
341#define ISA_SUPPORTS_MT_ASE (mips_opts.isa == ISA_MIPS32R2		\
342			     || mips_opts.isa == ISA_MIPS64R2)
343
344/* The argument of the -march= flag.  The architecture we are assembling.  */
345static int file_mips_arch = CPU_UNKNOWN;
346static const char *mips_arch_string;
347
348/* The argument of the -mtune= flag.  The architecture for which we
349   are optimizing.  */
350static int mips_tune = CPU_UNKNOWN;
351static const char *mips_tune_string;
352
353/* True when generating 32-bit code for a 64-bit processor.  */
354static int mips_32bitmode = 0;
355
356/* True if the given ABI requires 32-bit registers.  */
357#define ABI_NEEDS_32BIT_REGS(ABI) ((ABI) == O32_ABI)
358
359/* Likewise 64-bit registers.  */
360#define ABI_NEEDS_64BIT_REGS(ABI)	\
361  ((ABI) == N32_ABI 			\
362   || (ABI) == N64_ABI			\
363   || (ABI) == O64_ABI)
364
365/*  Return true if ISA supports 64 bit wide gp registers.  */
366#define ISA_HAS_64BIT_REGS(ISA)		\
367  ((ISA) == ISA_MIPS3			\
368   || (ISA) == ISA_MIPS4		\
369   || (ISA) == ISA_MIPS5		\
370   || (ISA) == ISA_MIPS64		\
371   || (ISA) == ISA_MIPS64R2)
372
373/*  Return true if ISA supports 64 bit wide float registers.  */
374#define ISA_HAS_64BIT_FPRS(ISA)		\
375  ((ISA) == ISA_MIPS3			\
376   || (ISA) == ISA_MIPS4		\
377   || (ISA) == ISA_MIPS5		\
378   || (ISA) == ISA_MIPS32R2		\
379   || (ISA) == ISA_MIPS64		\
380   || (ISA) == ISA_MIPS64R2)
381
382/* Return true if ISA supports 64-bit right rotate (dror et al.)
383   instructions.  */
384#define ISA_HAS_DROR(ISA)		\
385  ((ISA) == ISA_MIPS64R2)
386
387/* Return true if ISA supports 32-bit right rotate (ror et al.)
388   instructions.  */
389#define ISA_HAS_ROR(ISA)		\
390  ((ISA) == ISA_MIPS32R2		\
391   || (ISA) == ISA_MIPS64R2		\
392   || mips_opts.ase_smartmips)
393
394/* Return true if ISA supports single-precision floats in odd registers.  */
395#define ISA_HAS_ODD_SINGLE_FPR(ISA)	\
396  ((ISA) == ISA_MIPS32			\
397   || (ISA) == ISA_MIPS32R2		\
398   || (ISA) == ISA_MIPS64		\
399   || (ISA) == ISA_MIPS64R2)
400
401/* Return true if ISA supports move to/from high part of a 64-bit
402   floating-point register. */
403#define ISA_HAS_MXHC1(ISA)		\
404  ((ISA) == ISA_MIPS32R2		\
405   || (ISA) == ISA_MIPS64R2)
406
407#define HAVE_32BIT_GPRS		                   \
408    (mips_opts.gp32 || !ISA_HAS_64BIT_REGS (mips_opts.isa))
409
410#define HAVE_32BIT_FPRS                            \
411    (mips_opts.fp32 || !ISA_HAS_64BIT_FPRS (mips_opts.isa))
412
413#define HAVE_64BIT_GPRS (!HAVE_32BIT_GPRS)
414#define HAVE_64BIT_FPRS (!HAVE_32BIT_FPRS)
415
416#define HAVE_NEWABI (mips_abi == N32_ABI || mips_abi == N64_ABI)
417
418#define HAVE_64BIT_OBJECTS (mips_abi == N64_ABI)
419
420/* True if relocations are stored in-place.  */
421#define HAVE_IN_PLACE_ADDENDS (!HAVE_NEWABI)
422
423/* The ABI-derived address size.  */
424#define HAVE_64BIT_ADDRESSES \
425  (HAVE_64BIT_GPRS && (mips_abi == EABI_ABI || mips_abi == N64_ABI))
426#define HAVE_32BIT_ADDRESSES (!HAVE_64BIT_ADDRESSES)
427
428/* The size of symbolic constants (i.e., expressions of the form
429   "SYMBOL" or "SYMBOL + OFFSET").  */
430#define HAVE_32BIT_SYMBOLS \
431  (HAVE_32BIT_ADDRESSES || !HAVE_64BIT_OBJECTS || mips_opts.sym32)
432#define HAVE_64BIT_SYMBOLS (!HAVE_32BIT_SYMBOLS)
433
434/* Addresses are loaded in different ways, depending on the address size
435   in use.  The n32 ABI Documentation also mandates the use of additions
436   with overflow checking, but existing implementations don't follow it.  */
437#define ADDRESS_ADD_INSN						\
438   (HAVE_32BIT_ADDRESSES ? "addu" : "daddu")
439
440#define ADDRESS_ADDI_INSN						\
441   (HAVE_32BIT_ADDRESSES ? "addiu" : "daddiu")
442
443#define ADDRESS_LOAD_INSN						\
444   (HAVE_32BIT_ADDRESSES ? "lw" : "ld")
445
446#define ADDRESS_STORE_INSN						\
447   (HAVE_32BIT_ADDRESSES ? "sw" : "sd")
448
449/* Return true if the given CPU supports the MIPS16 ASE.  */
450#define CPU_HAS_MIPS16(cpu)						\
451   (strncmp (TARGET_CPU, "mips16", sizeof ("mips16") - 1) == 0		\
452    || strncmp (TARGET_CANONICAL, "mips-lsi-elf", sizeof ("mips-lsi-elf") - 1) == 0)
453
454/* True if CPU has a dror instruction.  */
455#define CPU_HAS_DROR(CPU)	((CPU) == CPU_VR5400 || (CPU) == CPU_VR5500)
456
457/* True if CPU has a ror instruction.  */
458#define CPU_HAS_ROR(CPU)	CPU_HAS_DROR (CPU)
459
460/* True if CPU has seq/sne and seqi/snei instructions.  */
461#define CPU_HAS_SEQ(CPU)	((CPU) == CPU_OCTEON)
462
463/* True if CPU does not implement the all the coprocessor insns.  For these
464   CPUs only those COP insns are accepted that are explicitly marked to be
465   available on the CPU.  ISA membership for COP insns is ignored.  */
466#define NO_ISA_COP(CPU)		((CPU) == CPU_OCTEON)
467
468/* True if mflo and mfhi can be immediately followed by instructions
469   which write to the HI and LO registers.
470
471   According to MIPS specifications, MIPS ISAs I, II, and III need
472   (at least) two instructions between the reads of HI/LO and
473   instructions which write them, and later ISAs do not.  Contradicting
474   the MIPS specifications, some MIPS IV processor user manuals (e.g.
475   the UM for the NEC Vr5000) document needing the instructions between
476   HI/LO reads and writes, as well.  Therefore, we declare only MIPS32,
477   MIPS64 and later ISAs to have the interlocks, plus any specific
478   earlier-ISA CPUs for which CPU documentation declares that the
479   instructions are really interlocked.  */
480#define hilo_interlocks \
481  (mips_opts.isa == ISA_MIPS32                        \
482   || mips_opts.isa == ISA_MIPS32R2                   \
483   || mips_opts.isa == ISA_MIPS64                     \
484   || mips_opts.isa == ISA_MIPS64R2                   \
485   || mips_opts.arch == CPU_R4010                     \
486   || mips_opts.arch == CPU_R10000                    \
487   || mips_opts.arch == CPU_R12000                    \
488   || mips_opts.arch == CPU_R14000                    \
489   || mips_opts.arch == CPU_R16000                    \
490   || mips_opts.arch == CPU_RM7000                    \
491   || mips_opts.arch == CPU_VR5500                    \
492   )
493
494/* Whether the processor uses hardware interlocks to protect reads
495   from the GPRs after they are loaded from memory, and thus does not
496   require nops to be inserted.  This applies to instructions marked
497   INSN_LOAD_MEMORY_DELAY.  These nops are only required at MIPS ISA
498   level I.  */
499#define gpr_interlocks \
500  (mips_opts.isa != ISA_MIPS1  \
501   || mips_opts.arch == CPU_R3900)
502
503/* Whether the processor uses hardware interlocks to avoid delays
504   required by coprocessor instructions, and thus does not require
505   nops to be inserted.  This applies to instructions marked
506   INSN_LOAD_COPROC_DELAY, INSN_COPROC_MOVE_DELAY, and to delays
507   between instructions marked INSN_WRITE_COND_CODE and ones marked
508   INSN_READ_COND_CODE.  These nops are only required at MIPS ISA
509   levels I, II, and III.  */
510/* Itbl support may require additional care here.  */
511#define cop_interlocks                                \
512  ((mips_opts.isa != ISA_MIPS1                        \
513    && mips_opts.isa != ISA_MIPS2                     \
514    && mips_opts.isa != ISA_MIPS3)                    \
515   || mips_opts.arch == CPU_R4300                     \
516   )
517
518/* Whether the processor uses hardware interlocks to protect reads
519   from coprocessor registers after they are loaded from memory, and
520   thus does not require nops to be inserted.  This applies to
521   instructions marked INSN_COPROC_MEMORY_DELAY.  These nops are only
522   requires at MIPS ISA level I.  */
523#define cop_mem_interlocks (mips_opts.isa != ISA_MIPS1)
524
525/* Is this a mfhi or mflo instruction?  */
526#define MF_HILO_INSN(PINFO) \
527  ((PINFO & INSN_READ_HI) || (PINFO & INSN_READ_LO))
528
529/* Returns true for a (non floating-point) coprocessor instruction.  Reading
530   or writing the condition code is only possible on the coprocessors and
531   these insns are not marked with INSN_COP.  Thus for these insns use the
532   condition-code flags.  */
533#define COP_INSN(PINFO)							\
534  (PINFO != INSN_MACRO							\
535   && ((PINFO) & (FP_S | FP_D)) == 0					\
536   && ((PINFO) & (INSN_COP | INSN_READ_COND_CODE | INSN_WRITE_COND_CODE)))
537
538/* MIPS PIC level.  */
539
540enum mips_pic_level mips_pic;
541
542/* 1 if we should generate 32 bit offsets from the $gp register in
543   SVR4_PIC mode.  Currently has no meaning in other modes.  */
544static int mips_big_got = 0;
545
546/* 1 if trap instructions should used for overflow rather than break
547   instructions.  */
548static int mips_trap = 0;
549
550/* 1 if double width floating point constants should not be constructed
551   by assembling two single width halves into two single width floating
552   point registers which just happen to alias the double width destination
553   register.  On some architectures this aliasing can be disabled by a bit
554   in the status register, and the setting of this bit cannot be determined
555   automatically at assemble time.  */
556static int mips_disable_float_construction;
557
558/* Non-zero if any .set noreorder directives were used.  */
559
560static int mips_any_noreorder;
561
562/* Non-zero if nops should be inserted when the register referenced in
563   an mfhi/mflo instruction is read in the next two instructions.  */
564static int mips_7000_hilo_fix;
565
566/* The size of objects in the small data section.  */
567static unsigned int g_switch_value = 8;
568/* Whether the -G option was used.  */
569static int g_switch_seen = 0;
570
571#define N_RMASK 0xc4
572#define N_VFP   0xd4
573
574/* If we can determine in advance that GP optimization won't be
575   possible, we can skip the relaxation stuff that tries to produce
576   GP-relative references.  This makes delay slot optimization work
577   better.
578
579   This function can only provide a guess, but it seems to work for
580   gcc output.  It needs to guess right for gcc, otherwise gcc
581   will put what it thinks is a GP-relative instruction in a branch
582   delay slot.
583
584   I don't know if a fix is needed for the SVR4_PIC mode.  I've only
585   fixed it for the non-PIC mode.  KR 95/04/07  */
586static int nopic_need_relax (symbolS *, int);
587
588/* handle of the OPCODE hash table */
589static struct hash_control *op_hash = NULL;
590
591/* The opcode hash table we use for the mips16.  */
592static struct hash_control *mips16_op_hash = NULL;
593
594/* This array holds the chars that always start a comment.  If the
595    pre-processor is disabled, these aren't very useful */
596const char comment_chars[] = "#";
597
598/* This array holds the chars that only start a comment at the beginning of
599   a line.  If the line seems to have the form '# 123 filename'
600   .line and .file directives will appear in the pre-processed output */
601/* Note that input_file.c hand checks for '#' at the beginning of the
602   first line of the input file.  This is because the compiler outputs
603   #NO_APP at the beginning of its output.  */
604/* Also note that C style comments are always supported.  */
605const char line_comment_chars[] = "#";
606
607/* This array holds machine specific line separator characters.  */
608const char line_separator_chars[] = ";";
609
610/* Chars that can be used to separate mant from exp in floating point nums */
611const char EXP_CHARS[] = "eE";
612
613/* Chars that mean this number is a floating point constant */
614/* As in 0f12.456 */
615/* or    0d1.2345e12 */
616const char FLT_CHARS[] = "rRsSfFdDxXpP";
617
618/* Also be aware that MAXIMUM_NUMBER_OF_CHARS_FOR_FLOAT may have to be
619   changed in read.c .  Ideally it shouldn't have to know about it at all,
620   but nothing is ideal around here.
621 */
622
623static char *insn_error;
624
625static int auto_align = 1;
626
627/* When outputting SVR4 PIC code, the assembler needs to know the
628   offset in the stack frame from which to restore the $gp register.
629   This is set by the .cprestore pseudo-op, and saved in this
630   variable.  */
631static offsetT mips_cprestore_offset = -1;
632
633/* Similar for NewABI PIC code, where $gp is callee-saved.  NewABI has some
634   more optimizations, it can use a register value instead of a memory-saved
635   offset and even an other register than $gp as global pointer.  */
636static offsetT mips_cpreturn_offset = -1;
637static int mips_cpreturn_register = -1;
638static int mips_gp_register = GP;
639static int mips_gprel_offset = 0;
640
641/* Whether mips_cprestore_offset has been set in the current function
642   (or whether it has already been warned about, if not).  */
643static int mips_cprestore_valid = 0;
644
645/* This is the register which holds the stack frame, as set by the
646   .frame pseudo-op.  This is needed to implement .cprestore.  */
647static int mips_frame_reg = SP;
648
649/* Whether mips_frame_reg has been set in the current function
650   (or whether it has already been warned about, if not).  */
651static int mips_frame_reg_valid = 0;
652
653/* To output NOP instructions correctly, we need to keep information
654   about the previous two instructions.  */
655
656/* Whether we are optimizing.  The default value of 2 means to remove
657   unneeded NOPs and swap branch instructions when possible.  A value
658   of 1 means to not swap branches.  A value of 0 means to always
659   insert NOPs.  */
660static int mips_optimize = 2;
661
662/* Debugging level.  -g sets this to 2.  -gN sets this to N.  -g0 is
663   equivalent to seeing no -g option at all.  */
664static int mips_debug = 0;
665
666/* The maximum number of NOPs needed to avoid the VR4130 mflo/mfhi errata.  */
667#define MAX_VR4130_NOPS 4
668
669/* The maximum number of NOPs needed to fill delay slots.  */
670#define MAX_DELAY_NOPS 2
671
672/* The maximum number of NOPs needed for any purpose.  */
673#define MAX_NOPS 4
674
675/* A list of previous instructions, with index 0 being the most recent.
676   We need to look back MAX_NOPS instructions when filling delay slots
677   or working around processor errata.  We need to look back one
678   instruction further if we're thinking about using history[0] to
679   fill a branch delay slot.  */
680static struct mips_cl_insn history[1 + MAX_NOPS];
681
682/* Nop instructions used by emit_nop.  */
683static struct mips_cl_insn nop_insn, mips16_nop_insn;
684
685/* The appropriate nop for the current mode.  */
686#define NOP_INSN (mips_opts.mips16 ? &mips16_nop_insn : &nop_insn)
687
688/* If this is set, it points to a frag holding nop instructions which
689   were inserted before the start of a noreorder section.  If those
690   nops turn out to be unnecessary, the size of the frag can be
691   decreased.  */
692static fragS *prev_nop_frag;
693
694/* The number of nop instructions we created in prev_nop_frag.  */
695static int prev_nop_frag_holds;
696
697/* The number of nop instructions that we know we need in
698   prev_nop_frag.  */
699static int prev_nop_frag_required;
700
701/* The number of instructions we've seen since prev_nop_frag.  */
702static int prev_nop_frag_since;
703
704/* For ECOFF and ELF, relocations against symbols are done in two
705   parts, with a HI relocation and a LO relocation.  Each relocation
706   has only 16 bits of space to store an addend.  This means that in
707   order for the linker to handle carries correctly, it must be able
708   to locate both the HI and the LO relocation.  This means that the
709   relocations must appear in order in the relocation table.
710
711   In order to implement this, we keep track of each unmatched HI
712   relocation.  We then sort them so that they immediately precede the
713   corresponding LO relocation.  */
714
715struct mips_hi_fixup
716{
717  /* Next HI fixup.  */
718  struct mips_hi_fixup *next;
719  /* This fixup.  */
720  fixS *fixp;
721  /* The section this fixup is in.  */
722  segT seg;
723};
724
725/* The list of unmatched HI relocs.  */
726
727static struct mips_hi_fixup *mips_hi_fixup_list;
728
729/* The frag containing the last explicit relocation operator.
730   Null if explicit relocations have not been used.  */
731
732static fragS *prev_reloc_op_frag;
733
734/* Map normal MIPS register numbers to mips16 register numbers.  */
735
736#define X ILLEGAL_REG
737static const int mips32_to_16_reg_map[] =
738{
739  X, X, 2, 3, 4, 5, 6, 7,
740  X, X, X, X, X, X, X, X,
741  0, 1, X, X, X, X, X, X,
742  X, X, X, X, X, X, X, X
743};
744#undef X
745
746/* Map mips16 register numbers to normal MIPS register numbers.  */
747
748static const unsigned int mips16_to_32_reg_map[] =
749{
750  16, 17, 2, 3, 4, 5, 6, 7
751};
752
753/* Classifies the kind of instructions we're interested in when
754   implementing -mfix-vr4120.  */
755enum fix_vr4120_class
756{
757  FIX_VR4120_MACC,
758  FIX_VR4120_DMACC,
759  FIX_VR4120_MULT,
760  FIX_VR4120_DMULT,
761  FIX_VR4120_DIV,
762  FIX_VR4120_MTHILO,
763  NUM_FIX_VR4120_CLASSES
764};
765
766/* ...likewise -mtrap-zero-jump.  */
767static bfd_boolean mips_trap_zero_jump;
768
769/* ...likewise -mfix-loongson2f-jump.  */
770static bfd_boolean mips_fix_loongson2f_jump;
771
772/* ...likewise -mfix-loongson2f-nop.  */
773static bfd_boolean mips_fix_loongson2f_nop;
774
775/* True if -mfix-loongson2f-nop or -mfix-loongson2f-jump passed.  */
776static bfd_boolean mips_fix_loongson2f;
777
778/* Given two FIX_VR4120_* values X and Y, bit Y of element X is set if
779   there must be at least one other instruction between an instruction
780   of type X and an instruction of type Y.  */
781static unsigned int vr4120_conflicts[NUM_FIX_VR4120_CLASSES];
782
783/* True if -mfix-vr4120 is in force.  */
784static int mips_fix_vr4120;
785
786/* ...likewise -mfix-vr4130.  */
787static int mips_fix_vr4130;
788
789/* ...likewise -mfix-24k.  */
790static int mips_fix_24k;
791
792/* ...likewise -mfix-cn63xxp1 */
793static bfd_boolean mips_fix_cn63xxp1;
794
795/* We don't relax branches by default, since this causes us to expand
796   `la .l2 - .l1' if there's a branch between .l1 and .l2, because we
797   fail to compute the offset before expanding the macro to the most
798   efficient expansion.  */
799
800static int mips_relax_branch;
801
802static int mips_fix_loongson2f_btb;
803
804/* The expansion of many macros depends on the type of symbol that
805   they refer to.  For example, when generating position-dependent code,
806   a macro that refers to a symbol may have two different expansions,
807   one which uses GP-relative addresses and one which uses absolute
808   addresses.  When generating SVR4-style PIC, a macro may have
809   different expansions for local and global symbols.
810
811   We handle these situations by generating both sequences and putting
812   them in variant frags.  In position-dependent code, the first sequence
813   will be the GP-relative one and the second sequence will be the
814   absolute one.  In SVR4 PIC, the first sequence will be for global
815   symbols and the second will be for local symbols.
816
817   The frag's "subtype" is RELAX_ENCODE (FIRST, SECOND), where FIRST and
818   SECOND are the lengths of the two sequences in bytes.  These fields
819   can be extracted using RELAX_FIRST() and RELAX_SECOND().  In addition,
820   the subtype has the following flags:
821
822   RELAX_USE_SECOND
823	Set if it has been decided that we should use the second
824	sequence instead of the first.
825
826   RELAX_SECOND_LONGER
827	Set in the first variant frag if the macro's second implementation
828	is longer than its first.  This refers to the macro as a whole,
829	not an individual relaxation.
830
831   RELAX_NOMACRO
832	Set in the first variant frag if the macro appeared in a .set nomacro
833	block and if one alternative requires a warning but the other does not.
834
835   RELAX_DELAY_SLOT
836	Like RELAX_NOMACRO, but indicates that the macro appears in a branch
837	delay slot.
838
839   The frag's "opcode" points to the first fixup for relaxable code.
840
841   Relaxable macros are generated using a sequence such as:
842
843      relax_start (SYMBOL);
844      ... generate first expansion ...
845      relax_switch ();
846      ... generate second expansion ...
847      relax_end ();
848
849   The code and fixups for the unwanted alternative are discarded
850   by md_convert_frag.  */
851#define RELAX_ENCODE(FIRST, SECOND) (((FIRST) << 8) | (SECOND))
852
853#define RELAX_FIRST(X) (((X) >> 8) & 0xff)
854#define RELAX_SECOND(X) ((X) & 0xff)
855#define RELAX_USE_SECOND 0x10000
856#define RELAX_SECOND_LONGER 0x20000
857#define RELAX_NOMACRO 0x40000
858#define RELAX_DELAY_SLOT 0x80000
859
860/* Branch without likely bit.  If label is out of range, we turn:
861
862 	beq reg1, reg2, label
863	delay slot
864
865   into
866
867        bne reg1, reg2, 0f
868        nop
869        j label
870     0: delay slot
871
872   with the following opcode replacements:
873
874	beq <-> bne
875	blez <-> bgtz
876	bltz <-> bgez
877	bc1f <-> bc1t
878
879	bltzal <-> bgezal  (with jal label instead of j label)
880
881   Even though keeping the delay slot instruction in the delay slot of
882   the branch would be more efficient, it would be very tricky to do
883   correctly, because we'd have to introduce a variable frag *after*
884   the delay slot instruction, and expand that instead.  Let's do it
885   the easy way for now, even if the branch-not-taken case now costs
886   one additional instruction.  Out-of-range branches are not supposed
887   to be common, anyway.
888
889   Branch likely.  If label is out of range, we turn:
890
891	beql reg1, reg2, label
892	delay slot (annulled if branch not taken)
893
894   into
895
896        beql reg1, reg2, 1f
897        nop
898        beql $0, $0, 2f
899        nop
900     1: j[al] label
901        delay slot (executed only if branch taken)
902     2:
903
904   It would be possible to generate a shorter sequence by losing the
905   likely bit, generating something like:
906
907	bne reg1, reg2, 0f
908	nop
909	j[al] label
910	delay slot (executed only if branch taken)
911     0:
912
913	beql -> bne
914	bnel -> beq
915	blezl -> bgtz
916	bgtzl -> blez
917	bltzl -> bgez
918	bgezl -> bltz
919	bc1fl -> bc1t
920	bc1tl -> bc1f
921
922	bltzall -> bgezal  (with jal label instead of j label)
923	bgezall -> bltzal  (ditto)
924
925
926   but it's not clear that it would actually improve performance.  */
927#define RELAX_BRANCH_ENCODE(uncond, likely, link, toofar) \
928  ((relax_substateT) \
929   (0xc0000000 \
930    | ((toofar) ? 1 : 0) \
931    | ((link) ? 2 : 0) \
932    | ((likely) ? 4 : 0) \
933    | ((uncond) ? 8 : 0)))
934#define RELAX_BRANCH_P(i) (((i) & 0xf0000000) == 0xc0000000)
935#define RELAX_BRANCH_UNCOND(i) (((i) & 8) != 0)
936#define RELAX_BRANCH_LIKELY(i) (((i) & 4) != 0)
937#define RELAX_BRANCH_LINK(i) (((i) & 2) != 0)
938#define RELAX_BRANCH_TOOFAR(i) (((i) & 1) != 0)
939
940/* For mips16 code, we use an entirely different form of relaxation.
941   mips16 supports two versions of most instructions which take
942   immediate values: a small one which takes some small value, and a
943   larger one which takes a 16 bit value.  Since branches also follow
944   this pattern, relaxing these values is required.
945
946   We can assemble both mips16 and normal MIPS code in a single
947   object.  Therefore, we need to support this type of relaxation at
948   the same time that we support the relaxation described above.  We
949   use the high bit of the subtype field to distinguish these cases.
950
951   The information we store for this type of relaxation is the
952   argument code found in the opcode file for this relocation, whether
953   the user explicitly requested a small or extended form, and whether
954   the relocation is in a jump or jal delay slot.  That tells us the
955   size of the value, and how it should be stored.  We also store
956   whether the fragment is considered to be extended or not.  We also
957   store whether this is known to be a branch to a different section,
958   whether we have tried to relax this frag yet, and whether we have
959   ever extended a PC relative fragment because of a shift count.  */
960#define RELAX_MIPS16_ENCODE(type, small, ext, dslot, jal_dslot)	\
961  (0x80000000							\
962   | ((type) & 0xff)						\
963   | ((small) ? 0x100 : 0)					\
964   | ((ext) ? 0x200 : 0)					\
965   | ((dslot) ? 0x400 : 0)					\
966   | ((jal_dslot) ? 0x800 : 0))
967#define RELAX_MIPS16_P(i) (((i) & 0xc0000000) == 0x80000000)
968#define RELAX_MIPS16_TYPE(i) ((i) & 0xff)
969#define RELAX_MIPS16_USER_SMALL(i) (((i) & 0x100) != 0)
970#define RELAX_MIPS16_USER_EXT(i) (((i) & 0x200) != 0)
971#define RELAX_MIPS16_DSLOT(i) (((i) & 0x400) != 0)
972#define RELAX_MIPS16_JAL_DSLOT(i) (((i) & 0x800) != 0)
973#define RELAX_MIPS16_EXTENDED(i) (((i) & 0x1000) != 0)
974#define RELAX_MIPS16_MARK_EXTENDED(i) ((i) | 0x1000)
975#define RELAX_MIPS16_CLEAR_EXTENDED(i) ((i) &~ 0x1000)
976#define RELAX_MIPS16_LONG_BRANCH(i) (((i) & 0x2000) != 0)
977#define RELAX_MIPS16_MARK_LONG_BRANCH(i) ((i) | 0x2000)
978#define RELAX_MIPS16_CLEAR_LONG_BRANCH(i) ((i) &~ 0x2000)
979
980/* Is the given value a sign-extended 32-bit value?  */
981#define IS_SEXT_32BIT_NUM(x)						\
982  (((x) &~ (offsetT) 0x7fffffff) == 0					\
983   || (((x) &~ (offsetT) 0x7fffffff) == ~ (offsetT) 0x7fffffff))
984
985/* Is the given value a sign-extended 16-bit value?  */
986#define IS_SEXT_16BIT_NUM(x)						\
987  (((x) &~ (offsetT) 0x7fff) == 0					\
988   || (((x) &~ (offsetT) 0x7fff) == ~ (offsetT) 0x7fff))
989
990/* Is the given value a zero-extended 32-bit value?  Or a negated one?  */
991#define IS_ZEXT_32BIT_NUM(x)						\
992  (((x) &~ (offsetT) 0xffffffff) == 0					\
993   || (((x) &~ (offsetT) 0xffffffff) == ~ (offsetT) 0xffffffff))
994
995/* Replace bits MASK << SHIFT of STRUCT with the equivalent bits in
996   VALUE << SHIFT.  VALUE is evaluated exactly once.  */
997#define INSERT_BITS(STRUCT, VALUE, MASK, SHIFT) \
998  (STRUCT) = (((STRUCT) & ~((MASK) << (SHIFT))) \
999	      | (((VALUE) & (MASK)) << (SHIFT)))
1000
1001/* Extract bits MASK << SHIFT from STRUCT and shift them right
1002   SHIFT places.  */
1003#define EXTRACT_BITS(STRUCT, MASK, SHIFT) \
1004  (((STRUCT) >> (SHIFT)) & (MASK))
1005
1006/* Change INSN's opcode so that the operand given by FIELD has value VALUE.
1007   INSN is a mips_cl_insn structure and VALUE is evaluated exactly once.
1008
1009   include/opcode/mips.h specifies operand fields using the macros
1010   OP_MASK_<FIELD> and OP_SH_<FIELD>.  The MIPS16 equivalents start
1011   with "MIPS16OP" instead of "OP".  */
1012#define INSERT_OPERAND(FIELD, INSN, VALUE) \
1013  INSERT_BITS ((INSN).insn_opcode, VALUE, OP_MASK_##FIELD, OP_SH_##FIELD)
1014#define MIPS16_INSERT_OPERAND(FIELD, INSN, VALUE) \
1015  INSERT_BITS ((INSN).insn_opcode, VALUE, \
1016		MIPS16OP_MASK_##FIELD, MIPS16OP_SH_##FIELD)
1017
1018/* Extract the operand given by FIELD from mips_cl_insn INSN.  */
1019#define EXTRACT_OPERAND(FIELD, INSN) \
1020  EXTRACT_BITS ((INSN).insn_opcode, OP_MASK_##FIELD, OP_SH_##FIELD)
1021#define MIPS16_EXTRACT_OPERAND(FIELD, INSN) \
1022  EXTRACT_BITS ((INSN).insn_opcode, \
1023		MIPS16OP_MASK_##FIELD, \
1024		MIPS16OP_SH_##FIELD)
1025
1026/* Global variables used when generating relaxable macros.  See the
1027   comment above RELAX_ENCODE for more details about how relaxation
1028   is used.  */
1029static struct {
1030  /* 0 if we're not emitting a relaxable macro.
1031     1 if we're emitting the first of the two relaxation alternatives.
1032     2 if we're emitting the second alternative.  */
1033  int sequence;
1034
1035  /* The first relaxable fixup in the current frag.  (In other words,
1036     the first fixup that refers to relaxable code.)  */
1037  fixS *first_fixup;
1038
1039  /* sizes[0] says how many bytes of the first alternative are stored in
1040     the current frag.  Likewise sizes[1] for the second alternative.  */
1041  unsigned int sizes[2];
1042
1043  /* The symbol on which the choice of sequence depends.  */
1044  symbolS *symbol;
1045} mips_relax;
1046
1047/* Global variables used to decide whether a macro needs a warning.  */
1048static struct {
1049  /* True if the macro is in a branch delay slot.  */
1050  bfd_boolean delay_slot_p;
1051
1052  /* For relaxable macros, sizes[0] is the length of the first alternative
1053     in bytes and sizes[1] is the length of the second alternative.
1054     For non-relaxable macros, both elements give the length of the
1055     macro in bytes.  */
1056  unsigned int sizes[2];
1057
1058  /* The first variant frag for this macro.  */
1059  fragS *first_frag;
1060} mips_macro_warning;
1061
1062/* Prototypes for static functions.  */
1063
1064#define internalError()							\
1065    as_fatal (_("internal Error, line %d, %s"), __LINE__, __FILE__)
1066
1067enum mips_regclass { MIPS_GR_REG, MIPS_FP_REG, MIPS16_REG };
1068
1069static void append_insn
1070  (struct mips_cl_insn *, expressionS *, bfd_reloc_code_real_type *);
1071static void mips_no_prev_insn (void);
1072static void macro_build (expressionS *, const char *, const char *, ...);
1073static void mips16_macro_build
1074  (expressionS *, const char *, const char *, va_list *);
1075static void load_register (int, expressionS *, int);
1076static void macro_build (expressionS *, const char *, const char *, ...);
1077static void macro_start (void);
1078static void macro_end (void);
1079static void macro (struct mips_cl_insn * ip);
1080static void mips16_macro (struct mips_cl_insn * ip);
1081static void mips_ip (char *str, struct mips_cl_insn * ip);
1082static void mips16_ip (char *str, struct mips_cl_insn * ip);
1083static void mips16_immed
1084  (char *, unsigned int, int, offsetT, bfd_boolean, bfd_boolean, bfd_boolean,
1085   unsigned long *, bfd_boolean *, unsigned short *);
1086static size_t my_getSmallExpression
1087  (expressionS *, bfd_reloc_code_real_type *, char *);
1088static void my_getExpression (expressionS *, char *);
1089static void s_align (int);
1090static void s_change_sec (int);
1091static void s_change_section (int);
1092static void s_cons (int);
1093static void s_float_cons (int);
1094static void s_mips_globl (int);
1095static void s_option (int);
1096static void s_mipsset (int);
1097static void s_abicalls (int);
1098static void s_cpload (int);
1099static void s_cpsetup (int);
1100static void s_cplocal (int);
1101static void s_cprestore (int);
1102static void s_cpreturn (int);
1103static void s_dtprelword (int);
1104static void s_dtpreldword (int);
1105static void s_gpvalue (int);
1106static void s_gpword (int);
1107static void s_gpdword (int);
1108static void s_cpadd (int);
1109static void s_insn (int);
1110static void md_obj_begin (void);
1111static void md_obj_end (void);
1112static void s_mips_ent (int);
1113static void s_mips_end (int);
1114static void s_mips_frame (int);
1115static void s_mips_mask (int reg_type);
1116static void s_mips_stab (int);
1117static void s_mips_weakext (int);
1118static void s_mips_file (int);
1119static void s_mips_loc (int);
1120static bfd_boolean pic_need_relax (symbolS *, asection *);
1121static int relaxed_branch_length (fragS *, asection *, int);
1122static int validate_mips_insn (const struct mips_opcode *);
1123
1124/* Table and functions used to map between CPU/ISA names, and
1125   ISA levels, and CPU numbers.  */
1126
1127struct mips_cpu_info
1128{
1129  const char *name;           /* CPU or ISA name.  */
1130  int flags;                  /* ASEs available, or ISA flag.  */
1131  int isa;                    /* ISA level.  */
1132  int cpu;                    /* CPU number (default CPU if ISA).  */
1133};
1134
1135#define MIPS_CPU_IS_ISA		0x0001	/* Is this an ISA?  (If 0, a CPU.) */
1136#define MIPS_CPU_ASE_SMARTMIPS	0x0002	/* CPU implements SmartMIPS ASE */
1137#define MIPS_CPU_ASE_DSP	0x0004	/* CPU implements DSP ASE */
1138#define MIPS_CPU_ASE_MT		0x0008	/* CPU implements MT ASE */
1139#define MIPS_CPU_ASE_MIPS3D	0x0010	/* CPU implements MIPS-3D ASE */
1140#define MIPS_CPU_ASE_MDMX	0x0020	/* CPU implements MDMX ASE */
1141#define MIPS_CPU_ASE_DSPR2	0x0040	/* CPU implements DSP R2 ASE */
1142
1143static const struct mips_cpu_info *mips_parse_cpu (const char *, const char *);
1144static const struct mips_cpu_info *mips_cpu_info_from_isa (int);
1145static const struct mips_cpu_info *mips_cpu_info_from_arch (int);
1146
1147/* Pseudo-op table.
1148
1149   The following pseudo-ops from the Kane and Heinrich MIPS book
1150   should be defined here, but are currently unsupported: .alias,
1151   .galive, .gjaldef, .gjrlive, .livereg, .noalias.
1152
1153   The following pseudo-ops from the Kane and Heinrich MIPS book are
1154   specific to the type of debugging information being generated, and
1155   should be defined by the object format: .aent, .begin, .bend,
1156   .bgnb, .end, .endb, .ent, .fmask, .frame, .loc, .mask, .verstamp,
1157   .vreg.
1158
1159   The following pseudo-ops from the Kane and Heinrich MIPS book are
1160   not MIPS CPU specific, but are also not specific to the object file
1161   format.  This file is probably the best place to define them, but
1162   they are not currently supported: .asm0, .endr, .lab, .struct.  */
1163
1164static const pseudo_typeS mips_pseudo_table[] =
1165{
1166  /* MIPS specific pseudo-ops.  */
1167  {"option", s_option, 0},
1168  {"set", s_mipsset, 0},
1169  {"rdata", s_change_sec, 'r'},
1170  {"sdata", s_change_sec, 's'},
1171  {"livereg", s_ignore, 0},
1172  {"abicalls", s_abicalls, 0},
1173  {"cpload", s_cpload, 0},
1174  {"cpsetup", s_cpsetup, 0},
1175  {"cplocal", s_cplocal, 0},
1176  {"cprestore", s_cprestore, 0},
1177  {"cpreturn", s_cpreturn, 0},
1178  {"dtprelword", s_dtprelword, 0},
1179  {"dtpreldword", s_dtpreldword, 0},
1180  {"gpvalue", s_gpvalue, 0},
1181  {"gpword", s_gpword, 0},
1182  {"gpdword", s_gpdword, 0},
1183  {"cpadd", s_cpadd, 0},
1184  {"insn", s_insn, 0},
1185
1186  /* Relatively generic pseudo-ops that happen to be used on MIPS
1187     chips.  */
1188  {"asciiz", stringer, 8 + 1},
1189  {"bss", s_change_sec, 'b'},
1190  {"err", s_err, 0},
1191  {"half", s_cons, 1},
1192  {"dword", s_cons, 3},
1193  {"weakext", s_mips_weakext, 0},
1194  {"origin", s_org, 0},
1195  {"repeat", s_rept, 0},
1196
1197  /* For MIPS this is non-standard, but we define it for consistency.  */
1198  {"sbss", s_change_sec, 'B'},
1199
1200  /* These pseudo-ops are defined in read.c, but must be overridden
1201     here for one reason or another.  */
1202  {"align", s_align, 0},
1203  {"byte", s_cons, 0},
1204  {"data", s_change_sec, 'd'},
1205  {"double", s_float_cons, 'd'},
1206  {"float", s_float_cons, 'f'},
1207  {"globl", s_mips_globl, 0},
1208  {"global", s_mips_globl, 0},
1209  {"hword", s_cons, 1},
1210  {"int", s_cons, 2},
1211  {"long", s_cons, 2},
1212  {"octa", s_cons, 4},
1213  {"quad", s_cons, 3},
1214  {"section", s_change_section, 0},
1215  {"short", s_cons, 1},
1216  {"single", s_float_cons, 'f'},
1217  {"stabn", s_mips_stab, 'n'},
1218  {"text", s_change_sec, 't'},
1219  {"word", s_cons, 2},
1220
1221  { "extern", ecoff_directive_extern, 0},
1222
1223  { NULL, NULL, 0 },
1224};
1225
1226static const pseudo_typeS mips_nonecoff_pseudo_table[] =
1227{
1228  /* These pseudo-ops should be defined by the object file format.
1229     However, a.out doesn't support them, so we have versions here.  */
1230  {"aent", s_mips_ent, 1},
1231  {"bgnb", s_ignore, 0},
1232  {"end", s_mips_end, 0},
1233  {"endb", s_ignore, 0},
1234  {"ent", s_mips_ent, 0},
1235  {"file", s_mips_file, 0},
1236  {"fmask", s_mips_mask, 'F'},
1237  {"frame", s_mips_frame, 0},
1238  {"loc", s_mips_loc, 0},
1239  {"mask", s_mips_mask, 'R'},
1240  {"verstamp", s_ignore, 0},
1241  { NULL, NULL, 0 },
1242};
1243
1244extern void pop_insert (const pseudo_typeS *);
1245
1246void
1247mips_pop_insert (void)
1248{
1249  pop_insert (mips_pseudo_table);
1250  if (! ECOFF_DEBUGGING)
1251    pop_insert (mips_nonecoff_pseudo_table);
1252}
1253
1254/* Symbols labelling the current insn.  */
1255
1256struct insn_label_list
1257{
1258  struct insn_label_list *next;
1259  symbolS *label;
1260};
1261
1262static struct insn_label_list *free_insn_labels;
1263#define label_list tc_segment_info_data.labels
1264
1265static void mips_clear_insn_labels (void);
1266
1267static inline void
1268mips_clear_insn_labels (void)
1269{
1270  register struct insn_label_list **pl;
1271  segment_info_type *si;
1272
1273  if (now_seg)
1274    {
1275      for (pl = &free_insn_labels; *pl != NULL; pl = &(*pl)->next)
1276	;
1277
1278      si = seg_info (now_seg);
1279      *pl = si->label_list;
1280      si->label_list = NULL;
1281    }
1282}
1283
1284
1285static char *expr_end;
1286
1287/* Expressions which appear in instructions.  These are set by
1288   mips_ip.  */
1289
1290static expressionS imm_expr;
1291static expressionS imm2_expr;
1292static expressionS offset_expr;
1293
1294/* Relocs associated with imm_expr and offset_expr.  */
1295
1296static bfd_reloc_code_real_type imm_reloc[3]
1297  = {BFD_RELOC_UNUSED, BFD_RELOC_UNUSED, BFD_RELOC_UNUSED};
1298static bfd_reloc_code_real_type offset_reloc[3]
1299  = {BFD_RELOC_UNUSED, BFD_RELOC_UNUSED, BFD_RELOC_UNUSED};
1300
1301/* These are set by mips16_ip if an explicit extension is used.  */
1302
1303static bfd_boolean mips16_small, mips16_ext;
1304
1305#ifdef OBJ_ELF
1306/* The pdr segment for per procedure frame/regmask info.  Not used for
1307   ECOFF debugging.  */
1308
1309static segT pdr_seg;
1310#endif
1311
1312/* The default target format to use.  */
1313
1314const char *
1315mips_target_format (void)
1316{
1317  switch (OUTPUT_FLAVOR)
1318    {
1319    case bfd_target_ecoff_flavour:
1320      return target_big_endian ? "ecoff-bigmips" : ECOFF_LITTLE_FORMAT;
1321    case bfd_target_coff_flavour:
1322      return "pe-mips";
1323    case bfd_target_elf_flavour:
1324#ifdef TE_VXWORKS
1325      if (!HAVE_64BIT_OBJECTS && !HAVE_NEWABI)
1326	return (target_big_endian
1327		? "elf32-bigmips-vxworks"
1328		: "elf32-littlemips-vxworks");
1329#endif
1330#ifdef TE_TMIPS
1331      /* This is traditional mips.  */
1332      return (target_big_endian
1333	      ? (HAVE_64BIT_OBJECTS
1334		 ? "elf64-tradbigmips"
1335		 : (HAVE_NEWABI
1336		    ? "elf32-ntradbigmips" : "elf32-tradbigmips"))
1337	      : (HAVE_64BIT_OBJECTS
1338		 ? "elf64-tradlittlemips"
1339		 : (HAVE_NEWABI
1340		    ? "elf32-ntradlittlemips" : "elf32-tradlittlemips")));
1341#else
1342      return (target_big_endian
1343	      ? (HAVE_64BIT_OBJECTS
1344		 ? "elf64-bigmips"
1345		 : (HAVE_NEWABI
1346		    ? "elf32-nbigmips" : "elf32-bigmips"))
1347	      : (HAVE_64BIT_OBJECTS
1348		 ? "elf64-littlemips"
1349		 : (HAVE_NEWABI
1350		    ? "elf32-nlittlemips" : "elf32-littlemips")));
1351#endif
1352    default:
1353      abort ();
1354      return NULL;
1355    }
1356}
1357
1358/* Return the length of instruction INSN.  */
1359
1360static inline unsigned int
1361insn_length (const struct mips_cl_insn *insn)
1362{
1363  if (!mips_opts.mips16)
1364    return 4;
1365  return insn->mips16_absolute_jump_p || insn->use_extend ? 4 : 2;
1366}
1367
1368/* Initialise INSN from opcode entry MO.  Leave its position unspecified.  */
1369
1370static void
1371create_insn (struct mips_cl_insn *insn, const struct mips_opcode *mo)
1372{
1373  size_t i;
1374
1375  insn->insn_mo = mo;
1376  insn->use_extend = FALSE;
1377  insn->extend = 0;
1378  insn->insn_opcode = mo->match;
1379  insn->frag = NULL;
1380  insn->where = 0;
1381  for (i = 0; i < ARRAY_SIZE (insn->fixp); i++)
1382    insn->fixp[i] = NULL;
1383  insn->fixed_p = (mips_opts.noreorder > 0);
1384  insn->noreorder_p = (mips_opts.noreorder > 0);
1385  insn->mips16_absolute_jump_p = 0;
1386}
1387
1388/* Record the current MIPS16 mode in now_seg.  */
1389
1390static void
1391mips_record_mips16_mode (void)
1392{
1393  segment_info_type *si;
1394
1395  si = seg_info (now_seg);
1396  if (si->tc_segment_info_data.mips16 != mips_opts.mips16)
1397    si->tc_segment_info_data.mips16 = mips_opts.mips16;
1398}
1399
1400/* Install INSN at the location specified by its "frag" and "where" fields.  */
1401
1402static void
1403install_insn (const struct mips_cl_insn *insn)
1404{
1405  char *f = insn->frag->fr_literal + insn->where;
1406  if (!mips_opts.mips16)
1407    md_number_to_chars (f, insn->insn_opcode, 4);
1408  else if (insn->mips16_absolute_jump_p)
1409    {
1410      md_number_to_chars (f, insn->insn_opcode >> 16, 2);
1411      md_number_to_chars (f + 2, insn->insn_opcode & 0xffff, 2);
1412    }
1413  else
1414    {
1415      if (insn->use_extend)
1416	{
1417	  md_number_to_chars (f, 0xf000 | insn->extend, 2);
1418	  f += 2;
1419	}
1420      md_number_to_chars (f, insn->insn_opcode, 2);
1421    }
1422  mips_record_mips16_mode ();
1423}
1424
1425/* Move INSN to offset WHERE in FRAG.  Adjust the fixups accordingly
1426   and install the opcode in the new location.  */
1427
1428static void
1429move_insn (struct mips_cl_insn *insn, fragS *frag, long where)
1430{
1431  size_t i;
1432
1433  insn->frag = frag;
1434  insn->where = where;
1435  for (i = 0; i < ARRAY_SIZE (insn->fixp); i++)
1436    if (insn->fixp[i] != NULL)
1437      {
1438	insn->fixp[i]->fx_frag = frag;
1439	insn->fixp[i]->fx_where = where;
1440      }
1441  install_insn (insn);
1442}
1443
1444/* Add INSN to the end of the output.  */
1445
1446static void
1447add_fixed_insn (struct mips_cl_insn *insn)
1448{
1449  char *f = frag_more (insn_length (insn));
1450  move_insn (insn, frag_now, f - frag_now->fr_literal);
1451}
1452
1453/* Start a variant frag and move INSN to the start of the variant part,
1454   marking it as fixed.  The other arguments are as for frag_var.  */
1455
1456static void
1457add_relaxed_insn (struct mips_cl_insn *insn, int max_chars, int var,
1458		  relax_substateT subtype, symbolS *symbol, offsetT offset)
1459{
1460  frag_grow (max_chars);
1461  move_insn (insn, frag_now, frag_more (0) - frag_now->fr_literal);
1462  insn->fixed_p = 1;
1463  frag_var (rs_machine_dependent, max_chars, var,
1464	    subtype, symbol, offset, NULL);
1465}
1466
1467/* Insert N copies of INSN into the history buffer, starting at
1468   position FIRST.  Neither FIRST nor N need to be clipped.  */
1469
1470static void
1471insert_into_history (unsigned int first, unsigned int n,
1472		     const struct mips_cl_insn *insn)
1473{
1474  if (mips_relax.sequence != 2)
1475    {
1476      unsigned int i;
1477
1478      for (i = ARRAY_SIZE (history); i-- > first;)
1479	if (i >= first + n)
1480	  history[i] = history[i - n];
1481	else
1482	  history[i] = *insn;
1483    }
1484}
1485
1486/* Emit a nop instruction, recording it in the history buffer.  */
1487
1488static void
1489emit_nop (void)
1490{
1491  add_fixed_insn (NOP_INSN);
1492  insert_into_history (0, 1, NOP_INSN);
1493}
1494
1495/* Initialize vr4120_conflicts.  There is a bit of duplication here:
1496   the idea is to make it obvious at a glance that each errata is
1497   included.  */
1498
1499static void
1500init_vr4120_conflicts (void)
1501{
1502#define CONFLICT(FIRST, SECOND) \
1503    vr4120_conflicts[FIX_VR4120_##FIRST] |= 1 << FIX_VR4120_##SECOND
1504
1505  /* Errata 21 - [D]DIV[U] after [D]MACC */
1506  CONFLICT (MACC, DIV);
1507  CONFLICT (DMACC, DIV);
1508
1509  /* Errata 23 - Continuous DMULT[U]/DMACC instructions.  */
1510  CONFLICT (DMULT, DMULT);
1511  CONFLICT (DMULT, DMACC);
1512  CONFLICT (DMACC, DMULT);
1513  CONFLICT (DMACC, DMACC);
1514
1515  /* Errata 24 - MT{LO,HI} after [D]MACC */
1516  CONFLICT (MACC, MTHILO);
1517  CONFLICT (DMACC, MTHILO);
1518
1519  /* VR4181A errata MD(1): "If a MULT, MULTU, DMULT or DMULTU
1520     instruction is executed immediately after a MACC or DMACC
1521     instruction, the result of [either instruction] is incorrect."  */
1522  CONFLICT (MACC, MULT);
1523  CONFLICT (MACC, DMULT);
1524  CONFLICT (DMACC, MULT);
1525  CONFLICT (DMACC, DMULT);
1526
1527  /* VR4181A errata MD(4): "If a MACC or DMACC instruction is
1528     executed immediately after a DMULT, DMULTU, DIV, DIVU,
1529     DDIV or DDIVU instruction, the result of the MACC or
1530     DMACC instruction is incorrect.".  */
1531  CONFLICT (DMULT, MACC);
1532  CONFLICT (DMULT, DMACC);
1533  CONFLICT (DIV, MACC);
1534  CONFLICT (DIV, DMACC);
1535
1536#undef CONFLICT
1537}
1538
1539struct regname {
1540  const char *name;
1541  unsigned int num;
1542};
1543
1544#define RTYPE_MASK	0x1ff00
1545#define RTYPE_NUM	0x00100
1546#define RTYPE_FPU	0x00200
1547#define RTYPE_FCC	0x00400
1548#define RTYPE_VEC	0x00800
1549#define RTYPE_GP	0x01000
1550#define RTYPE_CP0	0x02000
1551#define RTYPE_PC	0x04000
1552#define RTYPE_ACC	0x08000
1553#define RTYPE_CCC	0x10000
1554#define RNUM_MASK	0x000ff
1555#define RWARN		0x80000
1556
1557#define GENERIC_REGISTER_NUMBERS \
1558    {"$0",	RTYPE_NUM | 0},  \
1559    {"$1",	RTYPE_NUM | 1},  \
1560    {"$2",	RTYPE_NUM | 2},  \
1561    {"$3",	RTYPE_NUM | 3},  \
1562    {"$4",	RTYPE_NUM | 4},  \
1563    {"$5",	RTYPE_NUM | 5},  \
1564    {"$6",	RTYPE_NUM | 6},  \
1565    {"$7",	RTYPE_NUM | 7},  \
1566    {"$8",	RTYPE_NUM | 8},  \
1567    {"$9",	RTYPE_NUM | 9},  \
1568    {"$10",	RTYPE_NUM | 10}, \
1569    {"$11",	RTYPE_NUM | 11}, \
1570    {"$12",	RTYPE_NUM | 12}, \
1571    {"$13",	RTYPE_NUM | 13}, \
1572    {"$14",	RTYPE_NUM | 14}, \
1573    {"$15",	RTYPE_NUM | 15}, \
1574    {"$16",	RTYPE_NUM | 16}, \
1575    {"$17",	RTYPE_NUM | 17}, \
1576    {"$18",	RTYPE_NUM | 18}, \
1577    {"$19",	RTYPE_NUM | 19}, \
1578    {"$20",	RTYPE_NUM | 20}, \
1579    {"$21",	RTYPE_NUM | 21}, \
1580    {"$22",	RTYPE_NUM | 22}, \
1581    {"$23",	RTYPE_NUM | 23}, \
1582    {"$24",	RTYPE_NUM | 24}, \
1583    {"$25",	RTYPE_NUM | 25}, \
1584    {"$26",	RTYPE_NUM | 26}, \
1585    {"$27",	RTYPE_NUM | 27}, \
1586    {"$28",	RTYPE_NUM | 28}, \
1587    {"$29",	RTYPE_NUM | 29}, \
1588    {"$30",	RTYPE_NUM | 30}, \
1589    {"$31",	RTYPE_NUM | 31}
1590
1591#define FPU_REGISTER_NAMES       \
1592    {"$f0",	RTYPE_FPU | 0},  \
1593    {"$f1",	RTYPE_FPU | 1},  \
1594    {"$f2",	RTYPE_FPU | 2},  \
1595    {"$f3",	RTYPE_FPU | 3},  \
1596    {"$f4",	RTYPE_FPU | 4},  \
1597    {"$f5",	RTYPE_FPU | 5},  \
1598    {"$f6",	RTYPE_FPU | 6},  \
1599    {"$f7",	RTYPE_FPU | 7},  \
1600    {"$f8",	RTYPE_FPU | 8},  \
1601    {"$f9",	RTYPE_FPU | 9},  \
1602    {"$f10",	RTYPE_FPU | 10}, \
1603    {"$f11",	RTYPE_FPU | 11}, \
1604    {"$f12",	RTYPE_FPU | 12}, \
1605    {"$f13",	RTYPE_FPU | 13}, \
1606    {"$f14",	RTYPE_FPU | 14}, \
1607    {"$f15",	RTYPE_FPU | 15}, \
1608    {"$f16",	RTYPE_FPU | 16}, \
1609    {"$f17",	RTYPE_FPU | 17}, \
1610    {"$f18",	RTYPE_FPU | 18}, \
1611    {"$f19",	RTYPE_FPU | 19}, \
1612    {"$f20",	RTYPE_FPU | 20}, \
1613    {"$f21",	RTYPE_FPU | 21}, \
1614    {"$f22",	RTYPE_FPU | 22}, \
1615    {"$f23",	RTYPE_FPU | 23}, \
1616    {"$f24",	RTYPE_FPU | 24}, \
1617    {"$f25",	RTYPE_FPU | 25}, \
1618    {"$f26",	RTYPE_FPU | 26}, \
1619    {"$f27",	RTYPE_FPU | 27}, \
1620    {"$f28",	RTYPE_FPU | 28}, \
1621    {"$f29",	RTYPE_FPU | 29}, \
1622    {"$f30",	RTYPE_FPU | 30}, \
1623    {"$f31",	RTYPE_FPU | 31}
1624
1625#define FPU_CONDITION_CODE_NAMES \
1626    {"$fcc0",	RTYPE_FCC | 0},  \
1627    {"$fcc1",	RTYPE_FCC | 1},  \
1628    {"$fcc2",	RTYPE_FCC | 2},  \
1629    {"$fcc3",	RTYPE_FCC | 3},  \
1630    {"$fcc4",	RTYPE_FCC | 4},  \
1631    {"$fcc5",	RTYPE_FCC | 5},  \
1632    {"$fcc6",	RTYPE_FCC | 6},  \
1633    {"$fcc7",	RTYPE_FCC | 7}
1634
1635#define COPROC_CONDITION_CODE_NAMES         \
1636    {"$cc0",	RTYPE_FCC | RTYPE_CCC | 0}, \
1637    {"$cc1",	RTYPE_FCC | RTYPE_CCC | 1}, \
1638    {"$cc2",	RTYPE_FCC | RTYPE_CCC | 2}, \
1639    {"$cc3",	RTYPE_FCC | RTYPE_CCC | 3}, \
1640    {"$cc4",	RTYPE_FCC | RTYPE_CCC | 4}, \
1641    {"$cc5",	RTYPE_FCC | RTYPE_CCC | 5}, \
1642    {"$cc6",	RTYPE_FCC | RTYPE_CCC | 6}, \
1643    {"$cc7",	RTYPE_FCC | RTYPE_CCC | 7}
1644
1645#define N32N64_SYMBOLIC_REGISTER_NAMES \
1646    {"$a4",	RTYPE_GP | 8},  \
1647    {"$a5",	RTYPE_GP | 9},  \
1648    {"$a6",	RTYPE_GP | 10}, \
1649    {"$a7",	RTYPE_GP | 11}, \
1650    {"$ta0",	RTYPE_GP | 8},  /* alias for $a4 */ \
1651    {"$ta1",	RTYPE_GP | 9},  /* alias for $a5 */ \
1652    {"$ta2",	RTYPE_GP | 10}, /* alias for $a6 */ \
1653    {"$ta3",	RTYPE_GP | 11}, /* alias for $a7 */ \
1654    {"$t0",	RTYPE_GP | 12}, \
1655    {"$t1",	RTYPE_GP | 13}, \
1656    {"$t2",	RTYPE_GP | 14}, \
1657    {"$t3",	RTYPE_GP | 15}
1658
1659#define O32_SYMBOLIC_REGISTER_NAMES \
1660    {"$t0",	RTYPE_GP | 8},  \
1661    {"$t1",	RTYPE_GP | 9},  \
1662    {"$t2",	RTYPE_GP | 10}, \
1663    {"$t3",	RTYPE_GP | 11}, \
1664    {"$t4",	RTYPE_GP | 12}, \
1665    {"$t5",	RTYPE_GP | 13}, \
1666    {"$t6",	RTYPE_GP | 14}, \
1667    {"$t7",	RTYPE_GP | 15}, \
1668    {"$ta0",	RTYPE_GP | 12}, /* alias for $t4 */ \
1669    {"$ta1",	RTYPE_GP | 13}, /* alias for $t5 */ \
1670    {"$ta2",	RTYPE_GP | 14}, /* alias for $t6 */ \
1671    {"$ta3",	RTYPE_GP | 15}  /* alias for $t7 */
1672
1673/* Remaining symbolic register names */
1674#define SYMBOLIC_REGISTER_NAMES \
1675    {"$zero",	RTYPE_GP | 0},  \
1676    {"$at",	RTYPE_GP | 1},  \
1677    {"$AT",	RTYPE_GP | 1},  \
1678    {"$v0",	RTYPE_GP | 2},  \
1679    {"$v1",	RTYPE_GP | 3},  \
1680    {"$a0",	RTYPE_GP | 4},  \
1681    {"$a1",	RTYPE_GP | 5},  \
1682    {"$a2",	RTYPE_GP | 6},  \
1683    {"$a3",	RTYPE_GP | 7},  \
1684    {"$s0",	RTYPE_GP | 16}, \
1685    {"$s1",	RTYPE_GP | 17}, \
1686    {"$s2",	RTYPE_GP | 18}, \
1687    {"$s3",	RTYPE_GP | 19}, \
1688    {"$s4",	RTYPE_GP | 20}, \
1689    {"$s5",	RTYPE_GP | 21}, \
1690    {"$s6",	RTYPE_GP | 22}, \
1691    {"$s7",	RTYPE_GP | 23}, \
1692    {"$t8",	RTYPE_GP | 24}, \
1693    {"$t9",	RTYPE_GP | 25}, \
1694    {"$k0",	RTYPE_GP | 26}, \
1695    {"$kt0",	RTYPE_GP | 26}, \
1696    {"$k1",	RTYPE_GP | 27}, \
1697    {"$kt1",	RTYPE_GP | 27}, \
1698    {"$gp",	RTYPE_GP | 28}, \
1699    {"$sp",	RTYPE_GP | 29}, \
1700    {"$s8",	RTYPE_GP | 30}, \
1701    {"$fp",	RTYPE_GP | 30}, \
1702    {"$ra",	RTYPE_GP | 31}
1703
1704#define MIPS16_SPECIAL_REGISTER_NAMES \
1705    {"$pc",	RTYPE_PC | 0}
1706
1707#define MDMX_VECTOR_REGISTER_NAMES \
1708    /* {"$v0",	RTYPE_VEC | 0},  clash with REG 2 above */ \
1709    /* {"$v1",	RTYPE_VEC | 1},  clash with REG 3 above */ \
1710    {"$v2",	RTYPE_VEC | 2},  \
1711    {"$v3",	RTYPE_VEC | 3},  \
1712    {"$v4",	RTYPE_VEC | 4},  \
1713    {"$v5",	RTYPE_VEC | 5},  \
1714    {"$v6",	RTYPE_VEC | 6},  \
1715    {"$v7",	RTYPE_VEC | 7},  \
1716    {"$v8",	RTYPE_VEC | 8},  \
1717    {"$v9",	RTYPE_VEC | 9},  \
1718    {"$v10",	RTYPE_VEC | 10}, \
1719    {"$v11",	RTYPE_VEC | 11}, \
1720    {"$v12",	RTYPE_VEC | 12}, \
1721    {"$v13",	RTYPE_VEC | 13}, \
1722    {"$v14",	RTYPE_VEC | 14}, \
1723    {"$v15",	RTYPE_VEC | 15}, \
1724    {"$v16",	RTYPE_VEC | 16}, \
1725    {"$v17",	RTYPE_VEC | 17}, \
1726    {"$v18",	RTYPE_VEC | 18}, \
1727    {"$v19",	RTYPE_VEC | 19}, \
1728    {"$v20",	RTYPE_VEC | 20}, \
1729    {"$v21",	RTYPE_VEC | 21}, \
1730    {"$v22",	RTYPE_VEC | 22}, \
1731    {"$v23",	RTYPE_VEC | 23}, \
1732    {"$v24",	RTYPE_VEC | 24}, \
1733    {"$v25",	RTYPE_VEC | 25}, \
1734    {"$v26",	RTYPE_VEC | 26}, \
1735    {"$v27",	RTYPE_VEC | 27}, \
1736    {"$v28",	RTYPE_VEC | 28}, \
1737    {"$v29",	RTYPE_VEC | 29}, \
1738    {"$v30",	RTYPE_VEC | 30}, \
1739    {"$v31",	RTYPE_VEC | 31}
1740
1741#define MIPS_DSP_ACCUMULATOR_NAMES \
1742    {"$ac0",	RTYPE_ACC | 0}, \
1743    {"$ac1",	RTYPE_ACC | 1}, \
1744    {"$ac2",	RTYPE_ACC | 2}, \
1745    {"$ac3",	RTYPE_ACC | 3}
1746
1747static const struct regname reg_names[] = {
1748  GENERIC_REGISTER_NUMBERS,
1749  FPU_REGISTER_NAMES,
1750  FPU_CONDITION_CODE_NAMES,
1751  COPROC_CONDITION_CODE_NAMES,
1752
1753  /* The $txx registers depends on the abi,
1754     these will be added later into the symbol table from
1755     one of the tables below once mips_abi is set after
1756     parsing of arguments from the command line. */
1757  SYMBOLIC_REGISTER_NAMES,
1758
1759  MIPS16_SPECIAL_REGISTER_NAMES,
1760  MDMX_VECTOR_REGISTER_NAMES,
1761  MIPS_DSP_ACCUMULATOR_NAMES,
1762  {0, 0}
1763};
1764
1765static const struct regname reg_names_o32[] = {
1766  O32_SYMBOLIC_REGISTER_NAMES,
1767  {0, 0}
1768};
1769
1770static const struct regname reg_names_n32n64[] = {
1771  N32N64_SYMBOLIC_REGISTER_NAMES,
1772  {0, 0}
1773};
1774
1775static int
1776reg_lookup (char **s, unsigned int types, unsigned int *regnop)
1777{
1778  symbolS *symbolP;
1779  char *e;
1780  char save_c;
1781  int reg = -1;
1782
1783  /* Find end of name.  */
1784  e = *s;
1785  if (is_name_beginner (*e))
1786    ++e;
1787  while (is_part_of_name (*e))
1788    ++e;
1789
1790  /* Terminate name.  */
1791  save_c = *e;
1792  *e = '\0';
1793
1794  /* Look for a register symbol.  */
1795  if ((symbolP = symbol_find (*s)) && S_GET_SEGMENT (symbolP) == reg_section)
1796    {
1797      int r = S_GET_VALUE (symbolP);
1798      if (r & types)
1799	reg = r & RNUM_MASK;
1800      else if ((types & RTYPE_VEC) && (r & ~1) == (RTYPE_GP | 2))
1801	/* Convert GP reg $v0/1 to MDMX reg $v0/1!  */
1802	reg = (r & RNUM_MASK) - 2;
1803    }
1804  /* Else see if this is a register defined in an itbl entry.  */
1805  else if ((types & RTYPE_GP) && itbl_have_entries)
1806    {
1807      char *n = *s;
1808      unsigned long r;
1809
1810      if (*n == '$')
1811	++n;
1812      if (itbl_get_reg_val (n, &r))
1813	reg = r & RNUM_MASK;
1814    }
1815
1816  /* Advance to next token if a register was recognised.  */
1817  if (reg >= 0)
1818    *s = e;
1819  else if (types & RWARN)
1820    as_warn (_("Unrecognized register name `%s'"), *s);
1821
1822  *e = save_c;
1823  if (regnop)
1824    *regnop = reg;
1825  return reg >= 0;
1826}
1827
1828/* Return TRUE if opcode MO is valid on the currently selected ISA and
1829   architecture.  Use is_opcode_valid_16 for MIPS16 opcodes.  */
1830
1831static bfd_boolean
1832is_opcode_valid (const struct mips_opcode *mo)
1833{
1834  int isa = mips_opts.isa;
1835  int fp_s, fp_d;
1836
1837  if (mips_opts.ase_mdmx)
1838    isa |= INSN_MDMX;
1839  if (mips_opts.ase_dsp)
1840    isa |= INSN_DSP;
1841  if (mips_opts.ase_dsp && ISA_SUPPORTS_DSP64_ASE)
1842    isa |= INSN_DSP64;
1843  if (mips_opts.ase_dspr2)
1844    isa |= INSN_DSPR2;
1845  if (mips_opts.ase_mt)
1846    isa |= INSN_MT;
1847  if (mips_opts.ase_mips3d)
1848    isa |= INSN_MIPS3D;
1849  if (mips_opts.ase_smartmips)
1850    isa |= INSN_SMARTMIPS;
1851
1852  /* Don't accept instructions based on the ISA if the CPU does not implement
1853     all the coprocessor insns. */
1854  if (NO_ISA_COP (mips_opts.arch)
1855      && COP_INSN (mo->pinfo))
1856    isa = 0;
1857
1858  if (!OPCODE_IS_MEMBER (mo, isa, mips_opts.arch))
1859    return FALSE;
1860
1861  /* Check whether the instruction or macro requires single-precision or
1862     double-precision floating-point support.  Note that this information is
1863     stored differently in the opcode table for insns and macros.  */
1864  if (mo->pinfo == INSN_MACRO)
1865    {
1866      fp_s = mo->pinfo2 & INSN2_M_FP_S;
1867      fp_d = mo->pinfo2 & INSN2_M_FP_D;
1868    }
1869  else
1870    {
1871      fp_s = mo->pinfo & FP_S;
1872      fp_d = mo->pinfo & FP_D;
1873    }
1874
1875  if (fp_d && (mips_opts.soft_float || mips_opts.single_float))
1876    return FALSE;
1877
1878  if (fp_s && mips_opts.soft_float)
1879    return FALSE;
1880
1881  return TRUE;
1882}
1883
1884/* Return TRUE if the MIPS16 opcode MO is valid on the currently
1885   selected ISA and architecture.  */
1886
1887static bfd_boolean
1888is_opcode_valid_16 (const struct mips_opcode *mo)
1889{
1890  return OPCODE_IS_MEMBER (mo, mips_opts.isa, mips_opts.arch) ? TRUE : FALSE;
1891}
1892
1893/* This function is called once, at assembler startup time.  It should set up
1894   all the tables, etc. that the MD part of the assembler will need.  */
1895
1896void
1897md_begin (void)
1898{
1899  const char *retval = NULL;
1900  int i = 0;
1901  int broken = 0;
1902
1903  if (mips_pic != NO_PIC)
1904    {
1905      if (g_switch_seen && g_switch_value != 0)
1906	as_bad (_("-G may not be used in position-independent code"));
1907      g_switch_value = 0;
1908    }
1909
1910  if (! bfd_set_arch_mach (stdoutput, bfd_arch_mips, file_mips_arch))
1911    as_warn (_("Could not set architecture and machine"));
1912
1913  op_hash = hash_new ();
1914
1915  for (i = 0; i < NUMOPCODES;)
1916    {
1917      const char *name = mips_opcodes[i].name;
1918
1919      retval = hash_insert (op_hash, name, (void *) &mips_opcodes[i]);
1920      if (retval != NULL)
1921	{
1922	  fprintf (stderr, _("internal error: can't hash `%s': %s\n"),
1923		   mips_opcodes[i].name, retval);
1924	  /* Probably a memory allocation problem?  Give up now.  */
1925	  as_fatal (_("Broken assembler.  No assembly attempted."));
1926	}
1927      do
1928	{
1929	  if (mips_opcodes[i].pinfo != INSN_MACRO)
1930	    {
1931	      if (!validate_mips_insn (&mips_opcodes[i]))
1932		broken = 1;
1933	      if (nop_insn.insn_mo == NULL && strcmp (name, "nop") == 0)
1934		{
1935		  create_insn (&nop_insn, mips_opcodes + i);
1936		  if (mips_fix_loongson2f_nop)
1937		    nop_insn.insn_opcode = LOONGSON2F_NOP_INSN;
1938		  nop_insn.fixed_p = 1;
1939		}
1940	    }
1941	  ++i;
1942	}
1943      while ((i < NUMOPCODES) && !strcmp (mips_opcodes[i].name, name));
1944    }
1945
1946  mips16_op_hash = hash_new ();
1947
1948  i = 0;
1949  while (i < bfd_mips16_num_opcodes)
1950    {
1951      const char *name = mips16_opcodes[i].name;
1952
1953      retval = hash_insert (mips16_op_hash, name, (void *) &mips16_opcodes[i]);
1954      if (retval != NULL)
1955	as_fatal (_("internal: can't hash `%s': %s"),
1956		  mips16_opcodes[i].name, retval);
1957      do
1958	{
1959	  if (mips16_opcodes[i].pinfo != INSN_MACRO
1960	      && ((mips16_opcodes[i].match & mips16_opcodes[i].mask)
1961		  != mips16_opcodes[i].match))
1962	    {
1963	      fprintf (stderr, _("internal error: bad mips16 opcode: %s %s\n"),
1964		       mips16_opcodes[i].name, mips16_opcodes[i].args);
1965	      broken = 1;
1966	    }
1967	  if (mips16_nop_insn.insn_mo == NULL && strcmp (name, "nop") == 0)
1968	    {
1969	      create_insn (&mips16_nop_insn, mips16_opcodes + i);
1970	      mips16_nop_insn.fixed_p = 1;
1971	    }
1972	  ++i;
1973	}
1974      while (i < bfd_mips16_num_opcodes
1975	     && strcmp (mips16_opcodes[i].name, name) == 0);
1976    }
1977
1978  if (broken)
1979    as_fatal (_("Broken assembler.  No assembly attempted."));
1980
1981  /* We add all the general register names to the symbol table.  This
1982     helps us detect invalid uses of them.  */
1983  for (i = 0; reg_names[i].name; i++)
1984    symbol_table_insert (symbol_new (reg_names[i].name, reg_section,
1985				     reg_names[i].num, /* & RNUM_MASK, */
1986				     &zero_address_frag));
1987  if (HAVE_NEWABI)
1988    for (i = 0; reg_names_n32n64[i].name; i++)
1989      symbol_table_insert (symbol_new (reg_names_n32n64[i].name, reg_section,
1990				       reg_names_n32n64[i].num, /* & RNUM_MASK, */
1991				       &zero_address_frag));
1992  else
1993    for (i = 0; reg_names_o32[i].name; i++)
1994      symbol_table_insert (symbol_new (reg_names_o32[i].name, reg_section,
1995				       reg_names_o32[i].num, /* & RNUM_MASK, */
1996				       &zero_address_frag));
1997
1998  mips_no_prev_insn ();
1999
2000  mips_gprmask = 0;
2001  mips_cprmask[0] = 0;
2002  mips_cprmask[1] = 0;
2003  mips_cprmask[2] = 0;
2004  mips_cprmask[3] = 0;
2005
2006  /* set the default alignment for the text section (2**2) */
2007  record_alignment (text_section, 2);
2008
2009  bfd_set_gp_size (stdoutput, g_switch_value);
2010
2011#ifdef OBJ_ELF
2012  if (IS_ELF)
2013    {
2014      /* On a native system other than VxWorks, sections must be aligned
2015	 to 16 byte boundaries.  When configured for an embedded ELF
2016	 target, we don't bother.  */
2017      if (strncmp (TARGET_OS, "elf", 3) != 0
2018	  && strncmp (TARGET_OS, "vxworks", 7) != 0)
2019	{
2020	  (void) bfd_set_section_alignment (stdoutput, text_section, 4);
2021	  (void) bfd_set_section_alignment (stdoutput, data_section, 4);
2022	  (void) bfd_set_section_alignment (stdoutput, bss_section, 4);
2023	}
2024
2025      /* Create a .reginfo section for register masks and a .mdebug
2026	 section for debugging information.  */
2027      {
2028	segT seg;
2029	subsegT subseg;
2030	flagword flags;
2031	segT sec;
2032
2033	seg = now_seg;
2034	subseg = now_subseg;
2035
2036	/* The ABI says this section should be loaded so that the
2037	   running program can access it.  However, we don't load it
2038	   if we are configured for an embedded target */
2039	flags = SEC_READONLY | SEC_DATA;
2040	if (strncmp (TARGET_OS, "elf", 3) != 0)
2041	  flags |= SEC_ALLOC | SEC_LOAD;
2042
2043	if (mips_abi != N64_ABI)
2044	  {
2045	    sec = subseg_new (".reginfo", (subsegT) 0);
2046
2047	    bfd_set_section_flags (stdoutput, sec, flags);
2048	    bfd_set_section_alignment (stdoutput, sec, HAVE_NEWABI ? 3 : 2);
2049
2050	    mips_regmask_frag = frag_more (sizeof (Elf32_External_RegInfo));
2051	  }
2052	else
2053	  {
2054	    /* The 64-bit ABI uses a .MIPS.options section rather than
2055               .reginfo section.  */
2056	    sec = subseg_new (".MIPS.options", (subsegT) 0);
2057	    bfd_set_section_flags (stdoutput, sec, flags);
2058	    bfd_set_section_alignment (stdoutput, sec, 3);
2059
2060	    /* Set up the option header.  */
2061	    {
2062	      Elf_Internal_Options opthdr;
2063	      char *f;
2064
2065	      opthdr.kind = ODK_REGINFO;
2066	      opthdr.size = (sizeof (Elf_External_Options)
2067			     + sizeof (Elf64_External_RegInfo));
2068	      opthdr.section = 0;
2069	      opthdr.info = 0;
2070	      f = frag_more (sizeof (Elf_External_Options));
2071	      bfd_mips_elf_swap_options_out (stdoutput, &opthdr,
2072					     (Elf_External_Options *) f);
2073
2074	      mips_regmask_frag = frag_more (sizeof (Elf64_External_RegInfo));
2075	    }
2076	  }
2077
2078	if (ECOFF_DEBUGGING)
2079	  {
2080	    sec = subseg_new (".mdebug", (subsegT) 0);
2081	    (void) bfd_set_section_flags (stdoutput, sec,
2082					  SEC_HAS_CONTENTS | SEC_READONLY);
2083	    (void) bfd_set_section_alignment (stdoutput, sec, 2);
2084	  }
2085	else if (mips_flag_pdr)
2086	  {
2087	    pdr_seg = subseg_new (".pdr", (subsegT) 0);
2088	    (void) bfd_set_section_flags (stdoutput, pdr_seg,
2089					  SEC_READONLY | SEC_RELOC
2090					  | SEC_DEBUGGING);
2091	    (void) bfd_set_section_alignment (stdoutput, pdr_seg, 2);
2092	  }
2093
2094	subseg_set (seg, subseg);
2095      }
2096    }
2097#endif /* OBJ_ELF */
2098
2099  if (! ECOFF_DEBUGGING)
2100    md_obj_begin ();
2101
2102  if (mips_fix_vr4120)
2103    init_vr4120_conflicts ();
2104}
2105
2106void
2107md_mips_end (void)
2108{
2109  if (! ECOFF_DEBUGGING)
2110    md_obj_end ();
2111}
2112
2113void
2114md_assemble (char *str)
2115{
2116  struct mips_cl_insn insn;
2117  bfd_reloc_code_real_type unused_reloc[3]
2118    = {BFD_RELOC_UNUSED, BFD_RELOC_UNUSED, BFD_RELOC_UNUSED};
2119
2120  imm_expr.X_op = O_absent;
2121  imm2_expr.X_op = O_absent;
2122  offset_expr.X_op = O_absent;
2123  imm_reloc[0] = BFD_RELOC_UNUSED;
2124  imm_reloc[1] = BFD_RELOC_UNUSED;
2125  imm_reloc[2] = BFD_RELOC_UNUSED;
2126  offset_reloc[0] = BFD_RELOC_UNUSED;
2127  offset_reloc[1] = BFD_RELOC_UNUSED;
2128  offset_reloc[2] = BFD_RELOC_UNUSED;
2129
2130  if (mips_opts.mips16)
2131    mips16_ip (str, &insn);
2132  else
2133    {
2134      mips_ip (str, &insn);
2135      DBG ((_("returned from mips_ip(%s) insn_opcode = 0x%x\n"),
2136	    str, insn.insn_opcode));
2137    }
2138
2139  if (insn_error)
2140    {
2141      as_bad ("%s `%s'", insn_error, str);
2142      return;
2143    }
2144
2145  if (insn.insn_mo->pinfo == INSN_MACRO)
2146    {
2147      macro_start ();
2148      if (mips_opts.mips16)
2149	mips16_macro (&insn);
2150      else
2151	macro (&insn);
2152      macro_end ();
2153    }
2154  else
2155    {
2156      if (imm_expr.X_op != O_absent)
2157	append_insn (&insn, &imm_expr, imm_reloc);
2158      else if (offset_expr.X_op != O_absent)
2159	append_insn (&insn, &offset_expr, offset_reloc);
2160      else
2161	append_insn (&insn, NULL, unused_reloc);
2162    }
2163}
2164
2165/* Convenience functions for abstracting away the differences between
2166   MIPS16 and non-MIPS16 relocations.  */
2167
2168static inline bfd_boolean
2169mips16_reloc_p (bfd_reloc_code_real_type reloc)
2170{
2171  switch (reloc)
2172    {
2173    case BFD_RELOC_MIPS16_JMP:
2174    case BFD_RELOC_MIPS16_GPREL:
2175    case BFD_RELOC_MIPS16_GOT16:
2176    case BFD_RELOC_MIPS16_CALL16:
2177    case BFD_RELOC_MIPS16_HI16_S:
2178    case BFD_RELOC_MIPS16_HI16:
2179    case BFD_RELOC_MIPS16_LO16:
2180      return TRUE;
2181
2182    default:
2183      return FALSE;
2184    }
2185}
2186
2187static inline bfd_boolean
2188got16_reloc_p (bfd_reloc_code_real_type reloc)
2189{
2190  return reloc == BFD_RELOC_MIPS_GOT16 || reloc == BFD_RELOC_MIPS16_GOT16;
2191}
2192
2193static inline bfd_boolean
2194hi16_reloc_p (bfd_reloc_code_real_type reloc)
2195{
2196  return reloc == BFD_RELOC_HI16_S || reloc == BFD_RELOC_MIPS16_HI16_S;
2197}
2198
2199static inline bfd_boolean
2200lo16_reloc_p (bfd_reloc_code_real_type reloc)
2201{
2202  return reloc == BFD_RELOC_LO16 || reloc == BFD_RELOC_MIPS16_LO16;
2203}
2204
2205/* Return true if the given relocation might need a matching %lo().
2206   This is only "might" because SVR4 R_MIPS_GOT16 relocations only
2207   need a matching %lo() when applied to local symbols.  */
2208
2209static inline bfd_boolean
2210reloc_needs_lo_p (bfd_reloc_code_real_type reloc)
2211{
2212  return (HAVE_IN_PLACE_ADDENDS
2213	  && (hi16_reloc_p (reloc)
2214	      /* VxWorks R_MIPS_GOT16 relocs never need a matching %lo();
2215		 all GOT16 relocations evaluate to "G".  */
2216	      || (got16_reloc_p (reloc) && mips_pic != VXWORKS_PIC)));
2217}
2218
2219/* Return the type of %lo() reloc needed by RELOC, given that
2220   reloc_needs_lo_p.  */
2221
2222static inline bfd_reloc_code_real_type
2223matching_lo_reloc (bfd_reloc_code_real_type reloc)
2224{
2225  return mips16_reloc_p (reloc) ? BFD_RELOC_MIPS16_LO16 : BFD_RELOC_LO16;
2226}
2227
2228/* Return true if the given fixup is followed by a matching R_MIPS_LO16
2229   relocation.  */
2230
2231static inline bfd_boolean
2232fixup_has_matching_lo_p (fixS *fixp)
2233{
2234  return (fixp->fx_next != NULL
2235	  && fixp->fx_next->fx_r_type == matching_lo_reloc (fixp->fx_r_type)
2236	  && fixp->fx_addsy == fixp->fx_next->fx_addsy
2237	  && fixp->fx_offset == fixp->fx_next->fx_offset);
2238}
2239
2240/* See whether instruction IP reads register REG.  CLASS is the type
2241   of register.  */
2242
2243static int
2244insn_uses_reg (const struct mips_cl_insn *ip, unsigned int reg,
2245	       enum mips_regclass regclass)
2246{
2247  if (regclass == MIPS16_REG)
2248    {
2249      gas_assert (mips_opts.mips16);
2250      reg = mips16_to_32_reg_map[reg];
2251      regclass = MIPS_GR_REG;
2252    }
2253
2254  /* Don't report on general register ZERO, since it never changes.  */
2255  if (regclass == MIPS_GR_REG && reg == ZERO)
2256    return 0;
2257
2258  if (regclass == MIPS_FP_REG)
2259    {
2260      gas_assert (! mips_opts.mips16);
2261      /* If we are called with either $f0 or $f1, we must check $f0.
2262	 This is not optimal, because it will introduce an unnecessary
2263	 NOP between "lwc1 $f0" and "swc1 $f1".  To fix this we would
2264	 need to distinguish reading both $f0 and $f1 or just one of
2265	 them.  Note that we don't have to check the other way,
2266	 because there is no instruction that sets both $f0 and $f1
2267	 and requires a delay.  */
2268      if ((ip->insn_mo->pinfo & INSN_READ_FPR_S)
2269	  && ((EXTRACT_OPERAND (FS, *ip) & ~(unsigned) 1)
2270	      == (reg &~ (unsigned) 1)))
2271	return 1;
2272      if ((ip->insn_mo->pinfo & INSN_READ_FPR_T)
2273	  && ((EXTRACT_OPERAND (FT, *ip) & ~(unsigned) 1)
2274	      == (reg &~ (unsigned) 1)))
2275	return 1;
2276    }
2277  else if (! mips_opts.mips16)
2278    {
2279      if ((ip->insn_mo->pinfo & INSN_READ_GPR_S)
2280	  && EXTRACT_OPERAND (RS, *ip) == reg)
2281	return 1;
2282      if ((ip->insn_mo->pinfo & INSN_READ_GPR_T)
2283	  && EXTRACT_OPERAND (RT, *ip) == reg)
2284	return 1;
2285    }
2286  else
2287    {
2288      if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_X)
2289	  && mips16_to_32_reg_map[MIPS16_EXTRACT_OPERAND (RX, *ip)] == reg)
2290	return 1;
2291      if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_Y)
2292	  && mips16_to_32_reg_map[MIPS16_EXTRACT_OPERAND (RY, *ip)] == reg)
2293	return 1;
2294      if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_Z)
2295	  && (mips16_to_32_reg_map[MIPS16_EXTRACT_OPERAND (MOVE32Z, *ip)]
2296	      == reg))
2297	return 1;
2298      if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_T) && reg == TREG)
2299	return 1;
2300      if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_SP) && reg == SP)
2301	return 1;
2302      if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_31) && reg == RA)
2303	return 1;
2304      if ((ip->insn_mo->pinfo & MIPS16_INSN_READ_GPR_X)
2305	  && MIPS16_EXTRACT_OPERAND (REGR32, *ip) == reg)
2306	return 1;
2307    }
2308
2309  return 0;
2310}
2311
2312/* This function returns true if modifying a register requires a
2313   delay.  */
2314
2315static int
2316reg_needs_delay (unsigned int reg)
2317{
2318  unsigned long prev_pinfo;
2319
2320  prev_pinfo = history[0].insn_mo->pinfo;
2321  if (! mips_opts.noreorder
2322      && (((prev_pinfo & INSN_LOAD_MEMORY_DELAY)
2323	   && ! gpr_interlocks)
2324	  || ((prev_pinfo & INSN_LOAD_COPROC_DELAY)
2325	      && ! cop_interlocks)))
2326    {
2327      /* A load from a coprocessor or from memory.  All load delays
2328	 delay the use of general register rt for one instruction.  */
2329      /* Itbl support may require additional care here.  */
2330      know (prev_pinfo & INSN_WRITE_GPR_T);
2331      if (reg == EXTRACT_OPERAND (RT, history[0]))
2332	return 1;
2333    }
2334
2335  return 0;
2336}
2337
2338/* Move all labels in insn_labels to the current insertion point.  */
2339
2340static void
2341mips_move_labels (void)
2342{
2343  segment_info_type *si = seg_info (now_seg);
2344  struct insn_label_list *l;
2345  valueT val;
2346
2347  for (l = si->label_list; l != NULL; l = l->next)
2348    {
2349      gas_assert (S_GET_SEGMENT (l->label) == now_seg);
2350      symbol_set_frag (l->label, frag_now);
2351      val = (valueT) frag_now_fix ();
2352      /* mips16 text labels are stored as odd.  */
2353      if (mips_opts.mips16)
2354	++val;
2355      S_SET_VALUE (l->label, val);
2356    }
2357}
2358
2359static bfd_boolean
2360s_is_linkonce (symbolS *sym, segT from_seg)
2361{
2362  bfd_boolean linkonce = FALSE;
2363  segT symseg = S_GET_SEGMENT (sym);
2364
2365  if (symseg != from_seg && !S_IS_LOCAL (sym))
2366    {
2367      if ((bfd_get_section_flags (stdoutput, symseg) & SEC_LINK_ONCE))
2368	linkonce = TRUE;
2369#ifdef OBJ_ELF
2370      /* The GNU toolchain uses an extension for ELF: a section
2371	 beginning with the magic string .gnu.linkonce is a
2372	 linkonce section.  */
2373      if (strncmp (segment_name (symseg), ".gnu.linkonce",
2374		   sizeof ".gnu.linkonce" - 1) == 0)
2375	linkonce = TRUE;
2376#endif
2377    }
2378  return linkonce;
2379}
2380
2381/* Mark instruction labels in mips16 mode.  This permits the linker to
2382   handle them specially, such as generating jalx instructions when
2383   needed.  We also make them odd for the duration of the assembly, in
2384   order to generate the right sort of code.  We will make them even
2385   in the adjust_symtab routine, while leaving them marked.  This is
2386   convenient for the debugger and the disassembler.  The linker knows
2387   to make them odd again.  */
2388
2389static void
2390mips16_mark_labels (void)
2391{
2392  segment_info_type *si = seg_info (now_seg);
2393  struct insn_label_list *l;
2394
2395  if (!mips_opts.mips16)
2396    return;
2397
2398  for (l = si->label_list; l != NULL; l = l->next)
2399   {
2400      symbolS *label = l->label;
2401
2402#if defined(OBJ_ELF) || defined(OBJ_MAYBE_ELF)
2403      if (IS_ELF)
2404	S_SET_OTHER (label, ELF_ST_SET_MIPS16 (S_GET_OTHER (label)));
2405#endif
2406      if ((S_GET_VALUE (label) & 1) == 0
2407	/* Don't adjust the address if the label is global or weak, or
2408	   in a link-once section, since we'll be emitting symbol reloc
2409	   references to it which will be patched up by the linker, and
2410	   the final value of the symbol may or may not be MIPS16.  */
2411	  && ! S_IS_WEAK (label)
2412	  && ! S_IS_EXTERNAL (label)
2413	  && ! s_is_linkonce (label, now_seg))
2414	S_SET_VALUE (label, S_GET_VALUE (label) | 1);
2415    }
2416}
2417
2418/* End the current frag.  Make it a variant frag and record the
2419   relaxation info.  */
2420
2421static void
2422relax_close_frag (void)
2423{
2424  mips_macro_warning.first_frag = frag_now;
2425  frag_var (rs_machine_dependent, 0, 0,
2426	    RELAX_ENCODE (mips_relax.sizes[0], mips_relax.sizes[1]),
2427	    mips_relax.symbol, 0, (char *) mips_relax.first_fixup);
2428
2429  memset (&mips_relax.sizes, 0, sizeof (mips_relax.sizes));
2430  mips_relax.first_fixup = 0;
2431}
2432
2433/* Start a new relaxation sequence whose expansion depends on SYMBOL.
2434   See the comment above RELAX_ENCODE for more details.  */
2435
2436static void
2437relax_start (symbolS *symbol)
2438{
2439  gas_assert (mips_relax.sequence == 0);
2440  mips_relax.sequence = 1;
2441  mips_relax.symbol = symbol;
2442}
2443
2444/* Start generating the second version of a relaxable sequence.
2445   See the comment above RELAX_ENCODE for more details.  */
2446
2447static void
2448relax_switch (void)
2449{
2450  gas_assert (mips_relax.sequence == 1);
2451  mips_relax.sequence = 2;
2452}
2453
2454/* End the current relaxable sequence.  */
2455
2456static void
2457relax_end (void)
2458{
2459  gas_assert (mips_relax.sequence == 2);
2460  relax_close_frag ();
2461  mips_relax.sequence = 0;
2462}
2463
2464/* Classify an instruction according to the FIX_VR4120_* enumeration.
2465   Return NUM_FIX_VR4120_CLASSES if the instruction isn't affected
2466   by VR4120 errata.  */
2467
2468static unsigned int
2469classify_vr4120_insn (const char *name)
2470{
2471  if (strncmp (name, "macc", 4) == 0)
2472    return FIX_VR4120_MACC;
2473  if (strncmp (name, "dmacc", 5) == 0)
2474    return FIX_VR4120_DMACC;
2475  if (strncmp (name, "mult", 4) == 0)
2476    return FIX_VR4120_MULT;
2477  if (strncmp (name, "dmult", 5) == 0)
2478    return FIX_VR4120_DMULT;
2479  if (strstr (name, "div"))
2480    return FIX_VR4120_DIV;
2481  if (strcmp (name, "mtlo") == 0 || strcmp (name, "mthi") == 0)
2482    return FIX_VR4120_MTHILO;
2483  return NUM_FIX_VR4120_CLASSES;
2484}
2485
2486#define INSN_ERET  0x42000018
2487#define INSN_DERET 0x4200001f
2488
2489/* Return the number of instructions that must separate INSN1 and INSN2,
2490   where INSN1 is the earlier instruction.  Return the worst-case value
2491   for any INSN2 if INSN2 is null.  */
2492
2493static unsigned int
2494insns_between (const struct mips_cl_insn *insn1,
2495	       const struct mips_cl_insn *insn2)
2496{
2497  unsigned long pinfo1, pinfo2;
2498
2499  /* This function needs to know which pinfo flags are set for INSN2
2500     and which registers INSN2 uses.  The former is stored in PINFO2 and
2501     the latter is tested via INSN2_USES_REG.  If INSN2 is null, PINFO2
2502     will have every flag set and INSN2_USES_REG will always return true.  */
2503  pinfo1 = insn1->insn_mo->pinfo;
2504  pinfo2 = insn2 ? insn2->insn_mo->pinfo : ~0U;
2505
2506#define INSN2_USES_REG(REG, CLASS) \
2507   (insn2 == NULL || insn_uses_reg (insn2, REG, CLASS))
2508
2509  /* For most targets, write-after-read dependencies on the HI and LO
2510     registers must be separated by at least two instructions.  */
2511  if (!hilo_interlocks)
2512    {
2513      if ((pinfo1 & INSN_READ_LO) && (pinfo2 & INSN_WRITE_LO))
2514	return 2;
2515      if ((pinfo1 & INSN_READ_HI) && (pinfo2 & INSN_WRITE_HI))
2516	return 2;
2517    }
2518
2519  /* If we're working around r7000 errata, there must be two instructions
2520     between an mfhi or mflo and any instruction that uses the result.  */
2521  if (mips_7000_hilo_fix
2522      && MF_HILO_INSN (pinfo1)
2523      && INSN2_USES_REG (EXTRACT_OPERAND (RD, *insn1), MIPS_GR_REG))
2524    return 2;
2525
2526  /* If we're working around 24K errata, one instruction is required
2527     if an ERET or DERET is followed by a branch instruction.  */
2528  if (mips_fix_24k)
2529    {
2530      if (insn1->insn_opcode == INSN_ERET
2531	  || insn1->insn_opcode == INSN_DERET)
2532	{
2533	  if (insn2 == NULL
2534	      || insn2->insn_opcode == INSN_ERET
2535	      || insn2->insn_opcode == INSN_DERET
2536	      || (insn2->insn_mo->pinfo
2537		  & (INSN_UNCOND_BRANCH_DELAY
2538		     | INSN_COND_BRANCH_DELAY
2539		     | INSN_COND_BRANCH_LIKELY)) != 0)
2540	    return 1;
2541	}
2542    }
2543
2544  /* If working around VR4120 errata, check for combinations that need
2545     a single intervening instruction.  */
2546  if (mips_fix_vr4120)
2547    {
2548      unsigned int class1, class2;
2549
2550      class1 = classify_vr4120_insn (insn1->insn_mo->name);
2551      if (class1 != NUM_FIX_VR4120_CLASSES && vr4120_conflicts[class1] != 0)
2552	{
2553	  if (insn2 == NULL)
2554	    return 1;
2555	  class2 = classify_vr4120_insn (insn2->insn_mo->name);
2556	  if (vr4120_conflicts[class1] & (1 << class2))
2557	    return 1;
2558	}
2559    }
2560
2561  if (!mips_opts.mips16)
2562    {
2563      /* Check for GPR or coprocessor load delays.  All such delays
2564	 are on the RT register.  */
2565      /* Itbl support may require additional care here.  */
2566      if ((!gpr_interlocks && (pinfo1 & INSN_LOAD_MEMORY_DELAY))
2567	  || (!cop_interlocks && (pinfo1 & INSN_LOAD_COPROC_DELAY)))
2568	{
2569	  know (pinfo1 & INSN_WRITE_GPR_T);
2570	  if (INSN2_USES_REG (EXTRACT_OPERAND (RT, *insn1), MIPS_GR_REG))
2571	    return 1;
2572	}
2573
2574      /* Check for generic coprocessor hazards.
2575
2576	 This case is not handled very well.  There is no special
2577	 knowledge of CP0 handling, and the coprocessors other than
2578	 the floating point unit are not distinguished at all.  */
2579      /* Itbl support may require additional care here. FIXME!
2580	 Need to modify this to include knowledge about
2581	 user specified delays!  */
2582      else if ((!cop_interlocks && (pinfo1 & INSN_COPROC_MOVE_DELAY))
2583	       || (!cop_mem_interlocks && (pinfo1 & INSN_COPROC_MEMORY_DELAY)))
2584	{
2585	  /* Handle cases where INSN1 writes to a known general coprocessor
2586	     register.  There must be a one instruction delay before INSN2
2587	     if INSN2 reads that register, otherwise no delay is needed.  */
2588	  if (pinfo1 & INSN_WRITE_FPR_T)
2589	    {
2590	      if (INSN2_USES_REG (EXTRACT_OPERAND (FT, *insn1), MIPS_FP_REG))
2591		return 1;
2592	    }
2593	  else if (pinfo1 & INSN_WRITE_FPR_S)
2594	    {
2595	      if (INSN2_USES_REG (EXTRACT_OPERAND (FS, *insn1), MIPS_FP_REG))
2596		return 1;
2597	    }
2598	  else
2599	    {
2600	      /* Read-after-write dependencies on the control registers
2601		 require a two-instruction gap.  */
2602	      if ((pinfo1 & INSN_WRITE_COND_CODE)
2603		  && (pinfo2 & INSN_READ_COND_CODE))
2604		return 2;
2605
2606	      /* We don't know exactly what INSN1 does.  If INSN2 is
2607		 also a coprocessor instruction, assume there must be
2608		 a one instruction gap.  */
2609	      if (pinfo2 & INSN_COP)
2610		return 1;
2611	    }
2612	}
2613
2614      /* Check for read-after-write dependencies on the coprocessor
2615	 control registers in cases where INSN1 does not need a general
2616	 coprocessor delay.  This means that INSN1 is a floating point
2617	 comparison instruction.  */
2618      /* Itbl support may require additional care here.  */
2619      else if (!cop_interlocks
2620	       && (pinfo1 & INSN_WRITE_COND_CODE)
2621	       && (pinfo2 & INSN_READ_COND_CODE))
2622	return 1;
2623    }
2624
2625#undef INSN2_USES_REG
2626
2627  return 0;
2628}
2629
2630/* Return the number of nops that would be needed to work around the
2631   VR4130 mflo/mfhi errata if instruction INSN immediately followed
2632   the MAX_VR4130_NOPS instructions described by HIST.  */
2633
2634static int
2635nops_for_vr4130 (const struct mips_cl_insn *hist,
2636		 const struct mips_cl_insn *insn)
2637{
2638  int i, j, reg;
2639
2640  /* Check if the instruction writes to HI or LO.  MTHI and MTLO
2641     are not affected by the errata.  */
2642  if (insn != 0
2643      && ((insn->insn_mo->pinfo & (INSN_WRITE_HI | INSN_WRITE_LO)) == 0
2644	  || strcmp (insn->insn_mo->name, "mtlo") == 0
2645	  || strcmp (insn->insn_mo->name, "mthi") == 0))
2646    return 0;
2647
2648  /* Search for the first MFLO or MFHI.  */
2649  for (i = 0; i < MAX_VR4130_NOPS; i++)
2650    if (MF_HILO_INSN (hist[i].insn_mo->pinfo))
2651      {
2652	/* Extract the destination register.  */
2653	if (mips_opts.mips16)
2654	  reg = mips16_to_32_reg_map[MIPS16_EXTRACT_OPERAND (RX, hist[i])];
2655	else
2656	  reg = EXTRACT_OPERAND (RD, hist[i]);
2657
2658	/* No nops are needed if INSN reads that register.  */
2659	if (insn != NULL && insn_uses_reg (insn, reg, MIPS_GR_REG))
2660	  return 0;
2661
2662	/* ...or if any of the intervening instructions do.  */
2663	for (j = 0; j < i; j++)
2664	  if (insn_uses_reg (&hist[j], reg, MIPS_GR_REG))
2665	    return 0;
2666
2667	return MAX_VR4130_NOPS - i;
2668      }
2669  return 0;
2670}
2671
2672/* Return the number of nops that would be needed if instruction INSN
2673   immediately followed the MAX_NOPS instructions given by HIST,
2674   where HIST[0] is the most recent instruction.  If INSN is null,
2675   return the worse-case number of nops for any instruction.  */
2676
2677static int
2678nops_for_insn (const struct mips_cl_insn *hist,
2679	       const struct mips_cl_insn *insn)
2680{
2681  int i, nops, tmp_nops;
2682
2683  nops = 0;
2684  for (i = 0; i < MAX_DELAY_NOPS; i++)
2685    {
2686      tmp_nops = insns_between (hist + i, insn) - i;
2687      if (tmp_nops > nops)
2688	nops = tmp_nops;
2689    }
2690
2691  if (mips_fix_vr4130)
2692    {
2693      tmp_nops = nops_for_vr4130 (hist, insn);
2694      if (tmp_nops > nops)
2695	nops = tmp_nops;
2696    }
2697
2698  return nops;
2699}
2700
2701/* The variable arguments provide NUM_INSNS extra instructions that
2702   might be added to HIST.  Return the largest number of nops that
2703   would be needed after the extended sequence.  */
2704
2705static int
2706nops_for_sequence (int num_insns, const struct mips_cl_insn *hist, ...)
2707{
2708  va_list args;
2709  struct mips_cl_insn buffer[MAX_NOPS];
2710  struct mips_cl_insn *cursor;
2711  int nops;
2712
2713  va_start (args, hist);
2714  cursor = buffer + num_insns;
2715  memcpy (cursor, hist, (MAX_NOPS - num_insns) * sizeof (*cursor));
2716  while (cursor > buffer)
2717    *--cursor = *va_arg (args, const struct mips_cl_insn *);
2718
2719  nops = nops_for_insn (buffer, NULL);
2720  va_end (args);
2721  return nops;
2722}
2723
2724/* Like nops_for_insn, but if INSN is a branch, take into account the
2725   worst-case delay for the branch target.  */
2726
2727static int
2728nops_for_insn_or_target (const struct mips_cl_insn *hist,
2729			 const struct mips_cl_insn *insn)
2730{
2731  int nops, tmp_nops;
2732
2733  nops = nops_for_insn (hist, insn);
2734  if (insn->insn_mo->pinfo & (INSN_UNCOND_BRANCH_DELAY
2735			      | INSN_COND_BRANCH_DELAY
2736			      | INSN_COND_BRANCH_LIKELY))
2737    {
2738      tmp_nops = nops_for_sequence (2, hist, insn, NOP_INSN);
2739      if (tmp_nops > nops)
2740	nops = tmp_nops;
2741    }
2742  else if (mips_opts.mips16
2743	   && (insn->insn_mo->pinfo & (MIPS16_INSN_UNCOND_BRANCH
2744				       | MIPS16_INSN_COND_BRANCH)))
2745    {
2746      tmp_nops = nops_for_sequence (1, hist, insn);
2747      if (tmp_nops > nops)
2748	nops = tmp_nops;
2749    }
2750  return nops;
2751}
2752
2753static void
2754trap_zero_jump (struct mips_cl_insn * ip)
2755{
2756  if (strcmp (ip->insn_mo->name, "j") == 0
2757      || strcmp (ip->insn_mo->name, "jr") == 0
2758      || strcmp (ip->insn_mo->name, "jalr") == 0)
2759    {
2760      int sreg;
2761
2762      if (mips_opts.warn_about_macros)
2763        return;
2764
2765      sreg = EXTRACT_OPERAND (RS, *ip);
2766      if (mips_opts.isa == ISA_MIPS32
2767          || mips_opts.isa == ISA_MIPS32R2
2768          || mips_opts.isa == ISA_MIPS64
2769          || mips_opts.isa == ISA_MIPS64R2)
2770	{
2771	  expressionS ep;
2772	  ep.X_op = O_constant;
2773	  ep.X_add_number = 4096;
2774	  macro_build (&ep, "tltiu", "s,j", sreg, BFD_RELOC_LO16);
2775	}
2776      else if (mips_opts.isa != ISA_UNKNOWN
2777	       && mips_opts.isa != ISA_MIPS1)
2778	macro_build (NULL, "teq", "s,t", sreg, 0);
2779  }
2780}
2781
2782/* Fix NOP issue: Replace nops by "or at,at,zero".  */
2783
2784static void
2785fix_loongson2f_nop (struct mips_cl_insn * ip)
2786{
2787  if (strcmp (ip->insn_mo->name, "nop") == 0)
2788    ip->insn_opcode = LOONGSON2F_NOP_INSN;
2789}
2790
2791/* Fix Jump Issue: Eliminate instruction fetch from outside 256M region
2792                   jr target pc &= 'hffff_ffff_cfff_ffff.  */
2793
2794static void
2795fix_loongson2f_jump (struct mips_cl_insn * ip)
2796{
2797  if (strcmp (ip->insn_mo->name, "j") == 0
2798      || strcmp (ip->insn_mo->name, "jr") == 0
2799      || strcmp (ip->insn_mo->name, "jalr") == 0)
2800    {
2801      int sreg;
2802      expressionS ep;
2803
2804      if (! mips_opts.at)
2805        return;
2806
2807      sreg = EXTRACT_OPERAND (RS, *ip);
2808      if (sreg == ZERO || sreg == KT0 || sreg == KT1 || sreg == ATREG)
2809        return;
2810
2811      ep.X_op = O_constant;
2812      ep.X_add_number = 0xcfff0000;
2813      macro_build (&ep, "lui", "t,u", ATREG, BFD_RELOC_HI16);
2814      ep.X_add_number = 0xffff;
2815      macro_build (&ep, "ori", "t,r,i", ATREG, ATREG, BFD_RELOC_LO16);
2816      macro_build (NULL, "and", "d,v,t", sreg, sreg, ATREG);
2817      /* Hide these three instructions to avoid getting a ``macro expanded into
2818         multiple instructions'' warning. */
2819      if (mips_relax.sequence != 2)
2820        mips_macro_warning.sizes[0] -= 3 * 4;
2821      if (mips_relax.sequence != 1)
2822        mips_macro_warning.sizes[1] -= 3 * 4;
2823    }
2824}
2825
2826static void
2827fix_loongson2f (struct mips_cl_insn * ip)
2828{
2829  if (mips_fix_loongson2f_nop)
2830    fix_loongson2f_nop (ip);
2831
2832  if (mips_fix_loongson2f_jump)
2833    fix_loongson2f_jump (ip);
2834}
2835
2836/* Output an instruction.  IP is the instruction information.
2837   ADDRESS_EXPR is an operand of the instruction to be used with
2838   RELOC_TYPE.  */
2839
2840static void
2841append_insn (struct mips_cl_insn *ip, expressionS *address_expr,
2842	     bfd_reloc_code_real_type *reloc_type)
2843{
2844  unsigned long prev_pinfo, pinfo;
2845  relax_stateT prev_insn_frag_type = 0;
2846  bfd_boolean relaxed_branch = FALSE;
2847  segment_info_type *si = seg_info (now_seg);
2848
2849  if (mips_fix_loongson2f)
2850    fix_loongson2f (ip);
2851  if (mips_trap_zero_jump)
2852    trap_zero_jump (ip);
2853
2854  /* Mark instruction labels in mips16 mode.  */
2855  mips16_mark_labels ();
2856
2857  prev_pinfo = history[0].insn_mo->pinfo;
2858  pinfo = ip->insn_mo->pinfo;
2859
2860  if (mips_relax.sequence != 2 && !mips_opts.noreorder)
2861    {
2862      /* There are a lot of optimizations we could do that we don't.
2863	 In particular, we do not, in general, reorder instructions.
2864	 If you use gcc with optimization, it will reorder
2865	 instructions and generally do much more optimization then we
2866	 do here; repeating all that work in the assembler would only
2867	 benefit hand written assembly code, and does not seem worth
2868	 it.  */
2869      int nops = (mips_optimize == 0
2870		  ? nops_for_insn (history, NULL)
2871		  : nops_for_insn_or_target (history, ip));
2872      if (nops > 0)
2873	{
2874	  fragS *old_frag;
2875	  unsigned long old_frag_offset;
2876	  int i;
2877
2878	  old_frag = frag_now;
2879	  old_frag_offset = frag_now_fix ();
2880
2881	  for (i = 0; i < nops; i++)
2882	    emit_nop ();
2883
2884	  if (listing)
2885	    {
2886	      listing_prev_line ();
2887	      /* We may be at the start of a variant frag.  In case we
2888                 are, make sure there is enough space for the frag
2889                 after the frags created by listing_prev_line.  The
2890                 argument to frag_grow here must be at least as large
2891                 as the argument to all other calls to frag_grow in
2892                 this file.  We don't have to worry about being in the
2893                 middle of a variant frag, because the variants insert
2894                 all needed nop instructions themselves.  */
2895	      frag_grow (40);
2896	    }
2897
2898	  mips_move_labels ();
2899
2900#ifndef NO_ECOFF_DEBUGGING
2901	  if (ECOFF_DEBUGGING)
2902	    ecoff_fix_loc (old_frag, old_frag_offset);
2903#endif
2904	}
2905    }
2906  else if (mips_relax.sequence != 2 && prev_nop_frag != NULL)
2907    {
2908      /* Work out how many nops in prev_nop_frag are needed by IP.  */
2909      int nops = nops_for_insn_or_target (history, ip);
2910      gas_assert (nops <= prev_nop_frag_holds);
2911
2912      /* Enforce NOPS as a minimum.  */
2913      if (nops > prev_nop_frag_required)
2914	prev_nop_frag_required = nops;
2915
2916      if (prev_nop_frag_holds == prev_nop_frag_required)
2917	{
2918	  /* Settle for the current number of nops.  Update the history
2919	     accordingly (for the benefit of any future .set reorder code).  */
2920	  prev_nop_frag = NULL;
2921	  insert_into_history (prev_nop_frag_since,
2922			       prev_nop_frag_holds, NOP_INSN);
2923	}
2924      else
2925	{
2926	  /* Allow this instruction to replace one of the nops that was
2927	     tentatively added to prev_nop_frag.  */
2928	  prev_nop_frag->fr_fix -= mips_opts.mips16 ? 2 : 4;
2929	  prev_nop_frag_holds--;
2930	  prev_nop_frag_since++;
2931	}
2932    }
2933
2934#ifdef OBJ_ELF
2935  /* The value passed to dwarf2_emit_insn is the distance between
2936     the beginning of the current instruction and the address that
2937     should be recorded in the debug tables.  For MIPS16 debug info
2938     we want to use ISA-encoded addresses, so we pass -1 for an
2939     address higher by one than the current.  */
2940  dwarf2_emit_insn (mips_opts.mips16 ? -1 : 0);
2941#endif
2942
2943  /* Record the frag type before frag_var.  */
2944  if (history[0].frag)
2945    prev_insn_frag_type = history[0].frag->fr_type;
2946
2947  if (address_expr
2948      && *reloc_type == BFD_RELOC_16_PCREL_S2
2949      && (pinfo & INSN_UNCOND_BRANCH_DELAY || pinfo & INSN_COND_BRANCH_DELAY
2950	  || pinfo & INSN_COND_BRANCH_LIKELY)
2951      && mips_relax_branch
2952      /* Don't try branch relaxation within .set nomacro, or within
2953	 .set noat if we use $at for PIC computations.  If it turns
2954	 out that the branch was out-of-range, we'll get an error.  */
2955      && !mips_opts.warn_about_macros
2956      && (mips_opts.at || mips_pic == NO_PIC)
2957      && !mips_opts.mips16)
2958    {
2959      relaxed_branch = TRUE;
2960      add_relaxed_insn (ip, (relaxed_branch_length
2961			     (NULL, NULL,
2962			      (pinfo & INSN_UNCOND_BRANCH_DELAY) ? -1
2963			      : (pinfo & INSN_COND_BRANCH_LIKELY) ? 1
2964			      : 0)), 4,
2965			RELAX_BRANCH_ENCODE
2966			(pinfo & INSN_UNCOND_BRANCH_DELAY,
2967			 pinfo & INSN_COND_BRANCH_LIKELY,
2968			 pinfo & INSN_WRITE_GPR_31,
2969			 0),
2970			address_expr->X_add_symbol,
2971			address_expr->X_add_number);
2972      *reloc_type = BFD_RELOC_UNUSED;
2973    }
2974  else if (*reloc_type > BFD_RELOC_UNUSED)
2975    {
2976      /* We need to set up a variant frag.  */
2977      gas_assert (mips_opts.mips16 && address_expr != NULL);
2978      add_relaxed_insn (ip, 4, 0,
2979			RELAX_MIPS16_ENCODE
2980			(*reloc_type - BFD_RELOC_UNUSED,
2981			 mips16_small, mips16_ext,
2982			 prev_pinfo & INSN_UNCOND_BRANCH_DELAY,
2983			 history[0].mips16_absolute_jump_p),
2984			make_expr_symbol (address_expr), 0);
2985    }
2986  else if (mips_opts.mips16
2987	   && ! ip->use_extend
2988	   && *reloc_type != BFD_RELOC_MIPS16_JMP)
2989    {
2990      if ((pinfo & INSN_UNCOND_BRANCH_DELAY) == 0)
2991	/* Make sure there is enough room to swap this instruction with
2992	   a following jump instruction.  */
2993	frag_grow (6);
2994      add_fixed_insn (ip);
2995    }
2996  else
2997    {
2998      if (mips_opts.mips16
2999	  && mips_opts.noreorder
3000	  && (prev_pinfo & INSN_UNCOND_BRANCH_DELAY) != 0)
3001	as_warn (_("extended instruction in delay slot"));
3002
3003      if (mips_relax.sequence)
3004	{
3005	  /* If we've reached the end of this frag, turn it into a variant
3006	     frag and record the information for the instructions we've
3007	     written so far.  */
3008	  if (frag_room () < 4)
3009	    relax_close_frag ();
3010	  mips_relax.sizes[mips_relax.sequence - 1] += 4;
3011	}
3012
3013      if (mips_relax.sequence != 2)
3014	mips_macro_warning.sizes[0] += 4;
3015      if (mips_relax.sequence != 1)
3016	mips_macro_warning.sizes[1] += 4;
3017
3018      if (mips_opts.mips16)
3019	{
3020	  ip->fixed_p = 1;
3021	  ip->mips16_absolute_jump_p = (*reloc_type == BFD_RELOC_MIPS16_JMP);
3022	}
3023      add_fixed_insn (ip);
3024    }
3025
3026  if (address_expr != NULL && *reloc_type <= BFD_RELOC_UNUSED)
3027    {
3028      if (address_expr->X_op == O_constant)
3029	{
3030	  unsigned int tmp;
3031
3032	  switch (*reloc_type)
3033	    {
3034	    case BFD_RELOC_32:
3035	      ip->insn_opcode |= address_expr->X_add_number;
3036	      break;
3037
3038	    case BFD_RELOC_MIPS_HIGHEST:
3039	      tmp = (address_expr->X_add_number + 0x800080008000ull) >> 48;
3040	      ip->insn_opcode |= tmp & 0xffff;
3041	      break;
3042
3043	    case BFD_RELOC_MIPS_HIGHER:
3044	      tmp = (address_expr->X_add_number + 0x80008000ull) >> 32;
3045	      ip->insn_opcode |= tmp & 0xffff;
3046	      break;
3047
3048	    case BFD_RELOC_HI16_S:
3049	      tmp = (address_expr->X_add_number + 0x8000) >> 16;
3050	      ip->insn_opcode |= tmp & 0xffff;
3051	      break;
3052
3053	    case BFD_RELOC_HI16:
3054	      ip->insn_opcode |= (address_expr->X_add_number >> 16) & 0xffff;
3055	      break;
3056
3057	    case BFD_RELOC_UNUSED:
3058	    case BFD_RELOC_LO16:
3059	    case BFD_RELOC_MIPS_GOT_DISP:
3060	      ip->insn_opcode |= address_expr->X_add_number & 0xffff;
3061	      break;
3062
3063	    case BFD_RELOC_MIPS_JMP:
3064	      if ((address_expr->X_add_number & 3) != 0)
3065		as_bad (_("jump to misaligned address (0x%lx)"),
3066			(unsigned long) address_expr->X_add_number);
3067	      ip->insn_opcode |= (address_expr->X_add_number >> 2) & 0x3ffffff;
3068	      break;
3069
3070	    case BFD_RELOC_MIPS16_JMP:
3071	      if ((address_expr->X_add_number & 3) != 0)
3072		as_bad (_("jump to misaligned address (0x%lx)"),
3073			(unsigned long) address_expr->X_add_number);
3074	      ip->insn_opcode |=
3075		(((address_expr->X_add_number & 0x7c0000) << 3)
3076		 | ((address_expr->X_add_number & 0xf800000) >> 7)
3077		 | ((address_expr->X_add_number & 0x3fffc) >> 2));
3078	      break;
3079
3080	    case BFD_RELOC_16_PCREL_S2:
3081	      if ((address_expr->X_add_number & 3) != 0)
3082		as_bad (_("branch to misaligned address (0x%lx)"),
3083			(unsigned long) address_expr->X_add_number);
3084	      if (mips_relax_branch)
3085		goto need_reloc;
3086	      if ((address_expr->X_add_number + 0x20000) & ~0x3ffff)
3087		as_bad (_("branch address range overflow (0x%lx)"),
3088			(unsigned long) address_expr->X_add_number);
3089	      ip->insn_opcode |= (address_expr->X_add_number >> 2) & 0xffff;
3090	      break;
3091
3092	    default:
3093	      internalError ();
3094	    }
3095	}
3096      else if (*reloc_type < BFD_RELOC_UNUSED)
3097	need_reloc:
3098	{
3099	  reloc_howto_type *howto;
3100	  int i;
3101
3102	  /* In a compound relocation, it is the final (outermost)
3103	     operator that determines the relocated field.  */
3104	  for (i = 1; i < 3; i++)
3105	    if (reloc_type[i] == BFD_RELOC_UNUSED)
3106	      break;
3107
3108	  howto = bfd_reloc_type_lookup (stdoutput, reloc_type[i - 1]);
3109	  if (howto == NULL)
3110	    {
3111	      /* To reproduce this failure try assembling gas/testsuites/
3112		 gas/mips/mips16-intermix.s with a mips-ecoff targeted
3113		 assembler.  */
3114	      as_bad (_("Unsupported MIPS relocation number %d"), reloc_type[i - 1]);
3115	      howto = bfd_reloc_type_lookup (stdoutput, BFD_RELOC_16);
3116	    }
3117
3118	  ip->fixp[0] = fix_new_exp (ip->frag, ip->where,
3119				     bfd_get_reloc_size (howto),
3120				     address_expr,
3121				     reloc_type[0] == BFD_RELOC_16_PCREL_S2,
3122				     reloc_type[0]);
3123
3124	  /* Tag symbols that have a R_MIPS16_26 relocation against them.  */
3125	  if (reloc_type[0] == BFD_RELOC_MIPS16_JMP
3126	      && ip->fixp[0]->fx_addsy)
3127	    *symbol_get_tc (ip->fixp[0]->fx_addsy) = 1;
3128
3129	  /* These relocations can have an addend that won't fit in
3130	     4 octets for 64bit assembly.  */
3131	  if (HAVE_64BIT_GPRS
3132	      && ! howto->partial_inplace
3133	      && (reloc_type[0] == BFD_RELOC_16
3134		  || reloc_type[0] == BFD_RELOC_32
3135		  || reloc_type[0] == BFD_RELOC_MIPS_JMP
3136		  || reloc_type[0] == BFD_RELOC_GPREL16
3137		  || reloc_type[0] == BFD_RELOC_MIPS_LITERAL
3138		  || reloc_type[0] == BFD_RELOC_GPREL32
3139		  || reloc_type[0] == BFD_RELOC_64
3140		  || reloc_type[0] == BFD_RELOC_CTOR
3141		  || reloc_type[0] == BFD_RELOC_MIPS_SUB
3142		  || reloc_type[0] == BFD_RELOC_MIPS_HIGHEST
3143		  || reloc_type[0] == BFD_RELOC_MIPS_HIGHER
3144		  || reloc_type[0] == BFD_RELOC_MIPS_SCN_DISP
3145		  || reloc_type[0] == BFD_RELOC_MIPS_REL16
3146		  || reloc_type[0] == BFD_RELOC_MIPS_RELGOT
3147		  || reloc_type[0] == BFD_RELOC_MIPS16_GPREL
3148		  || hi16_reloc_p (reloc_type[0])
3149		  || lo16_reloc_p (reloc_type[0])))
3150	    ip->fixp[0]->fx_no_overflow = 1;
3151
3152	  if (mips_relax.sequence)
3153	    {
3154	      if (mips_relax.first_fixup == 0)
3155		mips_relax.first_fixup = ip->fixp[0];
3156	    }
3157	  else if (reloc_needs_lo_p (*reloc_type))
3158	    {
3159	      struct mips_hi_fixup *hi_fixup;
3160
3161	      /* Reuse the last entry if it already has a matching %lo.  */
3162	      hi_fixup = mips_hi_fixup_list;
3163	      if (hi_fixup == 0
3164		  || !fixup_has_matching_lo_p (hi_fixup->fixp))
3165		{
3166		  hi_fixup = ((struct mips_hi_fixup *)
3167			      xmalloc (sizeof (struct mips_hi_fixup)));
3168		  hi_fixup->next = mips_hi_fixup_list;
3169		  mips_hi_fixup_list = hi_fixup;
3170		}
3171	      hi_fixup->fixp = ip->fixp[0];
3172	      hi_fixup->seg = now_seg;
3173	    }
3174
3175	  /* Add fixups for the second and third relocations, if given.
3176	     Note that the ABI allows the second relocation to be
3177	     against RSS_UNDEF, RSS_GP, RSS_GP0 or RSS_LOC.  At the
3178	     moment we only use RSS_UNDEF, but we could add support
3179	     for the others if it ever becomes necessary.  */
3180	  for (i = 1; i < 3; i++)
3181	    if (reloc_type[i] != BFD_RELOC_UNUSED)
3182	      {
3183		ip->fixp[i] = fix_new (ip->frag, ip->where,
3184				       ip->fixp[0]->fx_size, NULL, 0,
3185				       FALSE, reloc_type[i]);
3186
3187		/* Use fx_tcbit to mark compound relocs.  */
3188		ip->fixp[0]->fx_tcbit = 1;
3189		ip->fixp[i]->fx_tcbit = 1;
3190	      }
3191	}
3192    }
3193  install_insn (ip);
3194
3195  /* Update the register mask information.  */
3196  if (! mips_opts.mips16)
3197    {
3198      if (pinfo & INSN_WRITE_GPR_D)
3199	mips_gprmask |= 1 << EXTRACT_OPERAND (RD, *ip);
3200      if ((pinfo & (INSN_WRITE_GPR_T | INSN_READ_GPR_T)) != 0)
3201	mips_gprmask |= 1 << EXTRACT_OPERAND (RT, *ip);
3202      if (pinfo & INSN_READ_GPR_S)
3203	mips_gprmask |= 1 << EXTRACT_OPERAND (RS, *ip);
3204      if (pinfo & INSN_WRITE_GPR_31)
3205	mips_gprmask |= 1 << RA;
3206      if (pinfo & INSN_WRITE_FPR_D)
3207	mips_cprmask[1] |= 1 << EXTRACT_OPERAND (FD, *ip);
3208      if ((pinfo & (INSN_WRITE_FPR_S | INSN_READ_FPR_S)) != 0)
3209	mips_cprmask[1] |= 1 << EXTRACT_OPERAND (FS, *ip);
3210      if ((pinfo & (INSN_WRITE_FPR_T | INSN_READ_FPR_T)) != 0)
3211	mips_cprmask[1] |= 1 << EXTRACT_OPERAND (FT, *ip);
3212      if ((pinfo & INSN_READ_FPR_R) != 0)
3213	mips_cprmask[1] |= 1 << EXTRACT_OPERAND (FR, *ip);
3214      if (pinfo & INSN_COP)
3215	{
3216	  /* We don't keep enough information to sort these cases out.
3217	     The itbl support does keep this information however, although
3218	     we currently don't support itbl fprmats as part of the cop
3219	     instruction.  May want to add this support in the future.  */
3220	}
3221      /* Never set the bit for $0, which is always zero.  */
3222      mips_gprmask &= ~1 << 0;
3223    }
3224  else
3225    {
3226      if (pinfo & (MIPS16_INSN_WRITE_X | MIPS16_INSN_READ_X))
3227	mips_gprmask |= 1 << MIPS16_EXTRACT_OPERAND (RX, *ip);
3228      if (pinfo & (MIPS16_INSN_WRITE_Y | MIPS16_INSN_READ_Y))
3229	mips_gprmask |= 1 << MIPS16_EXTRACT_OPERAND (RY, *ip);
3230      if (pinfo & MIPS16_INSN_WRITE_Z)
3231	mips_gprmask |= 1 << MIPS16_EXTRACT_OPERAND (RZ, *ip);
3232      if (pinfo & (MIPS16_INSN_WRITE_T | MIPS16_INSN_READ_T))
3233	mips_gprmask |= 1 << TREG;
3234      if (pinfo & (MIPS16_INSN_WRITE_SP | MIPS16_INSN_READ_SP))
3235	mips_gprmask |= 1 << SP;
3236      if (pinfo & (MIPS16_INSN_WRITE_31 | MIPS16_INSN_READ_31))
3237	mips_gprmask |= 1 << RA;
3238      if (pinfo & MIPS16_INSN_WRITE_GPR_Y)
3239	mips_gprmask |= 1 << MIPS16OP_EXTRACT_REG32R (ip->insn_opcode);
3240      if (pinfo & MIPS16_INSN_READ_Z)
3241	mips_gprmask |= 1 << MIPS16_EXTRACT_OPERAND (MOVE32Z, *ip);
3242      if (pinfo & MIPS16_INSN_READ_GPR_X)
3243	mips_gprmask |= 1 << MIPS16_EXTRACT_OPERAND (REGR32, *ip);
3244    }
3245
3246  if (mips_relax.sequence != 2 && !mips_opts.noreorder)
3247    {
3248      /* Filling the branch delay slot is more complex.  We try to
3249	 switch the branch with the previous instruction, which we can
3250	 do if the previous instruction does not set up a condition
3251	 that the branch tests and if the branch is not itself the
3252	 target of any branch.  */
3253      if ((pinfo & INSN_UNCOND_BRANCH_DELAY)
3254	  || (pinfo & INSN_COND_BRANCH_DELAY))
3255	{
3256	  if (mips_optimize < 2
3257	      /* If we have seen .set volatile or .set nomove, don't
3258		 optimize.  */
3259	      || mips_opts.nomove != 0
3260	      /* We can't swap if the previous instruction's position
3261		 is fixed.  */
3262	      || history[0].fixed_p
3263	      /* If the previous previous insn was in a .set
3264		 noreorder, we can't swap.  Actually, the MIPS
3265		 assembler will swap in this situation.  However, gcc
3266		 configured -with-gnu-as will generate code like
3267		   .set noreorder
3268		   lw	$4,XXX
3269		   .set	reorder
3270		   INSN
3271		   bne	$4,$0,foo
3272		 in which we can not swap the bne and INSN.  If gcc is
3273		 not configured -with-gnu-as, it does not output the
3274		 .set pseudo-ops.  */
3275	      || history[1].noreorder_p
3276	      /* If the branch is itself the target of a branch, we
3277		 can not swap.  We cheat on this; all we check for is
3278		 whether there is a label on this instruction.  If
3279		 there are any branches to anything other than a
3280		 label, users must use .set noreorder.  */
3281	      || si->label_list != NULL
3282	      /* If the previous instruction is in a variant frag
3283		 other than this branch's one, we cannot do the swap.
3284		 This does not apply to the mips16, which uses variant
3285		 frags for different purposes.  */
3286	      || (! mips_opts.mips16
3287		  && prev_insn_frag_type == rs_machine_dependent)
3288	      /* Check for conflicts between the branch and the instructions
3289		 before the candidate delay slot.  */
3290	      || nops_for_insn (history + 1, ip) > 0
3291	      /* Check for conflicts between the swapped sequence and the
3292		 target of the branch.  */
3293	      || nops_for_sequence (2, history + 1, ip, history) > 0
3294	      /* We do not swap with a trap instruction, since it
3295		 complicates trap handlers to have the trap
3296		 instruction be in a delay slot.  */
3297	      || (prev_pinfo & INSN_TRAP)
3298	      /* If the branch reads a register that the previous
3299		 instruction sets, we can not swap.  */
3300	      || (! mips_opts.mips16
3301		  && (prev_pinfo & INSN_WRITE_GPR_T)
3302		  && insn_uses_reg (ip, EXTRACT_OPERAND (RT, history[0]),
3303				    MIPS_GR_REG))
3304	      || (! mips_opts.mips16
3305		  && (prev_pinfo & INSN_WRITE_GPR_D)
3306		  && insn_uses_reg (ip, EXTRACT_OPERAND (RD, history[0]),
3307				    MIPS_GR_REG))
3308	      || (mips_opts.mips16
3309		  && (((prev_pinfo & MIPS16_INSN_WRITE_X)
3310		       && (insn_uses_reg
3311			   (ip, MIPS16_EXTRACT_OPERAND (RX, history[0]),
3312			    MIPS16_REG)))
3313		      || ((prev_pinfo & MIPS16_INSN_WRITE_Y)
3314			  && (insn_uses_reg
3315			      (ip, MIPS16_EXTRACT_OPERAND (RY, history[0]),
3316			       MIPS16_REG)))
3317		      || ((prev_pinfo & MIPS16_INSN_WRITE_Z)
3318			  && (insn_uses_reg
3319			      (ip, MIPS16_EXTRACT_OPERAND (RZ, history[0]),
3320			       MIPS16_REG)))
3321		      || ((prev_pinfo & MIPS16_INSN_WRITE_T)
3322			  && insn_uses_reg (ip, TREG, MIPS_GR_REG))
3323		      || ((prev_pinfo & MIPS16_INSN_WRITE_31)
3324			  && insn_uses_reg (ip, RA, MIPS_GR_REG))
3325		      || ((prev_pinfo & MIPS16_INSN_WRITE_GPR_Y)
3326			  && insn_uses_reg (ip,
3327					    MIPS16OP_EXTRACT_REG32R
3328					      (history[0].insn_opcode),
3329					    MIPS_GR_REG))))
3330	      /* If the branch writes a register that the previous
3331		 instruction sets, we can not swap (we know that
3332		 branches write only to RD or to $31).  */
3333	      || (! mips_opts.mips16
3334		  && (prev_pinfo & INSN_WRITE_GPR_T)
3335		  && (((pinfo & INSN_WRITE_GPR_D)
3336		       && (EXTRACT_OPERAND (RT, history[0])
3337			   == EXTRACT_OPERAND (RD, *ip)))
3338		      || ((pinfo & INSN_WRITE_GPR_31)
3339			  && EXTRACT_OPERAND (RT, history[0]) == RA)))
3340	      || (! mips_opts.mips16
3341		  && (prev_pinfo & INSN_WRITE_GPR_D)
3342		  && (((pinfo & INSN_WRITE_GPR_D)
3343		       && (EXTRACT_OPERAND (RD, history[0])
3344			   == EXTRACT_OPERAND (RD, *ip)))
3345		      || ((pinfo & INSN_WRITE_GPR_31)
3346			  && EXTRACT_OPERAND (RD, history[0]) == RA)))
3347	      || (mips_opts.mips16
3348		  && (pinfo & MIPS16_INSN_WRITE_31)
3349		  && ((prev_pinfo & MIPS16_INSN_WRITE_31)
3350		      || ((prev_pinfo & MIPS16_INSN_WRITE_GPR_Y)
3351			  && (MIPS16OP_EXTRACT_REG32R (history[0].insn_opcode)
3352			      == RA))))
3353	      /* If the branch writes a register that the previous
3354		 instruction reads, we can not swap (we know that
3355		 branches only write to RD or to $31).  */
3356	      || (! mips_opts.mips16
3357		  && (pinfo & INSN_WRITE_GPR_D)
3358		  && insn_uses_reg (&history[0],
3359				    EXTRACT_OPERAND (RD, *ip),
3360				    MIPS_GR_REG))
3361	      || (! mips_opts.mips16
3362		  && (pinfo & INSN_WRITE_GPR_31)
3363		  && insn_uses_reg (&history[0], RA, MIPS_GR_REG))
3364	      || (mips_opts.mips16
3365		  && (pinfo & MIPS16_INSN_WRITE_31)
3366		  && insn_uses_reg (&history[0], RA, MIPS_GR_REG))
3367	      /* If one instruction sets a condition code and the
3368                 other one uses a condition code, we can not swap.  */
3369	      || ((pinfo & INSN_READ_COND_CODE)
3370		  && (prev_pinfo & INSN_WRITE_COND_CODE))
3371	      || ((pinfo & INSN_WRITE_COND_CODE)
3372		  && (prev_pinfo & INSN_READ_COND_CODE))
3373	      /* If the previous instruction uses the PC, we can not
3374                 swap.  */
3375	      || (mips_opts.mips16
3376		  && (prev_pinfo & MIPS16_INSN_READ_PC))
3377	      /* If the previous instruction had a fixup in mips16
3378                 mode, we can not swap.  This normally means that the
3379                 previous instruction was a 4 byte branch anyhow.  */
3380	      || (mips_opts.mips16 && history[0].fixp[0])
3381	      /* If the previous instruction is a sync, sync.l, or
3382		 sync.p, we can not swap.  */
3383	      || (prev_pinfo & INSN_SYNC)
3384	      /* If the previous instruction is an ERET or
3385		 DERET, avoid the swap.  */
3386              || (history[0].insn_opcode == INSN_ERET)
3387              || (history[0].insn_opcode == INSN_DERET))
3388	    {
3389	      if (mips_opts.mips16
3390		  && (pinfo & INSN_UNCOND_BRANCH_DELAY)
3391		  && (pinfo & (MIPS16_INSN_READ_X | MIPS16_INSN_READ_31))
3392		  && ISA_SUPPORTS_MIPS16E)
3393		{
3394		  /* Convert MIPS16 jr/jalr into a "compact" jump.  */
3395		  ip->insn_opcode |= 0x0080;
3396		  install_insn (ip);
3397		  insert_into_history (0, 1, ip);
3398		}
3399	      else
3400		{
3401		  /* We could do even better for unconditional branches to
3402		     portions of this object file; we could pick up the
3403		     instruction at the destination, put it in the delay
3404		     slot, and bump the destination address.  */
3405		  insert_into_history (0, 1, ip);
3406		  emit_nop ();
3407		}
3408
3409	      if (mips_relax.sequence)
3410		mips_relax.sizes[mips_relax.sequence - 1] += 4;
3411	    }
3412	  else
3413	    {
3414	      /* It looks like we can actually do the swap.  */
3415	      struct mips_cl_insn delay = history[0];
3416	      if (mips_opts.mips16)
3417		{
3418		  know (delay.frag == ip->frag);
3419                  move_insn (ip, delay.frag, delay.where);
3420		  move_insn (&delay, ip->frag, ip->where + insn_length (ip));
3421		}
3422	      else if (relaxed_branch)
3423		{
3424		  /* Add the delay slot instruction to the end of the
3425		     current frag and shrink the fixed part of the
3426		     original frag.  If the branch occupies the tail of
3427		     the latter, move it backwards to cover the gap.  */
3428		  delay.frag->fr_fix -= 4;
3429		  if (delay.frag == ip->frag)
3430		    move_insn (ip, ip->frag, ip->where - 4);
3431		  add_fixed_insn (&delay);
3432		}
3433	      else
3434		{
3435		  move_insn (&delay, ip->frag, ip->where);
3436		  move_insn (ip, history[0].frag, history[0].where);
3437		}
3438	      history[0] = *ip;
3439	      delay.fixed_p = 1;
3440	      insert_into_history (0, 1, &delay);
3441	    }
3442
3443	  /* If that was an unconditional branch, forget the previous
3444	     insn information.  */
3445	  if (pinfo & INSN_UNCOND_BRANCH_DELAY)
3446	    {
3447	      mips_no_prev_insn ();
3448	    }
3449	}
3450      else if (pinfo & INSN_COND_BRANCH_LIKELY)
3451	{
3452	  /* We don't yet optimize a branch likely.  What we should do
3453	     is look at the target, copy the instruction found there
3454	     into the delay slot, and increment the branch to jump to
3455	     the next instruction.  */
3456	  insert_into_history (0, 1, ip);
3457	  emit_nop ();
3458	}
3459      else
3460	insert_into_history (0, 1, ip);
3461    }
3462  else
3463    insert_into_history (0, 1, ip);
3464
3465  /* We just output an insn, so the next one doesn't have a label.  */
3466  mips_clear_insn_labels ();
3467}
3468
3469/* Forget that there was any previous instruction or label.  */
3470
3471static void
3472mips_no_prev_insn (void)
3473{
3474  prev_nop_frag = NULL;
3475  insert_into_history (0, ARRAY_SIZE (history), NOP_INSN);
3476  mips_clear_insn_labels ();
3477}
3478
3479/* This function must be called before we emit something other than
3480   instructions.  It is like mips_no_prev_insn except that it inserts
3481   any NOPS that might be needed by previous instructions.  */
3482
3483void
3484mips_emit_delays (void)
3485{
3486  if (! mips_opts.noreorder)
3487    {
3488      int nops = nops_for_insn (history, NULL);
3489      if (nops > 0)
3490	{
3491	  while (nops-- > 0)
3492	    add_fixed_insn (NOP_INSN);
3493	  mips_move_labels ();
3494	}
3495    }
3496  mips_no_prev_insn ();
3497}
3498
3499/* Start a (possibly nested) noreorder block.  */
3500
3501static void
3502start_noreorder (void)
3503{
3504  if (mips_opts.noreorder == 0)
3505    {
3506      unsigned int i;
3507      int nops;
3508
3509      /* None of the instructions before the .set noreorder can be moved.  */
3510      for (i = 0; i < ARRAY_SIZE (history); i++)
3511	history[i].fixed_p = 1;
3512
3513      /* Insert any nops that might be needed between the .set noreorder
3514	 block and the previous instructions.  We will later remove any
3515	 nops that turn out not to be needed.  */
3516      nops = nops_for_insn (history, NULL);
3517      if (nops > 0)
3518	{
3519	  if (mips_optimize != 0)
3520	    {
3521	      /* Record the frag which holds the nop instructions, so
3522                 that we can remove them if we don't need them.  */
3523	      frag_grow (mips_opts.mips16 ? nops * 2 : nops * 4);
3524	      prev_nop_frag = frag_now;
3525	      prev_nop_frag_holds = nops;
3526	      prev_nop_frag_required = 0;
3527	      prev_nop_frag_since = 0;
3528	    }
3529
3530	  for (; nops > 0; --nops)
3531	    add_fixed_insn (NOP_INSN);
3532
3533	  /* Move on to a new frag, so that it is safe to simply
3534	     decrease the size of prev_nop_frag.  */
3535	  frag_wane (frag_now);
3536	  frag_new (0);
3537	  mips_move_labels ();
3538	}
3539      mips16_mark_labels ();
3540      mips_clear_insn_labels ();
3541    }
3542  mips_opts.noreorder++;
3543  mips_any_noreorder = 1;
3544}
3545
3546/* End a nested noreorder block.  */
3547
3548static void
3549end_noreorder (void)
3550{
3551
3552  mips_opts.noreorder--;
3553  if (mips_opts.noreorder == 0 && prev_nop_frag != NULL)
3554    {
3555      /* Commit to inserting prev_nop_frag_required nops and go back to
3556	 handling nop insertion the .set reorder way.  */
3557      prev_nop_frag->fr_fix -= ((prev_nop_frag_holds - prev_nop_frag_required)
3558				* (mips_opts.mips16 ? 2 : 4));
3559      insert_into_history (prev_nop_frag_since,
3560			   prev_nop_frag_required, NOP_INSN);
3561      prev_nop_frag = NULL;
3562    }
3563}
3564
3565/* Set up global variables for the start of a new macro.  */
3566
3567static void
3568macro_start (void)
3569{
3570  memset (&mips_macro_warning.sizes, 0, sizeof (mips_macro_warning.sizes));
3571  mips_macro_warning.delay_slot_p = (mips_opts.noreorder
3572				     && (history[0].insn_mo->pinfo
3573					 & (INSN_UNCOND_BRANCH_DELAY
3574					    | INSN_COND_BRANCH_DELAY
3575					    | INSN_COND_BRANCH_LIKELY)) != 0);
3576}
3577
3578/* Given that a macro is longer than 4 bytes, return the appropriate warning
3579   for it.  Return null if no warning is needed.  SUBTYPE is a bitmask of
3580   RELAX_DELAY_SLOT and RELAX_NOMACRO.  */
3581
3582static const char *
3583macro_warning (relax_substateT subtype)
3584{
3585  if (subtype & RELAX_DELAY_SLOT)
3586    return _("Macro instruction expanded into multiple instructions"
3587	     " in a branch delay slot");
3588  else if (subtype & RELAX_NOMACRO)
3589    return _("Macro instruction expanded into multiple instructions");
3590  else
3591    return 0;
3592}
3593
3594/* Finish up a macro.  Emit warnings as appropriate.  */
3595
3596static void
3597macro_end (void)
3598{
3599  if (mips_macro_warning.sizes[0] > 4 || mips_macro_warning.sizes[1] > 4)
3600    {
3601      relax_substateT subtype;
3602
3603      /* Set up the relaxation warning flags.  */
3604      subtype = 0;
3605      if (mips_macro_warning.sizes[1] > mips_macro_warning.sizes[0])
3606	subtype |= RELAX_SECOND_LONGER;
3607      if (mips_opts.warn_about_macros)
3608	subtype |= RELAX_NOMACRO;
3609      if (mips_macro_warning.delay_slot_p)
3610	subtype |= RELAX_DELAY_SLOT;
3611
3612      if (mips_macro_warning.sizes[0] > 4 && mips_macro_warning.sizes[1] > 4)
3613	{
3614	  /* Either the macro has a single implementation or both
3615	     implementations are longer than 4 bytes.  Emit the
3616	     warning now.  */
3617	  const char *msg = macro_warning (subtype);
3618	  if (msg != 0)
3619	    as_warn ("%s", msg);
3620	}
3621      else
3622	{
3623	  /* One implementation might need a warning but the other
3624	     definitely doesn't.  */
3625	  mips_macro_warning.first_frag->fr_subtype |= subtype;
3626	}
3627    }
3628}
3629
3630/* Read a macro's relocation codes from *ARGS and store them in *R.
3631   The first argument in *ARGS will be either the code for a single
3632   relocation or -1 followed by the three codes that make up a
3633   composite relocation.  */
3634
3635static void
3636macro_read_relocs (va_list *args, bfd_reloc_code_real_type *r)
3637{
3638  int i, next;
3639
3640  next = va_arg (*args, int);
3641  if (next >= 0)
3642    r[0] = (bfd_reloc_code_real_type) next;
3643  else
3644    for (i = 0; i < 3; i++)
3645      r[i] = (bfd_reloc_code_real_type) va_arg (*args, int);
3646}
3647
3648/* Fix jump through register issue on loongson2f processor for kernel code:
3649   force a BTB clear before the jump to prevent it from being incorrectly
3650   prefetched by the branch prediction engine. */
3651
3652static void
3653macro_build_jrpatch (expressionS *ep, unsigned int sreg)
3654{
3655  if (!mips_fix_loongson2f_btb)
3656    return;
3657
3658  if (sreg == ZERO || sreg == KT0 || sreg == KT1 || sreg == AT)
3659    return;
3660
3661  if (!mips_opts.at)
3662    {
3663      as_warn (_("unable to apply loongson2f BTB workaround when .set noat"));
3664      return;
3665    }
3666
3667  /* li $at, COP_0_BTB_CLEAR | COP_0_RAS_DISABLE */
3668  ep->X_op = O_constant;
3669  ep->X_add_number = 3;
3670  macro_build (ep, "ori", "t,r,i", AT, ZERO, BFD_RELOC_LO16);
3671
3672  /* dmtc0 $at, COP_0_DIAG */
3673  macro_build (NULL, "dmtc0", "t,G", AT, 22);
3674
3675  /* Hide these two instructions to avoid getting a ``macro expanded into
3676     multiple instructions'' warning. */
3677  if (mips_relax.sequence != 2)
3678    mips_macro_warning.sizes[0] -= 2 * 4;
3679  if (mips_relax.sequence != 1)
3680    mips_macro_warning.sizes[1] -= 2 * 4;
3681}
3682
3683/* Build an instruction created by a macro expansion.  This is passed
3684   a pointer to the count of instructions created so far, an
3685   expression, the name of the instruction to build, an operand format
3686   string, and corresponding arguments.  */
3687
3688static void
3689macro_build (expressionS *ep, const char *name, const char *fmt, ...)
3690{
3691  const struct mips_opcode *mo;
3692  struct mips_cl_insn insn;
3693  bfd_reloc_code_real_type r[3];
3694  va_list args;
3695
3696  va_start (args, fmt);
3697
3698  if (mips_opts.mips16)
3699    {
3700      mips16_macro_build (ep, name, fmt, &args);
3701      va_end (args);
3702      return;
3703    }
3704
3705  r[0] = BFD_RELOC_UNUSED;
3706  r[1] = BFD_RELOC_UNUSED;
3707  r[2] = BFD_RELOC_UNUSED;
3708  mo = (struct mips_opcode *) hash_find (op_hash, name);
3709  gas_assert (mo);
3710  gas_assert (strcmp (name, mo->name) == 0);
3711
3712  while (1)
3713    {
3714      /* Search until we get a match for NAME.  It is assumed here that
3715	 macros will never generate MDMX, MIPS-3D, or MT instructions.  */
3716      if (strcmp (fmt, mo->args) == 0
3717	  && mo->pinfo != INSN_MACRO
3718	  && is_opcode_valid (mo))
3719	break;
3720
3721      ++mo;
3722      gas_assert (mo->name);
3723      gas_assert (strcmp (name, mo->name) == 0);
3724    }
3725
3726  create_insn (&insn, mo);
3727  for (;;)
3728    {
3729      switch (*fmt++)
3730	{
3731	case '\0':
3732	  break;
3733
3734	case ',':
3735	case '(':
3736	case ')':
3737	  continue;
3738
3739	case '+':
3740	  switch (*fmt++)
3741	    {
3742	    case 'A':
3743	    case 'E':
3744	      INSERT_OPERAND (SHAMT, insn, va_arg (args, int));
3745	      continue;
3746
3747	    case 'B':
3748	    case 'F':
3749	      /* Note that in the macro case, these arguments are already
3750		 in MSB form.  (When handling the instruction in the
3751		 non-macro case, these arguments are sizes from which
3752		 MSB values must be calculated.)  */
3753	      INSERT_OPERAND (INSMSB, insn, va_arg (args, int));
3754	      continue;
3755
3756	    case 'C':
3757	    case 'G':
3758	    case 'H':
3759	      /* Note that in the macro case, these arguments are already
3760		 in MSBD form.  (When handling the instruction in the
3761		 non-macro case, these arguments are sizes from which
3762		 MSBD values must be calculated.)  */
3763	      INSERT_OPERAND (EXTMSBD, insn, va_arg (args, int));
3764	      continue;
3765
3766	    case 'Q':
3767	      INSERT_OPERAND (SEQI, insn, va_arg (args, int));
3768	      continue;
3769
3770	    default:
3771	      internalError ();
3772	    }
3773	  continue;
3774
3775	case '2':
3776	  INSERT_OPERAND (BP, insn, va_arg (args, int));
3777	  continue;
3778
3779	case 't':
3780	case 'w':
3781	case 'E':
3782	  INSERT_OPERAND (RT, insn, va_arg (args, int));
3783	  continue;
3784
3785	case 'c':
3786	  INSERT_OPERAND (CODE, insn, va_arg (args, int));
3787	  continue;
3788
3789	case 'T':
3790	case 'W':
3791	  INSERT_OPERAND (FT, insn, va_arg (args, int));
3792	  continue;
3793
3794	case 'd':
3795	case 'G':
3796	case 'K':
3797	  INSERT_OPERAND (RD, insn, va_arg (args, int));
3798	  continue;
3799
3800	case 'U':
3801	  {
3802	    int tmp = va_arg (args, int);
3803
3804	    INSERT_OPERAND (RT, insn, tmp);
3805	    INSERT_OPERAND (RD, insn, tmp);
3806	    continue;
3807	  }
3808
3809	case 'V':
3810	case 'S':
3811	  INSERT_OPERAND (FS, insn, va_arg (args, int));
3812	  continue;
3813
3814	case 'z':
3815	  continue;
3816
3817	case '<':
3818	  INSERT_OPERAND (SHAMT, insn, va_arg (args, int));
3819	  continue;
3820
3821	case 'D':
3822	  INSERT_OPERAND (FD, insn, va_arg (args, int));
3823	  continue;
3824
3825	case 'B':
3826	  INSERT_OPERAND (CODE20, insn, va_arg (args, int));
3827	  continue;
3828
3829	case 'J':
3830	  INSERT_OPERAND (CODE19, insn, va_arg (args, int));
3831	  continue;
3832
3833	case 'q':
3834	  INSERT_OPERAND (CODE2, insn, va_arg (args, int));
3835	  continue;
3836
3837	case 'b':
3838	case 's':
3839	case 'r':
3840	case 'v':
3841	  INSERT_OPERAND (RS, insn, va_arg (args, int));
3842	  continue;
3843
3844	case 'i':
3845	case 'j':
3846	  macro_read_relocs (&args, r);
3847	  gas_assert (*r == BFD_RELOC_GPREL16
3848		      || *r == BFD_RELOC_MIPS_HIGHER
3849		      || *r == BFD_RELOC_HI16_S
3850		      || *r == BFD_RELOC_LO16
3851		      || *r == BFD_RELOC_MIPS_GOT_OFST);
3852	  continue;
3853
3854	case 'o':
3855	  macro_read_relocs (&args, r);
3856	  continue;
3857
3858	case 'u':
3859	  macro_read_relocs (&args, r);
3860	  gas_assert (ep != NULL
3861		  && (ep->X_op == O_constant
3862		      || (ep->X_op == O_symbol
3863			  && (*r == BFD_RELOC_MIPS_HIGHEST
3864			      || *r == BFD_RELOC_HI16_S
3865			      || *r == BFD_RELOC_HI16
3866			      || *r == BFD_RELOC_GPREL16
3867			      || *r == BFD_RELOC_MIPS_GOT_HI16
3868			      || *r == BFD_RELOC_MIPS_CALL_HI16))));
3869	  continue;
3870
3871	case 'p':
3872	  gas_assert (ep != NULL);
3873
3874	  /*
3875	   * This allows macro() to pass an immediate expression for
3876	   * creating short branches without creating a symbol.
3877	   *
3878	   * We don't allow branch relaxation for these branches, as
3879	   * they should only appear in ".set nomacro" anyway.
3880	   */
3881	  if (ep->X_op == O_constant)
3882	    {
3883	      if ((ep->X_add_number & 3) != 0)
3884		as_bad (_("branch to misaligned address (0x%lx)"),
3885			(unsigned long) ep->X_add_number);
3886	      if ((ep->X_add_number + 0x20000) & ~0x3ffff)
3887		as_bad (_("branch address range overflow (0x%lx)"),
3888			(unsigned long) ep->X_add_number);
3889	      insn.insn_opcode |= (ep->X_add_number >> 2) & 0xffff;
3890	      ep = NULL;
3891	    }
3892	  else
3893	    *r = BFD_RELOC_16_PCREL_S2;
3894	  continue;
3895
3896	case 'a':
3897	  gas_assert (ep != NULL);
3898	  *r = BFD_RELOC_MIPS_JMP;
3899	  continue;
3900
3901	case 'C':
3902	  INSERT_OPERAND (COPZ, insn, va_arg (args, unsigned long));
3903	  continue;
3904
3905	case 'k':
3906	  INSERT_OPERAND (CACHE, insn, va_arg (args, unsigned long));
3907	  continue;
3908
3909	default:
3910	  internalError ();
3911	}
3912      break;
3913    }
3914  va_end (args);
3915  gas_assert (*r == BFD_RELOC_UNUSED ? ep == NULL : ep != NULL);
3916
3917  append_insn (&insn, ep, r);
3918}
3919
3920static void
3921mips16_macro_build (expressionS *ep, const char *name, const char *fmt,
3922		    va_list *args)
3923{
3924  struct mips_opcode *mo;
3925  struct mips_cl_insn insn;
3926  bfd_reloc_code_real_type r[3]
3927    = {BFD_RELOC_UNUSED, BFD_RELOC_UNUSED, BFD_RELOC_UNUSED};
3928
3929  mo = (struct mips_opcode *) hash_find (mips16_op_hash, name);
3930  gas_assert (mo);
3931  gas_assert (strcmp (name, mo->name) == 0);
3932
3933  while (strcmp (fmt, mo->args) != 0 || mo->pinfo == INSN_MACRO)
3934    {
3935      ++mo;
3936      gas_assert (mo->name);
3937      gas_assert (strcmp (name, mo->name) == 0);
3938    }
3939
3940  create_insn (&insn, mo);
3941  for (;;)
3942    {
3943      int c;
3944
3945      c = *fmt++;
3946      switch (c)
3947	{
3948	case '\0':
3949	  break;
3950
3951	case ',':
3952	case '(':
3953	case ')':
3954	  continue;
3955
3956	case 'y':
3957	case 'w':
3958	  MIPS16_INSERT_OPERAND (RY, insn, va_arg (*args, int));
3959	  continue;
3960
3961	case 'x':
3962	case 'v':
3963	  MIPS16_INSERT_OPERAND (RX, insn, va_arg (*args, int));
3964	  continue;
3965
3966	case 'z':
3967	  MIPS16_INSERT_OPERAND (RZ, insn, va_arg (*args, int));
3968	  continue;
3969
3970	case 'Z':
3971	  MIPS16_INSERT_OPERAND (MOVE32Z, insn, va_arg (*args, int));
3972	  continue;
3973
3974	case '0':
3975	case 'S':
3976	case 'P':
3977	case 'R':
3978	  continue;
3979
3980	case 'X':
3981	  MIPS16_INSERT_OPERAND (REGR32, insn, va_arg (*args, int));
3982	  continue;
3983
3984	case 'Y':
3985	  {
3986	    int regno;
3987
3988	    regno = va_arg (*args, int);
3989	    regno = ((regno & 7) << 2) | ((regno & 0x18) >> 3);
3990	    MIPS16_INSERT_OPERAND (REG32R, insn, regno);
3991	  }
3992	  continue;
3993
3994	case '<':
3995	case '>':
3996	case '4':
3997	case '5':
3998	case 'H':
3999	case 'W':
4000	case 'D':
4001	case 'j':
4002	case '8':
4003	case 'V':
4004	case 'C':
4005	case 'U':
4006	case 'k':
4007	case 'K':
4008	case 'p':
4009	case 'q':
4010	  {
4011	    gas_assert (ep != NULL);
4012
4013	    if (ep->X_op != O_constant)
4014	      *r = (int) BFD_RELOC_UNUSED + c;
4015	    else
4016	      {
4017		mips16_immed (NULL, 0, c, ep->X_add_number, FALSE, FALSE,
4018			      FALSE, &insn.insn_opcode, &insn.use_extend,
4019			      &insn.extend);
4020		ep = NULL;
4021		*r = BFD_RELOC_UNUSED;
4022	      }
4023	  }
4024	  continue;
4025
4026	case '6':
4027	  MIPS16_INSERT_OPERAND (IMM6, insn, va_arg (*args, int));
4028	  continue;
4029	}
4030
4031      break;
4032    }
4033
4034  gas_assert (*r == BFD_RELOC_UNUSED ? ep == NULL : ep != NULL);
4035
4036  append_insn (&insn, ep, r);
4037}
4038
4039/*
4040 * Sign-extend 32-bit mode constants that have bit 31 set and all
4041 * higher bits unset.
4042 */
4043static void
4044normalize_constant_expr (expressionS *ex)
4045{
4046  if (ex->X_op == O_constant
4047      && IS_ZEXT_32BIT_NUM (ex->X_add_number))
4048    ex->X_add_number = (((ex->X_add_number & 0xffffffff) ^ 0x80000000)
4049			- 0x80000000);
4050}
4051
4052/*
4053 * Sign-extend 32-bit mode address offsets that have bit 31 set and
4054 * all higher bits unset.
4055 */
4056static void
4057normalize_address_expr (expressionS *ex)
4058{
4059  if (((ex->X_op == O_constant && HAVE_32BIT_ADDRESSES)
4060	|| (ex->X_op == O_symbol && HAVE_32BIT_SYMBOLS))
4061      && IS_ZEXT_32BIT_NUM (ex->X_add_number))
4062    ex->X_add_number = (((ex->X_add_number & 0xffffffff) ^ 0x80000000)
4063			- 0x80000000);
4064}
4065
4066/*
4067 * Generate a "jalr" instruction with a relocation hint to the called
4068 * function.  This occurs in NewABI PIC code.
4069 */
4070static void
4071macro_build_jalr (expressionS *ep)
4072{
4073  char *f = NULL;
4074
4075  if (MIPS_JALR_HINT_P (ep))
4076    {
4077      frag_grow (8);
4078      f = frag_more (0);
4079    }
4080  macro_build_jrpatch (ep, PIC_CALL_REG);
4081  macro_build (NULL, "jalr", "d,s", RA, PIC_CALL_REG);
4082  if (MIPS_JALR_HINT_P (ep))
4083    fix_new_exp (frag_now, f - frag_now->fr_literal,
4084		 4, ep, FALSE, BFD_RELOC_MIPS_JALR);
4085}
4086
4087/*
4088 * Generate a "lui" instruction.
4089 */
4090static void
4091macro_build_lui (expressionS *ep, int regnum)
4092{
4093  expressionS high_expr;
4094  const struct mips_opcode *mo;
4095  struct mips_cl_insn insn;
4096  bfd_reloc_code_real_type r[3]
4097    = {BFD_RELOC_UNUSED, BFD_RELOC_UNUSED, BFD_RELOC_UNUSED};
4098  const char *name = "lui";
4099  const char *fmt = "t,u";
4100
4101  gas_assert (! mips_opts.mips16);
4102
4103  high_expr = *ep;
4104
4105  if (high_expr.X_op == O_constant)
4106    {
4107      /* We can compute the instruction now without a relocation entry.  */
4108      high_expr.X_add_number = ((high_expr.X_add_number + 0x8000)
4109				>> 16) & 0xffff;
4110      *r = BFD_RELOC_UNUSED;
4111    }
4112  else
4113    {
4114      gas_assert (ep->X_op == O_symbol);
4115      /* _gp_disp is a special case, used from s_cpload.
4116	 __gnu_local_gp is used if mips_no_shared.  */
4117      gas_assert (mips_pic == NO_PIC
4118	      || (! HAVE_NEWABI
4119		  && strcmp (S_GET_NAME (ep->X_add_symbol), "_gp_disp") == 0)
4120	      || (! mips_in_shared
4121		  && strcmp (S_GET_NAME (ep->X_add_symbol),
4122                             "__gnu_local_gp") == 0));
4123      *r = BFD_RELOC_HI16_S;
4124    }
4125
4126  mo = hash_find (op_hash, name);
4127  gas_assert (strcmp (name, mo->name) == 0);
4128  gas_assert (strcmp (fmt, mo->args) == 0);
4129  create_insn (&insn, mo);
4130
4131  insn.insn_opcode = insn.insn_mo->match;
4132  INSERT_OPERAND (RT, insn, regnum);
4133  if (*r == BFD_RELOC_UNUSED)
4134    {
4135      insn.insn_opcode |= high_expr.X_add_number;
4136      append_insn (&insn, NULL, r);
4137    }
4138  else
4139    append_insn (&insn, &high_expr, r);
4140}
4141
4142/* Generate a sequence of instructions to do a load or store from a constant
4143   offset off of a base register (breg) into/from a target register (treg),
4144   using AT if necessary.  */
4145static void
4146macro_build_ldst_constoffset (expressionS *ep, const char *op,
4147			      int treg, int breg, int dbl)
4148{
4149  gas_assert (ep->X_op == O_constant);
4150
4151  /* Sign-extending 32-bit constants makes their handling easier.  */
4152  if (!dbl)
4153    normalize_constant_expr (ep);
4154
4155  /* Right now, this routine can only handle signed 32-bit constants.  */
4156  if (! IS_SEXT_32BIT_NUM(ep->X_add_number + 0x8000))
4157    as_warn (_("operand overflow"));
4158
4159  if (IS_SEXT_16BIT_NUM(ep->X_add_number))
4160    {
4161      /* Signed 16-bit offset will fit in the op.  Easy!  */
4162      macro_build (ep, op, "t,o(b)", treg, BFD_RELOC_LO16, breg);
4163    }
4164  else
4165    {
4166      /* 32-bit offset, need multiple instructions and AT, like:
4167	   lui      $tempreg,const_hi       (BFD_RELOC_HI16_S)
4168	   addu     $tempreg,$tempreg,$breg
4169           <op>     $treg,const_lo($tempreg)   (BFD_RELOC_LO16)
4170         to handle the complete offset.  */
4171      macro_build_lui (ep, AT);
4172      macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", AT, AT, breg);
4173      macro_build (ep, op, "t,o(b)", treg, BFD_RELOC_LO16, AT);
4174
4175      if (!mips_opts.at)
4176	as_bad (_("Macro used $at after \".set noat\""));
4177    }
4178}
4179
4180/*			set_at()
4181 * Generates code to set the $at register to true (one)
4182 * if reg is less than the immediate expression.
4183 */
4184static void
4185set_at (int reg, int unsignedp)
4186{
4187  if (imm_expr.X_op == O_constant
4188      && imm_expr.X_add_number >= -0x8000
4189      && imm_expr.X_add_number < 0x8000)
4190    macro_build (&imm_expr, unsignedp ? "sltiu" : "slti", "t,r,j",
4191		 AT, reg, BFD_RELOC_LO16);
4192  else
4193    {
4194      load_register (AT, &imm_expr, HAVE_64BIT_GPRS);
4195      macro_build (NULL, unsignedp ? "sltu" : "slt", "d,v,t", AT, reg, AT);
4196    }
4197}
4198
4199/* Warn if an expression is not a constant.  */
4200
4201static void
4202check_absolute_expr (struct mips_cl_insn *ip, expressionS *ex)
4203{
4204  if (ex->X_op == O_big)
4205    as_bad (_("unsupported large constant"));
4206  else if (ex->X_op != O_constant)
4207    as_bad (_("Instruction %s requires absolute expression"),
4208	    ip->insn_mo->name);
4209
4210  if (HAVE_32BIT_GPRS)
4211    normalize_constant_expr (ex);
4212}
4213
4214/* Count the leading zeroes by performing a binary chop. This is a
4215   bulky bit of source, but performance is a LOT better for the
4216   majority of values than a simple loop to count the bits:
4217       for (lcnt = 0; (lcnt < 32); lcnt++)
4218         if ((v) & (1 << (31 - lcnt)))
4219           break;
4220  However it is not code size friendly, and the gain will drop a bit
4221  on certain cached systems.
4222*/
4223#define COUNT_TOP_ZEROES(v)             \
4224  (((v) & ~0xffff) == 0                 \
4225   ? ((v) & ~0xff) == 0                 \
4226     ? ((v) & ~0xf) == 0                \
4227       ? ((v) & ~0x3) == 0              \
4228         ? ((v) & ~0x1) == 0            \
4229           ? !(v)                       \
4230             ? 32                       \
4231             : 31                       \
4232           : 30                         \
4233         : ((v) & ~0x7) == 0            \
4234           ? 29                         \
4235           : 28                         \
4236       : ((v) & ~0x3f) == 0             \
4237         ? ((v) & ~0x1f) == 0           \
4238           ? 27                         \
4239           : 26                         \
4240         : ((v) & ~0x7f) == 0           \
4241           ? 25                         \
4242           : 24                         \
4243     : ((v) & ~0xfff) == 0              \
4244       ? ((v) & ~0x3ff) == 0            \
4245         ? ((v) & ~0x1ff) == 0          \
4246           ? 23                         \
4247           : 22                         \
4248         : ((v) & ~0x7ff) == 0          \
4249           ? 21                         \
4250           : 20                         \
4251       : ((v) & ~0x3fff) == 0           \
4252         ? ((v) & ~0x1fff) == 0         \
4253           ? 19                         \
4254           : 18                         \
4255         : ((v) & ~0x7fff) == 0         \
4256           ? 17                         \
4257           : 16                         \
4258   : ((v) & ~0xffffff) == 0             \
4259     ? ((v) & ~0xfffff) == 0            \
4260       ? ((v) & ~0x3ffff) == 0          \
4261         ? ((v) & ~0x1ffff) == 0        \
4262           ? 15                         \
4263           : 14                         \
4264         : ((v) & ~0x7ffff) == 0        \
4265           ? 13                         \
4266           : 12                         \
4267       : ((v) & ~0x3fffff) == 0         \
4268         ? ((v) & ~0x1fffff) == 0       \
4269           ? 11                         \
4270           : 10                         \
4271         : ((v) & ~0x7fffff) == 0       \
4272           ? 9                          \
4273           : 8                          \
4274     : ((v) & ~0xfffffff) == 0          \
4275       ? ((v) & ~0x3ffffff) == 0        \
4276         ? ((v) & ~0x1ffffff) == 0      \
4277           ? 7                          \
4278           : 6                          \
4279         : ((v) & ~0x7ffffff) == 0      \
4280           ? 5                          \
4281           : 4                          \
4282       : ((v) & ~0x3fffffff) == 0       \
4283         ? ((v) & ~0x1fffffff) == 0     \
4284           ? 3                          \
4285           : 2                          \
4286         : ((v) & ~0x7fffffff) == 0     \
4287           ? 1                          \
4288           : 0)
4289
4290/*			load_register()
4291 *  This routine generates the least number of instructions necessary to load
4292 *  an absolute expression value into a register.
4293 */
4294static void
4295load_register (int reg, expressionS *ep, int dbl)
4296{
4297  int freg;
4298  expressionS hi32, lo32;
4299
4300  if (ep->X_op != O_big)
4301    {
4302      gas_assert (ep->X_op == O_constant);
4303
4304      /* Sign-extending 32-bit constants makes their handling easier.  */
4305      if (!dbl)
4306	normalize_constant_expr (ep);
4307
4308      if (IS_SEXT_16BIT_NUM (ep->X_add_number))
4309	{
4310	  /* We can handle 16 bit signed values with an addiu to
4311	     $zero.  No need to ever use daddiu here, since $zero and
4312	     the result are always correct in 32 bit mode.  */
4313	  macro_build (ep, "addiu", "t,r,j", reg, 0, BFD_RELOC_LO16);
4314	  return;
4315	}
4316      else if (ep->X_add_number >= 0 && ep->X_add_number < 0x10000)
4317	{
4318	  /* We can handle 16 bit unsigned values with an ori to
4319             $zero.  */
4320	  macro_build (ep, "ori", "t,r,i", reg, 0, BFD_RELOC_LO16);
4321	  return;
4322	}
4323      else if ((IS_SEXT_32BIT_NUM (ep->X_add_number)))
4324	{
4325	  /* 32 bit values require an lui.  */
4326	  macro_build (ep, "lui", "t,u", reg, BFD_RELOC_HI16);
4327	  if ((ep->X_add_number & 0xffff) != 0)
4328	    macro_build (ep, "ori", "t,r,i", reg, reg, BFD_RELOC_LO16);
4329	  return;
4330	}
4331    }
4332
4333  /* The value is larger than 32 bits.  */
4334
4335  if (!dbl || HAVE_32BIT_GPRS)
4336    {
4337      char value[32];
4338
4339      sprintf_vma (value, ep->X_add_number);
4340      as_bad (_("Number (0x%s) larger than 32 bits"), value);
4341      macro_build (ep, "addiu", "t,r,j", reg, 0, BFD_RELOC_LO16);
4342      return;
4343    }
4344
4345  if (ep->X_op != O_big)
4346    {
4347      hi32 = *ep;
4348      hi32.X_add_number = (valueT) hi32.X_add_number >> 16;
4349      hi32.X_add_number = (valueT) hi32.X_add_number >> 16;
4350      hi32.X_add_number &= 0xffffffff;
4351      lo32 = *ep;
4352      lo32.X_add_number &= 0xffffffff;
4353    }
4354  else
4355    {
4356      gas_assert (ep->X_add_number > 2);
4357      if (ep->X_add_number == 3)
4358	generic_bignum[3] = 0;
4359      else if (ep->X_add_number > 4)
4360	as_bad (_("Number larger than 64 bits"));
4361      lo32.X_op = O_constant;
4362      lo32.X_add_number = generic_bignum[0] + (generic_bignum[1] << 16);
4363      hi32.X_op = O_constant;
4364      hi32.X_add_number = generic_bignum[2] + (generic_bignum[3] << 16);
4365    }
4366
4367  if (hi32.X_add_number == 0)
4368    freg = 0;
4369  else
4370    {
4371      int shift, bit;
4372      unsigned long hi, lo;
4373
4374      if (hi32.X_add_number == (offsetT) 0xffffffff)
4375	{
4376	  if ((lo32.X_add_number & 0xffff8000) == 0xffff8000)
4377	    {
4378	      macro_build (&lo32, "addiu", "t,r,j", reg, 0, BFD_RELOC_LO16);
4379	      return;
4380	    }
4381	  if (lo32.X_add_number & 0x80000000)
4382	    {
4383	      macro_build (&lo32, "lui", "t,u", reg, BFD_RELOC_HI16);
4384	      if (lo32.X_add_number & 0xffff)
4385		macro_build (&lo32, "ori", "t,r,i", reg, reg, BFD_RELOC_LO16);
4386	      return;
4387	    }
4388	}
4389
4390      /* Check for 16bit shifted constant.  We know that hi32 is
4391         non-zero, so start the mask on the first bit of the hi32
4392         value.  */
4393      shift = 17;
4394      do
4395	{
4396	  unsigned long himask, lomask;
4397
4398	  if (shift < 32)
4399	    {
4400	      himask = 0xffff >> (32 - shift);
4401	      lomask = (0xffff << shift) & 0xffffffff;
4402	    }
4403	  else
4404	    {
4405	      himask = 0xffff << (shift - 32);
4406	      lomask = 0;
4407	    }
4408	  if ((hi32.X_add_number & ~(offsetT) himask) == 0
4409	      && (lo32.X_add_number & ~(offsetT) lomask) == 0)
4410	    {
4411	      expressionS tmp;
4412
4413	      tmp.X_op = O_constant;
4414	      if (shift < 32)
4415		tmp.X_add_number = ((hi32.X_add_number << (32 - shift))
4416				    | (lo32.X_add_number >> shift));
4417	      else
4418		tmp.X_add_number = hi32.X_add_number >> (shift - 32);
4419	      macro_build (&tmp, "ori", "t,r,i", reg, 0, BFD_RELOC_LO16);
4420	      macro_build (NULL, (shift >= 32) ? "dsll32" : "dsll", "d,w,<",
4421			   reg, reg, (shift >= 32) ? shift - 32 : shift);
4422	      return;
4423	    }
4424	  ++shift;
4425	}
4426      while (shift <= (64 - 16));
4427
4428      /* Find the bit number of the lowest one bit, and store the
4429         shifted value in hi/lo.  */
4430      hi = (unsigned long) (hi32.X_add_number & 0xffffffff);
4431      lo = (unsigned long) (lo32.X_add_number & 0xffffffff);
4432      if (lo != 0)
4433	{
4434	  bit = 0;
4435	  while ((lo & 1) == 0)
4436	    {
4437	      lo >>= 1;
4438	      ++bit;
4439	    }
4440	  lo |= (hi & (((unsigned long) 1 << bit) - 1)) << (32 - bit);
4441	  hi >>= bit;
4442	}
4443      else
4444	{
4445	  bit = 32;
4446	  while ((hi & 1) == 0)
4447	    {
4448	      hi >>= 1;
4449	      ++bit;
4450	    }
4451	  lo = hi;
4452	  hi = 0;
4453	}
4454
4455      /* Optimize if the shifted value is a (power of 2) - 1.  */
4456      if ((hi == 0 && ((lo + 1) & lo) == 0)
4457	  || (lo == 0xffffffff && ((hi + 1) & hi) == 0))
4458	{
4459	  shift = COUNT_TOP_ZEROES ((unsigned int) hi32.X_add_number);
4460	  if (shift != 0)
4461	    {
4462	      expressionS tmp;
4463
4464	      /* This instruction will set the register to be all
4465                 ones.  */
4466	      tmp.X_op = O_constant;
4467	      tmp.X_add_number = (offsetT) -1;
4468	      macro_build (&tmp, "addiu", "t,r,j", reg, 0, BFD_RELOC_LO16);
4469	      if (bit != 0)
4470		{
4471		  bit += shift;
4472		  macro_build (NULL, (bit >= 32) ? "dsll32" : "dsll", "d,w,<",
4473			       reg, reg, (bit >= 32) ? bit - 32 : bit);
4474		}
4475	      macro_build (NULL, (shift >= 32) ? "dsrl32" : "dsrl", "d,w,<",
4476			   reg, reg, (shift >= 32) ? shift - 32 : shift);
4477	      return;
4478	    }
4479	}
4480
4481      /* Sign extend hi32 before calling load_register, because we can
4482         generally get better code when we load a sign extended value.  */
4483      if ((hi32.X_add_number & 0x80000000) != 0)
4484	hi32.X_add_number |= ~(offsetT) 0xffffffff;
4485      load_register (reg, &hi32, 0);
4486      freg = reg;
4487    }
4488  if ((lo32.X_add_number & 0xffff0000) == 0)
4489    {
4490      if (freg != 0)
4491	{
4492	  macro_build (NULL, "dsll32", "d,w,<", reg, freg, 0);
4493	  freg = reg;
4494	}
4495    }
4496  else
4497    {
4498      expressionS mid16;
4499
4500      if ((freg == 0) && (lo32.X_add_number == (offsetT) 0xffffffff))
4501	{
4502	  macro_build (&lo32, "lui", "t,u", reg, BFD_RELOC_HI16);
4503	  macro_build (NULL, "dsrl32", "d,w,<", reg, reg, 0);
4504	  return;
4505	}
4506
4507      if (freg != 0)
4508	{
4509	  macro_build (NULL, "dsll", "d,w,<", reg, freg, 16);
4510	  freg = reg;
4511	}
4512      mid16 = lo32;
4513      mid16.X_add_number >>= 16;
4514      macro_build (&mid16, "ori", "t,r,i", reg, freg, BFD_RELOC_LO16);
4515      macro_build (NULL, "dsll", "d,w,<", reg, reg, 16);
4516      freg = reg;
4517    }
4518  if ((lo32.X_add_number & 0xffff) != 0)
4519    macro_build (&lo32, "ori", "t,r,i", reg, freg, BFD_RELOC_LO16);
4520}
4521
4522static inline void
4523load_delay_nop (void)
4524{
4525  if (!gpr_interlocks)
4526    macro_build (NULL, "nop", "");
4527}
4528
4529/* Load an address into a register.  */
4530
4531static void
4532load_address (int reg, expressionS *ep, int *used_at)
4533{
4534  if (ep->X_op != O_constant
4535      && ep->X_op != O_symbol)
4536    {
4537      as_bad (_("expression too complex"));
4538      ep->X_op = O_constant;
4539    }
4540
4541  if (ep->X_op == O_constant)
4542    {
4543      load_register (reg, ep, HAVE_64BIT_ADDRESSES);
4544      return;
4545    }
4546
4547  if (mips_pic == NO_PIC)
4548    {
4549      /* If this is a reference to a GP relative symbol, we want
4550	   addiu	$reg,$gp,<sym>		(BFD_RELOC_GPREL16)
4551	 Otherwise we want
4552	   lui		$reg,<sym>		(BFD_RELOC_HI16_S)
4553	   addiu	$reg,$reg,<sym>		(BFD_RELOC_LO16)
4554	 If we have an addend, we always use the latter form.
4555
4556	 With 64bit address space and a usable $at we want
4557	   lui		$reg,<sym>		(BFD_RELOC_MIPS_HIGHEST)
4558	   lui		$at,<sym>		(BFD_RELOC_HI16_S)
4559	   daddiu	$reg,<sym>		(BFD_RELOC_MIPS_HIGHER)
4560	   daddiu	$at,<sym>		(BFD_RELOC_LO16)
4561	   dsll32	$reg,0
4562	   daddu	$reg,$reg,$at
4563
4564	 If $at is already in use, we use a path which is suboptimal
4565	 on superscalar processors.
4566	   lui		$reg,<sym>		(BFD_RELOC_MIPS_HIGHEST)
4567	   daddiu	$reg,<sym>		(BFD_RELOC_MIPS_HIGHER)
4568	   dsll		$reg,16
4569	   daddiu	$reg,<sym>		(BFD_RELOC_HI16_S)
4570	   dsll		$reg,16
4571	   daddiu	$reg,<sym>		(BFD_RELOC_LO16)
4572
4573	 For GP relative symbols in 64bit address space we can use
4574	 the same sequence as in 32bit address space.  */
4575      if (HAVE_64BIT_SYMBOLS)
4576	{
4577	  if ((valueT) ep->X_add_number <= MAX_GPREL_OFFSET
4578	      && !nopic_need_relax (ep->X_add_symbol, 1))
4579	    {
4580	      relax_start (ep->X_add_symbol);
4581	      macro_build (ep, ADDRESS_ADDI_INSN, "t,r,j", reg,
4582			   mips_gp_register, BFD_RELOC_GPREL16);
4583	      relax_switch ();
4584	    }
4585
4586	  if (*used_at == 0 && mips_opts.at)
4587	    {
4588	      macro_build (ep, "lui", "t,u", reg, BFD_RELOC_MIPS_HIGHEST);
4589	      macro_build (ep, "lui", "t,u", AT, BFD_RELOC_HI16_S);
4590	      macro_build (ep, "daddiu", "t,r,j", reg, reg,
4591			   BFD_RELOC_MIPS_HIGHER);
4592	      macro_build (ep, "daddiu", "t,r,j", AT, AT, BFD_RELOC_LO16);
4593	      macro_build (NULL, "dsll32", "d,w,<", reg, reg, 0);
4594	      macro_build (NULL, "daddu", "d,v,t", reg, reg, AT);
4595	      *used_at = 1;
4596	    }
4597	  else
4598	    {
4599	      macro_build (ep, "lui", "t,u", reg, BFD_RELOC_MIPS_HIGHEST);
4600	      macro_build (ep, "daddiu", "t,r,j", reg, reg,
4601			   BFD_RELOC_MIPS_HIGHER);
4602	      macro_build (NULL, "dsll", "d,w,<", reg, reg, 16);
4603	      macro_build (ep, "daddiu", "t,r,j", reg, reg, BFD_RELOC_HI16_S);
4604	      macro_build (NULL, "dsll", "d,w,<", reg, reg, 16);
4605	      macro_build (ep, "daddiu", "t,r,j", reg, reg, BFD_RELOC_LO16);
4606	    }
4607
4608	  if (mips_relax.sequence)
4609	    relax_end ();
4610	}
4611      else
4612	{
4613	  if ((valueT) ep->X_add_number <= MAX_GPREL_OFFSET
4614	      && !nopic_need_relax (ep->X_add_symbol, 1))
4615	    {
4616	      relax_start (ep->X_add_symbol);
4617	      macro_build (ep, ADDRESS_ADDI_INSN, "t,r,j", reg,
4618			   mips_gp_register, BFD_RELOC_GPREL16);
4619	      relax_switch ();
4620	    }
4621	  macro_build_lui (ep, reg);
4622	  macro_build (ep, ADDRESS_ADDI_INSN, "t,r,j",
4623		       reg, reg, BFD_RELOC_LO16);
4624	  if (mips_relax.sequence)
4625	    relax_end ();
4626	}
4627    }
4628  else if (!mips_big_got)
4629    {
4630      expressionS ex;
4631
4632      /* If this is a reference to an external symbol, we want
4633	   lw		$reg,<sym>($gp)		(BFD_RELOC_MIPS_GOT16)
4634	 Otherwise we want
4635	   lw		$reg,<sym>($gp)		(BFD_RELOC_MIPS_GOT16)
4636	   nop
4637	   addiu	$reg,$reg,<sym>		(BFD_RELOC_LO16)
4638	 If there is a constant, it must be added in after.
4639
4640	 If we have NewABI, we want
4641	   lw		$reg,<sym+cst>($gp)	(BFD_RELOC_MIPS_GOT_DISP)
4642         unless we're referencing a global symbol with a non-zero
4643         offset, in which case cst must be added separately.  */
4644      if (HAVE_NEWABI)
4645	{
4646	  if (ep->X_add_number)
4647	    {
4648	      ex.X_add_number = ep->X_add_number;
4649	      ep->X_add_number = 0;
4650	      relax_start (ep->X_add_symbol);
4651	      macro_build (ep, ADDRESS_LOAD_INSN, "t,o(b)", reg,
4652			   BFD_RELOC_MIPS_GOT_DISP, mips_gp_register);
4653	      if (ex.X_add_number < -0x8000 || ex.X_add_number >= 0x8000)
4654		as_bad (_("PIC code offset overflow (max 16 signed bits)"));
4655	      ex.X_op = O_constant;
4656	      macro_build (&ex, ADDRESS_ADDI_INSN, "t,r,j",
4657			   reg, reg, BFD_RELOC_LO16);
4658	      ep->X_add_number = ex.X_add_number;
4659	      relax_switch ();
4660	    }
4661	  macro_build (ep, ADDRESS_LOAD_INSN, "t,o(b)", reg,
4662		       BFD_RELOC_MIPS_GOT_DISP, mips_gp_register);
4663	  if (mips_relax.sequence)
4664	    relax_end ();
4665	}
4666      else
4667	{
4668	  ex.X_add_number = ep->X_add_number;
4669	  ep->X_add_number = 0;
4670	  macro_build (ep, ADDRESS_LOAD_INSN, "t,o(b)", reg,
4671		       BFD_RELOC_MIPS_GOT16, mips_gp_register);
4672	  load_delay_nop ();
4673	  relax_start (ep->X_add_symbol);
4674	  relax_switch ();
4675	  macro_build (ep, ADDRESS_ADDI_INSN, "t,r,j", reg, reg,
4676		       BFD_RELOC_LO16);
4677	  relax_end ();
4678
4679	  if (ex.X_add_number != 0)
4680	    {
4681	      if (ex.X_add_number < -0x8000 || ex.X_add_number >= 0x8000)
4682		as_bad (_("PIC code offset overflow (max 16 signed bits)"));
4683	      ex.X_op = O_constant;
4684	      macro_build (&ex, ADDRESS_ADDI_INSN, "t,r,j",
4685			   reg, reg, BFD_RELOC_LO16);
4686	    }
4687	}
4688    }
4689  else if (mips_big_got)
4690    {
4691      expressionS ex;
4692
4693      /* This is the large GOT case.  If this is a reference to an
4694	 external symbol, we want
4695	   lui		$reg,<sym>		(BFD_RELOC_MIPS_GOT_HI16)
4696	   addu		$reg,$reg,$gp
4697	   lw		$reg,<sym>($reg)	(BFD_RELOC_MIPS_GOT_LO16)
4698
4699	 Otherwise, for a reference to a local symbol in old ABI, we want
4700	   lw		$reg,<sym>($gp)		(BFD_RELOC_MIPS_GOT16)
4701	   nop
4702	   addiu	$reg,$reg,<sym>		(BFD_RELOC_LO16)
4703	 If there is a constant, it must be added in after.
4704
4705	 In the NewABI, for local symbols, with or without offsets, we want:
4706	   lw		$reg,<sym>($gp)		(BFD_RELOC_MIPS_GOT_PAGE)
4707	   addiu	$reg,$reg,<sym>		(BFD_RELOC_MIPS_GOT_OFST)
4708      */
4709      if (HAVE_NEWABI)
4710	{
4711	  ex.X_add_number = ep->X_add_number;
4712	  ep->X_add_number = 0;
4713	  relax_start (ep->X_add_symbol);
4714	  macro_build (ep, "lui", "t,u", reg, BFD_RELOC_MIPS_GOT_HI16);
4715	  macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
4716		       reg, reg, mips_gp_register);
4717	  macro_build (ep, ADDRESS_LOAD_INSN, "t,o(b)",
4718		       reg, BFD_RELOC_MIPS_GOT_LO16, reg);
4719	  if (ex.X_add_number < -0x8000 || ex.X_add_number >= 0x8000)
4720	    as_bad (_("PIC code offset overflow (max 16 signed bits)"));
4721	  else if (ex.X_add_number)
4722	    {
4723	      ex.X_op = O_constant;
4724	      macro_build (&ex, ADDRESS_ADDI_INSN, "t,r,j", reg, reg,
4725			   BFD_RELOC_LO16);
4726	    }
4727
4728	  ep->X_add_number = ex.X_add_number;
4729	  relax_switch ();
4730	  macro_build (ep, ADDRESS_LOAD_INSN, "t,o(b)", reg,
4731		       BFD_RELOC_MIPS_GOT_PAGE, mips_gp_register);
4732	  macro_build (ep, ADDRESS_ADDI_INSN, "t,r,j", reg, reg,
4733		       BFD_RELOC_MIPS_GOT_OFST);
4734	  relax_end ();
4735	}
4736      else
4737	{
4738	  ex.X_add_number = ep->X_add_number;
4739	  ep->X_add_number = 0;
4740	  relax_start (ep->X_add_symbol);
4741	  macro_build (ep, "lui", "t,u", reg, BFD_RELOC_MIPS_GOT_HI16);
4742	  macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
4743		       reg, reg, mips_gp_register);
4744	  macro_build (ep, ADDRESS_LOAD_INSN, "t,o(b)",
4745		       reg, BFD_RELOC_MIPS_GOT_LO16, reg);
4746	  relax_switch ();
4747	  if (reg_needs_delay (mips_gp_register))
4748	    {
4749	      /* We need a nop before loading from $gp.  This special
4750		 check is required because the lui which starts the main
4751		 instruction stream does not refer to $gp, and so will not
4752		 insert the nop which may be required.  */
4753	      macro_build (NULL, "nop", "");
4754	    }
4755	  macro_build (ep, ADDRESS_LOAD_INSN, "t,o(b)", reg,
4756		       BFD_RELOC_MIPS_GOT16, mips_gp_register);
4757	  load_delay_nop ();
4758	  macro_build (ep, ADDRESS_ADDI_INSN, "t,r,j", reg, reg,
4759		       BFD_RELOC_LO16);
4760	  relax_end ();
4761
4762	  if (ex.X_add_number != 0)
4763	    {
4764	      if (ex.X_add_number < -0x8000 || ex.X_add_number >= 0x8000)
4765		as_bad (_("PIC code offset overflow (max 16 signed bits)"));
4766	      ex.X_op = O_constant;
4767	      macro_build (&ex, ADDRESS_ADDI_INSN, "t,r,j", reg, reg,
4768			   BFD_RELOC_LO16);
4769	    }
4770	}
4771    }
4772  else
4773    abort ();
4774
4775  if (!mips_opts.at && *used_at == 1)
4776    as_bad (_("Macro used $at after \".set noat\""));
4777}
4778
4779/* Move the contents of register SOURCE into register DEST.  */
4780
4781static void
4782move_register (int dest, int source)
4783{
4784  macro_build (NULL, HAVE_32BIT_GPRS ? "addu" : "daddu", "d,v,t",
4785	       dest, source, 0);
4786}
4787
4788/* Emit an SVR4 PIC sequence to load address LOCAL into DEST, where
4789   LOCAL is the sum of a symbol and a 16-bit or 32-bit displacement.
4790   The two alternatives are:
4791
4792   Global symbol		Local sybmol
4793   -------------		------------
4794   lw DEST,%got(SYMBOL)		lw DEST,%got(SYMBOL + OFFSET)
4795   ...				...
4796   addiu DEST,DEST,OFFSET	addiu DEST,DEST,%lo(SYMBOL + OFFSET)
4797
4798   load_got_offset emits the first instruction and add_got_offset
4799   emits the second for a 16-bit offset or add_got_offset_hilo emits
4800   a sequence to add a 32-bit offset using a scratch register.  */
4801
4802static void
4803load_got_offset (int dest, expressionS *local)
4804{
4805  expressionS global;
4806
4807  global = *local;
4808  global.X_add_number = 0;
4809
4810  relax_start (local->X_add_symbol);
4811  macro_build (&global, ADDRESS_LOAD_INSN, "t,o(b)", dest,
4812	       BFD_RELOC_MIPS_GOT16, mips_gp_register);
4813  relax_switch ();
4814  macro_build (local, ADDRESS_LOAD_INSN, "t,o(b)", dest,
4815	       BFD_RELOC_MIPS_GOT16, mips_gp_register);
4816  relax_end ();
4817}
4818
4819static void
4820add_got_offset (int dest, expressionS *local)
4821{
4822  expressionS global;
4823
4824  global.X_op = O_constant;
4825  global.X_op_symbol = NULL;
4826  global.X_add_symbol = NULL;
4827  global.X_add_number = local->X_add_number;
4828
4829  relax_start (local->X_add_symbol);
4830  macro_build (&global, ADDRESS_ADDI_INSN, "t,r,j",
4831	       dest, dest, BFD_RELOC_LO16);
4832  relax_switch ();
4833  macro_build (local, ADDRESS_ADDI_INSN, "t,r,j", dest, dest, BFD_RELOC_LO16);
4834  relax_end ();
4835}
4836
4837static void
4838add_got_offset_hilo (int dest, expressionS *local, int tmp)
4839{
4840  expressionS global;
4841  int hold_mips_optimize;
4842
4843  global.X_op = O_constant;
4844  global.X_op_symbol = NULL;
4845  global.X_add_symbol = NULL;
4846  global.X_add_number = local->X_add_number;
4847
4848  relax_start (local->X_add_symbol);
4849  load_register (tmp, &global, HAVE_64BIT_ADDRESSES);
4850  relax_switch ();
4851  /* Set mips_optimize around the lui instruction to avoid
4852     inserting an unnecessary nop after the lw.  */
4853  hold_mips_optimize = mips_optimize;
4854  mips_optimize = 2;
4855  macro_build_lui (&global, tmp);
4856  mips_optimize = hold_mips_optimize;
4857  macro_build (local, ADDRESS_ADDI_INSN, "t,r,j", tmp, tmp, BFD_RELOC_LO16);
4858  relax_end ();
4859
4860  macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", dest, dest, tmp);
4861}
4862
4863/*
4864 *			Build macros
4865 *   This routine implements the seemingly endless macro or synthesized
4866 * instructions and addressing modes in the mips assembly language. Many
4867 * of these macros are simple and are similar to each other. These could
4868 * probably be handled by some kind of table or grammar approach instead of
4869 * this verbose method. Others are not simple macros but are more like
4870 * optimizing code generation.
4871 *   One interesting optimization is when several store macros appear
4872 * consecutively that would load AT with the upper half of the same address.
4873 * The ensuing load upper instructions are ommited. This implies some kind
4874 * of global optimization. We currently only optimize within a single macro.
4875 *   For many of the load and store macros if the address is specified as a
4876 * constant expression in the first 64k of memory (ie ld $2,0x4000c) we
4877 * first load register 'at' with zero and use it as the base register. The
4878 * mips assembler simply uses register $zero. Just one tiny optimization
4879 * we're missing.
4880 */
4881static void
4882macro (struct mips_cl_insn *ip)
4883{
4884  unsigned int treg, sreg, dreg, breg;
4885  unsigned int tempreg;
4886  int mask;
4887  int used_at = 0;
4888  expressionS expr1;
4889  const char *s;
4890  const char *s2;
4891  const char *fmt;
4892  int likely = 0;
4893  int dbl = 0;
4894  int coproc = 0;
4895  int lr = 0;
4896  int imm = 0;
4897  int call = 0;
4898  int off;
4899  offsetT maxnum;
4900  bfd_reloc_code_real_type r;
4901  int hold_mips_optimize;
4902
4903  gas_assert (! mips_opts.mips16);
4904
4905  treg = (ip->insn_opcode >> 16) & 0x1f;
4906  dreg = (ip->insn_opcode >> 11) & 0x1f;
4907  sreg = breg = (ip->insn_opcode >> 21) & 0x1f;
4908  mask = ip->insn_mo->mask;
4909
4910  expr1.X_op = O_constant;
4911  expr1.X_op_symbol = NULL;
4912  expr1.X_add_symbol = NULL;
4913  expr1.X_add_number = 1;
4914
4915  switch (mask)
4916    {
4917    case M_DABS:
4918      dbl = 1;
4919    case M_ABS:
4920      /* bgez $a0,.+12
4921	 move v0,$a0
4922	 sub v0,$zero,$a0
4923	 */
4924
4925      start_noreorder ();
4926
4927      expr1.X_add_number = 8;
4928      macro_build (&expr1, "bgez", "s,p", sreg);
4929      if (dreg == sreg)
4930	macro_build (NULL, "nop", "", 0);
4931      else
4932	move_register (dreg, sreg);
4933      macro_build (NULL, dbl ? "dsub" : "sub", "d,v,t", dreg, 0, sreg);
4934
4935      end_noreorder ();
4936      break;
4937
4938    case M_ADD_I:
4939      s = "addi";
4940      s2 = "add";
4941      goto do_addi;
4942    case M_ADDU_I:
4943      s = "addiu";
4944      s2 = "addu";
4945      goto do_addi;
4946    case M_DADD_I:
4947      dbl = 1;
4948      s = "daddi";
4949      s2 = "dadd";
4950      goto do_addi;
4951    case M_DADDU_I:
4952      dbl = 1;
4953      s = "daddiu";
4954      s2 = "daddu";
4955    do_addi:
4956      if (imm_expr.X_op == O_constant
4957	  && imm_expr.X_add_number >= -0x8000
4958	  && imm_expr.X_add_number < 0x8000)
4959	{
4960	  macro_build (&imm_expr, s, "t,r,j", treg, sreg, BFD_RELOC_LO16);
4961	  break;
4962	}
4963      used_at = 1;
4964      load_register (AT, &imm_expr, dbl);
4965      macro_build (NULL, s2, "d,v,t", treg, sreg, AT);
4966      break;
4967
4968    case M_AND_I:
4969      s = "andi";
4970      s2 = "and";
4971      goto do_bit;
4972    case M_OR_I:
4973      s = "ori";
4974      s2 = "or";
4975      goto do_bit;
4976    case M_NOR_I:
4977      s = "";
4978      s2 = "nor";
4979      goto do_bit;
4980    case M_XOR_I:
4981      s = "xori";
4982      s2 = "xor";
4983    do_bit:
4984      if (imm_expr.X_op == O_constant
4985	  && imm_expr.X_add_number >= 0
4986	  && imm_expr.X_add_number < 0x10000)
4987	{
4988	  if (mask != M_NOR_I)
4989	    macro_build (&imm_expr, s, "t,r,i", treg, sreg, BFD_RELOC_LO16);
4990	  else
4991	    {
4992	      macro_build (&imm_expr, "ori", "t,r,i",
4993			   treg, sreg, BFD_RELOC_LO16);
4994	      macro_build (NULL, "nor", "d,v,t", treg, treg, 0);
4995	    }
4996	  break;
4997	}
4998
4999      used_at = 1;
5000      load_register (AT, &imm_expr, HAVE_64BIT_GPRS);
5001      macro_build (NULL, s2, "d,v,t", treg, sreg, AT);
5002      break;
5003
5004    case M_BALIGN:
5005      switch (imm_expr.X_add_number)
5006	{
5007	case 0:
5008	  macro_build (NULL, "nop", "");
5009	  break;
5010	case 2:
5011	  macro_build (NULL, "packrl.ph", "d,s,t", treg, treg, sreg);
5012	  break;
5013	default:
5014	  macro_build (NULL, "balign", "t,s,2", treg, sreg,
5015		       (int)imm_expr.X_add_number);
5016	  break;
5017	}
5018      break;
5019
5020    case M_BEQ_I:
5021      s = "beq";
5022      goto beq_i;
5023    case M_BEQL_I:
5024      s = "beql";
5025      likely = 1;
5026      goto beq_i;
5027    case M_BNE_I:
5028      s = "bne";
5029      goto beq_i;
5030    case M_BNEL_I:
5031      s = "bnel";
5032      likely = 1;
5033    beq_i:
5034      if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
5035	{
5036	  macro_build (&offset_expr, s, "s,t,p", sreg, 0);
5037	  break;
5038	}
5039      used_at = 1;
5040      load_register (AT, &imm_expr, HAVE_64BIT_GPRS);
5041      macro_build (&offset_expr, s, "s,t,p", sreg, AT);
5042      break;
5043
5044    case M_BGEL:
5045      likely = 1;
5046    case M_BGE:
5047      if (treg == 0)
5048	{
5049	  macro_build (&offset_expr, likely ? "bgezl" : "bgez", "s,p", sreg);
5050	  break;
5051	}
5052      if (sreg == 0)
5053	{
5054	  macro_build (&offset_expr, likely ? "blezl" : "blez", "s,p", treg);
5055	  break;
5056	}
5057      used_at = 1;
5058      macro_build (NULL, "slt", "d,v,t", AT, sreg, treg);
5059      macro_build (&offset_expr, likely ? "beql" : "beq", "s,t,p", AT, 0);
5060      break;
5061
5062    case M_BGTL_I:
5063      likely = 1;
5064    case M_BGT_I:
5065      /* check for > max integer */
5066      maxnum = 0x7fffffff;
5067      if (HAVE_64BIT_GPRS && sizeof (maxnum) > 4)
5068	{
5069	  maxnum <<= 16;
5070	  maxnum |= 0xffff;
5071	  maxnum <<= 16;
5072	  maxnum |= 0xffff;
5073	}
5074      if (imm_expr.X_op == O_constant
5075	  && imm_expr.X_add_number >= maxnum
5076	  && (HAVE_32BIT_GPRS || sizeof (maxnum) > 4))
5077	{
5078	do_false:
5079	  /* result is always false */
5080	  if (! likely)
5081	    macro_build (NULL, "nop", "", 0);
5082	  else
5083	    macro_build (&offset_expr, "bnel", "s,t,p", 0, 0);
5084	  break;
5085	}
5086      if (imm_expr.X_op != O_constant)
5087	as_bad (_("Unsupported large constant"));
5088      ++imm_expr.X_add_number;
5089      /* FALLTHROUGH */
5090    case M_BGE_I:
5091    case M_BGEL_I:
5092      if (mask == M_BGEL_I)
5093	likely = 1;
5094      if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
5095	{
5096	  macro_build (&offset_expr, likely ? "bgezl" : "bgez", "s,p", sreg);
5097	  break;
5098	}
5099      if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 1)
5100	{
5101	  macro_build (&offset_expr, likely ? "bgtzl" : "bgtz", "s,p", sreg);
5102	  break;
5103	}
5104      maxnum = 0x7fffffff;
5105      if (HAVE_64BIT_GPRS && sizeof (maxnum) > 4)
5106	{
5107	  maxnum <<= 16;
5108	  maxnum |= 0xffff;
5109	  maxnum <<= 16;
5110	  maxnum |= 0xffff;
5111	}
5112      maxnum = - maxnum - 1;
5113      if (imm_expr.X_op == O_constant
5114	  && imm_expr.X_add_number <= maxnum
5115	  && (HAVE_32BIT_GPRS || sizeof (maxnum) > 4))
5116	{
5117	do_true:
5118	  /* result is always true */
5119	  as_warn (_("Branch %s is always true"), ip->insn_mo->name);
5120	  macro_build (&offset_expr, "b", "p");
5121	  break;
5122	}
5123      used_at = 1;
5124      set_at (sreg, 0);
5125      macro_build (&offset_expr, likely ? "beql" : "beq", "s,t,p", AT, 0);
5126      break;
5127
5128    case M_BGEUL:
5129      likely = 1;
5130    case M_BGEU:
5131      if (treg == 0)
5132	goto do_true;
5133      if (sreg == 0)
5134	{
5135	  macro_build (&offset_expr, likely ? "beql" : "beq",
5136		       "s,t,p", 0, treg);
5137	  break;
5138	}
5139      used_at = 1;
5140      macro_build (NULL, "sltu", "d,v,t", AT, sreg, treg);
5141      macro_build (&offset_expr, likely ? "beql" : "beq", "s,t,p", AT, 0);
5142      break;
5143
5144    case M_BGTUL_I:
5145      likely = 1;
5146    case M_BGTU_I:
5147      if (sreg == 0
5148	  || (HAVE_32BIT_GPRS
5149	      && imm_expr.X_op == O_constant
5150	      && imm_expr.X_add_number == (offsetT) 0xffffffff))
5151	goto do_false;
5152      if (imm_expr.X_op != O_constant)
5153	as_bad (_("Unsupported large constant"));
5154      ++imm_expr.X_add_number;
5155      /* FALLTHROUGH */
5156    case M_BGEU_I:
5157    case M_BGEUL_I:
5158      if (mask == M_BGEUL_I)
5159	likely = 1;
5160      if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
5161	goto do_true;
5162      if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 1)
5163	{
5164	  macro_build (&offset_expr, likely ? "bnel" : "bne",
5165		       "s,t,p", sreg, 0);
5166	  break;
5167	}
5168      used_at = 1;
5169      set_at (sreg, 1);
5170      macro_build (&offset_expr, likely ? "beql" : "beq", "s,t,p", AT, 0);
5171      break;
5172
5173    case M_BGTL:
5174      likely = 1;
5175    case M_BGT:
5176      if (treg == 0)
5177	{
5178	  macro_build (&offset_expr, likely ? "bgtzl" : "bgtz", "s,p", sreg);
5179	  break;
5180	}
5181      if (sreg == 0)
5182	{
5183	  macro_build (&offset_expr, likely ? "bltzl" : "bltz", "s,p", treg);
5184	  break;
5185	}
5186      used_at = 1;
5187      macro_build (NULL, "slt", "d,v,t", AT, treg, sreg);
5188      macro_build (&offset_expr, likely ? "bnel" : "bne", "s,t,p", AT, 0);
5189      break;
5190
5191    case M_BGTUL:
5192      likely = 1;
5193    case M_BGTU:
5194      if (treg == 0)
5195	{
5196	  macro_build (&offset_expr, likely ? "bnel" : "bne",
5197		       "s,t,p", sreg, 0);
5198	  break;
5199	}
5200      if (sreg == 0)
5201	goto do_false;
5202      used_at = 1;
5203      macro_build (NULL, "sltu", "d,v,t", AT, treg, sreg);
5204      macro_build (&offset_expr, likely ? "bnel" : "bne", "s,t,p", AT, 0);
5205      break;
5206
5207    case M_BLEL:
5208      likely = 1;
5209    case M_BLE:
5210      if (treg == 0)
5211	{
5212	  macro_build (&offset_expr, likely ? "blezl" : "blez", "s,p", sreg);
5213	  break;
5214	}
5215      if (sreg == 0)
5216	{
5217	  macro_build (&offset_expr, likely ? "bgezl" : "bgez", "s,p", treg);
5218	  break;
5219	}
5220      used_at = 1;
5221      macro_build (NULL, "slt", "d,v,t", AT, treg, sreg);
5222      macro_build (&offset_expr, likely ? "beql" : "beq", "s,t,p", AT, 0);
5223      break;
5224
5225    case M_BLEL_I:
5226      likely = 1;
5227    case M_BLE_I:
5228      maxnum = 0x7fffffff;
5229      if (HAVE_64BIT_GPRS && sizeof (maxnum) > 4)
5230	{
5231	  maxnum <<= 16;
5232	  maxnum |= 0xffff;
5233	  maxnum <<= 16;
5234	  maxnum |= 0xffff;
5235	}
5236      if (imm_expr.X_op == O_constant
5237	  && imm_expr.X_add_number >= maxnum
5238	  && (HAVE_32BIT_GPRS || sizeof (maxnum) > 4))
5239	goto do_true;
5240      if (imm_expr.X_op != O_constant)
5241	as_bad (_("Unsupported large constant"));
5242      ++imm_expr.X_add_number;
5243      /* FALLTHROUGH */
5244    case M_BLT_I:
5245    case M_BLTL_I:
5246      if (mask == M_BLTL_I)
5247	likely = 1;
5248      if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
5249	{
5250	  macro_build (&offset_expr, likely ? "bltzl" : "bltz", "s,p", sreg);
5251	  break;
5252	}
5253      if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 1)
5254	{
5255	  macro_build (&offset_expr, likely ? "blezl" : "blez", "s,p", sreg);
5256	  break;
5257	}
5258      used_at = 1;
5259      set_at (sreg, 0);
5260      macro_build (&offset_expr, likely ? "bnel" : "bne", "s,t,p", AT, 0);
5261      break;
5262
5263    case M_BLEUL:
5264      likely = 1;
5265    case M_BLEU:
5266      if (treg == 0)
5267	{
5268	  macro_build (&offset_expr, likely ? "beql" : "beq",
5269		       "s,t,p", sreg, 0);
5270	  break;
5271	}
5272      if (sreg == 0)
5273	goto do_true;
5274      used_at = 1;
5275      macro_build (NULL, "sltu", "d,v,t", AT, treg, sreg);
5276      macro_build (&offset_expr, likely ? "beql" : "beq", "s,t,p", AT, 0);
5277      break;
5278
5279    case M_BLEUL_I:
5280      likely = 1;
5281    case M_BLEU_I:
5282      if (sreg == 0
5283	  || (HAVE_32BIT_GPRS
5284	      && imm_expr.X_op == O_constant
5285	      && imm_expr.X_add_number == (offsetT) 0xffffffff))
5286	goto do_true;
5287      if (imm_expr.X_op != O_constant)
5288	as_bad (_("Unsupported large constant"));
5289      ++imm_expr.X_add_number;
5290      /* FALLTHROUGH */
5291    case M_BLTU_I:
5292    case M_BLTUL_I:
5293      if (mask == M_BLTUL_I)
5294	likely = 1;
5295      if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
5296	goto do_false;
5297      if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 1)
5298	{
5299	  macro_build (&offset_expr, likely ? "beql" : "beq",
5300		       "s,t,p", sreg, 0);
5301	  break;
5302	}
5303      used_at = 1;
5304      set_at (sreg, 1);
5305      macro_build (&offset_expr, likely ? "bnel" : "bne", "s,t,p", AT, 0);
5306      break;
5307
5308    case M_BLTL:
5309      likely = 1;
5310    case M_BLT:
5311      if (treg == 0)
5312	{
5313	  macro_build (&offset_expr, likely ? "bltzl" : "bltz", "s,p", sreg);
5314	  break;
5315	}
5316      if (sreg == 0)
5317	{
5318	  macro_build (&offset_expr, likely ? "bgtzl" : "bgtz", "s,p", treg);
5319	  break;
5320	}
5321      used_at = 1;
5322      macro_build (NULL, "slt", "d,v,t", AT, sreg, treg);
5323      macro_build (&offset_expr, likely ? "bnel" : "bne", "s,t,p", AT, 0);
5324      break;
5325
5326    case M_BLTUL:
5327      likely = 1;
5328    case M_BLTU:
5329      if (treg == 0)
5330	goto do_false;
5331      if (sreg == 0)
5332	{
5333	  macro_build (&offset_expr, likely ? "bnel" : "bne",
5334		       "s,t,p", 0, treg);
5335	  break;
5336	}
5337      used_at = 1;
5338      macro_build (NULL, "sltu", "d,v,t", AT, sreg, treg);
5339      macro_build (&offset_expr, likely ? "bnel" : "bne", "s,t,p", AT, 0);
5340      break;
5341
5342    case M_DEXT:
5343      {
5344	unsigned long pos;
5345	unsigned long size;
5346
5347        if (imm_expr.X_op != O_constant || imm2_expr.X_op != O_constant)
5348	  {
5349	    as_bad (_("Unsupported large constant"));
5350	    pos = size = 1;
5351	  }
5352	else
5353	  {
5354	    pos = (unsigned long) imm_expr.X_add_number;
5355	    size = (unsigned long) imm2_expr.X_add_number;
5356	  }
5357
5358	if (pos > 63)
5359	  {
5360	    as_bad (_("Improper position (%lu)"), pos);
5361	    pos = 1;
5362	  }
5363        if (size == 0 || size > 64
5364	    || (pos + size - 1) > 63)
5365	  {
5366	    as_bad (_("Improper extract size (%lu, position %lu)"),
5367		    size, pos);
5368	    size = 1;
5369	  }
5370
5371	if (size <= 32 && pos < 32)
5372	  {
5373	    s = "dext";
5374	    fmt = "t,r,+A,+C";
5375	  }
5376	else if (size <= 32)
5377	  {
5378	    s = "dextu";
5379	    fmt = "t,r,+E,+H";
5380	  }
5381	else
5382	  {
5383	    s = "dextm";
5384	    fmt = "t,r,+A,+G";
5385	  }
5386	macro_build ((expressionS *) NULL, s, fmt, treg, sreg, pos, size - 1);
5387      }
5388      break;
5389
5390    case M_DINS:
5391      {
5392	unsigned long pos;
5393	unsigned long size;
5394
5395        if (imm_expr.X_op != O_constant || imm2_expr.X_op != O_constant)
5396	  {
5397	    as_bad (_("Unsupported large constant"));
5398	    pos = size = 1;
5399	  }
5400	else
5401	  {
5402	    pos = (unsigned long) imm_expr.X_add_number;
5403	    size = (unsigned long) imm2_expr.X_add_number;
5404	  }
5405
5406	if (pos > 63)
5407	  {
5408	    as_bad (_("Improper position (%lu)"), pos);
5409	    pos = 1;
5410	  }
5411        if (size == 0 || size > 64
5412	    || (pos + size - 1) > 63)
5413	  {
5414	    as_bad (_("Improper insert size (%lu, position %lu)"),
5415		    size, pos);
5416	    size = 1;
5417	  }
5418
5419	if (pos < 32 && (pos + size - 1) < 32)
5420	  {
5421	    s = "dins";
5422	    fmt = "t,r,+A,+B";
5423	  }
5424	else if (pos >= 32)
5425	  {
5426	    s = "dinsu";
5427	    fmt = "t,r,+E,+F";
5428	  }
5429	else
5430	  {
5431	    s = "dinsm";
5432	    fmt = "t,r,+A,+F";
5433	  }
5434	macro_build ((expressionS *) NULL, s, fmt, treg, sreg, (int) pos,
5435		     (int) (pos + size - 1));
5436      }
5437      break;
5438
5439    case M_DDIV_3:
5440      dbl = 1;
5441    case M_DIV_3:
5442      s = "mflo";
5443      goto do_div3;
5444    case M_DREM_3:
5445      dbl = 1;
5446    case M_REM_3:
5447      s = "mfhi";
5448    do_div3:
5449      if (treg == 0)
5450	{
5451	  as_warn (_("Divide by zero."));
5452	  if (mips_trap)
5453	    macro_build (NULL, "teq", "s,t,q", 0, 0, 7);
5454	  else
5455	    macro_build (NULL, "break", "c", 7);
5456	  break;
5457	}
5458
5459      start_noreorder ();
5460      if (mips_trap)
5461	{
5462	  macro_build (NULL, "teq", "s,t,q", treg, 0, 7);
5463	  macro_build (NULL, dbl ? "ddiv" : "div", "z,s,t", sreg, treg);
5464	}
5465      else
5466	{
5467	  expr1.X_add_number = 8;
5468	  macro_build (&expr1, "bne", "s,t,p", treg, 0);
5469	  macro_build (NULL, dbl ? "ddiv" : "div", "z,s,t", sreg, treg);
5470	  macro_build (NULL, "break", "c", 7);
5471	}
5472      expr1.X_add_number = -1;
5473      used_at = 1;
5474      load_register (AT, &expr1, dbl);
5475      expr1.X_add_number = mips_trap ? (dbl ? 12 : 8) : (dbl ? 20 : 16);
5476      macro_build (&expr1, "bne", "s,t,p", treg, AT);
5477      if (dbl)
5478	{
5479	  expr1.X_add_number = 1;
5480	  load_register (AT, &expr1, dbl);
5481	  macro_build (NULL, "dsll32", "d,w,<", AT, AT, 31);
5482	}
5483      else
5484	{
5485	  expr1.X_add_number = 0x80000000;
5486	  macro_build (&expr1, "lui", "t,u", AT, BFD_RELOC_HI16);
5487	}
5488      if (mips_trap)
5489	{
5490	  macro_build (NULL, "teq", "s,t,q", sreg, AT, 6);
5491	  /* We want to close the noreorder block as soon as possible, so
5492	     that later insns are available for delay slot filling.  */
5493	  end_noreorder ();
5494	}
5495      else
5496	{
5497	  expr1.X_add_number = 8;
5498	  macro_build (&expr1, "bne", "s,t,p", sreg, AT);
5499	  macro_build (NULL, "nop", "", 0);
5500
5501	  /* We want to close the noreorder block as soon as possible, so
5502	     that later insns are available for delay slot filling.  */
5503	  end_noreorder ();
5504
5505	  macro_build (NULL, "break", "c", 6);
5506	}
5507      macro_build (NULL, s, "d", dreg);
5508      break;
5509
5510    case M_DIV_3I:
5511      s = "div";
5512      s2 = "mflo";
5513      goto do_divi;
5514    case M_DIVU_3I:
5515      s = "divu";
5516      s2 = "mflo";
5517      goto do_divi;
5518    case M_REM_3I:
5519      s = "div";
5520      s2 = "mfhi";
5521      goto do_divi;
5522    case M_REMU_3I:
5523      s = "divu";
5524      s2 = "mfhi";
5525      goto do_divi;
5526    case M_DDIV_3I:
5527      dbl = 1;
5528      s = "ddiv";
5529      s2 = "mflo";
5530      goto do_divi;
5531    case M_DDIVU_3I:
5532      dbl = 1;
5533      s = "ddivu";
5534      s2 = "mflo";
5535      goto do_divi;
5536    case M_DREM_3I:
5537      dbl = 1;
5538      s = "ddiv";
5539      s2 = "mfhi";
5540      goto do_divi;
5541    case M_DREMU_3I:
5542      dbl = 1;
5543      s = "ddivu";
5544      s2 = "mfhi";
5545    do_divi:
5546      if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
5547	{
5548	  as_warn (_("Divide by zero."));
5549	  if (mips_trap)
5550	    macro_build (NULL, "teq", "s,t,q", 0, 0, 7);
5551	  else
5552	    macro_build (NULL, "break", "c", 7);
5553	  break;
5554	}
5555      if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 1)
5556	{
5557	  if (strcmp (s2, "mflo") == 0)
5558	    move_register (dreg, sreg);
5559	  else
5560	    move_register (dreg, 0);
5561	  break;
5562	}
5563      if (imm_expr.X_op == O_constant
5564	  && imm_expr.X_add_number == -1
5565	  && s[strlen (s) - 1] != 'u')
5566	{
5567	  if (strcmp (s2, "mflo") == 0)
5568	    {
5569	      macro_build (NULL, dbl ? "dneg" : "neg", "d,w", dreg, sreg);
5570	    }
5571	  else
5572	    move_register (dreg, 0);
5573	  break;
5574	}
5575
5576      used_at = 1;
5577      load_register (AT, &imm_expr, dbl);
5578      macro_build (NULL, s, "z,s,t", sreg, AT);
5579      macro_build (NULL, s2, "d", dreg);
5580      break;
5581
5582    case M_DIVU_3:
5583      s = "divu";
5584      s2 = "mflo";
5585      goto do_divu3;
5586    case M_REMU_3:
5587      s = "divu";
5588      s2 = "mfhi";
5589      goto do_divu3;
5590    case M_DDIVU_3:
5591      s = "ddivu";
5592      s2 = "mflo";
5593      goto do_divu3;
5594    case M_DREMU_3:
5595      s = "ddivu";
5596      s2 = "mfhi";
5597    do_divu3:
5598      start_noreorder ();
5599      if (mips_trap)
5600	{
5601	  macro_build (NULL, "teq", "s,t,q", treg, 0, 7);
5602	  macro_build (NULL, s, "z,s,t", sreg, treg);
5603	  /* We want to close the noreorder block as soon as possible, so
5604	     that later insns are available for delay slot filling.  */
5605	  end_noreorder ();
5606	}
5607      else
5608	{
5609	  expr1.X_add_number = 8;
5610	  macro_build (&expr1, "bne", "s,t,p", treg, 0);
5611	  macro_build (NULL, s, "z,s,t", sreg, treg);
5612
5613	  /* We want to close the noreorder block as soon as possible, so
5614	     that later insns are available for delay slot filling.  */
5615	  end_noreorder ();
5616	  macro_build (NULL, "break", "c", 7);
5617	}
5618      macro_build (NULL, s2, "d", dreg);
5619      break;
5620
5621    case M_DLCA_AB:
5622      dbl = 1;
5623    case M_LCA_AB:
5624      call = 1;
5625      goto do_la;
5626    case M_DLA_AB:
5627      dbl = 1;
5628    case M_LA_AB:
5629    do_la:
5630      /* Load the address of a symbol into a register.  If breg is not
5631	 zero, we then add a base register to it.  */
5632
5633      if (dbl && HAVE_32BIT_GPRS)
5634	as_warn (_("dla used to load 32-bit register"));
5635
5636      if (! dbl && HAVE_64BIT_OBJECTS)
5637	as_warn (_("la used to load 64-bit address"));
5638
5639      if (offset_expr.X_op == O_constant
5640	  && offset_expr.X_add_number >= -0x8000
5641	  && offset_expr.X_add_number < 0x8000)
5642	{
5643	  macro_build (&offset_expr, ADDRESS_ADDI_INSN,
5644		       "t,r,j", treg, sreg, BFD_RELOC_LO16);
5645	  break;
5646	}
5647
5648      if (mips_opts.at && (treg == breg))
5649	{
5650	  tempreg = AT;
5651	  used_at = 1;
5652	}
5653      else
5654	{
5655	  tempreg = treg;
5656	}
5657
5658      if (offset_expr.X_op != O_symbol
5659	  && offset_expr.X_op != O_constant)
5660	{
5661	  as_bad (_("expression too complex"));
5662	  offset_expr.X_op = O_constant;
5663	}
5664
5665      if (offset_expr.X_op == O_constant)
5666	load_register (tempreg, &offset_expr, HAVE_64BIT_ADDRESSES);
5667      else if (mips_pic == NO_PIC)
5668	{
5669	  /* If this is a reference to a GP relative symbol, we want
5670	       addiu	$tempreg,$gp,<sym>	(BFD_RELOC_GPREL16)
5671	     Otherwise we want
5672	       lui	$tempreg,<sym>		(BFD_RELOC_HI16_S)
5673	       addiu	$tempreg,$tempreg,<sym>	(BFD_RELOC_LO16)
5674	     If we have a constant, we need two instructions anyhow,
5675	     so we may as well always use the latter form.
5676
5677	     With 64bit address space and a usable $at we want
5678	       lui	$tempreg,<sym>		(BFD_RELOC_MIPS_HIGHEST)
5679	       lui	$at,<sym>		(BFD_RELOC_HI16_S)
5680	       daddiu	$tempreg,<sym>		(BFD_RELOC_MIPS_HIGHER)
5681	       daddiu	$at,<sym>		(BFD_RELOC_LO16)
5682	       dsll32	$tempreg,0
5683	       daddu	$tempreg,$tempreg,$at
5684
5685	     If $at is already in use, we use a path which is suboptimal
5686	     on superscalar processors.
5687	       lui	$tempreg,<sym>		(BFD_RELOC_MIPS_HIGHEST)
5688	       daddiu	$tempreg,<sym>		(BFD_RELOC_MIPS_HIGHER)
5689	       dsll	$tempreg,16
5690	       daddiu	$tempreg,<sym>		(BFD_RELOC_HI16_S)
5691	       dsll	$tempreg,16
5692	       daddiu	$tempreg,<sym>		(BFD_RELOC_LO16)
5693
5694	     For GP relative symbols in 64bit address space we can use
5695	     the same sequence as in 32bit address space.  */
5696	  if (HAVE_64BIT_SYMBOLS)
5697	    {
5698	      if ((valueT) offset_expr.X_add_number <= MAX_GPREL_OFFSET
5699		  && !nopic_need_relax (offset_expr.X_add_symbol, 1))
5700		{
5701		  relax_start (offset_expr.X_add_symbol);
5702		  macro_build (&offset_expr, ADDRESS_ADDI_INSN, "t,r,j",
5703			       tempreg, mips_gp_register, BFD_RELOC_GPREL16);
5704		  relax_switch ();
5705		}
5706
5707	      if (used_at == 0 && mips_opts.at)
5708		{
5709		  macro_build (&offset_expr, "lui", "t,u",
5710			       tempreg, BFD_RELOC_MIPS_HIGHEST);
5711		  macro_build (&offset_expr, "lui", "t,u",
5712			       AT, BFD_RELOC_HI16_S);
5713		  macro_build (&offset_expr, "daddiu", "t,r,j",
5714			       tempreg, tempreg, BFD_RELOC_MIPS_HIGHER);
5715		  macro_build (&offset_expr, "daddiu", "t,r,j",
5716			       AT, AT, BFD_RELOC_LO16);
5717		  macro_build (NULL, "dsll32", "d,w,<", tempreg, tempreg, 0);
5718		  macro_build (NULL, "daddu", "d,v,t", tempreg, tempreg, AT);
5719		  used_at = 1;
5720		}
5721	      else
5722		{
5723		  macro_build (&offset_expr, "lui", "t,u",
5724			       tempreg, BFD_RELOC_MIPS_HIGHEST);
5725		  macro_build (&offset_expr, "daddiu", "t,r,j",
5726			       tempreg, tempreg, BFD_RELOC_MIPS_HIGHER);
5727		  macro_build (NULL, "dsll", "d,w,<", tempreg, tempreg, 16);
5728		  macro_build (&offset_expr, "daddiu", "t,r,j",
5729			       tempreg, tempreg, BFD_RELOC_HI16_S);
5730		  macro_build (NULL, "dsll", "d,w,<", tempreg, tempreg, 16);
5731		  macro_build (&offset_expr, "daddiu", "t,r,j",
5732			       tempreg, tempreg, BFD_RELOC_LO16);
5733		}
5734
5735	      if (mips_relax.sequence)
5736		relax_end ();
5737	    }
5738	  else
5739	    {
5740	      if ((valueT) offset_expr.X_add_number <= MAX_GPREL_OFFSET
5741		  && !nopic_need_relax (offset_expr.X_add_symbol, 1))
5742		{
5743		  relax_start (offset_expr.X_add_symbol);
5744		  macro_build (&offset_expr, ADDRESS_ADDI_INSN, "t,r,j",
5745			       tempreg, mips_gp_register, BFD_RELOC_GPREL16);
5746		  relax_switch ();
5747		}
5748	      if (!IS_SEXT_32BIT_NUM (offset_expr.X_add_number))
5749		as_bad (_("offset too large"));
5750	      macro_build_lui (&offset_expr, tempreg);
5751	      macro_build (&offset_expr, ADDRESS_ADDI_INSN, "t,r,j",
5752			   tempreg, tempreg, BFD_RELOC_LO16);
5753	      if (mips_relax.sequence)
5754		relax_end ();
5755	    }
5756	}
5757      else if (!mips_big_got && !HAVE_NEWABI)
5758	{
5759	  int lw_reloc_type = (int) BFD_RELOC_MIPS_GOT16;
5760
5761	  /* If this is a reference to an external symbol, and there
5762	     is no constant, we want
5763	       lw	$tempreg,<sym>($gp)	(BFD_RELOC_MIPS_GOT16)
5764	     or for lca or if tempreg is PIC_CALL_REG
5765	       lw	$tempreg,<sym>($gp)	(BFD_RELOC_MIPS_CALL16)
5766	     For a local symbol, we want
5767	       lw	$tempreg,<sym>($gp)	(BFD_RELOC_MIPS_GOT16)
5768	       nop
5769	       addiu	$tempreg,$tempreg,<sym>	(BFD_RELOC_LO16)
5770
5771	     If we have a small constant, and this is a reference to
5772	     an external symbol, we want
5773	       lw	$tempreg,<sym>($gp)	(BFD_RELOC_MIPS_GOT16)
5774	       nop
5775	       addiu	$tempreg,$tempreg,<constant>
5776	     For a local symbol, we want the same instruction
5777	     sequence, but we output a BFD_RELOC_LO16 reloc on the
5778	     addiu instruction.
5779
5780	     If we have a large constant, and this is a reference to
5781	     an external symbol, we want
5782	       lw	$tempreg,<sym>($gp)	(BFD_RELOC_MIPS_GOT16)
5783	       lui	$at,<hiconstant>
5784	       addiu	$at,$at,<loconstant>
5785	       addu	$tempreg,$tempreg,$at
5786	     For a local symbol, we want the same instruction
5787	     sequence, but we output a BFD_RELOC_LO16 reloc on the
5788	     addiu instruction.
5789	   */
5790
5791	  if (offset_expr.X_add_number == 0)
5792	    {
5793	      if (mips_pic == SVR4_PIC
5794		  && breg == 0
5795		  && (call || tempreg == PIC_CALL_REG))
5796		lw_reloc_type = (int) BFD_RELOC_MIPS_CALL16;
5797
5798	      relax_start (offset_expr.X_add_symbol);
5799	      macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)", tempreg,
5800			   lw_reloc_type, mips_gp_register);
5801	      if (breg != 0)
5802		{
5803		  /* We're going to put in an addu instruction using
5804		     tempreg, so we may as well insert the nop right
5805		     now.  */
5806		  load_delay_nop ();
5807		}
5808	      relax_switch ();
5809	      macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)",
5810			   tempreg, BFD_RELOC_MIPS_GOT16, mips_gp_register);
5811	      load_delay_nop ();
5812	      macro_build (&offset_expr, ADDRESS_ADDI_INSN, "t,r,j",
5813			   tempreg, tempreg, BFD_RELOC_LO16);
5814	      relax_end ();
5815	      /* FIXME: If breg == 0, and the next instruction uses
5816		 $tempreg, then if this variant case is used an extra
5817		 nop will be generated.  */
5818	    }
5819	  else if (offset_expr.X_add_number >= -0x8000
5820		   && offset_expr.X_add_number < 0x8000)
5821	    {
5822	      load_got_offset (tempreg, &offset_expr);
5823	      load_delay_nop ();
5824	      add_got_offset (tempreg, &offset_expr);
5825	    }
5826	  else
5827	    {
5828	      expr1.X_add_number = offset_expr.X_add_number;
5829	      offset_expr.X_add_number =
5830		((offset_expr.X_add_number + 0x8000) & 0xffff) - 0x8000;
5831	      load_got_offset (tempreg, &offset_expr);
5832	      offset_expr.X_add_number = expr1.X_add_number;
5833	      /* If we are going to add in a base register, and the
5834		 target register and the base register are the same,
5835		 then we are using AT as a temporary register.  Since
5836		 we want to load the constant into AT, we add our
5837		 current AT (from the global offset table) and the
5838		 register into the register now, and pretend we were
5839		 not using a base register.  */
5840	      if (breg == treg)
5841		{
5842		  load_delay_nop ();
5843		  macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
5844			       treg, AT, breg);
5845		  breg = 0;
5846		  tempreg = treg;
5847		}
5848	      add_got_offset_hilo (tempreg, &offset_expr, AT);
5849	      used_at = 1;
5850	    }
5851	}
5852      else if (!mips_big_got && HAVE_NEWABI)
5853	{
5854	  int add_breg_early = 0;
5855
5856	  /* If this is a reference to an external, and there is no
5857	     constant, or local symbol (*), with or without a
5858	     constant, we want
5859	       lw	$tempreg,<sym>($gp)	(BFD_RELOC_MIPS_GOT_DISP)
5860	     or for lca or if tempreg is PIC_CALL_REG
5861	       lw	$tempreg,<sym>($gp)	(BFD_RELOC_MIPS_CALL16)
5862
5863	     If we have a small constant, and this is a reference to
5864	     an external symbol, we want
5865	       lw	$tempreg,<sym>($gp)	(BFD_RELOC_MIPS_GOT_DISP)
5866	       addiu	$tempreg,$tempreg,<constant>
5867
5868	     If we have a large constant, and this is a reference to
5869	     an external symbol, we want
5870	       lw	$tempreg,<sym>($gp)	(BFD_RELOC_MIPS_GOT_DISP)
5871	       lui	$at,<hiconstant>
5872	       addiu	$at,$at,<loconstant>
5873	       addu	$tempreg,$tempreg,$at
5874
5875	     (*) Other assemblers seem to prefer GOT_PAGE/GOT_OFST for
5876	     local symbols, even though it introduces an additional
5877	     instruction.  */
5878
5879	  if (offset_expr.X_add_number)
5880	    {
5881	      expr1.X_add_number = offset_expr.X_add_number;
5882	      offset_expr.X_add_number = 0;
5883
5884	      relax_start (offset_expr.X_add_symbol);
5885	      macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)", tempreg,
5886			   BFD_RELOC_MIPS_GOT_DISP, mips_gp_register);
5887
5888	      if (expr1.X_add_number >= -0x8000
5889		  && expr1.X_add_number < 0x8000)
5890		{
5891		  macro_build (&expr1, ADDRESS_ADDI_INSN, "t,r,j",
5892			       tempreg, tempreg, BFD_RELOC_LO16);
5893		}
5894	      else if (IS_SEXT_32BIT_NUM (expr1.X_add_number + 0x8000))
5895		{
5896		  /* If we are going to add in a base register, and the
5897		     target register and the base register are the same,
5898		     then we are using AT as a temporary register.  Since
5899		     we want to load the constant into AT, we add our
5900		     current AT (from the global offset table) and the
5901		     register into the register now, and pretend we were
5902		     not using a base register.  */
5903		  if (breg != treg)
5904		    dreg = tempreg;
5905		  else
5906		    {
5907		      gas_assert (tempreg == AT);
5908		      macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
5909				   treg, AT, breg);
5910		      dreg = treg;
5911		      add_breg_early = 1;
5912		    }
5913
5914		  load_register (AT, &expr1, HAVE_64BIT_ADDRESSES);
5915		  macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
5916			       dreg, dreg, AT);
5917
5918		  used_at = 1;
5919		}
5920	      else
5921		as_bad (_("PIC code offset overflow (max 32 signed bits)"));
5922
5923	      relax_switch ();
5924	      offset_expr.X_add_number = expr1.X_add_number;
5925
5926	      macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)", tempreg,
5927			   BFD_RELOC_MIPS_GOT_DISP, mips_gp_register);
5928	      if (add_breg_early)
5929		{
5930		  macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
5931			       treg, tempreg, breg);
5932		  breg = 0;
5933		  tempreg = treg;
5934		}
5935	      relax_end ();
5936	    }
5937	  else if (breg == 0 && (call || tempreg == PIC_CALL_REG))
5938	    {
5939	      relax_start (offset_expr.X_add_symbol);
5940	      macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)", tempreg,
5941			   BFD_RELOC_MIPS_CALL16, mips_gp_register);
5942	      relax_switch ();
5943	      macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)", tempreg,
5944			   BFD_RELOC_MIPS_GOT_DISP, mips_gp_register);
5945	      relax_end ();
5946	    }
5947	  else
5948	    {
5949	      macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)", tempreg,
5950			   BFD_RELOC_MIPS_GOT_DISP, mips_gp_register);
5951	    }
5952	}
5953      else if (mips_big_got && !HAVE_NEWABI)
5954	{
5955	  int gpdelay;
5956	  int lui_reloc_type = (int) BFD_RELOC_MIPS_GOT_HI16;
5957	  int lw_reloc_type = (int) BFD_RELOC_MIPS_GOT_LO16;
5958	  int local_reloc_type = (int) BFD_RELOC_MIPS_GOT16;
5959
5960	  /* This is the large GOT case.  If this is a reference to an
5961	     external symbol, and there is no constant, we want
5962	       lui	$tempreg,<sym>		(BFD_RELOC_MIPS_GOT_HI16)
5963	       addu	$tempreg,$tempreg,$gp
5964	       lw	$tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_LO16)
5965	     or for lca or if tempreg is PIC_CALL_REG
5966	       lui	$tempreg,<sym>		(BFD_RELOC_MIPS_CALL_HI16)
5967	       addu	$tempreg,$tempreg,$gp
5968	       lw	$tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_CALL_LO16)
5969	     For a local symbol, we want
5970	       lw	$tempreg,<sym>($gp)	(BFD_RELOC_MIPS_GOT16)
5971	       nop
5972	       addiu	$tempreg,$tempreg,<sym>	(BFD_RELOC_LO16)
5973
5974	     If we have a small constant, and this is a reference to
5975	     an external symbol, we want
5976	       lui	$tempreg,<sym>		(BFD_RELOC_MIPS_GOT_HI16)
5977	       addu	$tempreg,$tempreg,$gp
5978	       lw	$tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_LO16)
5979	       nop
5980	       addiu	$tempreg,$tempreg,<constant>
5981	     For a local symbol, we want
5982	       lw	$tempreg,<sym>($gp)	(BFD_RELOC_MIPS_GOT16)
5983	       nop
5984	       addiu	$tempreg,$tempreg,<constant> (BFD_RELOC_LO16)
5985
5986	     If we have a large constant, and this is a reference to
5987	     an external symbol, we want
5988	       lui	$tempreg,<sym>		(BFD_RELOC_MIPS_GOT_HI16)
5989	       addu	$tempreg,$tempreg,$gp
5990	       lw	$tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_LO16)
5991	       lui	$at,<hiconstant>
5992	       addiu	$at,$at,<loconstant>
5993	       addu	$tempreg,$tempreg,$at
5994	     For a local symbol, we want
5995	       lw	$tempreg,<sym>($gp)	(BFD_RELOC_MIPS_GOT16)
5996	       lui	$at,<hiconstant>
5997	       addiu	$at,$at,<loconstant>	(BFD_RELOC_LO16)
5998	       addu	$tempreg,$tempreg,$at
5999	  */
6000
6001	  expr1.X_add_number = offset_expr.X_add_number;
6002	  offset_expr.X_add_number = 0;
6003	  relax_start (offset_expr.X_add_symbol);
6004	  gpdelay = reg_needs_delay (mips_gp_register);
6005	  if (expr1.X_add_number == 0 && breg == 0
6006	      && (call || tempreg == PIC_CALL_REG))
6007	    {
6008	      lui_reloc_type = (int) BFD_RELOC_MIPS_CALL_HI16;
6009	      lw_reloc_type = (int) BFD_RELOC_MIPS_CALL_LO16;
6010	    }
6011	  macro_build (&offset_expr, "lui", "t,u", tempreg, lui_reloc_type);
6012	  macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
6013		       tempreg, tempreg, mips_gp_register);
6014	  macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)",
6015		       tempreg, lw_reloc_type, tempreg);
6016	  if (expr1.X_add_number == 0)
6017	    {
6018	      if (breg != 0)
6019		{
6020		  /* We're going to put in an addu instruction using
6021		     tempreg, so we may as well insert the nop right
6022		     now.  */
6023		  load_delay_nop ();
6024		}
6025	    }
6026	  else if (expr1.X_add_number >= -0x8000
6027		   && expr1.X_add_number < 0x8000)
6028	    {
6029	      load_delay_nop ();
6030	      macro_build (&expr1, ADDRESS_ADDI_INSN, "t,r,j",
6031			   tempreg, tempreg, BFD_RELOC_LO16);
6032	    }
6033	  else
6034	    {
6035	      /* If we are going to add in a base register, and the
6036		 target register and the base register are the same,
6037		 then we are using AT as a temporary register.  Since
6038		 we want to load the constant into AT, we add our
6039		 current AT (from the global offset table) and the
6040		 register into the register now, and pretend we were
6041		 not using a base register.  */
6042	      if (breg != treg)
6043		dreg = tempreg;
6044	      else
6045		{
6046		  gas_assert (tempreg == AT);
6047		  load_delay_nop ();
6048		  macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
6049			       treg, AT, breg);
6050		  dreg = treg;
6051		}
6052
6053	      load_register (AT, &expr1, HAVE_64BIT_ADDRESSES);
6054	      macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", dreg, dreg, AT);
6055
6056	      used_at = 1;
6057	    }
6058	  offset_expr.X_add_number =
6059	    ((expr1.X_add_number + 0x8000) & 0xffff) - 0x8000;
6060	  relax_switch ();
6061
6062	  if (gpdelay)
6063	    {
6064	      /* This is needed because this instruction uses $gp, but
6065		 the first instruction on the main stream does not.  */
6066	      macro_build (NULL, "nop", "");
6067	    }
6068
6069	  macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)", tempreg,
6070		       local_reloc_type, mips_gp_register);
6071	  if (expr1.X_add_number >= -0x8000
6072	      && expr1.X_add_number < 0x8000)
6073	    {
6074	      load_delay_nop ();
6075	      macro_build (&offset_expr, ADDRESS_ADDI_INSN, "t,r,j",
6076			   tempreg, tempreg, BFD_RELOC_LO16);
6077	      /* FIXME: If add_number is 0, and there was no base
6078		 register, the external symbol case ended with a load,
6079		 so if the symbol turns out to not be external, and
6080		 the next instruction uses tempreg, an unnecessary nop
6081		 will be inserted.  */
6082	    }
6083	  else
6084	    {
6085	      if (breg == treg)
6086		{
6087		  /* We must add in the base register now, as in the
6088		     external symbol case.  */
6089		  gas_assert (tempreg == AT);
6090		  load_delay_nop ();
6091		  macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
6092			       treg, AT, breg);
6093		  tempreg = treg;
6094		  /* We set breg to 0 because we have arranged to add
6095		     it in in both cases.  */
6096		  breg = 0;
6097		}
6098
6099	      macro_build_lui (&expr1, AT);
6100	      macro_build (&offset_expr, ADDRESS_ADDI_INSN, "t,r,j",
6101			   AT, AT, BFD_RELOC_LO16);
6102	      macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
6103			   tempreg, tempreg, AT);
6104	      used_at = 1;
6105	    }
6106	  relax_end ();
6107	}
6108      else if (mips_big_got && HAVE_NEWABI)
6109	{
6110	  int lui_reloc_type = (int) BFD_RELOC_MIPS_GOT_HI16;
6111	  int lw_reloc_type = (int) BFD_RELOC_MIPS_GOT_LO16;
6112	  int add_breg_early = 0;
6113
6114	  /* This is the large GOT case.  If this is a reference to an
6115	     external symbol, and there is no constant, we want
6116	       lui	$tempreg,<sym>		(BFD_RELOC_MIPS_GOT_HI16)
6117	       add	$tempreg,$tempreg,$gp
6118	       lw	$tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_LO16)
6119	     or for lca or if tempreg is PIC_CALL_REG
6120	       lui	$tempreg,<sym>		(BFD_RELOC_MIPS_CALL_HI16)
6121	       add	$tempreg,$tempreg,$gp
6122	       lw	$tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_CALL_LO16)
6123
6124	     If we have a small constant, and this is a reference to
6125	     an external symbol, we want
6126	       lui	$tempreg,<sym>		(BFD_RELOC_MIPS_GOT_HI16)
6127	       add	$tempreg,$tempreg,$gp
6128	       lw	$tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_LO16)
6129	       addi	$tempreg,$tempreg,<constant>
6130
6131	     If we have a large constant, and this is a reference to
6132	     an external symbol, we want
6133	       lui	$tempreg,<sym>		(BFD_RELOC_MIPS_GOT_HI16)
6134	       addu	$tempreg,$tempreg,$gp
6135	       lw	$tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_LO16)
6136	       lui	$at,<hiconstant>
6137	       addi	$at,$at,<loconstant>
6138	       add	$tempreg,$tempreg,$at
6139
6140	     If we have NewABI, and we know it's a local symbol, we want
6141	       lw	$reg,<sym>($gp)		(BFD_RELOC_MIPS_GOT_PAGE)
6142	       addiu	$reg,$reg,<sym>		(BFD_RELOC_MIPS_GOT_OFST)
6143	     otherwise we have to resort to GOT_HI16/GOT_LO16.  */
6144
6145	  relax_start (offset_expr.X_add_symbol);
6146
6147	  expr1.X_add_number = offset_expr.X_add_number;
6148	  offset_expr.X_add_number = 0;
6149
6150	  if (expr1.X_add_number == 0 && breg == 0
6151	      && (call || tempreg == PIC_CALL_REG))
6152	    {
6153	      lui_reloc_type = (int) BFD_RELOC_MIPS_CALL_HI16;
6154	      lw_reloc_type = (int) BFD_RELOC_MIPS_CALL_LO16;
6155	    }
6156	  macro_build (&offset_expr, "lui", "t,u", tempreg, lui_reloc_type);
6157	  macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
6158		       tempreg, tempreg, mips_gp_register);
6159	  macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)",
6160		       tempreg, lw_reloc_type, tempreg);
6161
6162	  if (expr1.X_add_number == 0)
6163	    ;
6164	  else if (expr1.X_add_number >= -0x8000
6165		   && expr1.X_add_number < 0x8000)
6166	    {
6167	      macro_build (&expr1, ADDRESS_ADDI_INSN, "t,r,j",
6168			   tempreg, tempreg, BFD_RELOC_LO16);
6169	    }
6170	  else if (IS_SEXT_32BIT_NUM (expr1.X_add_number + 0x8000))
6171	    {
6172	      /* If we are going to add in a base register, and the
6173		 target register and the base register are the same,
6174		 then we are using AT as a temporary register.  Since
6175		 we want to load the constant into AT, we add our
6176		 current AT (from the global offset table) and the
6177		 register into the register now, and pretend we were
6178		 not using a base register.  */
6179	      if (breg != treg)
6180		dreg = tempreg;
6181	      else
6182		{
6183		  gas_assert (tempreg == AT);
6184		  macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
6185			       treg, AT, breg);
6186		  dreg = treg;
6187		  add_breg_early = 1;
6188		}
6189
6190	      load_register (AT, &expr1, HAVE_64BIT_ADDRESSES);
6191	      macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", dreg, dreg, AT);
6192
6193	      used_at = 1;
6194	    }
6195	  else
6196	    as_bad (_("PIC code offset overflow (max 32 signed bits)"));
6197
6198	  relax_switch ();
6199	  offset_expr.X_add_number = expr1.X_add_number;
6200	  macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)", tempreg,
6201		       BFD_RELOC_MIPS_GOT_PAGE, mips_gp_register);
6202	  macro_build (&offset_expr, ADDRESS_ADDI_INSN, "t,r,j", tempreg,
6203		       tempreg, BFD_RELOC_MIPS_GOT_OFST);
6204	  if (add_breg_early)
6205	    {
6206	      macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
6207			   treg, tempreg, breg);
6208	      breg = 0;
6209	      tempreg = treg;
6210	    }
6211	  relax_end ();
6212	}
6213      else
6214	abort ();
6215
6216      if (breg != 0)
6217	macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", treg, tempreg, breg);
6218      break;
6219
6220    case M_JR_S:
6221      macro_build_jrpatch (&expr1, sreg);
6222      macro_build (NULL, "jr", "s", sreg);
6223      return;	/* didn't modify $at */
6224
6225    case M_J_S:
6226      macro_build_jrpatch (&expr1, sreg);
6227      macro_build (NULL, "j", "s", sreg);
6228      return;	/* didn't modify $at */
6229
6230    case M_JALR_S:
6231      macro_build_jrpatch (&expr1, sreg);
6232      macro_build (NULL, "jalr", "s", sreg);
6233      return;	/* didn't modify $at */
6234
6235    case M_JALR_DS:
6236      macro_build_jrpatch (&expr1, sreg);
6237      macro_build (NULL, "jalr", "d,s", dreg, sreg);
6238      return;	/* didn't modify $at */
6239
6240    case M_MSGSND:
6241      {
6242	unsigned long temp = (treg << 16) | (0x01);
6243	macro_build (NULL, "c2", "C", temp);
6244      }
6245      /* AT is not used, just return */
6246      return;
6247
6248    case M_MSGLD:
6249      {
6250	unsigned long temp = (0x02);
6251	macro_build (NULL, "c2", "C", temp);
6252      }
6253      /* AT is not used, just return */
6254      return;
6255
6256    case M_MSGLD_T:
6257      {
6258	unsigned long temp = (treg << 16) | (0x02);
6259	macro_build (NULL, "c2", "C", temp);
6260      }
6261      /* AT is not used, just return */
6262      return;
6263
6264    case M_MSGWAIT:
6265      macro_build (NULL, "c2", "C", 3);
6266      /* AT is not used, just return */
6267      return;
6268
6269    case M_MSGWAIT_T:
6270      {
6271	unsigned long temp = (treg << 16) | 0x03;
6272	macro_build (NULL, "c2", "C", temp);
6273      }
6274      /* AT is not used, just return */
6275      return;
6276
6277    case M_J_A:
6278      /* The j instruction may not be used in PIC code, since it
6279	 requires an absolute address.  We convert it to a b
6280	 instruction.  */
6281      if (mips_pic == NO_PIC)
6282	macro_build (&offset_expr, "j", "a");
6283      else
6284	macro_build (&offset_expr, "b", "p");
6285      break;
6286
6287      /* The jal instructions must be handled as macros because when
6288	 generating PIC code they expand to multi-instruction
6289	 sequences.  Normally they are simple instructions.  */
6290    case M_JAL_1:
6291      dreg = RA;
6292      /* Fall through.  */
6293    case M_JAL_2:
6294      if (mips_pic == NO_PIC)
6295	{
6296	  macro_build_jrpatch (&expr1, sreg);
6297	  macro_build (NULL, "jalr", "d,s", dreg, sreg);
6298	}
6299      else
6300	{
6301	  if (sreg != PIC_CALL_REG)
6302	    as_warn (_("MIPS PIC call to register other than $25"));
6303
6304	  macro_build_jrpatch (&expr1, sreg);
6305	  macro_build (NULL, "jalr", "d,s", dreg, sreg);
6306	  if (mips_pic == SVR4_PIC && !HAVE_NEWABI)
6307	    {
6308	      if (mips_cprestore_offset < 0)
6309		as_warn (_("No .cprestore pseudo-op used in PIC code"));
6310	      else
6311		{
6312		  if (! mips_frame_reg_valid)
6313		    {
6314		      as_warn (_("No .frame pseudo-op used in PIC code"));
6315		      /* Quiet this warning.  */
6316		      mips_frame_reg_valid = 1;
6317		    }
6318		  if (! mips_cprestore_valid)
6319		    {
6320		      as_warn (_("No .cprestore pseudo-op used in PIC code"));
6321		      /* Quiet this warning.  */
6322		      mips_cprestore_valid = 1;
6323		    }
6324		  if (mips_opts.noreorder)
6325		    macro_build (NULL, "nop", "");
6326		  expr1.X_add_number = mips_cprestore_offset;
6327  		  macro_build_ldst_constoffset (&expr1, ADDRESS_LOAD_INSN,
6328						mips_gp_register,
6329						mips_frame_reg,
6330						HAVE_64BIT_ADDRESSES);
6331		}
6332	    }
6333	}
6334
6335      break;
6336
6337    case M_JAL_A:
6338      if (mips_pic == NO_PIC)
6339	macro_build (&offset_expr, "jal", "a");
6340      else if (mips_pic == SVR4_PIC)
6341	{
6342	  /* If this is a reference to an external symbol, and we are
6343	     using a small GOT, we want
6344	       lw	$25,<sym>($gp)		(BFD_RELOC_MIPS_CALL16)
6345	       nop
6346	       jalr	$ra,$25
6347	       nop
6348	       lw	$gp,cprestore($sp)
6349	     The cprestore value is set using the .cprestore
6350	     pseudo-op.  If we are using a big GOT, we want
6351	       lui	$25,<sym>		(BFD_RELOC_MIPS_CALL_HI16)
6352	       addu	$25,$25,$gp
6353	       lw	$25,<sym>($25)		(BFD_RELOC_MIPS_CALL_LO16)
6354	       nop
6355	       jalr	$ra,$25
6356	       nop
6357	       lw	$gp,cprestore($sp)
6358	     If the symbol is not external, we want
6359	       lw	$25,<sym>($gp)		(BFD_RELOC_MIPS_GOT16)
6360	       nop
6361	       addiu	$25,$25,<sym>		(BFD_RELOC_LO16)
6362	       jalr	$ra,$25
6363	       nop
6364	       lw $gp,cprestore($sp)
6365
6366	     For NewABI, we use the same CALL16 or CALL_HI16/CALL_LO16
6367	     sequences above, minus nops, unless the symbol is local,
6368	     which enables us to use GOT_PAGE/GOT_OFST (big got) or
6369	     GOT_DISP.  */
6370	  if (HAVE_NEWABI)
6371	    {
6372	      if (! mips_big_got)
6373		{
6374		  relax_start (offset_expr.X_add_symbol);
6375		  macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)",
6376			       PIC_CALL_REG, BFD_RELOC_MIPS_CALL16,
6377			       mips_gp_register);
6378		  relax_switch ();
6379		  macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)",
6380			       PIC_CALL_REG, BFD_RELOC_MIPS_GOT_DISP,
6381			       mips_gp_register);
6382		  relax_end ();
6383		}
6384	      else
6385		{
6386		  relax_start (offset_expr.X_add_symbol);
6387		  macro_build (&offset_expr, "lui", "t,u", PIC_CALL_REG,
6388			       BFD_RELOC_MIPS_CALL_HI16);
6389		  macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", PIC_CALL_REG,
6390			       PIC_CALL_REG, mips_gp_register);
6391		  macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)",
6392			       PIC_CALL_REG, BFD_RELOC_MIPS_CALL_LO16,
6393			       PIC_CALL_REG);
6394		  relax_switch ();
6395		  macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)",
6396			       PIC_CALL_REG, BFD_RELOC_MIPS_GOT_PAGE,
6397			       mips_gp_register);
6398		  macro_build (&offset_expr, ADDRESS_ADDI_INSN, "t,r,j",
6399			       PIC_CALL_REG, PIC_CALL_REG,
6400			       BFD_RELOC_MIPS_GOT_OFST);
6401		  relax_end ();
6402		}
6403
6404	      macro_build_jalr (&offset_expr);
6405	    }
6406	  else
6407	    {
6408	      relax_start (offset_expr.X_add_symbol);
6409	      if (! mips_big_got)
6410		{
6411		  macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)",
6412			       PIC_CALL_REG, BFD_RELOC_MIPS_CALL16,
6413			       mips_gp_register);
6414		  load_delay_nop ();
6415		  relax_switch ();
6416		}
6417	      else
6418		{
6419		  int gpdelay;
6420
6421		  gpdelay = reg_needs_delay (mips_gp_register);
6422		  macro_build (&offset_expr, "lui", "t,u", PIC_CALL_REG,
6423			       BFD_RELOC_MIPS_CALL_HI16);
6424		  macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", PIC_CALL_REG,
6425			       PIC_CALL_REG, mips_gp_register);
6426		  macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)",
6427			       PIC_CALL_REG, BFD_RELOC_MIPS_CALL_LO16,
6428			       PIC_CALL_REG);
6429		  load_delay_nop ();
6430		  relax_switch ();
6431		  if (gpdelay)
6432		    macro_build (NULL, "nop", "");
6433		}
6434	      macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)",
6435			   PIC_CALL_REG, BFD_RELOC_MIPS_GOT16,
6436			   mips_gp_register);
6437	      load_delay_nop ();
6438	      macro_build (&offset_expr, ADDRESS_ADDI_INSN, "t,r,j",
6439			   PIC_CALL_REG, PIC_CALL_REG, BFD_RELOC_LO16);
6440	      relax_end ();
6441	      macro_build_jalr (&offset_expr);
6442
6443	      if (mips_cprestore_offset < 0)
6444		as_warn (_("No .cprestore pseudo-op used in PIC code"));
6445	      else
6446		{
6447		  if (! mips_frame_reg_valid)
6448		    {
6449		      as_warn (_("No .frame pseudo-op used in PIC code"));
6450		      /* Quiet this warning.  */
6451		      mips_frame_reg_valid = 1;
6452		    }
6453		  if (! mips_cprestore_valid)
6454		    {
6455		      as_warn (_("No .cprestore pseudo-op used in PIC code"));
6456		      /* Quiet this warning.  */
6457		      mips_cprestore_valid = 1;
6458		    }
6459		  if (mips_opts.noreorder)
6460		    macro_build (NULL, "nop", "");
6461		  expr1.X_add_number = mips_cprestore_offset;
6462  		  macro_build_ldst_constoffset (&expr1, ADDRESS_LOAD_INSN,
6463						mips_gp_register,
6464						mips_frame_reg,
6465						HAVE_64BIT_ADDRESSES);
6466		}
6467	    }
6468	}
6469      else if (mips_pic == VXWORKS_PIC)
6470	as_bad (_("Non-PIC jump used in PIC library"));
6471      else
6472	abort ();
6473
6474      break;
6475
6476    case M_LB_AB:
6477      s = "lb";
6478      goto ld;
6479    case M_LBU_AB:
6480      s = "lbu";
6481      goto ld;
6482    case M_LH_AB:
6483      s = "lh";
6484      goto ld;
6485    case M_LHU_AB:
6486      s = "lhu";
6487      goto ld;
6488    case M_LW_AB:
6489      s = "lw";
6490      goto ld;
6491    case M_LWC0_AB:
6492      s = "lwc0";
6493      /* Itbl support may require additional care here.  */
6494      coproc = 1;
6495      goto ld;
6496    case M_LWC1_AB:
6497      s = "lwc1";
6498      /* Itbl support may require additional care here.  */
6499      coproc = 1;
6500      goto ld;
6501    case M_LWC2_AB:
6502      s = "lwc2";
6503      /* Itbl support may require additional care here.  */
6504      coproc = 1;
6505      goto ld;
6506    case M_LWC3_AB:
6507      s = "lwc3";
6508      /* Itbl support may require additional care here.  */
6509      coproc = 1;
6510      goto ld;
6511    case M_LWL_AB:
6512      s = "lwl";
6513      lr = 1;
6514      goto ld;
6515    case M_LWR_AB:
6516      s = "lwr";
6517      lr = 1;
6518      goto ld;
6519    case M_LDC1_AB:
6520      s = "ldc1";
6521      /* Itbl support may require additional care here.  */
6522      coproc = 1;
6523      goto ld;
6524    case M_LDC2_AB:
6525      s = "ldc2";
6526      /* Itbl support may require additional care here.  */
6527      coproc = 1;
6528      goto ld;
6529    case M_LDC3_AB:
6530      s = "ldc3";
6531      /* Itbl support may require additional care here.  */
6532      coproc = 1;
6533      goto ld;
6534    case M_LDL_AB:
6535      s = "ldl";
6536      lr = 1;
6537      goto ld;
6538    case M_LDR_AB:
6539      s = "ldr";
6540      lr = 1;
6541      goto ld;
6542    case M_LL_AB:
6543      s = "ll";
6544      goto ld;
6545    case M_LLD_AB:
6546      s = "lld";
6547      goto ld;
6548    case M_LWU_AB:
6549      s = "lwu";
6550    ld:
6551      if (breg == treg || coproc || lr)
6552	{
6553	  tempreg = AT;
6554	  used_at = 1;
6555	}
6556      else
6557	{
6558	  tempreg = treg;
6559	}
6560      goto ld_st;
6561    case M_SB_AB:
6562      s = "sb";
6563      goto st;
6564    case M_SH_AB:
6565      s = "sh";
6566      goto st;
6567    case M_SW_AB:
6568      s = "sw";
6569      goto st;
6570    case M_SWC0_AB:
6571      s = "swc0";
6572      /* Itbl support may require additional care here.  */
6573      coproc = 1;
6574      goto st;
6575    case M_SWC1_AB:
6576      s = "swc1";
6577      /* Itbl support may require additional care here.  */
6578      coproc = 1;
6579      goto st;
6580    case M_SWC2_AB:
6581      s = "swc2";
6582      /* Itbl support may require additional care here.  */
6583      coproc = 1;
6584      goto st;
6585    case M_SWC3_AB:
6586      s = "swc3";
6587      /* Itbl support may require additional care here.  */
6588      coproc = 1;
6589      goto st;
6590    case M_SWL_AB:
6591      s = "swl";
6592      goto st;
6593    case M_SWR_AB:
6594      s = "swr";
6595      goto st;
6596    case M_SC_AB:
6597      s = "sc";
6598      goto st;
6599    case M_SCD_AB:
6600      s = "scd";
6601      goto st;
6602    case M_CACHE_AB:
6603      s = "cache";
6604      goto st;
6605    case M_SDC1_AB:
6606      s = "sdc1";
6607      coproc = 1;
6608      /* Itbl support may require additional care here.  */
6609      goto st;
6610    case M_SDC2_AB:
6611      s = "sdc2";
6612      /* Itbl support may require additional care here.  */
6613      coproc = 1;
6614      goto st;
6615    case M_SDC3_AB:
6616      s = "sdc3";
6617      /* Itbl support may require additional care here.  */
6618      coproc = 1;
6619      goto st;
6620    case M_SDL_AB:
6621      s = "sdl";
6622      goto st;
6623    case M_SDR_AB:
6624      s = "sdr";
6625    st:
6626      tempreg = AT;
6627      used_at = 1;
6628    ld_st:
6629      if (coproc
6630	  && NO_ISA_COP (mips_opts.arch)
6631	  && (ip->insn_mo->pinfo2 & (INSN2_M_FP_S | INSN2_M_FP_D)) == 0)
6632	{
6633	  as_bad (_("opcode not supported on this processor: %s"),
6634		  mips_cpu_info_from_arch (mips_opts.arch)->name);
6635	  break;
6636	}
6637
6638      /* Itbl support may require additional care here.  */
6639      if (mask == M_LWC1_AB
6640	  || mask == M_SWC1_AB
6641	  || mask == M_LDC1_AB
6642	  || mask == M_SDC1_AB
6643	  || mask == M_L_DAB
6644	  || mask == M_S_DAB)
6645	fmt = "T,o(b)";
6646      else if (mask == M_CACHE_AB)
6647	fmt = "k,o(b)";
6648      else if (coproc)
6649	fmt = "E,o(b)";
6650      else
6651	fmt = "t,o(b)";
6652
6653      if (offset_expr.X_op != O_constant
6654	  && offset_expr.X_op != O_symbol)
6655	{
6656	  as_bad (_("expression too complex"));
6657	  offset_expr.X_op = O_constant;
6658	}
6659
6660      if (HAVE_32BIT_ADDRESSES
6661	  && !IS_SEXT_32BIT_NUM (offset_expr.X_add_number))
6662	{
6663	  char value [32];
6664
6665	  sprintf_vma (value, offset_expr.X_add_number);
6666	  as_bad (_("Number (0x%s) larger than 32 bits"), value);
6667	}
6668
6669      /* A constant expression in PIC code can be handled just as it
6670	 is in non PIC code.  */
6671      if (offset_expr.X_op == O_constant)
6672	{
6673	  expr1.X_add_number = ((offset_expr.X_add_number + 0x8000)
6674				& ~(bfd_vma) 0xffff);
6675	  normalize_address_expr (&expr1);
6676	  load_register (tempreg, &expr1, HAVE_64BIT_ADDRESSES);
6677	  if (breg != 0)
6678	    macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
6679			 tempreg, tempreg, breg);
6680	  macro_build (&offset_expr, s, fmt, treg, BFD_RELOC_LO16, tempreg);
6681	}
6682      else if (mips_pic == NO_PIC)
6683	{
6684	  /* If this is a reference to a GP relative symbol, and there
6685	     is no base register, we want
6686	       <op>	$treg,<sym>($gp)	(BFD_RELOC_GPREL16)
6687	     Otherwise, if there is no base register, we want
6688	       lui	$tempreg,<sym>		(BFD_RELOC_HI16_S)
6689	       <op>	$treg,<sym>($tempreg)	(BFD_RELOC_LO16)
6690	     If we have a constant, we need two instructions anyhow,
6691	     so we always use the latter form.
6692
6693	     If we have a base register, and this is a reference to a
6694	     GP relative symbol, we want
6695	       addu	$tempreg,$breg,$gp
6696	       <op>	$treg,<sym>($tempreg)	(BFD_RELOC_GPREL16)
6697	     Otherwise we want
6698	       lui	$tempreg,<sym>		(BFD_RELOC_HI16_S)
6699	       addu	$tempreg,$tempreg,$breg
6700	       <op>	$treg,<sym>($tempreg)	(BFD_RELOC_LO16)
6701	     With a constant we always use the latter case.
6702
6703	     With 64bit address space and no base register and $at usable,
6704	     we want
6705	       lui	$tempreg,<sym>		(BFD_RELOC_MIPS_HIGHEST)
6706	       lui	$at,<sym>		(BFD_RELOC_HI16_S)
6707	       daddiu	$tempreg,<sym>		(BFD_RELOC_MIPS_HIGHER)
6708	       dsll32	$tempreg,0
6709	       daddu	$tempreg,$at
6710	       <op>	$treg,<sym>($tempreg)	(BFD_RELOC_LO16)
6711	     If we have a base register, we want
6712	       lui	$tempreg,<sym>		(BFD_RELOC_MIPS_HIGHEST)
6713	       lui	$at,<sym>		(BFD_RELOC_HI16_S)
6714	       daddiu	$tempreg,<sym>		(BFD_RELOC_MIPS_HIGHER)
6715	       daddu	$at,$breg
6716	       dsll32	$tempreg,0
6717	       daddu	$tempreg,$at
6718	       <op>	$treg,<sym>($tempreg)	(BFD_RELOC_LO16)
6719
6720	     Without $at we can't generate the optimal path for superscalar
6721	     processors here since this would require two temporary registers.
6722	       lui	$tempreg,<sym>		(BFD_RELOC_MIPS_HIGHEST)
6723	       daddiu	$tempreg,<sym>		(BFD_RELOC_MIPS_HIGHER)
6724	       dsll	$tempreg,16
6725	       daddiu	$tempreg,<sym>		(BFD_RELOC_HI16_S)
6726	       dsll	$tempreg,16
6727	       <op>	$treg,<sym>($tempreg)	(BFD_RELOC_LO16)
6728	     If we have a base register, we want
6729	       lui	$tempreg,<sym>		(BFD_RELOC_MIPS_HIGHEST)
6730	       daddiu	$tempreg,<sym>		(BFD_RELOC_MIPS_HIGHER)
6731	       dsll	$tempreg,16
6732	       daddiu	$tempreg,<sym>		(BFD_RELOC_HI16_S)
6733	       dsll	$tempreg,16
6734	       daddu	$tempreg,$tempreg,$breg
6735	       <op>	$treg,<sym>($tempreg)	(BFD_RELOC_LO16)
6736
6737	     For GP relative symbols in 64bit address space we can use
6738	     the same sequence as in 32bit address space.  */
6739	  if (HAVE_64BIT_SYMBOLS)
6740	    {
6741	      if ((valueT) offset_expr.X_add_number <= MAX_GPREL_OFFSET
6742		  && !nopic_need_relax (offset_expr.X_add_symbol, 1))
6743		{
6744		  relax_start (offset_expr.X_add_symbol);
6745		  if (breg == 0)
6746		    {
6747		      macro_build (&offset_expr, s, fmt, treg,
6748				   BFD_RELOC_GPREL16, mips_gp_register);
6749		    }
6750		  else
6751		    {
6752		      macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
6753				   tempreg, breg, mips_gp_register);
6754		      macro_build (&offset_expr, s, fmt, treg,
6755				   BFD_RELOC_GPREL16, tempreg);
6756		    }
6757		  relax_switch ();
6758		}
6759
6760	      if (used_at == 0 && mips_opts.at)
6761		{
6762		  macro_build (&offset_expr, "lui", "t,u", tempreg,
6763			       BFD_RELOC_MIPS_HIGHEST);
6764		  macro_build (&offset_expr, "lui", "t,u", AT,
6765			       BFD_RELOC_HI16_S);
6766		  macro_build (&offset_expr, "daddiu", "t,r,j", tempreg,
6767			       tempreg, BFD_RELOC_MIPS_HIGHER);
6768		  if (breg != 0)
6769		    macro_build (NULL, "daddu", "d,v,t", AT, AT, breg);
6770		  macro_build (NULL, "dsll32", "d,w,<", tempreg, tempreg, 0);
6771		  macro_build (NULL, "daddu", "d,v,t", tempreg, tempreg, AT);
6772		  macro_build (&offset_expr, s, fmt, treg, BFD_RELOC_LO16,
6773			       tempreg);
6774		  used_at = 1;
6775		}
6776	      else
6777		{
6778		  macro_build (&offset_expr, "lui", "t,u", tempreg,
6779			       BFD_RELOC_MIPS_HIGHEST);
6780		  macro_build (&offset_expr, "daddiu", "t,r,j", tempreg,
6781			       tempreg, BFD_RELOC_MIPS_HIGHER);
6782		  macro_build (NULL, "dsll", "d,w,<", tempreg, tempreg, 16);
6783		  macro_build (&offset_expr, "daddiu", "t,r,j", tempreg,
6784			       tempreg, BFD_RELOC_HI16_S);
6785		  macro_build (NULL, "dsll", "d,w,<", tempreg, tempreg, 16);
6786		  if (breg != 0)
6787		    macro_build (NULL, "daddu", "d,v,t",
6788				 tempreg, tempreg, breg);
6789		  macro_build (&offset_expr, s, fmt, treg,
6790			       BFD_RELOC_LO16, tempreg);
6791		}
6792
6793	      if (mips_relax.sequence)
6794		relax_end ();
6795	      break;
6796	    }
6797
6798	  if (breg == 0)
6799	    {
6800	      if ((valueT) offset_expr.X_add_number <= MAX_GPREL_OFFSET
6801		  && !nopic_need_relax (offset_expr.X_add_symbol, 1))
6802		{
6803		  relax_start (offset_expr.X_add_symbol);
6804		  macro_build (&offset_expr, s, fmt, treg, BFD_RELOC_GPREL16,
6805			       mips_gp_register);
6806		  relax_switch ();
6807		}
6808	      macro_build_lui (&offset_expr, tempreg);
6809	      macro_build (&offset_expr, s, fmt, treg,
6810			   BFD_RELOC_LO16, tempreg);
6811	      if (mips_relax.sequence)
6812		relax_end ();
6813	    }
6814	  else
6815	    {
6816	      if ((valueT) offset_expr.X_add_number <= MAX_GPREL_OFFSET
6817		  && !nopic_need_relax (offset_expr.X_add_symbol, 1))
6818		{
6819		  relax_start (offset_expr.X_add_symbol);
6820		  macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
6821			       tempreg, breg, mips_gp_register);
6822		  macro_build (&offset_expr, s, fmt, treg,
6823			       BFD_RELOC_GPREL16, tempreg);
6824		  relax_switch ();
6825		}
6826	      macro_build_lui (&offset_expr, tempreg);
6827	      macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
6828			   tempreg, tempreg, breg);
6829	      macro_build (&offset_expr, s, fmt, treg,
6830			   BFD_RELOC_LO16, tempreg);
6831	      if (mips_relax.sequence)
6832		relax_end ();
6833	    }
6834	}
6835      else if (!mips_big_got)
6836	{
6837	  int lw_reloc_type = (int) BFD_RELOC_MIPS_GOT16;
6838
6839	  /* If this is a reference to an external symbol, we want
6840	       lw	$tempreg,<sym>($gp)	(BFD_RELOC_MIPS_GOT16)
6841	       nop
6842	       <op>	$treg,0($tempreg)
6843	     Otherwise we want
6844	       lw	$tempreg,<sym>($gp)	(BFD_RELOC_MIPS_GOT16)
6845	       nop
6846	       addiu	$tempreg,$tempreg,<sym>	(BFD_RELOC_LO16)
6847	       <op>	$treg,0($tempreg)
6848
6849	     For NewABI, we want
6850	       lw	$tempreg,<sym>($gp)	(BFD_RELOC_MIPS_GOT_PAGE)
6851	       <op>	$treg,<sym>($tempreg)   (BFD_RELOC_MIPS_GOT_OFST)
6852
6853	     If there is a base register, we add it to $tempreg before
6854	     the <op>.  If there is a constant, we stick it in the
6855	     <op> instruction.  We don't handle constants larger than
6856	     16 bits, because we have no way to load the upper 16 bits
6857	     (actually, we could handle them for the subset of cases
6858	     in which we are not using $at).  */
6859	  gas_assert (offset_expr.X_op == O_symbol);
6860	  if (HAVE_NEWABI)
6861	    {
6862	      macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)", tempreg,
6863			   BFD_RELOC_MIPS_GOT_PAGE, mips_gp_register);
6864	      if (breg != 0)
6865		macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
6866			     tempreg, tempreg, breg);
6867	      macro_build (&offset_expr, s, fmt, treg,
6868			   BFD_RELOC_MIPS_GOT_OFST, tempreg);
6869	      break;
6870	    }
6871	  expr1.X_add_number = offset_expr.X_add_number;
6872	  offset_expr.X_add_number = 0;
6873	  if (expr1.X_add_number < -0x8000
6874	      || expr1.X_add_number >= 0x8000)
6875	    as_bad (_("PIC code offset overflow (max 16 signed bits)"));
6876	  macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)", tempreg,
6877		       lw_reloc_type, mips_gp_register);
6878	  load_delay_nop ();
6879	  relax_start (offset_expr.X_add_symbol);
6880	  relax_switch ();
6881	  macro_build (&offset_expr, ADDRESS_ADDI_INSN, "t,r,j", tempreg,
6882		       tempreg, BFD_RELOC_LO16);
6883	  relax_end ();
6884	  if (breg != 0)
6885	    macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
6886			 tempreg, tempreg, breg);
6887	  macro_build (&expr1, s, fmt, treg, BFD_RELOC_LO16, tempreg);
6888	}
6889      else if (mips_big_got && !HAVE_NEWABI)
6890	{
6891	  int gpdelay;
6892
6893	  /* If this is a reference to an external symbol, we want
6894	       lui	$tempreg,<sym>		(BFD_RELOC_MIPS_GOT_HI16)
6895	       addu	$tempreg,$tempreg,$gp
6896	       lw	$tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_LO16)
6897	       <op>	$treg,0($tempreg)
6898	     Otherwise we want
6899	       lw	$tempreg,<sym>($gp)	(BFD_RELOC_MIPS_GOT16)
6900	       nop
6901	       addiu	$tempreg,$tempreg,<sym>	(BFD_RELOC_LO16)
6902	       <op>	$treg,0($tempreg)
6903	     If there is a base register, we add it to $tempreg before
6904	     the <op>.  If there is a constant, we stick it in the
6905	     <op> instruction.  We don't handle constants larger than
6906	     16 bits, because we have no way to load the upper 16 bits
6907	     (actually, we could handle them for the subset of cases
6908	     in which we are not using $at).  */
6909	  gas_assert (offset_expr.X_op == O_symbol);
6910	  expr1.X_add_number = offset_expr.X_add_number;
6911	  offset_expr.X_add_number = 0;
6912	  if (expr1.X_add_number < -0x8000
6913	      || expr1.X_add_number >= 0x8000)
6914	    as_bad (_("PIC code offset overflow (max 16 signed bits)"));
6915	  gpdelay = reg_needs_delay (mips_gp_register);
6916	  relax_start (offset_expr.X_add_symbol);
6917	  macro_build (&offset_expr, "lui", "t,u", tempreg,
6918		       BFD_RELOC_MIPS_GOT_HI16);
6919	  macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", tempreg, tempreg,
6920		       mips_gp_register);
6921	  macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)", tempreg,
6922		       BFD_RELOC_MIPS_GOT_LO16, tempreg);
6923	  relax_switch ();
6924	  if (gpdelay)
6925	    macro_build (NULL, "nop", "");
6926	  macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)", tempreg,
6927		       BFD_RELOC_MIPS_GOT16, mips_gp_register);
6928	  load_delay_nop ();
6929	  macro_build (&offset_expr, ADDRESS_ADDI_INSN, "t,r,j", tempreg,
6930		       tempreg, BFD_RELOC_LO16);
6931	  relax_end ();
6932
6933	  if (breg != 0)
6934	    macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
6935			 tempreg, tempreg, breg);
6936	  macro_build (&expr1, s, fmt, treg, BFD_RELOC_LO16, tempreg);
6937	}
6938      else if (mips_big_got && HAVE_NEWABI)
6939	{
6940	  /* If this is a reference to an external symbol, we want
6941	       lui	$tempreg,<sym>		(BFD_RELOC_MIPS_GOT_HI16)
6942	       add	$tempreg,$tempreg,$gp
6943	       lw	$tempreg,<sym>($tempreg) (BFD_RELOC_MIPS_GOT_LO16)
6944	       <op>	$treg,<ofst>($tempreg)
6945	     Otherwise, for local symbols, we want:
6946	       lw	$tempreg,<sym>($gp)	(BFD_RELOC_MIPS_GOT_PAGE)
6947	       <op>	$treg,<sym>($tempreg)   (BFD_RELOC_MIPS_GOT_OFST)  */
6948	  gas_assert (offset_expr.X_op == O_symbol);
6949	  expr1.X_add_number = offset_expr.X_add_number;
6950	  offset_expr.X_add_number = 0;
6951	  if (expr1.X_add_number < -0x8000
6952	      || expr1.X_add_number >= 0x8000)
6953	    as_bad (_("PIC code offset overflow (max 16 signed bits)"));
6954	  relax_start (offset_expr.X_add_symbol);
6955	  macro_build (&offset_expr, "lui", "t,u", tempreg,
6956		       BFD_RELOC_MIPS_GOT_HI16);
6957	  macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", tempreg, tempreg,
6958		       mips_gp_register);
6959	  macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)", tempreg,
6960		       BFD_RELOC_MIPS_GOT_LO16, tempreg);
6961	  if (breg != 0)
6962	    macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
6963			 tempreg, tempreg, breg);
6964	  macro_build (&expr1, s, fmt, treg, BFD_RELOC_LO16, tempreg);
6965
6966	  relax_switch ();
6967	  offset_expr.X_add_number = expr1.X_add_number;
6968	  macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)", tempreg,
6969		       BFD_RELOC_MIPS_GOT_PAGE, mips_gp_register);
6970	  if (breg != 0)
6971	    macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
6972			 tempreg, tempreg, breg);
6973	  macro_build (&offset_expr, s, fmt, treg,
6974		       BFD_RELOC_MIPS_GOT_OFST, tempreg);
6975	  relax_end ();
6976	}
6977      else
6978	abort ();
6979
6980      break;
6981
6982    case M_LI:
6983    case M_LI_S:
6984      load_register (treg, &imm_expr, 0);
6985      break;
6986
6987    case M_DLI:
6988      load_register (treg, &imm_expr, 1);
6989      break;
6990
6991    case M_LI_SS:
6992      if (imm_expr.X_op == O_constant)
6993	{
6994	  used_at = 1;
6995	  load_register (AT, &imm_expr, 0);
6996	  macro_build (NULL, "mtc1", "t,G", AT, treg);
6997	  break;
6998	}
6999      else
7000	{
7001	  gas_assert (offset_expr.X_op == O_symbol
7002		  && strcmp (segment_name (S_GET_SEGMENT
7003					   (offset_expr.X_add_symbol)),
7004			     ".lit4") == 0
7005		  && offset_expr.X_add_number == 0);
7006	  macro_build (&offset_expr, "lwc1", "T,o(b)", treg,
7007		       BFD_RELOC_MIPS_LITERAL, mips_gp_register);
7008	  break;
7009	}
7010
7011    case M_LI_D:
7012      /* Check if we have a constant in IMM_EXPR.  If the GPRs are 64 bits
7013         wide, IMM_EXPR is the entire value.  Otherwise IMM_EXPR is the high
7014         order 32 bits of the value and the low order 32 bits are either
7015         zero or in OFFSET_EXPR.  */
7016      if (imm_expr.X_op == O_constant || imm_expr.X_op == O_big)
7017	{
7018	  if (HAVE_64BIT_GPRS)
7019	    load_register (treg, &imm_expr, 1);
7020	  else
7021	    {
7022	      int hreg, lreg;
7023
7024	      if (target_big_endian)
7025		{
7026		  hreg = treg;
7027		  lreg = treg + 1;
7028		}
7029	      else
7030		{
7031		  hreg = treg + 1;
7032		  lreg = treg;
7033		}
7034
7035	      if (hreg <= 31)
7036		load_register (hreg, &imm_expr, 0);
7037	      if (lreg <= 31)
7038		{
7039		  if (offset_expr.X_op == O_absent)
7040		    move_register (lreg, 0);
7041		  else
7042		    {
7043		      gas_assert (offset_expr.X_op == O_constant);
7044		      load_register (lreg, &offset_expr, 0);
7045		    }
7046		}
7047	    }
7048	  break;
7049	}
7050
7051      /* We know that sym is in the .rdata section.  First we get the
7052	 upper 16 bits of the address.  */
7053      if (mips_pic == NO_PIC)
7054	{
7055	  macro_build_lui (&offset_expr, AT);
7056	  used_at = 1;
7057	}
7058      else
7059	{
7060	  macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)", AT,
7061		       BFD_RELOC_MIPS_GOT16, mips_gp_register);
7062	  used_at = 1;
7063	}
7064
7065      /* Now we load the register(s).  */
7066      if (HAVE_64BIT_GPRS)
7067	{
7068	  used_at = 1;
7069	  macro_build (&offset_expr, "ld", "t,o(b)", treg, BFD_RELOC_LO16, AT);
7070	}
7071      else
7072	{
7073	  used_at = 1;
7074	  macro_build (&offset_expr, "lw", "t,o(b)", treg, BFD_RELOC_LO16, AT);
7075	  if (treg != RA)
7076	    {
7077	      /* FIXME: How in the world do we deal with the possible
7078		 overflow here?  */
7079	      offset_expr.X_add_number += 4;
7080	      macro_build (&offset_expr, "lw", "t,o(b)",
7081			   treg + 1, BFD_RELOC_LO16, AT);
7082	    }
7083	}
7084      break;
7085
7086    case M_LI_DD:
7087      /* Check if we have a constant in IMM_EXPR.  If the FPRs are 64 bits
7088         wide, IMM_EXPR is the entire value and the GPRs are known to be 64
7089         bits wide as well.  Otherwise IMM_EXPR is the high order 32 bits of
7090         the value and the low order 32 bits are either zero or in
7091         OFFSET_EXPR.  */
7092      if (imm_expr.X_op == O_constant || imm_expr.X_op == O_big)
7093	{
7094	  used_at = 1;
7095	  load_register (AT, &imm_expr, HAVE_64BIT_FPRS);
7096	  if (HAVE_64BIT_FPRS)
7097	    {
7098	      gas_assert (HAVE_64BIT_GPRS);
7099	      macro_build (NULL, "dmtc1", "t,S", AT, treg);
7100	    }
7101	  else
7102	    {
7103	      macro_build (NULL, "mtc1", "t,G", AT, treg + 1);
7104	      if (offset_expr.X_op == O_absent)
7105		macro_build (NULL, "mtc1", "t,G", 0, treg);
7106	      else
7107		{
7108		  gas_assert (offset_expr.X_op == O_constant);
7109		  load_register (AT, &offset_expr, 0);
7110		  macro_build (NULL, "mtc1", "t,G", AT, treg);
7111		}
7112	    }
7113	  break;
7114	}
7115
7116      gas_assert (offset_expr.X_op == O_symbol
7117	      && offset_expr.X_add_number == 0);
7118      s = segment_name (S_GET_SEGMENT (offset_expr.X_add_symbol));
7119      if (strcmp (s, ".lit8") == 0)
7120	{
7121	  if (mips_opts.isa != ISA_MIPS1)
7122	    {
7123	      macro_build (&offset_expr, "ldc1", "T,o(b)", treg,
7124			   BFD_RELOC_MIPS_LITERAL, mips_gp_register);
7125	      break;
7126	    }
7127	  breg = mips_gp_register;
7128	  r = BFD_RELOC_MIPS_LITERAL;
7129	  goto dob;
7130	}
7131      else
7132	{
7133	  gas_assert (strcmp (s, RDATA_SECTION_NAME) == 0);
7134	  used_at = 1;
7135	  if (mips_pic != NO_PIC)
7136	    macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)", AT,
7137			 BFD_RELOC_MIPS_GOT16, mips_gp_register);
7138	  else
7139	    {
7140	      /* FIXME: This won't work for a 64 bit address.  */
7141	      macro_build_lui (&offset_expr, AT);
7142	    }
7143
7144	  if (mips_opts.isa != ISA_MIPS1)
7145	    {
7146	      macro_build (&offset_expr, "ldc1", "T,o(b)",
7147			   treg, BFD_RELOC_LO16, AT);
7148	      break;
7149	    }
7150	  breg = AT;
7151	  r = BFD_RELOC_LO16;
7152	  goto dob;
7153	}
7154
7155    case M_L_DOB:
7156      /* Even on a big endian machine $fn comes before $fn+1.  We have
7157	 to adjust when loading from memory.  */
7158      r = BFD_RELOC_LO16;
7159    dob:
7160      gas_assert (mips_opts.isa == ISA_MIPS1);
7161      macro_build (&offset_expr, "lwc1", "T,o(b)",
7162		   target_big_endian ? treg + 1 : treg, r, breg);
7163      /* FIXME: A possible overflow which I don't know how to deal
7164	 with.  */
7165      offset_expr.X_add_number += 4;
7166      macro_build (&offset_expr, "lwc1", "T,o(b)",
7167		   target_big_endian ? treg : treg + 1, r, breg);
7168      break;
7169
7170    case M_L_DAB:
7171      /*
7172       * The MIPS assembler seems to check for X_add_number not
7173       * being double aligned and generating:
7174       *	lui	at,%hi(foo+1)
7175       *	addu	at,at,v1
7176       *	addiu	at,at,%lo(foo+1)
7177       *	lwc1	f2,0(at)
7178       *	lwc1	f3,4(at)
7179       * But, the resulting address is the same after relocation so why
7180       * generate the extra instruction?
7181       */
7182      /* Itbl support may require additional care here.  */
7183      coproc = 1;
7184      if (mips_opts.isa != ISA_MIPS1)
7185	{
7186	  s = "ldc1";
7187	  goto ld;
7188	}
7189
7190      s = "lwc1";
7191      fmt = "T,o(b)";
7192      goto ldd_std;
7193
7194    case M_S_DAB:
7195      if (mips_opts.isa != ISA_MIPS1)
7196	{
7197	  s = "sdc1";
7198	  goto st;
7199	}
7200
7201      s = "swc1";
7202      fmt = "T,o(b)";
7203      /* Itbl support may require additional care here.  */
7204      coproc = 1;
7205      goto ldd_std;
7206
7207    case M_LD_AB:
7208      if (HAVE_64BIT_GPRS)
7209	{
7210	  s = "ld";
7211	  goto ld;
7212	}
7213
7214      s = "lw";
7215      fmt = "t,o(b)";
7216      goto ldd_std;
7217
7218    case M_SD_AB:
7219      if (HAVE_64BIT_GPRS)
7220	{
7221	  s = "sd";
7222	  goto st;
7223	}
7224
7225      s = "sw";
7226      fmt = "t,o(b)";
7227
7228    ldd_std:
7229      if (offset_expr.X_op != O_symbol
7230	  && offset_expr.X_op != O_constant)
7231	{
7232	  as_bad (_("expression too complex"));
7233	  offset_expr.X_op = O_constant;
7234	}
7235
7236      if (HAVE_32BIT_ADDRESSES
7237	  && !IS_SEXT_32BIT_NUM (offset_expr.X_add_number))
7238	{
7239	  char value [32];
7240
7241	  sprintf_vma (value, offset_expr.X_add_number);
7242	  as_bad (_("Number (0x%s) larger than 32 bits"), value);
7243	}
7244
7245      /* Even on a big endian machine $fn comes before $fn+1.  We have
7246	 to adjust when loading from memory.  We set coproc if we must
7247	 load $fn+1 first.  */
7248      /* Itbl support may require additional care here.  */
7249      if (! target_big_endian)
7250	coproc = 0;
7251
7252      if (mips_pic == NO_PIC
7253	  || offset_expr.X_op == O_constant)
7254	{
7255	  /* If this is a reference to a GP relative symbol, we want
7256	       <op>	$treg,<sym>($gp)	(BFD_RELOC_GPREL16)
7257	       <op>	$treg+1,<sym>+4($gp)	(BFD_RELOC_GPREL16)
7258	     If we have a base register, we use this
7259	       addu	$at,$breg,$gp
7260	       <op>	$treg,<sym>($at)	(BFD_RELOC_GPREL16)
7261	       <op>	$treg+1,<sym>+4($at)	(BFD_RELOC_GPREL16)
7262	     If this is not a GP relative symbol, we want
7263	       lui	$at,<sym>		(BFD_RELOC_HI16_S)
7264	       <op>	$treg,<sym>($at)	(BFD_RELOC_LO16)
7265	       <op>	$treg+1,<sym>+4($at)	(BFD_RELOC_LO16)
7266	     If there is a base register, we add it to $at after the
7267	     lui instruction.  If there is a constant, we always use
7268	     the last case.  */
7269	  if (offset_expr.X_op == O_symbol
7270	      && (valueT) offset_expr.X_add_number <= MAX_GPREL_OFFSET
7271	      && !nopic_need_relax (offset_expr.X_add_symbol, 1))
7272	    {
7273	      relax_start (offset_expr.X_add_symbol);
7274	      if (breg == 0)
7275		{
7276		  tempreg = mips_gp_register;
7277		}
7278	      else
7279		{
7280		  macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
7281			       AT, breg, mips_gp_register);
7282		  tempreg = AT;
7283		  used_at = 1;
7284		}
7285
7286	      /* Itbl support may require additional care here.  */
7287	      macro_build (&offset_expr, s, fmt, coproc ? treg + 1 : treg,
7288			   BFD_RELOC_GPREL16, tempreg);
7289	      offset_expr.X_add_number += 4;
7290
7291	      /* Set mips_optimize to 2 to avoid inserting an
7292                 undesired nop.  */
7293	      hold_mips_optimize = mips_optimize;
7294	      mips_optimize = 2;
7295	      /* Itbl support may require additional care here.  */
7296	      macro_build (&offset_expr, s, fmt, coproc ? treg : treg + 1,
7297			   BFD_RELOC_GPREL16, tempreg);
7298	      mips_optimize = hold_mips_optimize;
7299
7300	      relax_switch ();
7301
7302	      offset_expr.X_add_number -= 4;
7303	    }
7304	  used_at = 1;
7305	  macro_build_lui (&offset_expr, AT);
7306	  if (breg != 0)
7307	    macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", AT, breg, AT);
7308	  /* Itbl support may require additional care here.  */
7309	  macro_build (&offset_expr, s, fmt, coproc ? treg + 1 : treg,
7310		       BFD_RELOC_LO16, AT);
7311	  /* FIXME: How do we handle overflow here?  */
7312	  offset_expr.X_add_number += 4;
7313	  /* Itbl support may require additional care here.  */
7314	  macro_build (&offset_expr, s, fmt, coproc ? treg : treg + 1,
7315		       BFD_RELOC_LO16, AT);
7316	  if (mips_relax.sequence)
7317	    relax_end ();
7318	}
7319      else if (!mips_big_got)
7320	{
7321	  /* If this is a reference to an external symbol, we want
7322	       lw	$at,<sym>($gp)		(BFD_RELOC_MIPS_GOT16)
7323	       nop
7324	       <op>	$treg,0($at)
7325	       <op>	$treg+1,4($at)
7326	     Otherwise we want
7327	       lw	$at,<sym>($gp)		(BFD_RELOC_MIPS_GOT16)
7328	       nop
7329	       <op>	$treg,<sym>($at)	(BFD_RELOC_LO16)
7330	       <op>	$treg+1,<sym>+4($at)	(BFD_RELOC_LO16)
7331	     If there is a base register we add it to $at before the
7332	     lwc1 instructions.  If there is a constant we include it
7333	     in the lwc1 instructions.  */
7334	  used_at = 1;
7335	  expr1.X_add_number = offset_expr.X_add_number;
7336	  if (expr1.X_add_number < -0x8000
7337	      || expr1.X_add_number >= 0x8000 - 4)
7338	    as_bad (_("PIC code offset overflow (max 16 signed bits)"));
7339	  load_got_offset (AT, &offset_expr);
7340	  load_delay_nop ();
7341	  if (breg != 0)
7342	    macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", AT, breg, AT);
7343
7344	  /* Set mips_optimize to 2 to avoid inserting an undesired
7345             nop.  */
7346	  hold_mips_optimize = mips_optimize;
7347	  mips_optimize = 2;
7348
7349	  /* Itbl support may require additional care here.  */
7350	  relax_start (offset_expr.X_add_symbol);
7351	  macro_build (&expr1, s, fmt, coproc ? treg + 1 : treg,
7352		       BFD_RELOC_LO16, AT);
7353	  expr1.X_add_number += 4;
7354	  macro_build (&expr1, s, fmt, coproc ? treg : treg + 1,
7355		       BFD_RELOC_LO16, AT);
7356	  relax_switch ();
7357	  macro_build (&offset_expr, s, fmt, coproc ? treg + 1 : treg,
7358		       BFD_RELOC_LO16, AT);
7359	  offset_expr.X_add_number += 4;
7360	  macro_build (&offset_expr, s, fmt, coproc ? treg : treg + 1,
7361		       BFD_RELOC_LO16, AT);
7362	  relax_end ();
7363
7364	  mips_optimize = hold_mips_optimize;
7365	}
7366      else if (mips_big_got)
7367	{
7368	  int gpdelay;
7369
7370	  /* If this is a reference to an external symbol, we want
7371	       lui	$at,<sym>		(BFD_RELOC_MIPS_GOT_HI16)
7372	       addu	$at,$at,$gp
7373	       lw	$at,<sym>($at)		(BFD_RELOC_MIPS_GOT_LO16)
7374	       nop
7375	       <op>	$treg,0($at)
7376	       <op>	$treg+1,4($at)
7377	     Otherwise we want
7378	       lw	$at,<sym>($gp)		(BFD_RELOC_MIPS_GOT16)
7379	       nop
7380	       <op>	$treg,<sym>($at)	(BFD_RELOC_LO16)
7381	       <op>	$treg+1,<sym>+4($at)	(BFD_RELOC_LO16)
7382	     If there is a base register we add it to $at before the
7383	     lwc1 instructions.  If there is a constant we include it
7384	     in the lwc1 instructions.  */
7385	  used_at = 1;
7386	  expr1.X_add_number = offset_expr.X_add_number;
7387	  offset_expr.X_add_number = 0;
7388	  if (expr1.X_add_number < -0x8000
7389	      || expr1.X_add_number >= 0x8000 - 4)
7390	    as_bad (_("PIC code offset overflow (max 16 signed bits)"));
7391	  gpdelay = reg_needs_delay (mips_gp_register);
7392	  relax_start (offset_expr.X_add_symbol);
7393	  macro_build (&offset_expr, "lui", "t,u",
7394		       AT, BFD_RELOC_MIPS_GOT_HI16);
7395	  macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t",
7396		       AT, AT, mips_gp_register);
7397	  macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)",
7398		       AT, BFD_RELOC_MIPS_GOT_LO16, AT);
7399	  load_delay_nop ();
7400	  if (breg != 0)
7401	    macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", AT, breg, AT);
7402	  /* Itbl support may require additional care here.  */
7403	  macro_build (&expr1, s, fmt, coproc ? treg + 1 : treg,
7404		       BFD_RELOC_LO16, AT);
7405	  expr1.X_add_number += 4;
7406
7407	  /* Set mips_optimize to 2 to avoid inserting an undesired
7408             nop.  */
7409	  hold_mips_optimize = mips_optimize;
7410	  mips_optimize = 2;
7411	  /* Itbl support may require additional care here.  */
7412	  macro_build (&expr1, s, fmt, coproc ? treg : treg + 1,
7413		       BFD_RELOC_LO16, AT);
7414	  mips_optimize = hold_mips_optimize;
7415	  expr1.X_add_number -= 4;
7416
7417	  relax_switch ();
7418	  offset_expr.X_add_number = expr1.X_add_number;
7419	  if (gpdelay)
7420	    macro_build (NULL, "nop", "");
7421	  macro_build (&offset_expr, ADDRESS_LOAD_INSN, "t,o(b)", AT,
7422		       BFD_RELOC_MIPS_GOT16, mips_gp_register);
7423	  load_delay_nop ();
7424	  if (breg != 0)
7425	    macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", AT, breg, AT);
7426	  /* Itbl support may require additional care here.  */
7427	  macro_build (&offset_expr, s, fmt, coproc ? treg + 1 : treg,
7428		       BFD_RELOC_LO16, AT);
7429	  offset_expr.X_add_number += 4;
7430
7431	  /* Set mips_optimize to 2 to avoid inserting an undesired
7432             nop.  */
7433	  hold_mips_optimize = mips_optimize;
7434	  mips_optimize = 2;
7435	  /* Itbl support may require additional care here.  */
7436	  macro_build (&offset_expr, s, fmt, coproc ? treg : treg + 1,
7437		       BFD_RELOC_LO16, AT);
7438	  mips_optimize = hold_mips_optimize;
7439	  relax_end ();
7440	}
7441      else
7442	abort ();
7443
7444      break;
7445
7446    case M_LD_OB:
7447      s = HAVE_64BIT_GPRS ? "ld" : "lw";
7448      goto sd_ob;
7449    case M_SD_OB:
7450      s = HAVE_64BIT_GPRS ? "sd" : "sw";
7451    sd_ob:
7452      macro_build (&offset_expr, s, "t,o(b)", treg,
7453		   -1, offset_reloc[0], offset_reloc[1], offset_reloc[2],
7454		   breg);
7455      if (!HAVE_64BIT_GPRS)
7456	{
7457	  offset_expr.X_add_number += 4;
7458	  macro_build (&offset_expr, s, "t,o(b)", treg + 1,
7459		       -1, offset_reloc[0], offset_reloc[1], offset_reloc[2],
7460		       breg);
7461	}
7462      break;
7463
7464   /* New code added to support COPZ instructions.
7465      This code builds table entries out of the macros in mip_opcodes.
7466      R4000 uses interlocks to handle coproc delays.
7467      Other chips (like the R3000) require nops to be inserted for delays.
7468
7469      FIXME: Currently, we require that the user handle delays.
7470      In order to fill delay slots for non-interlocked chips,
7471      we must have a way to specify delays based on the coprocessor.
7472      Eg. 4 cycles if load coproc reg from memory, 1 if in cache, etc.
7473      What are the side-effects of the cop instruction?
7474      What cache support might we have and what are its effects?
7475      Both coprocessor & memory require delays. how long???
7476      What registers are read/set/modified?
7477
7478      If an itbl is provided to interpret cop instructions,
7479      this knowledge can be encoded in the itbl spec.  */
7480
7481    case M_COP0:
7482      s = "c0";
7483      goto copz;
7484    case M_COP1:
7485      s = "c1";
7486      goto copz;
7487    case M_COP2:
7488      s = "c2";
7489      goto copz;
7490    case M_COP3:
7491      s = "c3";
7492    copz:
7493      if (NO_ISA_COP (mips_opts.arch)
7494	  && (ip->insn_mo->pinfo2 & INSN2_M_FP_S) == 0)
7495	{
7496	  as_bad (_("opcode not supported on this processor: %s"),
7497		  mips_cpu_info_from_arch (mips_opts.arch)->name);
7498	  break;
7499	}
7500
7501      /* For now we just do C (same as Cz).  The parameter will be
7502         stored in insn_opcode by mips_ip.  */
7503      macro_build (NULL, s, "C", ip->insn_opcode);
7504      break;
7505
7506    case M_MOVE:
7507      move_register (dreg, sreg);
7508      break;
7509
7510    case M_DMUL:
7511      dbl = 1;
7512    case M_MUL:
7513      macro_build (NULL, dbl ? "dmultu" : "multu", "s,t", sreg, treg);
7514      macro_build (NULL, "mflo", "d", dreg);
7515      break;
7516
7517    case M_DMUL_I:
7518      dbl = 1;
7519    case M_MUL_I:
7520      /* The MIPS assembler some times generates shifts and adds.  I'm
7521	 not trying to be that fancy. GCC should do this for us
7522	 anyway.  */
7523      used_at = 1;
7524      load_register (AT, &imm_expr, dbl);
7525      macro_build (NULL, dbl ? "dmult" : "mult", "s,t", sreg, AT);
7526      macro_build (NULL, "mflo", "d", dreg);
7527      break;
7528
7529    case M_DMULO_I:
7530      dbl = 1;
7531    case M_MULO_I:
7532      imm = 1;
7533      goto do_mulo;
7534
7535    case M_DMULO:
7536      dbl = 1;
7537    case M_MULO:
7538    do_mulo:
7539      start_noreorder ();
7540      used_at = 1;
7541      if (imm)
7542	load_register (AT, &imm_expr, dbl);
7543      macro_build (NULL, dbl ? "dmult" : "mult", "s,t", sreg, imm ? AT : treg);
7544      macro_build (NULL, "mflo", "d", dreg);
7545      macro_build (NULL, dbl ? "dsra32" : "sra", "d,w,<", dreg, dreg, RA);
7546      macro_build (NULL, "mfhi", "d", AT);
7547      if (mips_trap)
7548	macro_build (NULL, "tne", "s,t,q", dreg, AT, 6);
7549      else
7550	{
7551	  expr1.X_add_number = 8;
7552	  macro_build (&expr1, "beq", "s,t,p", dreg, AT);
7553	  macro_build (NULL, "nop", "", 0);
7554	  macro_build (NULL, "break", "c", 6);
7555	}
7556      end_noreorder ();
7557      macro_build (NULL, "mflo", "d", dreg);
7558      break;
7559
7560    case M_DMULOU_I:
7561      dbl = 1;
7562    case M_MULOU_I:
7563      imm = 1;
7564      goto do_mulou;
7565
7566    case M_DMULOU:
7567      dbl = 1;
7568    case M_MULOU:
7569    do_mulou:
7570      start_noreorder ();
7571      used_at = 1;
7572      if (imm)
7573	load_register (AT, &imm_expr, dbl);
7574      macro_build (NULL, dbl ? "dmultu" : "multu", "s,t",
7575		   sreg, imm ? AT : treg);
7576      macro_build (NULL, "mfhi", "d", AT);
7577      macro_build (NULL, "mflo", "d", dreg);
7578      if (mips_trap)
7579	macro_build (NULL, "tne", "s,t,q", AT, 0, 6);
7580      else
7581	{
7582	  expr1.X_add_number = 8;
7583	  macro_build (&expr1, "beq", "s,t,p", AT, 0);
7584	  macro_build (NULL, "nop", "", 0);
7585	  macro_build (NULL, "break", "c", 6);
7586	}
7587      end_noreorder ();
7588      break;
7589
7590    case M_DROL:
7591      if (ISA_HAS_DROR (mips_opts.isa) || CPU_HAS_DROR (mips_opts.arch))
7592	{
7593	  if (dreg == sreg)
7594	    {
7595	      tempreg = AT;
7596	      used_at = 1;
7597	    }
7598	  else
7599	    {
7600	      tempreg = dreg;
7601	    }
7602	  macro_build (NULL, "dnegu", "d,w", tempreg, treg);
7603	  macro_build (NULL, "drorv", "d,t,s", dreg, sreg, tempreg);
7604	  break;
7605	}
7606      used_at = 1;
7607      macro_build (NULL, "dsubu", "d,v,t", AT, 0, treg);
7608      macro_build (NULL, "dsrlv", "d,t,s", AT, sreg, AT);
7609      macro_build (NULL, "dsllv", "d,t,s", dreg, sreg, treg);
7610      macro_build (NULL, "or", "d,v,t", dreg, dreg, AT);
7611      break;
7612
7613    case M_ROL:
7614      if (ISA_HAS_ROR (mips_opts.isa) || CPU_HAS_ROR (mips_opts.arch))
7615	{
7616	  if (dreg == sreg)
7617	    {
7618	      tempreg = AT;
7619	      used_at = 1;
7620	    }
7621	  else
7622	    {
7623	      tempreg = dreg;
7624	    }
7625	  macro_build (NULL, "negu", "d,w", tempreg, treg);
7626	  macro_build (NULL, "rorv", "d,t,s", dreg, sreg, tempreg);
7627	  break;
7628	}
7629      used_at = 1;
7630      macro_build (NULL, "subu", "d,v,t", AT, 0, treg);
7631      macro_build (NULL, "srlv", "d,t,s", AT, sreg, AT);
7632      macro_build (NULL, "sllv", "d,t,s", dreg, sreg, treg);
7633      macro_build (NULL, "or", "d,v,t", dreg, dreg, AT);
7634      break;
7635
7636    case M_DROL_I:
7637      {
7638	unsigned int rot;
7639	char *l;
7640	char *rr;
7641
7642	if (imm_expr.X_op != O_constant)
7643	  as_bad (_("Improper rotate count"));
7644	rot = imm_expr.X_add_number & 0x3f;
7645	if (ISA_HAS_DROR (mips_opts.isa) || CPU_HAS_DROR (mips_opts.arch))
7646	  {
7647	    rot = (64 - rot) & 0x3f;
7648	    if (rot >= 32)
7649	      macro_build (NULL, "dror32", "d,w,<", dreg, sreg, rot - 32);
7650	    else
7651	      macro_build (NULL, "dror", "d,w,<", dreg, sreg, rot);
7652	    break;
7653	  }
7654	if (rot == 0)
7655	  {
7656	    macro_build (NULL, "dsrl", "d,w,<", dreg, sreg, 0);
7657	    break;
7658	  }
7659	l = (rot < 0x20) ? "dsll" : "dsll32";
7660	rr = ((0x40 - rot) < 0x20) ? "dsrl" : "dsrl32";
7661	rot &= 0x1f;
7662	used_at = 1;
7663	macro_build (NULL, l, "d,w,<", AT, sreg, rot);
7664	macro_build (NULL, rr, "d,w,<", dreg, sreg, (0x20 - rot) & 0x1f);
7665	macro_build (NULL, "or", "d,v,t", dreg, dreg, AT);
7666      }
7667      break;
7668
7669    case M_ROL_I:
7670      {
7671	unsigned int rot;
7672
7673	if (imm_expr.X_op != O_constant)
7674	  as_bad (_("Improper rotate count"));
7675	rot = imm_expr.X_add_number & 0x1f;
7676	if (ISA_HAS_ROR (mips_opts.isa) || CPU_HAS_ROR (mips_opts.arch))
7677	  {
7678	    macro_build (NULL, "ror", "d,w,<", dreg, sreg, (32 - rot) & 0x1f);
7679	    break;
7680	  }
7681	if (rot == 0)
7682	  {
7683	    macro_build (NULL, "srl", "d,w,<", dreg, sreg, 0);
7684	    break;
7685	  }
7686	used_at = 1;
7687	macro_build (NULL, "sll", "d,w,<", AT, sreg, rot);
7688	macro_build (NULL, "srl", "d,w,<", dreg, sreg, (0x20 - rot) & 0x1f);
7689	macro_build (NULL, "or", "d,v,t", dreg, dreg, AT);
7690      }
7691      break;
7692
7693    case M_DROR:
7694      if (ISA_HAS_DROR (mips_opts.isa) || CPU_HAS_DROR (mips_opts.arch))
7695	{
7696	  macro_build (NULL, "drorv", "d,t,s", dreg, sreg, treg);
7697	  break;
7698	}
7699      used_at = 1;
7700      macro_build (NULL, "dsubu", "d,v,t", AT, 0, treg);
7701      macro_build (NULL, "dsllv", "d,t,s", AT, sreg, AT);
7702      macro_build (NULL, "dsrlv", "d,t,s", dreg, sreg, treg);
7703      macro_build (NULL, "or", "d,v,t", dreg, dreg, AT);
7704      break;
7705
7706    case M_ROR:
7707      if (ISA_HAS_ROR (mips_opts.isa) || CPU_HAS_ROR (mips_opts.arch))
7708	{
7709	  macro_build (NULL, "rorv", "d,t,s", dreg, sreg, treg);
7710	  break;
7711	}
7712      used_at = 1;
7713      macro_build (NULL, "subu", "d,v,t", AT, 0, treg);
7714      macro_build (NULL, "sllv", "d,t,s", AT, sreg, AT);
7715      macro_build (NULL, "srlv", "d,t,s", dreg, sreg, treg);
7716      macro_build (NULL, "or", "d,v,t", dreg, dreg, AT);
7717      break;
7718
7719    case M_DROR_I:
7720      {
7721	unsigned int rot;
7722	char *l;
7723	char *rr;
7724
7725	if (imm_expr.X_op != O_constant)
7726	  as_bad (_("Improper rotate count"));
7727	rot = imm_expr.X_add_number & 0x3f;
7728	if (ISA_HAS_DROR (mips_opts.isa) || CPU_HAS_DROR (mips_opts.arch))
7729	  {
7730	    if (rot >= 32)
7731	      macro_build (NULL, "dror32", "d,w,<", dreg, sreg, rot - 32);
7732	    else
7733	      macro_build (NULL, "dror", "d,w,<", dreg, sreg, rot);
7734	    break;
7735	  }
7736	if (rot == 0)
7737	  {
7738	    macro_build (NULL, "dsrl", "d,w,<", dreg, sreg, 0);
7739	    break;
7740	  }
7741	rr = (rot < 0x20) ? "dsrl" : "dsrl32";
7742	l = ((0x40 - rot) < 0x20) ? "dsll" : "dsll32";
7743	rot &= 0x1f;
7744	used_at = 1;
7745	macro_build (NULL, rr, "d,w,<", AT, sreg, rot);
7746	macro_build (NULL, l, "d,w,<", dreg, sreg, (0x20 - rot) & 0x1f);
7747	macro_build (NULL, "or", "d,v,t", dreg, dreg, AT);
7748      }
7749      break;
7750
7751    case M_ROR_I:
7752      {
7753	unsigned int rot;
7754
7755	if (imm_expr.X_op != O_constant)
7756	  as_bad (_("Improper rotate count"));
7757	rot = imm_expr.X_add_number & 0x1f;
7758	if (ISA_HAS_ROR (mips_opts.isa) || CPU_HAS_ROR (mips_opts.arch))
7759	  {
7760	    macro_build (NULL, "ror", "d,w,<", dreg, sreg, rot);
7761	    break;
7762	  }
7763	if (rot == 0)
7764	  {
7765	    macro_build (NULL, "srl", "d,w,<", dreg, sreg, 0);
7766	    break;
7767	  }
7768	used_at = 1;
7769	macro_build (NULL, "srl", "d,w,<", AT, sreg, rot);
7770	macro_build (NULL, "sll", "d,w,<", dreg, sreg, (0x20 - rot) & 0x1f);
7771	macro_build (NULL, "or", "d,v,t", dreg, dreg, AT);
7772      }
7773      break;
7774
7775    case M_S_DOB:
7776      gas_assert (mips_opts.isa == ISA_MIPS1);
7777      /* Even on a big endian machine $fn comes before $fn+1.  We have
7778	 to adjust when storing to memory.  */
7779      macro_build (&offset_expr, "swc1", "T,o(b)",
7780		   target_big_endian ? treg + 1 : treg, BFD_RELOC_LO16, breg);
7781      offset_expr.X_add_number += 4;
7782      macro_build (&offset_expr, "swc1", "T,o(b)",
7783		   target_big_endian ? treg : treg + 1, BFD_RELOC_LO16, breg);
7784      break;
7785
7786    case M_SEQ:
7787      if (sreg == 0)
7788	macro_build (&expr1, "sltiu", "t,r,j", dreg, treg, BFD_RELOC_LO16);
7789      else if (treg == 0)
7790	macro_build (&expr1, "sltiu", "t,r,j", dreg, sreg, BFD_RELOC_LO16);
7791      else
7792	{
7793	  macro_build (NULL, "xor", "d,v,t", dreg, sreg, treg);
7794	  macro_build (&expr1, "sltiu", "t,r,j", dreg, dreg, BFD_RELOC_LO16);
7795	}
7796      break;
7797
7798    case M_SEQ_I:
7799      if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
7800	{
7801	  macro_build (&expr1, "sltiu", "t,r,j", dreg, sreg, BFD_RELOC_LO16);
7802	  break;
7803	}
7804      if (sreg == 0)
7805	{
7806	  as_warn (_("Instruction %s: result is always false"),
7807		   ip->insn_mo->name);
7808	  move_register (dreg, 0);
7809	  break;
7810	}
7811      if (CPU_HAS_SEQ (mips_opts.arch)
7812	  && -512 <= imm_expr.X_add_number
7813	  && imm_expr.X_add_number < 512)
7814	{
7815	  macro_build (NULL, "seqi", "t,r,+Q", dreg, sreg,
7816		       (int) imm_expr.X_add_number);
7817	  break;
7818	}
7819      if (imm_expr.X_op == O_constant
7820	  && imm_expr.X_add_number >= 0
7821	  && imm_expr.X_add_number < 0x10000)
7822	{
7823	  macro_build (&imm_expr, "xori", "t,r,i", dreg, sreg, BFD_RELOC_LO16);
7824	}
7825      else if (imm_expr.X_op == O_constant
7826	       && imm_expr.X_add_number > -0x8000
7827	       && imm_expr.X_add_number < 0)
7828	{
7829	  imm_expr.X_add_number = -imm_expr.X_add_number;
7830	  macro_build (&imm_expr, HAVE_32BIT_GPRS ? "addiu" : "daddiu",
7831		       "t,r,j", dreg, sreg, BFD_RELOC_LO16);
7832	}
7833      else if (CPU_HAS_SEQ (mips_opts.arch))
7834	{
7835	  used_at = 1;
7836	  load_register (AT, &imm_expr, HAVE_64BIT_GPRS);
7837	  macro_build (NULL, "seq", "d,v,t", dreg, sreg, AT);
7838	  break;
7839	}
7840      else
7841	{
7842	  load_register (AT, &imm_expr, HAVE_64BIT_GPRS);
7843	  macro_build (NULL, "xor", "d,v,t", dreg, sreg, AT);
7844	  used_at = 1;
7845	}
7846      macro_build (&expr1, "sltiu", "t,r,j", dreg, dreg, BFD_RELOC_LO16);
7847      break;
7848
7849    case M_SGE:		/* sreg >= treg <==> not (sreg < treg) */
7850      s = "slt";
7851      goto sge;
7852    case M_SGEU:
7853      s = "sltu";
7854    sge:
7855      macro_build (NULL, s, "d,v,t", dreg, sreg, treg);
7856      macro_build (&expr1, "xori", "t,r,i", dreg, dreg, BFD_RELOC_LO16);
7857      break;
7858
7859    case M_SGE_I:		/* sreg >= I <==> not (sreg < I) */
7860    case M_SGEU_I:
7861      if (imm_expr.X_op == O_constant
7862	  && imm_expr.X_add_number >= -0x8000
7863	  && imm_expr.X_add_number < 0x8000)
7864	{
7865	  macro_build (&imm_expr, mask == M_SGE_I ? "slti" : "sltiu", "t,r,j",
7866		       dreg, sreg, BFD_RELOC_LO16);
7867	}
7868      else
7869	{
7870	  load_register (AT, &imm_expr, HAVE_64BIT_GPRS);
7871	  macro_build (NULL, mask == M_SGE_I ? "slt" : "sltu", "d,v,t",
7872		       dreg, sreg, AT);
7873	  used_at = 1;
7874	}
7875      macro_build (&expr1, "xori", "t,r,i", dreg, dreg, BFD_RELOC_LO16);
7876      break;
7877
7878    case M_SGT:		/* sreg > treg  <==>  treg < sreg */
7879      s = "slt";
7880      goto sgt;
7881    case M_SGTU:
7882      s = "sltu";
7883    sgt:
7884      macro_build (NULL, s, "d,v,t", dreg, treg, sreg);
7885      break;
7886
7887    case M_SGT_I:		/* sreg > I  <==>  I < sreg */
7888      s = "slt";
7889      goto sgti;
7890    case M_SGTU_I:
7891      s = "sltu";
7892    sgti:
7893      used_at = 1;
7894      load_register (AT, &imm_expr, HAVE_64BIT_GPRS);
7895      macro_build (NULL, s, "d,v,t", dreg, AT, sreg);
7896      break;
7897
7898    case M_SLE:	/* sreg <= treg  <==>  treg >= sreg  <==>  not (treg < sreg) */
7899      s = "slt";
7900      goto sle;
7901    case M_SLEU:
7902      s = "sltu";
7903    sle:
7904      macro_build (NULL, s, "d,v,t", dreg, treg, sreg);
7905      macro_build (&expr1, "xori", "t,r,i", dreg, dreg, BFD_RELOC_LO16);
7906      break;
7907
7908    case M_SLE_I:	/* sreg <= I <==> I >= sreg <==> not (I < sreg) */
7909      s = "slt";
7910      goto slei;
7911    case M_SLEU_I:
7912      s = "sltu";
7913    slei:
7914      used_at = 1;
7915      load_register (AT, &imm_expr, HAVE_64BIT_GPRS);
7916      macro_build (NULL, s, "d,v,t", dreg, AT, sreg);
7917      macro_build (&expr1, "xori", "t,r,i", dreg, dreg, BFD_RELOC_LO16);
7918      break;
7919
7920    case M_SLT_I:
7921      if (imm_expr.X_op == O_constant
7922	  && imm_expr.X_add_number >= -0x8000
7923	  && imm_expr.X_add_number < 0x8000)
7924	{
7925	  macro_build (&imm_expr, "slti", "t,r,j", dreg, sreg, BFD_RELOC_LO16);
7926	  break;
7927	}
7928      used_at = 1;
7929      load_register (AT, &imm_expr, HAVE_64BIT_GPRS);
7930      macro_build (NULL, "slt", "d,v,t", dreg, sreg, AT);
7931      break;
7932
7933    case M_SLTU_I:
7934      if (imm_expr.X_op == O_constant
7935	  && imm_expr.X_add_number >= -0x8000
7936	  && imm_expr.X_add_number < 0x8000)
7937	{
7938	  macro_build (&imm_expr, "sltiu", "t,r,j", dreg, sreg,
7939		       BFD_RELOC_LO16);
7940	  break;
7941	}
7942      used_at = 1;
7943      load_register (AT, &imm_expr, HAVE_64BIT_GPRS);
7944      macro_build (NULL, "sltu", "d,v,t", dreg, sreg, AT);
7945      break;
7946
7947    case M_SNE:
7948      if (sreg == 0)
7949	macro_build (NULL, "sltu", "d,v,t", dreg, 0, treg);
7950      else if (treg == 0)
7951	macro_build (NULL, "sltu", "d,v,t", dreg, 0, sreg);
7952      else
7953	{
7954	  macro_build (NULL, "xor", "d,v,t", dreg, sreg, treg);
7955	  macro_build (NULL, "sltu", "d,v,t", dreg, 0, dreg);
7956	}
7957      break;
7958
7959    case M_SNE_I:
7960      if (imm_expr.X_op == O_constant && imm_expr.X_add_number == 0)
7961	{
7962	  macro_build (NULL, "sltu", "d,v,t", dreg, 0, sreg);
7963	  break;
7964	}
7965      if (sreg == 0)
7966	{
7967	  as_warn (_("Instruction %s: result is always true"),
7968		   ip->insn_mo->name);
7969	  macro_build (&expr1, HAVE_32BIT_GPRS ? "addiu" : "daddiu", "t,r,j",
7970		       dreg, 0, BFD_RELOC_LO16);
7971	  break;
7972	}
7973      if (CPU_HAS_SEQ (mips_opts.arch)
7974	  && -512 <= imm_expr.X_add_number
7975	  && imm_expr.X_add_number < 512)
7976	{
7977	  macro_build (NULL, "snei", "t,r,+Q", dreg, sreg,
7978		       (int) imm_expr.X_add_number);
7979	  break;
7980	}
7981      if (imm_expr.X_op == O_constant
7982	  && imm_expr.X_add_number >= 0
7983	  && imm_expr.X_add_number < 0x10000)
7984	{
7985	  macro_build (&imm_expr, "xori", "t,r,i", dreg, sreg, BFD_RELOC_LO16);
7986	}
7987      else if (imm_expr.X_op == O_constant
7988	       && imm_expr.X_add_number > -0x8000
7989	       && imm_expr.X_add_number < 0)
7990	{
7991	  imm_expr.X_add_number = -imm_expr.X_add_number;
7992	  macro_build (&imm_expr, HAVE_32BIT_GPRS ? "addiu" : "daddiu",
7993		       "t,r,j", dreg, sreg, BFD_RELOC_LO16);
7994	}
7995      else if (CPU_HAS_SEQ (mips_opts.arch))
7996	{
7997	  used_at = 1;
7998	  load_register (AT, &imm_expr, HAVE_64BIT_GPRS);
7999	  macro_build (NULL, "sne", "d,v,t", dreg, sreg, AT);
8000	  break;
8001	}
8002      else
8003	{
8004	  load_register (AT, &imm_expr, HAVE_64BIT_GPRS);
8005	  macro_build (NULL, "xor", "d,v,t", dreg, sreg, AT);
8006	  used_at = 1;
8007	}
8008      macro_build (NULL, "sltu", "d,v,t", dreg, 0, dreg);
8009      break;
8010
8011    case M_DSUB_I:
8012      dbl = 1;
8013    case M_SUB_I:
8014      if (imm_expr.X_op == O_constant
8015	  && imm_expr.X_add_number > -0x8000
8016	  && imm_expr.X_add_number <= 0x8000)
8017	{
8018	  imm_expr.X_add_number = -imm_expr.X_add_number;
8019	  macro_build (&imm_expr, dbl ? "daddi" : "addi", "t,r,j",
8020		       dreg, sreg, BFD_RELOC_LO16);
8021	  break;
8022	}
8023      used_at = 1;
8024      load_register (AT, &imm_expr, dbl);
8025      macro_build (NULL, dbl ? "dsub" : "sub", "d,v,t", dreg, sreg, AT);
8026      break;
8027
8028    case M_DSUBU_I:
8029      dbl = 1;
8030    case M_SUBU_I:
8031      if (imm_expr.X_op == O_constant
8032	  && imm_expr.X_add_number > -0x8000
8033	  && imm_expr.X_add_number <= 0x8000)
8034	{
8035	  imm_expr.X_add_number = -imm_expr.X_add_number;
8036	  macro_build (&imm_expr, dbl ? "daddiu" : "addiu", "t,r,j",
8037		       dreg, sreg, BFD_RELOC_LO16);
8038	  break;
8039	}
8040      used_at = 1;
8041      load_register (AT, &imm_expr, dbl);
8042      macro_build (NULL, dbl ? "dsubu" : "subu", "d,v,t", dreg, sreg, AT);
8043      break;
8044
8045    case M_TEQ_I:
8046      s = "teq";
8047      goto trap;
8048    case M_TGE_I:
8049      s = "tge";
8050      goto trap;
8051    case M_TGEU_I:
8052      s = "tgeu";
8053      goto trap;
8054    case M_TLT_I:
8055      s = "tlt";
8056      goto trap;
8057    case M_TLTU_I:
8058      s = "tltu";
8059      goto trap;
8060    case M_TNE_I:
8061      s = "tne";
8062    trap:
8063      used_at = 1;
8064      load_register (AT, &imm_expr, HAVE_64BIT_GPRS);
8065      macro_build (NULL, s, "s,t", sreg, AT);
8066      break;
8067
8068    case M_TRUNCWS:
8069    case M_TRUNCWD:
8070      gas_assert (mips_opts.isa == ISA_MIPS1);
8071      used_at = 1;
8072      sreg = (ip->insn_opcode >> 11) & 0x1f;	/* floating reg */
8073      dreg = (ip->insn_opcode >> 06) & 0x1f;	/* floating reg */
8074
8075      /*
8076       * Is the double cfc1 instruction a bug in the mips assembler;
8077       * or is there a reason for it?
8078       */
8079      start_noreorder ();
8080      macro_build (NULL, "cfc1", "t,G", treg, RA);
8081      macro_build (NULL, "cfc1", "t,G", treg, RA);
8082      macro_build (NULL, "nop", "");
8083      expr1.X_add_number = 3;
8084      macro_build (&expr1, "ori", "t,r,i", AT, treg, BFD_RELOC_LO16);
8085      expr1.X_add_number = 2;
8086      macro_build (&expr1, "xori", "t,r,i", AT, AT, BFD_RELOC_LO16);
8087      macro_build (NULL, "ctc1", "t,G", AT, RA);
8088      macro_build (NULL, "nop", "");
8089      macro_build (NULL, mask == M_TRUNCWD ? "cvt.w.d" : "cvt.w.s", "D,S",
8090		   dreg, sreg);
8091      macro_build (NULL, "ctc1", "t,G", treg, RA);
8092      macro_build (NULL, "nop", "");
8093      end_noreorder ();
8094      break;
8095
8096    case M_ULH:
8097      s = "lb";
8098      goto ulh;
8099    case M_ULHU:
8100      s = "lbu";
8101    ulh:
8102      used_at = 1;
8103      if (offset_expr.X_add_number >= 0x7fff)
8104	as_bad (_("operand overflow"));
8105      if (! target_big_endian)
8106	++offset_expr.X_add_number;
8107      macro_build (&offset_expr, s, "t,o(b)", AT, BFD_RELOC_LO16, breg);
8108      if (! target_big_endian)
8109	--offset_expr.X_add_number;
8110      else
8111	++offset_expr.X_add_number;
8112      macro_build (&offset_expr, "lbu", "t,o(b)", treg, BFD_RELOC_LO16, breg);
8113      macro_build (NULL, "sll", "d,w,<", AT, AT, 8);
8114      macro_build (NULL, "or", "d,v,t", treg, treg, AT);
8115      break;
8116
8117    case M_ULD:
8118      s = "ldl";
8119      s2 = "ldr";
8120      off = 7;
8121      goto ulw;
8122    case M_ULW:
8123      s = "lwl";
8124      s2 = "lwr";
8125      off = 3;
8126    ulw:
8127      if (offset_expr.X_add_number >= 0x8000 - off)
8128	as_bad (_("operand overflow"));
8129      if (treg != breg)
8130	tempreg = treg;
8131      else
8132	{
8133	  used_at = 1;
8134	  tempreg = AT;
8135	}
8136      if (! target_big_endian)
8137	offset_expr.X_add_number += off;
8138      macro_build (&offset_expr, s, "t,o(b)", tempreg, BFD_RELOC_LO16, breg);
8139      if (! target_big_endian)
8140	offset_expr.X_add_number -= off;
8141      else
8142	offset_expr.X_add_number += off;
8143      macro_build (&offset_expr, s2, "t,o(b)", tempreg, BFD_RELOC_LO16, breg);
8144
8145      /* If necessary, move the result in tempreg the final destination.  */
8146      if (treg == tempreg)
8147        break;
8148      /* Protect second load's delay slot.  */
8149      load_delay_nop ();
8150      move_register (treg, tempreg);
8151      break;
8152
8153    case M_ULD_A:
8154      s = "ldl";
8155      s2 = "ldr";
8156      off = 7;
8157      goto ulwa;
8158    case M_ULW_A:
8159      s = "lwl";
8160      s2 = "lwr";
8161      off = 3;
8162    ulwa:
8163      used_at = 1;
8164      load_address (AT, &offset_expr, &used_at);
8165      if (breg != 0)
8166	macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", AT, AT, breg);
8167      if (! target_big_endian)
8168	expr1.X_add_number = off;
8169      else
8170	expr1.X_add_number = 0;
8171      macro_build (&expr1, s, "t,o(b)", treg, BFD_RELOC_LO16, AT);
8172      if (! target_big_endian)
8173	expr1.X_add_number = 0;
8174      else
8175	expr1.X_add_number = off;
8176      macro_build (&expr1, s2, "t,o(b)", treg, BFD_RELOC_LO16, AT);
8177      break;
8178
8179    case M_ULH_A:
8180    case M_ULHU_A:
8181      used_at = 1;
8182      load_address (AT, &offset_expr, &used_at);
8183      if (breg != 0)
8184	macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", AT, AT, breg);
8185      if (target_big_endian)
8186	expr1.X_add_number = 0;
8187      macro_build (&expr1, mask == M_ULH_A ? "lb" : "lbu", "t,o(b)",
8188		   treg, BFD_RELOC_LO16, AT);
8189      if (target_big_endian)
8190	expr1.X_add_number = 1;
8191      else
8192	expr1.X_add_number = 0;
8193      macro_build (&expr1, "lbu", "t,o(b)", AT, BFD_RELOC_LO16, AT);
8194      macro_build (NULL, "sll", "d,w,<", treg, treg, 8);
8195      macro_build (NULL, "or", "d,v,t", treg, treg, AT);
8196      break;
8197
8198    case M_USH:
8199      used_at = 1;
8200      if (offset_expr.X_add_number >= 0x7fff)
8201	as_bad (_("operand overflow"));
8202      if (target_big_endian)
8203	++offset_expr.X_add_number;
8204      macro_build (&offset_expr, "sb", "t,o(b)", treg, BFD_RELOC_LO16, breg);
8205      macro_build (NULL, "srl", "d,w,<", AT, treg, 8);
8206      if (target_big_endian)
8207	--offset_expr.X_add_number;
8208      else
8209	++offset_expr.X_add_number;
8210      macro_build (&offset_expr, "sb", "t,o(b)", AT, BFD_RELOC_LO16, breg);
8211      break;
8212
8213    case M_USD:
8214      s = "sdl";
8215      s2 = "sdr";
8216      off = 7;
8217      goto usw;
8218    case M_USW:
8219      s = "swl";
8220      s2 = "swr";
8221      off = 3;
8222    usw:
8223      if (offset_expr.X_add_number >= 0x8000 - off)
8224	as_bad (_("operand overflow"));
8225      if (! target_big_endian)
8226	offset_expr.X_add_number += off;
8227      macro_build (&offset_expr, s, "t,o(b)", treg, BFD_RELOC_LO16, breg);
8228      if (! target_big_endian)
8229	offset_expr.X_add_number -= off;
8230      else
8231	offset_expr.X_add_number += off;
8232      macro_build (&offset_expr, s2, "t,o(b)", treg, BFD_RELOC_LO16, breg);
8233      break;
8234
8235    case M_USD_A:
8236      s = "sdl";
8237      s2 = "sdr";
8238      off = 7;
8239      goto uswa;
8240    case M_USW_A:
8241      s = "swl";
8242      s2 = "swr";
8243      off = 3;
8244    uswa:
8245      used_at = 1;
8246      load_address (AT, &offset_expr, &used_at);
8247      if (breg != 0)
8248	macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", AT, AT, breg);
8249      if (! target_big_endian)
8250	expr1.X_add_number = off;
8251      else
8252	expr1.X_add_number = 0;
8253      macro_build (&expr1, s, "t,o(b)", treg, BFD_RELOC_LO16, AT);
8254      if (! target_big_endian)
8255	expr1.X_add_number = 0;
8256      else
8257	expr1.X_add_number = off;
8258      macro_build (&expr1, s2, "t,o(b)", treg, BFD_RELOC_LO16, AT);
8259      break;
8260
8261    case M_USH_A:
8262      used_at = 1;
8263      load_address (AT, &offset_expr, &used_at);
8264      if (breg != 0)
8265	macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", AT, AT, breg);
8266      if (! target_big_endian)
8267	expr1.X_add_number = 0;
8268      macro_build (&expr1, "sb", "t,o(b)", treg, BFD_RELOC_LO16, AT);
8269      macro_build (NULL, "srl", "d,w,<", treg, treg, 8);
8270      if (! target_big_endian)
8271	expr1.X_add_number = 1;
8272      else
8273	expr1.X_add_number = 0;
8274      macro_build (&expr1, "sb", "t,o(b)", treg, BFD_RELOC_LO16, AT);
8275      if (! target_big_endian)
8276	expr1.X_add_number = 0;
8277      else
8278	expr1.X_add_number = 1;
8279      macro_build (&expr1, "lbu", "t,o(b)", AT, BFD_RELOC_LO16, AT);
8280      macro_build (NULL, "sll", "d,w,<", treg, treg, 8);
8281      macro_build (NULL, "or", "d,v,t", treg, treg, AT);
8282      break;
8283
8284    default:
8285      /* FIXME: Check if this is one of the itbl macros, since they
8286	 are added dynamically.  */
8287      as_bad (_("Macro %s not implemented yet"), ip->insn_mo->name);
8288      break;
8289    }
8290  if (!mips_opts.at && used_at)
8291    as_bad (_("Macro used $at after \".set noat\""));
8292}
8293
8294/* Implement macros in mips16 mode.  */
8295
8296static void
8297mips16_macro (struct mips_cl_insn *ip)
8298{
8299  int mask;
8300  int xreg, yreg, zreg, tmp;
8301  expressionS expr1;
8302  int dbl;
8303  const char *s, *s2, *s3;
8304
8305  mask = ip->insn_mo->mask;
8306
8307  xreg = MIPS16_EXTRACT_OPERAND (RX, *ip);
8308  yreg = MIPS16_EXTRACT_OPERAND (RY, *ip);
8309  zreg = MIPS16_EXTRACT_OPERAND (RZ, *ip);
8310
8311  expr1.X_op = O_constant;
8312  expr1.X_op_symbol = NULL;
8313  expr1.X_add_symbol = NULL;
8314  expr1.X_add_number = 1;
8315
8316  dbl = 0;
8317
8318  switch (mask)
8319    {
8320    default:
8321      internalError ();
8322
8323    case M_DDIV_3:
8324      dbl = 1;
8325    case M_DIV_3:
8326      s = "mflo";
8327      goto do_div3;
8328    case M_DREM_3:
8329      dbl = 1;
8330    case M_REM_3:
8331      s = "mfhi";
8332    do_div3:
8333      start_noreorder ();
8334      macro_build (NULL, dbl ? "ddiv" : "div", "0,x,y", xreg, yreg);
8335      expr1.X_add_number = 2;
8336      macro_build (&expr1, "bnez", "x,p", yreg);
8337      macro_build (NULL, "break", "6", 7);
8338
8339      /* FIXME: The normal code checks for of -1 / -0x80000000 here,
8340         since that causes an overflow.  We should do that as well,
8341         but I don't see how to do the comparisons without a temporary
8342         register.  */
8343      end_noreorder ();
8344      macro_build (NULL, s, "x", zreg);
8345      break;
8346
8347    case M_DIVU_3:
8348      s = "divu";
8349      s2 = "mflo";
8350      goto do_divu3;
8351    case M_REMU_3:
8352      s = "divu";
8353      s2 = "mfhi";
8354      goto do_divu3;
8355    case M_DDIVU_3:
8356      s = "ddivu";
8357      s2 = "mflo";
8358      goto do_divu3;
8359    case M_DREMU_3:
8360      s = "ddivu";
8361      s2 = "mfhi";
8362    do_divu3:
8363      start_noreorder ();
8364      macro_build (NULL, s, "0,x,y", xreg, yreg);
8365      expr1.X_add_number = 2;
8366      macro_build (&expr1, "bnez", "x,p", yreg);
8367      macro_build (NULL, "break", "6", 7);
8368      end_noreorder ();
8369      macro_build (NULL, s2, "x", zreg);
8370      break;
8371
8372    case M_DMUL:
8373      dbl = 1;
8374    case M_MUL:
8375      macro_build (NULL, dbl ? "dmultu" : "multu", "x,y", xreg, yreg);
8376      macro_build (NULL, "mflo", "x", zreg);
8377      break;
8378
8379    case M_DSUBU_I:
8380      dbl = 1;
8381      goto do_subu;
8382    case M_SUBU_I:
8383    do_subu:
8384      if (imm_expr.X_op != O_constant)
8385	as_bad (_("Unsupported large constant"));
8386      imm_expr.X_add_number = -imm_expr.X_add_number;
8387      macro_build (&imm_expr, dbl ? "daddiu" : "addiu", "y,x,4", yreg, xreg);
8388      break;
8389
8390    case M_SUBU_I_2:
8391      if (imm_expr.X_op != O_constant)
8392	as_bad (_("Unsupported large constant"));
8393      imm_expr.X_add_number = -imm_expr.X_add_number;
8394      macro_build (&imm_expr, "addiu", "x,k", xreg);
8395      break;
8396
8397    case M_DSUBU_I_2:
8398      if (imm_expr.X_op != O_constant)
8399	as_bad (_("Unsupported large constant"));
8400      imm_expr.X_add_number = -imm_expr.X_add_number;
8401      macro_build (&imm_expr, "daddiu", "y,j", yreg);
8402      break;
8403
8404    case M_BEQ:
8405      s = "cmp";
8406      s2 = "bteqz";
8407      goto do_branch;
8408    case M_BNE:
8409      s = "cmp";
8410      s2 = "btnez";
8411      goto do_branch;
8412    case M_BLT:
8413      s = "slt";
8414      s2 = "btnez";
8415      goto do_branch;
8416    case M_BLTU:
8417      s = "sltu";
8418      s2 = "btnez";
8419      goto do_branch;
8420    case M_BLE:
8421      s = "slt";
8422      s2 = "bteqz";
8423      goto do_reverse_branch;
8424    case M_BLEU:
8425      s = "sltu";
8426      s2 = "bteqz";
8427      goto do_reverse_branch;
8428    case M_BGE:
8429      s = "slt";
8430      s2 = "bteqz";
8431      goto do_branch;
8432    case M_BGEU:
8433      s = "sltu";
8434      s2 = "bteqz";
8435      goto do_branch;
8436    case M_BGT:
8437      s = "slt";
8438      s2 = "btnez";
8439      goto do_reverse_branch;
8440    case M_BGTU:
8441      s = "sltu";
8442      s2 = "btnez";
8443
8444    do_reverse_branch:
8445      tmp = xreg;
8446      xreg = yreg;
8447      yreg = tmp;
8448
8449    do_branch:
8450      macro_build (NULL, s, "x,y", xreg, yreg);
8451      macro_build (&offset_expr, s2, "p");
8452      break;
8453
8454    case M_BEQ_I:
8455      s = "cmpi";
8456      s2 = "bteqz";
8457      s3 = "x,U";
8458      goto do_branch_i;
8459    case M_BNE_I:
8460      s = "cmpi";
8461      s2 = "btnez";
8462      s3 = "x,U";
8463      goto do_branch_i;
8464    case M_BLT_I:
8465      s = "slti";
8466      s2 = "btnez";
8467      s3 = "x,8";
8468      goto do_branch_i;
8469    case M_BLTU_I:
8470      s = "sltiu";
8471      s2 = "btnez";
8472      s3 = "x,8";
8473      goto do_branch_i;
8474    case M_BLE_I:
8475      s = "slti";
8476      s2 = "btnez";
8477      s3 = "x,8";
8478      goto do_addone_branch_i;
8479    case M_BLEU_I:
8480      s = "sltiu";
8481      s2 = "btnez";
8482      s3 = "x,8";
8483      goto do_addone_branch_i;
8484    case M_BGE_I:
8485      s = "slti";
8486      s2 = "bteqz";
8487      s3 = "x,8";
8488      goto do_branch_i;
8489    case M_BGEU_I:
8490      s = "sltiu";
8491      s2 = "bteqz";
8492      s3 = "x,8";
8493      goto do_branch_i;
8494    case M_BGT_I:
8495      s = "slti";
8496      s2 = "bteqz";
8497      s3 = "x,8";
8498      goto do_addone_branch_i;
8499    case M_BGTU_I:
8500      s = "sltiu";
8501      s2 = "bteqz";
8502      s3 = "x,8";
8503
8504    do_addone_branch_i:
8505      if (imm_expr.X_op != O_constant)
8506	as_bad (_("Unsupported large constant"));
8507      ++imm_expr.X_add_number;
8508
8509    do_branch_i:
8510      macro_build (&imm_expr, s, s3, xreg);
8511      macro_build (&offset_expr, s2, "p");
8512      break;
8513
8514    case M_ABS:
8515      expr1.X_add_number = 0;
8516      macro_build (&expr1, "slti", "x,8", yreg);
8517      if (xreg != yreg)
8518	move_register (xreg, yreg);
8519      expr1.X_add_number = 2;
8520      macro_build (&expr1, "bteqz", "p");
8521      macro_build (NULL, "neg", "x,w", xreg, xreg);
8522    }
8523}
8524
8525/* For consistency checking, verify that all bits are specified either
8526   by the match/mask part of the instruction definition, or by the
8527   operand list.  */
8528static int
8529validate_mips_insn (const struct mips_opcode *opc)
8530{
8531  const char *p = opc->args;
8532  char c;
8533  unsigned long used_bits = opc->mask;
8534
8535  if ((used_bits & opc->match) != opc->match)
8536    {
8537      as_bad (_("internal: bad mips opcode (mask error): %s %s"),
8538	      opc->name, opc->args);
8539      return 0;
8540    }
8541#define USE_BITS(mask,shift)	(used_bits |= ((mask) << (shift)))
8542  while (*p)
8543    switch (c = *p++)
8544      {
8545      case ',': break;
8546      case '(': break;
8547      case ')': break;
8548      case '+':
8549    	switch (c = *p++)
8550	  {
8551	  case '1': USE_BITS (OP_MASK_UDI1,     OP_SH_UDI1); 	break;
8552	  case '2': USE_BITS (OP_MASK_UDI2,	OP_SH_UDI2); 	break;
8553	  case '3': USE_BITS (OP_MASK_UDI3,	OP_SH_UDI3); 	break;
8554	  case '4': USE_BITS (OP_MASK_UDI4,	OP_SH_UDI4); 	break;
8555	  case 'A': USE_BITS (OP_MASK_SHAMT,	OP_SH_SHAMT);	break;
8556	  case 'B': USE_BITS (OP_MASK_INSMSB,	OP_SH_INSMSB);	break;
8557	  case 'C': USE_BITS (OP_MASK_EXTMSBD,	OP_SH_EXTMSBD);	break;
8558	  case 'D': USE_BITS (OP_MASK_RD,	OP_SH_RD);
8559		    USE_BITS (OP_MASK_SEL,	OP_SH_SEL);	break;
8560	  case 'E': USE_BITS (OP_MASK_SHAMT,	OP_SH_SHAMT);	break;
8561	  case 'F': USE_BITS (OP_MASK_INSMSB,	OP_SH_INSMSB);	break;
8562	  case 'G': USE_BITS (OP_MASK_EXTMSBD,	OP_SH_EXTMSBD);	break;
8563	  case 'H': USE_BITS (OP_MASK_EXTMSBD,	OP_SH_EXTMSBD);	break;
8564	  case 'I': break;
8565	  case 't': USE_BITS (OP_MASK_RT,	OP_SH_RT);	break;
8566	  case 'T': USE_BITS (OP_MASK_RT,	OP_SH_RT);
8567		    USE_BITS (OP_MASK_SEL,	OP_SH_SEL);	break;
8568	  case 'x': USE_BITS (OP_MASK_BBITIND,	OP_SH_BBITIND);	break;
8569	  case 'X': USE_BITS (OP_MASK_BBITIND,	OP_SH_BBITIND);	break;
8570	  case 'p': USE_BITS (OP_MASK_CINSPOS,	OP_SH_CINSPOS);	break;
8571	  case 'P': USE_BITS (OP_MASK_CINSPOS,	OP_SH_CINSPOS);	break;
8572	  case 'Q': USE_BITS (OP_MASK_SEQI,	OP_SH_SEQI);	break;
8573	  case 's': USE_BITS (OP_MASK_CINSLM1,	OP_SH_CINSLM1);	break;
8574	  case 'S': USE_BITS (OP_MASK_CINSLM1,	OP_SH_CINSLM1);	break;
8575
8576	  default:
8577	    as_bad (_("internal: bad mips opcode (unknown extension operand type `+%c'): %s %s"),
8578		    c, opc->name, opc->args);
8579	    return 0;
8580	  }
8581	break;
8582      case '<': USE_BITS (OP_MASK_SHAMT,	OP_SH_SHAMT);	break;
8583      case '>':	USE_BITS (OP_MASK_SHAMT,	OP_SH_SHAMT);	break;
8584      case 'A': break;
8585      case 'B': USE_BITS (OP_MASK_CODE20,       OP_SH_CODE20);  break;
8586      case 'C':	USE_BITS (OP_MASK_COPZ,		OP_SH_COPZ);	break;
8587      case 'D':	USE_BITS (OP_MASK_FD,		OP_SH_FD);	break;
8588      case 'E':	USE_BITS (OP_MASK_RT,		OP_SH_RT);	break;
8589      case 'F': break;
8590      case 'G':	USE_BITS (OP_MASK_RD,		OP_SH_RD);	break;
8591      case 'H': USE_BITS (OP_MASK_SEL,		OP_SH_SEL);	break;
8592      case 'I': break;
8593      case 'J': USE_BITS (OP_MASK_CODE19,       OP_SH_CODE19);  break;
8594      case 'K':	USE_BITS (OP_MASK_RD,		OP_SH_RD);	break;
8595      case 'L': break;
8596      case 'M':	USE_BITS (OP_MASK_CCC,		OP_SH_CCC);	break;
8597      case 'N':	USE_BITS (OP_MASK_BCC,		OP_SH_BCC);	break;
8598      case 'O':	USE_BITS (OP_MASK_ALN,		OP_SH_ALN);	break;
8599      case 'Q':	USE_BITS (OP_MASK_VSEL,		OP_SH_VSEL);
8600		USE_BITS (OP_MASK_FT,		OP_SH_FT);	break;
8601      case 'R':	USE_BITS (OP_MASK_FR,		OP_SH_FR);	break;
8602      case 'S':	USE_BITS (OP_MASK_FS,		OP_SH_FS);	break;
8603      case 'T':	USE_BITS (OP_MASK_FT,		OP_SH_FT);	break;
8604      case 'V':	USE_BITS (OP_MASK_FS,		OP_SH_FS);	break;
8605      case 'W':	USE_BITS (OP_MASK_FT,		OP_SH_FT);	break;
8606      case 'X':	USE_BITS (OP_MASK_FD,		OP_SH_FD);	break;
8607      case 'Y':	USE_BITS (OP_MASK_FS,		OP_SH_FS);	break;
8608      case 'Z':	USE_BITS (OP_MASK_FT,		OP_SH_FT);	break;
8609      case 'a':	USE_BITS (OP_MASK_TARGET,	OP_SH_TARGET);	break;
8610      case 'b':	USE_BITS (OP_MASK_RS,		OP_SH_RS);	break;
8611      case 'c':	USE_BITS (OP_MASK_CODE,		OP_SH_CODE);	break;
8612      case 'd':	USE_BITS (OP_MASK_RD,		OP_SH_RD);	break;
8613      case 'f': break;
8614      case 'h':	USE_BITS (OP_MASK_PREFX,	OP_SH_PREFX);	break;
8615      case 'i':	USE_BITS (OP_MASK_IMMEDIATE,	OP_SH_IMMEDIATE); break;
8616      case 'j':	USE_BITS (OP_MASK_DELTA,	OP_SH_DELTA);	break;
8617      case 'k':	USE_BITS (OP_MASK_CACHE,	OP_SH_CACHE);	break;
8618      case 'l': break;
8619      case 'o': USE_BITS (OP_MASK_DELTA,	OP_SH_DELTA);	break;
8620      case 'p':	USE_BITS (OP_MASK_DELTA,	OP_SH_DELTA);	break;
8621      case 'q':	USE_BITS (OP_MASK_CODE2,	OP_SH_CODE2);	break;
8622      case 'r': USE_BITS (OP_MASK_RS,		OP_SH_RS);	break;
8623      case 's':	USE_BITS (OP_MASK_RS,		OP_SH_RS);	break;
8624      case 't':	USE_BITS (OP_MASK_RT,		OP_SH_RT);	break;
8625      case 'u':	USE_BITS (OP_MASK_IMMEDIATE,	OP_SH_IMMEDIATE); break;
8626      case 'v':	USE_BITS (OP_MASK_RS,		OP_SH_RS);	break;
8627      case 'w':	USE_BITS (OP_MASK_RT,		OP_SH_RT);	break;
8628      case 'x': break;
8629      case 'z': break;
8630      case 'P': USE_BITS (OP_MASK_PERFREG,	OP_SH_PERFREG);	break;
8631      case 'U': USE_BITS (OP_MASK_RD,           OP_SH_RD);
8632	        USE_BITS (OP_MASK_RT,           OP_SH_RT);	break;
8633      case 'e': USE_BITS (OP_MASK_VECBYTE,	OP_SH_VECBYTE);	break;
8634      case '%': USE_BITS (OP_MASK_VECALIGN,	OP_SH_VECALIGN); break;
8635      case '[': break;
8636      case ']': break;
8637      case '1':	USE_BITS (OP_MASK_SHAMT,	OP_SH_SHAMT);	break;
8638      case '2': USE_BITS (OP_MASK_BP,		OP_SH_BP);	break;
8639      case '3': USE_BITS (OP_MASK_SA3,  	OP_SH_SA3);	break;
8640      case '4': USE_BITS (OP_MASK_SA4,  	OP_SH_SA4);	break;
8641      case '5': USE_BITS (OP_MASK_IMM8, 	OP_SH_IMM8);	break;
8642      case '6': USE_BITS (OP_MASK_RS,		OP_SH_RS);	break;
8643      case '7': USE_BITS (OP_MASK_DSPACC,	OP_SH_DSPACC);	break;
8644      case '8': USE_BITS (OP_MASK_WRDSP,	OP_SH_WRDSP);	break;
8645      case '9': USE_BITS (OP_MASK_DSPACC_S,	OP_SH_DSPACC_S);break;
8646      case '0': USE_BITS (OP_MASK_DSPSFT,	OP_SH_DSPSFT);	break;
8647      case '\'': USE_BITS (OP_MASK_RDDSP,	OP_SH_RDDSP);	break;
8648      case ':': USE_BITS (OP_MASK_DSPSFT_7,	OP_SH_DSPSFT_7);break;
8649      case '@': USE_BITS (OP_MASK_IMM10,	OP_SH_IMM10);	break;
8650      case '!': USE_BITS (OP_MASK_MT_U,		OP_SH_MT_U);	break;
8651      case '$': USE_BITS (OP_MASK_MT_H,		OP_SH_MT_H);	break;
8652      case '*': USE_BITS (OP_MASK_MTACC_T,	OP_SH_MTACC_T);	break;
8653      case '&': USE_BITS (OP_MASK_MTACC_D,	OP_SH_MTACC_D);	break;
8654      case 'g': USE_BITS (OP_MASK_RD,		OP_SH_RD);	break;
8655      default:
8656	as_bad (_("internal: bad mips opcode (unknown operand type `%c'): %s %s"),
8657		c, opc->name, opc->args);
8658	return 0;
8659      }
8660#undef USE_BITS
8661  if (used_bits != 0xffffffff)
8662    {
8663      as_bad (_("internal: bad mips opcode (bits 0x%lx undefined): %s %s"),
8664	      ~used_bits & 0xffffffff, opc->name, opc->args);
8665      return 0;
8666    }
8667  return 1;
8668}
8669
8670/* UDI immediates.  */
8671struct mips_immed {
8672  char		type;
8673  unsigned int	shift;
8674  unsigned long	mask;
8675  const char *	desc;
8676};
8677
8678static const struct mips_immed mips_immed[] = {
8679  { '1',	OP_SH_UDI1,	OP_MASK_UDI1,		0},
8680  { '2',	OP_SH_UDI2,	OP_MASK_UDI2,		0},
8681  { '3',	OP_SH_UDI3,	OP_MASK_UDI3,		0},
8682  { '4',	OP_SH_UDI4,	OP_MASK_UDI4,		0},
8683  { 0,0,0,0 }
8684};
8685
8686/* Check whether an odd floating-point register is allowed.  */
8687static int
8688mips_oddfpreg_ok (const struct mips_opcode *insn, int argnum)
8689{
8690  const char *s = insn->name;
8691
8692  if (insn->pinfo == INSN_MACRO)
8693    /* Let a macro pass, we'll catch it later when it is expanded.  */
8694    return 1;
8695
8696  if (ISA_HAS_ODD_SINGLE_FPR (mips_opts.isa))
8697    {
8698      /* Allow odd registers for single-precision ops.  */
8699      switch (insn->pinfo & (FP_S | FP_D))
8700	{
8701	case FP_S:
8702	case 0:
8703	  return 1;	/* both single precision - ok */
8704	case FP_D:
8705	  return 0;	/* both double precision - fail */
8706	default:
8707	  break;
8708	}
8709
8710      /* Cvt.w.x and cvt.x.w allow an odd register for a 'w' or 's' operand.  */
8711      s = strchr (insn->name, '.');
8712      if (argnum == 2)
8713	s = s != NULL ? strchr (s + 1, '.') : NULL;
8714      return (s != NULL && (s[1] == 'w' || s[1] == 's'));
8715    }
8716
8717  /* Single-precision coprocessor loads and moves are OK too.  */
8718  if ((insn->pinfo & FP_S)
8719      && (insn->pinfo & (INSN_COPROC_MEMORY_DELAY | INSN_STORE_MEMORY
8720			 | INSN_LOAD_COPROC_DELAY | INSN_COPROC_MOVE_DELAY)))
8721    return 1;
8722
8723  return 0;
8724}
8725
8726/* This routine assembles an instruction into its binary format.  As a
8727   side effect, it sets one of the global variables imm_reloc or
8728   offset_reloc to the type of relocation to do if one of the operands
8729   is an address expression.  */
8730
8731static void
8732mips_ip (char *str, struct mips_cl_insn *ip)
8733{
8734  char *s;
8735  const char *args;
8736  char c = 0;
8737  struct mips_opcode *insn;
8738  char *argsStart;
8739  unsigned int regno;
8740  unsigned int lastregno = 0;
8741  unsigned int lastpos = 0;
8742  unsigned int limlo, limhi;
8743  char *s_reset;
8744  char save_c = 0;
8745  offsetT min_range, max_range;
8746  int argnum;
8747  unsigned int rtype;
8748
8749  insn_error = NULL;
8750
8751  /* If the instruction contains a '.', we first try to match an instruction
8752     including the '.'.  Then we try again without the '.'.  */
8753  insn = NULL;
8754  for (s = str; *s != '\0' && !ISSPACE (*s); ++s)
8755    continue;
8756
8757  /* If we stopped on whitespace, then replace the whitespace with null for
8758     the call to hash_find.  Save the character we replaced just in case we
8759     have to re-parse the instruction.  */
8760  if (ISSPACE (*s))
8761    {
8762      save_c = *s;
8763      *s++ = '\0';
8764    }
8765
8766  insn = (struct mips_opcode *) hash_find (op_hash, str);
8767
8768  /* If we didn't find the instruction in the opcode table, try again, but
8769     this time with just the instruction up to, but not including the
8770     first '.'.  */
8771  if (insn == NULL)
8772    {
8773      /* Restore the character we overwrite above (if any).  */
8774      if (save_c)
8775	*(--s) = save_c;
8776
8777      /* Scan up to the first '.' or whitespace.  */
8778      for (s = str;
8779	   *s != '\0' && *s != '.' && !ISSPACE (*s);
8780	   ++s)
8781	continue;
8782
8783      /* If we did not find a '.', then we can quit now.  */
8784      if (*s != '.')
8785	{
8786	  insn_error = _("unrecognized opcode");
8787	  return;
8788	}
8789
8790      /* Lookup the instruction in the hash table.  */
8791      *s++ = '\0';
8792      if ((insn = (struct mips_opcode *) hash_find (op_hash, str)) == NULL)
8793	{
8794	  insn_error = _("unrecognized opcode");
8795	  return;
8796	}
8797    }
8798
8799  argsStart = s;
8800  for (;;)
8801    {
8802      bfd_boolean ok;
8803
8804      gas_assert (strcmp (insn->name, str) == 0);
8805
8806      ok = is_opcode_valid (insn);
8807      if (! ok)
8808	{
8809	  if (insn + 1 < &mips_opcodes[NUMOPCODES]
8810	      && strcmp (insn->name, insn[1].name) == 0)
8811	    {
8812	      ++insn;
8813	      continue;
8814	    }
8815	  else
8816	    {
8817	      if (!insn_error)
8818		{
8819		  static char buf[100];
8820		  sprintf (buf,
8821			   _("opcode not supported on this processor: %s (%s)"),
8822			   mips_cpu_info_from_arch (mips_opts.arch)->name,
8823			   mips_cpu_info_from_isa (mips_opts.isa)->name);
8824		  insn_error = buf;
8825		}
8826	      if (save_c)
8827		*(--s) = save_c;
8828	      return;
8829	    }
8830	}
8831
8832      create_insn (ip, insn);
8833      insn_error = NULL;
8834      argnum = 1;
8835      lastregno = 0xffffffff;
8836      for (args = insn->args;; ++args)
8837	{
8838	  int is_mdmx;
8839
8840	  s += strspn (s, " \t");
8841	  is_mdmx = 0;
8842	  switch (*args)
8843	    {
8844	    case '\0':		/* end of args */
8845	      if (*s == '\0')
8846		return;
8847	      break;
8848
8849	    case '2': /* dsp 2-bit unsigned immediate in bit 11 */
8850	      my_getExpression (&imm_expr, s);
8851	      check_absolute_expr (ip, &imm_expr);
8852	      if ((unsigned long) imm_expr.X_add_number != 1
8853		  && (unsigned long) imm_expr.X_add_number != 3)
8854		{
8855		  as_bad (_("BALIGN immediate not 1 or 3 (%lu)"),
8856			  (unsigned long) imm_expr.X_add_number);
8857		}
8858	      INSERT_OPERAND (BP, *ip, imm_expr.X_add_number);
8859	      imm_expr.X_op = O_absent;
8860	      s = expr_end;
8861	      continue;
8862
8863	    case '3': /* dsp 3-bit unsigned immediate in bit 21 */
8864	      my_getExpression (&imm_expr, s);
8865	      check_absolute_expr (ip, &imm_expr);
8866	      if (imm_expr.X_add_number & ~OP_MASK_SA3)
8867		{
8868		  as_bad (_("DSP immediate not in range 0..%d (%lu)"),
8869			  OP_MASK_SA3, (unsigned long) imm_expr.X_add_number);
8870		}
8871	      INSERT_OPERAND (SA3, *ip, imm_expr.X_add_number);
8872	      imm_expr.X_op = O_absent;
8873	      s = expr_end;
8874	      continue;
8875
8876	    case '4': /* dsp 4-bit unsigned immediate in bit 21 */
8877	      my_getExpression (&imm_expr, s);
8878	      check_absolute_expr (ip, &imm_expr);
8879	      if (imm_expr.X_add_number & ~OP_MASK_SA4)
8880		{
8881		  as_bad (_("DSP immediate not in range 0..%d (%lu)"),
8882			  OP_MASK_SA4, (unsigned long) imm_expr.X_add_number);
8883		}
8884	      INSERT_OPERAND (SA4, *ip, imm_expr.X_add_number);
8885	      imm_expr.X_op = O_absent;
8886	      s = expr_end;
8887	      continue;
8888
8889	    case '5': /* dsp 8-bit unsigned immediate in bit 16 */
8890	      my_getExpression (&imm_expr, s);
8891	      check_absolute_expr (ip, &imm_expr);
8892	      if (imm_expr.X_add_number & ~OP_MASK_IMM8)
8893		{
8894		  as_bad (_("DSP immediate not in range 0..%d (%lu)"),
8895			  OP_MASK_IMM8, (unsigned long) imm_expr.X_add_number);
8896		}
8897	      INSERT_OPERAND (IMM8, *ip, imm_expr.X_add_number);
8898	      imm_expr.X_op = O_absent;
8899	      s = expr_end;
8900	      continue;
8901
8902	    case '6': /* dsp 5-bit unsigned immediate in bit 21 */
8903	      my_getExpression (&imm_expr, s);
8904	      check_absolute_expr (ip, &imm_expr);
8905	      if (imm_expr.X_add_number & ~OP_MASK_RS)
8906		{
8907		  as_bad (_("DSP immediate not in range 0..%d (%lu)"),
8908			  OP_MASK_RS, (unsigned long) imm_expr.X_add_number);
8909		}
8910	      INSERT_OPERAND (RS, *ip, imm_expr.X_add_number);
8911	      imm_expr.X_op = O_absent;
8912	      s = expr_end;
8913	      continue;
8914
8915	    case '7': /* four dsp accumulators in bits 11,12 */
8916	      if (s[0] == '$' && s[1] == 'a' && s[2] == 'c' &&
8917		  s[3] >= '0' && s[3] <= '3')
8918		{
8919		  regno = s[3] - '0';
8920		  s += 4;
8921		  INSERT_OPERAND (DSPACC, *ip, regno);
8922		  continue;
8923		}
8924	      else
8925		as_bad (_("Invalid dsp acc register"));
8926	      break;
8927
8928	    case '8': /* dsp 6-bit unsigned immediate in bit 11 */
8929	      my_getExpression (&imm_expr, s);
8930	      check_absolute_expr (ip, &imm_expr);
8931	      if (imm_expr.X_add_number & ~OP_MASK_WRDSP)
8932		{
8933		  as_bad (_("DSP immediate not in range 0..%d (%lu)"),
8934			  OP_MASK_WRDSP,
8935			  (unsigned long) imm_expr.X_add_number);
8936		}
8937	      INSERT_OPERAND (WRDSP, *ip, imm_expr.X_add_number);
8938	      imm_expr.X_op = O_absent;
8939	      s = expr_end;
8940	      continue;
8941
8942	    case '9': /* four dsp accumulators in bits 21,22 */
8943	      if (s[0] == '$' && s[1] == 'a' && s[2] == 'c' &&
8944		  s[3] >= '0' && s[3] <= '3')
8945		{
8946		  regno = s[3] - '0';
8947		  s += 4;
8948		  INSERT_OPERAND (DSPACC_S, *ip, regno);
8949		  continue;
8950		}
8951	      else
8952		as_bad (_("Invalid dsp acc register"));
8953	      break;
8954
8955	    case '0': /* dsp 6-bit signed immediate in bit 20 */
8956	      my_getExpression (&imm_expr, s);
8957	      check_absolute_expr (ip, &imm_expr);
8958	      min_range = -((OP_MASK_DSPSFT + 1) >> 1);
8959	      max_range = ((OP_MASK_DSPSFT + 1) >> 1) - 1;
8960	      if (imm_expr.X_add_number < min_range ||
8961		  imm_expr.X_add_number > max_range)
8962		{
8963		  as_bad (_("DSP immediate not in range %ld..%ld (%ld)"),
8964			  (long) min_range, (long) max_range,
8965			  (long) imm_expr.X_add_number);
8966		}
8967	      INSERT_OPERAND (DSPSFT, *ip, imm_expr.X_add_number);
8968	      imm_expr.X_op = O_absent;
8969	      s = expr_end;
8970	      continue;
8971
8972	    case '\'': /* dsp 6-bit unsigned immediate in bit 16 */
8973	      my_getExpression (&imm_expr, s);
8974	      check_absolute_expr (ip, &imm_expr);
8975	      if (imm_expr.X_add_number & ~OP_MASK_RDDSP)
8976		{
8977		  as_bad (_("DSP immediate not in range 0..%d (%lu)"),
8978			  OP_MASK_RDDSP,
8979			  (unsigned long) imm_expr.X_add_number);
8980		}
8981	      INSERT_OPERAND (RDDSP, *ip, imm_expr.X_add_number);
8982	      imm_expr.X_op = O_absent;
8983	      s = expr_end;
8984	      continue;
8985
8986	    case ':': /* dsp 7-bit signed immediate in bit 19 */
8987	      my_getExpression (&imm_expr, s);
8988	      check_absolute_expr (ip, &imm_expr);
8989	      min_range = -((OP_MASK_DSPSFT_7 + 1) >> 1);
8990	      max_range = ((OP_MASK_DSPSFT_7 + 1) >> 1) - 1;
8991	      if (imm_expr.X_add_number < min_range ||
8992		  imm_expr.X_add_number > max_range)
8993		{
8994		  as_bad (_("DSP immediate not in range %ld..%ld (%ld)"),
8995			  (long) min_range, (long) max_range,
8996			  (long) imm_expr.X_add_number);
8997		}
8998	      INSERT_OPERAND (DSPSFT_7, *ip, imm_expr.X_add_number);
8999	      imm_expr.X_op = O_absent;
9000	      s = expr_end;
9001	      continue;
9002
9003	    case '@': /* dsp 10-bit signed immediate in bit 16 */
9004	      my_getExpression (&imm_expr, s);
9005	      check_absolute_expr (ip, &imm_expr);
9006	      min_range = -((OP_MASK_IMM10 + 1) >> 1);
9007	      max_range = ((OP_MASK_IMM10 + 1) >> 1) - 1;
9008	      if (imm_expr.X_add_number < min_range ||
9009		  imm_expr.X_add_number > max_range)
9010		{
9011		  as_bad (_("DSP immediate not in range %ld..%ld (%ld)"),
9012			  (long) min_range, (long) max_range,
9013			  (long) imm_expr.X_add_number);
9014		}
9015	      INSERT_OPERAND (IMM10, *ip, imm_expr.X_add_number);
9016	      imm_expr.X_op = O_absent;
9017	      s = expr_end;
9018	      continue;
9019
9020            case '!': /* MT usermode flag bit.  */
9021	      my_getExpression (&imm_expr, s);
9022	      check_absolute_expr (ip, &imm_expr);
9023	      if (imm_expr.X_add_number & ~OP_MASK_MT_U)
9024		as_bad (_("MT usermode bit not 0 or 1 (%lu)"),
9025			(unsigned long) imm_expr.X_add_number);
9026	      INSERT_OPERAND (MT_U, *ip, imm_expr.X_add_number);
9027	      imm_expr.X_op = O_absent;
9028	      s = expr_end;
9029	      continue;
9030
9031            case '$': /* MT load high flag bit.  */
9032	      my_getExpression (&imm_expr, s);
9033	      check_absolute_expr (ip, &imm_expr);
9034	      if (imm_expr.X_add_number & ~OP_MASK_MT_H)
9035		as_bad (_("MT load high bit not 0 or 1 (%lu)"),
9036			(unsigned long) imm_expr.X_add_number);
9037	      INSERT_OPERAND (MT_H, *ip, imm_expr.X_add_number);
9038	      imm_expr.X_op = O_absent;
9039	      s = expr_end;
9040	      continue;
9041
9042	    case '*': /* four dsp accumulators in bits 18,19 */
9043	      if (s[0] == '$' && s[1] == 'a' && s[2] == 'c' &&
9044		  s[3] >= '0' && s[3] <= '3')
9045		{
9046		  regno = s[3] - '0';
9047		  s += 4;
9048		  INSERT_OPERAND (MTACC_T, *ip, regno);
9049		  continue;
9050		}
9051	      else
9052		as_bad (_("Invalid dsp/smartmips acc register"));
9053	      break;
9054
9055	    case '&': /* four dsp accumulators in bits 13,14 */
9056	      if (s[0] == '$' && s[1] == 'a' && s[2] == 'c' &&
9057		  s[3] >= '0' && s[3] <= '3')
9058		{
9059		  regno = s[3] - '0';
9060		  s += 4;
9061		  INSERT_OPERAND (MTACC_D, *ip, regno);
9062		  continue;
9063		}
9064	      else
9065		as_bad (_("Invalid dsp/smartmips acc register"));
9066	      break;
9067
9068	    case ',':
9069	      ++argnum;
9070	      if (*s++ == *args)
9071		continue;
9072	      s--;
9073	      switch (*++args)
9074		{
9075		case 'r':
9076		case 'v':
9077		  INSERT_OPERAND (RS, *ip, lastregno);
9078		  continue;
9079
9080		case 'w':
9081		  INSERT_OPERAND (RT, *ip, lastregno);
9082		  continue;
9083
9084		case 'W':
9085		  INSERT_OPERAND (FT, *ip, lastregno);
9086		  continue;
9087
9088		case 'V':
9089		  INSERT_OPERAND (FS, *ip, lastregno);
9090		  continue;
9091		}
9092	      break;
9093
9094	    case '(':
9095	      /* Handle optional base register.
9096		 Either the base register is omitted or
9097		 we must have a left paren.  */
9098	      /* This is dependent on the next operand specifier
9099		 is a base register specification.  */
9100	      gas_assert (args[1] == 'b' || args[1] == '5'
9101		      || args[1] == '-' || args[1] == '4');
9102	      if (*s == '\0')
9103		return;
9104
9105	    case ')':		/* these must match exactly */
9106	    case '[':
9107	    case ']':
9108	      if (*s++ == *args)
9109		continue;
9110	      break;
9111
9112	    case '+':		/* Opcode extension character.  */
9113	      switch (*++args)
9114		{
9115		case '1':	/* UDI immediates.  */
9116		case '2':
9117		case '3':
9118		case '4':
9119		  {
9120		    const struct mips_immed *imm = mips_immed;
9121
9122		    while (imm->type && imm->type != *args)
9123		      ++imm;
9124		    if (! imm->type)
9125		      internalError ();
9126		    my_getExpression (&imm_expr, s);
9127		    check_absolute_expr (ip, &imm_expr);
9128		    if ((unsigned long) imm_expr.X_add_number & ~imm->mask)
9129		      {
9130		        as_warn (_("Illegal %s number (%lu, 0x%lx)"),
9131				 imm->desc ? imm->desc : ip->insn_mo->name,
9132				 (unsigned long) imm_expr.X_add_number,
9133				 (unsigned long) imm_expr.X_add_number);
9134			      imm_expr.X_add_number &= imm->mask;
9135		      }
9136		    ip->insn_opcode |= ((unsigned long) imm_expr.X_add_number
9137					<< imm->shift);
9138		    imm_expr.X_op = O_absent;
9139		    s = expr_end;
9140		  }
9141		  continue;
9142
9143		case 'A':		/* ins/ext position, becomes LSB.  */
9144		  limlo = 0;
9145		  limhi = 31;
9146		  goto do_lsb;
9147		case 'E':
9148		  limlo = 32;
9149		  limhi = 63;
9150		  goto do_lsb;
9151do_lsb:
9152		  my_getExpression (&imm_expr, s);
9153		  check_absolute_expr (ip, &imm_expr);
9154		  if ((unsigned long) imm_expr.X_add_number < limlo
9155		      || (unsigned long) imm_expr.X_add_number > limhi)
9156		    {
9157		      as_bad (_("Improper position (%lu)"),
9158			      (unsigned long) imm_expr.X_add_number);
9159		      imm_expr.X_add_number = limlo;
9160		    }
9161		  lastpos = imm_expr.X_add_number;
9162		  INSERT_OPERAND (SHAMT, *ip, imm_expr.X_add_number);
9163		  imm_expr.X_op = O_absent;
9164		  s = expr_end;
9165		  continue;
9166
9167		case 'B':		/* ins size, becomes MSB.  */
9168		  limlo = 1;
9169		  limhi = 32;
9170		  goto do_msb;
9171		case 'F':
9172		  limlo = 33;
9173		  limhi = 64;
9174		  goto do_msb;
9175do_msb:
9176		  my_getExpression (&imm_expr, s);
9177		  check_absolute_expr (ip, &imm_expr);
9178		  /* Check for negative input so that small negative numbers
9179		     will not succeed incorrectly.  The checks against
9180		     (pos+size) transitively check "size" itself,
9181		     assuming that "pos" is reasonable.  */
9182		  if ((long) imm_expr.X_add_number < 0
9183		      || ((unsigned long) imm_expr.X_add_number
9184			  + lastpos) < limlo
9185		      || ((unsigned long) imm_expr.X_add_number
9186			  + lastpos) > limhi)
9187		    {
9188		      as_bad (_("Improper insert size (%lu, position %lu)"),
9189			      (unsigned long) imm_expr.X_add_number,
9190			      (unsigned long) lastpos);
9191		      imm_expr.X_add_number = limlo - lastpos;
9192		    }
9193		  INSERT_OPERAND (INSMSB, *ip,
9194				 lastpos + imm_expr.X_add_number - 1);
9195		  imm_expr.X_op = O_absent;
9196		  s = expr_end;
9197		  continue;
9198
9199		case 'C':		/* ext size, becomes MSBD.  */
9200		  limlo = 1;
9201		  limhi = 32;
9202		  goto do_msbd;
9203		case 'G':
9204		  limlo = 33;
9205		  limhi = 64;
9206		  goto do_msbd;
9207		case 'H':
9208		  limlo = 33;
9209		  limhi = 64;
9210		  goto do_msbd;
9211do_msbd:
9212		  my_getExpression (&imm_expr, s);
9213		  check_absolute_expr (ip, &imm_expr);
9214		  /* Check for negative input so that small negative numbers
9215		     will not succeed incorrectly.  The checks against
9216		     (pos+size) transitively check "size" itself,
9217		     assuming that "pos" is reasonable.  */
9218		  if ((long) imm_expr.X_add_number < 0
9219		      || ((unsigned long) imm_expr.X_add_number
9220			  + lastpos) < limlo
9221		      || ((unsigned long) imm_expr.X_add_number
9222			  + lastpos) > limhi)
9223		    {
9224		      as_bad (_("Improper extract size (%lu, position %lu)"),
9225			      (unsigned long) imm_expr.X_add_number,
9226			      (unsigned long) lastpos);
9227		      imm_expr.X_add_number = limlo - lastpos;
9228		    }
9229		  INSERT_OPERAND (EXTMSBD, *ip, imm_expr.X_add_number - 1);
9230		  imm_expr.X_op = O_absent;
9231		  s = expr_end;
9232		  continue;
9233
9234		case 'D':
9235		  /* +D is for disassembly only; never match.  */
9236		  break;
9237
9238		case 'I':
9239		  /* "+I" is like "I", except that imm2_expr is used.  */
9240		  my_getExpression (&imm2_expr, s);
9241		  if (imm2_expr.X_op != O_big
9242		      && imm2_expr.X_op != O_constant)
9243		  insn_error = _("absolute expression required");
9244		  if (HAVE_32BIT_GPRS)
9245		    normalize_constant_expr (&imm2_expr);
9246		  s = expr_end;
9247		  continue;
9248
9249		case 'T': /* Coprocessor register.  */
9250		  /* +T is for disassembly only; never match.  */
9251		  break;
9252
9253		case 't': /* Coprocessor register number.  */
9254		  if (s[0] == '$' && ISDIGIT (s[1]))
9255		    {
9256		      ++s;
9257		      regno = 0;
9258		      do
9259		        {
9260			  regno *= 10;
9261			  regno += *s - '0';
9262			  ++s;
9263			}
9264		      while (ISDIGIT (*s));
9265		      if (regno > 31)
9266			as_bad (_("Invalid register number (%d)"), regno);
9267		      else
9268			{
9269			  INSERT_OPERAND (RT, *ip, regno);
9270			  continue;
9271			}
9272		    }
9273		  else
9274		    as_bad (_("Invalid coprocessor 0 register number"));
9275		  break;
9276
9277		case 'x':
9278		  /* bbit[01] and bbit[01]32 bit index.  Give error if index
9279		     is not in the valid range.  */
9280		  my_getExpression (&imm_expr, s);
9281		  check_absolute_expr (ip, &imm_expr);
9282		  if ((unsigned) imm_expr.X_add_number > 31)
9283		    {
9284		      as_bad (_("Improper bit index (%lu)"),
9285			      (unsigned long) imm_expr.X_add_number);
9286		      imm_expr.X_add_number = 0;
9287		    }
9288		  INSERT_OPERAND (BBITIND, *ip, imm_expr.X_add_number);
9289		  imm_expr.X_op = O_absent;
9290		  s = expr_end;
9291		  continue;
9292
9293		case 'X':
9294		  /* bbit[01] bit index when bbit is used but we generate
9295		     bbit[01]32 because the index is over 32.  Move to the
9296		     next candidate if index is not in the valid range.  */
9297		  my_getExpression (&imm_expr, s);
9298		  check_absolute_expr (ip, &imm_expr);
9299		  if ((unsigned) imm_expr.X_add_number < 32
9300		      || (unsigned) imm_expr.X_add_number > 63)
9301		    break;
9302		  INSERT_OPERAND (BBITIND, *ip, imm_expr.X_add_number - 32);
9303		  imm_expr.X_op = O_absent;
9304		  s = expr_end;
9305		  continue;
9306
9307		case 'p':
9308		  /* cins, cins32, exts and exts32 position field.  Give error
9309		     if it's not in the valid range.  */
9310		  my_getExpression (&imm_expr, s);
9311		  check_absolute_expr (ip, &imm_expr);
9312		  if ((unsigned) imm_expr.X_add_number > 31)
9313		    {
9314		      as_bad (_("Improper position (%lu)"),
9315			      (unsigned long) imm_expr.X_add_number);
9316		      imm_expr.X_add_number = 0;
9317		    }
9318		  /* Make the pos explicit to simplify +S.  */
9319		  lastpos = imm_expr.X_add_number + 32;
9320		  INSERT_OPERAND (CINSPOS, *ip, imm_expr.X_add_number);
9321		  imm_expr.X_op = O_absent;
9322		  s = expr_end;
9323		  continue;
9324
9325		case 'P':
9326		  /* cins, cins32, exts and exts32 position field.  Move to
9327		     the next candidate if it's not in the valid range.  */
9328		  my_getExpression (&imm_expr, s);
9329		  check_absolute_expr (ip, &imm_expr);
9330		  if ((unsigned) imm_expr.X_add_number < 32
9331		      || (unsigned) imm_expr.X_add_number > 63)
9332		    break;
9333 		  lastpos = imm_expr.X_add_number;
9334		  INSERT_OPERAND (CINSPOS, *ip, imm_expr.X_add_number - 32);
9335		  imm_expr.X_op = O_absent;
9336		  s = expr_end;
9337		  continue;
9338
9339		case 's':
9340		  /* cins and exts length-minus-one field.  */
9341		  my_getExpression (&imm_expr, s);
9342		  check_absolute_expr (ip, &imm_expr);
9343		  if ((unsigned long) imm_expr.X_add_number > 31)
9344		    {
9345		      as_bad (_("Improper size (%lu)"),
9346			      (unsigned long) imm_expr.X_add_number);
9347		      imm_expr.X_add_number = 0;
9348		    }
9349		  INSERT_OPERAND (CINSLM1, *ip, imm_expr.X_add_number);
9350		  imm_expr.X_op = O_absent;
9351		  s = expr_end;
9352		  continue;
9353
9354		case 'S':
9355		  /* cins32/exts32 and cins/exts aliasing cint32/exts32
9356		     length-minus-one field.  */
9357		  my_getExpression (&imm_expr, s);
9358		  check_absolute_expr (ip, &imm_expr);
9359		  if ((long) imm_expr.X_add_number < 0
9360		      || (unsigned long) imm_expr.X_add_number + lastpos > 63)
9361		    {
9362		      as_bad (_("Improper size (%lu)"),
9363			      (unsigned long) imm_expr.X_add_number);
9364		      imm_expr.X_add_number = 0;
9365		    }
9366		  INSERT_OPERAND (CINSLM1, *ip, imm_expr.X_add_number);
9367		  imm_expr.X_op = O_absent;
9368		  s = expr_end;
9369		  continue;
9370
9371		case 'Q':
9372		  /* seqi/snei immediate field.  */
9373		  my_getExpression (&imm_expr, s);
9374		  check_absolute_expr (ip, &imm_expr);
9375		  if ((long) imm_expr.X_add_number < -512
9376		      || (long) imm_expr.X_add_number >= 512)
9377		    {
9378		      as_bad (_("Improper immediate (%ld)"),
9379			       (long) imm_expr.X_add_number);
9380		      imm_expr.X_add_number = 0;
9381		    }
9382		  INSERT_OPERAND (SEQI, *ip, imm_expr.X_add_number);
9383		  imm_expr.X_op = O_absent;
9384		  s = expr_end;
9385		  continue;
9386
9387		default:
9388		  as_bad (_("internal: bad mips opcode (unknown extension operand type `+%c'): %s %s"),
9389		    *args, insn->name, insn->args);
9390		  /* Further processing is fruitless.  */
9391		  return;
9392		}
9393	      break;
9394
9395	    case '<':		/* must be at least one digit */
9396	      /*
9397	       * According to the manual, if the shift amount is greater
9398	       * than 31 or less than 0, then the shift amount should be
9399	       * mod 32.  In reality the mips assembler issues an error.
9400	       * We issue a warning and mask out all but the low 5 bits.
9401	       */
9402	      my_getExpression (&imm_expr, s);
9403	      check_absolute_expr (ip, &imm_expr);
9404	      if ((unsigned long) imm_expr.X_add_number > 31)
9405		as_warn (_("Improper shift amount (%lu)"),
9406			 (unsigned long) imm_expr.X_add_number);
9407	      INSERT_OPERAND (SHAMT, *ip, imm_expr.X_add_number);
9408	      imm_expr.X_op = O_absent;
9409	      s = expr_end;
9410	      continue;
9411
9412	    case '>':		/* shift amount minus 32 */
9413	      my_getExpression (&imm_expr, s);
9414	      check_absolute_expr (ip, &imm_expr);
9415	      if ((unsigned long) imm_expr.X_add_number < 32
9416		  || (unsigned long) imm_expr.X_add_number > 63)
9417		break;
9418	      INSERT_OPERAND (SHAMT, *ip, imm_expr.X_add_number - 32);
9419	      imm_expr.X_op = O_absent;
9420	      s = expr_end;
9421	      continue;
9422
9423	    case 'k':		/* cache code */
9424	    case 'h':		/* prefx code */
9425	    case '1':		/* sync type */
9426	      my_getExpression (&imm_expr, s);
9427	      check_absolute_expr (ip, &imm_expr);
9428	      if ((unsigned long) imm_expr.X_add_number > 31)
9429		as_warn (_("Invalid value for `%s' (%lu)"),
9430			 ip->insn_mo->name,
9431			 (unsigned long) imm_expr.X_add_number);
9432	      if (*args == 'k')
9433		{
9434		  if (mips_fix_cn63xxp1 && strcmp ("pref", insn->name) == 0)
9435		    switch (imm_expr.X_add_number)
9436		      {
9437		      case 5:
9438		      case 25:
9439		      case 26:
9440		      case 27:
9441		      case 28:
9442		      case 29:
9443		      case 30:
9444		      case 31:  /* These are ok.  */
9445			break;
9446
9447		      default:  /* The rest must be changed to 28.  */
9448			imm_expr.X_add_number = 28;
9449			break;
9450		      }
9451		  INSERT_OPERAND (CACHE, *ip, imm_expr.X_add_number);
9452		}
9453	      else if (*args == 'h')
9454		INSERT_OPERAND (PREFX, *ip, imm_expr.X_add_number);
9455	      else
9456		INSERT_OPERAND (SHAMT, *ip, imm_expr.X_add_number);
9457	      imm_expr.X_op = O_absent;
9458	      s = expr_end;
9459	      continue;
9460
9461	    case 'c':		/* break code */
9462	      my_getExpression (&imm_expr, s);
9463	      check_absolute_expr (ip, &imm_expr);
9464	      if ((unsigned long) imm_expr.X_add_number > OP_MASK_CODE)
9465		as_warn (_("Code for %s not in range 0..1023 (%lu)"),
9466			 ip->insn_mo->name,
9467			 (unsigned long) imm_expr.X_add_number);
9468	      INSERT_OPERAND (CODE, *ip, imm_expr.X_add_number);
9469	      imm_expr.X_op = O_absent;
9470	      s = expr_end;
9471	      continue;
9472
9473	    case 'q':		/* lower break code */
9474	      my_getExpression (&imm_expr, s);
9475	      check_absolute_expr (ip, &imm_expr);
9476	      if ((unsigned long) imm_expr.X_add_number > OP_MASK_CODE2)
9477		as_warn (_("Lower code for %s not in range 0..1023 (%lu)"),
9478			 ip->insn_mo->name,
9479			 (unsigned long) imm_expr.X_add_number);
9480	      INSERT_OPERAND (CODE2, *ip, imm_expr.X_add_number);
9481	      imm_expr.X_op = O_absent;
9482	      s = expr_end;
9483	      continue;
9484
9485	    case 'B':           /* 20-bit syscall/break code.  */
9486	      my_getExpression (&imm_expr, s);
9487	      check_absolute_expr (ip, &imm_expr);
9488	      if ((unsigned long) imm_expr.X_add_number > OP_MASK_CODE20)
9489		as_warn (_("Code for %s not in range 0..1048575 (%lu)"),
9490			 ip->insn_mo->name,
9491			 (unsigned long) imm_expr.X_add_number);
9492	      INSERT_OPERAND (CODE20, *ip, imm_expr.X_add_number);
9493	      imm_expr.X_op = O_absent;
9494	      s = expr_end;
9495	      continue;
9496
9497	    case 'C':           /* Coprocessor code */
9498	      my_getExpression (&imm_expr, s);
9499	      check_absolute_expr (ip, &imm_expr);
9500	      if ((unsigned long) imm_expr.X_add_number > OP_MASK_COPZ)
9501		{
9502		  as_warn (_("Coproccesor code > 25 bits (%lu)"),
9503			   (unsigned long) imm_expr.X_add_number);
9504		  imm_expr.X_add_number &= OP_MASK_COPZ;
9505		}
9506	      INSERT_OPERAND (COPZ, *ip, imm_expr.X_add_number);
9507	      imm_expr.X_op = O_absent;
9508	      s = expr_end;
9509	      continue;
9510
9511	    case 'J':           /* 19-bit wait code.  */
9512	      my_getExpression (&imm_expr, s);
9513	      check_absolute_expr (ip, &imm_expr);
9514	      if ((unsigned long) imm_expr.X_add_number > OP_MASK_CODE19)
9515		{
9516		  as_warn (_("Illegal 19-bit code (%lu)"),
9517			   (unsigned long) imm_expr.X_add_number);
9518		  imm_expr.X_add_number &= OP_MASK_CODE19;
9519		}
9520	      INSERT_OPERAND (CODE19, *ip, imm_expr.X_add_number);
9521	      imm_expr.X_op = O_absent;
9522	      s = expr_end;
9523	      continue;
9524
9525	    case 'P':		/* Performance register.  */
9526	      my_getExpression (&imm_expr, s);
9527	      check_absolute_expr (ip, &imm_expr);
9528	      if (imm_expr.X_add_number != 0 && imm_expr.X_add_number != 1)
9529		as_warn (_("Invalid performance register (%lu)"),
9530			 (unsigned long) imm_expr.X_add_number);
9531	      INSERT_OPERAND (PERFREG, *ip, imm_expr.X_add_number);
9532	      imm_expr.X_op = O_absent;
9533	      s = expr_end;
9534	      continue;
9535
9536	    case 'G':		/* Coprocessor destination register.  */
9537	      if (((ip->insn_opcode >> OP_SH_OP) & OP_MASK_OP) == OP_OP_COP0)
9538		ok = reg_lookup (&s, RTYPE_NUM | RTYPE_CP0, &regno);
9539	      else
9540		ok = reg_lookup (&s, RTYPE_NUM | RTYPE_GP, &regno);
9541	      INSERT_OPERAND (RD, *ip, regno);
9542	      if (ok)
9543		{
9544		  lastregno = regno;
9545		  continue;
9546		}
9547	      else
9548		break;
9549
9550	    case 'b':		/* base register */
9551	    case 'd':		/* destination register */
9552	    case 's':		/* source register */
9553	    case 't':		/* target register */
9554	    case 'r':		/* both target and source */
9555	    case 'v':		/* both dest and source */
9556	    case 'w':		/* both dest and target */
9557	    case 'E':		/* coprocessor target register */
9558	    case 'K':		/* 'rdhwr' destination register */
9559	    case 'x':		/* ignore register name */
9560	    case 'z':		/* must be zero register */
9561	    case 'U':           /* destination register (clo/clz).  */
9562	    case 'g':		/* coprocessor destination register */
9563	      s_reset = s;
9564	      if (*args == 'E' || *args == 'K')
9565		ok = reg_lookup (&s, RTYPE_NUM, &regno);
9566	      else
9567		{
9568		  ok = reg_lookup (&s, RTYPE_NUM | RTYPE_GP, &regno);
9569		  if (regno == AT && mips_opts.at)
9570		    {
9571		      if (mips_opts.at == ATREG)
9572			as_warn (_("used $at without \".set noat\""));
9573		      else
9574			as_warn (_("used $%u with \".set at=$%u\""),
9575				 regno, mips_opts.at);
9576		    }
9577		}
9578	      if (ok)
9579		{
9580		  c = *args;
9581		  if (*s == ' ')
9582		    ++s;
9583		  if (args[1] != *s)
9584		    {
9585		      if (c == 'r' || c == 'v' || c == 'w')
9586			{
9587			  regno = lastregno;
9588			  s = s_reset;
9589			  ++args;
9590			}
9591		    }
9592		  /* 'z' only matches $0.  */
9593		  if (c == 'z' && regno != 0)
9594		    break;
9595
9596		  if (c == 's' && !strncmp (ip->insn_mo->name, "jalr", 4))
9597		    {
9598		      if (regno == lastregno)
9599		        {
9600			  insn_error = _("source and destination must be different");
9601			  continue;
9602		        }
9603		      if (regno == 31 && lastregno == 0xffffffff)
9604		        {
9605			  insn_error = _("a destination register must be supplied");
9606			  continue;
9607		        }
9608		    }
9609	/* Now that we have assembled one operand, we use the args string
9610	 * to figure out where it goes in the instruction.  */
9611		  switch (c)
9612		    {
9613		    case 'r':
9614		    case 's':
9615		    case 'v':
9616		    case 'b':
9617		      INSERT_OPERAND (RS, *ip, regno);
9618		      break;
9619		    case 'd':
9620		    case 'G':
9621		    case 'K':
9622		    case 'g':
9623		      INSERT_OPERAND (RD, *ip, regno);
9624		      break;
9625		    case 'U':
9626		      INSERT_OPERAND (RD, *ip, regno);
9627		      INSERT_OPERAND (RT, *ip, regno);
9628		      break;
9629		    case 'w':
9630		    case 't':
9631		    case 'E':
9632		      INSERT_OPERAND (RT, *ip, regno);
9633		      break;
9634		    case 'x':
9635		      /* This case exists because on the r3000 trunc
9636			 expands into a macro which requires a gp
9637			 register.  On the r6000 or r4000 it is
9638			 assembled into a single instruction which
9639			 ignores the register.  Thus the insn version
9640			 is MIPS_ISA2 and uses 'x', and the macro
9641			 version is MIPS_ISA1 and uses 't'.  */
9642		      break;
9643		    case 'z':
9644		      /* This case is for the div instruction, which
9645			 acts differently if the destination argument
9646			 is $0.  This only matches $0, and is checked
9647			 outside the switch.  */
9648		      break;
9649		    case 'D':
9650		      /* Itbl operand; not yet implemented. FIXME ?? */
9651		      break;
9652		      /* What about all other operands like 'i', which
9653			 can be specified in the opcode table? */
9654		    }
9655		  lastregno = regno;
9656		  continue;
9657		}
9658	      switch (*args++)
9659		{
9660		case 'r':
9661		case 'v':
9662		  INSERT_OPERAND (RS, *ip, lastregno);
9663		  continue;
9664		case 'w':
9665		  INSERT_OPERAND (RT, *ip, lastregno);
9666		  continue;
9667		}
9668	      break;
9669
9670	    case 'O':		/* MDMX alignment immediate constant.  */
9671	      my_getExpression (&imm_expr, s);
9672	      check_absolute_expr (ip, &imm_expr);
9673	      if ((unsigned long) imm_expr.X_add_number > OP_MASK_ALN)
9674		as_warn (_("Improper align amount (%ld), using low bits"),
9675			 (long) imm_expr.X_add_number);
9676	      INSERT_OPERAND (ALN, *ip, imm_expr.X_add_number);
9677	      imm_expr.X_op = O_absent;
9678	      s = expr_end;
9679	      continue;
9680
9681	    case 'Q':		/* MDMX vector, element sel, or const.  */
9682	      if (s[0] != '$')
9683		{
9684		  /* MDMX Immediate.  */
9685		  my_getExpression (&imm_expr, s);
9686		  check_absolute_expr (ip, &imm_expr);
9687		  if ((unsigned long) imm_expr.X_add_number > OP_MASK_FT)
9688		    as_warn (_("Invalid MDMX Immediate (%ld)"),
9689			     (long) imm_expr.X_add_number);
9690		  INSERT_OPERAND (FT, *ip, imm_expr.X_add_number);
9691		  if (ip->insn_opcode & (OP_MASK_VSEL << OP_SH_VSEL))
9692		    ip->insn_opcode |= MDMX_FMTSEL_IMM_QH << OP_SH_VSEL;
9693		  else
9694		    ip->insn_opcode |= MDMX_FMTSEL_IMM_OB << OP_SH_VSEL;
9695		  imm_expr.X_op = O_absent;
9696		  s = expr_end;
9697		  continue;
9698		}
9699	      /* Not MDMX Immediate.  Fall through.  */
9700	    case 'X':           /* MDMX destination register.  */
9701	    case 'Y':           /* MDMX source register.  */
9702	    case 'Z':           /* MDMX target register.  */
9703	      is_mdmx = 1;
9704	    case 'D':		/* floating point destination register */
9705	    case 'S':		/* floating point source register */
9706	    case 'T':		/* floating point target register */
9707	    case 'R':		/* floating point source register */
9708	    case 'V':
9709	    case 'W':
9710	      rtype = RTYPE_FPU;
9711	      if (is_mdmx
9712		  || (mips_opts.ase_mdmx
9713		      && (ip->insn_mo->pinfo & FP_D)
9714		      && (ip->insn_mo->pinfo & (INSN_COPROC_MOVE_DELAY
9715						| INSN_COPROC_MEMORY_DELAY
9716						| INSN_LOAD_COPROC_DELAY
9717						| INSN_LOAD_MEMORY_DELAY
9718						| INSN_STORE_MEMORY))))
9719		rtype |= RTYPE_VEC;
9720	      s_reset = s;
9721	      if (reg_lookup (&s, rtype, &regno))
9722		{
9723		  if ((regno & 1) != 0
9724		      && HAVE_32BIT_FPRS
9725		      && ! mips_oddfpreg_ok (ip->insn_mo, argnum))
9726		    as_warn (_("Float register should be even, was %d"),
9727			     regno);
9728
9729		  c = *args;
9730		  if (*s == ' ')
9731		    ++s;
9732		  if (args[1] != *s)
9733		    {
9734		      if (c == 'V' || c == 'W')
9735			{
9736			  regno = lastregno;
9737			  s = s_reset;
9738			  ++args;
9739			}
9740		    }
9741		  switch (c)
9742		    {
9743		    case 'D':
9744		    case 'X':
9745		      INSERT_OPERAND (FD, *ip, regno);
9746		      break;
9747		    case 'V':
9748		    case 'S':
9749		    case 'Y':
9750		      INSERT_OPERAND (FS, *ip, regno);
9751		      break;
9752		    case 'Q':
9753		      /* This is like 'Z', but also needs to fix the MDMX
9754			 vector/scalar select bits.  Note that the
9755			 scalar immediate case is handled above.  */
9756		      if (*s == '[')
9757			{
9758			  int is_qh = (ip->insn_opcode & (1 << OP_SH_VSEL));
9759			  int max_el = (is_qh ? 3 : 7);
9760			  s++;
9761			  my_getExpression(&imm_expr, s);
9762			  check_absolute_expr (ip, &imm_expr);
9763			  s = expr_end;
9764			  if (imm_expr.X_add_number > max_el)
9765			    as_bad (_("Bad element selector %ld"),
9766				    (long) imm_expr.X_add_number);
9767			  imm_expr.X_add_number &= max_el;
9768			  ip->insn_opcode |= (imm_expr.X_add_number
9769					      << (OP_SH_VSEL +
9770						  (is_qh ? 2 : 1)));
9771			  imm_expr.X_op = O_absent;
9772			  if (*s != ']')
9773			    as_warn (_("Expecting ']' found '%s'"), s);
9774			  else
9775			    s++;
9776			}
9777		      else
9778                        {
9779                          if (ip->insn_opcode & (OP_MASK_VSEL << OP_SH_VSEL))
9780                            ip->insn_opcode |= (MDMX_FMTSEL_VEC_QH
9781						<< OP_SH_VSEL);
9782			  else
9783			    ip->insn_opcode |= (MDMX_FMTSEL_VEC_OB <<
9784						OP_SH_VSEL);
9785			}
9786                      /* Fall through */
9787		    case 'W':
9788		    case 'T':
9789		    case 'Z':
9790		      INSERT_OPERAND (FT, *ip, regno);
9791		      break;
9792		    case 'R':
9793		      INSERT_OPERAND (FR, *ip, regno);
9794		      break;
9795		    }
9796		  lastregno = regno;
9797		  continue;
9798		}
9799
9800	      switch (*args++)
9801		{
9802		case 'V':
9803		  INSERT_OPERAND (FS, *ip, lastregno);
9804		  continue;
9805		case 'W':
9806		  INSERT_OPERAND (FT, *ip, lastregno);
9807		  continue;
9808		}
9809	      break;
9810
9811	    case 'I':
9812	      my_getExpression (&imm_expr, s);
9813	      if (imm_expr.X_op != O_big
9814		  && imm_expr.X_op != O_constant)
9815		insn_error = _("absolute expression required");
9816	      if (HAVE_32BIT_GPRS)
9817		normalize_constant_expr (&imm_expr);
9818	      s = expr_end;
9819	      continue;
9820
9821	    case 'A':
9822	      my_getExpression (&offset_expr, s);
9823	      normalize_address_expr (&offset_expr);
9824	      *imm_reloc = BFD_RELOC_32;
9825	      s = expr_end;
9826	      continue;
9827
9828	    case 'F':
9829	    case 'L':
9830	    case 'f':
9831	    case 'l':
9832	      {
9833		int f64;
9834		int using_gprs;
9835		char *save_in;
9836		char *err;
9837		unsigned char temp[8];
9838		int len;
9839		unsigned int length;
9840		segT seg;
9841		subsegT subseg;
9842		char *p;
9843
9844		/* These only appear as the last operand in an
9845		   instruction, and every instruction that accepts
9846		   them in any variant accepts them in all variants.
9847		   This means we don't have to worry about backing out
9848		   any changes if the instruction does not match.
9849
9850		   The difference between them is the size of the
9851		   floating point constant and where it goes.  For 'F'
9852		   and 'L' the constant is 64 bits; for 'f' and 'l' it
9853		   is 32 bits.  Where the constant is placed is based
9854		   on how the MIPS assembler does things:
9855		    F -- .rdata
9856		    L -- .lit8
9857		    f -- immediate value
9858		    l -- .lit4
9859
9860		    The .lit4 and .lit8 sections are only used if
9861		    permitted by the -G argument.
9862
9863		    The code below needs to know whether the target register
9864		    is 32 or 64 bits wide.  It relies on the fact 'f' and
9865		    'F' are used with GPR-based instructions and 'l' and
9866		    'L' are used with FPR-based instructions.  */
9867
9868		f64 = *args == 'F' || *args == 'L';
9869		using_gprs = *args == 'F' || *args == 'f';
9870
9871		save_in = input_line_pointer;
9872		input_line_pointer = s;
9873		err = md_atof (f64 ? 'd' : 'f', (char *) temp, &len);
9874		length = len;
9875		s = input_line_pointer;
9876		input_line_pointer = save_in;
9877		if (err != NULL && *err != '\0')
9878		  {
9879		    as_bad (_("Bad floating point constant: %s"), err);
9880		    memset (temp, '\0', sizeof temp);
9881		    length = f64 ? 8 : 4;
9882		  }
9883
9884		gas_assert (length == (unsigned) (f64 ? 8 : 4));
9885
9886		if (*args == 'f'
9887		    || (*args == 'l'
9888			&& (g_switch_value < 4
9889			    || (temp[0] == 0 && temp[1] == 0)
9890			    || (temp[2] == 0 && temp[3] == 0))))
9891		  {
9892		    imm_expr.X_op = O_constant;
9893		    if (! target_big_endian)
9894		      imm_expr.X_add_number = bfd_getl32 (temp);
9895		    else
9896		      imm_expr.X_add_number = bfd_getb32 (temp);
9897		  }
9898		else if (length > 4
9899			 && ! mips_disable_float_construction
9900			 /* Constants can only be constructed in GPRs and
9901			    copied to FPRs if the GPRs are at least as wide
9902			    as the FPRs.  Force the constant into memory if
9903			    we are using 64-bit FPRs but the GPRs are only
9904			    32 bits wide.  */
9905			 && (using_gprs
9906			     || ! (HAVE_64BIT_FPRS && HAVE_32BIT_GPRS))
9907			 && ((temp[0] == 0 && temp[1] == 0)
9908			     || (temp[2] == 0 && temp[3] == 0))
9909			 && ((temp[4] == 0 && temp[5] == 0)
9910			     || (temp[6] == 0 && temp[7] == 0)))
9911		  {
9912		    /* The value is simple enough to load with a couple of
9913                       instructions.  If using 32-bit registers, set
9914                       imm_expr to the high order 32 bits and offset_expr to
9915                       the low order 32 bits.  Otherwise, set imm_expr to
9916                       the entire 64 bit constant.  */
9917		    if (using_gprs ? HAVE_32BIT_GPRS : HAVE_32BIT_FPRS)
9918		      {
9919			imm_expr.X_op = O_constant;
9920			offset_expr.X_op = O_constant;
9921			if (! target_big_endian)
9922			  {
9923			    imm_expr.X_add_number = bfd_getl32 (temp + 4);
9924			    offset_expr.X_add_number = bfd_getl32 (temp);
9925			  }
9926			else
9927			  {
9928			    imm_expr.X_add_number = bfd_getb32 (temp);
9929			    offset_expr.X_add_number = bfd_getb32 (temp + 4);
9930			  }
9931			if (offset_expr.X_add_number == 0)
9932			  offset_expr.X_op = O_absent;
9933		      }
9934		    else if (sizeof (imm_expr.X_add_number) > 4)
9935		      {
9936			imm_expr.X_op = O_constant;
9937			if (! target_big_endian)
9938			  imm_expr.X_add_number = bfd_getl64 (temp);
9939			else
9940			  imm_expr.X_add_number = bfd_getb64 (temp);
9941		      }
9942		    else
9943		      {
9944			imm_expr.X_op = O_big;
9945			imm_expr.X_add_number = 4;
9946			if (! target_big_endian)
9947			  {
9948			    generic_bignum[0] = bfd_getl16 (temp);
9949			    generic_bignum[1] = bfd_getl16 (temp + 2);
9950			    generic_bignum[2] = bfd_getl16 (temp + 4);
9951			    generic_bignum[3] = bfd_getl16 (temp + 6);
9952			  }
9953			else
9954			  {
9955			    generic_bignum[0] = bfd_getb16 (temp + 6);
9956			    generic_bignum[1] = bfd_getb16 (temp + 4);
9957			    generic_bignum[2] = bfd_getb16 (temp + 2);
9958			    generic_bignum[3] = bfd_getb16 (temp);
9959			  }
9960		      }
9961		  }
9962		else
9963		  {
9964		    const char *newname;
9965		    segT new_seg;
9966
9967		    /* Switch to the right section.  */
9968		    seg = now_seg;
9969		    subseg = now_subseg;
9970		    switch (*args)
9971		      {
9972		      default: /* unused default case avoids warnings.  */
9973		      case 'L':
9974			newname = RDATA_SECTION_NAME;
9975			if (g_switch_value >= 8)
9976			  newname = ".lit8";
9977			break;
9978		      case 'F':
9979			newname = RDATA_SECTION_NAME;
9980			break;
9981		      case 'l':
9982			gas_assert (g_switch_value >= 4);
9983			newname = ".lit4";
9984			break;
9985		      }
9986		    new_seg = subseg_new (newname, (subsegT) 0);
9987		    if (IS_ELF)
9988		      bfd_set_section_flags (stdoutput, new_seg,
9989					     (SEC_ALLOC
9990					      | SEC_LOAD
9991					      | SEC_READONLY
9992					      | SEC_DATA));
9993		    frag_align (*args == 'l' ? 2 : 3, 0, 0);
9994		    if (IS_ELF && strncmp (TARGET_OS, "elf", 3) != 0)
9995		      record_alignment (new_seg, 4);
9996		    else
9997		      record_alignment (new_seg, *args == 'l' ? 2 : 3);
9998		    if (seg == now_seg)
9999		      as_bad (_("Can't use floating point insn in this section"));
10000
10001		    /* Set the argument to the current address in the
10002		       section.  */
10003		    offset_expr.X_op = O_symbol;
10004		    offset_expr.X_add_symbol = symbol_temp_new_now ();
10005		    offset_expr.X_add_number = 0;
10006
10007		    /* Put the floating point number into the section.  */
10008		    p = frag_more ((int) length);
10009		    memcpy (p, temp, length);
10010
10011		    /* Switch back to the original section.  */
10012		    subseg_set (seg, subseg);
10013		  }
10014	      }
10015	      continue;
10016
10017	    case 'i':		/* 16 bit unsigned immediate */
10018	    case 'j':		/* 16 bit signed immediate */
10019	      *imm_reloc = BFD_RELOC_LO16;
10020	      if (my_getSmallExpression (&imm_expr, imm_reloc, s) == 0)
10021		{
10022		  int more;
10023		  offsetT minval, maxval;
10024
10025		  more = (insn + 1 < &mips_opcodes[NUMOPCODES]
10026			  && strcmp (insn->name, insn[1].name) == 0);
10027
10028		  /* If the expression was written as an unsigned number,
10029		     only treat it as signed if there are no more
10030		     alternatives.  */
10031		  if (more
10032		      && *args == 'j'
10033		      && sizeof (imm_expr.X_add_number) <= 4
10034		      && imm_expr.X_op == O_constant
10035		      && imm_expr.X_add_number < 0
10036		      && imm_expr.X_unsigned
10037		      && HAVE_64BIT_GPRS)
10038		    break;
10039
10040		  /* For compatibility with older assemblers, we accept
10041		     0x8000-0xffff as signed 16-bit numbers when only
10042		     signed numbers are allowed.  */
10043		  if (*args == 'i')
10044		    minval = 0, maxval = 0xffff;
10045		  else if (more)
10046		    minval = -0x8000, maxval = 0x7fff;
10047		  else
10048		    minval = -0x8000, maxval = 0xffff;
10049
10050		  if (imm_expr.X_op != O_constant
10051		      || imm_expr.X_add_number < minval
10052		      || imm_expr.X_add_number > maxval)
10053		    {
10054		      if (more)
10055			break;
10056		      if (imm_expr.X_op == O_constant
10057			  || imm_expr.X_op == O_big)
10058			as_bad (_("expression out of range"));
10059		    }
10060		}
10061	      s = expr_end;
10062	      continue;
10063
10064	    case 'o':		/* 16 bit offset */
10065	      offset_reloc[0] = BFD_RELOC_LO16;
10066	      offset_reloc[1] = BFD_RELOC_UNUSED;
10067	      offset_reloc[2] = BFD_RELOC_UNUSED;
10068
10069	      /* Check whether there is only a single bracketed expression
10070		 left.  If so, it must be the base register and the
10071		 constant must be zero.  */
10072	      if (*s == '(' && strchr (s + 1, '(') == 0)
10073		{
10074		  offset_expr.X_op = O_constant;
10075		  offset_expr.X_add_number = 0;
10076		  continue;
10077		}
10078
10079	      /* If this value won't fit into a 16 bit offset, then go
10080		 find a macro that will generate the 32 bit offset
10081		 code pattern.  */
10082	      if (my_getSmallExpression (&offset_expr, offset_reloc, s) == 0
10083		  && (offset_expr.X_op != O_constant
10084		      || offset_expr.X_add_number >= 0x8000
10085		      || offset_expr.X_add_number < -0x8000))
10086		break;
10087
10088	      s = expr_end;
10089	      continue;
10090
10091	    case 'p':		/* pc relative offset */
10092	      *offset_reloc = BFD_RELOC_16_PCREL_S2;
10093	      my_getExpression (&offset_expr, s);
10094	      s = expr_end;
10095	      continue;
10096
10097	    case 'u':		/* upper 16 bits */
10098	      if (my_getSmallExpression (&imm_expr, imm_reloc, s) == 0
10099		  && imm_expr.X_op == O_constant
10100		  && (imm_expr.X_add_number < 0
10101		      || imm_expr.X_add_number >= 0x10000))
10102		as_bad (_("lui expression not in range 0..65535"));
10103	      s = expr_end;
10104	      continue;
10105
10106	    case 'a':		/* 26 bit address */
10107	      my_getExpression (&offset_expr, s);
10108	      s = expr_end;
10109	      *offset_reloc = BFD_RELOC_MIPS_JMP;
10110	      continue;
10111
10112	    case 'N':		/* 3 bit branch condition code */
10113	    case 'M':		/* 3 bit compare condition code */
10114	      rtype = RTYPE_CCC;
10115	      if (ip->insn_mo->pinfo & (FP_D| FP_S))
10116		rtype |= RTYPE_FCC;
10117	      if (!reg_lookup (&s, rtype, &regno))
10118		break;
10119	      if ((strcmp(str + strlen(str) - 3, ".ps") == 0
10120		   || strcmp(str + strlen(str) - 5, "any2f") == 0
10121		   || strcmp(str + strlen(str) - 5, "any2t") == 0)
10122		  && (regno & 1) != 0)
10123		as_warn (_("Condition code register should be even for %s, was %d"),
10124			 str, regno);
10125	      if ((strcmp(str + strlen(str) - 5, "any4f") == 0
10126		   || strcmp(str + strlen(str) - 5, "any4t") == 0)
10127		  && (regno & 3) != 0)
10128		as_warn (_("Condition code register should be 0 or 4 for %s, was %d"),
10129			 str, regno);
10130	      if (*args == 'N')
10131		INSERT_OPERAND (BCC, *ip, regno);
10132	      else
10133		INSERT_OPERAND (CCC, *ip, regno);
10134	      continue;
10135
10136	    case 'H':
10137	      if (s[0] == '0' && (s[1] == 'x' || s[1] == 'X'))
10138		s += 2;
10139	      if (ISDIGIT (*s))
10140		{
10141		  c = 0;
10142		  do
10143		    {
10144		      c *= 10;
10145		      c += *s - '0';
10146		      ++s;
10147		    }
10148		  while (ISDIGIT (*s));
10149		}
10150	      else
10151		c = 8; /* Invalid sel value.  */
10152
10153	      if (c > 7)
10154		as_bad (_("invalid coprocessor sub-selection value (0-7)"));
10155	      ip->insn_opcode |= c;
10156	      continue;
10157
10158	    case 'e':
10159	      /* Must be at least one digit.  */
10160	      my_getExpression (&imm_expr, s);
10161	      check_absolute_expr (ip, &imm_expr);
10162
10163	      if ((unsigned long) imm_expr.X_add_number
10164		  > (unsigned long) OP_MASK_VECBYTE)
10165		{
10166		  as_bad (_("bad byte vector index (%ld)"),
10167			   (long) imm_expr.X_add_number);
10168		  imm_expr.X_add_number = 0;
10169		}
10170
10171	      INSERT_OPERAND (VECBYTE, *ip, imm_expr.X_add_number);
10172	      imm_expr.X_op = O_absent;
10173	      s = expr_end;
10174	      continue;
10175
10176	    case '%':
10177	      my_getExpression (&imm_expr, s);
10178	      check_absolute_expr (ip, &imm_expr);
10179
10180	      if ((unsigned long) imm_expr.X_add_number
10181		  > (unsigned long) OP_MASK_VECALIGN)
10182		{
10183		  as_bad (_("bad byte vector index (%ld)"),
10184			   (long) imm_expr.X_add_number);
10185		  imm_expr.X_add_number = 0;
10186		}
10187
10188	      INSERT_OPERAND (VECALIGN, *ip, imm_expr.X_add_number);
10189	      imm_expr.X_op = O_absent;
10190	      s = expr_end;
10191	      continue;
10192
10193	    default:
10194	      as_bad (_("bad char = '%c'\n"), *args);
10195	      internalError ();
10196	    }
10197	  break;
10198	}
10199      /* Args don't match.  */
10200      if (insn + 1 < &mips_opcodes[NUMOPCODES] &&
10201	  !strcmp (insn->name, insn[1].name))
10202	{
10203	  ++insn;
10204	  s = argsStart;
10205	  insn_error = _("illegal operands");
10206	  continue;
10207	}
10208      if (save_c)
10209	*(--argsStart) = save_c;
10210      insn_error = _("illegal operands");
10211      return;
10212    }
10213}
10214
10215#define SKIP_SPACE_TABS(S) { while (*(S) == ' ' || *(S) == '\t') ++(S); }
10216
10217/* This routine assembles an instruction into its binary format when
10218   assembling for the mips16.  As a side effect, it sets one of the
10219   global variables imm_reloc or offset_reloc to the type of
10220   relocation to do if one of the operands is an address expression.
10221   It also sets mips16_small and mips16_ext if the user explicitly
10222   requested a small or extended instruction.  */
10223
10224static void
10225mips16_ip (char *str, struct mips_cl_insn *ip)
10226{
10227  char *s;
10228  const char *args;
10229  struct mips_opcode *insn;
10230  char *argsstart;
10231  unsigned int regno;
10232  unsigned int lastregno = 0;
10233  char *s_reset;
10234  size_t i;
10235
10236  insn_error = NULL;
10237
10238  mips16_small = FALSE;
10239  mips16_ext = FALSE;
10240
10241  for (s = str; ISLOWER (*s); ++s)
10242    ;
10243  switch (*s)
10244    {
10245    case '\0':
10246      break;
10247
10248    case ' ':
10249      *s++ = '\0';
10250      break;
10251
10252    case '.':
10253      if (s[1] == 't' && s[2] == ' ')
10254	{
10255	  *s = '\0';
10256	  mips16_small = TRUE;
10257	  s += 3;
10258	  break;
10259	}
10260      else if (s[1] == 'e' && s[2] == ' ')
10261	{
10262	  *s = '\0';
10263	  mips16_ext = TRUE;
10264	  s += 3;
10265	  break;
10266	}
10267      /* Fall through.  */
10268    default:
10269      insn_error = _("unknown opcode");
10270      return;
10271    }
10272
10273  if (mips_opts.noautoextend && ! mips16_ext)
10274    mips16_small = TRUE;
10275
10276  if ((insn = (struct mips_opcode *) hash_find (mips16_op_hash, str)) == NULL)
10277    {
10278      insn_error = _("unrecognized opcode");
10279      return;
10280    }
10281
10282  argsstart = s;
10283  for (;;)
10284    {
10285      bfd_boolean ok;
10286
10287      gas_assert (strcmp (insn->name, str) == 0);
10288
10289      ok = is_opcode_valid_16 (insn);
10290      if (! ok)
10291	{
10292	  if (insn + 1 < &mips16_opcodes[bfd_mips16_num_opcodes]
10293	      && strcmp (insn->name, insn[1].name) == 0)
10294	    {
10295	      ++insn;
10296	      continue;
10297	    }
10298	  else
10299	    {
10300	      if (!insn_error)
10301		{
10302		  static char buf[100];
10303		  sprintf (buf,
10304			   _("opcode not supported on this processor: %s (%s)"),
10305			   mips_cpu_info_from_arch (mips_opts.arch)->name,
10306			   mips_cpu_info_from_isa (mips_opts.isa)->name);
10307		  insn_error = buf;
10308		}
10309	      return;
10310	    }
10311	}
10312
10313      create_insn (ip, insn);
10314      imm_expr.X_op = O_absent;
10315      imm_reloc[0] = BFD_RELOC_UNUSED;
10316      imm_reloc[1] = BFD_RELOC_UNUSED;
10317      imm_reloc[2] = BFD_RELOC_UNUSED;
10318      imm2_expr.X_op = O_absent;
10319      offset_expr.X_op = O_absent;
10320      offset_reloc[0] = BFD_RELOC_UNUSED;
10321      offset_reloc[1] = BFD_RELOC_UNUSED;
10322      offset_reloc[2] = BFD_RELOC_UNUSED;
10323      for (args = insn->args; 1; ++args)
10324	{
10325	  int c;
10326
10327	  if (*s == ' ')
10328	    ++s;
10329
10330	  /* In this switch statement we call break if we did not find
10331             a match, continue if we did find a match, or return if we
10332             are done.  */
10333
10334	  c = *args;
10335	  switch (c)
10336	    {
10337	    case '\0':
10338	      if (*s == '\0')
10339		{
10340		  /* Stuff the immediate value in now, if we can.  */
10341		  if (imm_expr.X_op == O_constant
10342		      && *imm_reloc > BFD_RELOC_UNUSED
10343		      && *imm_reloc != BFD_RELOC_MIPS16_GOT16
10344		      && *imm_reloc != BFD_RELOC_MIPS16_CALL16
10345		      && insn->pinfo != INSN_MACRO)
10346		    {
10347		      valueT tmp;
10348
10349		      switch (*offset_reloc)
10350			{
10351			  case BFD_RELOC_MIPS16_HI16_S:
10352			    tmp = (imm_expr.X_add_number + 0x8000) >> 16;
10353			    break;
10354
10355			  case BFD_RELOC_MIPS16_HI16:
10356			    tmp = imm_expr.X_add_number >> 16;
10357			    break;
10358
10359			  case BFD_RELOC_MIPS16_LO16:
10360			    tmp = ((imm_expr.X_add_number + 0x8000) & 0xffff)
10361				  - 0x8000;
10362			    break;
10363
10364			  case BFD_RELOC_UNUSED:
10365			    tmp = imm_expr.X_add_number;
10366			    break;
10367
10368			  default:
10369			    internalError ();
10370			}
10371		      *offset_reloc = BFD_RELOC_UNUSED;
10372
10373		      mips16_immed (NULL, 0, *imm_reloc - BFD_RELOC_UNUSED,
10374				    tmp, TRUE, mips16_small,
10375				    mips16_ext, &ip->insn_opcode,
10376				    &ip->use_extend, &ip->extend);
10377		      imm_expr.X_op = O_absent;
10378		      *imm_reloc = BFD_RELOC_UNUSED;
10379		    }
10380
10381		  return;
10382		}
10383	      break;
10384
10385	    case ',':
10386	      if (*s++ == c)
10387		continue;
10388	      s--;
10389	      switch (*++args)
10390		{
10391		case 'v':
10392		  MIPS16_INSERT_OPERAND (RX, *ip, lastregno);
10393		  continue;
10394		case 'w':
10395		  MIPS16_INSERT_OPERAND (RY, *ip, lastregno);
10396		  continue;
10397		}
10398	      break;
10399
10400	    case '(':
10401	    case ')':
10402	      if (*s++ == c)
10403		continue;
10404	      break;
10405
10406	    case 'v':
10407	    case 'w':
10408	      if (s[0] != '$')
10409		{
10410		  if (c == 'v')
10411		    MIPS16_INSERT_OPERAND (RX, *ip, lastregno);
10412		  else
10413		    MIPS16_INSERT_OPERAND (RY, *ip, lastregno);
10414		  ++args;
10415		  continue;
10416		}
10417	      /* Fall through.  */
10418	    case 'x':
10419	    case 'y':
10420	    case 'z':
10421	    case 'Z':
10422	    case '0':
10423	    case 'S':
10424	    case 'R':
10425	    case 'X':
10426	    case 'Y':
10427  	      s_reset = s;
10428	      if (!reg_lookup (&s, RTYPE_NUM | RTYPE_GP, &regno))
10429		{
10430		  if (c == 'v' || c == 'w')
10431		    {
10432		      if (c == 'v')
10433			MIPS16_INSERT_OPERAND (RX, *ip, lastregno);
10434		      else
10435			MIPS16_INSERT_OPERAND (RY, *ip, lastregno);
10436		      ++args;
10437		      continue;
10438		    }
10439		  break;
10440		}
10441
10442	      if (*s == ' ')
10443		++s;
10444	      if (args[1] != *s)
10445		{
10446		  if (c == 'v' || c == 'w')
10447		    {
10448		      regno = mips16_to_32_reg_map[lastregno];
10449		      s = s_reset;
10450		      ++args;
10451		    }
10452		}
10453
10454	      switch (c)
10455		{
10456		case 'x':
10457		case 'y':
10458		case 'z':
10459		case 'v':
10460		case 'w':
10461		case 'Z':
10462		  regno = mips32_to_16_reg_map[regno];
10463		  break;
10464
10465		case '0':
10466		  if (regno != 0)
10467		    regno = ILLEGAL_REG;
10468		  break;
10469
10470		case 'S':
10471		  if (regno != SP)
10472		    regno = ILLEGAL_REG;
10473		  break;
10474
10475		case 'R':
10476		  if (regno != RA)
10477		    regno = ILLEGAL_REG;
10478		  break;
10479
10480		case 'X':
10481		case 'Y':
10482		  if (regno == AT && mips_opts.at)
10483		    {
10484		      if (mips_opts.at == ATREG)
10485			as_warn (_("used $at without \".set noat\""));
10486		      else
10487			as_warn (_("used $%u with \".set at=$%u\""),
10488				 regno, mips_opts.at);
10489		    }
10490		  break;
10491
10492		default:
10493		  internalError ();
10494		}
10495
10496	      if (regno == ILLEGAL_REG)
10497		break;
10498
10499	      switch (c)
10500		{
10501		case 'x':
10502		case 'v':
10503		  MIPS16_INSERT_OPERAND (RX, *ip, regno);
10504		  break;
10505		case 'y':
10506		case 'w':
10507		  MIPS16_INSERT_OPERAND (RY, *ip, regno);
10508		  break;
10509		case 'z':
10510		  MIPS16_INSERT_OPERAND (RZ, *ip, regno);
10511		  break;
10512		case 'Z':
10513		  MIPS16_INSERT_OPERAND (MOVE32Z, *ip, regno);
10514		case '0':
10515		case 'S':
10516		case 'R':
10517		  break;
10518		case 'X':
10519		  MIPS16_INSERT_OPERAND (REGR32, *ip, regno);
10520		  break;
10521		case 'Y':
10522		  regno = ((regno & 7) << 2) | ((regno & 0x18) >> 3);
10523		  MIPS16_INSERT_OPERAND (REG32R, *ip, regno);
10524		  break;
10525		default:
10526		  internalError ();
10527		}
10528
10529	      lastregno = regno;
10530	      continue;
10531
10532	    case 'P':
10533	      if (strncmp (s, "$pc", 3) == 0)
10534		{
10535		  s += 3;
10536		  continue;
10537		}
10538	      break;
10539
10540	    case '5':
10541	    case 'H':
10542	    case 'W':
10543	    case 'D':
10544	    case 'j':
10545	    case 'V':
10546	    case 'C':
10547	    case 'U':
10548	    case 'k':
10549	    case 'K':
10550	      i = my_getSmallExpression (&imm_expr, imm_reloc, s);
10551	      if (i > 0)
10552		{
10553		  if (imm_expr.X_op != O_constant)
10554		    {
10555		      mips16_ext = TRUE;
10556		      ip->use_extend = TRUE;
10557		      ip->extend = 0;
10558		    }
10559		  else
10560		    {
10561		      /* We need to relax this instruction.  */
10562		      *offset_reloc = *imm_reloc;
10563		      *imm_reloc = (int) BFD_RELOC_UNUSED + c;
10564		    }
10565		  s = expr_end;
10566		  continue;
10567		}
10568	      *imm_reloc = BFD_RELOC_UNUSED;
10569	      /* Fall through.  */
10570	    case '<':
10571	    case '>':
10572	    case '[':
10573	    case ']':
10574	    case '4':
10575	    case '8':
10576	      my_getExpression (&imm_expr, s);
10577	      if (imm_expr.X_op == O_register)
10578		{
10579		  /* What we thought was an expression turned out to
10580                     be a register.  */
10581
10582		  if (s[0] == '(' && args[1] == '(')
10583		    {
10584		      /* It looks like the expression was omitted
10585			 before a register indirection, which means
10586			 that the expression is implicitly zero.  We
10587			 still set up imm_expr, so that we handle
10588			 explicit extensions correctly.  */
10589		      imm_expr.X_op = O_constant;
10590		      imm_expr.X_add_number = 0;
10591		      *imm_reloc = (int) BFD_RELOC_UNUSED + c;
10592		      continue;
10593		    }
10594
10595		  break;
10596		}
10597
10598	      /* We need to relax this instruction.  */
10599	      *imm_reloc = (int) BFD_RELOC_UNUSED + c;
10600	      s = expr_end;
10601	      continue;
10602
10603	    case 'p':
10604	    case 'q':
10605	    case 'A':
10606	    case 'B':
10607	    case 'E':
10608	      /* We use offset_reloc rather than imm_reloc for the PC
10609                 relative operands.  This lets macros with both
10610                 immediate and address operands work correctly.  */
10611	      my_getExpression (&offset_expr, s);
10612
10613	      if (offset_expr.X_op == O_register)
10614		break;
10615
10616	      /* We need to relax this instruction.  */
10617	      *offset_reloc = (int) BFD_RELOC_UNUSED + c;
10618	      s = expr_end;
10619	      continue;
10620
10621	    case '6':		/* break code */
10622	      my_getExpression (&imm_expr, s);
10623	      check_absolute_expr (ip, &imm_expr);
10624	      if ((unsigned long) imm_expr.X_add_number > 63)
10625		as_warn (_("Invalid value for `%s' (%lu)"),
10626			 ip->insn_mo->name,
10627			 (unsigned long) imm_expr.X_add_number);
10628	      MIPS16_INSERT_OPERAND (IMM6, *ip, imm_expr.X_add_number);
10629	      imm_expr.X_op = O_absent;
10630	      s = expr_end;
10631	      continue;
10632
10633	    case 'a':		/* 26 bit address */
10634	      my_getExpression (&offset_expr, s);
10635	      s = expr_end;
10636	      *offset_reloc = BFD_RELOC_MIPS16_JMP;
10637	      ip->insn_opcode <<= 16;
10638	      continue;
10639
10640	    case 'l':		/* register list for entry macro */
10641	    case 'L':		/* register list for exit macro */
10642	      {
10643		int mask;
10644
10645		if (c == 'l')
10646		  mask = 0;
10647		else
10648		  mask = 7 << 3;
10649		while (*s != '\0')
10650		  {
10651		    unsigned int freg, reg1, reg2;
10652
10653		    while (*s == ' ' || *s == ',')
10654		      ++s;
10655		    if (reg_lookup (&s, RTYPE_GP | RTYPE_NUM, &reg1))
10656		      freg = 0;
10657		    else if (reg_lookup (&s, RTYPE_FPU, &reg1))
10658		      freg = 1;
10659		    else
10660		      {
10661			as_bad (_("can't parse register list"));
10662			break;
10663		      }
10664		    if (*s == ' ')
10665		      ++s;
10666		    if (*s != '-')
10667		      reg2 = reg1;
10668		    else
10669		      {
10670			++s;
10671			if (!reg_lookup (&s, freg ? RTYPE_FPU
10672					 : (RTYPE_GP | RTYPE_NUM), &reg2))
10673			  {
10674			    as_bad (_("invalid register list"));
10675			    break;
10676			  }
10677		      }
10678		    if (freg && reg1 == 0 && reg2 == 0 && c == 'L')
10679		      {
10680			mask &= ~ (7 << 3);
10681			mask |= 5 << 3;
10682		      }
10683		    else if (freg && reg1 == 0 && reg2 == 1 && c == 'L')
10684		      {
10685			mask &= ~ (7 << 3);
10686			mask |= 6 << 3;
10687		      }
10688		    else if (reg1 == 4 && reg2 >= 4 && reg2 <= 7 && c != 'L')
10689		      mask |= (reg2 - 3) << 3;
10690		    else if (reg1 == 16 && reg2 >= 16 && reg2 <= 17)
10691		      mask |= (reg2 - 15) << 1;
10692		    else if (reg1 == RA && reg2 == RA)
10693		      mask |= 1;
10694		    else
10695		      {
10696			as_bad (_("invalid register list"));
10697			break;
10698		      }
10699		  }
10700		/* The mask is filled in in the opcode table for the
10701                   benefit of the disassembler.  We remove it before
10702                   applying the actual mask.  */
10703		ip->insn_opcode &= ~ ((7 << 3) << MIPS16OP_SH_IMM6);
10704		ip->insn_opcode |= mask << MIPS16OP_SH_IMM6;
10705	      }
10706	    continue;
10707
10708	    case 'm':		/* Register list for save insn.  */
10709	    case 'M':		/* Register list for restore insn.  */
10710	      {
10711		int opcode = 0;
10712		int framesz = 0, seen_framesz = 0;
10713		int nargs = 0, statics = 0, sregs = 0;
10714
10715		while (*s != '\0')
10716		  {
10717		    unsigned int reg1, reg2;
10718
10719		    SKIP_SPACE_TABS (s);
10720		    while (*s == ',')
10721		      ++s;
10722		    SKIP_SPACE_TABS (s);
10723
10724		    my_getExpression (&imm_expr, s);
10725		    if (imm_expr.X_op == O_constant)
10726		      {
10727			/* Handle the frame size.  */
10728			if (seen_framesz)
10729			  {
10730			    as_bad (_("more than one frame size in list"));
10731			    break;
10732			  }
10733			seen_framesz = 1;
10734			framesz = imm_expr.X_add_number;
10735			imm_expr.X_op = O_absent;
10736			s = expr_end;
10737			continue;
10738		      }
10739
10740		    if (! reg_lookup (&s, RTYPE_GP | RTYPE_NUM, &reg1))
10741		      {
10742			as_bad (_("can't parse register list"));
10743			break;
10744		      }
10745
10746		    while (*s == ' ')
10747		      ++s;
10748
10749		    if (*s != '-')
10750		      reg2 = reg1;
10751		    else
10752		      {
10753			++s;
10754			if (! reg_lookup (&s, RTYPE_GP | RTYPE_NUM, &reg2)
10755			    || reg2 < reg1)
10756			  {
10757			    as_bad (_("can't parse register list"));
10758			    break;
10759			  }
10760		      }
10761
10762		    while (reg1 <= reg2)
10763		      {
10764			if (reg1 >= 4 && reg1 <= 7)
10765			  {
10766			    if (!seen_framesz)
10767				/* args $a0-$a3 */
10768				nargs |= 1 << (reg1 - 4);
10769			    else
10770				/* statics $a0-$a3 */
10771				statics |= 1 << (reg1 - 4);
10772			  }
10773			else if ((reg1 >= 16 && reg1 <= 23) || reg1 == 30)
10774			  {
10775			    /* $s0-$s8 */
10776			    sregs |= 1 << ((reg1 == 30) ? 8 : (reg1 - 16));
10777			  }
10778			else if (reg1 == 31)
10779			  {
10780			    /* Add $ra to insn.  */
10781			    opcode |= 0x40;
10782			  }
10783			else
10784			  {
10785			    as_bad (_("unexpected register in list"));
10786			    break;
10787			  }
10788			if (++reg1 == 24)
10789			  reg1 = 30;
10790		      }
10791		  }
10792
10793		/* Encode args/statics combination.  */
10794		if (nargs & statics)
10795		  as_bad (_("arg/static registers overlap"));
10796		else if (nargs == 0xf)
10797		  /* All $a0-$a3 are args.  */
10798		  opcode |= MIPS16_ALL_ARGS << 16;
10799		else if (statics == 0xf)
10800		  /* All $a0-$a3 are statics.  */
10801		  opcode |= MIPS16_ALL_STATICS << 16;
10802		else
10803		  {
10804		    int narg = 0, nstat = 0;
10805
10806		    /* Count arg registers.  */
10807		    while (nargs & 0x1)
10808		      {
10809			nargs >>= 1;
10810			narg++;
10811		      }
10812		    if (nargs != 0)
10813		      as_bad (_("invalid arg register list"));
10814
10815		    /* Count static registers.  */
10816		    while (statics & 0x8)
10817		      {
10818			statics = (statics << 1) & 0xf;
10819			nstat++;
10820		      }
10821		    if (statics != 0)
10822		      as_bad (_("invalid static register list"));
10823
10824		    /* Encode args/statics.  */
10825		    opcode |= ((narg << 2) | nstat) << 16;
10826		  }
10827
10828		/* Encode $s0/$s1.  */
10829		if (sregs & (1 << 0))		/* $s0 */
10830		  opcode |= 0x20;
10831		if (sregs & (1 << 1))		/* $s1 */
10832		  opcode |= 0x10;
10833		sregs >>= 2;
10834
10835		if (sregs != 0)
10836		  {
10837		    /* Count regs $s2-$s8.  */
10838		    int nsreg = 0;
10839		    while (sregs & 1)
10840		      {
10841			sregs >>= 1;
10842			nsreg++;
10843		      }
10844		    if (sregs != 0)
10845		      as_bad (_("invalid static register list"));
10846		    /* Encode $s2-$s8. */
10847		    opcode |= nsreg << 24;
10848		  }
10849
10850		/* Encode frame size.  */
10851		if (!seen_framesz)
10852		  as_bad (_("missing frame size"));
10853		else if ((framesz & 7) != 0 || framesz < 0
10854			 || framesz > 0xff * 8)
10855		  as_bad (_("invalid frame size"));
10856		else if (framesz != 128 || (opcode >> 16) != 0)
10857		  {
10858		    framesz /= 8;
10859		    opcode |= (((framesz & 0xf0) << 16)
10860			     | (framesz & 0x0f));
10861		  }
10862
10863		/* Finally build the instruction.  */
10864		if ((opcode >> 16) != 0 || framesz == 0)
10865		  {
10866		    ip->use_extend = TRUE;
10867		    ip->extend = opcode >> 16;
10868		  }
10869		ip->insn_opcode |= opcode & 0x7f;
10870	      }
10871	    continue;
10872
10873	    case 'e':		/* extend code */
10874	      my_getExpression (&imm_expr, s);
10875	      check_absolute_expr (ip, &imm_expr);
10876	      if ((unsigned long) imm_expr.X_add_number > 0x7ff)
10877		{
10878		  as_warn (_("Invalid value for `%s' (%lu)"),
10879			   ip->insn_mo->name,
10880			   (unsigned long) imm_expr.X_add_number);
10881		  imm_expr.X_add_number &= 0x7ff;
10882		}
10883	      ip->insn_opcode |= imm_expr.X_add_number;
10884	      imm_expr.X_op = O_absent;
10885	      s = expr_end;
10886	      continue;
10887
10888	    default:
10889	      internalError ();
10890	    }
10891	  break;
10892	}
10893
10894      /* Args don't match.  */
10895      if (insn + 1 < &mips16_opcodes[bfd_mips16_num_opcodes] &&
10896	  strcmp (insn->name, insn[1].name) == 0)
10897	{
10898	  ++insn;
10899	  s = argsstart;
10900	  continue;
10901	}
10902
10903      insn_error = _("illegal operands");
10904
10905      return;
10906    }
10907}
10908
10909/* This structure holds information we know about a mips16 immediate
10910   argument type.  */
10911
10912struct mips16_immed_operand
10913{
10914  /* The type code used in the argument string in the opcode table.  */
10915  int type;
10916  /* The number of bits in the short form of the opcode.  */
10917  int nbits;
10918  /* The number of bits in the extended form of the opcode.  */
10919  int extbits;
10920  /* The amount by which the short form is shifted when it is used;
10921     for example, the sw instruction has a shift count of 2.  */
10922  int shift;
10923  /* The amount by which the short form is shifted when it is stored
10924     into the instruction code.  */
10925  int op_shift;
10926  /* Non-zero if the short form is unsigned.  */
10927  int unsp;
10928  /* Non-zero if the extended form is unsigned.  */
10929  int extu;
10930  /* Non-zero if the value is PC relative.  */
10931  int pcrel;
10932};
10933
10934/* The mips16 immediate operand types.  */
10935
10936static const struct mips16_immed_operand mips16_immed_operands[] =
10937{
10938  { '<',  3,  5, 0, MIPS16OP_SH_RZ,   1, 1, 0 },
10939  { '>',  3,  5, 0, MIPS16OP_SH_RX,   1, 1, 0 },
10940  { '[',  3,  6, 0, MIPS16OP_SH_RZ,   1, 1, 0 },
10941  { ']',  3,  6, 0, MIPS16OP_SH_RX,   1, 1, 0 },
10942  { '4',  4, 15, 0, MIPS16OP_SH_IMM4, 0, 0, 0 },
10943  { '5',  5, 16, 0, MIPS16OP_SH_IMM5, 1, 0, 0 },
10944  { 'H',  5, 16, 1, MIPS16OP_SH_IMM5, 1, 0, 0 },
10945  { 'W',  5, 16, 2, MIPS16OP_SH_IMM5, 1, 0, 0 },
10946  { 'D',  5, 16, 3, MIPS16OP_SH_IMM5, 1, 0, 0 },
10947  { 'j',  5, 16, 0, MIPS16OP_SH_IMM5, 0, 0, 0 },
10948  { '8',  8, 16, 0, MIPS16OP_SH_IMM8, 1, 0, 0 },
10949  { 'V',  8, 16, 2, MIPS16OP_SH_IMM8, 1, 0, 0 },
10950  { 'C',  8, 16, 3, MIPS16OP_SH_IMM8, 1, 0, 0 },
10951  { 'U',  8, 16, 0, MIPS16OP_SH_IMM8, 1, 1, 0 },
10952  { 'k',  8, 16, 0, MIPS16OP_SH_IMM8, 0, 0, 0 },
10953  { 'K',  8, 16, 3, MIPS16OP_SH_IMM8, 0, 0, 0 },
10954  { 'p',  8, 16, 0, MIPS16OP_SH_IMM8, 0, 0, 1 },
10955  { 'q', 11, 16, 0, MIPS16OP_SH_IMM8, 0, 0, 1 },
10956  { 'A',  8, 16, 2, MIPS16OP_SH_IMM8, 1, 0, 1 },
10957  { 'B',  5, 16, 3, MIPS16OP_SH_IMM5, 1, 0, 1 },
10958  { 'E',  5, 16, 2, MIPS16OP_SH_IMM5, 1, 0, 1 }
10959};
10960
10961#define MIPS16_NUM_IMMED \
10962  (sizeof mips16_immed_operands / sizeof mips16_immed_operands[0])
10963
10964/* Handle a mips16 instruction with an immediate value.  This or's the
10965   small immediate value into *INSN.  It sets *USE_EXTEND to indicate
10966   whether an extended value is needed; if one is needed, it sets
10967   *EXTEND to the value.  The argument type is TYPE.  The value is VAL.
10968   If SMALL is true, an unextended opcode was explicitly requested.
10969   If EXT is true, an extended opcode was explicitly requested.  If
10970   WARN is true, warn if EXT does not match reality.  */
10971
10972static void
10973mips16_immed (char *file, unsigned int line, int type, offsetT val,
10974	      bfd_boolean warn, bfd_boolean small, bfd_boolean ext,
10975	      unsigned long *insn, bfd_boolean *use_extend,
10976	      unsigned short *extend)
10977{
10978  const struct mips16_immed_operand *op;
10979  int mintiny, maxtiny;
10980  bfd_boolean needext;
10981
10982  op = mips16_immed_operands;
10983  while (op->type != type)
10984    {
10985      ++op;
10986      gas_assert (op < mips16_immed_operands + MIPS16_NUM_IMMED);
10987    }
10988
10989  if (op->unsp)
10990    {
10991      if (type == '<' || type == '>' || type == '[' || type == ']')
10992	{
10993	  mintiny = 1;
10994	  maxtiny = 1 << op->nbits;
10995	}
10996      else
10997	{
10998	  mintiny = 0;
10999	  maxtiny = (1 << op->nbits) - 1;
11000	}
11001    }
11002  else
11003    {
11004      mintiny = - (1 << (op->nbits - 1));
11005      maxtiny = (1 << (op->nbits - 1)) - 1;
11006    }
11007
11008  /* Branch offsets have an implicit 0 in the lowest bit.  */
11009  if (type == 'p' || type == 'q')
11010    val /= 2;
11011
11012  if ((val & ((1 << op->shift) - 1)) != 0
11013      || val < (mintiny << op->shift)
11014      || val > (maxtiny << op->shift))
11015    needext = TRUE;
11016  else
11017    needext = FALSE;
11018
11019  if (warn && ext && ! needext)
11020    as_warn_where (file, line,
11021		   _("extended operand requested but not required"));
11022  if (small && needext)
11023    as_bad_where (file, line, _("invalid unextended operand value"));
11024
11025  if (small || (! ext && ! needext))
11026    {
11027      int insnval;
11028
11029      *use_extend = FALSE;
11030      insnval = ((val >> op->shift) & ((1 << op->nbits) - 1));
11031      insnval <<= op->op_shift;
11032      *insn |= insnval;
11033    }
11034  else
11035    {
11036      long minext, maxext;
11037      int extval;
11038
11039      if (op->extu)
11040	{
11041	  minext = 0;
11042	  maxext = (1 << op->extbits) - 1;
11043	}
11044      else
11045	{
11046	  minext = - (1 << (op->extbits - 1));
11047	  maxext = (1 << (op->extbits - 1)) - 1;
11048	}
11049      if (val < minext || val > maxext)
11050	as_bad_where (file, line,
11051		      _("operand value out of range for instruction"));
11052
11053      *use_extend = TRUE;
11054      if (op->extbits == 16)
11055	{
11056	  extval = ((val >> 11) & 0x1f) | (val & 0x7e0);
11057	  val &= 0x1f;
11058	}
11059      else if (op->extbits == 15)
11060	{
11061	  extval = ((val >> 11) & 0xf) | (val & 0x7f0);
11062	  val &= 0xf;
11063	}
11064      else
11065	{
11066	  extval = ((val & 0x1f) << 6) | (val & 0x20);
11067	  val = 0;
11068	}
11069
11070      *extend = (unsigned short) extval;
11071      *insn |= val;
11072    }
11073}
11074
11075struct percent_op_match
11076{
11077  const char *str;
11078  bfd_reloc_code_real_type reloc;
11079};
11080
11081static const struct percent_op_match mips_percent_op[] =
11082{
11083  {"%lo", BFD_RELOC_LO16},
11084#ifdef OBJ_ELF
11085  {"%call_hi", BFD_RELOC_MIPS_CALL_HI16},
11086  {"%call_lo", BFD_RELOC_MIPS_CALL_LO16},
11087  {"%call16", BFD_RELOC_MIPS_CALL16},
11088  {"%got_disp", BFD_RELOC_MIPS_GOT_DISP},
11089  {"%got_page", BFD_RELOC_MIPS_GOT_PAGE},
11090  {"%got_ofst", BFD_RELOC_MIPS_GOT_OFST},
11091  {"%got_hi", BFD_RELOC_MIPS_GOT_HI16},
11092  {"%got_lo", BFD_RELOC_MIPS_GOT_LO16},
11093  {"%got", BFD_RELOC_MIPS_GOT16},
11094  {"%gp_rel", BFD_RELOC_GPREL16},
11095  {"%half", BFD_RELOC_16},
11096  {"%highest", BFD_RELOC_MIPS_HIGHEST},
11097  {"%higher", BFD_RELOC_MIPS_HIGHER},
11098  {"%neg", BFD_RELOC_MIPS_SUB},
11099  {"%tlsgd", BFD_RELOC_MIPS_TLS_GD},
11100  {"%tlsldm", BFD_RELOC_MIPS_TLS_LDM},
11101  {"%dtprel_hi", BFD_RELOC_MIPS_TLS_DTPREL_HI16},
11102  {"%dtprel_lo", BFD_RELOC_MIPS_TLS_DTPREL_LO16},
11103  {"%tprel_hi", BFD_RELOC_MIPS_TLS_TPREL_HI16},
11104  {"%tprel_lo", BFD_RELOC_MIPS_TLS_TPREL_LO16},
11105  {"%gottprel", BFD_RELOC_MIPS_TLS_GOTTPREL},
11106#endif
11107  {"%hi", BFD_RELOC_HI16_S}
11108};
11109
11110static const struct percent_op_match mips16_percent_op[] =
11111{
11112  {"%lo", BFD_RELOC_MIPS16_LO16},
11113  {"%gprel", BFD_RELOC_MIPS16_GPREL},
11114  {"%got", BFD_RELOC_MIPS16_GOT16},
11115  {"%call16", BFD_RELOC_MIPS16_CALL16},
11116  {"%hi", BFD_RELOC_MIPS16_HI16_S}
11117};
11118
11119
11120/* Return true if *STR points to a relocation operator.  When returning true,
11121   move *STR over the operator and store its relocation code in *RELOC.
11122   Leave both *STR and *RELOC alone when returning false.  */
11123
11124static bfd_boolean
11125parse_relocation (char **str, bfd_reloc_code_real_type *reloc)
11126{
11127  const struct percent_op_match *percent_op;
11128  size_t limit, i;
11129
11130  if (mips_opts.mips16)
11131    {
11132      percent_op = mips16_percent_op;
11133      limit = ARRAY_SIZE (mips16_percent_op);
11134    }
11135  else
11136    {
11137      percent_op = mips_percent_op;
11138      limit = ARRAY_SIZE (mips_percent_op);
11139    }
11140
11141  for (i = 0; i < limit; i++)
11142    if (strncasecmp (*str, percent_op[i].str, strlen (percent_op[i].str)) == 0)
11143      {
11144	int len = strlen (percent_op[i].str);
11145
11146	if (!ISSPACE ((*str)[len]) && (*str)[len] != '(')
11147	  continue;
11148
11149	*str += strlen (percent_op[i].str);
11150	*reloc = percent_op[i].reloc;
11151
11152	/* Check whether the output BFD supports this relocation.
11153	   If not, issue an error and fall back on something safe.  */
11154	if (!bfd_reloc_type_lookup (stdoutput, percent_op[i].reloc))
11155	  {
11156	    as_bad (_("relocation %s isn't supported by the current ABI"),
11157		    percent_op[i].str);
11158	    *reloc = BFD_RELOC_UNUSED;
11159	  }
11160	return TRUE;
11161      }
11162  return FALSE;
11163}
11164
11165
11166/* Parse string STR as a 16-bit relocatable operand.  Store the
11167   expression in *EP and the relocations in the array starting
11168   at RELOC.  Return the number of relocation operators used.
11169
11170   On exit, EXPR_END points to the first character after the expression.  */
11171
11172static size_t
11173my_getSmallExpression (expressionS *ep, bfd_reloc_code_real_type *reloc,
11174		       char *str)
11175{
11176  bfd_reloc_code_real_type reversed_reloc[3];
11177  size_t reloc_index, i;
11178  int crux_depth, str_depth;
11179  char *crux;
11180
11181  /* Search for the start of the main expression, recoding relocations
11182     in REVERSED_RELOC.  End the loop with CRUX pointing to the start
11183     of the main expression and with CRUX_DEPTH containing the number
11184     of open brackets at that point.  */
11185  reloc_index = -1;
11186  str_depth = 0;
11187  do
11188    {
11189      reloc_index++;
11190      crux = str;
11191      crux_depth = str_depth;
11192
11193      /* Skip over whitespace and brackets, keeping count of the number
11194	 of brackets.  */
11195      while (*str == ' ' || *str == '\t' || *str == '(')
11196	if (*str++ == '(')
11197	  str_depth++;
11198    }
11199  while (*str == '%'
11200	 && reloc_index < (HAVE_NEWABI ? 3 : 1)
11201	 && parse_relocation (&str, &reversed_reloc[reloc_index]));
11202
11203  my_getExpression (ep, crux);
11204  str = expr_end;
11205
11206  /* Match every open bracket.  */
11207  while (crux_depth > 0 && (*str == ')' || *str == ' ' || *str == '\t'))
11208    if (*str++ == ')')
11209      crux_depth--;
11210
11211  if (crux_depth > 0)
11212    as_bad (_("unclosed '('"));
11213
11214  expr_end = str;
11215
11216  if (reloc_index != 0)
11217    {
11218      prev_reloc_op_frag = frag_now;
11219      for (i = 0; i < reloc_index; i++)
11220	reloc[i] = reversed_reloc[reloc_index - 1 - i];
11221    }
11222
11223  return reloc_index;
11224}
11225
11226static void
11227my_getExpression (expressionS *ep, char *str)
11228{
11229  char *save_in;
11230
11231  save_in = input_line_pointer;
11232  input_line_pointer = str;
11233  expression (ep);
11234  expr_end = input_line_pointer;
11235  input_line_pointer = save_in;
11236}
11237
11238char *
11239md_atof (int type, char *litP, int *sizeP)
11240{
11241  return ieee_md_atof (type, litP, sizeP, target_big_endian);
11242}
11243
11244void
11245md_number_to_chars (char *buf, valueT val, int n)
11246{
11247  if (target_big_endian)
11248    number_to_chars_bigendian (buf, val, n);
11249  else
11250    number_to_chars_littleendian (buf, val, n);
11251}
11252
11253#ifdef OBJ_ELF
11254static int support_64bit_objects(void)
11255{
11256  const char **list, **l;
11257  int yes;
11258
11259  list = bfd_target_list ();
11260  for (l = list; *l != NULL; l++)
11261#ifdef TE_TMIPS
11262    /* This is traditional mips */
11263    if (strcmp (*l, "elf64-tradbigmips") == 0
11264	|| strcmp (*l, "elf64-tradlittlemips") == 0)
11265#else
11266    if (strcmp (*l, "elf64-bigmips") == 0
11267	|| strcmp (*l, "elf64-littlemips") == 0)
11268#endif
11269      break;
11270  yes = (*l != NULL);
11271  free (list);
11272  return yes;
11273}
11274#endif /* OBJ_ELF */
11275
11276const char *md_shortopts = "O::g::G:";
11277
11278enum options
11279  {
11280    OPTION_MARCH = OPTION_MD_BASE,
11281    OPTION_MTUNE,
11282    OPTION_MIPS1,
11283    OPTION_MIPS2,
11284    OPTION_MIPS3,
11285    OPTION_MIPS4,
11286    OPTION_MIPS5,
11287    OPTION_MIPS32,
11288    OPTION_MIPS64,
11289    OPTION_MIPS32R2,
11290    OPTION_MIPS64R2,
11291    OPTION_MIPS16,
11292    OPTION_NO_MIPS16,
11293    OPTION_MIPS3D,
11294    OPTION_NO_MIPS3D,
11295    OPTION_MDMX,
11296    OPTION_NO_MDMX,
11297    OPTION_DSP,
11298    OPTION_NO_DSP,
11299    OPTION_MT,
11300    OPTION_NO_MT,
11301    OPTION_SMARTMIPS,
11302    OPTION_NO_SMARTMIPS,
11303    OPTION_DSPR2,
11304    OPTION_NO_DSPR2,
11305    OPTION_COMPAT_ARCH_BASE,
11306    OPTION_M4650,
11307    OPTION_NO_M4650,
11308    OPTION_M4010,
11309    OPTION_NO_M4010,
11310    OPTION_M4100,
11311    OPTION_NO_M4100,
11312    OPTION_M3900,
11313    OPTION_NO_M3900,
11314    OPTION_M7000_HILO_FIX,
11315    OPTION_MNO_7000_HILO_FIX,
11316    OPTION_FIX_24K,
11317    OPTION_NO_FIX_24K,
11318    OPTION_FIX_LOONGSON2F_JUMP,
11319    OPTION_NO_FIX_LOONGSON2F_JUMP,
11320    OPTION_FIX_LOONGSON2F_NOP,
11321    OPTION_NO_FIX_LOONGSON2F_NOP,
11322    OPTION_FIX_VR4120,
11323    OPTION_NO_FIX_VR4120,
11324    OPTION_FIX_VR4130,
11325    OPTION_NO_FIX_VR4130,
11326    OPTION_FIX_CN63XXP1,
11327    OPTION_NO_FIX_CN63XXP1,
11328    OPTION_TRAP,
11329    OPTION_BREAK,
11330    OPTION_EB,
11331    OPTION_EL,
11332    OPTION_FP32,
11333    OPTION_GP32,
11334    OPTION_CONSTRUCT_FLOATS,
11335    OPTION_NO_CONSTRUCT_FLOATS,
11336    OPTION_FP64,
11337    OPTION_GP64,
11338    OPTION_RELAX_BRANCH,
11339    OPTION_NO_RELAX_BRANCH,
11340    OPTION_MSHARED,
11341    OPTION_MNO_SHARED,
11342    OPTION_MSYM32,
11343    OPTION_MNO_SYM32,
11344    OPTION_SOFT_FLOAT,
11345    OPTION_HARD_FLOAT,
11346    OPTION_SINGLE_FLOAT,
11347    OPTION_DOUBLE_FLOAT,
11348    OPTION_32,
11349    OPTION_TRAP_ZERO_JUMP,
11350    OPTION_NO_TRAP_ZERO_JUMP,
11351#ifdef OBJ_ELF
11352    OPTION_CALL_SHARED,
11353    OPTION_CALL_NONPIC,
11354    OPTION_NON_SHARED,
11355    OPTION_XGOT,
11356    OPTION_MABI,
11357    OPTION_N32,
11358    OPTION_64,
11359    OPTION_MDEBUG,
11360    OPTION_NO_MDEBUG,
11361    OPTION_PDR,
11362    OPTION_NO_PDR,
11363    OPTION_MVXWORKS_PIC,
11364#endif /* OBJ_ELF */
11365    OPTION_FIX_LOONGSON2F_BTB,
11366    OPTION_NO_FIX_LOONGSON2F_BTB,
11367    OPTION_END_OF_ENUM
11368  };
11369
11370struct option md_longopts[] =
11371{
11372  /* Options which specify architecture.  */
11373  {"march", required_argument, NULL, OPTION_MARCH},
11374  {"mtune", required_argument, NULL, OPTION_MTUNE},
11375  {"mips0", no_argument, NULL, OPTION_MIPS1},
11376  {"mips1", no_argument, NULL, OPTION_MIPS1},
11377  {"mips2", no_argument, NULL, OPTION_MIPS2},
11378  {"mips3", no_argument, NULL, OPTION_MIPS3},
11379  {"mips4", no_argument, NULL, OPTION_MIPS4},
11380  {"mips5", no_argument, NULL, OPTION_MIPS5},
11381  {"mips32", no_argument, NULL, OPTION_MIPS32},
11382  {"mips64", no_argument, NULL, OPTION_MIPS64},
11383  {"mips32r2", no_argument, NULL, OPTION_MIPS32R2},
11384  {"mips64r2", no_argument, NULL, OPTION_MIPS64R2},
11385
11386  /* Options which specify Application Specific Extensions (ASEs).  */
11387  {"mips16", no_argument, NULL, OPTION_MIPS16},
11388  {"no-mips16", no_argument, NULL, OPTION_NO_MIPS16},
11389  {"mips3d", no_argument, NULL, OPTION_MIPS3D},
11390  {"no-mips3d", no_argument, NULL, OPTION_NO_MIPS3D},
11391  {"mdmx", no_argument, NULL, OPTION_MDMX},
11392  {"no-mdmx", no_argument, NULL, OPTION_NO_MDMX},
11393  {"mdsp", no_argument, NULL, OPTION_DSP},
11394  {"mno-dsp", no_argument, NULL, OPTION_NO_DSP},
11395  {"mmt", no_argument, NULL, OPTION_MT},
11396  {"mno-mt", no_argument, NULL, OPTION_NO_MT},
11397  {"msmartmips", no_argument, NULL, OPTION_SMARTMIPS},
11398  {"mno-smartmips", no_argument, NULL, OPTION_NO_SMARTMIPS},
11399  {"mdspr2", no_argument, NULL, OPTION_DSPR2},
11400  {"mno-dspr2", no_argument, NULL, OPTION_NO_DSPR2},
11401
11402  /* Old-style architecture options.  Don't add more of these.  */
11403  {"m4650", no_argument, NULL, OPTION_M4650},
11404  {"no-m4650", no_argument, NULL, OPTION_NO_M4650},
11405  {"m4010", no_argument, NULL, OPTION_M4010},
11406  {"no-m4010", no_argument, NULL, OPTION_NO_M4010},
11407  {"m4100", no_argument, NULL, OPTION_M4100},
11408  {"no-m4100", no_argument, NULL, OPTION_NO_M4100},
11409  {"m3900", no_argument, NULL, OPTION_M3900},
11410  {"no-m3900", no_argument, NULL, OPTION_NO_M3900},
11411
11412  /* Options which enable bug fixes.  */
11413  {"mfix7000", no_argument, NULL, OPTION_M7000_HILO_FIX},
11414  {"no-fix-7000", no_argument, NULL, OPTION_MNO_7000_HILO_FIX},
11415  {"mno-fix7000", no_argument, NULL, OPTION_MNO_7000_HILO_FIX},
11416  {"mfix-loongson2f-jump", no_argument, NULL, OPTION_FIX_LOONGSON2F_JUMP},
11417  {"mno-fix-loongson2f-jump", no_argument, NULL, OPTION_NO_FIX_LOONGSON2F_JUMP},
11418  {"mfix-loongson2f-nop", no_argument, NULL, OPTION_FIX_LOONGSON2F_NOP},
11419  {"mno-fix-loongson2f-nop", no_argument, NULL, OPTION_NO_FIX_LOONGSON2F_NOP},
11420  {"mfix-loongson2f-btb", no_argument, NULL, OPTION_FIX_LOONGSON2F_BTB},
11421  {"mno-fix-loongson2f-btb", no_argument, NULL, OPTION_NO_FIX_LOONGSON2F_BTB},
11422  {"mfix-vr4120",    no_argument, NULL, OPTION_FIX_VR4120},
11423  {"mno-fix-vr4120", no_argument, NULL, OPTION_NO_FIX_VR4120},
11424  {"mfix-vr4130",    no_argument, NULL, OPTION_FIX_VR4130},
11425  {"mno-fix-vr4130", no_argument, NULL, OPTION_NO_FIX_VR4130},
11426  {"mfix-24k",    no_argument, NULL, OPTION_FIX_24K},
11427  {"mno-fix-24k", no_argument, NULL, OPTION_NO_FIX_24K},
11428  {"mfix-cn63xxp1", no_argument, NULL, OPTION_FIX_CN63XXP1},
11429  {"mno-fix-cn63xxp1", no_argument, NULL, OPTION_NO_FIX_CN63XXP1},
11430
11431  /* Miscellaneous options.  */
11432  {"trap", no_argument, NULL, OPTION_TRAP},
11433  {"no-break", no_argument, NULL, OPTION_TRAP},
11434  {"break", no_argument, NULL, OPTION_BREAK},
11435  {"no-trap", no_argument, NULL, OPTION_BREAK},
11436  {"EB", no_argument, NULL, OPTION_EB},
11437  {"EL", no_argument, NULL, OPTION_EL},
11438  {"mfp32", no_argument, NULL, OPTION_FP32},
11439  {"mgp32", no_argument, NULL, OPTION_GP32},
11440  {"construct-floats", no_argument, NULL, OPTION_CONSTRUCT_FLOATS},
11441  {"no-construct-floats", no_argument, NULL, OPTION_NO_CONSTRUCT_FLOATS},
11442  {"mfp64", no_argument, NULL, OPTION_FP64},
11443  {"mgp64", no_argument, NULL, OPTION_GP64},
11444  {"relax-branch", no_argument, NULL, OPTION_RELAX_BRANCH},
11445  {"no-relax-branch", no_argument, NULL, OPTION_NO_RELAX_BRANCH},
11446  {"mshared", no_argument, NULL, OPTION_MSHARED},
11447  {"mno-shared", no_argument, NULL, OPTION_MNO_SHARED},
11448  {"msym32", no_argument, NULL, OPTION_MSYM32},
11449  {"mno-sym32", no_argument, NULL, OPTION_MNO_SYM32},
11450  {"msoft-float", no_argument, NULL, OPTION_SOFT_FLOAT},
11451  {"mhard-float", no_argument, NULL, OPTION_HARD_FLOAT},
11452  {"msingle-float", no_argument, NULL, OPTION_SINGLE_FLOAT},
11453  {"mdouble-float", no_argument, NULL, OPTION_DOUBLE_FLOAT},
11454
11455  /* Strictly speaking this next option is ELF specific,
11456     but we allow it for other ports as well in order to
11457     make testing easier.  */
11458  {"32",          no_argument, NULL, OPTION_32},
11459
11460  {"mtrap-zero-jump", no_argument, NULL, OPTION_TRAP_ZERO_JUMP},
11461  {"mno-trap-zero-jump", no_argument, NULL, OPTION_NO_TRAP_ZERO_JUMP},
11462
11463  /* ELF-specific options.  */
11464#ifdef OBJ_ELF
11465  {"KPIC",        no_argument, NULL, OPTION_CALL_SHARED},
11466  {"call_shared", no_argument, NULL, OPTION_CALL_SHARED},
11467  {"call_nonpic", no_argument, NULL, OPTION_CALL_NONPIC},
11468  {"non_shared",  no_argument, NULL, OPTION_NON_SHARED},
11469  {"xgot",        no_argument, NULL, OPTION_XGOT},
11470  {"mabi", required_argument, NULL, OPTION_MABI},
11471  {"n32",         no_argument, NULL, OPTION_N32},
11472  {"64",          no_argument, NULL, OPTION_64},
11473  {"mdebug", no_argument, NULL, OPTION_MDEBUG},
11474  {"no-mdebug", no_argument, NULL, OPTION_NO_MDEBUG},
11475  {"mpdr", no_argument, NULL, OPTION_PDR},
11476  {"mno-pdr", no_argument, NULL, OPTION_NO_PDR},
11477  {"mvxworks-pic", no_argument, NULL, OPTION_MVXWORKS_PIC},
11478#endif /* OBJ_ELF */
11479
11480  {NULL, no_argument, NULL, 0}
11481};
11482size_t md_longopts_size = sizeof (md_longopts);
11483
11484/* Set STRING_PTR (either &mips_arch_string or &mips_tune_string) to
11485   NEW_VALUE.  Warn if another value was already specified.  Note:
11486   we have to defer parsing the -march and -mtune arguments in order
11487   to handle 'from-abi' correctly, since the ABI might be specified
11488   in a later argument.  */
11489
11490static void
11491mips_set_option_string (const char **string_ptr, const char *new_value)
11492{
11493  if (*string_ptr != 0 && strcasecmp (*string_ptr, new_value) != 0)
11494    as_warn (_("A different %s was already specified, is now %s"),
11495	     string_ptr == &mips_arch_string ? "-march" : "-mtune",
11496	     new_value);
11497
11498  *string_ptr = new_value;
11499}
11500
11501int
11502md_parse_option (int c, char *arg)
11503{
11504  switch (c)
11505    {
11506    case OPTION_CONSTRUCT_FLOATS:
11507      mips_disable_float_construction = 0;
11508      break;
11509
11510    case OPTION_NO_CONSTRUCT_FLOATS:
11511      mips_disable_float_construction = 1;
11512      break;
11513
11514    case OPTION_TRAP:
11515      mips_trap = 1;
11516      break;
11517
11518    case OPTION_BREAK:
11519      mips_trap = 0;
11520      break;
11521
11522    case OPTION_EB:
11523      target_big_endian = 1;
11524      break;
11525
11526    case OPTION_EL:
11527      target_big_endian = 0;
11528      break;
11529
11530    case 'O':
11531      if (arg == NULL)
11532	mips_optimize = 1;
11533      else if (arg[0] == '0')
11534	mips_optimize = 0;
11535      else if (arg[0] == '1')
11536	mips_optimize = 1;
11537      else
11538	mips_optimize = 2;
11539      break;
11540
11541    case 'g':
11542      if (arg == NULL)
11543	mips_debug = 2;
11544      else
11545	mips_debug = atoi (arg);
11546      break;
11547
11548    case OPTION_MIPS1:
11549      file_mips_isa = ISA_MIPS1;
11550      break;
11551
11552    case OPTION_MIPS2:
11553      file_mips_isa = ISA_MIPS2;
11554      break;
11555
11556    case OPTION_MIPS3:
11557      file_mips_isa = ISA_MIPS3;
11558      break;
11559
11560    case OPTION_MIPS4:
11561      file_mips_isa = ISA_MIPS4;
11562      break;
11563
11564    case OPTION_MIPS5:
11565      file_mips_isa = ISA_MIPS5;
11566      break;
11567
11568    case OPTION_MIPS32:
11569      file_mips_isa = ISA_MIPS32;
11570      break;
11571
11572    case OPTION_MIPS32R2:
11573      file_mips_isa = ISA_MIPS32R2;
11574      break;
11575
11576    case OPTION_MIPS64R2:
11577      file_mips_isa = ISA_MIPS64R2;
11578      break;
11579
11580    case OPTION_MIPS64:
11581      file_mips_isa = ISA_MIPS64;
11582      break;
11583
11584    case OPTION_MTUNE:
11585      mips_set_option_string (&mips_tune_string, arg);
11586      break;
11587
11588    case OPTION_MARCH:
11589      mips_set_option_string (&mips_arch_string, arg);
11590      break;
11591
11592    case OPTION_M4650:
11593      mips_set_option_string (&mips_arch_string, "4650");
11594      mips_set_option_string (&mips_tune_string, "4650");
11595      break;
11596
11597    case OPTION_NO_M4650:
11598      break;
11599
11600    case OPTION_M4010:
11601      mips_set_option_string (&mips_arch_string, "4010");
11602      mips_set_option_string (&mips_tune_string, "4010");
11603      break;
11604
11605    case OPTION_NO_M4010:
11606      break;
11607
11608    case OPTION_M4100:
11609      mips_set_option_string (&mips_arch_string, "4100");
11610      mips_set_option_string (&mips_tune_string, "4100");
11611      break;
11612
11613    case OPTION_NO_M4100:
11614      break;
11615
11616    case OPTION_M3900:
11617      mips_set_option_string (&mips_arch_string, "3900");
11618      mips_set_option_string (&mips_tune_string, "3900");
11619      break;
11620
11621    case OPTION_NO_M3900:
11622      break;
11623
11624    case OPTION_MDMX:
11625      mips_opts.ase_mdmx = 1;
11626      break;
11627
11628    case OPTION_NO_MDMX:
11629      mips_opts.ase_mdmx = 0;
11630      break;
11631
11632    case OPTION_DSP:
11633      mips_opts.ase_dsp = 1;
11634      mips_opts.ase_dspr2 = 0;
11635      break;
11636
11637    case OPTION_NO_DSP:
11638      mips_opts.ase_dsp = 0;
11639      mips_opts.ase_dspr2 = 0;
11640      break;
11641
11642    case OPTION_DSPR2:
11643      mips_opts.ase_dspr2 = 1;
11644      mips_opts.ase_dsp = 1;
11645      break;
11646
11647    case OPTION_NO_DSPR2:
11648      mips_opts.ase_dspr2 = 0;
11649      mips_opts.ase_dsp = 0;
11650      break;
11651
11652    case OPTION_MT:
11653      mips_opts.ase_mt = 1;
11654      break;
11655
11656    case OPTION_NO_MT:
11657      mips_opts.ase_mt = 0;
11658      break;
11659
11660    case OPTION_MIPS16:
11661      mips_opts.mips16 = 1;
11662      mips_no_prev_insn ();
11663      break;
11664
11665    case OPTION_NO_MIPS16:
11666      mips_opts.mips16 = 0;
11667      mips_no_prev_insn ();
11668      break;
11669
11670    case OPTION_MIPS3D:
11671      mips_opts.ase_mips3d = 1;
11672      break;
11673
11674    case OPTION_NO_MIPS3D:
11675      mips_opts.ase_mips3d = 0;
11676      break;
11677
11678    case OPTION_SMARTMIPS:
11679      mips_opts.ase_smartmips = 1;
11680      break;
11681
11682    case OPTION_NO_SMARTMIPS:
11683      mips_opts.ase_smartmips = 0;
11684      break;
11685
11686    case OPTION_FIX_24K:
11687      mips_fix_24k = 1;
11688      break;
11689
11690    case OPTION_NO_FIX_24K:
11691      mips_fix_24k = 0;
11692      break;
11693
11694    case OPTION_FIX_LOONGSON2F_JUMP:
11695      mips_fix_loongson2f_jump = TRUE;
11696      break;
11697
11698    case OPTION_NO_FIX_LOONGSON2F_JUMP:
11699      mips_fix_loongson2f_jump = FALSE;
11700      break;
11701
11702    case OPTION_FIX_LOONGSON2F_NOP:
11703      mips_fix_loongson2f_nop = TRUE;
11704      break;
11705
11706    case OPTION_NO_FIX_LOONGSON2F_NOP:
11707      mips_fix_loongson2f_nop = FALSE;
11708      break;
11709
11710    case OPTION_FIX_VR4120:
11711      mips_fix_vr4120 = 1;
11712      break;
11713
11714    case OPTION_NO_FIX_VR4120:
11715      mips_fix_vr4120 = 0;
11716      break;
11717
11718    case OPTION_FIX_VR4130:
11719      mips_fix_vr4130 = 1;
11720      break;
11721
11722    case OPTION_NO_FIX_VR4130:
11723      mips_fix_vr4130 = 0;
11724      break;
11725
11726    case OPTION_FIX_LOONGSON2F_BTB:
11727      mips_fix_loongson2f_btb = 1;
11728      break;
11729
11730    case OPTION_NO_FIX_LOONGSON2F_BTB:
11731      mips_fix_loongson2f_btb = 0;
11732      break;
11733
11734    case OPTION_FIX_CN63XXP1:
11735      mips_fix_cn63xxp1 = TRUE;
11736      break;
11737
11738    case OPTION_NO_FIX_CN63XXP1:
11739      mips_fix_cn63xxp1 = FALSE;
11740      break;
11741
11742    case OPTION_RELAX_BRANCH:
11743      mips_relax_branch = 1;
11744      break;
11745
11746    case OPTION_NO_RELAX_BRANCH:
11747      mips_relax_branch = 0;
11748      break;
11749
11750    case OPTION_MSHARED:
11751      mips_in_shared = TRUE;
11752      break;
11753
11754    case OPTION_MNO_SHARED:
11755      mips_in_shared = FALSE;
11756      break;
11757
11758    case OPTION_MSYM32:
11759      mips_opts.sym32 = TRUE;
11760      break;
11761
11762    case OPTION_MNO_SYM32:
11763      mips_opts.sym32 = FALSE;
11764      break;
11765
11766    case OPTION_TRAP_ZERO_JUMP:
11767      mips_trap_zero_jump = TRUE;
11768      break;
11769
11770    case OPTION_NO_TRAP_ZERO_JUMP:
11771      mips_trap_zero_jump = FALSE;
11772      break;
11773
11774#ifdef OBJ_ELF
11775      /* When generating ELF code, we permit -KPIC and -call_shared to
11776	 select SVR4_PIC, and -non_shared to select no PIC.  This is
11777	 intended to be compatible with Irix 5.  */
11778    case OPTION_CALL_SHARED:
11779      if (!IS_ELF)
11780	{
11781	  as_bad (_("-call_shared is supported only for ELF format"));
11782	  return 0;
11783	}
11784      mips_pic = SVR4_PIC;
11785      mips_abicalls = TRUE;
11786      break;
11787
11788    case OPTION_CALL_NONPIC:
11789      if (!IS_ELF)
11790	{
11791	  as_bad (_("-call_nonpic is supported only for ELF format"));
11792	  return 0;
11793	}
11794      mips_pic = NO_PIC;
11795      mips_abicalls = TRUE;
11796      break;
11797
11798    case OPTION_NON_SHARED:
11799      if (!IS_ELF)
11800	{
11801	  as_bad (_("-non_shared is supported only for ELF format"));
11802	  return 0;
11803	}
11804      mips_pic = NO_PIC;
11805      mips_abicalls = FALSE;
11806      break;
11807
11808      /* The -xgot option tells the assembler to use 32 bit offsets
11809         when accessing the got in SVR4_PIC mode.  It is for Irix
11810         compatibility.  */
11811    case OPTION_XGOT:
11812      mips_big_got = 1;
11813      break;
11814#endif /* OBJ_ELF */
11815
11816    case 'G':
11817      g_switch_value = atoi (arg);
11818      g_switch_seen = 1;
11819      break;
11820
11821      /* The -32, -n32 and -64 options are shortcuts for -mabi=32, -mabi=n32
11822	 and -mabi=64.  */
11823    case OPTION_32:
11824      if (IS_ELF)
11825	mips_abi = O32_ABI;
11826      /* We silently ignore -32 for non-ELF targets.  This greatly
11827	 simplifies the construction of the MIPS GAS test cases.  */
11828      break;
11829
11830#ifdef OBJ_ELF
11831    case OPTION_N32:
11832      if (!IS_ELF)
11833	{
11834	  as_bad (_("-n32 is supported for ELF format only"));
11835	  return 0;
11836	}
11837      mips_abi = N32_ABI;
11838      break;
11839
11840    case OPTION_64:
11841      if (!IS_ELF)
11842	{
11843	  as_bad (_("-64 is supported for ELF format only"));
11844	  return 0;
11845	}
11846      mips_abi = N64_ABI;
11847      if (!support_64bit_objects())
11848	as_fatal (_("No compiled in support for 64 bit object file format"));
11849      break;
11850#endif /* OBJ_ELF */
11851
11852    case OPTION_GP32:
11853      file_mips_gp32 = 1;
11854      break;
11855
11856    case OPTION_GP64:
11857      file_mips_gp32 = 0;
11858      break;
11859
11860    case OPTION_FP32:
11861      file_mips_fp32 = 1;
11862      break;
11863
11864    case OPTION_FP64:
11865      file_mips_fp32 = 0;
11866      break;
11867
11868    case OPTION_SINGLE_FLOAT:
11869      file_mips_single_float = 1;
11870      break;
11871
11872    case OPTION_DOUBLE_FLOAT:
11873      file_mips_single_float = 0;
11874      break;
11875
11876    case OPTION_SOFT_FLOAT:
11877      file_mips_soft_float = 1;
11878      break;
11879
11880    case OPTION_HARD_FLOAT:
11881      file_mips_soft_float = 0;
11882      break;
11883
11884#ifdef OBJ_ELF
11885    case OPTION_MABI:
11886      if (!IS_ELF)
11887	{
11888	  as_bad (_("-mabi is supported for ELF format only"));
11889	  return 0;
11890	}
11891      if (strcmp (arg, "32") == 0)
11892	mips_abi = O32_ABI;
11893      else if (strcmp (arg, "o64") == 0)
11894	mips_abi = O64_ABI;
11895      else if (strcmp (arg, "n32") == 0)
11896	mips_abi = N32_ABI;
11897      else if (strcmp (arg, "64") == 0)
11898	{
11899	  mips_abi = N64_ABI;
11900	  if (! support_64bit_objects())
11901	    as_fatal (_("No compiled in support for 64 bit object file "
11902			"format"));
11903	}
11904      else if (strcmp (arg, "eabi") == 0)
11905	mips_abi = EABI_ABI;
11906      else
11907	{
11908	  as_fatal (_("invalid abi -mabi=%s"), arg);
11909	  return 0;
11910	}
11911      break;
11912#endif /* OBJ_ELF */
11913
11914    case OPTION_M7000_HILO_FIX:
11915      mips_7000_hilo_fix = TRUE;
11916      break;
11917
11918    case OPTION_MNO_7000_HILO_FIX:
11919      mips_7000_hilo_fix = FALSE;
11920      break;
11921
11922#ifdef OBJ_ELF
11923    case OPTION_MDEBUG:
11924      mips_flag_mdebug = TRUE;
11925      break;
11926
11927    case OPTION_NO_MDEBUG:
11928      mips_flag_mdebug = FALSE;
11929      break;
11930
11931    case OPTION_PDR:
11932      mips_flag_pdr = TRUE;
11933      break;
11934
11935    case OPTION_NO_PDR:
11936      mips_flag_pdr = FALSE;
11937      break;
11938
11939    case OPTION_MVXWORKS_PIC:
11940      mips_pic = VXWORKS_PIC;
11941      break;
11942#endif /* OBJ_ELF */
11943
11944    default:
11945      return 0;
11946    }
11947
11948    mips_fix_loongson2f = mips_fix_loongson2f_nop || mips_fix_loongson2f_jump;
11949
11950  return 1;
11951}
11952
11953/* Set up globals to generate code for the ISA or processor
11954   described by INFO.  */
11955
11956static void
11957mips_set_architecture (const struct mips_cpu_info *info)
11958{
11959  if (info != 0)
11960    {
11961      file_mips_arch = info->cpu;
11962      mips_opts.arch = info->cpu;
11963      mips_opts.isa = info->isa;
11964    }
11965}
11966
11967
11968/* Likewise for tuning.  */
11969
11970static void
11971mips_set_tune (const struct mips_cpu_info *info)
11972{
11973  if (info != 0)
11974    mips_tune = info->cpu;
11975}
11976
11977
11978void
11979mips_after_parse_args (void)
11980{
11981  const struct mips_cpu_info *arch_info = 0;
11982  const struct mips_cpu_info *tune_info = 0;
11983
11984  /* GP relative stuff not working for PE */
11985  if (strncmp (TARGET_OS, "pe", 2) == 0)
11986    {
11987      if (g_switch_seen && g_switch_value != 0)
11988	as_bad (_("-G not supported in this configuration."));
11989      g_switch_value = 0;
11990    }
11991
11992  if (mips_abi == NO_ABI)
11993    mips_abi = MIPS_DEFAULT_ABI;
11994
11995  /* The following code determines the architecture and register size.
11996     Similar code was added to GCC 3.3 (see override_options() in
11997     config/mips/mips.c).  The GAS and GCC code should be kept in sync
11998     as much as possible.  */
11999
12000  if (mips_arch_string != 0)
12001    arch_info = mips_parse_cpu ("-march", mips_arch_string);
12002
12003  if (file_mips_isa != ISA_UNKNOWN)
12004    {
12005      /* Handle -mipsN.  At this point, file_mips_isa contains the
12006	 ISA level specified by -mipsN, while arch_info->isa contains
12007	 the -march selection (if any).  */
12008      if (arch_info != 0)
12009	{
12010	  /* -march takes precedence over -mipsN, since it is more descriptive.
12011	     There's no harm in specifying both as long as the ISA levels
12012	     are the same.  */
12013	  if (file_mips_isa != arch_info->isa)
12014	    as_bad (_("-%s conflicts with the other architecture options, which imply -%s"),
12015		    mips_cpu_info_from_isa (file_mips_isa)->name,
12016		    mips_cpu_info_from_isa (arch_info->isa)->name);
12017	}
12018      else
12019	arch_info = mips_cpu_info_from_isa (file_mips_isa);
12020    }
12021
12022  if (arch_info == 0)
12023    arch_info = mips_parse_cpu ("default CPU", MIPS_CPU_STRING_DEFAULT);
12024
12025  if (ABI_NEEDS_64BIT_REGS (mips_abi) && !ISA_HAS_64BIT_REGS (arch_info->isa))
12026    as_bad (_("-march=%s is not compatible with the selected ABI"),
12027	    arch_info->name);
12028
12029  mips_set_architecture (arch_info);
12030
12031  /* Optimize for file_mips_arch, unless -mtune selects a different processor.  */
12032  if (mips_tune_string != 0)
12033    tune_info = mips_parse_cpu ("-mtune", mips_tune_string);
12034
12035  if (tune_info == 0)
12036    mips_set_tune (arch_info);
12037  else
12038    mips_set_tune (tune_info);
12039
12040  if (file_mips_gp32 >= 0)
12041    {
12042      /* The user specified the size of the integer registers.  Make sure
12043	 it agrees with the ABI and ISA.  */
12044      if (file_mips_gp32 == 0 && !ISA_HAS_64BIT_REGS (mips_opts.isa))
12045	as_bad (_("-mgp64 used with a 32-bit processor"));
12046      else if (file_mips_gp32 == 1 && ABI_NEEDS_64BIT_REGS (mips_abi))
12047	as_bad (_("-mgp32 used with a 64-bit ABI"));
12048      else if (file_mips_gp32 == 0 && ABI_NEEDS_32BIT_REGS (mips_abi))
12049	as_bad (_("-mgp64 used with a 32-bit ABI"));
12050    }
12051  else
12052    {
12053      /* Infer the integer register size from the ABI and processor.
12054	 Restrict ourselves to 32-bit registers if that's all the
12055	 processor has, or if the ABI cannot handle 64-bit registers.  */
12056      file_mips_gp32 = (ABI_NEEDS_32BIT_REGS (mips_abi)
12057			|| !ISA_HAS_64BIT_REGS (mips_opts.isa));
12058    }
12059
12060  switch (file_mips_fp32)
12061    {
12062    default:
12063    case -1:
12064      /* No user specified float register size.
12065	 ??? GAS treats single-float processors as though they had 64-bit
12066	 float registers (although it complains when double-precision
12067	 instructions are used).  As things stand, saying they have 32-bit
12068	 registers would lead to spurious "register must be even" messages.
12069	 So here we assume float registers are never smaller than the
12070	 integer ones.  */
12071      if (file_mips_gp32 == 0)
12072	/* 64-bit integer registers implies 64-bit float registers.  */
12073	file_mips_fp32 = 0;
12074      else if ((mips_opts.ase_mips3d > 0 || mips_opts.ase_mdmx > 0)
12075	       && ISA_HAS_64BIT_FPRS (mips_opts.isa))
12076	/* -mips3d and -mdmx imply 64-bit float registers, if possible.  */
12077	file_mips_fp32 = 0;
12078      else
12079	/* 32-bit float registers.  */
12080	file_mips_fp32 = 1;
12081      break;
12082
12083    /* The user specified the size of the float registers.  Check if it
12084       agrees with the ABI and ISA.  */
12085    case 0:
12086      if (!ISA_HAS_64BIT_FPRS (mips_opts.isa))
12087	as_bad (_("-mfp64 used with a 32-bit fpu"));
12088      else if (ABI_NEEDS_32BIT_REGS (mips_abi)
12089	       && !ISA_HAS_MXHC1 (mips_opts.isa))
12090	as_warn (_("-mfp64 used with a 32-bit ABI"));
12091      break;
12092    case 1:
12093      if (ABI_NEEDS_64BIT_REGS (mips_abi))
12094	as_warn (_("-mfp32 used with a 64-bit ABI"));
12095      break;
12096    }
12097
12098  /* End of GCC-shared inference code.  */
12099
12100  /* This flag is set when we have a 64-bit capable CPU but use only
12101     32-bit wide registers.  Note that EABI does not use it.  */
12102  if (ISA_HAS_64BIT_REGS (mips_opts.isa)
12103      && ((mips_abi == NO_ABI && file_mips_gp32 == 1)
12104	  || mips_abi == O32_ABI))
12105    mips_32bitmode = 1;
12106
12107  if (mips_opts.isa == ISA_MIPS1 && mips_trap)
12108    as_bad (_("trap exception not supported at ISA 1"));
12109
12110  /* If the selected architecture includes support for ASEs, enable
12111     generation of code for them.  */
12112  if (mips_opts.mips16 == -1)
12113    mips_opts.mips16 = (CPU_HAS_MIPS16 (file_mips_arch)) ? 1 : 0;
12114  if (mips_opts.ase_mips3d == -1)
12115    mips_opts.ase_mips3d = ((arch_info->flags & MIPS_CPU_ASE_MIPS3D)
12116			    && file_mips_fp32 == 0) ? 1 : 0;
12117  if (mips_opts.ase_mips3d && file_mips_fp32 == 1)
12118    as_bad (_("-mfp32 used with -mips3d"));
12119
12120  if (mips_opts.ase_mdmx == -1)
12121    mips_opts.ase_mdmx = ((arch_info->flags & MIPS_CPU_ASE_MDMX)
12122			  && file_mips_fp32 == 0) ? 1 : 0;
12123  if (mips_opts.ase_mdmx && file_mips_fp32 == 1)
12124    as_bad (_("-mfp32 used with -mdmx"));
12125
12126  if (mips_opts.ase_smartmips == -1)
12127    mips_opts.ase_smartmips = (arch_info->flags & MIPS_CPU_ASE_SMARTMIPS) ? 1 : 0;
12128  if (mips_opts.ase_smartmips && !ISA_SUPPORTS_SMARTMIPS)
12129    as_warn (_("%s ISA does not support SmartMIPS"),
12130	     mips_cpu_info_from_isa (mips_opts.isa)->name);
12131
12132  if (mips_opts.ase_dsp == -1)
12133    mips_opts.ase_dsp = (arch_info->flags & MIPS_CPU_ASE_DSP) ? 1 : 0;
12134  if (mips_opts.ase_dsp && !ISA_SUPPORTS_DSP_ASE)
12135    as_warn (_("%s ISA does not support DSP ASE"),
12136	     mips_cpu_info_from_isa (mips_opts.isa)->name);
12137
12138  if (mips_opts.ase_dspr2 == -1)
12139    {
12140      mips_opts.ase_dspr2 = (arch_info->flags & MIPS_CPU_ASE_DSPR2) ? 1 : 0;
12141      mips_opts.ase_dsp = (arch_info->flags & MIPS_CPU_ASE_DSP) ? 1 : 0;
12142    }
12143  if (mips_opts.ase_dspr2 && !ISA_SUPPORTS_DSPR2_ASE)
12144    as_warn (_("%s ISA does not support DSP R2 ASE"),
12145	     mips_cpu_info_from_isa (mips_opts.isa)->name);
12146
12147  if (mips_opts.ase_mt == -1)
12148    mips_opts.ase_mt = (arch_info->flags & MIPS_CPU_ASE_MT) ? 1 : 0;
12149  if (mips_opts.ase_mt && !ISA_SUPPORTS_MT_ASE)
12150    as_warn (_("%s ISA does not support MT ASE"),
12151	     mips_cpu_info_from_isa (mips_opts.isa)->name);
12152
12153  file_mips_isa = mips_opts.isa;
12154  file_ase_mips16 = mips_opts.mips16;
12155  file_ase_mips3d = mips_opts.ase_mips3d;
12156  file_ase_mdmx = mips_opts.ase_mdmx;
12157  file_ase_smartmips = mips_opts.ase_smartmips;
12158  file_ase_dsp = mips_opts.ase_dsp;
12159  file_ase_dspr2 = mips_opts.ase_dspr2;
12160  file_ase_mt = mips_opts.ase_mt;
12161  mips_opts.gp32 = file_mips_gp32;
12162  mips_opts.fp32 = file_mips_fp32;
12163  mips_opts.soft_float = file_mips_soft_float;
12164  mips_opts.single_float = file_mips_single_float;
12165
12166  if (mips_flag_mdebug < 0)
12167    {
12168#ifdef OBJ_MAYBE_ECOFF
12169      if (OUTPUT_FLAVOR == bfd_target_ecoff_flavour)
12170	mips_flag_mdebug = 1;
12171      else
12172#endif /* OBJ_MAYBE_ECOFF */
12173	mips_flag_mdebug = 0;
12174    }
12175}
12176
12177void
12178mips_init_after_args (void)
12179{
12180  /* initialize opcodes */
12181  bfd_mips_num_opcodes = bfd_mips_num_builtin_opcodes;
12182  mips_opcodes = (struct mips_opcode *) mips_builtin_opcodes;
12183}
12184
12185long
12186md_pcrel_from (fixS *fixP)
12187{
12188  valueT addr = fixP->fx_where + fixP->fx_frag->fr_address;
12189  switch (fixP->fx_r_type)
12190    {
12191    case BFD_RELOC_16_PCREL_S2:
12192    case BFD_RELOC_MIPS_JMP:
12193      /* Return the address of the delay slot.  */
12194      return addr + 4;
12195    default:
12196      /* We have no relocation type for PC relative MIPS16 instructions.  */
12197      if (fixP->fx_addsy && S_GET_SEGMENT (fixP->fx_addsy) != now_seg)
12198	as_bad_where (fixP->fx_file, fixP->fx_line,
12199		      _("PC relative MIPS16 instruction references a different section"));
12200      return addr;
12201    }
12202}
12203
12204/* This is called before the symbol table is processed.  In order to
12205   work with gcc when using mips-tfile, we must keep all local labels.
12206   However, in other cases, we want to discard them.  If we were
12207   called with -g, but we didn't see any debugging information, it may
12208   mean that gcc is smuggling debugging information through to
12209   mips-tfile, in which case we must generate all local labels.  */
12210
12211void
12212mips_frob_file_before_adjust (void)
12213{
12214#ifndef NO_ECOFF_DEBUGGING
12215  if (ECOFF_DEBUGGING
12216      && mips_debug != 0
12217      && ! ecoff_debugging_seen)
12218    flag_keep_locals = 1;
12219#endif
12220}
12221
12222/* Sort any unmatched HI16 and GOT16 relocs so that they immediately precede
12223   the corresponding LO16 reloc.  This is called before md_apply_fix and
12224   tc_gen_reloc.  Unmatched relocs can only be generated by use of explicit
12225   relocation operators.
12226
12227   For our purposes, a %lo() expression matches a %got() or %hi()
12228   expression if:
12229
12230      (a) it refers to the same symbol; and
12231      (b) the offset applied in the %lo() expression is no lower than
12232	  the offset applied in the %got() or %hi().
12233
12234   (b) allows us to cope with code like:
12235
12236	lui	$4,%hi(foo)
12237	lh	$4,%lo(foo+2)($4)
12238
12239   ...which is legal on RELA targets, and has a well-defined behaviour
12240   if the user knows that adding 2 to "foo" will not induce a carry to
12241   the high 16 bits.
12242
12243   When several %lo()s match a particular %got() or %hi(), we use the
12244   following rules to distinguish them:
12245
12246     (1) %lo()s with smaller offsets are a better match than %lo()s with
12247         higher offsets.
12248
12249     (2) %lo()s with no matching %got() or %hi() are better than those
12250         that already have a matching %got() or %hi().
12251
12252     (3) later %lo()s are better than earlier %lo()s.
12253
12254   These rules are applied in order.
12255
12256   (1) means, among other things, that %lo()s with identical offsets are
12257   chosen if they exist.
12258
12259   (2) means that we won't associate several high-part relocations with
12260   the same low-part relocation unless there's no alternative.  Having
12261   several high parts for the same low part is a GNU extension; this rule
12262   allows careful users to avoid it.
12263
12264   (3) is purely cosmetic.  mips_hi_fixup_list is is in reverse order,
12265   with the last high-part relocation being at the front of the list.
12266   It therefore makes sense to choose the last matching low-part
12267   relocation, all other things being equal.  It's also easier
12268   to code that way.  */
12269
12270void
12271mips_frob_file (void)
12272{
12273  struct mips_hi_fixup *l;
12274  bfd_reloc_code_real_type looking_for_rtype = BFD_RELOC_UNUSED;
12275
12276  for (l = mips_hi_fixup_list; l != NULL; l = l->next)
12277    {
12278      segment_info_type *seginfo;
12279      bfd_boolean matched_lo_p;
12280      fixS **hi_pos, **lo_pos, **pos;
12281
12282      gas_assert (reloc_needs_lo_p (l->fixp->fx_r_type));
12283
12284      /* If a GOT16 relocation turns out to be against a global symbol,
12285	 there isn't supposed to be a matching LO.  */
12286      if (got16_reloc_p (l->fixp->fx_r_type)
12287	  && !pic_need_relax (l->fixp->fx_addsy, l->seg))
12288	continue;
12289
12290      /* Check quickly whether the next fixup happens to be a matching %lo.  */
12291      if (fixup_has_matching_lo_p (l->fixp))
12292	continue;
12293
12294      seginfo = seg_info (l->seg);
12295
12296      /* Set HI_POS to the position of this relocation in the chain.
12297	 Set LO_POS to the position of the chosen low-part relocation.
12298	 MATCHED_LO_P is true on entry to the loop if *POS is a low-part
12299	 relocation that matches an immediately-preceding high-part
12300	 relocation.  */
12301      hi_pos = NULL;
12302      lo_pos = NULL;
12303      matched_lo_p = FALSE;
12304      looking_for_rtype = matching_lo_reloc (l->fixp->fx_r_type);
12305
12306      for (pos = &seginfo->fix_root; *pos != NULL; pos = &(*pos)->fx_next)
12307	{
12308	  if (*pos == l->fixp)
12309	    hi_pos = pos;
12310
12311	  if ((*pos)->fx_r_type == looking_for_rtype
12312	      && symbol_same_p ((*pos)->fx_addsy, l->fixp->fx_addsy)
12313	      && (*pos)->fx_offset >= l->fixp->fx_offset
12314	      && (lo_pos == NULL
12315		  || (*pos)->fx_offset < (*lo_pos)->fx_offset
12316		  || (!matched_lo_p
12317		      && (*pos)->fx_offset == (*lo_pos)->fx_offset)))
12318	    lo_pos = pos;
12319
12320	  matched_lo_p = (reloc_needs_lo_p ((*pos)->fx_r_type)
12321			  && fixup_has_matching_lo_p (*pos));
12322	}
12323
12324      /* If we found a match, remove the high-part relocation from its
12325	 current position and insert it before the low-part relocation.
12326	 Make the offsets match so that fixup_has_matching_lo_p()
12327	 will return true.
12328
12329	 We don't warn about unmatched high-part relocations since some
12330	 versions of gcc have been known to emit dead "lui ...%hi(...)"
12331	 instructions.  */
12332      if (lo_pos != NULL)
12333	{
12334	  l->fixp->fx_offset = (*lo_pos)->fx_offset;
12335	  if (l->fixp->fx_next != *lo_pos)
12336	    {
12337	      *hi_pos = l->fixp->fx_next;
12338	      l->fixp->fx_next = *lo_pos;
12339	      *lo_pos = l->fixp;
12340	    }
12341	}
12342    }
12343}
12344
12345/* We may have combined relocations without symbols in the N32/N64 ABI.
12346   We have to prevent gas from dropping them.  */
12347
12348int
12349mips_force_relocation (fixS *fixp)
12350{
12351  if (generic_force_reloc (fixp))
12352    return 1;
12353
12354  if (HAVE_NEWABI
12355      && S_GET_SEGMENT (fixp->fx_addsy) == bfd_abs_section_ptr
12356      && (fixp->fx_r_type == BFD_RELOC_MIPS_SUB
12357	  || hi16_reloc_p (fixp->fx_r_type)
12358	  || lo16_reloc_p (fixp->fx_r_type)))
12359    return 1;
12360
12361  return 0;
12362}
12363
12364/* Apply a fixup to the object file.  */
12365
12366void
12367md_apply_fix (fixS *fixP, valueT *valP, segT seg ATTRIBUTE_UNUSED)
12368{
12369  bfd_byte *buf;
12370  long insn;
12371  reloc_howto_type *howto;
12372
12373  /* We ignore generic BFD relocations we don't know about.  */
12374  howto = bfd_reloc_type_lookup (stdoutput, fixP->fx_r_type);
12375  if (! howto)
12376    return;
12377
12378  gas_assert (fixP->fx_size == 4
12379	  || fixP->fx_r_type == BFD_RELOC_16
12380	  || fixP->fx_r_type == BFD_RELOC_64
12381	  || fixP->fx_r_type == BFD_RELOC_CTOR
12382	  || fixP->fx_r_type == BFD_RELOC_MIPS_SUB
12383	  || fixP->fx_r_type == BFD_RELOC_VTABLE_INHERIT
12384	  || fixP->fx_r_type == BFD_RELOC_VTABLE_ENTRY
12385	  || fixP->fx_r_type == BFD_RELOC_MIPS_TLS_DTPREL64);
12386
12387  buf = (bfd_byte *) (fixP->fx_frag->fr_literal + fixP->fx_where);
12388
12389  gas_assert (!fixP->fx_pcrel || fixP->fx_r_type == BFD_RELOC_16_PCREL_S2);
12390
12391  /* Don't treat parts of a composite relocation as done.  There are two
12392     reasons for this:
12393
12394     (1) The second and third parts will be against 0 (RSS_UNDEF) but
12395	 should nevertheless be emitted if the first part is.
12396
12397     (2) In normal usage, composite relocations are never assembly-time
12398	 constants.  The easiest way of dealing with the pathological
12399	 exceptions is to generate a relocation against STN_UNDEF and
12400	 leave everything up to the linker.  */
12401  if (fixP->fx_addsy == NULL && !fixP->fx_pcrel && fixP->fx_tcbit == 0)
12402    fixP->fx_done = 1;
12403
12404  switch (fixP->fx_r_type)
12405    {
12406    case BFD_RELOC_MIPS_TLS_GD:
12407    case BFD_RELOC_MIPS_TLS_LDM:
12408    case BFD_RELOC_MIPS_TLS_DTPREL32:
12409    case BFD_RELOC_MIPS_TLS_DTPREL64:
12410    case BFD_RELOC_MIPS_TLS_DTPREL_HI16:
12411    case BFD_RELOC_MIPS_TLS_DTPREL_LO16:
12412    case BFD_RELOC_MIPS_TLS_GOTTPREL:
12413    case BFD_RELOC_MIPS_TLS_TPREL_HI16:
12414    case BFD_RELOC_MIPS_TLS_TPREL_LO16:
12415      S_SET_THREAD_LOCAL (fixP->fx_addsy);
12416      /* fall through */
12417
12418    case BFD_RELOC_MIPS_JMP:
12419    case BFD_RELOC_MIPS_SHIFT5:
12420    case BFD_RELOC_MIPS_SHIFT6:
12421    case BFD_RELOC_MIPS_GOT_DISP:
12422    case BFD_RELOC_MIPS_GOT_PAGE:
12423    case BFD_RELOC_MIPS_GOT_OFST:
12424    case BFD_RELOC_MIPS_SUB:
12425    case BFD_RELOC_MIPS_INSERT_A:
12426    case BFD_RELOC_MIPS_INSERT_B:
12427    case BFD_RELOC_MIPS_DELETE:
12428    case BFD_RELOC_MIPS_HIGHEST:
12429    case BFD_RELOC_MIPS_HIGHER:
12430    case BFD_RELOC_MIPS_SCN_DISP:
12431    case BFD_RELOC_MIPS_REL16:
12432    case BFD_RELOC_MIPS_RELGOT:
12433    case BFD_RELOC_MIPS_JALR:
12434    case BFD_RELOC_HI16:
12435    case BFD_RELOC_HI16_S:
12436    case BFD_RELOC_GPREL16:
12437    case BFD_RELOC_MIPS_LITERAL:
12438    case BFD_RELOC_MIPS_CALL16:
12439    case BFD_RELOC_MIPS_GOT16:
12440    case BFD_RELOC_GPREL32:
12441    case BFD_RELOC_MIPS_GOT_HI16:
12442    case BFD_RELOC_MIPS_GOT_LO16:
12443    case BFD_RELOC_MIPS_CALL_HI16:
12444    case BFD_RELOC_MIPS_CALL_LO16:
12445    case BFD_RELOC_MIPS16_GPREL:
12446    case BFD_RELOC_MIPS16_GOT16:
12447    case BFD_RELOC_MIPS16_CALL16:
12448    case BFD_RELOC_MIPS16_HI16:
12449    case BFD_RELOC_MIPS16_HI16_S:
12450    case BFD_RELOC_MIPS16_JMP:
12451      /* Nothing needed to do.  The value comes from the reloc entry.  */
12452      break;
12453
12454    case BFD_RELOC_64:
12455      /* This is handled like BFD_RELOC_32, but we output a sign
12456         extended value if we are only 32 bits.  */
12457      if (fixP->fx_done)
12458	{
12459	  if (8 <= sizeof (valueT))
12460	    md_number_to_chars ((char *) buf, *valP, 8);
12461	  else
12462	    {
12463	      valueT hiv;
12464
12465	      if ((*valP & 0x80000000) != 0)
12466		hiv = 0xffffffff;
12467	      else
12468		hiv = 0;
12469	      md_number_to_chars ((char *)(buf + (target_big_endian ? 4 : 0)),
12470				  *valP, 4);
12471	      md_number_to_chars ((char *)(buf + (target_big_endian ? 0 : 4)),
12472				  hiv, 4);
12473	    }
12474	}
12475      break;
12476
12477    case BFD_RELOC_RVA:
12478    case BFD_RELOC_32:
12479    case BFD_RELOC_16:
12480      /* If we are deleting this reloc entry, we must fill in the
12481	 value now.  This can happen if we have a .word which is not
12482	 resolved when it appears but is later defined.  */
12483      if (fixP->fx_done)
12484	md_number_to_chars ((char *) buf, *valP, fixP->fx_size);
12485      break;
12486
12487    case BFD_RELOC_LO16:
12488    case BFD_RELOC_MIPS16_LO16:
12489      /* FIXME: Now that embedded-PIC is gone, some of this code/comment
12490	 may be safe to remove, but if so it's not obvious.  */
12491      /* When handling an embedded PIC switch statement, we can wind
12492	 up deleting a LO16 reloc.  See the 'o' case in mips_ip.  */
12493      if (fixP->fx_done)
12494	{
12495	  if (*valP + 0x8000 > 0xffff)
12496	    as_bad_where (fixP->fx_file, fixP->fx_line,
12497			  _("relocation overflow"));
12498	  if (target_big_endian)
12499	    buf += 2;
12500	  md_number_to_chars ((char *) buf, *valP, 2);
12501	}
12502      break;
12503
12504    case BFD_RELOC_16_PCREL_S2:
12505      if ((*valP & 0x3) != 0)
12506	as_bad_where (fixP->fx_file, fixP->fx_line,
12507		      _("Branch to misaligned address (%lx)"), (long) *valP);
12508
12509      /* We need to save the bits in the instruction since fixup_segment()
12510	 might be deleting the relocation entry (i.e., a branch within
12511	 the current segment).  */
12512      if (! fixP->fx_done)
12513	break;
12514
12515      /* Update old instruction data.  */
12516      if (target_big_endian)
12517	insn = (buf[0] << 24) | (buf[1] << 16) | (buf[2] << 8) | buf[3];
12518      else
12519	insn = (buf[3] << 24) | (buf[2] << 16) | (buf[1] << 8) | buf[0];
12520
12521      if (*valP + 0x20000 <= 0x3ffff)
12522	{
12523	  insn |= (*valP >> 2) & 0xffff;
12524	  md_number_to_chars ((char *) buf, insn, 4);
12525	}
12526      else if (mips_pic == NO_PIC
12527	       && fixP->fx_done
12528	       && fixP->fx_frag->fr_address >= text_section->vma
12529	       && (fixP->fx_frag->fr_address
12530		   < text_section->vma + bfd_get_section_size (text_section))
12531	       && ((insn & 0xffff0000) == 0x10000000	 /* beq $0,$0 */
12532		   || (insn & 0xffff0000) == 0x04010000	 /* bgez $0 */
12533		   || (insn & 0xffff0000) == 0x04110000)) /* bgezal $0 */
12534	{
12535	  /* The branch offset is too large.  If this is an
12536             unconditional branch, and we are not generating PIC code,
12537             we can convert it to an absolute jump instruction.  */
12538	  if ((insn & 0xffff0000) == 0x04110000)	 /* bgezal $0 */
12539	    insn = 0x0c000000;	/* jal */
12540	  else
12541	    insn = 0x08000000;	/* j */
12542	  fixP->fx_r_type = BFD_RELOC_MIPS_JMP;
12543	  fixP->fx_done = 0;
12544	  fixP->fx_addsy = section_symbol (text_section);
12545	  *valP += md_pcrel_from (fixP);
12546	  md_number_to_chars ((char *) buf, insn, 4);
12547	}
12548      else
12549	{
12550	  /* If we got here, we have branch-relaxation disabled,
12551	     and there's nothing we can do to fix this instruction
12552	     without turning it into a longer sequence.  */
12553	  as_bad_where (fixP->fx_file, fixP->fx_line,
12554			_("Branch out of range"));
12555	}
12556      break;
12557
12558    case BFD_RELOC_VTABLE_INHERIT:
12559      fixP->fx_done = 0;
12560      if (fixP->fx_addsy
12561          && !S_IS_DEFINED (fixP->fx_addsy)
12562          && !S_IS_WEAK (fixP->fx_addsy))
12563        S_SET_WEAK (fixP->fx_addsy);
12564      break;
12565
12566    case BFD_RELOC_VTABLE_ENTRY:
12567      fixP->fx_done = 0;
12568      break;
12569
12570    default:
12571      internalError ();
12572    }
12573
12574  /* Remember value for tc_gen_reloc.  */
12575  fixP->fx_addnumber = *valP;
12576}
12577
12578static symbolS *
12579get_symbol (void)
12580{
12581  int c;
12582  char *name;
12583  symbolS *p;
12584
12585  name = input_line_pointer;
12586  c = get_symbol_end ();
12587  p = (symbolS *) symbol_find_or_make (name);
12588  *input_line_pointer = c;
12589  return p;
12590}
12591
12592/* Align the current frag to a given power of two.  If a particular
12593   fill byte should be used, FILL points to an integer that contains
12594   that byte, otherwise FILL is null.
12595
12596   The MIPS assembler also automatically adjusts any preceding
12597   label.  */
12598
12599static void
12600mips_align (int to, int *fill, symbolS *label)
12601{
12602  mips_emit_delays ();
12603  mips_record_mips16_mode ();
12604  if (fill == NULL && subseg_text_p (now_seg))
12605    frag_align_code (to, 0);
12606  else
12607    frag_align (to, fill ? *fill : 0, 0);
12608  record_alignment (now_seg, to);
12609  if (label != NULL)
12610    {
12611      gas_assert (S_GET_SEGMENT (label) == now_seg);
12612      symbol_set_frag (label, frag_now);
12613      S_SET_VALUE (label, (valueT) frag_now_fix ());
12614    }
12615}
12616
12617/* Align to a given power of two.  .align 0 turns off the automatic
12618   alignment used by the data creating pseudo-ops.  */
12619
12620static void
12621s_align (int x ATTRIBUTE_UNUSED)
12622{
12623  int temp, fill_value, *fill_ptr;
12624  long max_alignment = 28;
12625
12626  /* o Note that the assembler pulls down any immediately preceding label
12627       to the aligned address.
12628     o It's not documented but auto alignment is reinstated by
12629       a .align pseudo instruction.
12630     o Note also that after auto alignment is turned off the mips assembler
12631       issues an error on attempt to assemble an improperly aligned data item.
12632       We don't.  */
12633
12634  temp = get_absolute_expression ();
12635  if (temp > max_alignment)
12636    as_bad (_("Alignment too large: %d. assumed."), temp = max_alignment);
12637  else if (temp < 0)
12638    {
12639      as_warn (_("Alignment negative: 0 assumed."));
12640      temp = 0;
12641    }
12642  if (*input_line_pointer == ',')
12643    {
12644      ++input_line_pointer;
12645      fill_value = get_absolute_expression ();
12646      fill_ptr = &fill_value;
12647    }
12648  else
12649    fill_ptr = 0;
12650  if (temp)
12651    {
12652      segment_info_type *si = seg_info (now_seg);
12653      struct insn_label_list *l = si->label_list;
12654      /* Auto alignment should be switched on by next section change.  */
12655      auto_align = 1;
12656      mips_align (temp, fill_ptr, l != NULL ? l->label : NULL);
12657    }
12658  else
12659    {
12660      auto_align = 0;
12661    }
12662
12663  demand_empty_rest_of_line ();
12664}
12665
12666static void
12667s_change_sec (int sec)
12668{
12669  segT seg;
12670
12671#ifdef OBJ_ELF
12672  /* The ELF backend needs to know that we are changing sections, so
12673     that .previous works correctly.  We could do something like check
12674     for an obj_section_change_hook macro, but that might be confusing
12675     as it would not be appropriate to use it in the section changing
12676     functions in read.c, since obj-elf.c intercepts those.  FIXME:
12677     This should be cleaner, somehow.  */
12678  if (IS_ELF)
12679    obj_elf_section_change_hook ();
12680#endif
12681
12682  mips_emit_delays ();
12683
12684  switch (sec)
12685    {
12686    case 't':
12687      s_text (0);
12688      break;
12689    case 'd':
12690      s_data (0);
12691      break;
12692    case 'b':
12693      subseg_set (bss_section, (subsegT) get_absolute_expression ());
12694      demand_empty_rest_of_line ();
12695      break;
12696
12697    case 'r':
12698      seg = subseg_new (RDATA_SECTION_NAME,
12699			(subsegT) get_absolute_expression ());
12700      if (IS_ELF)
12701	{
12702	  bfd_set_section_flags (stdoutput, seg, (SEC_ALLOC | SEC_LOAD
12703						  | SEC_READONLY | SEC_RELOC
12704						  | SEC_DATA));
12705	  if (strncmp (TARGET_OS, "elf", 3) != 0)
12706	    record_alignment (seg, 4);
12707	}
12708      demand_empty_rest_of_line ();
12709      break;
12710
12711    case 's':
12712      seg = subseg_new (".sdata", (subsegT) get_absolute_expression ());
12713      if (IS_ELF)
12714	{
12715	  bfd_set_section_flags (stdoutput, seg,
12716				 SEC_ALLOC | SEC_LOAD | SEC_RELOC | SEC_DATA);
12717	  if (strncmp (TARGET_OS, "elf", 3) != 0)
12718	    record_alignment (seg, 4);
12719	}
12720      demand_empty_rest_of_line ();
12721      break;
12722
12723    case 'B':
12724      seg = subseg_new (".sbss", (subsegT) get_absolute_expression ());
12725      if (IS_ELF)
12726	{
12727	  bfd_set_section_flags (stdoutput, seg, SEC_ALLOC);
12728	  if (strncmp (TARGET_OS, "elf", 3) != 0)
12729	    record_alignment (seg, 4);
12730	}
12731      demand_empty_rest_of_line ();
12732      break;
12733    }
12734
12735  auto_align = 1;
12736}
12737
12738void
12739s_change_section (int ignore ATTRIBUTE_UNUSED)
12740{
12741#ifdef OBJ_ELF
12742  char *section_name;
12743  char c;
12744  char next_c = 0;
12745  int section_type;
12746  int section_flag;
12747  int section_entry_size;
12748  int section_alignment;
12749
12750  if (!IS_ELF)
12751    return;
12752
12753  section_name = input_line_pointer;
12754  c = get_symbol_end ();
12755  if (c)
12756    next_c = *(input_line_pointer + 1);
12757
12758  /* Do we have .section Name<,"flags">?  */
12759  if (c != ',' || (c == ',' && next_c == '"'))
12760    {
12761      /* just after name is now '\0'.  */
12762      *input_line_pointer = c;
12763      input_line_pointer = section_name;
12764      obj_elf_section (ignore);
12765      return;
12766    }
12767  input_line_pointer++;
12768
12769  /* Do we have .section Name<,type><,flag><,entry_size><,alignment>  */
12770  if (c == ',')
12771    section_type = get_absolute_expression ();
12772  else
12773    section_type = 0;
12774  if (*input_line_pointer++ == ',')
12775    section_flag = get_absolute_expression ();
12776  else
12777    section_flag = 0;
12778  if (*input_line_pointer++ == ',')
12779    section_entry_size = get_absolute_expression ();
12780  else
12781    section_entry_size = 0;
12782  if (*input_line_pointer++ == ',')
12783    section_alignment = get_absolute_expression ();
12784  else
12785    section_alignment = 0;
12786  /* FIXME: really ignore?  */
12787  (void) section_alignment;
12788
12789  section_name = xstrdup (section_name);
12790
12791  /* When using the generic form of .section (as implemented by obj-elf.c),
12792     there's no way to set the section type to SHT_MIPS_DWARF.  Users have
12793     traditionally had to fall back on the more common @progbits instead.
12794
12795     There's nothing really harmful in this, since bfd will correct
12796     SHT_PROGBITS to SHT_MIPS_DWARF before writing out the file.  But it
12797     means that, for backwards compatibility, the special_section entries
12798     for dwarf sections must use SHT_PROGBITS rather than SHT_MIPS_DWARF.
12799
12800     Even so, we shouldn't force users of the MIPS .section syntax to
12801     incorrectly label the sections as SHT_PROGBITS.  The best compromise
12802     seems to be to map SHT_MIPS_DWARF to SHT_PROGBITS before calling the
12803     generic type-checking code.  */
12804  if (section_type == SHT_MIPS_DWARF)
12805    section_type = SHT_PROGBITS;
12806
12807  obj_elf_change_section (section_name, section_type, section_flag,
12808			  section_entry_size, 0, 0, 0);
12809
12810  if (now_seg->name != section_name)
12811    free (section_name);
12812#endif /* OBJ_ELF */
12813}
12814
12815void
12816mips_enable_auto_align (void)
12817{
12818  auto_align = 1;
12819}
12820
12821static void
12822s_cons (int log_size)
12823{
12824  segment_info_type *si = seg_info (now_seg);
12825  struct insn_label_list *l = si->label_list;
12826  symbolS *label;
12827
12828  label = l != NULL ? l->label : NULL;
12829  mips_emit_delays ();
12830  if (log_size > 0 && auto_align)
12831    mips_align (log_size, 0, label);
12832  cons (1 << log_size);
12833  mips_clear_insn_labels ();
12834}
12835
12836static void
12837s_float_cons (int type)
12838{
12839  segment_info_type *si = seg_info (now_seg);
12840  struct insn_label_list *l = si->label_list;
12841  symbolS *label;
12842
12843  label = l != NULL ? l->label : NULL;
12844
12845  mips_emit_delays ();
12846
12847  if (auto_align)
12848    {
12849      if (type == 'd')
12850	mips_align (3, 0, label);
12851      else
12852	mips_align (2, 0, label);
12853    }
12854
12855  float_cons (type);
12856  mips_clear_insn_labels ();
12857}
12858
12859/* Handle .globl.  We need to override it because on Irix 5 you are
12860   permitted to say
12861       .globl foo .text
12862   where foo is an undefined symbol, to mean that foo should be
12863   considered to be the address of a function.  */
12864
12865static void
12866s_mips_globl (int x ATTRIBUTE_UNUSED)
12867{
12868  char *name;
12869  int c;
12870  symbolS *symbolP;
12871  flagword flag;
12872
12873  do
12874    {
12875      name = input_line_pointer;
12876      c = get_symbol_end ();
12877      symbolP = symbol_find_or_make (name);
12878      S_SET_EXTERNAL (symbolP);
12879
12880      *input_line_pointer = c;
12881      SKIP_WHITESPACE ();
12882
12883      /* On Irix 5, every global symbol that is not explicitly labelled as
12884         being a function is apparently labelled as being an object.  */
12885      flag = BSF_OBJECT;
12886
12887      if (!is_end_of_line[(unsigned char) *input_line_pointer]
12888	  && (*input_line_pointer != ','))
12889	{
12890	  char *secname;
12891	  asection *sec;
12892
12893	  secname = input_line_pointer;
12894	  c = get_symbol_end ();
12895	  sec = bfd_get_section_by_name (stdoutput, secname);
12896	  if (sec == NULL)
12897	    as_bad (_("%s: no such section"), secname);
12898	  *input_line_pointer = c;
12899
12900	  if (sec != NULL && (sec->flags & SEC_CODE) != 0)
12901	    flag = BSF_FUNCTION;
12902	}
12903
12904      symbol_get_bfdsym (symbolP)->flags |= flag;
12905
12906      c = *input_line_pointer;
12907      if (c == ',')
12908	{
12909	  input_line_pointer++;
12910	  SKIP_WHITESPACE ();
12911	  if (is_end_of_line[(unsigned char) *input_line_pointer])
12912	    c = '\n';
12913	}
12914    }
12915  while (c == ',');
12916
12917  demand_empty_rest_of_line ();
12918}
12919
12920static void
12921s_option (int x ATTRIBUTE_UNUSED)
12922{
12923  char *opt;
12924  char c;
12925
12926  opt = input_line_pointer;
12927  c = get_symbol_end ();
12928
12929  if (*opt == 'O')
12930    {
12931      /* FIXME: What does this mean?  */
12932    }
12933  else if (strncmp (opt, "pic", 3) == 0)
12934    {
12935      int i;
12936
12937      i = atoi (opt + 3);
12938      if (i == 0)
12939	mips_pic = NO_PIC;
12940      else if (i == 2)
12941	{
12942	mips_pic = SVR4_PIC;
12943	  mips_abicalls = TRUE;
12944	}
12945      else
12946	as_bad (_(".option pic%d not supported"), i);
12947
12948      if (mips_pic == SVR4_PIC)
12949	{
12950	  if (g_switch_seen && g_switch_value != 0)
12951	    as_warn (_("-G may not be used with SVR4 PIC code"));
12952	  g_switch_value = 0;
12953	  bfd_set_gp_size (stdoutput, 0);
12954	}
12955    }
12956  else
12957    as_warn (_("Unrecognized option \"%s\""), opt);
12958
12959  *input_line_pointer = c;
12960  demand_empty_rest_of_line ();
12961}
12962
12963/* This structure is used to hold a stack of .set values.  */
12964
12965struct mips_option_stack
12966{
12967  struct mips_option_stack *next;
12968  struct mips_set_options options;
12969};
12970
12971static struct mips_option_stack *mips_opts_stack;
12972
12973/* Handle the .set pseudo-op.  */
12974
12975static void
12976s_mipsset (int x ATTRIBUTE_UNUSED)
12977{
12978  char *name = input_line_pointer, ch;
12979
12980  while (!is_end_of_line[(unsigned char) *input_line_pointer])
12981    ++input_line_pointer;
12982  ch = *input_line_pointer;
12983  *input_line_pointer = '\0';
12984
12985  if (strcmp (name, "reorder") == 0)
12986    {
12987      if (mips_opts.noreorder)
12988	end_noreorder ();
12989    }
12990  else if (strcmp (name, "noreorder") == 0)
12991    {
12992      if (!mips_opts.noreorder)
12993	start_noreorder ();
12994    }
12995  else if (strncmp (name, "at=", 3) == 0)
12996    {
12997      char *s = name + 3;
12998
12999      if (!reg_lookup (&s, RTYPE_NUM | RTYPE_GP, &mips_opts.at))
13000	as_bad (_("Unrecognized register name `%s'"), s);
13001    }
13002  else if (strcmp (name, "at") == 0)
13003    {
13004      mips_opts.at = ATREG;
13005    }
13006  else if (strcmp (name, "noat") == 0)
13007    {
13008      mips_opts.at = ZERO;
13009    }
13010  else if (strcmp (name, "macro") == 0)
13011    {
13012      mips_opts.warn_about_macros = 0;
13013    }
13014  else if (strcmp (name, "nomacro") == 0)
13015    {
13016      if (mips_opts.noreorder == 0)
13017	as_bad (_("`noreorder' must be set before `nomacro'"));
13018      mips_opts.warn_about_macros = 1;
13019    }
13020  else if (strcmp (name, "move") == 0 || strcmp (name, "novolatile") == 0)
13021    {
13022      mips_opts.nomove = 0;
13023    }
13024  else if (strcmp (name, "nomove") == 0 || strcmp (name, "volatile") == 0)
13025    {
13026      mips_opts.nomove = 1;
13027    }
13028  else if (strcmp (name, "bopt") == 0)
13029    {
13030      mips_opts.nobopt = 0;
13031    }
13032  else if (strcmp (name, "nobopt") == 0)
13033    {
13034      mips_opts.nobopt = 1;
13035    }
13036  else if (strcmp (name, "gp=default") == 0)
13037    mips_opts.gp32 = file_mips_gp32;
13038  else if (strcmp (name, "gp=32") == 0)
13039    mips_opts.gp32 = 1;
13040  else if (strcmp (name, "gp=64") == 0)
13041    {
13042      if (!ISA_HAS_64BIT_REGS (mips_opts.isa))
13043	as_warn (_("%s isa does not support 64-bit registers"),
13044		 mips_cpu_info_from_isa (mips_opts.isa)->name);
13045      mips_opts.gp32 = 0;
13046    }
13047  else if (strcmp (name, "fp=default") == 0)
13048    mips_opts.fp32 = file_mips_fp32;
13049  else if (strcmp (name, "fp=32") == 0)
13050    mips_opts.fp32 = 1;
13051  else if (strcmp (name, "fp=64") == 0)
13052    {
13053      if (!ISA_HAS_64BIT_FPRS (mips_opts.isa))
13054	as_warn (_("%s isa does not support 64-bit floating point registers"),
13055		 mips_cpu_info_from_isa (mips_opts.isa)->name);
13056      mips_opts.fp32 = 0;
13057    }
13058  else if (strcmp (name, "softfloat") == 0)
13059    mips_opts.soft_float = 1;
13060  else if (strcmp (name, "hardfloat") == 0)
13061    mips_opts.soft_float = 0;
13062  else if (strcmp (name, "singlefloat") == 0)
13063    mips_opts.single_float = 1;
13064  else if (strcmp (name, "doublefloat") == 0)
13065    mips_opts.single_float = 0;
13066  else if (strcmp (name, "mips16") == 0
13067	   || strcmp (name, "MIPS-16") == 0)
13068    mips_opts.mips16 = 1;
13069  else if (strcmp (name, "nomips16") == 0
13070	   || strcmp (name, "noMIPS-16") == 0)
13071    mips_opts.mips16 = 0;
13072  else if (strcmp (name, "smartmips") == 0)
13073    {
13074      if (!ISA_SUPPORTS_SMARTMIPS)
13075	as_warn (_("%s ISA does not support SmartMIPS ASE"),
13076		 mips_cpu_info_from_isa (mips_opts.isa)->name);
13077      mips_opts.ase_smartmips = 1;
13078    }
13079  else if (strcmp (name, "nosmartmips") == 0)
13080    mips_opts.ase_smartmips = 0;
13081  else if (strcmp (name, "mips3d") == 0)
13082    mips_opts.ase_mips3d = 1;
13083  else if (strcmp (name, "nomips3d") == 0)
13084    mips_opts.ase_mips3d = 0;
13085  else if (strcmp (name, "mdmx") == 0)
13086    mips_opts.ase_mdmx = 1;
13087  else if (strcmp (name, "nomdmx") == 0)
13088    mips_opts.ase_mdmx = 0;
13089  else if (strcmp (name, "dsp") == 0)
13090    {
13091      if (!ISA_SUPPORTS_DSP_ASE)
13092	as_warn (_("%s ISA does not support DSP ASE"),
13093		 mips_cpu_info_from_isa (mips_opts.isa)->name);
13094      mips_opts.ase_dsp = 1;
13095      mips_opts.ase_dspr2 = 0;
13096    }
13097  else if (strcmp (name, "nodsp") == 0)
13098    {
13099      mips_opts.ase_dsp = 0;
13100      mips_opts.ase_dspr2 = 0;
13101    }
13102  else if (strcmp (name, "dspr2") == 0)
13103    {
13104      if (!ISA_SUPPORTS_DSPR2_ASE)
13105	as_warn (_("%s ISA does not support DSP R2 ASE"),
13106		 mips_cpu_info_from_isa (mips_opts.isa)->name);
13107      mips_opts.ase_dspr2 = 1;
13108      mips_opts.ase_dsp = 1;
13109    }
13110  else if (strcmp (name, "nodspr2") == 0)
13111    {
13112      mips_opts.ase_dspr2 = 0;
13113      mips_opts.ase_dsp = 0;
13114    }
13115  else if (strcmp (name, "mt") == 0)
13116    {
13117      if (!ISA_SUPPORTS_MT_ASE)
13118	as_warn (_("%s ISA does not support MT ASE"),
13119		 mips_cpu_info_from_isa (mips_opts.isa)->name);
13120      mips_opts.ase_mt = 1;
13121    }
13122  else if (strcmp (name, "nomt") == 0)
13123    mips_opts.ase_mt = 0;
13124  else if (strncmp (name, "mips", 4) == 0 || strncmp (name, "arch=", 5) == 0)
13125    {
13126      int reset = 0;
13127
13128      /* Permit the user to change the ISA and architecture on the fly.
13129	 Needless to say, misuse can cause serious problems.  */
13130      if (strcmp (name, "mips0") == 0 || strcmp (name, "arch=default") == 0)
13131	{
13132	  reset = 1;
13133	  mips_opts.isa = file_mips_isa;
13134	  mips_opts.arch = file_mips_arch;
13135	}
13136      else if (strncmp (name, "arch=", 5) == 0)
13137	{
13138	  const struct mips_cpu_info *p;
13139
13140	  p = mips_parse_cpu("internal use", name + 5);
13141	  if (!p)
13142	    as_bad (_("unknown architecture %s"), name + 5);
13143	  else
13144	    {
13145	      mips_opts.arch = p->cpu;
13146	      mips_opts.isa = p->isa;
13147	    }
13148	}
13149      else if (strncmp (name, "mips", 4) == 0)
13150	{
13151	  const struct mips_cpu_info *p;
13152
13153	  p = mips_parse_cpu("internal use", name);
13154	  if (!p)
13155	    as_bad (_("unknown ISA level %s"), name + 4);
13156	  else
13157	    {
13158	      mips_opts.arch = p->cpu;
13159	      mips_opts.isa = p->isa;
13160	    }
13161	}
13162      else
13163	as_bad (_("unknown ISA or architecture %s"), name);
13164
13165      switch (mips_opts.isa)
13166	{
13167	case  0:
13168	  break;
13169	case ISA_MIPS1:
13170	case ISA_MIPS2:
13171	case ISA_MIPS32:
13172	case ISA_MIPS32R2:
13173	  mips_opts.gp32 = 1;
13174	  mips_opts.fp32 = 1;
13175	  break;
13176	case ISA_MIPS3:
13177	case ISA_MIPS4:
13178	case ISA_MIPS5:
13179	case ISA_MIPS64:
13180	case ISA_MIPS64R2:
13181	  mips_opts.gp32 = 0;
13182	  mips_opts.fp32 = 0;
13183	  break;
13184	default:
13185	  as_bad (_("unknown ISA level %s"), name + 4);
13186	  break;
13187	}
13188      if (reset)
13189	{
13190	  mips_opts.gp32 = file_mips_gp32;
13191	  mips_opts.fp32 = file_mips_fp32;
13192	}
13193    }
13194  else if (strcmp (name, "autoextend") == 0)
13195    mips_opts.noautoextend = 0;
13196  else if (strcmp (name, "noautoextend") == 0)
13197    mips_opts.noautoextend = 1;
13198  else if (strcmp (name, "push") == 0)
13199    {
13200      struct mips_option_stack *s;
13201
13202      s = (struct mips_option_stack *) xmalloc (sizeof *s);
13203      s->next = mips_opts_stack;
13204      s->options = mips_opts;
13205      mips_opts_stack = s;
13206    }
13207  else if (strcmp (name, "pop") == 0)
13208    {
13209      struct mips_option_stack *s;
13210
13211      s = mips_opts_stack;
13212      if (s == NULL)
13213	as_bad (_(".set pop with no .set push"));
13214      else
13215	{
13216	  /* If we're changing the reorder mode we need to handle
13217             delay slots correctly.  */
13218	  if (s->options.noreorder && ! mips_opts.noreorder)
13219	    start_noreorder ();
13220	  else if (! s->options.noreorder && mips_opts.noreorder)
13221	    end_noreorder ();
13222
13223	  mips_opts = s->options;
13224	  mips_opts_stack = s->next;
13225	  free (s);
13226	}
13227    }
13228  else if (strcmp (name, "sym32") == 0)
13229    mips_opts.sym32 = TRUE;
13230  else if (strcmp (name, "nosym32") == 0)
13231    mips_opts.sym32 = FALSE;
13232  else if (strchr (name, ','))
13233    {
13234      /* Generic ".set" directive; use the generic handler.  */
13235      *input_line_pointer = ch;
13236      input_line_pointer = name;
13237      s_set (0);
13238      return;
13239    }
13240  else
13241    {
13242      as_warn (_("Tried to set unrecognized symbol: %s\n"), name);
13243    }
13244  *input_line_pointer = ch;
13245  demand_empty_rest_of_line ();
13246}
13247
13248/* Handle the .abicalls pseudo-op.  I believe this is equivalent to
13249   .option pic2.  It means to generate SVR4 PIC calls.  */
13250
13251static void
13252s_abicalls (int ignore ATTRIBUTE_UNUSED)
13253{
13254  mips_pic = SVR4_PIC;
13255  mips_abicalls = TRUE;
13256
13257  if (g_switch_seen && g_switch_value != 0)
13258    as_warn (_("-G may not be used with SVR4 PIC code"));
13259  g_switch_value = 0;
13260
13261  bfd_set_gp_size (stdoutput, 0);
13262  demand_empty_rest_of_line ();
13263}
13264
13265/* Handle the .cpload pseudo-op.  This is used when generating SVR4
13266   PIC code.  It sets the $gp register for the function based on the
13267   function address, which is in the register named in the argument.
13268   This uses a relocation against _gp_disp, which is handled specially
13269   by the linker.  The result is:
13270	lui	$gp,%hi(_gp_disp)
13271	addiu	$gp,$gp,%lo(_gp_disp)
13272	addu	$gp,$gp,.cpload argument
13273   The .cpload argument is normally $25 == $t9.
13274
13275   The -mno-shared option changes this to:
13276	lui	$gp,%hi(__gnu_local_gp)
13277	addiu	$gp,$gp,%lo(__gnu_local_gp)
13278   and the argument is ignored.  This saves an instruction, but the
13279   resulting code is not position independent; it uses an absolute
13280   address for __gnu_local_gp.  Thus code assembled with -mno-shared
13281   can go into an ordinary executable, but not into a shared library.  */
13282
13283static void
13284s_cpload (int ignore ATTRIBUTE_UNUSED)
13285{
13286  expressionS ex;
13287  int reg;
13288  int in_shared;
13289
13290  /* If we are not generating SVR4 PIC code, or if this is NewABI code,
13291     .cpload is ignored.  */
13292  if (mips_pic != SVR4_PIC || HAVE_NEWABI)
13293    {
13294      s_ignore (0);
13295      return;
13296    }
13297
13298  /* .cpload should be in a .set noreorder section.  */
13299  if (mips_opts.noreorder == 0)
13300    as_warn (_(".cpload not in noreorder section"));
13301
13302  reg = tc_get_register (0);
13303
13304  /* If we need to produce a 64-bit address, we are better off using
13305     the default instruction sequence.  */
13306  in_shared = mips_in_shared || HAVE_64BIT_SYMBOLS;
13307
13308  ex.X_op = O_symbol;
13309  ex.X_add_symbol = symbol_find_or_make (in_shared ? "_gp_disp" :
13310                                         "__gnu_local_gp");
13311  ex.X_op_symbol = NULL;
13312  ex.X_add_number = 0;
13313
13314  /* In ELF, this symbol is implicitly an STT_OBJECT symbol.  */
13315  symbol_get_bfdsym (ex.X_add_symbol)->flags |= BSF_OBJECT;
13316
13317  macro_start ();
13318  macro_build_lui (&ex, mips_gp_register);
13319  macro_build (&ex, "addiu", "t,r,j", mips_gp_register,
13320	       mips_gp_register, BFD_RELOC_LO16);
13321  if (in_shared)
13322    macro_build (NULL, "addu", "d,v,t", mips_gp_register,
13323		 mips_gp_register, reg);
13324  macro_end ();
13325
13326  demand_empty_rest_of_line ();
13327}
13328
13329/* Handle the .cpsetup pseudo-op defined for NewABI PIC code.  The syntax is:
13330     .cpsetup $reg1, offset|$reg2, label
13331
13332   If offset is given, this results in:
13333     sd		$gp, offset($sp)
13334     lui	$gp, %hi(%neg(%gp_rel(label)))
13335     addiu	$gp, $gp, %lo(%neg(%gp_rel(label)))
13336     daddu	$gp, $gp, $reg1
13337
13338   If $reg2 is given, this results in:
13339     daddu	$reg2, $gp, $0
13340     lui	$gp, %hi(%neg(%gp_rel(label)))
13341     addiu	$gp, $gp, %lo(%neg(%gp_rel(label)))
13342     daddu	$gp, $gp, $reg1
13343   $reg1 is normally $25 == $t9.
13344
13345   The -mno-shared option replaces the last three instructions with
13346	lui	$gp,%hi(_gp)
13347	addiu	$gp,$gp,%lo(_gp)  */
13348
13349static void
13350s_cpsetup (int ignore ATTRIBUTE_UNUSED)
13351{
13352  expressionS ex_off;
13353  expressionS ex_sym;
13354  int reg1;
13355
13356  /* If we are not generating SVR4 PIC code, .cpsetup is ignored.
13357     We also need NewABI support.  */
13358  if (mips_pic != SVR4_PIC || ! HAVE_NEWABI)
13359    {
13360      s_ignore (0);
13361      return;
13362    }
13363
13364  reg1 = tc_get_register (0);
13365  SKIP_WHITESPACE ();
13366  if (*input_line_pointer != ',')
13367    {
13368      as_bad (_("missing argument separator ',' for .cpsetup"));
13369      return;
13370    }
13371  else
13372    ++input_line_pointer;
13373  SKIP_WHITESPACE ();
13374  if (*input_line_pointer == '$')
13375    {
13376      mips_cpreturn_register = tc_get_register (0);
13377      mips_cpreturn_offset = -1;
13378    }
13379  else
13380    {
13381      mips_cpreturn_offset = get_absolute_expression ();
13382      mips_cpreturn_register = -1;
13383    }
13384  SKIP_WHITESPACE ();
13385  if (*input_line_pointer != ',')
13386    {
13387      as_bad (_("missing argument separator ',' for .cpsetup"));
13388      return;
13389    }
13390  else
13391    ++input_line_pointer;
13392  SKIP_WHITESPACE ();
13393  expression (&ex_sym);
13394
13395  macro_start ();
13396  if (mips_cpreturn_register == -1)
13397    {
13398      ex_off.X_op = O_constant;
13399      ex_off.X_add_symbol = NULL;
13400      ex_off.X_op_symbol = NULL;
13401      ex_off.X_add_number = mips_cpreturn_offset;
13402
13403      macro_build (&ex_off, "sd", "t,o(b)", mips_gp_register,
13404		   BFD_RELOC_LO16, SP);
13405    }
13406  else
13407    macro_build (NULL, "daddu", "d,v,t", mips_cpreturn_register,
13408		 mips_gp_register, 0);
13409
13410  if (mips_in_shared || HAVE_64BIT_SYMBOLS)
13411    {
13412      macro_build (&ex_sym, "lui", "t,u", mips_gp_register,
13413		   -1, BFD_RELOC_GPREL16, BFD_RELOC_MIPS_SUB,
13414		   BFD_RELOC_HI16_S);
13415
13416      macro_build (&ex_sym, "addiu", "t,r,j", mips_gp_register,
13417		   mips_gp_register, -1, BFD_RELOC_GPREL16,
13418		   BFD_RELOC_MIPS_SUB, BFD_RELOC_LO16);
13419
13420      macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", mips_gp_register,
13421		   mips_gp_register, reg1);
13422    }
13423  else
13424    {
13425      expressionS ex;
13426
13427      ex.X_op = O_symbol;
13428      ex.X_add_symbol = symbol_find_or_make ("__gnu_local_gp");
13429      ex.X_op_symbol = NULL;
13430      ex.X_add_number = 0;
13431
13432      /* In ELF, this symbol is implicitly an STT_OBJECT symbol.  */
13433      symbol_get_bfdsym (ex.X_add_symbol)->flags |= BSF_OBJECT;
13434
13435      macro_build_lui (&ex, mips_gp_register);
13436      macro_build (&ex, "addiu", "t,r,j", mips_gp_register,
13437		   mips_gp_register, BFD_RELOC_LO16);
13438    }
13439
13440  macro_end ();
13441
13442  demand_empty_rest_of_line ();
13443}
13444
13445static void
13446s_cplocal (int ignore ATTRIBUTE_UNUSED)
13447{
13448  /* If we are not generating SVR4 PIC code, or if this is not NewABI code,
13449     .cplocal is ignored.  */
13450  if (mips_pic != SVR4_PIC || ! HAVE_NEWABI)
13451    {
13452      s_ignore (0);
13453      return;
13454    }
13455
13456  mips_gp_register = tc_get_register (0);
13457  demand_empty_rest_of_line ();
13458}
13459
13460/* Handle the .cprestore pseudo-op.  This stores $gp into a given
13461   offset from $sp.  The offset is remembered, and after making a PIC
13462   call $gp is restored from that location.  */
13463
13464static void
13465s_cprestore (int ignore ATTRIBUTE_UNUSED)
13466{
13467  expressionS ex;
13468
13469  /* If we are not generating SVR4 PIC code, or if this is NewABI code,
13470     .cprestore is ignored.  */
13471  if (mips_pic != SVR4_PIC || HAVE_NEWABI)
13472    {
13473      s_ignore (0);
13474      return;
13475    }
13476
13477  mips_cprestore_offset = get_absolute_expression ();
13478  mips_cprestore_valid = 1;
13479
13480  ex.X_op = O_constant;
13481  ex.X_add_symbol = NULL;
13482  ex.X_op_symbol = NULL;
13483  ex.X_add_number = mips_cprestore_offset;
13484
13485  macro_start ();
13486  macro_build_ldst_constoffset (&ex, ADDRESS_STORE_INSN, mips_gp_register,
13487				SP, HAVE_64BIT_ADDRESSES);
13488  macro_end ();
13489
13490  demand_empty_rest_of_line ();
13491}
13492
13493/* Handle the .cpreturn pseudo-op defined for NewABI PIC code. If an offset
13494   was given in the preceding .cpsetup, it results in:
13495     ld		$gp, offset($sp)
13496
13497   If a register $reg2 was given there, it results in:
13498     daddu	$gp, $reg2, $0  */
13499
13500static void
13501s_cpreturn (int ignore ATTRIBUTE_UNUSED)
13502{
13503  expressionS ex;
13504
13505  /* If we are not generating SVR4 PIC code, .cpreturn is ignored.
13506     We also need NewABI support.  */
13507  if (mips_pic != SVR4_PIC || ! HAVE_NEWABI)
13508    {
13509      s_ignore (0);
13510      return;
13511    }
13512
13513  macro_start ();
13514  if (mips_cpreturn_register == -1)
13515    {
13516      ex.X_op = O_constant;
13517      ex.X_add_symbol = NULL;
13518      ex.X_op_symbol = NULL;
13519      ex.X_add_number = mips_cpreturn_offset;
13520
13521      macro_build (&ex, "ld", "t,o(b)", mips_gp_register, BFD_RELOC_LO16, SP);
13522    }
13523  else
13524    macro_build (NULL, "daddu", "d,v,t", mips_gp_register,
13525		 mips_cpreturn_register, 0);
13526  macro_end ();
13527
13528  demand_empty_rest_of_line ();
13529}
13530
13531/* Handle the .dtprelword and .dtpreldword pseudo-ops.  They generate
13532   a 32-bit or 64-bit DTP-relative relocation (BYTES says which) for
13533   use in DWARF debug information.  */
13534
13535static void
13536s_dtprel_internal (size_t bytes)
13537{
13538  expressionS ex;
13539  char *p;
13540
13541  expression (&ex);
13542
13543  if (ex.X_op != O_symbol)
13544    {
13545      as_bad (_("Unsupported use of %s"), (bytes == 8
13546					   ? ".dtpreldword"
13547					   : ".dtprelword"));
13548      ignore_rest_of_line ();
13549    }
13550
13551  p = frag_more (bytes);
13552  md_number_to_chars (p, 0, bytes);
13553  fix_new_exp (frag_now, p - frag_now->fr_literal, bytes, &ex, FALSE,
13554	       (bytes == 8
13555		? BFD_RELOC_MIPS_TLS_DTPREL64
13556		: BFD_RELOC_MIPS_TLS_DTPREL32));
13557
13558  demand_empty_rest_of_line ();
13559}
13560
13561/* Handle .dtprelword.  */
13562
13563static void
13564s_dtprelword (int ignore ATTRIBUTE_UNUSED)
13565{
13566  s_dtprel_internal (4);
13567}
13568
13569/* Handle .dtpreldword.  */
13570
13571static void
13572s_dtpreldword (int ignore ATTRIBUTE_UNUSED)
13573{
13574  s_dtprel_internal (8);
13575}
13576
13577/* Handle the .gpvalue pseudo-op.  This is used when generating NewABI PIC
13578   code.  It sets the offset to use in gp_rel relocations.  */
13579
13580static void
13581s_gpvalue (int ignore ATTRIBUTE_UNUSED)
13582{
13583  /* If we are not generating SVR4 PIC code, .gpvalue is ignored.
13584     We also need NewABI support.  */
13585  if (mips_pic != SVR4_PIC || ! HAVE_NEWABI)
13586    {
13587      s_ignore (0);
13588      return;
13589    }
13590
13591  mips_gprel_offset = get_absolute_expression ();
13592
13593  demand_empty_rest_of_line ();
13594}
13595
13596/* Handle the .gpword pseudo-op.  This is used when generating PIC
13597   code.  It generates a 32 bit GP relative reloc.  */
13598
13599static void
13600s_gpword (int ignore ATTRIBUTE_UNUSED)
13601{
13602  segment_info_type *si;
13603  struct insn_label_list *l;
13604  symbolS *label;
13605  expressionS ex;
13606  char *p;
13607
13608  /* When not generating PIC code, this is treated as .word.  */
13609  if (mips_pic != SVR4_PIC)
13610    {
13611      s_cons (2);
13612      return;
13613    }
13614
13615  si = seg_info (now_seg);
13616  l = si->label_list;
13617  label = l != NULL ? l->label : NULL;
13618  mips_emit_delays ();
13619  if (auto_align)
13620    mips_align (2, 0, label);
13621
13622  expression (&ex);
13623  mips_clear_insn_labels ();
13624
13625  if (ex.X_op != O_symbol || ex.X_add_number != 0)
13626    {
13627      as_bad (_("Unsupported use of .gpword"));
13628      ignore_rest_of_line ();
13629    }
13630
13631  p = frag_more (4);
13632  md_number_to_chars (p, 0, 4);
13633  fix_new_exp (frag_now, p - frag_now->fr_literal, 4, &ex, FALSE,
13634	       BFD_RELOC_GPREL32);
13635
13636  demand_empty_rest_of_line ();
13637}
13638
13639static void
13640s_gpdword (int ignore ATTRIBUTE_UNUSED)
13641{
13642  segment_info_type *si;
13643  struct insn_label_list *l;
13644  symbolS *label;
13645  expressionS ex;
13646  char *p;
13647
13648  /* When not generating PIC code, this is treated as .dword.  */
13649  if (mips_pic != SVR4_PIC)
13650    {
13651      s_cons (3);
13652      return;
13653    }
13654
13655  si = seg_info (now_seg);
13656  l = si->label_list;
13657  label = l != NULL ? l->label : NULL;
13658  mips_emit_delays ();
13659  if (auto_align)
13660    mips_align (3, 0, label);
13661
13662  expression (&ex);
13663  mips_clear_insn_labels ();
13664
13665  if (ex.X_op != O_symbol || ex.X_add_number != 0)
13666    {
13667      as_bad (_("Unsupported use of .gpdword"));
13668      ignore_rest_of_line ();
13669    }
13670
13671  p = frag_more (8);
13672  md_number_to_chars (p, 0, 8);
13673  fix_new_exp (frag_now, p - frag_now->fr_literal, 4, &ex, FALSE,
13674	       BFD_RELOC_GPREL32)->fx_tcbit = 1;
13675
13676  /* GPREL32 composed with 64 gives a 64-bit GP offset.  */
13677  fix_new (frag_now, p - frag_now->fr_literal, 8, NULL, 0,
13678	   FALSE, BFD_RELOC_64)->fx_tcbit = 1;
13679
13680  demand_empty_rest_of_line ();
13681}
13682
13683/* Handle the .cpadd pseudo-op.  This is used when dealing with switch
13684   tables in SVR4 PIC code.  */
13685
13686static void
13687s_cpadd (int ignore ATTRIBUTE_UNUSED)
13688{
13689  int reg;
13690
13691  /* This is ignored when not generating SVR4 PIC code.  */
13692  if (mips_pic != SVR4_PIC)
13693    {
13694      s_ignore (0);
13695      return;
13696    }
13697
13698  /* Add $gp to the register named as an argument.  */
13699  macro_start ();
13700  reg = tc_get_register (0);
13701  macro_build (NULL, ADDRESS_ADD_INSN, "d,v,t", reg, reg, mips_gp_register);
13702  macro_end ();
13703
13704  demand_empty_rest_of_line ();
13705}
13706
13707/* Handle the .insn pseudo-op.  This marks instruction labels in
13708   mips16 mode.  This permits the linker to handle them specially,
13709   such as generating jalx instructions when needed.  We also make
13710   them odd for the duration of the assembly, in order to generate the
13711   right sort of code.  We will make them even in the adjust_symtab
13712   routine, while leaving them marked.  This is convenient for the
13713   debugger and the disassembler.  The linker knows to make them odd
13714   again.  */
13715
13716static void
13717s_insn (int ignore ATTRIBUTE_UNUSED)
13718{
13719  mips16_mark_labels ();
13720
13721  demand_empty_rest_of_line ();
13722}
13723
13724/* Handle a .stabn directive.  We need these in order to mark a label
13725   as being a mips16 text label correctly.  Sometimes the compiler
13726   will emit a label, followed by a .stabn, and then switch sections.
13727   If the label and .stabn are in mips16 mode, then the label is
13728   really a mips16 text label.  */
13729
13730static void
13731s_mips_stab (int type)
13732{
13733  if (type == 'n')
13734    mips16_mark_labels ();
13735
13736  s_stab (type);
13737}
13738
13739/* Handle the .weakext pseudo-op as defined in Kane and Heinrich.  */
13740
13741static void
13742s_mips_weakext (int ignore ATTRIBUTE_UNUSED)
13743{
13744  char *name;
13745  int c;
13746  symbolS *symbolP;
13747  expressionS exp;
13748
13749  name = input_line_pointer;
13750  c = get_symbol_end ();
13751  symbolP = symbol_find_or_make (name);
13752  S_SET_WEAK (symbolP);
13753  *input_line_pointer = c;
13754
13755  SKIP_WHITESPACE ();
13756
13757  if (! is_end_of_line[(unsigned char) *input_line_pointer])
13758    {
13759      if (S_IS_DEFINED (symbolP))
13760	{
13761	  as_bad (_("ignoring attempt to redefine symbol %s"),
13762		  S_GET_NAME (symbolP));
13763	  ignore_rest_of_line ();
13764	  return;
13765	}
13766
13767      if (*input_line_pointer == ',')
13768	{
13769	  ++input_line_pointer;
13770	  SKIP_WHITESPACE ();
13771	}
13772
13773      expression (&exp);
13774      if (exp.X_op != O_symbol)
13775	{
13776	  as_bad (_("bad .weakext directive"));
13777	  ignore_rest_of_line ();
13778	  return;
13779	}
13780      symbol_set_value_expression (symbolP, &exp);
13781    }
13782
13783  demand_empty_rest_of_line ();
13784}
13785
13786/* Parse a register string into a number.  Called from the ECOFF code
13787   to parse .frame.  The argument is non-zero if this is the frame
13788   register, so that we can record it in mips_frame_reg.  */
13789
13790int
13791tc_get_register (int frame)
13792{
13793  unsigned int reg;
13794
13795  SKIP_WHITESPACE ();
13796  if (! reg_lookup (&input_line_pointer, RWARN | RTYPE_NUM | RTYPE_GP, &reg))
13797    reg = 0;
13798  if (frame)
13799    {
13800      mips_frame_reg = reg != 0 ? reg : SP;
13801      mips_frame_reg_valid = 1;
13802      mips_cprestore_valid = 0;
13803    }
13804  return reg;
13805}
13806
13807valueT
13808md_section_align (asection *seg, valueT addr)
13809{
13810  int align = bfd_get_section_alignment (stdoutput, seg);
13811
13812  if (IS_ELF)
13813    {
13814      /* We don't need to align ELF sections to the full alignment.
13815	 However, Irix 5 may prefer that we align them at least to a 16
13816	 byte boundary.  We don't bother to align the sections if we
13817	 are targeted for an embedded system.  */
13818      if (strncmp (TARGET_OS, "elf", 3) == 0)
13819        return addr;
13820      if (align > 4)
13821        align = 4;
13822    }
13823
13824  return ((addr + (1 << align) - 1) & (-1 << align));
13825}
13826
13827/* Utility routine, called from above as well.  If called while the
13828   input file is still being read, it's only an approximation.  (For
13829   example, a symbol may later become defined which appeared to be
13830   undefined earlier.)  */
13831
13832static int
13833nopic_need_relax (symbolS *sym, int before_relaxing)
13834{
13835  if (sym == 0)
13836    return 0;
13837
13838  if (g_switch_value > 0)
13839    {
13840      const char *symname;
13841      int change;
13842
13843      /* Find out whether this symbol can be referenced off the $gp
13844	 register.  It can be if it is smaller than the -G size or if
13845	 it is in the .sdata or .sbss section.  Certain symbols can
13846	 not be referenced off the $gp, although it appears as though
13847	 they can.  */
13848      symname = S_GET_NAME (sym);
13849      if (symname != (const char *) NULL
13850	  && (strcmp (symname, "eprol") == 0
13851	      || strcmp (symname, "etext") == 0
13852	      || strcmp (symname, "_gp") == 0
13853	      || strcmp (symname, "edata") == 0
13854	      || strcmp (symname, "_fbss") == 0
13855	      || strcmp (symname, "_fdata") == 0
13856	      || strcmp (symname, "_ftext") == 0
13857	      || strcmp (symname, "end") == 0
13858	      || strcmp (symname, "_gp_disp") == 0))
13859	change = 1;
13860      else if ((! S_IS_DEFINED (sym) || S_IS_COMMON (sym))
13861	       && (0
13862#ifndef NO_ECOFF_DEBUGGING
13863		   || (symbol_get_obj (sym)->ecoff_extern_size != 0
13864		       && (symbol_get_obj (sym)->ecoff_extern_size
13865			   <= g_switch_value))
13866#endif
13867		   /* We must defer this decision until after the whole
13868		      file has been read, since there might be a .extern
13869		      after the first use of this symbol.  */
13870		   || (before_relaxing
13871#ifndef NO_ECOFF_DEBUGGING
13872		       && symbol_get_obj (sym)->ecoff_extern_size == 0
13873#endif
13874		       && S_GET_VALUE (sym) == 0)
13875		   || (S_GET_VALUE (sym) != 0
13876		       && S_GET_VALUE (sym) <= g_switch_value)))
13877	change = 0;
13878      else
13879	{
13880	  const char *segname;
13881
13882	  segname = segment_name (S_GET_SEGMENT (sym));
13883	  gas_assert (strcmp (segname, ".lit8") != 0
13884		  && strcmp (segname, ".lit4") != 0);
13885	  change = (strcmp (segname, ".sdata") != 0
13886		    && strcmp (segname, ".sbss") != 0
13887		    && strncmp (segname, ".sdata.", 7) != 0
13888		    && strncmp (segname, ".sbss.", 6) != 0
13889		    && strncmp (segname, ".gnu.linkonce.sb.", 17) != 0
13890		    && strncmp (segname, ".gnu.linkonce.s.", 16) != 0);
13891	}
13892      return change;
13893    }
13894  else
13895    /* We are not optimizing for the $gp register.  */
13896    return 1;
13897}
13898
13899
13900/* Return true if the given symbol should be considered local for SVR4 PIC.  */
13901
13902static bfd_boolean
13903pic_need_relax (symbolS *sym, asection *segtype)
13904{
13905  asection *symsec;
13906
13907  /* Handle the case of a symbol equated to another symbol.  */
13908  while (symbol_equated_reloc_p (sym))
13909    {
13910      symbolS *n;
13911
13912      /* It's possible to get a loop here in a badly written program.  */
13913      n = symbol_get_value_expression (sym)->X_add_symbol;
13914      if (n == sym)
13915	break;
13916      sym = n;
13917    }
13918
13919  if (symbol_section_p (sym))
13920    return TRUE;
13921
13922  symsec = S_GET_SEGMENT (sym);
13923
13924  /* This must duplicate the test in adjust_reloc_syms.  */
13925  return (symsec != &bfd_und_section
13926	  && symsec != &bfd_abs_section
13927	  && !bfd_is_com_section (symsec)
13928	  && !s_is_linkonce (sym, segtype)
13929#ifdef OBJ_ELF
13930	  /* A global or weak symbol is treated as external.  */
13931	  && (!IS_ELF || (! S_IS_WEAK (sym) && ! S_IS_EXTERNAL (sym)))
13932#endif
13933	  );
13934}
13935
13936
13937/* Given a mips16 variant frag FRAGP, return non-zero if it needs an
13938   extended opcode.  SEC is the section the frag is in.  */
13939
13940static int
13941mips16_extended_frag (fragS *fragp, asection *sec, long stretch)
13942{
13943  int type;
13944  const struct mips16_immed_operand *op;
13945  offsetT val;
13946  int mintiny, maxtiny;
13947  segT symsec;
13948  fragS *sym_frag;
13949
13950  if (RELAX_MIPS16_USER_SMALL (fragp->fr_subtype))
13951    return 0;
13952  if (RELAX_MIPS16_USER_EXT (fragp->fr_subtype))
13953    return 1;
13954
13955  type = RELAX_MIPS16_TYPE (fragp->fr_subtype);
13956  op = mips16_immed_operands;
13957  while (op->type != type)
13958    {
13959      ++op;
13960      gas_assert (op < mips16_immed_operands + MIPS16_NUM_IMMED);
13961    }
13962
13963  if (op->unsp)
13964    {
13965      if (type == '<' || type == '>' || type == '[' || type == ']')
13966	{
13967	  mintiny = 1;
13968	  maxtiny = 1 << op->nbits;
13969	}
13970      else
13971	{
13972	  mintiny = 0;
13973	  maxtiny = (1 << op->nbits) - 1;
13974	}
13975    }
13976  else
13977    {
13978      mintiny = - (1 << (op->nbits - 1));
13979      maxtiny = (1 << (op->nbits - 1)) - 1;
13980    }
13981
13982  sym_frag = symbol_get_frag (fragp->fr_symbol);
13983  val = S_GET_VALUE (fragp->fr_symbol);
13984  symsec = S_GET_SEGMENT (fragp->fr_symbol);
13985
13986  if (op->pcrel)
13987    {
13988      addressT addr;
13989
13990      /* We won't have the section when we are called from
13991         mips_relax_frag.  However, we will always have been called
13992         from md_estimate_size_before_relax first.  If this is a
13993         branch to a different section, we mark it as such.  If SEC is
13994         NULL, and the frag is not marked, then it must be a branch to
13995         the same section.  */
13996      if (sec == NULL)
13997	{
13998	  if (RELAX_MIPS16_LONG_BRANCH (fragp->fr_subtype))
13999	    return 1;
14000	}
14001      else
14002	{
14003	  /* Must have been called from md_estimate_size_before_relax.  */
14004	  if (symsec != sec)
14005	    {
14006	      fragp->fr_subtype =
14007		RELAX_MIPS16_MARK_LONG_BRANCH (fragp->fr_subtype);
14008
14009	      /* FIXME: We should support this, and let the linker
14010                 catch branches and loads that are out of range.  */
14011	      as_bad_where (fragp->fr_file, fragp->fr_line,
14012			    _("unsupported PC relative reference to different section"));
14013
14014	      return 1;
14015	    }
14016	  if (fragp != sym_frag && sym_frag->fr_address == 0)
14017	    /* Assume non-extended on the first relaxation pass.
14018	       The address we have calculated will be bogus if this is
14019	       a forward branch to another frag, as the forward frag
14020	       will have fr_address == 0.  */
14021	    return 0;
14022	}
14023
14024      /* In this case, we know for sure that the symbol fragment is in
14025	 the same section.  If the relax_marker of the symbol fragment
14026	 differs from the relax_marker of this fragment, we have not
14027	 yet adjusted the symbol fragment fr_address.  We want to add
14028	 in STRETCH in order to get a better estimate of the address.
14029	 This particularly matters because of the shift bits.  */
14030      if (stretch != 0
14031	  && sym_frag->relax_marker != fragp->relax_marker)
14032	{
14033	  fragS *f;
14034
14035	  /* Adjust stretch for any alignment frag.  Note that if have
14036             been expanding the earlier code, the symbol may be
14037             defined in what appears to be an earlier frag.  FIXME:
14038             This doesn't handle the fr_subtype field, which specifies
14039             a maximum number of bytes to skip when doing an
14040             alignment.  */
14041	  for (f = fragp; f != NULL && f != sym_frag; f = f->fr_next)
14042	    {
14043	      if (f->fr_type == rs_align || f->fr_type == rs_align_code)
14044		{
14045		  if (stretch < 0)
14046		    stretch = - ((- stretch)
14047				 & ~ ((1 << (int) f->fr_offset) - 1));
14048		  else
14049		    stretch &= ~ ((1 << (int) f->fr_offset) - 1);
14050		  if (stretch == 0)
14051		    break;
14052		}
14053	    }
14054	  if (f != NULL)
14055	    val += stretch;
14056	}
14057
14058      addr = fragp->fr_address + fragp->fr_fix;
14059
14060      /* The base address rules are complicated.  The base address of
14061         a branch is the following instruction.  The base address of a
14062         PC relative load or add is the instruction itself, but if it
14063         is in a delay slot (in which case it can not be extended) use
14064         the address of the instruction whose delay slot it is in.  */
14065      if (type == 'p' || type == 'q')
14066	{
14067	  addr += 2;
14068
14069	  /* If we are currently assuming that this frag should be
14070	     extended, then, the current address is two bytes
14071	     higher.  */
14072	  if (RELAX_MIPS16_EXTENDED (fragp->fr_subtype))
14073	    addr += 2;
14074
14075	  /* Ignore the low bit in the target, since it will be set
14076             for a text label.  */
14077	  if ((val & 1) != 0)
14078	    --val;
14079	}
14080      else if (RELAX_MIPS16_JAL_DSLOT (fragp->fr_subtype))
14081	addr -= 4;
14082      else if (RELAX_MIPS16_DSLOT (fragp->fr_subtype))
14083	addr -= 2;
14084
14085      val -= addr & ~ ((1 << op->shift) - 1);
14086
14087      /* Branch offsets have an implicit 0 in the lowest bit.  */
14088      if (type == 'p' || type == 'q')
14089	val /= 2;
14090
14091      /* If any of the shifted bits are set, we must use an extended
14092         opcode.  If the address depends on the size of this
14093         instruction, this can lead to a loop, so we arrange to always
14094         use an extended opcode.  We only check this when we are in
14095         the main relaxation loop, when SEC is NULL.  */
14096      if ((val & ((1 << op->shift) - 1)) != 0 && sec == NULL)
14097	{
14098	  fragp->fr_subtype =
14099	    RELAX_MIPS16_MARK_LONG_BRANCH (fragp->fr_subtype);
14100	  return 1;
14101	}
14102
14103      /* If we are about to mark a frag as extended because the value
14104         is precisely maxtiny + 1, then there is a chance of an
14105         infinite loop as in the following code:
14106	     la	$4,foo
14107	     .skip	1020
14108	     .align	2
14109	   foo:
14110	 In this case when the la is extended, foo is 0x3fc bytes
14111	 away, so the la can be shrunk, but then foo is 0x400 away, so
14112	 the la must be extended.  To avoid this loop, we mark the
14113	 frag as extended if it was small, and is about to become
14114	 extended with a value of maxtiny + 1.  */
14115      if (val == ((maxtiny + 1) << op->shift)
14116	  && ! RELAX_MIPS16_EXTENDED (fragp->fr_subtype)
14117	  && sec == NULL)
14118	{
14119	  fragp->fr_subtype =
14120	    RELAX_MIPS16_MARK_LONG_BRANCH (fragp->fr_subtype);
14121	  return 1;
14122	}
14123    }
14124  else if (symsec != absolute_section && sec != NULL)
14125    as_bad_where (fragp->fr_file, fragp->fr_line, _("unsupported relocation"));
14126
14127  if ((val & ((1 << op->shift) - 1)) != 0
14128      || val < (mintiny << op->shift)
14129      || val > (maxtiny << op->shift))
14130    return 1;
14131  else
14132    return 0;
14133}
14134
14135/* Compute the length of a branch sequence, and adjust the
14136   RELAX_BRANCH_TOOFAR bit accordingly.  If FRAGP is NULL, the
14137   worst-case length is computed, with UPDATE being used to indicate
14138   whether an unconditional (-1), branch-likely (+1) or regular (0)
14139   branch is to be computed.  */
14140static int
14141relaxed_branch_length (fragS *fragp, asection *sec, int update)
14142{
14143  bfd_boolean toofar;
14144  int length;
14145
14146  if (fragp
14147      && S_IS_DEFINED (fragp->fr_symbol)
14148      && sec == S_GET_SEGMENT (fragp->fr_symbol))
14149    {
14150      addressT addr;
14151      offsetT val;
14152
14153      val = S_GET_VALUE (fragp->fr_symbol) + fragp->fr_offset;
14154
14155      addr = fragp->fr_address + fragp->fr_fix + 4;
14156
14157      val -= addr;
14158
14159      toofar = val < - (0x8000 << 2) || val >= (0x8000 << 2);
14160    }
14161  else if (fragp)
14162    /* If the symbol is not defined or it's in a different segment,
14163       assume the user knows what's going on and emit a short
14164       branch.  */
14165    toofar = FALSE;
14166  else
14167    toofar = TRUE;
14168
14169  if (fragp && update && toofar != RELAX_BRANCH_TOOFAR (fragp->fr_subtype))
14170    fragp->fr_subtype
14171      = RELAX_BRANCH_ENCODE (RELAX_BRANCH_UNCOND (fragp->fr_subtype),
14172			     RELAX_BRANCH_LIKELY (fragp->fr_subtype),
14173			     RELAX_BRANCH_LINK (fragp->fr_subtype),
14174			     toofar);
14175
14176  length = 4;
14177  if (toofar)
14178    {
14179      if (fragp ? RELAX_BRANCH_LIKELY (fragp->fr_subtype) : (update > 0))
14180	length += 8;
14181
14182      if (mips_pic != NO_PIC)
14183	{
14184	  /* Additional space for PIC loading of target address.  */
14185	  length += 8;
14186	  if (mips_opts.isa == ISA_MIPS1)
14187	    /* Additional space for $at-stabilizing nop.  */
14188	    length += 4;
14189	}
14190
14191      /* If branch is conditional.  */
14192      if (fragp ? !RELAX_BRANCH_UNCOND (fragp->fr_subtype) : (update >= 0))
14193	length += 8;
14194    }
14195
14196  return length;
14197}
14198
14199/* Estimate the size of a frag before relaxing.  Unless this is the
14200   mips16, we are not really relaxing here, and the final size is
14201   encoded in the subtype information.  For the mips16, we have to
14202   decide whether we are using an extended opcode or not.  */
14203
14204int
14205md_estimate_size_before_relax (fragS *fragp, asection *segtype)
14206{
14207  int change;
14208
14209  if (RELAX_BRANCH_P (fragp->fr_subtype))
14210    {
14211
14212      fragp->fr_var = relaxed_branch_length (fragp, segtype, FALSE);
14213
14214      return fragp->fr_var;
14215    }
14216
14217  if (RELAX_MIPS16_P (fragp->fr_subtype))
14218    /* We don't want to modify the EXTENDED bit here; it might get us
14219       into infinite loops.  We change it only in mips_relax_frag().  */
14220    return (RELAX_MIPS16_EXTENDED (fragp->fr_subtype) ? 4 : 2);
14221
14222  if (mips_pic == NO_PIC)
14223    change = nopic_need_relax (fragp->fr_symbol, 0);
14224  else if (mips_pic == SVR4_PIC)
14225    change = pic_need_relax (fragp->fr_symbol, segtype);
14226  else if (mips_pic == VXWORKS_PIC)
14227    /* For vxworks, GOT16 relocations never have a corresponding LO16.  */
14228    change = 0;
14229  else
14230    abort ();
14231
14232  if (change)
14233    {
14234      fragp->fr_subtype |= RELAX_USE_SECOND;
14235      return -RELAX_FIRST (fragp->fr_subtype);
14236    }
14237  else
14238    return -RELAX_SECOND (fragp->fr_subtype);
14239}
14240
14241/* This is called to see whether a reloc against a defined symbol
14242   should be converted into a reloc against a section.  */
14243
14244int
14245mips_fix_adjustable (fixS *fixp)
14246{
14247  if (fixp->fx_r_type == BFD_RELOC_VTABLE_INHERIT
14248      || fixp->fx_r_type == BFD_RELOC_VTABLE_ENTRY)
14249    return 0;
14250
14251  if (fixp->fx_addsy == NULL)
14252    return 1;
14253
14254  /* If symbol SYM is in a mergeable section, relocations of the form
14255     SYM + 0 can usually be made section-relative.  The mergeable data
14256     is then identified by the section offset rather than by the symbol.
14257
14258     However, if we're generating REL LO16 relocations, the offset is split
14259     between the LO16 and parterning high part relocation.  The linker will
14260     need to recalculate the complete offset in order to correctly identify
14261     the merge data.
14262
14263     The linker has traditionally not looked for the parterning high part
14264     relocation, and has thus allowed orphaned R_MIPS_LO16 relocations to be
14265     placed anywhere.  Rather than break backwards compatibility by changing
14266     this, it seems better not to force the issue, and instead keep the
14267     original symbol.  This will work with either linker behavior.  */
14268  if ((lo16_reloc_p (fixp->fx_r_type)
14269       || reloc_needs_lo_p (fixp->fx_r_type))
14270      && HAVE_IN_PLACE_ADDENDS
14271      && (S_GET_SEGMENT (fixp->fx_addsy)->flags & SEC_MERGE) != 0)
14272    return 0;
14273
14274  /* There is no place to store an in-place offset for JALR relocations.  */
14275  if (fixp->fx_r_type == BFD_RELOC_MIPS_JALR && HAVE_IN_PLACE_ADDENDS)
14276    return 0;
14277
14278#ifdef OBJ_ELF
14279  /* R_MIPS16_26 relocations against non-MIPS16 functions might resolve
14280     to a floating-point stub.  The same is true for non-R_MIPS16_26
14281     relocations against MIPS16 functions; in this case, the stub becomes
14282     the function's canonical address.
14283
14284     Floating-point stubs are stored in unique .mips16.call.* or
14285     .mips16.fn.* sections.  If a stub T for function F is in section S,
14286     the first relocation in section S must be against F; this is how the
14287     linker determines the target function.  All relocations that might
14288     resolve to T must also be against F.  We therefore have the following
14289     restrictions, which are given in an intentionally-redundant way:
14290
14291       1. We cannot reduce R_MIPS16_26 relocations against non-MIPS16
14292	  symbols.
14293
14294       2. We cannot reduce a stub's relocations against non-MIPS16 symbols
14295	  if that stub might be used.
14296
14297       3. We cannot reduce non-R_MIPS16_26 relocations against MIPS16
14298	  symbols.
14299
14300       4. We cannot reduce a stub's relocations against MIPS16 symbols if
14301	  that stub might be used.
14302
14303     There is a further restriction:
14304
14305       5. We cannot reduce R_MIPS16_26 relocations against MIPS16 symbols
14306	  on targets with in-place addends; the relocation field cannot
14307	  encode the low bit.
14308
14309     For simplicity, we deal with (3)-(5) by not reducing _any_ relocation
14310     against a MIPS16 symbol.
14311
14312     We deal with (1)-(2) by saying that, if there's a R_MIPS16_26
14313     relocation against some symbol R, no relocation against R may be
14314     reduced.  (Note that this deals with (2) as well as (1) because
14315     relocations against global symbols will never be reduced on ELF
14316     targets.)  This approach is a little simpler than trying to detect
14317     stub sections, and gives the "all or nothing" per-symbol consistency
14318     that we have for MIPS16 symbols.  */
14319  if (IS_ELF
14320      && fixp->fx_subsy == NULL
14321      && (ELF_ST_IS_MIPS16 (S_GET_OTHER (fixp->fx_addsy))
14322	  || *symbol_get_tc (fixp->fx_addsy)))
14323    return 0;
14324#endif
14325
14326  return 1;
14327}
14328
14329/* Translate internal representation of relocation info to BFD target
14330   format.  */
14331
14332arelent **
14333tc_gen_reloc (asection *section ATTRIBUTE_UNUSED, fixS *fixp)
14334{
14335  static arelent *retval[4];
14336  arelent *reloc;
14337  bfd_reloc_code_real_type code;
14338
14339  memset (retval, 0, sizeof(retval));
14340  reloc = retval[0] = (arelent *) xcalloc (1, sizeof (arelent));
14341  reloc->sym_ptr_ptr = (asymbol **) xmalloc (sizeof (asymbol *));
14342  *reloc->sym_ptr_ptr = symbol_get_bfdsym (fixp->fx_addsy);
14343  reloc->address = fixp->fx_frag->fr_address + fixp->fx_where;
14344
14345  if (fixp->fx_pcrel)
14346    {
14347      gas_assert (fixp->fx_r_type == BFD_RELOC_16_PCREL_S2);
14348
14349      /* At this point, fx_addnumber is "symbol offset - pcrel address".
14350	 Relocations want only the symbol offset.  */
14351      reloc->addend = fixp->fx_addnumber + reloc->address;
14352      if (!IS_ELF)
14353	{
14354	  /* A gruesome hack which is a result of the gruesome gas
14355	     reloc handling.  What's worse, for COFF (as opposed to
14356	     ECOFF), we might need yet another copy of reloc->address.
14357	     See bfd_install_relocation.  */
14358	  reloc->addend += reloc->address;
14359	}
14360    }
14361  else
14362    reloc->addend = fixp->fx_addnumber;
14363
14364  /* Since the old MIPS ELF ABI uses Rel instead of Rela, encode the vtable
14365     entry to be used in the relocation's section offset.  */
14366  if (! HAVE_NEWABI && fixp->fx_r_type == BFD_RELOC_VTABLE_ENTRY)
14367    {
14368      reloc->address = reloc->addend;
14369      reloc->addend = 0;
14370    }
14371
14372  code = fixp->fx_r_type;
14373
14374  reloc->howto = bfd_reloc_type_lookup (stdoutput, code);
14375  if (reloc->howto == NULL)
14376    {
14377      as_bad_where (fixp->fx_file, fixp->fx_line,
14378		    _("Can not represent %s relocation in this object file format"),
14379		    bfd_get_reloc_code_name (code));
14380      retval[0] = NULL;
14381    }
14382
14383  return retval;
14384}
14385
14386/* Relax a machine dependent frag.  This returns the amount by which
14387   the current size of the frag should change.  */
14388
14389int
14390mips_relax_frag (asection *sec, fragS *fragp, long stretch)
14391{
14392  if (RELAX_BRANCH_P (fragp->fr_subtype))
14393    {
14394      offsetT old_var = fragp->fr_var;
14395
14396      fragp->fr_var = relaxed_branch_length (fragp, sec, TRUE);
14397
14398      return fragp->fr_var - old_var;
14399    }
14400
14401  if (! RELAX_MIPS16_P (fragp->fr_subtype))
14402    return 0;
14403
14404  if (mips16_extended_frag (fragp, NULL, stretch))
14405    {
14406      if (RELAX_MIPS16_EXTENDED (fragp->fr_subtype))
14407	return 0;
14408      fragp->fr_subtype = RELAX_MIPS16_MARK_EXTENDED (fragp->fr_subtype);
14409      return 2;
14410    }
14411  else
14412    {
14413      if (! RELAX_MIPS16_EXTENDED (fragp->fr_subtype))
14414	return 0;
14415      fragp->fr_subtype = RELAX_MIPS16_CLEAR_EXTENDED (fragp->fr_subtype);
14416      return -2;
14417    }
14418
14419  return 0;
14420}
14421
14422/* Convert a machine dependent frag.  */
14423
14424void
14425md_convert_frag (bfd *abfd ATTRIBUTE_UNUSED, segT asec, fragS *fragp)
14426{
14427  if (RELAX_BRANCH_P (fragp->fr_subtype))
14428    {
14429      bfd_byte *buf;
14430      unsigned long insn;
14431      expressionS exp;
14432      fixS *fixp;
14433
14434      buf = (bfd_byte *)fragp->fr_literal + fragp->fr_fix;
14435
14436      if (target_big_endian)
14437	insn = bfd_getb32 (buf);
14438      else
14439	insn = bfd_getl32 (buf);
14440
14441      if (!RELAX_BRANCH_TOOFAR (fragp->fr_subtype))
14442	{
14443	  /* We generate a fixup instead of applying it right now
14444	     because, if there are linker relaxations, we're going to
14445	     need the relocations.  */
14446	  exp.X_op = O_symbol;
14447	  exp.X_add_symbol = fragp->fr_symbol;
14448	  exp.X_add_number = fragp->fr_offset;
14449
14450	  fixp = fix_new_exp (fragp, buf - (bfd_byte *)fragp->fr_literal,
14451			      4, &exp, TRUE, BFD_RELOC_16_PCREL_S2);
14452	  fixp->fx_file = fragp->fr_file;
14453	  fixp->fx_line = fragp->fr_line;
14454
14455	  md_number_to_chars ((char *) buf, insn, 4);
14456	  buf += 4;
14457	}
14458      else
14459	{
14460	  int i;
14461
14462	  as_warn_where (fragp->fr_file, fragp->fr_line,
14463			 _("relaxed out-of-range branch into a jump"));
14464
14465	  if (RELAX_BRANCH_UNCOND (fragp->fr_subtype))
14466	    goto uncond;
14467
14468	  if (!RELAX_BRANCH_LIKELY (fragp->fr_subtype))
14469	    {
14470	      /* Reverse the branch.  */
14471	      switch ((insn >> 28) & 0xf)
14472		{
14473		case 4:
14474		  /* bc[0-3][tf]l? and bc1any[24][ft] instructions can
14475		     have the condition reversed by tweaking a single
14476		     bit, and their opcodes all have 0x4???????.  */
14477		  gas_assert ((insn & 0xf1000000) == 0x41000000);
14478		  insn ^= 0x00010000;
14479		  break;
14480
14481		case 0:
14482		  /* bltz	0x04000000	bgez	0x04010000
14483		     bltzal	0x04100000	bgezal	0x04110000  */
14484		  gas_assert ((insn & 0xfc0e0000) == 0x04000000);
14485		  insn ^= 0x00010000;
14486		  break;
14487
14488		case 1:
14489		  /* beq	0x10000000	bne	0x14000000
14490		     blez	0x18000000	bgtz	0x1c000000  */
14491		  insn ^= 0x04000000;
14492		  break;
14493
14494		default:
14495		  abort ();
14496		}
14497	    }
14498
14499	  if (RELAX_BRANCH_LINK (fragp->fr_subtype))
14500	    {
14501	      /* Clear the and-link bit.  */
14502	      gas_assert ((insn & 0xfc1c0000) == 0x04100000);
14503
14504	      /* bltzal		0x04100000	bgezal	0x04110000
14505		 bltzall	0x04120000	bgezall	0x04130000  */
14506	      insn &= ~0x00100000;
14507	    }
14508
14509	  /* Branch over the branch (if the branch was likely) or the
14510	     full jump (not likely case).  Compute the offset from the
14511	     current instruction to branch to.  */
14512	  if (RELAX_BRANCH_LIKELY (fragp->fr_subtype))
14513	    i = 16;
14514	  else
14515	    {
14516	      /* How many bytes in instructions we've already emitted?  */
14517	      i = buf - (bfd_byte *)fragp->fr_literal - fragp->fr_fix;
14518	      /* How many bytes in instructions from here to the end?  */
14519	      i = fragp->fr_var - i;
14520	    }
14521	  /* Convert to instruction count.  */
14522	  i >>= 2;
14523	  /* Branch counts from the next instruction.  */
14524	  i--;
14525	  insn |= i;
14526	  /* Branch over the jump.  */
14527	  md_number_to_chars ((char *) buf, insn, 4);
14528	  buf += 4;
14529
14530	  /* nop */
14531	  md_number_to_chars ((char *) buf, 0, 4);
14532	  buf += 4;
14533
14534	  if (RELAX_BRANCH_LIKELY (fragp->fr_subtype))
14535	    {
14536	      /* beql $0, $0, 2f */
14537	      insn = 0x50000000;
14538	      /* Compute the PC offset from the current instruction to
14539		 the end of the variable frag.  */
14540	      /* How many bytes in instructions we've already emitted?  */
14541	      i = buf - (bfd_byte *)fragp->fr_literal - fragp->fr_fix;
14542	      /* How many bytes in instructions from here to the end?  */
14543	      i = fragp->fr_var - i;
14544	      /* Convert to instruction count.  */
14545	      i >>= 2;
14546	      /* Don't decrement i, because we want to branch over the
14547		 delay slot.  */
14548
14549	      insn |= i;
14550	      md_number_to_chars ((char *) buf, insn, 4);
14551	      buf += 4;
14552
14553	      md_number_to_chars ((char *) buf, 0, 4);
14554	      buf += 4;
14555	    }
14556
14557	uncond:
14558	  if (mips_pic == NO_PIC)
14559	    {
14560	      /* j or jal.  */
14561	      insn = (RELAX_BRANCH_LINK (fragp->fr_subtype)
14562		      ? 0x0c000000 : 0x08000000);
14563	      exp.X_op = O_symbol;
14564	      exp.X_add_symbol = fragp->fr_symbol;
14565	      exp.X_add_number = fragp->fr_offset;
14566
14567	      fixp = fix_new_exp (fragp, buf - (bfd_byte *)fragp->fr_literal,
14568				  4, &exp, FALSE, BFD_RELOC_MIPS_JMP);
14569	      fixp->fx_file = fragp->fr_file;
14570	      fixp->fx_line = fragp->fr_line;
14571
14572	      md_number_to_chars ((char *) buf, insn, 4);
14573	      buf += 4;
14574	    }
14575	  else
14576	    {
14577	      /* lw/ld $at, <sym>($gp)  R_MIPS_GOT16 */
14578	      insn = HAVE_64BIT_ADDRESSES ? 0xdf810000 : 0x8f810000;
14579	      exp.X_op = O_symbol;
14580	      exp.X_add_symbol = fragp->fr_symbol;
14581	      exp.X_add_number = fragp->fr_offset;
14582
14583	      if (fragp->fr_offset)
14584		{
14585		  exp.X_add_symbol = make_expr_symbol (&exp);
14586		  exp.X_add_number = 0;
14587		}
14588
14589	      fixp = fix_new_exp (fragp, buf - (bfd_byte *)fragp->fr_literal,
14590				  4, &exp, FALSE, BFD_RELOC_MIPS_GOT16);
14591	      fixp->fx_file = fragp->fr_file;
14592	      fixp->fx_line = fragp->fr_line;
14593
14594	      md_number_to_chars ((char *) buf, insn, 4);
14595	      buf += 4;
14596
14597	      if (mips_opts.isa == ISA_MIPS1)
14598		{
14599		  /* nop */
14600		  md_number_to_chars ((char *) buf, 0, 4);
14601		  buf += 4;
14602		}
14603
14604	      /* d/addiu $at, $at, <sym>  R_MIPS_LO16 */
14605	      insn = HAVE_64BIT_ADDRESSES ? 0x64210000 : 0x24210000;
14606
14607	      fixp = fix_new_exp (fragp, buf - (bfd_byte *)fragp->fr_literal,
14608				  4, &exp, FALSE, BFD_RELOC_LO16);
14609	      fixp->fx_file = fragp->fr_file;
14610	      fixp->fx_line = fragp->fr_line;
14611
14612	      md_number_to_chars ((char *) buf, insn, 4);
14613	      buf += 4;
14614
14615	      /* j(al)r $at.  */
14616	      if (RELAX_BRANCH_LINK (fragp->fr_subtype))
14617		insn = 0x0020f809;
14618	      else
14619		insn = 0x00200008;
14620
14621	      md_number_to_chars ((char *) buf, insn, 4);
14622	      buf += 4;
14623	    }
14624	}
14625
14626      gas_assert (buf == (bfd_byte *)fragp->fr_literal
14627	      + fragp->fr_fix + fragp->fr_var);
14628
14629      fragp->fr_fix += fragp->fr_var;
14630
14631      return;
14632    }
14633
14634  if (RELAX_MIPS16_P (fragp->fr_subtype))
14635    {
14636      int type;
14637      const struct mips16_immed_operand *op;
14638      bfd_boolean small, ext;
14639      offsetT val;
14640      bfd_byte *buf;
14641      unsigned long insn;
14642      bfd_boolean use_extend;
14643      unsigned short extend;
14644
14645      type = RELAX_MIPS16_TYPE (fragp->fr_subtype);
14646      op = mips16_immed_operands;
14647      while (op->type != type)
14648	++op;
14649
14650      if (RELAX_MIPS16_EXTENDED (fragp->fr_subtype))
14651	{
14652	  small = FALSE;
14653	  ext = TRUE;
14654	}
14655      else
14656	{
14657	  small = TRUE;
14658	  ext = FALSE;
14659	}
14660
14661      resolve_symbol_value (fragp->fr_symbol);
14662      val = S_GET_VALUE (fragp->fr_symbol);
14663      if (op->pcrel)
14664	{
14665	  addressT addr;
14666
14667	  addr = fragp->fr_address + fragp->fr_fix;
14668
14669	  /* The rules for the base address of a PC relative reloc are
14670             complicated; see mips16_extended_frag.  */
14671	  if (type == 'p' || type == 'q')
14672	    {
14673	      addr += 2;
14674	      if (ext)
14675		addr += 2;
14676	      /* Ignore the low bit in the target, since it will be
14677                 set for a text label.  */
14678	      if ((val & 1) != 0)
14679		--val;
14680	    }
14681	  else if (RELAX_MIPS16_JAL_DSLOT (fragp->fr_subtype))
14682	    addr -= 4;
14683	  else if (RELAX_MIPS16_DSLOT (fragp->fr_subtype))
14684	    addr -= 2;
14685
14686	  addr &= ~ (addressT) ((1 << op->shift) - 1);
14687	  val -= addr;
14688
14689	  /* Make sure the section winds up with the alignment we have
14690             assumed.  */
14691	  if (op->shift > 0)
14692	    record_alignment (asec, op->shift);
14693	}
14694
14695      if (ext
14696	  && (RELAX_MIPS16_JAL_DSLOT (fragp->fr_subtype)
14697	      || RELAX_MIPS16_DSLOT (fragp->fr_subtype)))
14698	as_warn_where (fragp->fr_file, fragp->fr_line,
14699		       _("extended instruction in delay slot"));
14700
14701      buf = (bfd_byte *) (fragp->fr_literal + fragp->fr_fix);
14702
14703      if (target_big_endian)
14704	insn = bfd_getb16 (buf);
14705      else
14706	insn = bfd_getl16 (buf);
14707
14708      mips16_immed (fragp->fr_file, fragp->fr_line, type, val,
14709		    RELAX_MIPS16_USER_EXT (fragp->fr_subtype),
14710		    small, ext, &insn, &use_extend, &extend);
14711
14712      if (use_extend)
14713	{
14714	  md_number_to_chars ((char *) buf, 0xf000 | extend, 2);
14715	  fragp->fr_fix += 2;
14716	  buf += 2;
14717	}
14718
14719      md_number_to_chars ((char *) buf, insn, 2);
14720      fragp->fr_fix += 2;
14721      buf += 2;
14722    }
14723  else
14724    {
14725      int first, second;
14726      fixS *fixp;
14727
14728      first = RELAX_FIRST (fragp->fr_subtype);
14729      second = RELAX_SECOND (fragp->fr_subtype);
14730      fixp = (fixS *) fragp->fr_opcode;
14731
14732      /* Possibly emit a warning if we've chosen the longer option.  */
14733      if (((fragp->fr_subtype & RELAX_USE_SECOND) != 0)
14734	  == ((fragp->fr_subtype & RELAX_SECOND_LONGER) != 0))
14735	{
14736	  const char *msg = macro_warning (fragp->fr_subtype);
14737	  if (msg != 0)
14738	    as_warn_where (fragp->fr_file, fragp->fr_line, "%s", msg);
14739	}
14740
14741      /* Go through all the fixups for the first sequence.  Disable them
14742	 (by marking them as done) if we're going to use the second
14743	 sequence instead.  */
14744      while (fixp
14745	     && fixp->fx_frag == fragp
14746	     && fixp->fx_where < fragp->fr_fix - second)
14747	{
14748	  if (fragp->fr_subtype & RELAX_USE_SECOND)
14749	    fixp->fx_done = 1;
14750	  fixp = fixp->fx_next;
14751	}
14752
14753      /* Go through the fixups for the second sequence.  Disable them if
14754	 we're going to use the first sequence, otherwise adjust their
14755	 addresses to account for the relaxation.  */
14756      while (fixp && fixp->fx_frag == fragp)
14757	{
14758	  if (fragp->fr_subtype & RELAX_USE_SECOND)
14759	    fixp->fx_where -= first;
14760	  else
14761	    fixp->fx_done = 1;
14762	  fixp = fixp->fx_next;
14763	}
14764
14765      /* Now modify the frag contents.  */
14766      if (fragp->fr_subtype & RELAX_USE_SECOND)
14767	{
14768	  char *start;
14769
14770	  start = fragp->fr_literal + fragp->fr_fix - first - second;
14771	  memmove (start, start + first, second);
14772	  fragp->fr_fix -= first;
14773	}
14774      else
14775	fragp->fr_fix -= second;
14776    }
14777}
14778
14779#ifdef OBJ_ELF
14780
14781/* This function is called after the relocs have been generated.
14782   We've been storing mips16 text labels as odd.  Here we convert them
14783   back to even for the convenience of the debugger.  */
14784
14785void
14786mips_frob_file_after_relocs (void)
14787{
14788  asymbol **syms;
14789  unsigned int count, i;
14790
14791  if (!IS_ELF)
14792    return;
14793
14794  syms = bfd_get_outsymbols (stdoutput);
14795  count = bfd_get_symcount (stdoutput);
14796  for (i = 0; i < count; i++, syms++)
14797    {
14798      if (ELF_ST_IS_MIPS16 (elf_symbol (*syms)->internal_elf_sym.st_other)
14799	  && ((*syms)->value & 1) != 0)
14800	{
14801	  (*syms)->value &= ~1;
14802	  /* If the symbol has an odd size, it was probably computed
14803	     incorrectly, so adjust that as well.  */
14804	  if ((elf_symbol (*syms)->internal_elf_sym.st_size & 1) != 0)
14805	    ++elf_symbol (*syms)->internal_elf_sym.st_size;
14806	}
14807    }
14808}
14809
14810#endif
14811
14812/* This function is called whenever a label is defined, including fake
14813   labels instantiated off the dot special symbol.  It is used when
14814   handling branch delays; if a branch has a label, we assume we cannot
14815   move it.  This also bumps the value of the symbol by 1 in compressed
14816   code.  */
14817
14818void
14819mips_record_label (symbolS *sym)
14820{
14821  segment_info_type *si = seg_info (now_seg);
14822  struct insn_label_list *l;
14823
14824  if (free_insn_labels == NULL)
14825    l = (struct insn_label_list *) xmalloc (sizeof *l);
14826  else
14827    {
14828      l = free_insn_labels;
14829      free_insn_labels = l->next;
14830    }
14831
14832  l->label = sym;
14833  l->next = si->label_list;
14834  si->label_list = l;
14835}
14836
14837/* This function is called as tc_frob_label() whenever a label is defined
14838   and adds a DWARF-2 record we only want for true labels.  */
14839
14840void
14841mips_define_label (symbolS *sym)
14842{
14843  mips_record_label (sym);
14844#ifdef OBJ_ELF
14845  dwarf2_emit_label (sym);
14846#endif
14847}
14848
14849#if defined (OBJ_ELF) || defined (OBJ_MAYBE_ELF)
14850
14851/* Some special processing for a MIPS ELF file.  */
14852
14853void
14854mips_elf_final_processing (void)
14855{
14856  /* Write out the register information.  */
14857  if (mips_abi != N64_ABI)
14858    {
14859      Elf32_RegInfo s;
14860
14861      s.ri_gprmask = mips_gprmask;
14862      s.ri_cprmask[0] = mips_cprmask[0];
14863      s.ri_cprmask[1] = mips_cprmask[1];
14864      s.ri_cprmask[2] = mips_cprmask[2];
14865      s.ri_cprmask[3] = mips_cprmask[3];
14866      /* The gp_value field is set by the MIPS ELF backend.  */
14867
14868      bfd_mips_elf32_swap_reginfo_out (stdoutput, &s,
14869				       ((Elf32_External_RegInfo *)
14870					mips_regmask_frag));
14871    }
14872  else
14873    {
14874      Elf64_Internal_RegInfo s;
14875
14876      s.ri_gprmask = mips_gprmask;
14877      s.ri_pad = 0;
14878      s.ri_cprmask[0] = mips_cprmask[0];
14879      s.ri_cprmask[1] = mips_cprmask[1];
14880      s.ri_cprmask[2] = mips_cprmask[2];
14881      s.ri_cprmask[3] = mips_cprmask[3];
14882      /* The gp_value field is set by the MIPS ELF backend.  */
14883
14884      bfd_mips_elf64_swap_reginfo_out (stdoutput, &s,
14885				       ((Elf64_External_RegInfo *)
14886					mips_regmask_frag));
14887    }
14888
14889  /* Set the MIPS ELF flag bits.  FIXME: There should probably be some
14890     sort of BFD interface for this.  */
14891  if (mips_any_noreorder)
14892    elf_elfheader (stdoutput)->e_flags |= EF_MIPS_NOREORDER;
14893  if (mips_pic != NO_PIC)
14894    {
14895    elf_elfheader (stdoutput)->e_flags |= EF_MIPS_PIC;
14896      elf_elfheader (stdoutput)->e_flags |= EF_MIPS_CPIC;
14897    }
14898  if (mips_abicalls)
14899    elf_elfheader (stdoutput)->e_flags |= EF_MIPS_CPIC;
14900
14901  /* Set MIPS ELF flags for ASEs.  */
14902  /* We may need to define a new flag for DSP ASE, and set this flag when
14903     file_ase_dsp is true.  */
14904  /* Same for DSP R2.  */
14905  /* We may need to define a new flag for MT ASE, and set this flag when
14906     file_ase_mt is true.  */
14907  if (file_ase_mips16)
14908    elf_elfheader (stdoutput)->e_flags |= EF_MIPS_ARCH_ASE_M16;
14909#if 0 /* XXX FIXME */
14910  if (file_ase_mips3d)
14911    elf_elfheader (stdoutput)->e_flags |= ???;
14912#endif
14913  if (file_ase_mdmx)
14914    elf_elfheader (stdoutput)->e_flags |= EF_MIPS_ARCH_ASE_MDMX;
14915
14916  /* Set the MIPS ELF ABI flags.  */
14917  if (mips_abi == O32_ABI && USE_E_MIPS_ABI_O32)
14918    elf_elfheader (stdoutput)->e_flags |= E_MIPS_ABI_O32;
14919  else if (mips_abi == O64_ABI)
14920    elf_elfheader (stdoutput)->e_flags |= E_MIPS_ABI_O64;
14921  else if (mips_abi == EABI_ABI)
14922    {
14923      if (!file_mips_gp32)
14924	elf_elfheader (stdoutput)->e_flags |= E_MIPS_ABI_EABI64;
14925      else
14926	elf_elfheader (stdoutput)->e_flags |= E_MIPS_ABI_EABI32;
14927    }
14928  else if (mips_abi == N32_ABI)
14929    elf_elfheader (stdoutput)->e_flags |= EF_MIPS_ABI2;
14930
14931  /* Nothing to do for N64_ABI.  */
14932
14933  if (mips_32bitmode)
14934    elf_elfheader (stdoutput)->e_flags |= EF_MIPS_32BITMODE;
14935
14936#if 0 /* XXX FIXME */
14937  /* 32 bit code with 64 bit FP registers.  */
14938  if (!file_mips_fp32 && ABI_NEEDS_32BIT_REGS (mips_abi))
14939    elf_elfheader (stdoutput)->e_flags |= ???;
14940#endif
14941}
14942
14943#endif /* OBJ_ELF || OBJ_MAYBE_ELF */
14944
14945typedef struct proc {
14946  symbolS *func_sym;
14947  symbolS *func_end_sym;
14948  unsigned long reg_mask;
14949  unsigned long reg_offset;
14950  unsigned long fpreg_mask;
14951  unsigned long fpreg_offset;
14952  unsigned long frame_offset;
14953  unsigned long frame_reg;
14954  unsigned long pc_reg;
14955} procS;
14956
14957static procS cur_proc;
14958static procS *cur_proc_ptr;
14959static int numprocs;
14960
14961/* Implement NOP_OPCODE.  We encode a MIPS16 nop as "1" and a normal
14962   nop as "0".  */
14963
14964char
14965mips_nop_opcode (void)
14966{
14967  return seg_info (now_seg)->tc_segment_info_data.mips16;
14968}
14969
14970/* Fill in an rs_align_code fragment.  This only needs to do something
14971   for MIPS16 code, where 0 is not a nop.  */
14972
14973void
14974mips_handle_align (fragS *fragp)
14975{
14976  char *p;
14977  int bytes, size, excess;
14978  valueT opcode;
14979
14980  if (fragp->fr_type != rs_align_code)
14981    return;
14982
14983  p = fragp->fr_literal + fragp->fr_fix;
14984  if (*p)
14985    {
14986      opcode = mips16_nop_insn.insn_opcode;
14987      size = 2;
14988    }
14989  else
14990    {
14991      opcode = nop_insn.insn_opcode;
14992      size = 4;
14993    }
14994
14995  bytes = fragp->fr_next->fr_address - fragp->fr_address - fragp->fr_fix;
14996  excess = bytes % size;
14997  if (excess != 0)
14998    {
14999      /* If we're not inserting a whole number of instructions,
15000	 pad the end of the fixed part of the frag with zeros.  */
15001      memset (p, 0, excess);
15002      p += excess;
15003      fragp->fr_fix += excess;
15004    }
15005
15006  md_number_to_chars (p, opcode, size);
15007  fragp->fr_var = size;
15008}
15009
15010static void
15011md_obj_begin (void)
15012{
15013}
15014
15015static void
15016md_obj_end (void)
15017{
15018  /* Check for premature end, nesting errors, etc.  */
15019  if (cur_proc_ptr)
15020    as_warn (_("missing .end at end of assembly"));
15021}
15022
15023static long
15024get_number (void)
15025{
15026  int negative = 0;
15027  long val = 0;
15028
15029  if (*input_line_pointer == '-')
15030    {
15031      ++input_line_pointer;
15032      negative = 1;
15033    }
15034  if (!ISDIGIT (*input_line_pointer))
15035    as_bad (_("expected simple number"));
15036  if (input_line_pointer[0] == '0')
15037    {
15038      if (input_line_pointer[1] == 'x')
15039	{
15040	  input_line_pointer += 2;
15041	  while (ISXDIGIT (*input_line_pointer))
15042	    {
15043	      val <<= 4;
15044	      val |= hex_value (*input_line_pointer++);
15045	    }
15046	  return negative ? -val : val;
15047	}
15048      else
15049	{
15050	  ++input_line_pointer;
15051	  while (ISDIGIT (*input_line_pointer))
15052	    {
15053	      val <<= 3;
15054	      val |= *input_line_pointer++ - '0';
15055	    }
15056	  return negative ? -val : val;
15057	}
15058    }
15059  if (!ISDIGIT (*input_line_pointer))
15060    {
15061      printf (_(" *input_line_pointer == '%c' 0x%02x\n"),
15062	      *input_line_pointer, *input_line_pointer);
15063      as_warn (_("invalid number"));
15064      return -1;
15065    }
15066  while (ISDIGIT (*input_line_pointer))
15067    {
15068      val *= 10;
15069      val += *input_line_pointer++ - '0';
15070    }
15071  return negative ? -val : val;
15072}
15073
15074/* The .file directive; just like the usual .file directive, but there
15075   is an initial number which is the ECOFF file index.  In the non-ECOFF
15076   case .file implies DWARF-2.  */
15077
15078static void
15079s_mips_file (int x ATTRIBUTE_UNUSED)
15080{
15081  static int first_file_directive = 0;
15082
15083  if (ECOFF_DEBUGGING)
15084    {
15085      get_number ();
15086      s_app_file (0);
15087    }
15088  else
15089    {
15090      char *filename;
15091
15092      filename = dwarf2_directive_file (0);
15093
15094      /* Versions of GCC up to 3.1 start files with a ".file"
15095	 directive even for stabs output.  Make sure that this
15096	 ".file" is handled.  Note that you need a version of GCC
15097         after 3.1 in order to support DWARF-2 on MIPS.  */
15098      if (filename != NULL && ! first_file_directive)
15099	{
15100	  (void) new_logical_line (filename, -1);
15101	  s_app_file_string (filename, 0);
15102	}
15103      first_file_directive = 1;
15104    }
15105}
15106
15107/* The .loc directive, implying DWARF-2.  */
15108
15109static void
15110s_mips_loc (int x ATTRIBUTE_UNUSED)
15111{
15112  if (!ECOFF_DEBUGGING)
15113    dwarf2_directive_loc (0);
15114}
15115
15116/* The .end directive.  */
15117
15118static void
15119s_mips_end (int x ATTRIBUTE_UNUSED)
15120{
15121  symbolS *p;
15122
15123  /* Following functions need their own .frame and .cprestore directives.  */
15124  mips_frame_reg_valid = 0;
15125  mips_cprestore_valid = 0;
15126
15127  if (!is_end_of_line[(unsigned char) *input_line_pointer])
15128    {
15129      p = get_symbol ();
15130      demand_empty_rest_of_line ();
15131    }
15132  else
15133    p = NULL;
15134
15135  if ((bfd_get_section_flags (stdoutput, now_seg) & SEC_CODE) == 0)
15136    as_warn (_(".end not in text section"));
15137
15138  if (!cur_proc_ptr)
15139    {
15140      as_warn (_(".end directive without a preceding .ent directive."));
15141      demand_empty_rest_of_line ();
15142      return;
15143    }
15144
15145  if (p != NULL)
15146    {
15147      gas_assert (S_GET_NAME (p));
15148      if (strcmp (S_GET_NAME (p), S_GET_NAME (cur_proc_ptr->func_sym)))
15149	as_warn (_(".end symbol does not match .ent symbol."));
15150
15151      if (debug_type == DEBUG_STABS)
15152	stabs_generate_asm_endfunc (S_GET_NAME (p),
15153				    S_GET_NAME (p));
15154    }
15155  else
15156    as_warn (_(".end directive missing or unknown symbol"));
15157
15158#ifdef OBJ_ELF
15159  /* Create an expression to calculate the size of the function.  */
15160  if (p && cur_proc_ptr)
15161    {
15162      OBJ_SYMFIELD_TYPE *obj = symbol_get_obj (p);
15163      expressionS *exp = xmalloc (sizeof (expressionS));
15164
15165      obj->size = exp;
15166      exp->X_op = O_subtract;
15167      exp->X_add_symbol = symbol_temp_new_now ();
15168      exp->X_op_symbol = p;
15169      exp->X_add_number = 0;
15170
15171      cur_proc_ptr->func_end_sym = exp->X_add_symbol;
15172    }
15173
15174  /* Generate a .pdr section.  */
15175  if (IS_ELF && !ECOFF_DEBUGGING && mips_flag_pdr)
15176    {
15177      segT saved_seg = now_seg;
15178      subsegT saved_subseg = now_subseg;
15179      expressionS exp;
15180      char *fragp;
15181
15182#ifdef md_flush_pending_output
15183      md_flush_pending_output ();
15184#endif
15185
15186      gas_assert (pdr_seg);
15187      subseg_set (pdr_seg, 0);
15188
15189      /* Write the symbol.  */
15190      exp.X_op = O_symbol;
15191      exp.X_add_symbol = p;
15192      exp.X_add_number = 0;
15193      emit_expr (&exp, 4);
15194
15195      fragp = frag_more (7 * 4);
15196
15197      md_number_to_chars (fragp, cur_proc_ptr->reg_mask, 4);
15198      md_number_to_chars (fragp + 4, cur_proc_ptr->reg_offset, 4);
15199      md_number_to_chars (fragp + 8, cur_proc_ptr->fpreg_mask, 4);
15200      md_number_to_chars (fragp + 12, cur_proc_ptr->fpreg_offset, 4);
15201      md_number_to_chars (fragp + 16, cur_proc_ptr->frame_offset, 4);
15202      md_number_to_chars (fragp + 20, cur_proc_ptr->frame_reg, 4);
15203      md_number_to_chars (fragp + 24, cur_proc_ptr->pc_reg, 4);
15204
15205      subseg_set (saved_seg, saved_subseg);
15206    }
15207#endif /* OBJ_ELF */
15208
15209  cur_proc_ptr = NULL;
15210}
15211
15212/* The .aent and .ent directives.  */
15213
15214static void
15215s_mips_ent (int aent)
15216{
15217  symbolS *symbolP;
15218
15219  symbolP = get_symbol ();
15220  if (*input_line_pointer == ',')
15221    ++input_line_pointer;
15222  SKIP_WHITESPACE ();
15223  if (ISDIGIT (*input_line_pointer)
15224      || *input_line_pointer == '-')
15225    get_number ();
15226
15227  if ((bfd_get_section_flags (stdoutput, now_seg) & SEC_CODE) == 0)
15228    as_warn (_(".ent or .aent not in text section."));
15229
15230  if (!aent && cur_proc_ptr)
15231    as_warn (_("missing .end"));
15232
15233  if (!aent)
15234    {
15235      /* This function needs its own .frame and .cprestore directives.  */
15236      mips_frame_reg_valid = 0;
15237      mips_cprestore_valid = 0;
15238
15239      cur_proc_ptr = &cur_proc;
15240      memset (cur_proc_ptr, '\0', sizeof (procS));
15241
15242      cur_proc_ptr->func_sym = symbolP;
15243
15244      ++numprocs;
15245
15246      if (debug_type == DEBUG_STABS)
15247        stabs_generate_asm_func (S_GET_NAME (symbolP),
15248				 S_GET_NAME (symbolP));
15249    }
15250
15251  symbol_get_bfdsym (symbolP)->flags |= BSF_FUNCTION;
15252
15253  demand_empty_rest_of_line ();
15254}
15255
15256/* The .frame directive. If the mdebug section is present (IRIX 5 native)
15257   then ecoff.c (ecoff_directive_frame) is used. For embedded targets,
15258   s_mips_frame is used so that we can set the PDR information correctly.
15259   We can't use the ecoff routines because they make reference to the ecoff
15260   symbol table (in the mdebug section).  */
15261
15262static void
15263s_mips_frame (int ignore ATTRIBUTE_UNUSED)
15264{
15265#ifdef OBJ_ELF
15266  if (IS_ELF && !ECOFF_DEBUGGING)
15267    {
15268      long val;
15269
15270      if (cur_proc_ptr == (procS *) NULL)
15271	{
15272	  as_warn (_(".frame outside of .ent"));
15273	  demand_empty_rest_of_line ();
15274	  return;
15275	}
15276
15277      cur_proc_ptr->frame_reg = tc_get_register (1);
15278
15279      SKIP_WHITESPACE ();
15280      if (*input_line_pointer++ != ','
15281	  || get_absolute_expression_and_terminator (&val) != ',')
15282	{
15283	  as_warn (_("Bad .frame directive"));
15284	  --input_line_pointer;
15285	  demand_empty_rest_of_line ();
15286	  return;
15287	}
15288
15289      cur_proc_ptr->frame_offset = val;
15290      cur_proc_ptr->pc_reg = tc_get_register (0);
15291
15292      demand_empty_rest_of_line ();
15293    }
15294  else
15295#endif /* OBJ_ELF */
15296    s_ignore (ignore);
15297}
15298
15299/* The .fmask and .mask directives. If the mdebug section is present
15300   (IRIX 5 native) then ecoff.c (ecoff_directive_mask) is used. For
15301   embedded targets, s_mips_mask is used so that we can set the PDR
15302   information correctly. We can't use the ecoff routines because they
15303   make reference to the ecoff symbol table (in the mdebug section).  */
15304
15305static void
15306s_mips_mask (int reg_type)
15307{
15308#ifdef OBJ_ELF
15309  if (IS_ELF && !ECOFF_DEBUGGING)
15310    {
15311      long mask, off;
15312
15313      if (cur_proc_ptr == (procS *) NULL)
15314	{
15315	  as_warn (_(".mask/.fmask outside of .ent"));
15316	  demand_empty_rest_of_line ();
15317	  return;
15318	}
15319
15320      if (get_absolute_expression_and_terminator (&mask) != ',')
15321	{
15322	  as_warn (_("Bad .mask/.fmask directive"));
15323	  --input_line_pointer;
15324	  demand_empty_rest_of_line ();
15325	  return;
15326	}
15327
15328      off = get_absolute_expression ();
15329
15330      if (reg_type == 'F')
15331	{
15332	  cur_proc_ptr->fpreg_mask = mask;
15333	  cur_proc_ptr->fpreg_offset = off;
15334	}
15335      else
15336	{
15337	  cur_proc_ptr->reg_mask = mask;
15338	  cur_proc_ptr->reg_offset = off;
15339	}
15340
15341      demand_empty_rest_of_line ();
15342    }
15343  else
15344#endif /* OBJ_ELF */
15345    s_ignore (reg_type);
15346}
15347
15348/* A table describing all the processors gas knows about.  Names are
15349   matched in the order listed.
15350
15351   To ease comparison, please keep this table in the same order as
15352   gcc's mips_cpu_info_table[].  */
15353static const struct mips_cpu_info mips_cpu_info_table[] =
15354{
15355  /* Entries for generic ISAs */
15356  { "mips1",          MIPS_CPU_IS_ISA,		ISA_MIPS1,      CPU_R3000 },
15357  { "mips2",          MIPS_CPU_IS_ISA,		ISA_MIPS2,      CPU_R6000 },
15358  { "mips3",          MIPS_CPU_IS_ISA,		ISA_MIPS3,      CPU_R4000 },
15359  { "mips4",          MIPS_CPU_IS_ISA,		ISA_MIPS4,      CPU_R8000 },
15360  { "mips5",          MIPS_CPU_IS_ISA,		ISA_MIPS5,      CPU_MIPS5 },
15361  { "mips32",         MIPS_CPU_IS_ISA,		ISA_MIPS32,     CPU_MIPS32 },
15362  { "mips32r2",       MIPS_CPU_IS_ISA,		ISA_MIPS32R2,   CPU_MIPS32R2 },
15363  { "mips64",         MIPS_CPU_IS_ISA,		ISA_MIPS64,     CPU_MIPS64 },
15364  { "mips64r2",       MIPS_CPU_IS_ISA,		ISA_MIPS64R2,   CPU_MIPS64R2 },
15365
15366  /* MIPS I */
15367  { "r3000",          0,			ISA_MIPS1,      CPU_R3000 },
15368  { "r2000",          0,			ISA_MIPS1,      CPU_R3000 },
15369  { "r3900",          0,			ISA_MIPS1,      CPU_R3900 },
15370
15371  /* MIPS II */
15372  { "r6000",          0,			ISA_MIPS2,      CPU_R6000 },
15373
15374  /* MIPS III */
15375  { "r4000",          0,			ISA_MIPS3,      CPU_R4000 },
15376  { "r4010",          0,			ISA_MIPS2,      CPU_R4010 },
15377  { "vr4100",         0,			ISA_MIPS3,      CPU_VR4100 },
15378  { "vr4111",         0,			ISA_MIPS3,      CPU_R4111 },
15379  { "vr4120",         0,			ISA_MIPS3,      CPU_VR4120 },
15380  { "vr4130",         0,			ISA_MIPS3,      CPU_VR4120 },
15381  { "vr4181",         0,			ISA_MIPS3,      CPU_R4111 },
15382  { "vr4300",         0,			ISA_MIPS3,      CPU_R4300 },
15383  { "r4400",          0,			ISA_MIPS3,      CPU_R4400 },
15384  { "r4600",          0,			ISA_MIPS3,      CPU_R4600 },
15385  { "orion",          0,			ISA_MIPS3,      CPU_R4600 },
15386  { "r4650",          0,			ISA_MIPS3,      CPU_R4650 },
15387  /* ST Microelectronics Loongson 2E and 2F cores */
15388  { "loongson2e",     0,			ISA_MIPS3,   CPU_LOONGSON_2E },
15389  { "loongson2f",     0,			ISA_MIPS3,   CPU_LOONGSON_2F },
15390
15391  /* MIPS IV */
15392  { "r8000",          0,			ISA_MIPS4,      CPU_R8000 },
15393  { "r10000",         0,			ISA_MIPS4,      CPU_R10000 },
15394  { "r12000",         0,			ISA_MIPS4,      CPU_R12000 },
15395  { "r14000",         0,			ISA_MIPS4,      CPU_R14000 },
15396  { "r16000",         0,			ISA_MIPS4,      CPU_R16000 },
15397  { "vr5000",         0,			ISA_MIPS4,      CPU_R5000 },
15398  { "vr5400",         0,			ISA_MIPS4,      CPU_VR5400 },
15399  { "vr5500",         0,			ISA_MIPS4,      CPU_VR5500 },
15400  { "rm5200",         0,			ISA_MIPS4,      CPU_R5000 },
15401  { "rm5230",         0,			ISA_MIPS4,      CPU_R5000 },
15402  { "rm5231",         0,			ISA_MIPS4,      CPU_R5000 },
15403  { "rm5261",         0,			ISA_MIPS4,      CPU_R5000 },
15404  { "rm5721",         0,			ISA_MIPS4,      CPU_R5000 },
15405  { "rm7000",         0,			ISA_MIPS4,      CPU_RM7000 },
15406  { "rm9000",         0,			ISA_MIPS4,      CPU_RM9000 },
15407
15408  /* MIPS 32 */
15409  { "4kc",            0,			ISA_MIPS32,	CPU_MIPS32 },
15410  { "4km",            0,			ISA_MIPS32,	CPU_MIPS32 },
15411  { "4kp",            0,			ISA_MIPS32,	CPU_MIPS32 },
15412  { "4ksc",           MIPS_CPU_ASE_SMARTMIPS,	ISA_MIPS32,	CPU_MIPS32 },
15413
15414  /* MIPS 32 Release 2 */
15415  { "4kec",           0,			ISA_MIPS32R2,   CPU_MIPS32R2 },
15416  { "4kem",           0,			ISA_MIPS32R2,   CPU_MIPS32R2 },
15417  { "4kep",           0,			ISA_MIPS32R2,   CPU_MIPS32R2 },
15418  { "4ksd",           MIPS_CPU_ASE_SMARTMIPS,	ISA_MIPS32R2,   CPU_MIPS32R2 },
15419  { "m4k",            0,			ISA_MIPS32R2,   CPU_MIPS32R2 },
15420  { "m4kp",           0,			ISA_MIPS32R2,   CPU_MIPS32R2 },
15421  { "24kc",           0,			ISA_MIPS32R2,   CPU_MIPS32R2 },
15422  { "24kf2_1",        0,			ISA_MIPS32R2,   CPU_MIPS32R2 },
15423  { "24kf",           0,			ISA_MIPS32R2,   CPU_MIPS32R2 },
15424  { "24kf1_1",        0,			ISA_MIPS32R2,   CPU_MIPS32R2 },
15425  /* Deprecated forms of the above.  */
15426  { "24kfx",          0,			ISA_MIPS32R2,   CPU_MIPS32R2 },
15427  { "24kx",           0,			ISA_MIPS32R2,   CPU_MIPS32R2 },
15428  /* 24KE is a 24K with DSP ASE, other ASEs are optional.  */
15429  { "24kec",          MIPS_CPU_ASE_DSP,		ISA_MIPS32R2,	CPU_MIPS32R2 },
15430  { "24kef2_1",       MIPS_CPU_ASE_DSP,		ISA_MIPS32R2,	CPU_MIPS32R2 },
15431  { "24kef",          MIPS_CPU_ASE_DSP,		ISA_MIPS32R2,	CPU_MIPS32R2 },
15432  { "24kef1_1",       MIPS_CPU_ASE_DSP,		ISA_MIPS32R2,	CPU_MIPS32R2 },
15433  /* Deprecated forms of the above.  */
15434  { "24kefx",         MIPS_CPU_ASE_DSP,		ISA_MIPS32R2,	CPU_MIPS32R2 },
15435  { "24kex",          MIPS_CPU_ASE_DSP,		ISA_MIPS32R2,	CPU_MIPS32R2 },
15436  /* 34K is a 24K with DSP and MT ASE, other ASEs are optional.  */
15437  { "34kc",           MIPS_CPU_ASE_DSP | MIPS_CPU_ASE_MT,
15438						ISA_MIPS32R2,	CPU_MIPS32R2 },
15439  { "34kf2_1",        MIPS_CPU_ASE_DSP | MIPS_CPU_ASE_MT,
15440						ISA_MIPS32R2,	CPU_MIPS32R2 },
15441  { "34kf",           MIPS_CPU_ASE_DSP | MIPS_CPU_ASE_MT,
15442						ISA_MIPS32R2,	CPU_MIPS32R2 },
15443  { "34kf1_1",        MIPS_CPU_ASE_DSP | MIPS_CPU_ASE_MT,
15444						ISA_MIPS32R2,	CPU_MIPS32R2 },
15445  /* Deprecated forms of the above.  */
15446  { "34kfx",          MIPS_CPU_ASE_DSP | MIPS_CPU_ASE_MT,
15447						ISA_MIPS32R2,	CPU_MIPS32R2 },
15448  { "34kx",           MIPS_CPU_ASE_DSP | MIPS_CPU_ASE_MT,
15449						ISA_MIPS32R2,	CPU_MIPS32R2 },
15450  /* 74K with DSP and DSPR2 ASE, other ASEs are optional.  */
15451  { "74kc",           MIPS_CPU_ASE_DSP | MIPS_CPU_ASE_DSPR2,
15452						ISA_MIPS32R2,	CPU_MIPS32R2 },
15453  { "74kf2_1",        MIPS_CPU_ASE_DSP | MIPS_CPU_ASE_DSPR2,
15454						ISA_MIPS32R2,	CPU_MIPS32R2 },
15455  { "74kf",           MIPS_CPU_ASE_DSP | MIPS_CPU_ASE_DSPR2,
15456						ISA_MIPS32R2,	CPU_MIPS32R2 },
15457  { "74kf1_1",        MIPS_CPU_ASE_DSP | MIPS_CPU_ASE_DSPR2,
15458						ISA_MIPS32R2,	CPU_MIPS32R2 },
15459  { "74kf3_2",        MIPS_CPU_ASE_DSP | MIPS_CPU_ASE_DSPR2,
15460						ISA_MIPS32R2,	CPU_MIPS32R2 },
15461  /* Deprecated forms of the above.  */
15462  { "74kfx",          MIPS_CPU_ASE_DSP | MIPS_CPU_ASE_DSPR2,
15463						ISA_MIPS32R2,	CPU_MIPS32R2 },
15464  { "74kx",           MIPS_CPU_ASE_DSP | MIPS_CPU_ASE_DSPR2,
15465						ISA_MIPS32R2,	CPU_MIPS32R2 },
15466  /* 1004K cores are multiprocessor versions of the 34K.  */
15467  { "1004kc",         MIPS_CPU_ASE_DSP | MIPS_CPU_ASE_MT,
15468						ISA_MIPS32R2,	CPU_MIPS32R2 },
15469  { "1004kf2_1",      MIPS_CPU_ASE_DSP | MIPS_CPU_ASE_MT,
15470						ISA_MIPS32R2,	CPU_MIPS32R2 },
15471  { "1004kf",         MIPS_CPU_ASE_DSP | MIPS_CPU_ASE_MT,
15472						ISA_MIPS32R2,	CPU_MIPS32R2 },
15473  { "1004kf1_1",      MIPS_CPU_ASE_DSP | MIPS_CPU_ASE_MT,
15474						ISA_MIPS32R2,	CPU_MIPS32R2 },
15475
15476  /* MIPS 64 */
15477  { "5kc",            0,			ISA_MIPS64,	CPU_MIPS64 },
15478  { "5kf",            0,			ISA_MIPS64,	CPU_MIPS64 },
15479  { "20kc",           MIPS_CPU_ASE_MIPS3D,	ISA_MIPS64,	CPU_MIPS64 },
15480  { "25kf",           MIPS_CPU_ASE_MIPS3D,	ISA_MIPS64,     CPU_MIPS64 },
15481
15482  /* Broadcom SB-1 CPU core */
15483  { "sb1",            MIPS_CPU_ASE_MIPS3D | MIPS_CPU_ASE_MDMX,
15484						ISA_MIPS64,	CPU_SB1 },
15485  /* Broadcom SB-1A CPU core */
15486  { "sb1a",           MIPS_CPU_ASE_MIPS3D | MIPS_CPU_ASE_MDMX,
15487						ISA_MIPS64,	CPU_SB1 },
15488
15489  /* MIPS 64 Release 2 */
15490
15491  /* Cavium Networks Octeon CPU core */
15492  { "octeon",	      0,      ISA_MIPS64R2,   CPU_OCTEON },
15493
15494  /* RMI Xlr */
15495  { "xlr",	      0,      ISA_MIPS64,     CPU_XLR },
15496
15497  /* End marker */
15498  { NULL, 0, 0, 0 }
15499};
15500
15501
15502/* Return true if GIVEN is the same as CANONICAL, or if it is CANONICAL
15503   with a final "000" replaced by "k".  Ignore case.
15504
15505   Note: this function is shared between GCC and GAS.  */
15506
15507static bfd_boolean
15508mips_strict_matching_cpu_name_p (const char *canonical, const char *given)
15509{
15510  while (*given != 0 && TOLOWER (*given) == TOLOWER (*canonical))
15511    given++, canonical++;
15512
15513  return ((*given == 0 && *canonical == 0)
15514	  || (strcmp (canonical, "000") == 0 && strcasecmp (given, "k") == 0));
15515}
15516
15517
15518/* Return true if GIVEN matches CANONICAL, where GIVEN is a user-supplied
15519   CPU name.  We've traditionally allowed a lot of variation here.
15520
15521   Note: this function is shared between GCC and GAS.  */
15522
15523static bfd_boolean
15524mips_matching_cpu_name_p (const char *canonical, const char *given)
15525{
15526  /* First see if the name matches exactly, or with a final "000"
15527     turned into "k".  */
15528  if (mips_strict_matching_cpu_name_p (canonical, given))
15529    return TRUE;
15530
15531  /* If not, try comparing based on numerical designation alone.
15532     See if GIVEN is an unadorned number, or 'r' followed by a number.  */
15533  if (TOLOWER (*given) == 'r')
15534    given++;
15535  if (!ISDIGIT (*given))
15536    return FALSE;
15537
15538  /* Skip over some well-known prefixes in the canonical name,
15539     hoping to find a number there too.  */
15540  if (TOLOWER (canonical[0]) == 'v' && TOLOWER (canonical[1]) == 'r')
15541    canonical += 2;
15542  else if (TOLOWER (canonical[0]) == 'r' && TOLOWER (canonical[1]) == 'm')
15543    canonical += 2;
15544  else if (TOLOWER (canonical[0]) == 'r')
15545    canonical += 1;
15546
15547  return mips_strict_matching_cpu_name_p (canonical, given);
15548}
15549
15550
15551/* Parse an option that takes the name of a processor as its argument.
15552   OPTION is the name of the option and CPU_STRING is the argument.
15553   Return the corresponding processor enumeration if the CPU_STRING is
15554   recognized, otherwise report an error and return null.
15555
15556   A similar function exists in GCC.  */
15557
15558static const struct mips_cpu_info *
15559mips_parse_cpu (const char *option, const char *cpu_string)
15560{
15561  const struct mips_cpu_info *p;
15562
15563  /* 'from-abi' selects the most compatible architecture for the given
15564     ABI: MIPS I for 32-bit ABIs and MIPS III for 64-bit ABIs.  For the
15565     EABIs, we have to decide whether we're using the 32-bit or 64-bit
15566     version.  Look first at the -mgp options, if given, otherwise base
15567     the choice on MIPS_DEFAULT_64BIT.
15568
15569     Treat NO_ABI like the EABIs.  One reason to do this is that the
15570     plain 'mips' and 'mips64' configs have 'from-abi' as their default
15571     architecture.  This code picks MIPS I for 'mips' and MIPS III for
15572     'mips64', just as we did in the days before 'from-abi'.  */
15573  if (strcasecmp (cpu_string, "from-abi") == 0)
15574    {
15575      if (ABI_NEEDS_32BIT_REGS (mips_abi))
15576	return mips_cpu_info_from_isa (ISA_MIPS1);
15577
15578      if (ABI_NEEDS_64BIT_REGS (mips_abi))
15579	return mips_cpu_info_from_isa (ISA_MIPS3);
15580
15581      if (file_mips_gp32 >= 0)
15582	return mips_cpu_info_from_isa (file_mips_gp32 ? ISA_MIPS1 : ISA_MIPS3);
15583
15584      return mips_cpu_info_from_isa (MIPS_DEFAULT_64BIT
15585				     ? ISA_MIPS3
15586				     : ISA_MIPS1);
15587    }
15588
15589  /* 'default' has traditionally been a no-op.  Probably not very useful.  */
15590  if (strcasecmp (cpu_string, "default") == 0)
15591    return 0;
15592
15593  for (p = mips_cpu_info_table; p->name != 0; p++)
15594    if (mips_matching_cpu_name_p (p->name, cpu_string))
15595      return p;
15596
15597  as_bad (_("Bad value (%s) for %s"), cpu_string, option);
15598  return 0;
15599}
15600
15601/* Return the canonical processor information for ISA (a member of the
15602   ISA_MIPS* enumeration).  */
15603
15604static const struct mips_cpu_info *
15605mips_cpu_info_from_isa (int isa)
15606{
15607  int i;
15608
15609  for (i = 0; mips_cpu_info_table[i].name != NULL; i++)
15610    if ((mips_cpu_info_table[i].flags & MIPS_CPU_IS_ISA)
15611	&& isa == mips_cpu_info_table[i].isa)
15612      return (&mips_cpu_info_table[i]);
15613
15614  return NULL;
15615}
15616
15617static const struct mips_cpu_info *
15618mips_cpu_info_from_arch (int arch)
15619{
15620  int i;
15621
15622  for (i = 0; mips_cpu_info_table[i].name != NULL; i++)
15623    if (arch == mips_cpu_info_table[i].cpu)
15624      return (&mips_cpu_info_table[i]);
15625
15626  return NULL;
15627}
15628
15629static void
15630show (FILE *stream, const char *string, int *col_p, int *first_p)
15631{
15632  if (*first_p)
15633    {
15634      fprintf (stream, "%24s", "");
15635      *col_p = 24;
15636    }
15637  else
15638    {
15639      fprintf (stream, ", ");
15640      *col_p += 2;
15641    }
15642
15643  if (*col_p + strlen (string) > 72)
15644    {
15645      fprintf (stream, "\n%24s", "");
15646      *col_p = 24;
15647    }
15648
15649  fprintf (stream, "%s", string);
15650  *col_p += strlen (string);
15651
15652  *first_p = 0;
15653}
15654
15655void
15656md_show_usage (FILE *stream)
15657{
15658  int column, first;
15659  size_t i;
15660
15661  fprintf (stream, _("\
15662MIPS options:\n\
15663-EB			generate big endian output\n\
15664-EL			generate little endian output\n\
15665-g, -g2			do not remove unneeded NOPs or swap branches\n\
15666-G NUM			allow referencing objects up to NUM bytes\n\
15667			implicitly with the gp register [default 8]\n"));
15668  fprintf (stream, _("\
15669-mips1			generate MIPS ISA I instructions\n\
15670-mips2			generate MIPS ISA II instructions\n\
15671-mips3			generate MIPS ISA III instructions\n\
15672-mips4			generate MIPS ISA IV instructions\n\
15673-mips5                  generate MIPS ISA V instructions\n\
15674-mips32                 generate MIPS32 ISA instructions\n\
15675-mips32r2               generate MIPS32 release 2 ISA instructions\n\
15676-mips64                 generate MIPS64 ISA instructions\n\
15677-mips64r2               generate MIPS64 release 2 ISA instructions\n\
15678-march=CPU/-mtune=CPU	generate code/schedule for CPU, where CPU is one of:\n"));
15679
15680  first = 1;
15681
15682  for (i = 0; mips_cpu_info_table[i].name != NULL; i++)
15683    show (stream, mips_cpu_info_table[i].name, &column, &first);
15684  show (stream, "from-abi", &column, &first);
15685  fputc ('\n', stream);
15686
15687  fprintf (stream, _("\
15688-mCPU			equivalent to -march=CPU -mtune=CPU. Deprecated.\n\
15689-no-mCPU		don't generate code specific to CPU.\n\
15690			For -mCPU and -no-mCPU, CPU must be one of:\n"));
15691
15692  first = 1;
15693
15694  show (stream, "3900", &column, &first);
15695  show (stream, "4010", &column, &first);
15696  show (stream, "4100", &column, &first);
15697  show (stream, "4650", &column, &first);
15698  fputc ('\n', stream);
15699
15700  fprintf (stream, _("\
15701-mips16			generate mips16 instructions\n\
15702-no-mips16		do not generate mips16 instructions\n"));
15703  fprintf (stream, _("\
15704-msmartmips		generate smartmips instructions\n\
15705-mno-smartmips		do not generate smartmips instructions\n"));
15706  fprintf (stream, _("\
15707-mdsp			generate DSP instructions\n\
15708-mno-dsp		do not generate DSP instructions\n"));
15709  fprintf (stream, _("\
15710-mdspr2			generate DSP R2 instructions\n\
15711-mno-dspr2		do not generate DSP R2 instructions\n"));
15712  fprintf (stream, _("\
15713-mmt			generate MT instructions\n\
15714-mno-mt			do not generate MT instructions\n"));
15715  fprintf (stream, _("\
15716-mfix-loongson2f-jump	work around Loongson2F JUMP instructions\n\
15717-mfix-loongson2f-nop	work around Loongson2F NOP errata\n\
15718-mfix-loongson2f-btb	work around Loongson2F BTB errata\n\
15719-mfix-vr4120		work around certain VR4120 errata\n\
15720-mfix-vr4130		work around VR4130 mflo/mfhi errata\n\
15721-mfix-24k		insert a nop after ERET and DERET instructions\n\
15722-mfix-cn63xxp1		work around CN63XXP1 PREF errata\n\
15723-mgp32			use 32-bit GPRs, regardless of the chosen ISA\n\
15724-mfp32			use 32-bit FPRs, regardless of the chosen ISA\n\
15725-msym32			assume all symbols have 32-bit values\n\
15726-O0			remove unneeded NOPs, do not swap branches\n\
15727-O			remove unneeded NOPs and swap branches\n\
15728--trap, --no-break	trap exception on div by 0 and mult overflow\n\
15729--break, --no-trap	break exception on div by 0 and mult overflow\n"));
15730  fprintf (stream, _("\
15731-mhard-float		allow floating-point instructions\n\
15732-msoft-float		do not allow floating-point instructions\n\
15733-msingle-float		only allow 32-bit floating-point operations\n\
15734-mdouble-float		allow 32-bit and 64-bit floating-point operations\n\
15735--[no-]construct-floats [dis]allow floating point values to be constructed\n"
15736		     ));
15737#ifdef OBJ_ELF
15738  fprintf (stream, _("\
15739-KPIC, -call_shared	generate SVR4 position independent code\n\
15740-call_nonpic		generate non-PIC code that can operate with DSOs\n\
15741-mvxworks-pic		generate VxWorks position independent code\n\
15742-non_shared		do not generate code that can operate with DSOs\n\
15743-xgot			assume a 32 bit GOT\n\
15744-mpdr, -mno-pdr		enable/disable creation of .pdr sections\n\
15745-mshared, -mno-shared   disable/enable .cpload optimization for\n\
15746                        position dependent (non shared) code\n\
15747-mabi=ABI		create ABI conformant object file for:\n"));
15748
15749  first = 1;
15750
15751  show (stream, "32", &column, &first);
15752  show (stream, "o64", &column, &first);
15753  show (stream, "n32", &column, &first);
15754  show (stream, "64", &column, &first);
15755  show (stream, "eabi", &column, &first);
15756
15757  fputc ('\n', stream);
15758
15759  fprintf (stream, _("\
15760-32			create o32 ABI object file (default)\n\
15761-n32			create n32 ABI object file\n\
15762-64			create 64 ABI object file\n"));
15763#endif
15764}
15765
15766#ifdef TE_IRIX
15767enum dwarf2_format
15768mips_dwarf2_format (asection *sec ATTRIBUTE_UNUSED)
15769{
15770  if (HAVE_64BIT_SYMBOLS)
15771    return dwarf2_format_64bit_irix;
15772  else
15773    return dwarf2_format_32bit;
15774}
15775#endif
15776
15777int
15778mips_dwarf2_addr_size (void)
15779{
15780  if (HAVE_64BIT_OBJECTS)
15781    return 8;
15782  else
15783    return 4;
15784}
15785
15786/* Standard calling conventions leave the CFA at SP on entry.  */
15787void
15788mips_cfi_frame_initial_instructions (void)
15789{
15790  cfi_add_CFA_def_cfa_register (SP);
15791}
15792
15793int
15794tc_mips_regname_to_dw2regnum (char *regname)
15795{
15796  unsigned int regnum = -1;
15797  unsigned int reg;
15798
15799  if (reg_lookup (&regname, RTYPE_GP | RTYPE_NUM, &reg))
15800    regnum = reg;
15801
15802  return regnum;
15803}
15804